* gcc-interface/decl.c (gnat_to_gnu_field): Do not set the alignment
[official-gcc.git] / gcc / ada / sem_util.adb
blobea2379c3e1a72b5e2b4af7cb95fba991d4846643
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_Elab; use Sem_Elab;
57 with Sem_Eval; use Sem_Eval;
58 with Sem_Prag; use Sem_Prag;
59 with Sem_Res; use Sem_Res;
60 with Sem_Warn; use Sem_Warn;
61 with Sem_Type; use Sem_Type;
62 with Sinfo; use Sinfo;
63 with Sinput; use Sinput;
64 with Stand; use Stand;
65 with Style;
66 with Stringt; use Stringt;
67 with Targparm; use Targparm;
68 with Tbuild; use Tbuild;
69 with Ttypes; use Ttypes;
70 with Uname; use Uname;
72 with GNAT.HTable; use GNAT.HTable;
74 package body Sem_Util is
76 -----------------------
77 -- Local Subprograms --
78 -----------------------
80 function Build_Component_Subtype
81 (C : List_Id;
82 Loc : Source_Ptr;
83 T : Entity_Id) return Node_Id;
84 -- This function builds the subtype for Build_Actual_Subtype_Of_Component
85 -- and Build_Discriminal_Subtype_Of_Component. C is a list of constraints,
86 -- Loc is the source location, T is the original subtype.
88 function Has_Enabled_Property
89 (Item_Id : Entity_Id;
90 Property : Name_Id) return Boolean;
91 -- Subsidiary to routines Async_xxx_Enabled and Effective_xxx_Enabled.
92 -- Determine whether an abstract state or a variable denoted by entity
93 -- Item_Id has enabled property Property.
95 function Has_Null_Extension (T : Entity_Id) return Boolean;
96 -- T is a derived tagged type. Check whether the type extension is null.
97 -- If the parent type is fully initialized, T can be treated as such.
99 function Is_Fully_Initialized_Variant (Typ : Entity_Id) return Boolean;
100 -- Subsidiary to Is_Fully_Initialized_Type. For an unconstrained type
101 -- with discriminants whose default values are static, examine only the
102 -- components in the selected variant to determine whether all of them
103 -- have a default.
105 type Null_Status_Kind is
106 (Is_Null,
107 -- This value indicates that a subexpression is known to have a null
108 -- value at compile time.
110 Is_Non_Null,
111 -- This value indicates that a subexpression is known to have a non-null
112 -- value at compile time.
114 Unknown);
115 -- This value indicates that it cannot be determined at compile time
116 -- whether a subexpression yields a null or non-null value.
118 function Null_Status (N : Node_Id) return Null_Status_Kind;
119 -- Determine whether subexpression N of an access type yields a null value,
120 -- a non-null value, or the value cannot be determined at compile time. The
121 -- routine does not take simple flow diagnostics into account, it relies on
122 -- static facts such as the presence of null exclusions.
124 function Old_Requires_Transient_Scope (Id : Entity_Id) return Boolean;
125 function New_Requires_Transient_Scope (Id : Entity_Id) return Boolean;
126 -- ???We retain the old and new algorithms for Requires_Transient_Scope for
127 -- the time being. New_Requires_Transient_Scope is used by default; the
128 -- debug switch -gnatdQ can be used to do Old_Requires_Transient_Scope
129 -- instead. The intent is to use this temporarily to measure before/after
130 -- efficiency. Note: when this temporary code is removed, the documentation
131 -- of dQ in debug.adb should be removed.
133 procedure Results_Differ
134 (Id : Entity_Id;
135 Old_Val : Boolean;
136 New_Val : Boolean);
137 -- ???Debugging code. Called when the Old_Val and New_Val differ. This
138 -- routine will be removed eventially when New_Requires_Transient_Scope
139 -- becomes Requires_Transient_Scope and Old_Requires_Transient_Scope is
140 -- eliminated.
142 function Subprogram_Name (N : Node_Id) return String;
143 -- Return the fully qualified name of the enclosing subprogram for the
144 -- given node N, with file:line:col information appended, e.g.
145 -- "subp:file:line:col", corresponding to the source location of the
146 -- body of the subprogram.
148 ------------------------------
149 -- Abstract_Interface_List --
150 ------------------------------
152 function Abstract_Interface_List (Typ : Entity_Id) return List_Id is
153 Nod : Node_Id;
155 begin
156 if Is_Concurrent_Type (Typ) then
158 -- If we are dealing with a synchronized subtype, go to the base
159 -- type, whose declaration has the interface list.
161 -- Shouldn't this be Declaration_Node???
163 Nod := Parent (Base_Type (Typ));
165 if Nkind (Nod) = N_Full_Type_Declaration then
166 return Empty_List;
167 end if;
169 elsif Ekind (Typ) = E_Record_Type_With_Private then
170 if Nkind (Parent (Typ)) = N_Full_Type_Declaration then
171 Nod := Type_Definition (Parent (Typ));
173 elsif Nkind (Parent (Typ)) = N_Private_Type_Declaration then
174 if Present (Full_View (Typ))
175 and then
176 Nkind (Parent (Full_View (Typ))) = N_Full_Type_Declaration
177 then
178 Nod := Type_Definition (Parent (Full_View (Typ)));
180 -- If the full-view is not available we cannot do anything else
181 -- here (the source has errors).
183 else
184 return Empty_List;
185 end if;
187 -- Support for generic formals with interfaces is still missing ???
189 elsif Nkind (Parent (Typ)) = N_Formal_Type_Declaration then
190 return Empty_List;
192 else
193 pragma Assert
194 (Nkind (Parent (Typ)) = N_Private_Extension_Declaration);
195 Nod := Parent (Typ);
196 end if;
198 elsif Ekind (Typ) = E_Record_Subtype then
199 Nod := Type_Definition (Parent (Etype (Typ)));
201 elsif Ekind (Typ) = E_Record_Subtype_With_Private then
203 -- Recurse, because parent may still be a private extension. Also
204 -- note that the full view of the subtype or the full view of its
205 -- base type may (both) be unavailable.
207 return Abstract_Interface_List (Etype (Typ));
209 elsif Ekind (Typ) = E_Record_Type then
210 if Nkind (Parent (Typ)) = N_Formal_Type_Declaration then
211 Nod := Formal_Type_Definition (Parent (Typ));
212 else
213 Nod := Type_Definition (Parent (Typ));
214 end if;
216 -- Otherwise the type is of a kind which does not implement interfaces
218 else
219 return Empty_List;
220 end if;
222 return Interface_List (Nod);
223 end Abstract_Interface_List;
225 --------------------------------
226 -- Add_Access_Type_To_Process --
227 --------------------------------
229 procedure Add_Access_Type_To_Process (E : Entity_Id; A : Entity_Id) is
230 L : Elist_Id;
232 begin
233 Ensure_Freeze_Node (E);
234 L := Access_Types_To_Process (Freeze_Node (E));
236 if No (L) then
237 L := New_Elmt_List;
238 Set_Access_Types_To_Process (Freeze_Node (E), L);
239 end if;
241 Append_Elmt (A, L);
242 end Add_Access_Type_To_Process;
244 --------------------------
245 -- Add_Block_Identifier --
246 --------------------------
248 procedure Add_Block_Identifier (N : Node_Id; Id : out Entity_Id) is
249 Loc : constant Source_Ptr := Sloc (N);
251 begin
252 pragma Assert (Nkind (N) = N_Block_Statement);
254 -- The block already has a label, return its entity
256 if Present (Identifier (N)) then
257 Id := Entity (Identifier (N));
259 -- Create a new block label and set its attributes
261 else
262 Id := New_Internal_Entity (E_Block, Current_Scope, Loc, 'B');
263 Set_Etype (Id, Standard_Void_Type);
264 Set_Parent (Id, N);
266 Set_Identifier (N, New_Occurrence_Of (Id, Loc));
267 Set_Block_Node (Id, Identifier (N));
268 end if;
269 end Add_Block_Identifier;
271 ----------------------------
272 -- Add_Global_Declaration --
273 ----------------------------
275 procedure Add_Global_Declaration (N : Node_Id) is
276 Aux_Node : constant Node_Id := Aux_Decls_Node (Cunit (Current_Sem_Unit));
278 begin
279 if No (Declarations (Aux_Node)) then
280 Set_Declarations (Aux_Node, New_List);
281 end if;
283 Append_To (Declarations (Aux_Node), N);
284 Analyze (N);
285 end Add_Global_Declaration;
287 --------------------------------
288 -- Address_Integer_Convert_OK --
289 --------------------------------
291 function Address_Integer_Convert_OK (T1, T2 : Entity_Id) return Boolean is
292 begin
293 if Allow_Integer_Address
294 and then ((Is_Descendant_Of_Address (T1)
295 and then Is_Private_Type (T1)
296 and then Is_Integer_Type (T2))
297 or else
298 (Is_Descendant_Of_Address (T2)
299 and then Is_Private_Type (T2)
300 and then Is_Integer_Type (T1)))
301 then
302 return True;
303 else
304 return False;
305 end if;
306 end Address_Integer_Convert_OK;
308 -------------------
309 -- Address_Value --
310 -------------------
312 function Address_Value (N : Node_Id) return Node_Id is
313 Expr : Node_Id := N;
315 begin
316 loop
317 -- For constant, get constant expression
319 if Is_Entity_Name (Expr)
320 and then Ekind (Entity (Expr)) = E_Constant
321 then
322 Expr := Constant_Value (Entity (Expr));
324 -- For unchecked conversion, get result to convert
326 elsif Nkind (Expr) = N_Unchecked_Type_Conversion then
327 Expr := Expression (Expr);
329 -- For (common case) of To_Address call, get argument
331 elsif Nkind (Expr) = N_Function_Call
332 and then Is_Entity_Name (Name (Expr))
333 and then Is_RTE (Entity (Name (Expr)), RE_To_Address)
334 then
335 Expr := First (Parameter_Associations (Expr));
337 if Nkind (Expr) = N_Parameter_Association then
338 Expr := Explicit_Actual_Parameter (Expr);
339 end if;
341 -- We finally have the real expression
343 else
344 exit;
345 end if;
346 end loop;
348 return Expr;
349 end Address_Value;
351 -----------------
352 -- Addressable --
353 -----------------
355 -- For now, just 8/16/32/64
357 function Addressable (V : Uint) return Boolean is
358 begin
359 return V = Uint_8 or else
360 V = Uint_16 or else
361 V = Uint_32 or else
362 V = Uint_64;
363 end Addressable;
365 function Addressable (V : Int) return Boolean is
366 begin
367 return V = 8 or else
368 V = 16 or else
369 V = 32 or else
370 V = 64;
371 end Addressable;
373 ---------------------------------
374 -- Aggregate_Constraint_Checks --
375 ---------------------------------
377 procedure Aggregate_Constraint_Checks
378 (Exp : Node_Id;
379 Check_Typ : Entity_Id)
381 Exp_Typ : constant Entity_Id := Etype (Exp);
383 begin
384 if Raises_Constraint_Error (Exp) then
385 return;
386 end if;
388 -- Ada 2005 (AI-230): Generate a conversion to an anonymous access
389 -- component's type to force the appropriate accessibility checks.
391 -- Ada 2005 (AI-231): Generate conversion to the null-excluding type to
392 -- force the corresponding run-time check
394 if Is_Access_Type (Check_Typ)
395 and then Is_Local_Anonymous_Access (Check_Typ)
396 then
397 Rewrite (Exp, Convert_To (Check_Typ, Relocate_Node (Exp)));
398 Analyze_And_Resolve (Exp, Check_Typ);
399 Check_Unset_Reference (Exp);
400 end if;
402 -- What follows is really expansion activity, so check that expansion
403 -- is on and is allowed. In GNATprove mode, we also want check flags to
404 -- be added in the tree, so that the formal verification can rely on
405 -- those to be present. In GNATprove mode for formal verification, some
406 -- treatment typically only done during expansion needs to be performed
407 -- on the tree, but it should not be applied inside generics. Otherwise,
408 -- this breaks the name resolution mechanism for generic instances.
410 if not Expander_Active
411 and (Inside_A_Generic or not Full_Analysis or not GNATprove_Mode)
412 then
413 return;
414 end if;
416 if Is_Access_Type (Check_Typ)
417 and then Can_Never_Be_Null (Check_Typ)
418 and then not Can_Never_Be_Null (Exp_Typ)
419 then
420 Install_Null_Excluding_Check (Exp);
421 end if;
423 -- First check if we have to insert discriminant checks
425 if Has_Discriminants (Exp_Typ) then
426 Apply_Discriminant_Check (Exp, Check_Typ);
428 -- Next emit length checks for array aggregates
430 elsif Is_Array_Type (Exp_Typ) then
431 Apply_Length_Check (Exp, Check_Typ);
433 -- Finally emit scalar and string checks. If we are dealing with a
434 -- scalar literal we need to check by hand because the Etype of
435 -- literals is not necessarily correct.
437 elsif Is_Scalar_Type (Exp_Typ)
438 and then Compile_Time_Known_Value (Exp)
439 then
440 if Is_Out_Of_Range (Exp, Base_Type (Check_Typ)) then
441 Apply_Compile_Time_Constraint_Error
442 (Exp, "value not in range of}??", CE_Range_Check_Failed,
443 Ent => Base_Type (Check_Typ),
444 Typ => Base_Type (Check_Typ));
446 elsif Is_Out_Of_Range (Exp, Check_Typ) then
447 Apply_Compile_Time_Constraint_Error
448 (Exp, "value not in range of}??", CE_Range_Check_Failed,
449 Ent => Check_Typ,
450 Typ => Check_Typ);
452 elsif not Range_Checks_Suppressed (Check_Typ) then
453 Apply_Scalar_Range_Check (Exp, Check_Typ);
454 end if;
456 -- Verify that target type is also scalar, to prevent view anomalies
457 -- in instantiations.
459 elsif (Is_Scalar_Type (Exp_Typ)
460 or else Nkind (Exp) = N_String_Literal)
461 and then Is_Scalar_Type (Check_Typ)
462 and then Exp_Typ /= Check_Typ
463 then
464 if Is_Entity_Name (Exp)
465 and then Ekind (Entity (Exp)) = E_Constant
466 then
467 -- If expression is a constant, it is worthwhile checking whether
468 -- it is a bound of the type.
470 if (Is_Entity_Name (Type_Low_Bound (Check_Typ))
471 and then Entity (Exp) = Entity (Type_Low_Bound (Check_Typ)))
472 or else
473 (Is_Entity_Name (Type_High_Bound (Check_Typ))
474 and then Entity (Exp) = Entity (Type_High_Bound (Check_Typ)))
475 then
476 return;
478 else
479 Rewrite (Exp, Convert_To (Check_Typ, Relocate_Node (Exp)));
480 Analyze_And_Resolve (Exp, Check_Typ);
481 Check_Unset_Reference (Exp);
482 end if;
484 -- Could use a comment on this case ???
486 else
487 Rewrite (Exp, Convert_To (Check_Typ, Relocate_Node (Exp)));
488 Analyze_And_Resolve (Exp, Check_Typ);
489 Check_Unset_Reference (Exp);
490 end if;
492 end if;
493 end Aggregate_Constraint_Checks;
495 -----------------------
496 -- Alignment_In_Bits --
497 -----------------------
499 function Alignment_In_Bits (E : Entity_Id) return Uint is
500 begin
501 return Alignment (E) * System_Storage_Unit;
502 end Alignment_In_Bits;
504 --------------------------------------
505 -- All_Composite_Constraints_Static --
506 --------------------------------------
508 function All_Composite_Constraints_Static
509 (Constr : Node_Id) return Boolean
511 begin
512 if No (Constr) or else Error_Posted (Constr) then
513 return True;
514 end if;
516 case Nkind (Constr) is
517 when N_Subexpr =>
518 if Nkind (Constr) in N_Has_Entity
519 and then Present (Entity (Constr))
520 then
521 if Is_Type (Entity (Constr)) then
522 return
523 not Is_Discrete_Type (Entity (Constr))
524 or else Is_OK_Static_Subtype (Entity (Constr));
525 end if;
527 elsif Nkind (Constr) = N_Range then
528 return
529 Is_OK_Static_Expression (Low_Bound (Constr))
530 and then
531 Is_OK_Static_Expression (High_Bound (Constr));
533 elsif Nkind (Constr) = N_Attribute_Reference
534 and then Attribute_Name (Constr) = Name_Range
535 then
536 return
537 Is_OK_Static_Expression
538 (Type_Low_Bound (Etype (Prefix (Constr))))
539 and then
540 Is_OK_Static_Expression
541 (Type_High_Bound (Etype (Prefix (Constr))));
542 end if;
544 return
545 not Present (Etype (Constr)) -- previous error
546 or else not Is_Discrete_Type (Etype (Constr))
547 or else Is_OK_Static_Expression (Constr);
549 when N_Discriminant_Association =>
550 return All_Composite_Constraints_Static (Expression (Constr));
552 when N_Range_Constraint =>
553 return
554 All_Composite_Constraints_Static (Range_Expression (Constr));
556 when N_Index_Or_Discriminant_Constraint =>
557 declare
558 One_Cstr : Entity_Id;
559 begin
560 One_Cstr := First (Constraints (Constr));
561 while Present (One_Cstr) loop
562 if not All_Composite_Constraints_Static (One_Cstr) then
563 return False;
564 end if;
566 Next (One_Cstr);
567 end loop;
568 end;
570 return True;
572 when N_Subtype_Indication =>
573 return
574 All_Composite_Constraints_Static (Subtype_Mark (Constr))
575 and then
576 All_Composite_Constraints_Static (Constraint (Constr));
578 when others =>
579 raise Program_Error;
580 end case;
581 end All_Composite_Constraints_Static;
583 ------------------------
584 -- Append_Entity_Name --
585 ------------------------
587 procedure Append_Entity_Name (Buf : in out Bounded_String; E : Entity_Id) is
588 Temp : Bounded_String;
590 procedure Inner (E : Entity_Id);
591 -- Inner recursive routine, keep outer routine nonrecursive to ease
592 -- debugging when we get strange results from this routine.
594 -----------
595 -- Inner --
596 -----------
598 procedure Inner (E : Entity_Id) is
599 Scop : Node_Id;
601 begin
602 -- If entity has an internal name, skip by it, and print its scope.
603 -- Note that we strip a final R from the name before the test; this
604 -- is needed for some cases of instantiations.
606 declare
607 E_Name : Bounded_String;
609 begin
610 Append (E_Name, Chars (E));
612 if E_Name.Chars (E_Name.Length) = 'R' then
613 E_Name.Length := E_Name.Length - 1;
614 end if;
616 if Is_Internal_Name (E_Name) then
617 Inner (Scope (E));
618 return;
619 end if;
620 end;
622 Scop := Scope (E);
624 -- Just print entity name if its scope is at the outer level
626 if Scop = Standard_Standard then
627 null;
629 -- If scope comes from source, write scope and entity
631 elsif Comes_From_Source (Scop) then
632 Append_Entity_Name (Temp, Scop);
633 Append (Temp, '.');
635 -- If in wrapper package skip past it
637 elsif Present (Scop) and then Is_Wrapper_Package (Scop) then
638 Append_Entity_Name (Temp, Scope (Scop));
639 Append (Temp, '.');
641 -- Otherwise nothing to output (happens in unnamed block statements)
643 else
644 null;
645 end if;
647 -- Output the name
649 declare
650 E_Name : Bounded_String;
652 begin
653 Append_Unqualified_Decoded (E_Name, Chars (E));
655 -- Remove trailing upper-case letters from the name (useful for
656 -- dealing with some cases of internal names generated in the case
657 -- of references from within a generic).
659 while E_Name.Length > 1
660 and then E_Name.Chars (E_Name.Length) in 'A' .. 'Z'
661 loop
662 E_Name.Length := E_Name.Length - 1;
663 end loop;
665 -- Adjust casing appropriately (gets name from source if possible)
667 Adjust_Name_Case (E_Name, Sloc (E));
668 Append (Temp, E_Name);
669 end;
670 end Inner;
672 -- Start of processing for Append_Entity_Name
674 begin
675 Inner (E);
676 Append (Buf, Temp);
677 end Append_Entity_Name;
679 ---------------------------------
680 -- Append_Inherited_Subprogram --
681 ---------------------------------
683 procedure Append_Inherited_Subprogram (S : Entity_Id) is
684 Par : constant Entity_Id := Alias (S);
685 -- The parent subprogram
687 Scop : constant Entity_Id := Scope (Par);
688 -- The scope of definition of the parent subprogram
690 Typ : constant Entity_Id := Defining_Entity (Parent (S));
691 -- The derived type of which S is a primitive operation
693 Decl : Node_Id;
694 Next_E : Entity_Id;
696 begin
697 if Ekind (Current_Scope) = E_Package
698 and then In_Private_Part (Current_Scope)
699 and then Has_Private_Declaration (Typ)
700 and then Is_Tagged_Type (Typ)
701 and then Scop = Current_Scope
702 then
703 -- The inherited operation is available at the earliest place after
704 -- the derived type declaration ( RM 7.3.1 (6/1)). This is only
705 -- relevant for type extensions. If the parent operation appears
706 -- after the type extension, the operation is not visible.
708 Decl := First
709 (Visible_Declarations
710 (Package_Specification (Current_Scope)));
711 while Present (Decl) loop
712 if Nkind (Decl) = N_Private_Extension_Declaration
713 and then Defining_Entity (Decl) = Typ
714 then
715 if Sloc (Decl) > Sloc (Par) then
716 Next_E := Next_Entity (Par);
717 Set_Next_Entity (Par, S);
718 Set_Next_Entity (S, Next_E);
719 return;
721 else
722 exit;
723 end if;
724 end if;
726 Next (Decl);
727 end loop;
728 end if;
730 -- If partial view is not a type extension, or it appears before the
731 -- subprogram declaration, insert normally at end of entity list.
733 Append_Entity (S, Current_Scope);
734 end Append_Inherited_Subprogram;
736 -----------------------------------------
737 -- Apply_Compile_Time_Constraint_Error --
738 -----------------------------------------
740 procedure Apply_Compile_Time_Constraint_Error
741 (N : Node_Id;
742 Msg : String;
743 Reason : RT_Exception_Code;
744 Ent : Entity_Id := Empty;
745 Typ : Entity_Id := Empty;
746 Loc : Source_Ptr := No_Location;
747 Rep : Boolean := True;
748 Warn : Boolean := False)
750 Stat : constant Boolean := Is_Static_Expression (N);
751 R_Stat : constant Node_Id :=
752 Make_Raise_Constraint_Error (Sloc (N), Reason => Reason);
753 Rtyp : Entity_Id;
755 begin
756 if No (Typ) then
757 Rtyp := Etype (N);
758 else
759 Rtyp := Typ;
760 end if;
762 Discard_Node
763 (Compile_Time_Constraint_Error (N, Msg, Ent, Loc, Warn => Warn));
765 -- In GNATprove mode, do not replace the node with an exception raised.
766 -- In such a case, either the call to Compile_Time_Constraint_Error
767 -- issues an error which stops analysis, or it issues a warning in
768 -- a few cases where a suitable check flag is set for GNATprove to
769 -- generate a check message.
771 if not Rep or GNATprove_Mode then
772 return;
773 end if;
775 -- Now we replace the node by an N_Raise_Constraint_Error node
776 -- This does not need reanalyzing, so set it as analyzed now.
778 Rewrite (N, R_Stat);
779 Set_Analyzed (N, True);
781 Set_Etype (N, Rtyp);
782 Set_Raises_Constraint_Error (N);
784 -- Now deal with possible local raise handling
786 Possible_Local_Raise (N, Standard_Constraint_Error);
788 -- If the original expression was marked as static, the result is
789 -- still marked as static, but the Raises_Constraint_Error flag is
790 -- always set so that further static evaluation is not attempted.
792 if Stat then
793 Set_Is_Static_Expression (N);
794 end if;
795 end Apply_Compile_Time_Constraint_Error;
797 ---------------------------
798 -- Async_Readers_Enabled --
799 ---------------------------
801 function Async_Readers_Enabled (Id : Entity_Id) return Boolean is
802 begin
803 return Has_Enabled_Property (Id, Name_Async_Readers);
804 end Async_Readers_Enabled;
806 ---------------------------
807 -- Async_Writers_Enabled --
808 ---------------------------
810 function Async_Writers_Enabled (Id : Entity_Id) return Boolean is
811 begin
812 return Has_Enabled_Property (Id, Name_Async_Writers);
813 end Async_Writers_Enabled;
815 --------------------------------------
816 -- Available_Full_View_Of_Component --
817 --------------------------------------
819 function Available_Full_View_Of_Component (T : Entity_Id) return Boolean is
820 ST : constant Entity_Id := Scope (T);
821 SCT : constant Entity_Id := Scope (Component_Type (T));
822 begin
823 return In_Open_Scopes (ST)
824 and then In_Open_Scopes (SCT)
825 and then Scope_Depth (ST) >= Scope_Depth (SCT);
826 end Available_Full_View_Of_Component;
828 -------------------
829 -- Bad_Attribute --
830 -------------------
832 procedure Bad_Attribute
833 (N : Node_Id;
834 Nam : Name_Id;
835 Warn : Boolean := False)
837 begin
838 Error_Msg_Warn := Warn;
839 Error_Msg_N ("unrecognized attribute&<<", N);
841 -- Check for possible misspelling
843 Error_Msg_Name_1 := First_Attribute_Name;
844 while Error_Msg_Name_1 <= Last_Attribute_Name loop
845 if Is_Bad_Spelling_Of (Nam, Error_Msg_Name_1) then
846 Error_Msg_N -- CODEFIX
847 ("\possible misspelling of %<<", N);
848 exit;
849 end if;
851 Error_Msg_Name_1 := Error_Msg_Name_1 + 1;
852 end loop;
853 end Bad_Attribute;
855 --------------------------------
856 -- Bad_Predicated_Subtype_Use --
857 --------------------------------
859 procedure Bad_Predicated_Subtype_Use
860 (Msg : String;
861 N : Node_Id;
862 Typ : Entity_Id;
863 Suggest_Static : Boolean := False)
865 Gen : Entity_Id;
867 begin
868 -- Avoid cascaded errors
870 if Error_Posted (N) then
871 return;
872 end if;
874 if Inside_A_Generic then
875 Gen := Current_Scope;
876 while Present (Gen) and then Ekind (Gen) /= E_Generic_Package loop
877 Gen := Scope (Gen);
878 end loop;
880 if No (Gen) then
881 return;
882 end if;
884 if Is_Generic_Formal (Typ) and then Is_Discrete_Type (Typ) then
885 Set_No_Predicate_On_Actual (Typ);
886 end if;
888 elsif Has_Predicates (Typ) then
889 if Is_Generic_Actual_Type (Typ) then
891 -- The restriction on loop parameters is only that the type
892 -- should have no dynamic predicates.
894 if Nkind (Parent (N)) = N_Loop_Parameter_Specification
895 and then not Has_Dynamic_Predicate_Aspect (Typ)
896 and then Is_OK_Static_Subtype (Typ)
897 then
898 return;
899 end if;
901 Gen := Current_Scope;
902 while not Is_Generic_Instance (Gen) loop
903 Gen := Scope (Gen);
904 end loop;
906 pragma Assert (Present (Gen));
908 if Ekind (Gen) = E_Package and then In_Package_Body (Gen) then
909 Error_Msg_Warn := SPARK_Mode /= On;
910 Error_Msg_FE (Msg & "<<", N, Typ);
911 Error_Msg_F ("\Program_Error [<<", N);
913 Insert_Action (N,
914 Make_Raise_Program_Error (Sloc (N),
915 Reason => PE_Bad_Predicated_Generic_Type));
917 else
918 Error_Msg_FE (Msg & "<<", N, Typ);
919 end if;
921 else
922 Error_Msg_FE (Msg, N, Typ);
923 end if;
925 -- Emit an optional suggestion on how to remedy the error if the
926 -- context warrants it.
928 if Suggest_Static and then Has_Static_Predicate (Typ) then
929 Error_Msg_FE ("\predicate of & should be marked static", N, Typ);
930 end if;
931 end if;
932 end Bad_Predicated_Subtype_Use;
934 -----------------------------------------
935 -- Bad_Unordered_Enumeration_Reference --
936 -----------------------------------------
938 function Bad_Unordered_Enumeration_Reference
939 (N : Node_Id;
940 T : Entity_Id) return Boolean
942 begin
943 return Is_Enumeration_Type (T)
944 and then Warn_On_Unordered_Enumeration_Type
945 and then not Is_Generic_Type (T)
946 and then Comes_From_Source (N)
947 and then not Has_Pragma_Ordered (T)
948 and then not In_Same_Extended_Unit (N, T);
949 end Bad_Unordered_Enumeration_Reference;
951 ----------------------------
952 -- Begin_Keyword_Location --
953 ----------------------------
955 function Begin_Keyword_Location (N : Node_Id) return Source_Ptr is
956 HSS : Node_Id;
958 begin
959 pragma Assert (Nkind_In (N, N_Block_Statement,
960 N_Entry_Body,
961 N_Package_Body,
962 N_Subprogram_Body,
963 N_Task_Body));
965 HSS := Handled_Statement_Sequence (N);
967 -- When the handled sequence of statements comes from source, the
968 -- location of the "begin" keyword is that of the sequence itself.
969 -- Note that an internal construct may inherit a source sequence.
971 if Comes_From_Source (HSS) then
972 return Sloc (HSS);
974 -- The parser generates an internal handled sequence of statements to
975 -- capture the location of the "begin" keyword if present in the source.
976 -- Since there are no source statements, the location of the "begin"
977 -- keyword is effectively that of the "end" keyword.
979 elsif Comes_From_Source (N) then
980 return Sloc (HSS);
982 -- Otherwise the construct is internal and should carry the location of
983 -- the original construct which prompted its creation.
985 else
986 return Sloc (N);
987 end if;
988 end Begin_Keyword_Location;
990 --------------------------
991 -- Build_Actual_Subtype --
992 --------------------------
994 function Build_Actual_Subtype
995 (T : Entity_Id;
996 N : Node_Or_Entity_Id) return Node_Id
998 Loc : Source_Ptr;
999 -- Normally Sloc (N), but may point to corresponding body in some cases
1001 Constraints : List_Id;
1002 Decl : Node_Id;
1003 Discr : Entity_Id;
1004 Hi : Node_Id;
1005 Lo : Node_Id;
1006 Subt : Entity_Id;
1007 Disc_Type : Entity_Id;
1008 Obj : Node_Id;
1010 begin
1011 Loc := Sloc (N);
1013 if Nkind (N) = N_Defining_Identifier then
1014 Obj := New_Occurrence_Of (N, Loc);
1016 -- If this is a formal parameter of a subprogram declaration, and
1017 -- we are compiling the body, we want the declaration for the
1018 -- actual subtype to carry the source position of the body, to
1019 -- prevent anomalies in gdb when stepping through the code.
1021 if Is_Formal (N) then
1022 declare
1023 Decl : constant Node_Id := Unit_Declaration_Node (Scope (N));
1024 begin
1025 if Nkind (Decl) = N_Subprogram_Declaration
1026 and then Present (Corresponding_Body (Decl))
1027 then
1028 Loc := Sloc (Corresponding_Body (Decl));
1029 end if;
1030 end;
1031 end if;
1033 else
1034 Obj := N;
1035 end if;
1037 if Is_Array_Type (T) then
1038 Constraints := New_List;
1039 for J in 1 .. Number_Dimensions (T) loop
1041 -- Build an array subtype declaration with the nominal subtype and
1042 -- the bounds of the actual. Add the declaration in front of the
1043 -- local declarations for the subprogram, for analysis before any
1044 -- reference to the formal in the body.
1046 Lo :=
1047 Make_Attribute_Reference (Loc,
1048 Prefix =>
1049 Duplicate_Subexpr_No_Checks (Obj, Name_Req => True),
1050 Attribute_Name => Name_First,
1051 Expressions => New_List (
1052 Make_Integer_Literal (Loc, J)));
1054 Hi :=
1055 Make_Attribute_Reference (Loc,
1056 Prefix =>
1057 Duplicate_Subexpr_No_Checks (Obj, Name_Req => True),
1058 Attribute_Name => Name_Last,
1059 Expressions => New_List (
1060 Make_Integer_Literal (Loc, J)));
1062 Append (Make_Range (Loc, Lo, Hi), Constraints);
1063 end loop;
1065 -- If the type has unknown discriminants there is no constrained
1066 -- subtype to build. This is never called for a formal or for a
1067 -- lhs, so returning the type is ok ???
1069 elsif Has_Unknown_Discriminants (T) then
1070 return T;
1072 else
1073 Constraints := New_List;
1075 -- Type T is a generic derived type, inherit the discriminants from
1076 -- the parent type.
1078 if Is_Private_Type (T)
1079 and then No (Full_View (T))
1081 -- T was flagged as an error if it was declared as a formal
1082 -- derived type with known discriminants. In this case there
1083 -- is no need to look at the parent type since T already carries
1084 -- its own discriminants.
1086 and then not Error_Posted (T)
1087 then
1088 Disc_Type := Etype (Base_Type (T));
1089 else
1090 Disc_Type := T;
1091 end if;
1093 Discr := First_Discriminant (Disc_Type);
1094 while Present (Discr) loop
1095 Append_To (Constraints,
1096 Make_Selected_Component (Loc,
1097 Prefix =>
1098 Duplicate_Subexpr_No_Checks (Obj),
1099 Selector_Name => New_Occurrence_Of (Discr, Loc)));
1100 Next_Discriminant (Discr);
1101 end loop;
1102 end if;
1104 Subt := Make_Temporary (Loc, 'S', Related_Node => N);
1105 Set_Is_Internal (Subt);
1107 Decl :=
1108 Make_Subtype_Declaration (Loc,
1109 Defining_Identifier => Subt,
1110 Subtype_Indication =>
1111 Make_Subtype_Indication (Loc,
1112 Subtype_Mark => New_Occurrence_Of (T, Loc),
1113 Constraint =>
1114 Make_Index_Or_Discriminant_Constraint (Loc,
1115 Constraints => Constraints)));
1117 Mark_Rewrite_Insertion (Decl);
1118 return Decl;
1119 end Build_Actual_Subtype;
1121 ---------------------------------------
1122 -- Build_Actual_Subtype_Of_Component --
1123 ---------------------------------------
1125 function Build_Actual_Subtype_Of_Component
1126 (T : Entity_Id;
1127 N : Node_Id) return Node_Id
1129 Loc : constant Source_Ptr := Sloc (N);
1130 P : constant Node_Id := Prefix (N);
1131 D : Elmt_Id;
1132 Id : Node_Id;
1133 Index_Typ : Entity_Id;
1135 Desig_Typ : Entity_Id;
1136 -- This is either a copy of T, or if T is an access type, then it is
1137 -- the directly designated type of this access type.
1139 function Build_Actual_Array_Constraint return List_Id;
1140 -- If one or more of the bounds of the component depends on
1141 -- discriminants, build actual constraint using the discriminants
1142 -- of the prefix.
1144 function Build_Actual_Record_Constraint return List_Id;
1145 -- Similar to previous one, for discriminated components constrained
1146 -- by the discriminant of the enclosing object.
1148 -----------------------------------
1149 -- Build_Actual_Array_Constraint --
1150 -----------------------------------
1152 function Build_Actual_Array_Constraint return List_Id is
1153 Constraints : constant List_Id := New_List;
1154 Indx : Node_Id;
1155 Hi : Node_Id;
1156 Lo : Node_Id;
1157 Old_Hi : Node_Id;
1158 Old_Lo : Node_Id;
1160 begin
1161 Indx := First_Index (Desig_Typ);
1162 while Present (Indx) loop
1163 Old_Lo := Type_Low_Bound (Etype (Indx));
1164 Old_Hi := Type_High_Bound (Etype (Indx));
1166 if Denotes_Discriminant (Old_Lo) then
1167 Lo :=
1168 Make_Selected_Component (Loc,
1169 Prefix => New_Copy_Tree (P),
1170 Selector_Name => New_Occurrence_Of (Entity (Old_Lo), Loc));
1172 else
1173 Lo := New_Copy_Tree (Old_Lo);
1175 -- The new bound will be reanalyzed in the enclosing
1176 -- declaration. For literal bounds that come from a type
1177 -- declaration, the type of the context must be imposed, so
1178 -- insure that analysis will take place. For non-universal
1179 -- types this is not strictly necessary.
1181 Set_Analyzed (Lo, False);
1182 end if;
1184 if Denotes_Discriminant (Old_Hi) then
1185 Hi :=
1186 Make_Selected_Component (Loc,
1187 Prefix => New_Copy_Tree (P),
1188 Selector_Name => New_Occurrence_Of (Entity (Old_Hi), Loc));
1190 else
1191 Hi := New_Copy_Tree (Old_Hi);
1192 Set_Analyzed (Hi, False);
1193 end if;
1195 Append (Make_Range (Loc, Lo, Hi), Constraints);
1196 Next_Index (Indx);
1197 end loop;
1199 return Constraints;
1200 end Build_Actual_Array_Constraint;
1202 ------------------------------------
1203 -- Build_Actual_Record_Constraint --
1204 ------------------------------------
1206 function Build_Actual_Record_Constraint return List_Id is
1207 Constraints : constant List_Id := New_List;
1208 D : Elmt_Id;
1209 D_Val : Node_Id;
1211 begin
1212 D := First_Elmt (Discriminant_Constraint (Desig_Typ));
1213 while Present (D) loop
1214 if Denotes_Discriminant (Node (D)) then
1215 D_Val := Make_Selected_Component (Loc,
1216 Prefix => New_Copy_Tree (P),
1217 Selector_Name => New_Occurrence_Of (Entity (Node (D)), Loc));
1219 else
1220 D_Val := New_Copy_Tree (Node (D));
1221 end if;
1223 Append (D_Val, Constraints);
1224 Next_Elmt (D);
1225 end loop;
1227 return Constraints;
1228 end Build_Actual_Record_Constraint;
1230 -- Start of processing for Build_Actual_Subtype_Of_Component
1232 begin
1233 -- Why the test for Spec_Expression mode here???
1235 if In_Spec_Expression then
1236 return Empty;
1238 -- More comments for the rest of this body would be good ???
1240 elsif Nkind (N) = N_Explicit_Dereference then
1241 if Is_Composite_Type (T)
1242 and then not Is_Constrained (T)
1243 and then not (Is_Class_Wide_Type (T)
1244 and then Is_Constrained (Root_Type (T)))
1245 and then not Has_Unknown_Discriminants (T)
1246 then
1247 -- If the type of the dereference is already constrained, it is an
1248 -- actual subtype.
1250 if Is_Array_Type (Etype (N))
1251 and then Is_Constrained (Etype (N))
1252 then
1253 return Empty;
1254 else
1255 Remove_Side_Effects (P);
1256 return Build_Actual_Subtype (T, N);
1257 end if;
1258 else
1259 return Empty;
1260 end if;
1261 end if;
1263 if Ekind (T) = E_Access_Subtype then
1264 Desig_Typ := Designated_Type (T);
1265 else
1266 Desig_Typ := T;
1267 end if;
1269 if Ekind (Desig_Typ) = E_Array_Subtype then
1270 Id := First_Index (Desig_Typ);
1271 while Present (Id) loop
1272 Index_Typ := Underlying_Type (Etype (Id));
1274 if Denotes_Discriminant (Type_Low_Bound (Index_Typ))
1275 or else
1276 Denotes_Discriminant (Type_High_Bound (Index_Typ))
1277 then
1278 Remove_Side_Effects (P);
1279 return
1280 Build_Component_Subtype
1281 (Build_Actual_Array_Constraint, Loc, Base_Type (T));
1282 end if;
1284 Next_Index (Id);
1285 end loop;
1287 elsif Is_Composite_Type (Desig_Typ)
1288 and then Has_Discriminants (Desig_Typ)
1289 and then not Has_Unknown_Discriminants (Desig_Typ)
1290 then
1291 if Is_Private_Type (Desig_Typ)
1292 and then No (Discriminant_Constraint (Desig_Typ))
1293 then
1294 Desig_Typ := Full_View (Desig_Typ);
1295 end if;
1297 D := First_Elmt (Discriminant_Constraint (Desig_Typ));
1298 while Present (D) loop
1299 if Denotes_Discriminant (Node (D)) then
1300 Remove_Side_Effects (P);
1301 return
1302 Build_Component_Subtype (
1303 Build_Actual_Record_Constraint, Loc, Base_Type (T));
1304 end if;
1306 Next_Elmt (D);
1307 end loop;
1308 end if;
1310 -- If none of the above, the actual and nominal subtypes are the same
1312 return Empty;
1313 end Build_Actual_Subtype_Of_Component;
1315 ---------------------------------
1316 -- Build_Class_Wide_Clone_Body --
1317 ---------------------------------
1319 procedure Build_Class_Wide_Clone_Body
1320 (Spec_Id : Entity_Id;
1321 Bod : Node_Id)
1323 Loc : constant Source_Ptr := Sloc (Bod);
1324 Clone_Id : constant Entity_Id := Class_Wide_Clone (Spec_Id);
1325 Clone_Body : Node_Id;
1327 begin
1328 -- The declaration of the class-wide clone was created when the
1329 -- corresponding class-wide condition was analyzed.
1331 Clone_Body :=
1332 Make_Subprogram_Body (Loc,
1333 Specification =>
1334 Copy_Subprogram_Spec (Parent (Clone_Id)),
1335 Declarations => Declarations (Bod),
1336 Handled_Statement_Sequence => Handled_Statement_Sequence (Bod));
1338 -- The new operation is internal and overriding indicators do not apply
1339 -- (the original primitive may have carried one).
1341 Set_Must_Override (Specification (Clone_Body), False);
1342 Insert_Before (Bod, Clone_Body);
1343 Analyze (Clone_Body);
1344 end Build_Class_Wide_Clone_Body;
1346 ---------------------------------
1347 -- Build_Class_Wide_Clone_Call --
1348 ---------------------------------
1350 function Build_Class_Wide_Clone_Call
1351 (Loc : Source_Ptr;
1352 Decls : List_Id;
1353 Spec_Id : Entity_Id;
1354 Spec : Node_Id) return Node_Id
1356 Clone_Id : constant Entity_Id := Class_Wide_Clone (Spec_Id);
1357 Par_Type : constant Entity_Id := Find_Dispatching_Type (Spec_Id);
1359 Actuals : List_Id;
1360 Call : Node_Id;
1361 Formal : Entity_Id;
1362 New_Body : Node_Id;
1363 New_F_Spec : Entity_Id;
1364 New_Formal : Entity_Id;
1366 begin
1367 Actuals := Empty_List;
1368 Formal := First_Formal (Spec_Id);
1369 New_F_Spec := First (Parameter_Specifications (Spec));
1371 -- Build parameter association for call to class-wide clone.
1373 while Present (Formal) loop
1374 New_Formal := Defining_Identifier (New_F_Spec);
1376 -- If controlling argument and operation is inherited, add conversion
1377 -- to parent type for the call.
1379 if Etype (Formal) = Par_Type
1380 and then not Is_Empty_List (Decls)
1381 then
1382 Append_To (Actuals,
1383 Make_Type_Conversion (Loc,
1384 New_Occurrence_Of (Par_Type, Loc),
1385 New_Occurrence_Of (New_Formal, Loc)));
1387 else
1388 Append_To (Actuals, New_Occurrence_Of (New_Formal, Loc));
1389 end if;
1391 Next_Formal (Formal);
1392 Next (New_F_Spec);
1393 end loop;
1395 if Ekind (Spec_Id) = E_Procedure then
1396 Call :=
1397 Make_Procedure_Call_Statement (Loc,
1398 Name => New_Occurrence_Of (Clone_Id, Loc),
1399 Parameter_Associations => Actuals);
1400 else
1401 Call :=
1402 Make_Simple_Return_Statement (Loc,
1403 Expression =>
1404 Make_Function_Call (Loc,
1405 Name => New_Occurrence_Of (Clone_Id, Loc),
1406 Parameter_Associations => Actuals));
1407 end if;
1409 New_Body :=
1410 Make_Subprogram_Body (Loc,
1411 Specification =>
1412 Copy_Subprogram_Spec (Spec),
1413 Declarations => Decls,
1414 Handled_Statement_Sequence =>
1415 Make_Handled_Sequence_Of_Statements (Loc,
1416 Statements => New_List (Call),
1417 End_Label => Make_Identifier (Loc, Chars (Spec_Id))));
1419 return New_Body;
1420 end Build_Class_Wide_Clone_Call;
1422 ---------------------------------
1423 -- Build_Class_Wide_Clone_Decl --
1424 ---------------------------------
1426 procedure Build_Class_Wide_Clone_Decl (Spec_Id : Entity_Id) is
1427 Loc : constant Source_Ptr := Sloc (Spec_Id);
1428 Clone_Id : constant Entity_Id :=
1429 Make_Defining_Identifier (Loc,
1430 New_External_Name (Chars (Spec_Id), Suffix => "CL"));
1432 Decl : Node_Id;
1433 Spec : Node_Id;
1435 begin
1436 Spec := Copy_Subprogram_Spec (Parent (Spec_Id));
1437 Set_Must_Override (Spec, False);
1438 Set_Must_Not_Override (Spec, False);
1439 Set_Defining_Unit_Name (Spec, Clone_Id);
1441 Decl := Make_Subprogram_Declaration (Loc, Spec);
1442 Append (Decl, List_Containing (Unit_Declaration_Node (Spec_Id)));
1444 -- Link clone to original subprogram, for use when building body and
1445 -- wrapper call to inherited operation.
1447 Set_Class_Wide_Clone (Spec_Id, Clone_Id);
1448 end Build_Class_Wide_Clone_Decl;
1450 -----------------------------
1451 -- Build_Component_Subtype --
1452 -----------------------------
1454 function Build_Component_Subtype
1455 (C : List_Id;
1456 Loc : Source_Ptr;
1457 T : Entity_Id) return Node_Id
1459 Subt : Entity_Id;
1460 Decl : Node_Id;
1462 begin
1463 -- Unchecked_Union components do not require component subtypes
1465 if Is_Unchecked_Union (T) then
1466 return Empty;
1467 end if;
1469 Subt := Make_Temporary (Loc, 'S');
1470 Set_Is_Internal (Subt);
1472 Decl :=
1473 Make_Subtype_Declaration (Loc,
1474 Defining_Identifier => Subt,
1475 Subtype_Indication =>
1476 Make_Subtype_Indication (Loc,
1477 Subtype_Mark => New_Occurrence_Of (Base_Type (T), Loc),
1478 Constraint =>
1479 Make_Index_Or_Discriminant_Constraint (Loc,
1480 Constraints => C)));
1482 Mark_Rewrite_Insertion (Decl);
1483 return Decl;
1484 end Build_Component_Subtype;
1486 ---------------------------
1487 -- Build_Default_Subtype --
1488 ---------------------------
1490 function Build_Default_Subtype
1491 (T : Entity_Id;
1492 N : Node_Id) return Entity_Id
1494 Loc : constant Source_Ptr := Sloc (N);
1495 Disc : Entity_Id;
1497 Bas : Entity_Id;
1498 -- The base type that is to be constrained by the defaults
1500 begin
1501 if not Has_Discriminants (T) or else Is_Constrained (T) then
1502 return T;
1503 end if;
1505 Bas := Base_Type (T);
1507 -- If T is non-private but its base type is private, this is the
1508 -- completion of a subtype declaration whose parent type is private
1509 -- (see Complete_Private_Subtype in Sem_Ch3). The proper discriminants
1510 -- are to be found in the full view of the base. Check that the private
1511 -- status of T and its base differ.
1513 if Is_Private_Type (Bas)
1514 and then not Is_Private_Type (T)
1515 and then Present (Full_View (Bas))
1516 then
1517 Bas := Full_View (Bas);
1518 end if;
1520 Disc := First_Discriminant (T);
1522 if No (Discriminant_Default_Value (Disc)) then
1523 return T;
1524 end if;
1526 declare
1527 Act : constant Entity_Id := Make_Temporary (Loc, 'S');
1528 Constraints : constant List_Id := New_List;
1529 Decl : Node_Id;
1531 begin
1532 while Present (Disc) loop
1533 Append_To (Constraints,
1534 New_Copy_Tree (Discriminant_Default_Value (Disc)));
1535 Next_Discriminant (Disc);
1536 end loop;
1538 Decl :=
1539 Make_Subtype_Declaration (Loc,
1540 Defining_Identifier => Act,
1541 Subtype_Indication =>
1542 Make_Subtype_Indication (Loc,
1543 Subtype_Mark => New_Occurrence_Of (Bas, Loc),
1544 Constraint =>
1545 Make_Index_Or_Discriminant_Constraint (Loc,
1546 Constraints => Constraints)));
1548 Insert_Action (N, Decl);
1550 -- If the context is a component declaration the subtype declaration
1551 -- will be analyzed when the enclosing type is frozen, otherwise do
1552 -- it now.
1554 if Ekind (Current_Scope) /= E_Record_Type then
1555 Analyze (Decl);
1556 end if;
1558 return Act;
1559 end;
1560 end Build_Default_Subtype;
1562 --------------------------------------------
1563 -- Build_Discriminal_Subtype_Of_Component --
1564 --------------------------------------------
1566 function Build_Discriminal_Subtype_Of_Component
1567 (T : Entity_Id) return Node_Id
1569 Loc : constant Source_Ptr := Sloc (T);
1570 D : Elmt_Id;
1571 Id : Node_Id;
1573 function Build_Discriminal_Array_Constraint return List_Id;
1574 -- If one or more of the bounds of the component depends on
1575 -- discriminants, build actual constraint using the discriminants
1576 -- of the prefix.
1578 function Build_Discriminal_Record_Constraint return List_Id;
1579 -- Similar to previous one, for discriminated components constrained by
1580 -- the discriminant of the enclosing object.
1582 ----------------------------------------
1583 -- Build_Discriminal_Array_Constraint --
1584 ----------------------------------------
1586 function Build_Discriminal_Array_Constraint return List_Id is
1587 Constraints : constant List_Id := New_List;
1588 Indx : Node_Id;
1589 Hi : Node_Id;
1590 Lo : Node_Id;
1591 Old_Hi : Node_Id;
1592 Old_Lo : Node_Id;
1594 begin
1595 Indx := First_Index (T);
1596 while Present (Indx) loop
1597 Old_Lo := Type_Low_Bound (Etype (Indx));
1598 Old_Hi := Type_High_Bound (Etype (Indx));
1600 if Denotes_Discriminant (Old_Lo) then
1601 Lo := New_Occurrence_Of (Discriminal (Entity (Old_Lo)), Loc);
1603 else
1604 Lo := New_Copy_Tree (Old_Lo);
1605 end if;
1607 if Denotes_Discriminant (Old_Hi) then
1608 Hi := New_Occurrence_Of (Discriminal (Entity (Old_Hi)), Loc);
1610 else
1611 Hi := New_Copy_Tree (Old_Hi);
1612 end if;
1614 Append (Make_Range (Loc, Lo, Hi), Constraints);
1615 Next_Index (Indx);
1616 end loop;
1618 return Constraints;
1619 end Build_Discriminal_Array_Constraint;
1621 -----------------------------------------
1622 -- Build_Discriminal_Record_Constraint --
1623 -----------------------------------------
1625 function Build_Discriminal_Record_Constraint return List_Id is
1626 Constraints : constant List_Id := New_List;
1627 D : Elmt_Id;
1628 D_Val : Node_Id;
1630 begin
1631 D := First_Elmt (Discriminant_Constraint (T));
1632 while Present (D) loop
1633 if Denotes_Discriminant (Node (D)) then
1634 D_Val :=
1635 New_Occurrence_Of (Discriminal (Entity (Node (D))), Loc);
1636 else
1637 D_Val := New_Copy_Tree (Node (D));
1638 end if;
1640 Append (D_Val, Constraints);
1641 Next_Elmt (D);
1642 end loop;
1644 return Constraints;
1645 end Build_Discriminal_Record_Constraint;
1647 -- Start of processing for Build_Discriminal_Subtype_Of_Component
1649 begin
1650 if Ekind (T) = E_Array_Subtype then
1651 Id := First_Index (T);
1652 while Present (Id) loop
1653 if Denotes_Discriminant (Type_Low_Bound (Etype (Id)))
1654 or else
1655 Denotes_Discriminant (Type_High_Bound (Etype (Id)))
1656 then
1657 return Build_Component_Subtype
1658 (Build_Discriminal_Array_Constraint, Loc, T);
1659 end if;
1661 Next_Index (Id);
1662 end loop;
1664 elsif Ekind (T) = E_Record_Subtype
1665 and then Has_Discriminants (T)
1666 and then not Has_Unknown_Discriminants (T)
1667 then
1668 D := First_Elmt (Discriminant_Constraint (T));
1669 while Present (D) loop
1670 if Denotes_Discriminant (Node (D)) then
1671 return Build_Component_Subtype
1672 (Build_Discriminal_Record_Constraint, Loc, T);
1673 end if;
1675 Next_Elmt (D);
1676 end loop;
1677 end if;
1679 -- If none of the above, the actual and nominal subtypes are the same
1681 return Empty;
1682 end Build_Discriminal_Subtype_Of_Component;
1684 ------------------------------
1685 -- Build_Elaboration_Entity --
1686 ------------------------------
1688 procedure Build_Elaboration_Entity (N : Node_Id; Spec_Id : Entity_Id) is
1689 Loc : constant Source_Ptr := Sloc (N);
1690 Decl : Node_Id;
1691 Elab_Ent : Entity_Id;
1693 procedure Set_Package_Name (Ent : Entity_Id);
1694 -- Given an entity, sets the fully qualified name of the entity in
1695 -- Name_Buffer, with components separated by double underscores. This
1696 -- is a recursive routine that climbs the scope chain to Standard.
1698 ----------------------
1699 -- Set_Package_Name --
1700 ----------------------
1702 procedure Set_Package_Name (Ent : Entity_Id) is
1703 begin
1704 if Scope (Ent) /= Standard_Standard then
1705 Set_Package_Name (Scope (Ent));
1707 declare
1708 Nam : constant String := Get_Name_String (Chars (Ent));
1709 begin
1710 Name_Buffer (Name_Len + 1) := '_';
1711 Name_Buffer (Name_Len + 2) := '_';
1712 Name_Buffer (Name_Len + 3 .. Name_Len + Nam'Length + 2) := Nam;
1713 Name_Len := Name_Len + Nam'Length + 2;
1714 end;
1716 else
1717 Get_Name_String (Chars (Ent));
1718 end if;
1719 end Set_Package_Name;
1721 -- Start of processing for Build_Elaboration_Entity
1723 begin
1724 -- Ignore call if already constructed
1726 if Present (Elaboration_Entity (Spec_Id)) then
1727 return;
1729 -- Ignore in ASIS mode, elaboration entity is not in source and plays
1730 -- no role in analysis.
1732 elsif ASIS_Mode then
1733 return;
1735 -- Do not generate an elaboration entity in GNATprove move because the
1736 -- elaboration counter is a form of expansion.
1738 elsif GNATprove_Mode then
1739 return;
1741 -- See if we need elaboration entity
1743 -- We always need an elaboration entity when preserving control flow, as
1744 -- we want to remain explicit about the unit's elaboration order.
1746 elsif Opt.Suppress_Control_Flow_Optimizations then
1747 null;
1749 -- We always need an elaboration entity for the dynamic elaboration
1750 -- model, since it is needed to properly generate the PE exception for
1751 -- access before elaboration.
1753 elsif Dynamic_Elaboration_Checks then
1754 null;
1756 -- For the static model, we don't need the elaboration counter if this
1757 -- unit is sure to have no elaboration code, since that means there
1758 -- is no elaboration unit to be called. Note that we can't just decide
1759 -- after the fact by looking to see whether there was elaboration code,
1760 -- because that's too late to make this decision.
1762 elsif Restriction_Active (No_Elaboration_Code) then
1763 return;
1765 -- Similarly, for the static model, we can skip the elaboration counter
1766 -- if we have the No_Multiple_Elaboration restriction, since for the
1767 -- static model, that's the only purpose of the counter (to avoid
1768 -- multiple elaboration).
1770 elsif Restriction_Active (No_Multiple_Elaboration) then
1771 return;
1772 end if;
1774 -- Here we need the elaboration entity
1776 -- Construct name of elaboration entity as xxx_E, where xxx is the unit
1777 -- name with dots replaced by double underscore. We have to manually
1778 -- construct this name, since it will be elaborated in the outer scope,
1779 -- and thus will not have the unit name automatically prepended.
1781 Set_Package_Name (Spec_Id);
1782 Add_Str_To_Name_Buffer ("_E");
1784 -- Create elaboration counter
1786 Elab_Ent := Make_Defining_Identifier (Loc, Chars => Name_Find);
1787 Set_Elaboration_Entity (Spec_Id, Elab_Ent);
1789 Decl :=
1790 Make_Object_Declaration (Loc,
1791 Defining_Identifier => Elab_Ent,
1792 Object_Definition =>
1793 New_Occurrence_Of (Standard_Short_Integer, Loc),
1794 Expression => Make_Integer_Literal (Loc, Uint_0));
1796 Push_Scope (Standard_Standard);
1797 Add_Global_Declaration (Decl);
1798 Pop_Scope;
1800 -- Reset True_Constant indication, since we will indeed assign a value
1801 -- to the variable in the binder main. We also kill the Current_Value
1802 -- and Last_Assignment fields for the same reason.
1804 Set_Is_True_Constant (Elab_Ent, False);
1805 Set_Current_Value (Elab_Ent, Empty);
1806 Set_Last_Assignment (Elab_Ent, Empty);
1808 -- We do not want any further qualification of the name (if we did not
1809 -- do this, we would pick up the name of the generic package in the case
1810 -- of a library level generic instantiation).
1812 Set_Has_Qualified_Name (Elab_Ent);
1813 Set_Has_Fully_Qualified_Name (Elab_Ent);
1814 end Build_Elaboration_Entity;
1816 --------------------------------
1817 -- Build_Explicit_Dereference --
1818 --------------------------------
1820 procedure Build_Explicit_Dereference
1821 (Expr : Node_Id;
1822 Disc : Entity_Id)
1824 Loc : constant Source_Ptr := Sloc (Expr);
1825 I : Interp_Index;
1826 It : Interp;
1828 begin
1829 -- An entity of a type with a reference aspect is overloaded with
1830 -- both interpretations: with and without the dereference. Now that
1831 -- the dereference is made explicit, set the type of the node properly,
1832 -- to prevent anomalies in the backend. Same if the expression is an
1833 -- overloaded function call whose return type has a reference aspect.
1835 if Is_Entity_Name (Expr) then
1836 Set_Etype (Expr, Etype (Entity (Expr)));
1838 -- The designated entity will not be examined again when resolving
1839 -- the dereference, so generate a reference to it now.
1841 Generate_Reference (Entity (Expr), Expr);
1843 elsif Nkind (Expr) = N_Function_Call then
1845 -- If the name of the indexing function is overloaded, locate the one
1846 -- whose return type has an implicit dereference on the desired
1847 -- discriminant, and set entity and type of function call.
1849 if Is_Overloaded (Name (Expr)) then
1850 Get_First_Interp (Name (Expr), I, It);
1852 while Present (It.Nam) loop
1853 if Ekind ((It.Typ)) = E_Record_Type
1854 and then First_Entity ((It.Typ)) = Disc
1855 then
1856 Set_Entity (Name (Expr), It.Nam);
1857 Set_Etype (Name (Expr), Etype (It.Nam));
1858 exit;
1859 end if;
1861 Get_Next_Interp (I, It);
1862 end loop;
1863 end if;
1865 -- Set type of call from resolved function name.
1867 Set_Etype (Expr, Etype (Name (Expr)));
1868 end if;
1870 Set_Is_Overloaded (Expr, False);
1872 -- The expression will often be a generalized indexing that yields a
1873 -- container element that is then dereferenced, in which case the
1874 -- generalized indexing call is also non-overloaded.
1876 if Nkind (Expr) = N_Indexed_Component
1877 and then Present (Generalized_Indexing (Expr))
1878 then
1879 Set_Is_Overloaded (Generalized_Indexing (Expr), False);
1880 end if;
1882 Rewrite (Expr,
1883 Make_Explicit_Dereference (Loc,
1884 Prefix =>
1885 Make_Selected_Component (Loc,
1886 Prefix => Relocate_Node (Expr),
1887 Selector_Name => New_Occurrence_Of (Disc, Loc))));
1888 Set_Etype (Prefix (Expr), Etype (Disc));
1889 Set_Etype (Expr, Designated_Type (Etype (Disc)));
1890 end Build_Explicit_Dereference;
1892 ---------------------------
1893 -- Build_Overriding_Spec --
1894 ---------------------------
1896 function Build_Overriding_Spec
1897 (Op : Entity_Id;
1898 Typ : Entity_Id) return Node_Id
1900 Loc : constant Source_Ptr := Sloc (Typ);
1901 Par_Typ : constant Entity_Id := Find_Dispatching_Type (Op);
1902 Spec : constant Node_Id := Specification (Unit_Declaration_Node (Op));
1904 Formal_Spec : Node_Id;
1905 Formal_Type : Node_Id;
1906 New_Spec : Node_Id;
1908 begin
1909 New_Spec := Copy_Subprogram_Spec (Spec);
1911 Formal_Spec := First (Parameter_Specifications (New_Spec));
1912 while Present (Formal_Spec) loop
1913 Formal_Type := Parameter_Type (Formal_Spec);
1915 if Is_Entity_Name (Formal_Type)
1916 and then Entity (Formal_Type) = Par_Typ
1917 then
1918 Rewrite (Formal_Type, New_Occurrence_Of (Typ, Loc));
1919 end if;
1921 -- Nothing needs to be done for access parameters
1923 Next (Formal_Spec);
1924 end loop;
1926 return New_Spec;
1927 end Build_Overriding_Spec;
1929 -----------------------------------
1930 -- Cannot_Raise_Constraint_Error --
1931 -----------------------------------
1933 function Cannot_Raise_Constraint_Error (Expr : Node_Id) return Boolean is
1934 begin
1935 if Compile_Time_Known_Value (Expr) then
1936 return True;
1938 elsif Do_Range_Check (Expr) then
1939 return False;
1941 elsif Raises_Constraint_Error (Expr) then
1942 return False;
1944 else
1945 case Nkind (Expr) is
1946 when N_Identifier =>
1947 return True;
1949 when N_Expanded_Name =>
1950 return True;
1952 when N_Selected_Component =>
1953 return not Do_Discriminant_Check (Expr);
1955 when N_Attribute_Reference =>
1956 if Do_Overflow_Check (Expr) then
1957 return False;
1959 elsif No (Expressions (Expr)) then
1960 return True;
1962 else
1963 declare
1964 N : Node_Id;
1966 begin
1967 N := First (Expressions (Expr));
1968 while Present (N) loop
1969 if Cannot_Raise_Constraint_Error (N) then
1970 Next (N);
1971 else
1972 return False;
1973 end if;
1974 end loop;
1976 return True;
1977 end;
1978 end if;
1980 when N_Type_Conversion =>
1981 if Do_Overflow_Check (Expr)
1982 or else Do_Length_Check (Expr)
1983 or else Do_Tag_Check (Expr)
1984 then
1985 return False;
1986 else
1987 return Cannot_Raise_Constraint_Error (Expression (Expr));
1988 end if;
1990 when N_Unchecked_Type_Conversion =>
1991 return Cannot_Raise_Constraint_Error (Expression (Expr));
1993 when N_Unary_Op =>
1994 if Do_Overflow_Check (Expr) then
1995 return False;
1996 else
1997 return Cannot_Raise_Constraint_Error (Right_Opnd (Expr));
1998 end if;
2000 when N_Op_Divide
2001 | N_Op_Mod
2002 | N_Op_Rem
2004 if Do_Division_Check (Expr)
2005 or else
2006 Do_Overflow_Check (Expr)
2007 then
2008 return False;
2009 else
2010 return
2011 Cannot_Raise_Constraint_Error (Left_Opnd (Expr))
2012 and then
2013 Cannot_Raise_Constraint_Error (Right_Opnd (Expr));
2014 end if;
2016 when N_Op_Add
2017 | N_Op_And
2018 | N_Op_Concat
2019 | N_Op_Eq
2020 | N_Op_Expon
2021 | N_Op_Ge
2022 | N_Op_Gt
2023 | N_Op_Le
2024 | N_Op_Lt
2025 | N_Op_Multiply
2026 | N_Op_Ne
2027 | N_Op_Or
2028 | N_Op_Rotate_Left
2029 | N_Op_Rotate_Right
2030 | N_Op_Shift_Left
2031 | N_Op_Shift_Right
2032 | N_Op_Shift_Right_Arithmetic
2033 | N_Op_Subtract
2034 | N_Op_Xor
2036 if Do_Overflow_Check (Expr) then
2037 return False;
2038 else
2039 return
2040 Cannot_Raise_Constraint_Error (Left_Opnd (Expr))
2041 and then
2042 Cannot_Raise_Constraint_Error (Right_Opnd (Expr));
2043 end if;
2045 when others =>
2046 return False;
2047 end case;
2048 end if;
2049 end Cannot_Raise_Constraint_Error;
2051 -----------------------------------------
2052 -- Check_Dynamically_Tagged_Expression --
2053 -----------------------------------------
2055 procedure Check_Dynamically_Tagged_Expression
2056 (Expr : Node_Id;
2057 Typ : Entity_Id;
2058 Related_Nod : Node_Id)
2060 begin
2061 pragma Assert (Is_Tagged_Type (Typ));
2063 -- In order to avoid spurious errors when analyzing the expanded code,
2064 -- this check is done only for nodes that come from source and for
2065 -- actuals of generic instantiations.
2067 if (Comes_From_Source (Related_Nod)
2068 or else In_Generic_Actual (Expr))
2069 and then (Is_Class_Wide_Type (Etype (Expr))
2070 or else Is_Dynamically_Tagged (Expr))
2071 and then not Is_Class_Wide_Type (Typ)
2072 then
2073 Error_Msg_N ("dynamically tagged expression not allowed!", Expr);
2074 end if;
2075 end Check_Dynamically_Tagged_Expression;
2077 --------------------------
2078 -- Check_Fully_Declared --
2079 --------------------------
2081 procedure Check_Fully_Declared (T : Entity_Id; N : Node_Id) is
2082 begin
2083 if Ekind (T) = E_Incomplete_Type then
2085 -- Ada 2005 (AI-50217): If the type is available through a limited
2086 -- with_clause, verify that its full view has been analyzed.
2088 if From_Limited_With (T)
2089 and then Present (Non_Limited_View (T))
2090 and then Ekind (Non_Limited_View (T)) /= E_Incomplete_Type
2091 then
2092 -- The non-limited view is fully declared
2094 null;
2096 else
2097 Error_Msg_NE
2098 ("premature usage of incomplete}", N, First_Subtype (T));
2099 end if;
2101 -- Need comments for these tests ???
2103 elsif Has_Private_Component (T)
2104 and then not Is_Generic_Type (Root_Type (T))
2105 and then not In_Spec_Expression
2106 then
2107 -- Special case: if T is the anonymous type created for a single
2108 -- task or protected object, use the name of the source object.
2110 if Is_Concurrent_Type (T)
2111 and then not Comes_From_Source (T)
2112 and then Nkind (N) = N_Object_Declaration
2113 then
2114 Error_Msg_NE
2115 ("type of& has incomplete component",
2116 N, Defining_Identifier (N));
2117 else
2118 Error_Msg_NE
2119 ("premature usage of incomplete}",
2120 N, First_Subtype (T));
2121 end if;
2122 end if;
2123 end Check_Fully_Declared;
2125 -------------------------------------------
2126 -- Check_Function_With_Address_Parameter --
2127 -------------------------------------------
2129 procedure Check_Function_With_Address_Parameter (Subp_Id : Entity_Id) is
2130 F : Entity_Id;
2131 T : Entity_Id;
2133 begin
2134 F := First_Formal (Subp_Id);
2135 while Present (F) loop
2136 T := Etype (F);
2138 if Is_Private_Type (T) and then Present (Full_View (T)) then
2139 T := Full_View (T);
2140 end if;
2142 if Is_Descendant_Of_Address (T) or else Is_Limited_Type (T) then
2143 Set_Is_Pure (Subp_Id, False);
2144 exit;
2145 end if;
2147 Next_Formal (F);
2148 end loop;
2149 end Check_Function_With_Address_Parameter;
2151 -------------------------------------
2152 -- Check_Function_Writable_Actuals --
2153 -------------------------------------
2155 procedure Check_Function_Writable_Actuals (N : Node_Id) is
2156 Writable_Actuals_List : Elist_Id := No_Elist;
2157 Identifiers_List : Elist_Id := No_Elist;
2158 Aggr_Error_Node : Node_Id := Empty;
2159 Error_Node : Node_Id := Empty;
2161 procedure Collect_Identifiers (N : Node_Id);
2162 -- In a single traversal of subtree N collect in Writable_Actuals_List
2163 -- all the actuals of functions with writable actuals, and in the list
2164 -- Identifiers_List collect all the identifiers that are not actuals of
2165 -- functions with writable actuals. If a writable actual is referenced
2166 -- twice as writable actual then Error_Node is set to reference its
2167 -- second occurrence, the error is reported, and the tree traversal
2168 -- is abandoned.
2170 procedure Preanalyze_Without_Errors (N : Node_Id);
2171 -- Preanalyze N without reporting errors. Very dubious, you can't just
2172 -- go analyzing things more than once???
2174 -------------------------
2175 -- Collect_Identifiers --
2176 -------------------------
2178 procedure Collect_Identifiers (N : Node_Id) is
2180 function Check_Node (N : Node_Id) return Traverse_Result;
2181 -- Process a single node during the tree traversal to collect the
2182 -- writable actuals of functions and all the identifiers which are
2183 -- not writable actuals of functions.
2185 function Contains (List : Elist_Id; N : Node_Id) return Boolean;
2186 -- Returns True if List has a node whose Entity is Entity (N)
2188 ----------------
2189 -- Check_Node --
2190 ----------------
2192 function Check_Node (N : Node_Id) return Traverse_Result is
2193 Is_Writable_Actual : Boolean := False;
2194 Id : Entity_Id;
2196 begin
2197 if Nkind (N) = N_Identifier then
2199 -- No analysis possible if the entity is not decorated
2201 if No (Entity (N)) then
2202 return Skip;
2204 -- Don't collect identifiers of packages, called functions, etc
2206 elsif Ekind_In (Entity (N), E_Package,
2207 E_Function,
2208 E_Procedure,
2209 E_Entry)
2210 then
2211 return Skip;
2213 -- For rewritten nodes, continue the traversal in the original
2214 -- subtree. Needed to handle aggregates in original expressions
2215 -- extracted from the tree by Remove_Side_Effects.
2217 elsif Is_Rewrite_Substitution (N) then
2218 Collect_Identifiers (Original_Node (N));
2219 return Skip;
2221 -- For now we skip aggregate discriminants, since they require
2222 -- performing the analysis in two phases to identify conflicts:
2223 -- first one analyzing discriminants and second one analyzing
2224 -- the rest of components (since at run time, discriminants are
2225 -- evaluated prior to components): too much computation cost
2226 -- to identify a corner case???
2228 elsif Nkind (Parent (N)) = N_Component_Association
2229 and then Nkind_In (Parent (Parent (N)),
2230 N_Aggregate,
2231 N_Extension_Aggregate)
2232 then
2233 declare
2234 Choice : constant Node_Id := First (Choices (Parent (N)));
2236 begin
2237 if Ekind (Entity (N)) = E_Discriminant then
2238 return Skip;
2240 elsif Expression (Parent (N)) = N
2241 and then Nkind (Choice) = N_Identifier
2242 and then Ekind (Entity (Choice)) = E_Discriminant
2243 then
2244 return Skip;
2245 end if;
2246 end;
2248 -- Analyze if N is a writable actual of a function
2250 elsif Nkind (Parent (N)) = N_Function_Call then
2251 declare
2252 Call : constant Node_Id := Parent (N);
2253 Actual : Node_Id;
2254 Formal : Node_Id;
2256 begin
2257 Id := Get_Called_Entity (Call);
2259 -- In case of previous error, no check is possible
2261 if No (Id) then
2262 return Abandon;
2263 end if;
2265 if Ekind_In (Id, E_Function, E_Generic_Function)
2266 and then Has_Out_Or_In_Out_Parameter (Id)
2267 then
2268 Formal := First_Formal (Id);
2269 Actual := First_Actual (Call);
2270 while Present (Actual) and then Present (Formal) loop
2271 if Actual = N then
2272 if Ekind_In (Formal, E_Out_Parameter,
2273 E_In_Out_Parameter)
2274 then
2275 Is_Writable_Actual := True;
2276 end if;
2278 exit;
2279 end if;
2281 Next_Formal (Formal);
2282 Next_Actual (Actual);
2283 end loop;
2284 end if;
2285 end;
2286 end if;
2288 if Is_Writable_Actual then
2290 -- Skip checking the error in non-elementary types since
2291 -- RM 6.4.1(6.15/3) is restricted to elementary types, but
2292 -- store this actual in Writable_Actuals_List since it is
2293 -- needed to perform checks on other constructs that have
2294 -- arbitrary order of evaluation (for example, aggregates).
2296 if not Is_Elementary_Type (Etype (N)) then
2297 if not Contains (Writable_Actuals_List, N) then
2298 Append_New_Elmt (N, To => Writable_Actuals_List);
2299 end if;
2301 -- Second occurrence of an elementary type writable actual
2303 elsif Contains (Writable_Actuals_List, N) then
2305 -- Report the error on the second occurrence of the
2306 -- identifier. We cannot assume that N is the second
2307 -- occurrence (according to their location in the
2308 -- sources), since Traverse_Func walks through Field2
2309 -- last (see comment in the body of Traverse_Func).
2311 declare
2312 Elmt : Elmt_Id;
2314 begin
2315 Elmt := First_Elmt (Writable_Actuals_List);
2316 while Present (Elmt)
2317 and then Entity (Node (Elmt)) /= Entity (N)
2318 loop
2319 Next_Elmt (Elmt);
2320 end loop;
2322 if Sloc (N) > Sloc (Node (Elmt)) then
2323 Error_Node := N;
2324 else
2325 Error_Node := Node (Elmt);
2326 end if;
2328 Error_Msg_NE
2329 ("value may be affected by call to & "
2330 & "because order of evaluation is arbitrary",
2331 Error_Node, Id);
2332 return Abandon;
2333 end;
2335 -- First occurrence of a elementary type writable actual
2337 else
2338 Append_New_Elmt (N, To => Writable_Actuals_List);
2339 end if;
2341 else
2342 if Identifiers_List = No_Elist then
2343 Identifiers_List := New_Elmt_List;
2344 end if;
2346 Append_Unique_Elmt (N, Identifiers_List);
2347 end if;
2348 end if;
2350 return OK;
2351 end Check_Node;
2353 --------------
2354 -- Contains --
2355 --------------
2357 function Contains
2358 (List : Elist_Id;
2359 N : Node_Id) return Boolean
2361 pragma Assert (Nkind (N) in N_Has_Entity);
2363 Elmt : Elmt_Id;
2365 begin
2366 if List = No_Elist then
2367 return False;
2368 end if;
2370 Elmt := First_Elmt (List);
2371 while Present (Elmt) loop
2372 if Entity (Node (Elmt)) = Entity (N) then
2373 return True;
2374 else
2375 Next_Elmt (Elmt);
2376 end if;
2377 end loop;
2379 return False;
2380 end Contains;
2382 ------------------
2383 -- Do_Traversal --
2384 ------------------
2386 procedure Do_Traversal is new Traverse_Proc (Check_Node);
2387 -- The traversal procedure
2389 -- Start of processing for Collect_Identifiers
2391 begin
2392 if Present (Error_Node) then
2393 return;
2394 end if;
2396 if Nkind (N) in N_Subexpr and then Is_OK_Static_Expression (N) then
2397 return;
2398 end if;
2400 Do_Traversal (N);
2401 end Collect_Identifiers;
2403 -------------------------------
2404 -- Preanalyze_Without_Errors --
2405 -------------------------------
2407 procedure Preanalyze_Without_Errors (N : Node_Id) is
2408 Status : constant Boolean := Get_Ignore_Errors;
2409 begin
2410 Set_Ignore_Errors (True);
2411 Preanalyze (N);
2412 Set_Ignore_Errors (Status);
2413 end Preanalyze_Without_Errors;
2415 -- Start of processing for Check_Function_Writable_Actuals
2417 begin
2418 -- The check only applies to Ada 2012 code on which Check_Actuals has
2419 -- been set, and only to constructs that have multiple constituents
2420 -- whose order of evaluation is not specified by the language.
2422 if Ada_Version < Ada_2012
2423 or else not Check_Actuals (N)
2424 or else (not (Nkind (N) in N_Op)
2425 and then not (Nkind (N) in N_Membership_Test)
2426 and then not Nkind_In (N, N_Range,
2427 N_Aggregate,
2428 N_Extension_Aggregate,
2429 N_Full_Type_Declaration,
2430 N_Function_Call,
2431 N_Procedure_Call_Statement,
2432 N_Entry_Call_Statement))
2433 or else (Nkind (N) = N_Full_Type_Declaration
2434 and then not Is_Record_Type (Defining_Identifier (N)))
2436 -- In addition, this check only applies to source code, not to code
2437 -- generated by constraint checks.
2439 or else not Comes_From_Source (N)
2440 then
2441 return;
2442 end if;
2444 -- If a construct C has two or more direct constituents that are names
2445 -- or expressions whose evaluation may occur in an arbitrary order, at
2446 -- least one of which contains a function call with an in out or out
2447 -- parameter, then the construct is legal only if: for each name N that
2448 -- is passed as a parameter of mode in out or out to some inner function
2449 -- call C2 (not including the construct C itself), there is no other
2450 -- name anywhere within a direct constituent of the construct C other
2451 -- than the one containing C2, that is known to refer to the same
2452 -- object (RM 6.4.1(6.17/3)).
2454 case Nkind (N) is
2455 when N_Range =>
2456 Collect_Identifiers (Low_Bound (N));
2457 Collect_Identifiers (High_Bound (N));
2459 when N_Membership_Test
2460 | N_Op
2462 declare
2463 Expr : Node_Id;
2465 begin
2466 Collect_Identifiers (Left_Opnd (N));
2468 if Present (Right_Opnd (N)) then
2469 Collect_Identifiers (Right_Opnd (N));
2470 end if;
2472 if Nkind_In (N, N_In, N_Not_In)
2473 and then Present (Alternatives (N))
2474 then
2475 Expr := First (Alternatives (N));
2476 while Present (Expr) loop
2477 Collect_Identifiers (Expr);
2479 Next (Expr);
2480 end loop;
2481 end if;
2482 end;
2484 when N_Full_Type_Declaration =>
2485 declare
2486 function Get_Record_Part (N : Node_Id) return Node_Id;
2487 -- Return the record part of this record type definition
2489 function Get_Record_Part (N : Node_Id) return Node_Id is
2490 Type_Def : constant Node_Id := Type_Definition (N);
2491 begin
2492 if Nkind (Type_Def) = N_Derived_Type_Definition then
2493 return Record_Extension_Part (Type_Def);
2494 else
2495 return Type_Def;
2496 end if;
2497 end Get_Record_Part;
2499 Comp : Node_Id;
2500 Def_Id : Entity_Id := Defining_Identifier (N);
2501 Rec : Node_Id := Get_Record_Part (N);
2503 begin
2504 -- No need to perform any analysis if the record has no
2505 -- components
2507 if No (Rec) or else No (Component_List (Rec)) then
2508 return;
2509 end if;
2511 -- Collect the identifiers starting from the deepest
2512 -- derivation. Done to report the error in the deepest
2513 -- derivation.
2515 loop
2516 if Present (Component_List (Rec)) then
2517 Comp := First (Component_Items (Component_List (Rec)));
2518 while Present (Comp) loop
2519 if Nkind (Comp) = N_Component_Declaration
2520 and then Present (Expression (Comp))
2521 then
2522 Collect_Identifiers (Expression (Comp));
2523 end if;
2525 Next (Comp);
2526 end loop;
2527 end if;
2529 exit when No (Underlying_Type (Etype (Def_Id)))
2530 or else Base_Type (Underlying_Type (Etype (Def_Id)))
2531 = Def_Id;
2533 Def_Id := Base_Type (Underlying_Type (Etype (Def_Id)));
2534 Rec := Get_Record_Part (Parent (Def_Id));
2535 end loop;
2536 end;
2538 when N_Entry_Call_Statement
2539 | N_Subprogram_Call
2541 declare
2542 Id : constant Entity_Id := Get_Called_Entity (N);
2543 Formal : Node_Id;
2544 Actual : Node_Id;
2546 begin
2547 Formal := First_Formal (Id);
2548 Actual := First_Actual (N);
2549 while Present (Actual) and then Present (Formal) loop
2550 if Ekind_In (Formal, E_Out_Parameter,
2551 E_In_Out_Parameter)
2552 then
2553 Collect_Identifiers (Actual);
2554 end if;
2556 Next_Formal (Formal);
2557 Next_Actual (Actual);
2558 end loop;
2559 end;
2561 when N_Aggregate
2562 | N_Extension_Aggregate
2564 declare
2565 Assoc : Node_Id;
2566 Choice : Node_Id;
2567 Comp_Expr : Node_Id;
2569 begin
2570 -- Handle the N_Others_Choice of array aggregates with static
2571 -- bounds. There is no need to perform this analysis in
2572 -- aggregates without static bounds since we cannot evaluate
2573 -- if the N_Others_Choice covers several elements. There is
2574 -- no need to handle the N_Others choice of record aggregates
2575 -- since at this stage it has been already expanded by
2576 -- Resolve_Record_Aggregate.
2578 if Is_Array_Type (Etype (N))
2579 and then Nkind (N) = N_Aggregate
2580 and then Present (Aggregate_Bounds (N))
2581 and then Compile_Time_Known_Bounds (Etype (N))
2582 and then Expr_Value (High_Bound (Aggregate_Bounds (N)))
2584 Expr_Value (Low_Bound (Aggregate_Bounds (N)))
2585 then
2586 declare
2587 Count_Components : Uint := Uint_0;
2588 Num_Components : Uint;
2589 Others_Assoc : Node_Id;
2590 Others_Choice : Node_Id := Empty;
2591 Others_Box_Present : Boolean := False;
2593 begin
2594 -- Count positional associations
2596 if Present (Expressions (N)) then
2597 Comp_Expr := First (Expressions (N));
2598 while Present (Comp_Expr) loop
2599 Count_Components := Count_Components + 1;
2600 Next (Comp_Expr);
2601 end loop;
2602 end if;
2604 -- Count the rest of elements and locate the N_Others
2605 -- choice (if any)
2607 Assoc := First (Component_Associations (N));
2608 while Present (Assoc) loop
2609 Choice := First (Choices (Assoc));
2610 while Present (Choice) loop
2611 if Nkind (Choice) = N_Others_Choice then
2612 Others_Assoc := Assoc;
2613 Others_Choice := Choice;
2614 Others_Box_Present := Box_Present (Assoc);
2616 -- Count several components
2618 elsif Nkind_In (Choice, N_Range,
2619 N_Subtype_Indication)
2620 or else (Is_Entity_Name (Choice)
2621 and then Is_Type (Entity (Choice)))
2622 then
2623 declare
2624 L, H : Node_Id;
2625 begin
2626 Get_Index_Bounds (Choice, L, H);
2627 pragma Assert
2628 (Compile_Time_Known_Value (L)
2629 and then Compile_Time_Known_Value (H));
2630 Count_Components :=
2631 Count_Components
2632 + Expr_Value (H) - Expr_Value (L) + 1;
2633 end;
2635 -- Count single component. No other case available
2636 -- since we are handling an aggregate with static
2637 -- bounds.
2639 else
2640 pragma Assert (Is_OK_Static_Expression (Choice)
2641 or else Nkind (Choice) = N_Identifier
2642 or else Nkind (Choice) = N_Integer_Literal);
2644 Count_Components := Count_Components + 1;
2645 end if;
2647 Next (Choice);
2648 end loop;
2650 Next (Assoc);
2651 end loop;
2653 Num_Components :=
2654 Expr_Value (High_Bound (Aggregate_Bounds (N))) -
2655 Expr_Value (Low_Bound (Aggregate_Bounds (N))) + 1;
2657 pragma Assert (Count_Components <= Num_Components);
2659 -- Handle the N_Others choice if it covers several
2660 -- components
2662 if Present (Others_Choice)
2663 and then (Num_Components - Count_Components) > 1
2664 then
2665 if not Others_Box_Present then
2667 -- At this stage, if expansion is active, the
2668 -- expression of the others choice has not been
2669 -- analyzed. Hence we generate a duplicate and
2670 -- we analyze it silently to have available the
2671 -- minimum decoration required to collect the
2672 -- identifiers.
2674 if not Expander_Active then
2675 Comp_Expr := Expression (Others_Assoc);
2676 else
2677 Comp_Expr :=
2678 New_Copy_Tree (Expression (Others_Assoc));
2679 Preanalyze_Without_Errors (Comp_Expr);
2680 end if;
2682 Collect_Identifiers (Comp_Expr);
2684 if Writable_Actuals_List /= No_Elist then
2686 -- As suggested by Robert, at current stage we
2687 -- report occurrences of this case as warnings.
2689 Error_Msg_N
2690 ("writable function parameter may affect "
2691 & "value in other component because order "
2692 & "of evaluation is unspecified??",
2693 Node (First_Elmt (Writable_Actuals_List)));
2694 end if;
2695 end if;
2696 end if;
2697 end;
2699 -- For an array aggregate, a discrete_choice_list that has
2700 -- a nonstatic range is considered as two or more separate
2701 -- occurrences of the expression (RM 6.4.1(20/3)).
2703 elsif Is_Array_Type (Etype (N))
2704 and then Nkind (N) = N_Aggregate
2705 and then Present (Aggregate_Bounds (N))
2706 and then not Compile_Time_Known_Bounds (Etype (N))
2707 then
2708 -- Collect identifiers found in the dynamic bounds
2710 declare
2711 Count_Components : Natural := 0;
2712 Low, High : Node_Id;
2714 begin
2715 Assoc := First (Component_Associations (N));
2716 while Present (Assoc) loop
2717 Choice := First (Choices (Assoc));
2718 while Present (Choice) loop
2719 if Nkind_In (Choice, N_Range,
2720 N_Subtype_Indication)
2721 or else (Is_Entity_Name (Choice)
2722 and then Is_Type (Entity (Choice)))
2723 then
2724 Get_Index_Bounds (Choice, Low, High);
2726 if not Compile_Time_Known_Value (Low) then
2727 Collect_Identifiers (Low);
2729 if No (Aggr_Error_Node) then
2730 Aggr_Error_Node := Low;
2731 end if;
2732 end if;
2734 if not Compile_Time_Known_Value (High) then
2735 Collect_Identifiers (High);
2737 if No (Aggr_Error_Node) then
2738 Aggr_Error_Node := High;
2739 end if;
2740 end if;
2742 -- The RM rule is violated if there is more than
2743 -- a single choice in a component association.
2745 else
2746 Count_Components := Count_Components + 1;
2748 if No (Aggr_Error_Node)
2749 and then Count_Components > 1
2750 then
2751 Aggr_Error_Node := Choice;
2752 end if;
2754 if not Compile_Time_Known_Value (Choice) then
2755 Collect_Identifiers (Choice);
2756 end if;
2757 end if;
2759 Next (Choice);
2760 end loop;
2762 Next (Assoc);
2763 end loop;
2764 end;
2765 end if;
2767 -- Handle ancestor part of extension aggregates
2769 if Nkind (N) = N_Extension_Aggregate then
2770 Collect_Identifiers (Ancestor_Part (N));
2771 end if;
2773 -- Handle positional associations
2775 if Present (Expressions (N)) then
2776 Comp_Expr := First (Expressions (N));
2777 while Present (Comp_Expr) loop
2778 if not Is_OK_Static_Expression (Comp_Expr) then
2779 Collect_Identifiers (Comp_Expr);
2780 end if;
2782 Next (Comp_Expr);
2783 end loop;
2784 end if;
2786 -- Handle discrete associations
2788 if Present (Component_Associations (N)) then
2789 Assoc := First (Component_Associations (N));
2790 while Present (Assoc) loop
2792 if not Box_Present (Assoc) then
2793 Choice := First (Choices (Assoc));
2794 while Present (Choice) loop
2796 -- For now we skip discriminants since it requires
2797 -- performing the analysis in two phases: first one
2798 -- analyzing discriminants and second one analyzing
2799 -- the rest of components since discriminants are
2800 -- evaluated prior to components: too much extra
2801 -- work to detect a corner case???
2803 if Nkind (Choice) in N_Has_Entity
2804 and then Present (Entity (Choice))
2805 and then Ekind (Entity (Choice)) = E_Discriminant
2806 then
2807 null;
2809 elsif Box_Present (Assoc) then
2810 null;
2812 else
2813 if not Analyzed (Expression (Assoc)) then
2814 Comp_Expr :=
2815 New_Copy_Tree (Expression (Assoc));
2816 Set_Parent (Comp_Expr, Parent (N));
2817 Preanalyze_Without_Errors (Comp_Expr);
2818 else
2819 Comp_Expr := Expression (Assoc);
2820 end if;
2822 Collect_Identifiers (Comp_Expr);
2823 end if;
2825 Next (Choice);
2826 end loop;
2827 end if;
2829 Next (Assoc);
2830 end loop;
2831 end if;
2832 end;
2834 when others =>
2835 return;
2836 end case;
2838 -- No further action needed if we already reported an error
2840 if Present (Error_Node) then
2841 return;
2842 end if;
2844 -- Check violation of RM 6.20/3 in aggregates
2846 if Present (Aggr_Error_Node)
2847 and then Writable_Actuals_List /= No_Elist
2848 then
2849 Error_Msg_N
2850 ("value may be affected by call in other component because they "
2851 & "are evaluated in unspecified order",
2852 Node (First_Elmt (Writable_Actuals_List)));
2853 return;
2854 end if;
2856 -- Check if some writable argument of a function is referenced
2858 if Writable_Actuals_List /= No_Elist
2859 and then Identifiers_List /= No_Elist
2860 then
2861 declare
2862 Elmt_1 : Elmt_Id;
2863 Elmt_2 : Elmt_Id;
2865 begin
2866 Elmt_1 := First_Elmt (Writable_Actuals_List);
2867 while Present (Elmt_1) loop
2868 Elmt_2 := First_Elmt (Identifiers_List);
2869 while Present (Elmt_2) loop
2870 if Entity (Node (Elmt_1)) = Entity (Node (Elmt_2)) then
2871 case Nkind (Parent (Node (Elmt_2))) is
2872 when N_Aggregate
2873 | N_Component_Association
2874 | N_Component_Declaration
2876 Error_Msg_N
2877 ("value may be affected by call in other "
2878 & "component because they are evaluated "
2879 & "in unspecified order",
2880 Node (Elmt_2));
2882 when N_In
2883 | N_Not_In
2885 Error_Msg_N
2886 ("value may be affected by call in other "
2887 & "alternative because they are evaluated "
2888 & "in unspecified order",
2889 Node (Elmt_2));
2891 when others =>
2892 Error_Msg_N
2893 ("value of actual may be affected by call in "
2894 & "other actual because they are evaluated "
2895 & "in unspecified order",
2896 Node (Elmt_2));
2897 end case;
2898 end if;
2900 Next_Elmt (Elmt_2);
2901 end loop;
2903 Next_Elmt (Elmt_1);
2904 end loop;
2905 end;
2906 end if;
2907 end Check_Function_Writable_Actuals;
2909 --------------------------------
2910 -- Check_Implicit_Dereference --
2911 --------------------------------
2913 procedure Check_Implicit_Dereference (N : Node_Id; Typ : Entity_Id) is
2914 Disc : Entity_Id;
2915 Desig : Entity_Id;
2916 Nam : Node_Id;
2918 begin
2919 if Nkind (N) = N_Indexed_Component
2920 and then Present (Generalized_Indexing (N))
2921 then
2922 Nam := Generalized_Indexing (N);
2923 else
2924 Nam := N;
2925 end if;
2927 if Ada_Version < Ada_2012
2928 or else not Has_Implicit_Dereference (Base_Type (Typ))
2929 then
2930 return;
2932 elsif not Comes_From_Source (N)
2933 and then Nkind (N) /= N_Indexed_Component
2934 then
2935 return;
2937 elsif Is_Entity_Name (Nam) and then Is_Type (Entity (Nam)) then
2938 null;
2940 else
2941 Disc := First_Discriminant (Typ);
2942 while Present (Disc) loop
2943 if Has_Implicit_Dereference (Disc) then
2944 Desig := Designated_Type (Etype (Disc));
2945 Add_One_Interp (Nam, Disc, Desig);
2947 -- If the node is a generalized indexing, add interpretation
2948 -- to that node as well, for subsequent resolution.
2950 if Nkind (N) = N_Indexed_Component then
2951 Add_One_Interp (N, Disc, Desig);
2952 end if;
2954 -- If the operation comes from a generic unit and the context
2955 -- is a selected component, the selector name may be global
2956 -- and set in the instance already. Remove the entity to
2957 -- force resolution of the selected component, and the
2958 -- generation of an explicit dereference if needed.
2960 if In_Instance
2961 and then Nkind (Parent (Nam)) = N_Selected_Component
2962 then
2963 Set_Entity (Selector_Name (Parent (Nam)), Empty);
2964 end if;
2966 exit;
2967 end if;
2969 Next_Discriminant (Disc);
2970 end loop;
2971 end if;
2972 end Check_Implicit_Dereference;
2974 ----------------------------------
2975 -- Check_Internal_Protected_Use --
2976 ----------------------------------
2978 procedure Check_Internal_Protected_Use (N : Node_Id; Nam : Entity_Id) is
2979 S : Entity_Id;
2980 Prot : Entity_Id;
2982 begin
2983 Prot := Empty;
2985 S := Current_Scope;
2986 while Present (S) loop
2987 if S = Standard_Standard then
2988 exit;
2990 elsif Ekind (S) = E_Function
2991 and then Ekind (Scope (S)) = E_Protected_Type
2992 then
2993 Prot := Scope (S);
2994 exit;
2995 end if;
2997 S := Scope (S);
2998 end loop;
3000 if Present (Prot)
3001 and then Scope (Nam) = Prot
3002 and then Ekind (Nam) /= E_Function
3003 then
3004 -- An indirect function call (e.g. a callback within a protected
3005 -- function body) is not statically illegal. If the access type is
3006 -- anonymous and is the type of an access parameter, the scope of Nam
3007 -- will be the protected type, but it is not a protected operation.
3009 if Ekind (Nam) = E_Subprogram_Type
3010 and then Nkind (Associated_Node_For_Itype (Nam)) =
3011 N_Function_Specification
3012 then
3013 null;
3015 elsif Nkind (N) = N_Subprogram_Renaming_Declaration then
3016 Error_Msg_N
3017 ("within protected function cannot use protected procedure in "
3018 & "renaming or as generic actual", N);
3020 elsif Nkind (N) = N_Attribute_Reference then
3021 Error_Msg_N
3022 ("within protected function cannot take access of protected "
3023 & "procedure", N);
3025 else
3026 Error_Msg_N
3027 ("within protected function, protected object is constant", N);
3028 Error_Msg_N
3029 ("\cannot call operation that may modify it", N);
3030 end if;
3031 end if;
3033 -- Verify that an internal call does not appear within a precondition
3034 -- of a protected operation. This implements AI12-0166.
3035 -- The precondition aspect has been rewritten as a pragma Precondition
3036 -- and we check whether the scope of the called subprogram is the same
3037 -- as that of the entity to which the aspect applies.
3039 if Convention (Nam) = Convention_Protected then
3040 declare
3041 P : Node_Id;
3043 begin
3044 P := Parent (N);
3045 while Present (P) loop
3046 if Nkind (P) = N_Pragma
3047 and then Chars (Pragma_Identifier (P)) = Name_Precondition
3048 and then From_Aspect_Specification (P)
3049 and then
3050 Scope (Entity (Corresponding_Aspect (P))) = Scope (Nam)
3051 then
3052 Error_Msg_N
3053 ("internal call cannot appear in precondition of "
3054 & "protected operation", N);
3055 return;
3057 elsif Nkind (P) = N_Pragma
3058 and then Chars (Pragma_Identifier (P)) = Name_Contract_Cases
3059 then
3060 -- Check whether call is in a case guard. It is legal in a
3061 -- consequence.
3063 P := N;
3064 while Present (P) loop
3065 if Nkind (Parent (P)) = N_Component_Association
3066 and then P /= Expression (Parent (P))
3067 then
3068 Error_Msg_N
3069 ("internal call cannot appear in case guard in a "
3070 & "contract case", N);
3071 end if;
3073 P := Parent (P);
3074 end loop;
3076 return;
3078 elsif Nkind (P) = N_Parameter_Specification
3079 and then Scope (Current_Scope) = Scope (Nam)
3080 and then Nkind_In (Parent (P), N_Entry_Declaration,
3081 N_Subprogram_Declaration)
3082 then
3083 Error_Msg_N
3084 ("internal call cannot appear in default for formal of "
3085 & "protected operation", N);
3086 return;
3087 end if;
3089 P := Parent (P);
3090 end loop;
3091 end;
3092 end if;
3093 end Check_Internal_Protected_Use;
3095 ---------------------------------------
3096 -- Check_Later_Vs_Basic_Declarations --
3097 ---------------------------------------
3099 procedure Check_Later_Vs_Basic_Declarations
3100 (Decls : List_Id;
3101 During_Parsing : Boolean)
3103 Body_Sloc : Source_Ptr;
3104 Decl : Node_Id;
3106 function Is_Later_Declarative_Item (Decl : Node_Id) return Boolean;
3107 -- Return whether Decl is considered as a declarative item.
3108 -- When During_Parsing is True, the semantics of Ada 83 is followed.
3109 -- When During_Parsing is False, the semantics of SPARK is followed.
3111 -------------------------------
3112 -- Is_Later_Declarative_Item --
3113 -------------------------------
3115 function Is_Later_Declarative_Item (Decl : Node_Id) return Boolean is
3116 begin
3117 if Nkind (Decl) in N_Later_Decl_Item then
3118 return True;
3120 elsif Nkind (Decl) = N_Pragma then
3121 return True;
3123 elsif During_Parsing then
3124 return False;
3126 -- In SPARK, a package declaration is not considered as a later
3127 -- declarative item.
3129 elsif Nkind (Decl) = N_Package_Declaration then
3130 return False;
3132 -- In SPARK, a renaming is considered as a later declarative item
3134 elsif Nkind (Decl) in N_Renaming_Declaration then
3135 return True;
3137 else
3138 return False;
3139 end if;
3140 end Is_Later_Declarative_Item;
3142 -- Start of processing for Check_Later_Vs_Basic_Declarations
3144 begin
3145 Decl := First (Decls);
3147 -- Loop through sequence of basic declarative items
3149 Outer : while Present (Decl) loop
3150 if not Nkind_In (Decl, N_Subprogram_Body, N_Package_Body, N_Task_Body)
3151 and then Nkind (Decl) not in N_Body_Stub
3152 then
3153 Next (Decl);
3155 -- Once a body is encountered, we only allow later declarative
3156 -- items. The inner loop checks the rest of the list.
3158 else
3159 Body_Sloc := Sloc (Decl);
3161 Inner : while Present (Decl) loop
3162 if not Is_Later_Declarative_Item (Decl) then
3163 if During_Parsing then
3164 if Ada_Version = Ada_83 then
3165 Error_Msg_Sloc := Body_Sloc;
3166 Error_Msg_N
3167 ("(Ada 83) decl cannot appear after body#", Decl);
3168 end if;
3169 else
3170 Error_Msg_Sloc := Body_Sloc;
3171 Check_SPARK_05_Restriction
3172 ("decl cannot appear after body#", Decl);
3173 end if;
3174 end if;
3176 Next (Decl);
3177 end loop Inner;
3178 end if;
3179 end loop Outer;
3180 end Check_Later_Vs_Basic_Declarations;
3182 ---------------------------
3183 -- Check_No_Hidden_State --
3184 ---------------------------
3186 procedure Check_No_Hidden_State (Id : Entity_Id) is
3187 Context : Entity_Id := Empty;
3188 Not_Visible : Boolean := False;
3189 Scop : Entity_Id;
3191 begin
3192 pragma Assert (Ekind_In (Id, E_Abstract_State, E_Variable));
3194 -- Find the proper context where the object or state appears
3196 Scop := Scope (Id);
3197 while Present (Scop) loop
3198 Context := Scop;
3200 -- Keep track of the context's visibility
3202 Not_Visible := Not_Visible or else In_Private_Part (Context);
3204 -- Prevent the search from going too far
3206 if Context = Standard_Standard then
3207 return;
3209 -- Objects and states that appear immediately within a subprogram or
3210 -- inside a construct nested within a subprogram do not introduce a
3211 -- hidden state. They behave as local variable declarations.
3213 elsif Is_Subprogram (Context) then
3214 return;
3216 -- When examining a package body, use the entity of the spec as it
3217 -- carries the abstract state declarations.
3219 elsif Ekind (Context) = E_Package_Body then
3220 Context := Spec_Entity (Context);
3221 end if;
3223 -- Stop the traversal when a package subject to a null abstract state
3224 -- has been found.
3226 if Ekind_In (Context, E_Generic_Package, E_Package)
3227 and then Has_Null_Abstract_State (Context)
3228 then
3229 exit;
3230 end if;
3232 Scop := Scope (Scop);
3233 end loop;
3235 -- At this point we know that there is at least one package with a null
3236 -- abstract state in visibility. Emit an error message unconditionally
3237 -- if the entity being processed is a state because the placement of the
3238 -- related package is irrelevant. This is not the case for objects as
3239 -- the intermediate context matters.
3241 if Present (Context)
3242 and then (Ekind (Id) = E_Abstract_State or else Not_Visible)
3243 then
3244 Error_Msg_N ("cannot introduce hidden state &", Id);
3245 Error_Msg_NE ("\package & has null abstract state", Id, Context);
3246 end if;
3247 end Check_No_Hidden_State;
3249 ----------------------------------------
3250 -- Check_Nonvolatile_Function_Profile --
3251 ----------------------------------------
3253 procedure Check_Nonvolatile_Function_Profile (Func_Id : Entity_Id) is
3254 Formal : Entity_Id;
3256 begin
3257 -- Inspect all formal parameters
3259 Formal := First_Formal (Func_Id);
3260 while Present (Formal) loop
3261 if Is_Effectively_Volatile (Etype (Formal)) then
3262 Error_Msg_NE
3263 ("nonvolatile function & cannot have a volatile parameter",
3264 Formal, Func_Id);
3265 end if;
3267 Next_Formal (Formal);
3268 end loop;
3270 -- Inspect the return type
3272 if Is_Effectively_Volatile (Etype (Func_Id)) then
3273 Error_Msg_NE
3274 ("nonvolatile function & cannot have a volatile return type",
3275 Result_Definition (Parent (Func_Id)), Func_Id);
3276 end if;
3277 end Check_Nonvolatile_Function_Profile;
3279 -----------------------------
3280 -- Check_Part_Of_Reference --
3281 -----------------------------
3283 procedure Check_Part_Of_Reference (Var_Id : Entity_Id; Ref : Node_Id) is
3284 Conc_Obj : constant Entity_Id := Encapsulating_State (Var_Id);
3285 Decl : Node_Id;
3286 OK_Use : Boolean := False;
3287 Par : Node_Id;
3288 Prag_Nam : Name_Id;
3289 Spec_Id : Entity_Id;
3291 begin
3292 -- Traverse the parent chain looking for a suitable context for the
3293 -- reference to the concurrent constituent.
3295 Par := Parent (Ref);
3296 while Present (Par) loop
3297 if Nkind (Par) = N_Pragma then
3298 Prag_Nam := Pragma_Name (Par);
3300 -- A concurrent constituent is allowed to appear in pragmas
3301 -- Initial_Condition and Initializes as this is part of the
3302 -- elaboration checks for the constituent (SPARK RM 9.3).
3304 if Nam_In (Prag_Nam, Name_Initial_Condition, Name_Initializes) then
3305 OK_Use := True;
3306 exit;
3308 -- When the reference appears within pragma Depends or Global,
3309 -- check whether the pragma applies to a single task type. Note
3310 -- that the pragma is not encapsulated by the type definition,
3311 -- but this is still a valid context.
3313 elsif Nam_In (Prag_Nam, Name_Depends, Name_Global) then
3314 Decl := Find_Related_Declaration_Or_Body (Par);
3316 if Nkind (Decl) = N_Object_Declaration
3317 and then Defining_Entity (Decl) = Conc_Obj
3318 then
3319 OK_Use := True;
3320 exit;
3321 end if;
3322 end if;
3324 -- The reference appears somewhere in the definition of the single
3325 -- protected/task type (SPARK RM 9.3).
3327 elsif Nkind_In (Par, N_Single_Protected_Declaration,
3328 N_Single_Task_Declaration)
3329 and then Defining_Entity (Par) = Conc_Obj
3330 then
3331 OK_Use := True;
3332 exit;
3334 -- The reference appears within the expanded declaration or the body
3335 -- of the single protected/task type (SPARK RM 9.3).
3337 elsif Nkind_In (Par, N_Protected_Body,
3338 N_Protected_Type_Declaration,
3339 N_Task_Body,
3340 N_Task_Type_Declaration)
3341 then
3342 Spec_Id := Unique_Defining_Entity (Par);
3344 if Present (Anonymous_Object (Spec_Id))
3345 and then Anonymous_Object (Spec_Id) = Conc_Obj
3346 then
3347 OK_Use := True;
3348 exit;
3349 end if;
3351 -- The reference has been relocated within an internally generated
3352 -- package or subprogram. Assume that the reference is legal as the
3353 -- real check was already performed in the original context of the
3354 -- reference.
3356 elsif Nkind_In (Par, N_Package_Body,
3357 N_Package_Declaration,
3358 N_Subprogram_Body,
3359 N_Subprogram_Declaration)
3360 and then not Comes_From_Source (Par)
3361 then
3362 -- Continue to examine the context if the reference appears in a
3363 -- subprogram body which was previously an expression function,
3364 -- unless this is during preanalysis (when In_Spec_Expression is
3365 -- True), as the body may not yet be inserted in the tree.
3367 if Nkind (Par) = N_Subprogram_Body
3368 and then Was_Expression_Function (Par)
3369 and then not In_Spec_Expression
3370 then
3371 null;
3373 -- Otherwise the reference is legal
3375 else
3376 OK_Use := True;
3377 exit;
3378 end if;
3380 -- The reference has been relocated to an inlined body for GNATprove.
3381 -- Assume that the reference is legal as the real check was already
3382 -- performed in the original context of the reference.
3384 elsif GNATprove_Mode
3385 and then Nkind (Par) = N_Subprogram_Body
3386 and then Chars (Defining_Entity (Par)) = Name_uParent
3387 then
3388 OK_Use := True;
3389 exit;
3390 end if;
3392 Par := Parent (Par);
3393 end loop;
3395 -- The reference is illegal as it appears outside the definition or
3396 -- body of the single protected/task type.
3398 if not OK_Use then
3399 Error_Msg_NE
3400 ("reference to variable & cannot appear in this context",
3401 Ref, Var_Id);
3402 Error_Msg_Name_1 := Chars (Var_Id);
3404 if Is_Single_Protected_Object (Conc_Obj) then
3405 Error_Msg_NE
3406 ("\% is constituent of single protected type &", Ref, Conc_Obj);
3408 else
3409 Error_Msg_NE
3410 ("\% is constituent of single task type &", Ref, Conc_Obj);
3411 end if;
3412 end if;
3413 end Check_Part_Of_Reference;
3415 ------------------------------------------
3416 -- Check_Potentially_Blocking_Operation --
3417 ------------------------------------------
3419 procedure Check_Potentially_Blocking_Operation (N : Node_Id) is
3420 S : Entity_Id;
3422 begin
3423 -- N is one of the potentially blocking operations listed in 9.5.1(8).
3424 -- When pragma Detect_Blocking is active, the run time will raise
3425 -- Program_Error. Here we only issue a warning, since we generally
3426 -- support the use of potentially blocking operations in the absence
3427 -- of the pragma.
3429 -- Indirect blocking through a subprogram call cannot be diagnosed
3430 -- statically without interprocedural analysis, so we do not attempt
3431 -- to do it here.
3433 S := Scope (Current_Scope);
3434 while Present (S) and then S /= Standard_Standard loop
3435 if Is_Protected_Type (S) then
3436 Error_Msg_N
3437 ("potentially blocking operation in protected operation??", N);
3438 return;
3439 end if;
3441 S := Scope (S);
3442 end loop;
3443 end Check_Potentially_Blocking_Operation;
3445 ------------------------------------
3446 -- Check_Previous_Null_Procedure --
3447 ------------------------------------
3449 procedure Check_Previous_Null_Procedure
3450 (Decl : Node_Id;
3451 Prev : Entity_Id)
3453 begin
3454 if Ekind (Prev) = E_Procedure
3455 and then Nkind (Parent (Prev)) = N_Procedure_Specification
3456 and then Null_Present (Parent (Prev))
3457 then
3458 Error_Msg_Sloc := Sloc (Prev);
3459 Error_Msg_N
3460 ("declaration cannot complete previous null procedure#", Decl);
3461 end if;
3462 end Check_Previous_Null_Procedure;
3464 ---------------------------------
3465 -- Check_Result_And_Post_State --
3466 ---------------------------------
3468 procedure Check_Result_And_Post_State (Subp_Id : Entity_Id) is
3469 procedure Check_Result_And_Post_State_In_Pragma
3470 (Prag : Node_Id;
3471 Result_Seen : in out Boolean);
3472 -- Determine whether pragma Prag mentions attribute 'Result and whether
3473 -- the pragma contains an expression that evaluates differently in pre-
3474 -- and post-state. Prag is a [refined] postcondition or a contract-cases
3475 -- pragma. Result_Seen is set when the pragma mentions attribute 'Result
3477 function Has_In_Out_Parameter (Subp_Id : Entity_Id) return Boolean;
3478 -- Determine whether subprogram Subp_Id contains at least one IN OUT
3479 -- formal parameter.
3481 -------------------------------------------
3482 -- Check_Result_And_Post_State_In_Pragma --
3483 -------------------------------------------
3485 procedure Check_Result_And_Post_State_In_Pragma
3486 (Prag : Node_Id;
3487 Result_Seen : in out Boolean)
3489 procedure Check_Conjunct (Expr : Node_Id);
3490 -- Check an individual conjunct in a conjunction of Boolean
3491 -- expressions, connected by "and" or "and then" operators.
3493 procedure Check_Conjuncts (Expr : Node_Id);
3494 -- Apply the post-state check to every conjunct in an expression, in
3495 -- case this is a conjunction of Boolean expressions. Otherwise apply
3496 -- it to the expression as a whole.
3498 procedure Check_Expression (Expr : Node_Id);
3499 -- Perform the 'Result and post-state checks on a given expression
3501 function Is_Function_Result (N : Node_Id) return Traverse_Result;
3502 -- Attempt to find attribute 'Result in a subtree denoted by N
3504 function Is_Trivial_Boolean (N : Node_Id) return Boolean;
3505 -- Determine whether source node N denotes "True" or "False"
3507 function Mentions_Post_State (N : Node_Id) return Boolean;
3508 -- Determine whether a subtree denoted by N mentions any construct
3509 -- that denotes a post-state.
3511 procedure Check_Function_Result is
3512 new Traverse_Proc (Is_Function_Result);
3514 --------------------
3515 -- Check_Conjunct --
3516 --------------------
3518 procedure Check_Conjunct (Expr : Node_Id) is
3519 function Adjust_Message (Msg : String) return String;
3520 -- Prepend a prefix to the input message Msg denoting that the
3521 -- message applies to a conjunct in the expression, when this
3522 -- is the case.
3524 function Applied_On_Conjunct return Boolean;
3525 -- Returns True if the message applies to a conjunct in the
3526 -- expression, instead of the whole expression.
3528 function Has_Global_Output (Subp : Entity_Id) return Boolean;
3529 -- Returns True if Subp has an output in its Global contract
3531 function Has_No_Output (Subp : Entity_Id) return Boolean;
3532 -- Returns True if Subp has no declared output: no function
3533 -- result, no output parameter, and no output in its Global
3534 -- contract.
3536 --------------------
3537 -- Adjust_Message --
3538 --------------------
3540 function Adjust_Message (Msg : String) return String is
3541 begin
3542 if Applied_On_Conjunct then
3543 return "conjunct in " & Msg;
3544 else
3545 return Msg;
3546 end if;
3547 end Adjust_Message;
3549 -------------------------
3550 -- Applied_On_Conjunct --
3551 -------------------------
3553 function Applied_On_Conjunct return Boolean is
3554 begin
3555 -- Expr is the conjunct of an enclosing "and" expression
3557 return Nkind (Parent (Expr)) in N_Subexpr
3559 -- or Expr is a conjunct of an enclosing "and then"
3560 -- expression in a postcondition aspect that was split into
3561 -- multiple pragmas. The first conjunct has the "and then"
3562 -- expression as Original_Node, and other conjuncts have
3563 -- Split_PCC set to True.
3565 or else Nkind (Original_Node (Expr)) = N_And_Then
3566 or else Split_PPC (Prag);
3567 end Applied_On_Conjunct;
3569 -----------------------
3570 -- Has_Global_Output --
3571 -----------------------
3573 function Has_Global_Output (Subp : Entity_Id) return Boolean is
3574 Global : constant Node_Id := Get_Pragma (Subp, Pragma_Global);
3575 List : Node_Id;
3576 Assoc : Node_Id;
3578 begin
3579 if No (Global) then
3580 return False;
3581 end if;
3583 List := Expression (Get_Argument (Global, Subp));
3585 -- Empty list (no global items) or single global item
3586 -- declaration (only input items).
3588 if Nkind_In (List, N_Null,
3589 N_Expanded_Name,
3590 N_Identifier,
3591 N_Selected_Component)
3592 then
3593 return False;
3595 -- Simple global list (only input items) or moded global list
3596 -- declaration.
3598 elsif Nkind (List) = N_Aggregate then
3599 if Present (Expressions (List)) then
3600 return False;
3602 else
3603 Assoc := First (Component_Associations (List));
3604 while Present (Assoc) loop
3605 if Chars (First (Choices (Assoc))) /= Name_Input then
3606 return True;
3607 end if;
3609 Next (Assoc);
3610 end loop;
3612 return False;
3613 end if;
3615 -- To accommodate partial decoration of disabled SPARK
3616 -- features, this routine may be called with illegal input.
3617 -- If this is the case, do not raise Program_Error.
3619 else
3620 return False;
3621 end if;
3622 end Has_Global_Output;
3624 -------------------
3625 -- Has_No_Output --
3626 -------------------
3628 function Has_No_Output (Subp : Entity_Id) return Boolean is
3629 Param : Node_Id;
3631 begin
3632 -- A function has its result as output
3634 if Ekind (Subp) = E_Function then
3635 return False;
3636 end if;
3638 -- An OUT or IN OUT parameter is an output
3640 Param := First_Formal (Subp);
3641 while Present (Param) loop
3642 if Ekind_In (Param, E_Out_Parameter, E_In_Out_Parameter) then
3643 return False;
3644 end if;
3646 Next_Formal (Param);
3647 end loop;
3649 -- An item of mode Output or In_Out in the Global contract is
3650 -- an output.
3652 if Has_Global_Output (Subp) then
3653 return False;
3654 end if;
3656 return True;
3657 end Has_No_Output;
3659 -- Local variables
3661 Err_Node : Node_Id;
3662 -- Error node when reporting a warning on a (refined)
3663 -- postcondition.
3665 -- Start of processing for Check_Conjunct
3667 begin
3668 if Applied_On_Conjunct then
3669 Err_Node := Expr;
3670 else
3671 Err_Node := Prag;
3672 end if;
3674 -- Do not report missing reference to outcome in postcondition if
3675 -- either the postcondition is trivially True or False, or if the
3676 -- subprogram is ghost and has no declared output.
3678 if not Is_Trivial_Boolean (Expr)
3679 and then not Mentions_Post_State (Expr)
3680 and then not (Is_Ghost_Entity (Subp_Id)
3681 and then Has_No_Output (Subp_Id))
3682 then
3683 if Pragma_Name (Prag) = Name_Contract_Cases then
3684 Error_Msg_NE (Adjust_Message
3685 ("contract case does not check the outcome of calling "
3686 & "&?T?"), Expr, Subp_Id);
3688 elsif Pragma_Name (Prag) = Name_Refined_Post then
3689 Error_Msg_NE (Adjust_Message
3690 ("refined postcondition does not check the outcome of "
3691 & "calling &?T?"), Err_Node, Subp_Id);
3693 else
3694 Error_Msg_NE (Adjust_Message
3695 ("postcondition does not check the outcome of calling "
3696 & "&?T?"), Err_Node, Subp_Id);
3697 end if;
3698 end if;
3699 end Check_Conjunct;
3701 ---------------------
3702 -- Check_Conjuncts --
3703 ---------------------
3705 procedure Check_Conjuncts (Expr : Node_Id) is
3706 begin
3707 if Nkind_In (Expr, N_Op_And, N_And_Then) then
3708 Check_Conjuncts (Left_Opnd (Expr));
3709 Check_Conjuncts (Right_Opnd (Expr));
3710 else
3711 Check_Conjunct (Expr);
3712 end if;
3713 end Check_Conjuncts;
3715 ----------------------
3716 -- Check_Expression --
3717 ----------------------
3719 procedure Check_Expression (Expr : Node_Id) is
3720 begin
3721 if not Is_Trivial_Boolean (Expr) then
3722 Check_Function_Result (Expr);
3723 Check_Conjuncts (Expr);
3724 end if;
3725 end Check_Expression;
3727 ------------------------
3728 -- Is_Function_Result --
3729 ------------------------
3731 function Is_Function_Result (N : Node_Id) return Traverse_Result is
3732 begin
3733 if Is_Attribute_Result (N) then
3734 Result_Seen := True;
3735 return Abandon;
3737 -- Continue the traversal
3739 else
3740 return OK;
3741 end if;
3742 end Is_Function_Result;
3744 ------------------------
3745 -- Is_Trivial_Boolean --
3746 ------------------------
3748 function Is_Trivial_Boolean (N : Node_Id) return Boolean is
3749 begin
3750 return
3751 Comes_From_Source (N)
3752 and then Is_Entity_Name (N)
3753 and then (Entity (N) = Standard_True
3754 or else
3755 Entity (N) = Standard_False);
3756 end Is_Trivial_Boolean;
3758 -------------------------
3759 -- Mentions_Post_State --
3760 -------------------------
3762 function Mentions_Post_State (N : Node_Id) return Boolean is
3763 Post_State_Seen : Boolean := False;
3765 function Is_Post_State (N : Node_Id) return Traverse_Result;
3766 -- Attempt to find a construct that denotes a post-state. If this
3767 -- is the case, set flag Post_State_Seen.
3769 -------------------
3770 -- Is_Post_State --
3771 -------------------
3773 function Is_Post_State (N : Node_Id) return Traverse_Result is
3774 Ent : Entity_Id;
3776 begin
3777 if Nkind_In (N, N_Explicit_Dereference, N_Function_Call) then
3778 Post_State_Seen := True;
3779 return Abandon;
3781 elsif Nkind_In (N, N_Expanded_Name, N_Identifier) then
3782 Ent := Entity (N);
3784 -- Treat an undecorated reference as OK
3786 if No (Ent)
3788 -- A reference to an assignable entity is considered a
3789 -- change in the post-state of a subprogram.
3791 or else Ekind_In (Ent, E_Generic_In_Out_Parameter,
3792 E_In_Out_Parameter,
3793 E_Out_Parameter,
3794 E_Variable)
3796 -- The reference may be modified through a dereference
3798 or else (Is_Access_Type (Etype (Ent))
3799 and then Nkind (Parent (N)) =
3800 N_Selected_Component)
3801 then
3802 Post_State_Seen := True;
3803 return Abandon;
3804 end if;
3806 elsif Nkind (N) = N_Attribute_Reference then
3807 if Attribute_Name (N) = Name_Old then
3808 return Skip;
3810 elsif Attribute_Name (N) = Name_Result then
3811 Post_State_Seen := True;
3812 return Abandon;
3813 end if;
3814 end if;
3816 return OK;
3817 end Is_Post_State;
3819 procedure Find_Post_State is new Traverse_Proc (Is_Post_State);
3821 -- Start of processing for Mentions_Post_State
3823 begin
3824 Find_Post_State (N);
3826 return Post_State_Seen;
3827 end Mentions_Post_State;
3829 -- Local variables
3831 Expr : constant Node_Id :=
3832 Get_Pragma_Arg
3833 (First (Pragma_Argument_Associations (Prag)));
3834 Nam : constant Name_Id := Pragma_Name (Prag);
3835 CCase : Node_Id;
3837 -- Start of processing for Check_Result_And_Post_State_In_Pragma
3839 begin
3840 -- Examine all consequences
3842 if Nam = Name_Contract_Cases then
3843 CCase := First (Component_Associations (Expr));
3844 while Present (CCase) loop
3845 Check_Expression (Expression (CCase));
3847 Next (CCase);
3848 end loop;
3850 -- Examine the expression of a postcondition
3852 else pragma Assert (Nam_In (Nam, Name_Postcondition,
3853 Name_Refined_Post));
3854 Check_Expression (Expr);
3855 end if;
3856 end Check_Result_And_Post_State_In_Pragma;
3858 --------------------------
3859 -- Has_In_Out_Parameter --
3860 --------------------------
3862 function Has_In_Out_Parameter (Subp_Id : Entity_Id) return Boolean is
3863 Formal : Entity_Id;
3865 begin
3866 -- Traverse the formals looking for an IN OUT parameter
3868 Formal := First_Formal (Subp_Id);
3869 while Present (Formal) loop
3870 if Ekind (Formal) = E_In_Out_Parameter then
3871 return True;
3872 end if;
3874 Next_Formal (Formal);
3875 end loop;
3877 return False;
3878 end Has_In_Out_Parameter;
3880 -- Local variables
3882 Items : constant Node_Id := Contract (Subp_Id);
3883 Subp_Decl : constant Node_Id := Unit_Declaration_Node (Subp_Id);
3884 Case_Prag : Node_Id := Empty;
3885 Post_Prag : Node_Id := Empty;
3886 Prag : Node_Id;
3887 Seen_In_Case : Boolean := False;
3888 Seen_In_Post : Boolean := False;
3889 Spec_Id : Entity_Id;
3891 -- Start of processing for Check_Result_And_Post_State
3893 begin
3894 -- The lack of attribute 'Result or a post-state is classified as a
3895 -- suspicious contract. Do not perform the check if the corresponding
3896 -- swich is not set.
3898 if not Warn_On_Suspicious_Contract then
3899 return;
3901 -- Nothing to do if there is no contract
3903 elsif No (Items) then
3904 return;
3905 end if;
3907 -- Retrieve the entity of the subprogram spec (if any)
3909 if Nkind (Subp_Decl) = N_Subprogram_Body
3910 and then Present (Corresponding_Spec (Subp_Decl))
3911 then
3912 Spec_Id := Corresponding_Spec (Subp_Decl);
3914 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
3915 and then Present (Corresponding_Spec_Of_Stub (Subp_Decl))
3916 then
3917 Spec_Id := Corresponding_Spec_Of_Stub (Subp_Decl);
3919 else
3920 Spec_Id := Subp_Id;
3921 end if;
3923 -- Examine all postconditions for attribute 'Result and a post-state
3925 Prag := Pre_Post_Conditions (Items);
3926 while Present (Prag) loop
3927 if Nam_In (Pragma_Name_Unmapped (Prag),
3928 Name_Postcondition, Name_Refined_Post)
3929 and then not Error_Posted (Prag)
3930 then
3931 Post_Prag := Prag;
3932 Check_Result_And_Post_State_In_Pragma (Prag, Seen_In_Post);
3933 end if;
3935 Prag := Next_Pragma (Prag);
3936 end loop;
3938 -- Examine the contract cases of the subprogram for attribute 'Result
3939 -- and a post-state.
3941 Prag := Contract_Test_Cases (Items);
3942 while Present (Prag) loop
3943 if Pragma_Name (Prag) = Name_Contract_Cases
3944 and then not Error_Posted (Prag)
3945 then
3946 Case_Prag := Prag;
3947 Check_Result_And_Post_State_In_Pragma (Prag, Seen_In_Case);
3948 end if;
3950 Prag := Next_Pragma (Prag);
3951 end loop;
3953 -- Do not emit any errors if the subprogram is not a function
3955 if not Ekind_In (Spec_Id, E_Function, E_Generic_Function) then
3956 null;
3958 -- Regardless of whether the function has postconditions or contract
3959 -- cases, or whether they mention attribute 'Result, an IN OUT formal
3960 -- parameter is always treated as a result.
3962 elsif Has_In_Out_Parameter (Spec_Id) then
3963 null;
3965 -- The function has both a postcondition and contract cases and they do
3966 -- not mention attribute 'Result.
3968 elsif Present (Case_Prag)
3969 and then not Seen_In_Case
3970 and then Present (Post_Prag)
3971 and then not Seen_In_Post
3972 then
3973 Error_Msg_N
3974 ("neither postcondition nor contract cases mention function "
3975 & "result?T?", Post_Prag);
3977 -- The function has contract cases only and they do not mention
3978 -- attribute 'Result.
3980 elsif Present (Case_Prag) and then not Seen_In_Case then
3981 Error_Msg_N ("contract cases do not mention result?T?", Case_Prag);
3983 -- The function has postconditions only and they do not mention
3984 -- attribute 'Result.
3986 elsif Present (Post_Prag) and then not Seen_In_Post then
3987 Error_Msg_N
3988 ("postcondition does not mention function result?T?", Post_Prag);
3989 end if;
3990 end Check_Result_And_Post_State;
3992 -----------------------------
3993 -- Check_State_Refinements --
3994 -----------------------------
3996 procedure Check_State_Refinements
3997 (Context : Node_Id;
3998 Is_Main_Unit : Boolean := False)
4000 procedure Check_Package (Pack : Node_Id);
4001 -- Verify that all abstract states of a [generic] package denoted by its
4002 -- declarative node Pack have proper refinement. Recursively verify the
4003 -- visible and private declarations of the [generic] package for other
4004 -- nested packages.
4006 procedure Check_Packages_In (Decls : List_Id);
4007 -- Seek out [generic] package declarations within declarative list Decls
4008 -- and verify the status of their abstract state refinement.
4010 function SPARK_Mode_Is_Off (N : Node_Id) return Boolean;
4011 -- Determine whether construct N is subject to pragma SPARK_Mode Off
4013 -------------------
4014 -- Check_Package --
4015 -------------------
4017 procedure Check_Package (Pack : Node_Id) is
4018 Body_Id : constant Entity_Id := Corresponding_Body (Pack);
4019 Spec : constant Node_Id := Specification (Pack);
4020 States : constant Elist_Id :=
4021 Abstract_States (Defining_Entity (Pack));
4023 State_Elmt : Elmt_Id;
4024 State_Id : Entity_Id;
4026 begin
4027 -- Do not verify proper state refinement when the package is subject
4028 -- to pragma SPARK_Mode Off because this disables the requirement for
4029 -- state refinement.
4031 if SPARK_Mode_Is_Off (Pack) then
4032 null;
4034 -- State refinement can only occur in a completing package body. Do
4035 -- not verify proper state refinement when the body is subject to
4036 -- pragma SPARK_Mode Off because this disables the requirement for
4037 -- state refinement.
4039 elsif Present (Body_Id)
4040 and then SPARK_Mode_Is_Off (Unit_Declaration_Node (Body_Id))
4041 then
4042 null;
4044 -- Do not verify proper state refinement when the package is an
4045 -- instance as this check was already performed in the generic.
4047 elsif Present (Generic_Parent (Spec)) then
4048 null;
4050 -- Otherwise examine the contents of the package
4052 else
4053 if Present (States) then
4054 State_Elmt := First_Elmt (States);
4055 while Present (State_Elmt) loop
4056 State_Id := Node (State_Elmt);
4058 -- Emit an error when a non-null state lacks any form of
4059 -- refinement.
4061 if not Is_Null_State (State_Id)
4062 and then not Has_Null_Refinement (State_Id)
4063 and then not Has_Non_Null_Refinement (State_Id)
4064 then
4065 Error_Msg_N ("state & requires refinement", State_Id);
4066 end if;
4068 Next_Elmt (State_Elmt);
4069 end loop;
4070 end if;
4072 Check_Packages_In (Visible_Declarations (Spec));
4073 Check_Packages_In (Private_Declarations (Spec));
4074 end if;
4075 end Check_Package;
4077 -----------------------
4078 -- Check_Packages_In --
4079 -----------------------
4081 procedure Check_Packages_In (Decls : List_Id) is
4082 Decl : Node_Id;
4084 begin
4085 if Present (Decls) then
4086 Decl := First (Decls);
4087 while Present (Decl) loop
4088 if Nkind_In (Decl, N_Generic_Package_Declaration,
4089 N_Package_Declaration)
4090 then
4091 Check_Package (Decl);
4092 end if;
4094 Next (Decl);
4095 end loop;
4096 end if;
4097 end Check_Packages_In;
4099 -----------------------
4100 -- SPARK_Mode_Is_Off --
4101 -----------------------
4103 function SPARK_Mode_Is_Off (N : Node_Id) return Boolean is
4104 Id : constant Entity_Id := Defining_Entity (N);
4105 Prag : constant Node_Id := SPARK_Pragma (Id);
4107 begin
4108 -- Default the mode to "off" when the context is an instance and all
4109 -- SPARK_Mode pragmas found within are to be ignored.
4111 if Ignore_SPARK_Mode_Pragmas (Id) then
4112 return True;
4114 else
4115 return
4116 Present (Prag)
4117 and then Get_SPARK_Mode_From_Annotation (Prag) = Off;
4118 end if;
4119 end SPARK_Mode_Is_Off;
4121 -- Start of processing for Check_State_Refinements
4123 begin
4124 -- A block may declare a nested package
4126 if Nkind (Context) = N_Block_Statement then
4127 Check_Packages_In (Declarations (Context));
4129 -- An entry, protected, subprogram, or task body may declare a nested
4130 -- package.
4132 elsif Nkind_In (Context, N_Entry_Body,
4133 N_Protected_Body,
4134 N_Subprogram_Body,
4135 N_Task_Body)
4136 then
4137 -- Do not verify proper state refinement when the body is subject to
4138 -- pragma SPARK_Mode Off because this disables the requirement for
4139 -- state refinement.
4141 if not SPARK_Mode_Is_Off (Context) then
4142 Check_Packages_In (Declarations (Context));
4143 end if;
4145 -- A package body may declare a nested package
4147 elsif Nkind (Context) = N_Package_Body then
4148 Check_Package (Unit_Declaration_Node (Corresponding_Spec (Context)));
4150 -- Do not verify proper state refinement when the body is subject to
4151 -- pragma SPARK_Mode Off because this disables the requirement for
4152 -- state refinement.
4154 if not SPARK_Mode_Is_Off (Context) then
4155 Check_Packages_In (Declarations (Context));
4156 end if;
4158 -- A library level [generic] package may declare a nested package
4160 elsif Nkind_In (Context, N_Generic_Package_Declaration,
4161 N_Package_Declaration)
4162 and then Is_Main_Unit
4163 then
4164 Check_Package (Context);
4165 end if;
4166 end Check_State_Refinements;
4168 ------------------------------
4169 -- Check_Unprotected_Access --
4170 ------------------------------
4172 procedure Check_Unprotected_Access
4173 (Context : Node_Id;
4174 Expr : Node_Id)
4176 Cont_Encl_Typ : Entity_Id;
4177 Pref_Encl_Typ : Entity_Id;
4179 function Enclosing_Protected_Type (Obj : Node_Id) return Entity_Id;
4180 -- Check whether Obj is a private component of a protected object.
4181 -- Return the protected type where the component resides, Empty
4182 -- otherwise.
4184 function Is_Public_Operation return Boolean;
4185 -- Verify that the enclosing operation is callable from outside the
4186 -- protected object, to minimize false positives.
4188 ------------------------------
4189 -- Enclosing_Protected_Type --
4190 ------------------------------
4192 function Enclosing_Protected_Type (Obj : Node_Id) return Entity_Id is
4193 begin
4194 if Is_Entity_Name (Obj) then
4195 declare
4196 Ent : Entity_Id := Entity (Obj);
4198 begin
4199 -- The object can be a renaming of a private component, use
4200 -- the original record component.
4202 if Is_Prival (Ent) then
4203 Ent := Prival_Link (Ent);
4204 end if;
4206 if Is_Protected_Type (Scope (Ent)) then
4207 return Scope (Ent);
4208 end if;
4209 end;
4210 end if;
4212 -- For indexed and selected components, recursively check the prefix
4214 if Nkind_In (Obj, N_Indexed_Component, N_Selected_Component) then
4215 return Enclosing_Protected_Type (Prefix (Obj));
4217 -- The object does not denote a protected component
4219 else
4220 return Empty;
4221 end if;
4222 end Enclosing_Protected_Type;
4224 -------------------------
4225 -- Is_Public_Operation --
4226 -------------------------
4228 function Is_Public_Operation return Boolean is
4229 S : Entity_Id;
4230 E : Entity_Id;
4232 begin
4233 S := Current_Scope;
4234 while Present (S) and then S /= Pref_Encl_Typ loop
4235 if Scope (S) = Pref_Encl_Typ then
4236 E := First_Entity (Pref_Encl_Typ);
4237 while Present (E)
4238 and then E /= First_Private_Entity (Pref_Encl_Typ)
4239 loop
4240 if E = S then
4241 return True;
4242 end if;
4244 Next_Entity (E);
4245 end loop;
4246 end if;
4248 S := Scope (S);
4249 end loop;
4251 return False;
4252 end Is_Public_Operation;
4254 -- Start of processing for Check_Unprotected_Access
4256 begin
4257 if Nkind (Expr) = N_Attribute_Reference
4258 and then Attribute_Name (Expr) = Name_Unchecked_Access
4259 then
4260 Cont_Encl_Typ := Enclosing_Protected_Type (Context);
4261 Pref_Encl_Typ := Enclosing_Protected_Type (Prefix (Expr));
4263 -- Check whether we are trying to export a protected component to a
4264 -- context with an equal or lower access level.
4266 if Present (Pref_Encl_Typ)
4267 and then No (Cont_Encl_Typ)
4268 and then Is_Public_Operation
4269 and then Scope_Depth (Pref_Encl_Typ) >=
4270 Object_Access_Level (Context)
4271 then
4272 Error_Msg_N
4273 ("??possible unprotected access to protected data", Expr);
4274 end if;
4275 end if;
4276 end Check_Unprotected_Access;
4278 ------------------------------
4279 -- Check_Unused_Body_States --
4280 ------------------------------
4282 procedure Check_Unused_Body_States (Body_Id : Entity_Id) is
4283 procedure Process_Refinement_Clause
4284 (Clause : Node_Id;
4285 States : Elist_Id);
4286 -- Inspect all constituents of refinement clause Clause and remove any
4287 -- matches from body state list States.
4289 procedure Report_Unused_Body_States (States : Elist_Id);
4290 -- Emit errors for each abstract state or object found in list States
4292 -------------------------------
4293 -- Process_Refinement_Clause --
4294 -------------------------------
4296 procedure Process_Refinement_Clause
4297 (Clause : Node_Id;
4298 States : Elist_Id)
4300 procedure Process_Constituent (Constit : Node_Id);
4301 -- Remove constituent Constit from body state list States
4303 -------------------------
4304 -- Process_Constituent --
4305 -------------------------
4307 procedure Process_Constituent (Constit : Node_Id) is
4308 Constit_Id : Entity_Id;
4310 begin
4311 -- Guard against illegal constituents. Only abstract states and
4312 -- objects can appear on the right hand side of a refinement.
4314 if Is_Entity_Name (Constit) then
4315 Constit_Id := Entity_Of (Constit);
4317 if Present (Constit_Id)
4318 and then Ekind_In (Constit_Id, E_Abstract_State,
4319 E_Constant,
4320 E_Variable)
4321 then
4322 Remove (States, Constit_Id);
4323 end if;
4324 end if;
4325 end Process_Constituent;
4327 -- Local variables
4329 Constit : Node_Id;
4331 -- Start of processing for Process_Refinement_Clause
4333 begin
4334 if Nkind (Clause) = N_Component_Association then
4335 Constit := Expression (Clause);
4337 -- Multiple constituents appear as an aggregate
4339 if Nkind (Constit) = N_Aggregate then
4340 Constit := First (Expressions (Constit));
4341 while Present (Constit) loop
4342 Process_Constituent (Constit);
4343 Next (Constit);
4344 end loop;
4346 -- Various forms of a single constituent
4348 else
4349 Process_Constituent (Constit);
4350 end if;
4351 end if;
4352 end Process_Refinement_Clause;
4354 -------------------------------
4355 -- Report_Unused_Body_States --
4356 -------------------------------
4358 procedure Report_Unused_Body_States (States : Elist_Id) is
4359 Posted : Boolean := False;
4360 State_Elmt : Elmt_Id;
4361 State_Id : Entity_Id;
4363 begin
4364 if Present (States) then
4365 State_Elmt := First_Elmt (States);
4366 while Present (State_Elmt) loop
4367 State_Id := Node (State_Elmt);
4369 -- Constants are part of the hidden state of a package, but the
4370 -- compiler cannot determine whether they have variable input
4371 -- (SPARK RM 7.1.1(2)) and cannot classify them properly as a
4372 -- hidden state. Do not emit an error when a constant does not
4373 -- participate in a state refinement, even though it acts as a
4374 -- hidden state.
4376 if Ekind (State_Id) = E_Constant then
4377 null;
4379 -- Generate an error message of the form:
4381 -- body of package ... has unused hidden states
4382 -- abstract state ... defined at ...
4383 -- variable ... defined at ...
4385 else
4386 if not Posted then
4387 Posted := True;
4388 SPARK_Msg_N
4389 ("body of package & has unused hidden states", Body_Id);
4390 end if;
4392 Error_Msg_Sloc := Sloc (State_Id);
4394 if Ekind (State_Id) = E_Abstract_State then
4395 SPARK_Msg_NE
4396 ("\abstract state & defined #", Body_Id, State_Id);
4398 else
4399 SPARK_Msg_NE ("\variable & defined #", Body_Id, State_Id);
4400 end if;
4401 end if;
4403 Next_Elmt (State_Elmt);
4404 end loop;
4405 end if;
4406 end Report_Unused_Body_States;
4408 -- Local variables
4410 Prag : constant Node_Id := Get_Pragma (Body_Id, Pragma_Refined_State);
4411 Spec_Id : constant Entity_Id := Spec_Entity (Body_Id);
4412 Clause : Node_Id;
4413 States : Elist_Id;
4415 -- Start of processing for Check_Unused_Body_States
4417 begin
4418 -- Inspect the clauses of pragma Refined_State and determine whether all
4419 -- visible states declared within the package body participate in the
4420 -- refinement.
4422 if Present (Prag) then
4423 Clause := Expression (Get_Argument (Prag, Spec_Id));
4424 States := Collect_Body_States (Body_Id);
4426 -- Multiple non-null state refinements appear as an aggregate
4428 if Nkind (Clause) = N_Aggregate then
4429 Clause := First (Component_Associations (Clause));
4430 while Present (Clause) loop
4431 Process_Refinement_Clause (Clause, States);
4432 Next (Clause);
4433 end loop;
4435 -- Various forms of a single state refinement
4437 else
4438 Process_Refinement_Clause (Clause, States);
4439 end if;
4441 -- Ensure that all abstract states and objects declared in the
4442 -- package body state space are utilized as constituents.
4444 Report_Unused_Body_States (States);
4445 end if;
4446 end Check_Unused_Body_States;
4448 -----------------
4449 -- Choice_List --
4450 -----------------
4452 function Choice_List (N : Node_Id) return List_Id is
4453 begin
4454 if Nkind (N) = N_Iterated_Component_Association then
4455 return Discrete_Choices (N);
4456 else
4457 return Choices (N);
4458 end if;
4459 end Choice_List;
4461 -------------------------
4462 -- Collect_Body_States --
4463 -------------------------
4465 function Collect_Body_States (Body_Id : Entity_Id) return Elist_Id is
4466 function Is_Visible_Object (Obj_Id : Entity_Id) return Boolean;
4467 -- Determine whether object Obj_Id is a suitable visible state of a
4468 -- package body.
4470 procedure Collect_Visible_States
4471 (Pack_Id : Entity_Id;
4472 States : in out Elist_Id);
4473 -- Gather the entities of all abstract states and objects declared in
4474 -- the visible state space of package Pack_Id.
4476 ----------------------------
4477 -- Collect_Visible_States --
4478 ----------------------------
4480 procedure Collect_Visible_States
4481 (Pack_Id : Entity_Id;
4482 States : in out Elist_Id)
4484 Item_Id : Entity_Id;
4486 begin
4487 -- Traverse the entity chain of the package and inspect all visible
4488 -- items.
4490 Item_Id := First_Entity (Pack_Id);
4491 while Present (Item_Id) and then not In_Private_Part (Item_Id) loop
4493 -- Do not consider internally generated items as those cannot be
4494 -- named and participate in refinement.
4496 if not Comes_From_Source (Item_Id) then
4497 null;
4499 elsif Ekind (Item_Id) = E_Abstract_State then
4500 Append_New_Elmt (Item_Id, States);
4502 elsif Ekind_In (Item_Id, E_Constant, E_Variable)
4503 and then Is_Visible_Object (Item_Id)
4504 then
4505 Append_New_Elmt (Item_Id, States);
4507 -- Recursively gather the visible states of a nested package
4509 elsif Ekind (Item_Id) = E_Package then
4510 Collect_Visible_States (Item_Id, States);
4511 end if;
4513 Next_Entity (Item_Id);
4514 end loop;
4515 end Collect_Visible_States;
4517 -----------------------
4518 -- Is_Visible_Object --
4519 -----------------------
4521 function Is_Visible_Object (Obj_Id : Entity_Id) return Boolean is
4522 begin
4523 -- Objects that map generic formals to their actuals are not visible
4524 -- from outside the generic instantiation.
4526 if Present (Corresponding_Generic_Association
4527 (Declaration_Node (Obj_Id)))
4528 then
4529 return False;
4531 -- Constituents of a single protected/task type act as components of
4532 -- the type and are not visible from outside the type.
4534 elsif Ekind (Obj_Id) = E_Variable
4535 and then Present (Encapsulating_State (Obj_Id))
4536 and then Is_Single_Concurrent_Object (Encapsulating_State (Obj_Id))
4537 then
4538 return False;
4540 else
4541 return True;
4542 end if;
4543 end Is_Visible_Object;
4545 -- Local variables
4547 Body_Decl : constant Node_Id := Unit_Declaration_Node (Body_Id);
4548 Decl : Node_Id;
4549 Item_Id : Entity_Id;
4550 States : Elist_Id := No_Elist;
4552 -- Start of processing for Collect_Body_States
4554 begin
4555 -- Inspect the declarations of the body looking for source objects,
4556 -- packages and package instantiations. Note that even though this
4557 -- processing is very similar to Collect_Visible_States, a package
4558 -- body does not have a First/Next_Entity list.
4560 Decl := First (Declarations (Body_Decl));
4561 while Present (Decl) loop
4563 -- Capture source objects as internally generated temporaries cannot
4564 -- be named and participate in refinement.
4566 if Nkind (Decl) = N_Object_Declaration then
4567 Item_Id := Defining_Entity (Decl);
4569 if Comes_From_Source (Item_Id)
4570 and then Is_Visible_Object (Item_Id)
4571 then
4572 Append_New_Elmt (Item_Id, States);
4573 end if;
4575 -- Capture the visible abstract states and objects of a source
4576 -- package [instantiation].
4578 elsif Nkind (Decl) = N_Package_Declaration then
4579 Item_Id := Defining_Entity (Decl);
4581 if Comes_From_Source (Item_Id) then
4582 Collect_Visible_States (Item_Id, States);
4583 end if;
4584 end if;
4586 Next (Decl);
4587 end loop;
4589 return States;
4590 end Collect_Body_States;
4592 ------------------------
4593 -- Collect_Interfaces --
4594 ------------------------
4596 procedure Collect_Interfaces
4597 (T : Entity_Id;
4598 Ifaces_List : out Elist_Id;
4599 Exclude_Parents : Boolean := False;
4600 Use_Full_View : Boolean := True)
4602 procedure Collect (Typ : Entity_Id);
4603 -- Subsidiary subprogram used to traverse the whole list
4604 -- of directly and indirectly implemented interfaces
4606 -------------
4607 -- Collect --
4608 -------------
4610 procedure Collect (Typ : Entity_Id) is
4611 Ancestor : Entity_Id;
4612 Full_T : Entity_Id;
4613 Id : Node_Id;
4614 Iface : Entity_Id;
4616 begin
4617 Full_T := Typ;
4619 -- Handle private types and subtypes
4621 if Use_Full_View
4622 and then Is_Private_Type (Typ)
4623 and then Present (Full_View (Typ))
4624 then
4625 Full_T := Full_View (Typ);
4627 if Ekind (Full_T) = E_Record_Subtype then
4628 Full_T := Etype (Typ);
4630 if Present (Full_View (Full_T)) then
4631 Full_T := Full_View (Full_T);
4632 end if;
4633 end if;
4634 end if;
4636 -- Include the ancestor if we are generating the whole list of
4637 -- abstract interfaces.
4639 if Etype (Full_T) /= Typ
4641 -- Protect the frontend against wrong sources. For example:
4643 -- package P is
4644 -- type A is tagged null record;
4645 -- type B is new A with private;
4646 -- type C is new A with private;
4647 -- private
4648 -- type B is new C with null record;
4649 -- type C is new B with null record;
4650 -- end P;
4652 and then Etype (Full_T) /= T
4653 then
4654 Ancestor := Etype (Full_T);
4655 Collect (Ancestor);
4657 if Is_Interface (Ancestor) and then not Exclude_Parents then
4658 Append_Unique_Elmt (Ancestor, Ifaces_List);
4659 end if;
4660 end if;
4662 -- Traverse the graph of ancestor interfaces
4664 if Is_Non_Empty_List (Abstract_Interface_List (Full_T)) then
4665 Id := First (Abstract_Interface_List (Full_T));
4666 while Present (Id) loop
4667 Iface := Etype (Id);
4669 -- Protect against wrong uses. For example:
4670 -- type I is interface;
4671 -- type O is tagged null record;
4672 -- type Wrong is new I and O with null record; -- ERROR
4674 if Is_Interface (Iface) then
4675 if Exclude_Parents
4676 and then Etype (T) /= T
4677 and then Interface_Present_In_Ancestor (Etype (T), Iface)
4678 then
4679 null;
4680 else
4681 Collect (Iface);
4682 Append_Unique_Elmt (Iface, Ifaces_List);
4683 end if;
4684 end if;
4686 Next (Id);
4687 end loop;
4688 end if;
4689 end Collect;
4691 -- Start of processing for Collect_Interfaces
4693 begin
4694 pragma Assert (Is_Tagged_Type (T) or else Is_Concurrent_Type (T));
4695 Ifaces_List := New_Elmt_List;
4696 Collect (T);
4697 end Collect_Interfaces;
4699 ----------------------------------
4700 -- Collect_Interface_Components --
4701 ----------------------------------
4703 procedure Collect_Interface_Components
4704 (Tagged_Type : Entity_Id;
4705 Components_List : out Elist_Id)
4707 procedure Collect (Typ : Entity_Id);
4708 -- Subsidiary subprogram used to climb to the parents
4710 -------------
4711 -- Collect --
4712 -------------
4714 procedure Collect (Typ : Entity_Id) is
4715 Tag_Comp : Entity_Id;
4716 Parent_Typ : Entity_Id;
4718 begin
4719 -- Handle private types
4721 if Present (Full_View (Etype (Typ))) then
4722 Parent_Typ := Full_View (Etype (Typ));
4723 else
4724 Parent_Typ := Etype (Typ);
4725 end if;
4727 if Parent_Typ /= Typ
4729 -- Protect the frontend against wrong sources. For example:
4731 -- package P is
4732 -- type A is tagged null record;
4733 -- type B is new A with private;
4734 -- type C is new A with private;
4735 -- private
4736 -- type B is new C with null record;
4737 -- type C is new B with null record;
4738 -- end P;
4740 and then Parent_Typ /= Tagged_Type
4741 then
4742 Collect (Parent_Typ);
4743 end if;
4745 -- Collect the components containing tags of secondary dispatch
4746 -- tables.
4748 Tag_Comp := Next_Tag_Component (First_Tag_Component (Typ));
4749 while Present (Tag_Comp) loop
4750 pragma Assert (Present (Related_Type (Tag_Comp)));
4751 Append_Elmt (Tag_Comp, Components_List);
4753 Tag_Comp := Next_Tag_Component (Tag_Comp);
4754 end loop;
4755 end Collect;
4757 -- Start of processing for Collect_Interface_Components
4759 begin
4760 pragma Assert (Ekind (Tagged_Type) = E_Record_Type
4761 and then Is_Tagged_Type (Tagged_Type));
4763 Components_List := New_Elmt_List;
4764 Collect (Tagged_Type);
4765 end Collect_Interface_Components;
4767 -----------------------------
4768 -- Collect_Interfaces_Info --
4769 -----------------------------
4771 procedure Collect_Interfaces_Info
4772 (T : Entity_Id;
4773 Ifaces_List : out Elist_Id;
4774 Components_List : out Elist_Id;
4775 Tags_List : out Elist_Id)
4777 Comps_List : Elist_Id;
4778 Comp_Elmt : Elmt_Id;
4779 Comp_Iface : Entity_Id;
4780 Iface_Elmt : Elmt_Id;
4781 Iface : Entity_Id;
4783 function Search_Tag (Iface : Entity_Id) return Entity_Id;
4784 -- Search for the secondary tag associated with the interface type
4785 -- Iface that is implemented by T.
4787 ----------------
4788 -- Search_Tag --
4789 ----------------
4791 function Search_Tag (Iface : Entity_Id) return Entity_Id is
4792 ADT : Elmt_Id;
4793 begin
4794 if not Is_CPP_Class (T) then
4795 ADT := Next_Elmt (Next_Elmt (First_Elmt (Access_Disp_Table (T))));
4796 else
4797 ADT := Next_Elmt (First_Elmt (Access_Disp_Table (T)));
4798 end if;
4800 while Present (ADT)
4801 and then Is_Tag (Node (ADT))
4802 and then Related_Type (Node (ADT)) /= Iface
4803 loop
4804 -- Skip secondary dispatch table referencing thunks to user
4805 -- defined primitives covered by this interface.
4807 pragma Assert (Has_Suffix (Node (ADT), 'P'));
4808 Next_Elmt (ADT);
4810 -- Skip secondary dispatch tables of Ada types
4812 if not Is_CPP_Class (T) then
4814 -- Skip secondary dispatch table referencing thunks to
4815 -- predefined primitives.
4817 pragma Assert (Has_Suffix (Node (ADT), 'Y'));
4818 Next_Elmt (ADT);
4820 -- Skip secondary dispatch table referencing user-defined
4821 -- primitives covered by this interface.
4823 pragma Assert (Has_Suffix (Node (ADT), 'D'));
4824 Next_Elmt (ADT);
4826 -- Skip secondary dispatch table referencing predefined
4827 -- primitives.
4829 pragma Assert (Has_Suffix (Node (ADT), 'Z'));
4830 Next_Elmt (ADT);
4831 end if;
4832 end loop;
4834 pragma Assert (Is_Tag (Node (ADT)));
4835 return Node (ADT);
4836 end Search_Tag;
4838 -- Start of processing for Collect_Interfaces_Info
4840 begin
4841 Collect_Interfaces (T, Ifaces_List);
4842 Collect_Interface_Components (T, Comps_List);
4844 -- Search for the record component and tag associated with each
4845 -- interface type of T.
4847 Components_List := New_Elmt_List;
4848 Tags_List := New_Elmt_List;
4850 Iface_Elmt := First_Elmt (Ifaces_List);
4851 while Present (Iface_Elmt) loop
4852 Iface := Node (Iface_Elmt);
4854 -- Associate the primary tag component and the primary dispatch table
4855 -- with all the interfaces that are parents of T
4857 if Is_Ancestor (Iface, T, Use_Full_View => True) then
4858 Append_Elmt (First_Tag_Component (T), Components_List);
4859 Append_Elmt (Node (First_Elmt (Access_Disp_Table (T))), Tags_List);
4861 -- Otherwise search for the tag component and secondary dispatch
4862 -- table of Iface
4864 else
4865 Comp_Elmt := First_Elmt (Comps_List);
4866 while Present (Comp_Elmt) loop
4867 Comp_Iface := Related_Type (Node (Comp_Elmt));
4869 if Comp_Iface = Iface
4870 or else Is_Ancestor (Iface, Comp_Iface, Use_Full_View => True)
4871 then
4872 Append_Elmt (Node (Comp_Elmt), Components_List);
4873 Append_Elmt (Search_Tag (Comp_Iface), Tags_List);
4874 exit;
4875 end if;
4877 Next_Elmt (Comp_Elmt);
4878 end loop;
4879 pragma Assert (Present (Comp_Elmt));
4880 end if;
4882 Next_Elmt (Iface_Elmt);
4883 end loop;
4884 end Collect_Interfaces_Info;
4886 ---------------------
4887 -- Collect_Parents --
4888 ---------------------
4890 procedure Collect_Parents
4891 (T : Entity_Id;
4892 List : out Elist_Id;
4893 Use_Full_View : Boolean := True)
4895 Current_Typ : Entity_Id := T;
4896 Parent_Typ : Entity_Id;
4898 begin
4899 List := New_Elmt_List;
4901 -- No action if the if the type has no parents
4903 if T = Etype (T) then
4904 return;
4905 end if;
4907 loop
4908 Parent_Typ := Etype (Current_Typ);
4910 if Is_Private_Type (Parent_Typ)
4911 and then Present (Full_View (Parent_Typ))
4912 and then Use_Full_View
4913 then
4914 Parent_Typ := Full_View (Base_Type (Parent_Typ));
4915 end if;
4917 Append_Elmt (Parent_Typ, List);
4919 exit when Parent_Typ = Current_Typ;
4920 Current_Typ := Parent_Typ;
4921 end loop;
4922 end Collect_Parents;
4924 ----------------------------------
4925 -- Collect_Primitive_Operations --
4926 ----------------------------------
4928 function Collect_Primitive_Operations (T : Entity_Id) return Elist_Id is
4929 B_Type : constant Entity_Id := Base_Type (T);
4930 B_Decl : constant Node_Id := Original_Node (Parent (B_Type));
4931 B_Scope : Entity_Id := Scope (B_Type);
4932 Op_List : Elist_Id;
4933 Formal : Entity_Id;
4934 Is_Prim : Boolean;
4935 Is_Type_In_Pkg : Boolean;
4936 Formal_Derived : Boolean := False;
4937 Id : Entity_Id;
4939 function Match (E : Entity_Id) return Boolean;
4940 -- True if E's base type is B_Type, or E is of an anonymous access type
4941 -- and the base type of its designated type is B_Type.
4943 -----------
4944 -- Match --
4945 -----------
4947 function Match (E : Entity_Id) return Boolean is
4948 Etyp : Entity_Id := Etype (E);
4950 begin
4951 if Ekind (Etyp) = E_Anonymous_Access_Type then
4952 Etyp := Designated_Type (Etyp);
4953 end if;
4955 -- In Ada 2012 a primitive operation may have a formal of an
4956 -- incomplete view of the parent type.
4958 return Base_Type (Etyp) = B_Type
4959 or else
4960 (Ada_Version >= Ada_2012
4961 and then Ekind (Etyp) = E_Incomplete_Type
4962 and then Full_View (Etyp) = B_Type);
4963 end Match;
4965 -- Start of processing for Collect_Primitive_Operations
4967 begin
4968 -- For tagged types, the primitive operations are collected as they
4969 -- are declared, and held in an explicit list which is simply returned.
4971 if Is_Tagged_Type (B_Type) then
4972 return Primitive_Operations (B_Type);
4974 -- An untagged generic type that is a derived type inherits the
4975 -- primitive operations of its parent type. Other formal types only
4976 -- have predefined operators, which are not explicitly represented.
4978 elsif Is_Generic_Type (B_Type) then
4979 if Nkind (B_Decl) = N_Formal_Type_Declaration
4980 and then Nkind (Formal_Type_Definition (B_Decl)) =
4981 N_Formal_Derived_Type_Definition
4982 then
4983 Formal_Derived := True;
4984 else
4985 return New_Elmt_List;
4986 end if;
4987 end if;
4989 Op_List := New_Elmt_List;
4991 if B_Scope = Standard_Standard then
4992 if B_Type = Standard_String then
4993 Append_Elmt (Standard_Op_Concat, Op_List);
4995 elsif B_Type = Standard_Wide_String then
4996 Append_Elmt (Standard_Op_Concatw, Op_List);
4998 else
4999 null;
5000 end if;
5002 -- Locate the primitive subprograms of the type
5004 else
5005 -- The primitive operations appear after the base type, except
5006 -- if the derivation happens within the private part of B_Scope
5007 -- and the type is a private type, in which case both the type
5008 -- and some primitive operations may appear before the base
5009 -- type, and the list of candidates starts after the type.
5011 if In_Open_Scopes (B_Scope)
5012 and then Scope (T) = B_Scope
5013 and then In_Private_Part (B_Scope)
5014 then
5015 Id := Next_Entity (T);
5017 -- In Ada 2012, If the type has an incomplete partial view, there
5018 -- may be primitive operations declared before the full view, so
5019 -- we need to start scanning from the incomplete view, which is
5020 -- earlier on the entity chain.
5022 elsif Nkind (Parent (B_Type)) = N_Full_Type_Declaration
5023 and then Present (Incomplete_View (Parent (B_Type)))
5024 then
5025 Id := Defining_Entity (Incomplete_View (Parent (B_Type)));
5027 -- If T is a derived from a type with an incomplete view declared
5028 -- elsewhere, that incomplete view is irrelevant, we want the
5029 -- operations in the scope of T.
5031 if Scope (Id) /= Scope (B_Type) then
5032 Id := Next_Entity (B_Type);
5033 end if;
5035 else
5036 Id := Next_Entity (B_Type);
5037 end if;
5039 -- Set flag if this is a type in a package spec
5041 Is_Type_In_Pkg :=
5042 Is_Package_Or_Generic_Package (B_Scope)
5043 and then
5044 Nkind (Parent (Declaration_Node (First_Subtype (T)))) /=
5045 N_Package_Body;
5047 while Present (Id) loop
5049 -- Test whether the result type or any of the parameter types of
5050 -- each subprogram following the type match that type when the
5051 -- type is declared in a package spec, is a derived type, or the
5052 -- subprogram is marked as primitive. (The Is_Primitive test is
5053 -- needed to find primitives of nonderived types in declarative
5054 -- parts that happen to override the predefined "=" operator.)
5056 -- Note that generic formal subprograms are not considered to be
5057 -- primitive operations and thus are never inherited.
5059 if Is_Overloadable (Id)
5060 and then (Is_Type_In_Pkg
5061 or else Is_Derived_Type (B_Type)
5062 or else Is_Primitive (Id))
5063 and then Nkind (Parent (Parent (Id)))
5064 not in N_Formal_Subprogram_Declaration
5065 then
5066 Is_Prim := False;
5068 if Match (Id) then
5069 Is_Prim := True;
5071 else
5072 Formal := First_Formal (Id);
5073 while Present (Formal) loop
5074 if Match (Formal) then
5075 Is_Prim := True;
5076 exit;
5077 end if;
5079 Next_Formal (Formal);
5080 end loop;
5081 end if;
5083 -- For a formal derived type, the only primitives are the ones
5084 -- inherited from the parent type. Operations appearing in the
5085 -- package declaration are not primitive for it.
5087 if Is_Prim
5088 and then (not Formal_Derived or else Present (Alias (Id)))
5089 then
5090 -- In the special case of an equality operator aliased to
5091 -- an overriding dispatching equality belonging to the same
5092 -- type, we don't include it in the list of primitives.
5093 -- This avoids inheriting multiple equality operators when
5094 -- deriving from untagged private types whose full type is
5095 -- tagged, which can otherwise cause ambiguities. Note that
5096 -- this should only happen for this kind of untagged parent
5097 -- type, since normally dispatching operations are inherited
5098 -- using the type's Primitive_Operations list.
5100 if Chars (Id) = Name_Op_Eq
5101 and then Is_Dispatching_Operation (Id)
5102 and then Present (Alias (Id))
5103 and then Present (Overridden_Operation (Alias (Id)))
5104 and then Base_Type (Etype (First_Entity (Id))) =
5105 Base_Type (Etype (First_Entity (Alias (Id))))
5106 then
5107 null;
5109 -- Include the subprogram in the list of primitives
5111 else
5112 Append_Elmt (Id, Op_List);
5113 end if;
5114 end if;
5115 end if;
5117 Next_Entity (Id);
5119 -- For a type declared in System, some of its operations may
5120 -- appear in the target-specific extension to System.
5122 if No (Id)
5123 and then B_Scope = RTU_Entity (System)
5124 and then Present_System_Aux
5125 then
5126 B_Scope := System_Aux_Id;
5127 Id := First_Entity (System_Aux_Id);
5128 end if;
5129 end loop;
5130 end if;
5132 return Op_List;
5133 end Collect_Primitive_Operations;
5135 -----------------------------------
5136 -- Compile_Time_Constraint_Error --
5137 -----------------------------------
5139 function Compile_Time_Constraint_Error
5140 (N : Node_Id;
5141 Msg : String;
5142 Ent : Entity_Id := Empty;
5143 Loc : Source_Ptr := No_Location;
5144 Warn : Boolean := False) return Node_Id
5146 Msgc : String (1 .. Msg'Length + 3);
5147 -- Copy of message, with room for possible ?? or << and ! at end
5149 Msgl : Natural;
5150 Wmsg : Boolean;
5151 Eloc : Source_Ptr;
5153 -- Start of processing for Compile_Time_Constraint_Error
5155 begin
5156 -- If this is a warning, convert it into an error if we are in code
5157 -- subject to SPARK_Mode being set On, unless Warn is True to force a
5158 -- warning. The rationale is that a compile-time constraint error should
5159 -- lead to an error instead of a warning when SPARK_Mode is On, but in
5160 -- a few cases we prefer to issue a warning and generate both a suitable
5161 -- run-time error in GNAT and a suitable check message in GNATprove.
5162 -- Those cases are those that likely correspond to deactivated SPARK
5163 -- code, so that this kind of code can be compiled and analyzed instead
5164 -- of being rejected.
5166 Error_Msg_Warn := Warn or SPARK_Mode /= On;
5168 -- A static constraint error in an instance body is not a fatal error.
5169 -- we choose to inhibit the message altogether, because there is no
5170 -- obvious node (for now) on which to post it. On the other hand the
5171 -- offending node must be replaced with a constraint_error in any case.
5173 -- No messages are generated if we already posted an error on this node
5175 if not Error_Posted (N) then
5176 if Loc /= No_Location then
5177 Eloc := Loc;
5178 else
5179 Eloc := Sloc (N);
5180 end if;
5182 -- Copy message to Msgc, converting any ? in the message into <
5183 -- instead, so that we have an error in GNATprove mode.
5185 Msgl := Msg'Length;
5187 for J in 1 .. Msgl loop
5188 if Msg (J) = '?' and then (J = 1 or else Msg (J - 1) /= ''') then
5189 Msgc (J) := '<';
5190 else
5191 Msgc (J) := Msg (J);
5192 end if;
5193 end loop;
5195 -- Message is a warning, even in Ada 95 case
5197 if Msg (Msg'Last) = '?' or else Msg (Msg'Last) = '<' then
5198 Wmsg := True;
5200 -- In Ada 83, all messages are warnings. In the private part and the
5201 -- body of an instance, constraint_checks are only warnings. We also
5202 -- make this a warning if the Warn parameter is set.
5204 elsif Warn
5205 or else (Ada_Version = Ada_83 and then Comes_From_Source (N))
5206 or else In_Instance_Not_Visible
5207 then
5208 Msgl := Msgl + 1;
5209 Msgc (Msgl) := '<';
5210 Msgl := Msgl + 1;
5211 Msgc (Msgl) := '<';
5212 Wmsg := True;
5214 -- Otherwise we have a real error message (Ada 95 static case) and we
5215 -- make this an unconditional message. Note that in the warning case
5216 -- we do not make the message unconditional, it seems reasonable to
5217 -- delete messages like this (about exceptions that will be raised)
5218 -- in dead code.
5220 else
5221 Wmsg := False;
5222 Msgl := Msgl + 1;
5223 Msgc (Msgl) := '!';
5224 end if;
5226 -- One more test, skip the warning if the related expression is
5227 -- statically unevaluated, since we don't want to warn about what
5228 -- will happen when something is evaluated if it never will be
5229 -- evaluated.
5231 if not Is_Statically_Unevaluated (N) then
5232 if Present (Ent) then
5233 Error_Msg_NEL (Msgc (1 .. Msgl), N, Ent, Eloc);
5234 else
5235 Error_Msg_NEL (Msgc (1 .. Msgl), N, Etype (N), Eloc);
5236 end if;
5238 if Wmsg then
5240 -- Check whether the context is an Init_Proc
5242 if Inside_Init_Proc then
5243 declare
5244 Conc_Typ : constant Entity_Id :=
5245 Corresponding_Concurrent_Type
5246 (Entity (Parameter_Type (First
5247 (Parameter_Specifications
5248 (Parent (Current_Scope))))));
5250 begin
5251 -- Don't complain if the corresponding concurrent type
5252 -- doesn't come from source (i.e. a single task/protected
5253 -- object).
5255 if Present (Conc_Typ)
5256 and then not Comes_From_Source (Conc_Typ)
5257 then
5258 Error_Msg_NEL
5259 ("\& [<<", N, Standard_Constraint_Error, Eloc);
5261 else
5262 if GNATprove_Mode then
5263 Error_Msg_NEL
5264 ("\& would have been raised for objects of this "
5265 & "type", N, Standard_Constraint_Error, Eloc);
5266 else
5267 Error_Msg_NEL
5268 ("\& will be raised for objects of this type??",
5269 N, Standard_Constraint_Error, Eloc);
5270 end if;
5271 end if;
5272 end;
5274 else
5275 Error_Msg_NEL ("\& [<<", N, Standard_Constraint_Error, Eloc);
5276 end if;
5278 else
5279 Error_Msg ("\static expression fails Constraint_Check", Eloc);
5280 Set_Error_Posted (N);
5281 end if;
5282 end if;
5283 end if;
5285 return N;
5286 end Compile_Time_Constraint_Error;
5288 -----------------------
5289 -- Conditional_Delay --
5290 -----------------------
5292 procedure Conditional_Delay (New_Ent, Old_Ent : Entity_Id) is
5293 begin
5294 if Has_Delayed_Freeze (Old_Ent) and then not Is_Frozen (Old_Ent) then
5295 Set_Has_Delayed_Freeze (New_Ent);
5296 end if;
5297 end Conditional_Delay;
5299 -------------------------
5300 -- Copy_Component_List --
5301 -------------------------
5303 function Copy_Component_List
5304 (R_Typ : Entity_Id;
5305 Loc : Source_Ptr) return List_Id
5307 Comp : Node_Id;
5308 Comps : constant List_Id := New_List;
5310 begin
5311 Comp := First_Component (Underlying_Type (R_Typ));
5312 while Present (Comp) loop
5313 if Comes_From_Source (Comp) then
5314 declare
5315 Comp_Decl : constant Node_Id := Declaration_Node (Comp);
5316 begin
5317 Append_To (Comps,
5318 Make_Component_Declaration (Loc,
5319 Defining_Identifier =>
5320 Make_Defining_Identifier (Loc, Chars (Comp)),
5321 Component_Definition =>
5322 New_Copy_Tree
5323 (Component_Definition (Comp_Decl), New_Sloc => Loc)));
5324 end;
5325 end if;
5327 Next_Component (Comp);
5328 end loop;
5330 return Comps;
5331 end Copy_Component_List;
5333 -------------------------
5334 -- Copy_Parameter_List --
5335 -------------------------
5337 function Copy_Parameter_List (Subp_Id : Entity_Id) return List_Id is
5338 Loc : constant Source_Ptr := Sloc (Subp_Id);
5339 Plist : List_Id;
5340 Formal : Entity_Id;
5342 begin
5343 if No (First_Formal (Subp_Id)) then
5344 return No_List;
5345 else
5346 Plist := New_List;
5347 Formal := First_Formal (Subp_Id);
5348 while Present (Formal) loop
5349 Append_To (Plist,
5350 Make_Parameter_Specification (Loc,
5351 Defining_Identifier =>
5352 Make_Defining_Identifier (Sloc (Formal), Chars (Formal)),
5353 In_Present => In_Present (Parent (Formal)),
5354 Out_Present => Out_Present (Parent (Formal)),
5355 Parameter_Type =>
5356 New_Occurrence_Of (Etype (Formal), Loc),
5357 Expression =>
5358 New_Copy_Tree (Expression (Parent (Formal)))));
5360 Next_Formal (Formal);
5361 end loop;
5362 end if;
5364 return Plist;
5365 end Copy_Parameter_List;
5367 ----------------------------
5368 -- Copy_SPARK_Mode_Aspect --
5369 ----------------------------
5371 procedure Copy_SPARK_Mode_Aspect (From : Node_Id; To : Node_Id) is
5372 pragma Assert (not Has_Aspects (To));
5373 Asp : Node_Id;
5375 begin
5376 if Has_Aspects (From) then
5377 Asp := Find_Aspect (Defining_Entity (From), Aspect_SPARK_Mode);
5379 if Present (Asp) then
5380 Set_Aspect_Specifications (To, New_List (New_Copy_Tree (Asp)));
5381 Set_Has_Aspects (To, True);
5382 end if;
5383 end if;
5384 end Copy_SPARK_Mode_Aspect;
5386 --------------------------
5387 -- Copy_Subprogram_Spec --
5388 --------------------------
5390 function Copy_Subprogram_Spec (Spec : Node_Id) return Node_Id is
5391 Def_Id : Node_Id;
5392 Formal_Spec : Node_Id;
5393 Result : Node_Id;
5395 begin
5396 -- The structure of the original tree must be replicated without any
5397 -- alterations. Use New_Copy_Tree for this purpose.
5399 Result := New_Copy_Tree (Spec);
5401 -- However, the spec of a null procedure carries the corresponding null
5402 -- statement of the body (created by the parser), and this cannot be
5403 -- shared with the new subprogram spec.
5405 if Nkind (Result) = N_Procedure_Specification then
5406 Set_Null_Statement (Result, Empty);
5407 end if;
5409 -- Create a new entity for the defining unit name
5411 Def_Id := Defining_Unit_Name (Result);
5412 Set_Defining_Unit_Name (Result,
5413 Make_Defining_Identifier (Sloc (Def_Id), Chars (Def_Id)));
5415 -- Create new entities for the formal parameters
5417 if Present (Parameter_Specifications (Result)) then
5418 Formal_Spec := First (Parameter_Specifications (Result));
5419 while Present (Formal_Spec) loop
5420 Def_Id := Defining_Identifier (Formal_Spec);
5421 Set_Defining_Identifier (Formal_Spec,
5422 Make_Defining_Identifier (Sloc (Def_Id), Chars (Def_Id)));
5424 Next (Formal_Spec);
5425 end loop;
5426 end if;
5428 return Result;
5429 end Copy_Subprogram_Spec;
5431 --------------------------------
5432 -- Corresponding_Generic_Type --
5433 --------------------------------
5435 function Corresponding_Generic_Type (T : Entity_Id) return Entity_Id is
5436 Inst : Entity_Id;
5437 Gen : Entity_Id;
5438 Typ : Entity_Id;
5440 begin
5441 if not Is_Generic_Actual_Type (T) then
5442 return Any_Type;
5444 -- If the actual is the actual of an enclosing instance, resolution
5445 -- was correct in the generic.
5447 elsif Nkind (Parent (T)) = N_Subtype_Declaration
5448 and then Is_Entity_Name (Subtype_Indication (Parent (T)))
5449 and then
5450 Is_Generic_Actual_Type (Entity (Subtype_Indication (Parent (T))))
5451 then
5452 return Any_Type;
5454 else
5455 Inst := Scope (T);
5457 if Is_Wrapper_Package (Inst) then
5458 Inst := Related_Instance (Inst);
5459 end if;
5461 Gen :=
5462 Generic_Parent
5463 (Specification (Unit_Declaration_Node (Inst)));
5465 -- Generic actual has the same name as the corresponding formal
5467 Typ := First_Entity (Gen);
5468 while Present (Typ) loop
5469 if Chars (Typ) = Chars (T) then
5470 return Typ;
5471 end if;
5473 Next_Entity (Typ);
5474 end loop;
5476 return Any_Type;
5477 end if;
5478 end Corresponding_Generic_Type;
5480 --------------------
5481 -- Current_Entity --
5482 --------------------
5484 -- The currently visible definition for a given identifier is the
5485 -- one most chained at the start of the visibility chain, i.e. the
5486 -- one that is referenced by the Node_Id value of the name of the
5487 -- given identifier.
5489 function Current_Entity (N : Node_Id) return Entity_Id is
5490 begin
5491 return Get_Name_Entity_Id (Chars (N));
5492 end Current_Entity;
5494 -----------------------------
5495 -- Current_Entity_In_Scope --
5496 -----------------------------
5498 function Current_Entity_In_Scope (N : Node_Id) return Entity_Id is
5499 E : Entity_Id;
5500 CS : constant Entity_Id := Current_Scope;
5502 Transient_Case : constant Boolean := Scope_Is_Transient;
5504 begin
5505 E := Get_Name_Entity_Id (Chars (N));
5506 while Present (E)
5507 and then Scope (E) /= CS
5508 and then (not Transient_Case or else Scope (E) /= Scope (CS))
5509 loop
5510 E := Homonym (E);
5511 end loop;
5513 return E;
5514 end Current_Entity_In_Scope;
5516 -------------------
5517 -- Current_Scope --
5518 -------------------
5520 function Current_Scope return Entity_Id is
5521 begin
5522 if Scope_Stack.Last = -1 then
5523 return Standard_Standard;
5524 else
5525 declare
5526 C : constant Entity_Id :=
5527 Scope_Stack.Table (Scope_Stack.Last).Entity;
5528 begin
5529 if Present (C) then
5530 return C;
5531 else
5532 return Standard_Standard;
5533 end if;
5534 end;
5535 end if;
5536 end Current_Scope;
5538 ----------------------------
5539 -- Current_Scope_No_Loops --
5540 ----------------------------
5542 function Current_Scope_No_Loops return Entity_Id is
5543 S : Entity_Id;
5545 begin
5546 -- Examine the scope stack starting from the current scope and skip any
5547 -- internally generated loops.
5549 S := Current_Scope;
5550 while Present (S) and then S /= Standard_Standard loop
5551 if Ekind (S) = E_Loop and then not Comes_From_Source (S) then
5552 S := Scope (S);
5553 else
5554 exit;
5555 end if;
5556 end loop;
5558 return S;
5559 end Current_Scope_No_Loops;
5561 ------------------------
5562 -- Current_Subprogram --
5563 ------------------------
5565 function Current_Subprogram return Entity_Id is
5566 Scop : constant Entity_Id := Current_Scope;
5567 begin
5568 if Is_Subprogram_Or_Generic_Subprogram (Scop) then
5569 return Scop;
5570 else
5571 return Enclosing_Subprogram (Scop);
5572 end if;
5573 end Current_Subprogram;
5575 ----------------------------------
5576 -- Deepest_Type_Access_Level --
5577 ----------------------------------
5579 function Deepest_Type_Access_Level (Typ : Entity_Id) return Uint is
5580 begin
5581 if Ekind (Typ) = E_Anonymous_Access_Type
5582 and then not Is_Local_Anonymous_Access (Typ)
5583 and then Nkind (Associated_Node_For_Itype (Typ)) = N_Object_Declaration
5584 then
5585 -- Typ is the type of an Ada 2012 stand-alone object of an anonymous
5586 -- access type.
5588 return
5589 Scope_Depth (Enclosing_Dynamic_Scope
5590 (Defining_Identifier
5591 (Associated_Node_For_Itype (Typ))));
5593 -- For generic formal type, return Int'Last (infinite).
5594 -- See comment preceding Is_Generic_Type call in Type_Access_Level.
5596 elsif Is_Generic_Type (Root_Type (Typ)) then
5597 return UI_From_Int (Int'Last);
5599 else
5600 return Type_Access_Level (Typ);
5601 end if;
5602 end Deepest_Type_Access_Level;
5604 ---------------------
5605 -- Defining_Entity --
5606 ---------------------
5608 function Defining_Entity
5609 (N : Node_Id;
5610 Empty_On_Errors : Boolean := False;
5611 Concurrent_Subunit : Boolean := False) return Entity_Id
5613 begin
5614 case Nkind (N) is
5615 when N_Abstract_Subprogram_Declaration
5616 | N_Expression_Function
5617 | N_Formal_Subprogram_Declaration
5618 | N_Generic_Package_Declaration
5619 | N_Generic_Subprogram_Declaration
5620 | N_Package_Declaration
5621 | N_Subprogram_Body
5622 | N_Subprogram_Body_Stub
5623 | N_Subprogram_Declaration
5624 | N_Subprogram_Renaming_Declaration
5626 return Defining_Entity (Specification (N));
5628 when N_Component_Declaration
5629 | N_Defining_Program_Unit_Name
5630 | N_Discriminant_Specification
5631 | N_Entry_Body
5632 | N_Entry_Declaration
5633 | N_Entry_Index_Specification
5634 | N_Exception_Declaration
5635 | N_Exception_Renaming_Declaration
5636 | N_Formal_Object_Declaration
5637 | N_Formal_Package_Declaration
5638 | N_Formal_Type_Declaration
5639 | N_Full_Type_Declaration
5640 | N_Implicit_Label_Declaration
5641 | N_Incomplete_Type_Declaration
5642 | N_Iterator_Specification
5643 | N_Loop_Parameter_Specification
5644 | N_Number_Declaration
5645 | N_Object_Declaration
5646 | N_Object_Renaming_Declaration
5647 | N_Package_Body_Stub
5648 | N_Parameter_Specification
5649 | N_Private_Extension_Declaration
5650 | N_Private_Type_Declaration
5651 | N_Protected_Body
5652 | N_Protected_Body_Stub
5653 | N_Protected_Type_Declaration
5654 | N_Single_Protected_Declaration
5655 | N_Single_Task_Declaration
5656 | N_Subtype_Declaration
5657 | N_Task_Body
5658 | N_Task_Body_Stub
5659 | N_Task_Type_Declaration
5661 return Defining_Identifier (N);
5663 when N_Subunit =>
5664 declare
5665 Bod : constant Node_Id := Proper_Body (N);
5666 Orig_Bod : constant Node_Id := Original_Node (Bod);
5668 begin
5669 -- Retrieve the entity of the original protected or task body
5670 -- if requested by the caller.
5672 if Concurrent_Subunit
5673 and then Nkind (Bod) = N_Null_Statement
5674 and then Nkind_In (Orig_Bod, N_Protected_Body, N_Task_Body)
5675 then
5676 return Defining_Entity (Orig_Bod);
5677 else
5678 return Defining_Entity (Bod);
5679 end if;
5680 end;
5682 when N_Function_Instantiation
5683 | N_Function_Specification
5684 | N_Generic_Function_Renaming_Declaration
5685 | N_Generic_Package_Renaming_Declaration
5686 | N_Generic_Procedure_Renaming_Declaration
5687 | N_Package_Body
5688 | N_Package_Instantiation
5689 | N_Package_Renaming_Declaration
5690 | N_Package_Specification
5691 | N_Procedure_Instantiation
5692 | N_Procedure_Specification
5694 declare
5695 Nam : constant Node_Id := Defining_Unit_Name (N);
5696 Err : Entity_Id := Empty;
5698 begin
5699 if Nkind (Nam) in N_Entity then
5700 return Nam;
5702 -- For Error, make up a name and attach to declaration so we
5703 -- can continue semantic analysis.
5705 elsif Nam = Error then
5706 if Empty_On_Errors then
5707 return Empty;
5708 else
5709 Err := Make_Temporary (Sloc (N), 'T');
5710 Set_Defining_Unit_Name (N, Err);
5712 return Err;
5713 end if;
5715 -- If not an entity, get defining identifier
5717 else
5718 return Defining_Identifier (Nam);
5719 end if;
5720 end;
5722 when N_Block_Statement
5723 | N_Loop_Statement
5725 return Entity (Identifier (N));
5727 when others =>
5728 if Empty_On_Errors then
5729 return Empty;
5730 else
5731 raise Program_Error;
5732 end if;
5733 end case;
5734 end Defining_Entity;
5736 --------------------------
5737 -- Denotes_Discriminant --
5738 --------------------------
5740 function Denotes_Discriminant
5741 (N : Node_Id;
5742 Check_Concurrent : Boolean := False) return Boolean
5744 E : Entity_Id;
5746 begin
5747 if not Is_Entity_Name (N) or else No (Entity (N)) then
5748 return False;
5749 else
5750 E := Entity (N);
5751 end if;
5753 -- If we are checking for a protected type, the discriminant may have
5754 -- been rewritten as the corresponding discriminal of the original type
5755 -- or of the corresponding concurrent record, depending on whether we
5756 -- are in the spec or body of the protected type.
5758 return Ekind (E) = E_Discriminant
5759 or else
5760 (Check_Concurrent
5761 and then Ekind (E) = E_In_Parameter
5762 and then Present (Discriminal_Link (E))
5763 and then
5764 (Is_Concurrent_Type (Scope (Discriminal_Link (E)))
5765 or else
5766 Is_Concurrent_Record_Type (Scope (Discriminal_Link (E)))));
5767 end Denotes_Discriminant;
5769 -------------------------
5770 -- Denotes_Same_Object --
5771 -------------------------
5773 function Denotes_Same_Object (A1, A2 : Node_Id) return Boolean is
5774 Obj1 : Node_Id := A1;
5775 Obj2 : Node_Id := A2;
5777 function Has_Prefix (N : Node_Id) return Boolean;
5778 -- Return True if N has attribute Prefix
5780 function Is_Renaming (N : Node_Id) return Boolean;
5781 -- Return true if N names a renaming entity
5783 function Is_Valid_Renaming (N : Node_Id) return Boolean;
5784 -- For renamings, return False if the prefix of any dereference within
5785 -- the renamed object_name is a variable, or any expression within the
5786 -- renamed object_name contains references to variables or calls on
5787 -- nonstatic functions; otherwise return True (RM 6.4.1(6.10/3))
5789 ----------------
5790 -- Has_Prefix --
5791 ----------------
5793 function Has_Prefix (N : Node_Id) return Boolean is
5794 begin
5795 return
5796 Nkind_In (N,
5797 N_Attribute_Reference,
5798 N_Expanded_Name,
5799 N_Explicit_Dereference,
5800 N_Indexed_Component,
5801 N_Reference,
5802 N_Selected_Component,
5803 N_Slice);
5804 end Has_Prefix;
5806 -----------------
5807 -- Is_Renaming --
5808 -----------------
5810 function Is_Renaming (N : Node_Id) return Boolean is
5811 begin
5812 return Is_Entity_Name (N)
5813 and then Present (Renamed_Entity (Entity (N)));
5814 end Is_Renaming;
5816 -----------------------
5817 -- Is_Valid_Renaming --
5818 -----------------------
5820 function Is_Valid_Renaming (N : Node_Id) return Boolean is
5822 function Check_Renaming (N : Node_Id) return Boolean;
5823 -- Recursive function used to traverse all the prefixes of N
5825 function Check_Renaming (N : Node_Id) return Boolean is
5826 begin
5827 if Is_Renaming (N)
5828 and then not Check_Renaming (Renamed_Entity (Entity (N)))
5829 then
5830 return False;
5831 end if;
5833 if Nkind (N) = N_Indexed_Component then
5834 declare
5835 Indx : Node_Id;
5837 begin
5838 Indx := First (Expressions (N));
5839 while Present (Indx) loop
5840 if not Is_OK_Static_Expression (Indx) then
5841 return False;
5842 end if;
5844 Next_Index (Indx);
5845 end loop;
5846 end;
5847 end if;
5849 if Has_Prefix (N) then
5850 declare
5851 P : constant Node_Id := Prefix (N);
5853 begin
5854 if Nkind (N) = N_Explicit_Dereference
5855 and then Is_Variable (P)
5856 then
5857 return False;
5859 elsif Is_Entity_Name (P)
5860 and then Ekind (Entity (P)) = E_Function
5861 then
5862 return False;
5864 elsif Nkind (P) = N_Function_Call then
5865 return False;
5866 end if;
5868 -- Recursion to continue traversing the prefix of the
5869 -- renaming expression
5871 return Check_Renaming (P);
5872 end;
5873 end if;
5875 return True;
5876 end Check_Renaming;
5878 -- Start of processing for Is_Valid_Renaming
5880 begin
5881 return Check_Renaming (N);
5882 end Is_Valid_Renaming;
5884 -- Start of processing for Denotes_Same_Object
5886 begin
5887 -- Both names statically denote the same stand-alone object or parameter
5888 -- (RM 6.4.1(6.5/3))
5890 if Is_Entity_Name (Obj1)
5891 and then Is_Entity_Name (Obj2)
5892 and then Entity (Obj1) = Entity (Obj2)
5893 then
5894 return True;
5895 end if;
5897 -- For renamings, the prefix of any dereference within the renamed
5898 -- object_name is not a variable, and any expression within the
5899 -- renamed object_name contains no references to variables nor
5900 -- calls on nonstatic functions (RM 6.4.1(6.10/3)).
5902 if Is_Renaming (Obj1) then
5903 if Is_Valid_Renaming (Obj1) then
5904 Obj1 := Renamed_Entity (Entity (Obj1));
5905 else
5906 return False;
5907 end if;
5908 end if;
5910 if Is_Renaming (Obj2) then
5911 if Is_Valid_Renaming (Obj2) then
5912 Obj2 := Renamed_Entity (Entity (Obj2));
5913 else
5914 return False;
5915 end if;
5916 end if;
5918 -- No match if not same node kind (such cases are handled by
5919 -- Denotes_Same_Prefix)
5921 if Nkind (Obj1) /= Nkind (Obj2) then
5922 return False;
5924 -- After handling valid renamings, one of the two names statically
5925 -- denoted a renaming declaration whose renamed object_name is known
5926 -- to denote the same object as the other (RM 6.4.1(6.10/3))
5928 elsif Is_Entity_Name (Obj1) then
5929 if Is_Entity_Name (Obj2) then
5930 return Entity (Obj1) = Entity (Obj2);
5931 else
5932 return False;
5933 end if;
5935 -- Both names are selected_components, their prefixes are known to
5936 -- denote the same object, and their selector_names denote the same
5937 -- component (RM 6.4.1(6.6/3)).
5939 elsif Nkind (Obj1) = N_Selected_Component then
5940 return Denotes_Same_Object (Prefix (Obj1), Prefix (Obj2))
5941 and then
5942 Entity (Selector_Name (Obj1)) = Entity (Selector_Name (Obj2));
5944 -- Both names are dereferences and the dereferenced names are known to
5945 -- denote the same object (RM 6.4.1(6.7/3))
5947 elsif Nkind (Obj1) = N_Explicit_Dereference then
5948 return Denotes_Same_Object (Prefix (Obj1), Prefix (Obj2));
5950 -- Both names are indexed_components, their prefixes are known to denote
5951 -- the same object, and each of the pairs of corresponding index values
5952 -- are either both static expressions with the same static value or both
5953 -- names that are known to denote the same object (RM 6.4.1(6.8/3))
5955 elsif Nkind (Obj1) = N_Indexed_Component then
5956 if not Denotes_Same_Object (Prefix (Obj1), Prefix (Obj2)) then
5957 return False;
5958 else
5959 declare
5960 Indx1 : Node_Id;
5961 Indx2 : Node_Id;
5963 begin
5964 Indx1 := First (Expressions (Obj1));
5965 Indx2 := First (Expressions (Obj2));
5966 while Present (Indx1) loop
5968 -- Indexes must denote the same static value or same object
5970 if Is_OK_Static_Expression (Indx1) then
5971 if not Is_OK_Static_Expression (Indx2) then
5972 return False;
5974 elsif Expr_Value (Indx1) /= Expr_Value (Indx2) then
5975 return False;
5976 end if;
5978 elsif not Denotes_Same_Object (Indx1, Indx2) then
5979 return False;
5980 end if;
5982 Next (Indx1);
5983 Next (Indx2);
5984 end loop;
5986 return True;
5987 end;
5988 end if;
5990 -- Both names are slices, their prefixes are known to denote the same
5991 -- object, and the two slices have statically matching index constraints
5992 -- (RM 6.4.1(6.9/3))
5994 elsif Nkind (Obj1) = N_Slice
5995 and then Denotes_Same_Object (Prefix (Obj1), Prefix (Obj2))
5996 then
5997 declare
5998 Lo1, Lo2, Hi1, Hi2 : Node_Id;
6000 begin
6001 Get_Index_Bounds (Etype (Obj1), Lo1, Hi1);
6002 Get_Index_Bounds (Etype (Obj2), Lo2, Hi2);
6004 -- Check whether bounds are statically identical. There is no
6005 -- attempt to detect partial overlap of slices.
6007 return Denotes_Same_Object (Lo1, Lo2)
6008 and then
6009 Denotes_Same_Object (Hi1, Hi2);
6010 end;
6012 -- In the recursion, literals appear as indexes
6014 elsif Nkind (Obj1) = N_Integer_Literal
6015 and then
6016 Nkind (Obj2) = N_Integer_Literal
6017 then
6018 return Intval (Obj1) = Intval (Obj2);
6020 else
6021 return False;
6022 end if;
6023 end Denotes_Same_Object;
6025 -------------------------
6026 -- Denotes_Same_Prefix --
6027 -------------------------
6029 function Denotes_Same_Prefix (A1, A2 : Node_Id) return Boolean is
6030 begin
6031 if Is_Entity_Name (A1) then
6032 if Nkind_In (A2, N_Selected_Component, N_Indexed_Component)
6033 and then not Is_Access_Type (Etype (A1))
6034 then
6035 return Denotes_Same_Object (A1, Prefix (A2))
6036 or else Denotes_Same_Prefix (A1, Prefix (A2));
6037 else
6038 return False;
6039 end if;
6041 elsif Is_Entity_Name (A2) then
6042 return Denotes_Same_Prefix (A1 => A2, A2 => A1);
6044 elsif Nkind_In (A1, N_Selected_Component, N_Indexed_Component, N_Slice)
6045 and then
6046 Nkind_In (A2, N_Selected_Component, N_Indexed_Component, N_Slice)
6047 then
6048 declare
6049 Root1, Root2 : Node_Id;
6050 Depth1, Depth2 : Nat := 0;
6052 begin
6053 Root1 := Prefix (A1);
6054 while not Is_Entity_Name (Root1) loop
6055 if not Nkind_In
6056 (Root1, N_Selected_Component, N_Indexed_Component)
6057 then
6058 return False;
6059 else
6060 Root1 := Prefix (Root1);
6061 end if;
6063 Depth1 := Depth1 + 1;
6064 end loop;
6066 Root2 := Prefix (A2);
6067 while not Is_Entity_Name (Root2) loop
6068 if not Nkind_In (Root2, N_Selected_Component,
6069 N_Indexed_Component)
6070 then
6071 return False;
6072 else
6073 Root2 := Prefix (Root2);
6074 end if;
6076 Depth2 := Depth2 + 1;
6077 end loop;
6079 -- If both have the same depth and they do not denote the same
6080 -- object, they are disjoint and no warning is needed.
6082 if Depth1 = Depth2 then
6083 return False;
6085 elsif Depth1 > Depth2 then
6086 Root1 := Prefix (A1);
6087 for J in 1 .. Depth1 - Depth2 - 1 loop
6088 Root1 := Prefix (Root1);
6089 end loop;
6091 return Denotes_Same_Object (Root1, A2);
6093 else
6094 Root2 := Prefix (A2);
6095 for J in 1 .. Depth2 - Depth1 - 1 loop
6096 Root2 := Prefix (Root2);
6097 end loop;
6099 return Denotes_Same_Object (A1, Root2);
6100 end if;
6101 end;
6103 else
6104 return False;
6105 end if;
6106 end Denotes_Same_Prefix;
6108 ----------------------
6109 -- Denotes_Variable --
6110 ----------------------
6112 function Denotes_Variable (N : Node_Id) return Boolean is
6113 begin
6114 return Is_Variable (N) and then Paren_Count (N) = 0;
6115 end Denotes_Variable;
6117 -----------------------------
6118 -- Depends_On_Discriminant --
6119 -----------------------------
6121 function Depends_On_Discriminant (N : Node_Id) return Boolean is
6122 L : Node_Id;
6123 H : Node_Id;
6125 begin
6126 Get_Index_Bounds (N, L, H);
6127 return Denotes_Discriminant (L) or else Denotes_Discriminant (H);
6128 end Depends_On_Discriminant;
6130 -------------------------
6131 -- Designate_Same_Unit --
6132 -------------------------
6134 function Designate_Same_Unit
6135 (Name1 : Node_Id;
6136 Name2 : Node_Id) return Boolean
6138 K1 : constant Node_Kind := Nkind (Name1);
6139 K2 : constant Node_Kind := Nkind (Name2);
6141 function Prefix_Node (N : Node_Id) return Node_Id;
6142 -- Returns the parent unit name node of a defining program unit name
6143 -- or the prefix if N is a selected component or an expanded name.
6145 function Select_Node (N : Node_Id) return Node_Id;
6146 -- Returns the defining identifier node of a defining program unit
6147 -- name or the selector node if N is a selected component or an
6148 -- expanded name.
6150 -----------------
6151 -- Prefix_Node --
6152 -----------------
6154 function Prefix_Node (N : Node_Id) return Node_Id is
6155 begin
6156 if Nkind (N) = N_Defining_Program_Unit_Name then
6157 return Name (N);
6158 else
6159 return Prefix (N);
6160 end if;
6161 end Prefix_Node;
6163 -----------------
6164 -- Select_Node --
6165 -----------------
6167 function Select_Node (N : Node_Id) return Node_Id is
6168 begin
6169 if Nkind (N) = N_Defining_Program_Unit_Name then
6170 return Defining_Identifier (N);
6171 else
6172 return Selector_Name (N);
6173 end if;
6174 end Select_Node;
6176 -- Start of processing for Designate_Same_Unit
6178 begin
6179 if Nkind_In (K1, N_Identifier, N_Defining_Identifier)
6180 and then
6181 Nkind_In (K2, N_Identifier, N_Defining_Identifier)
6182 then
6183 return Chars (Name1) = Chars (Name2);
6185 elsif Nkind_In (K1, N_Expanded_Name,
6186 N_Selected_Component,
6187 N_Defining_Program_Unit_Name)
6188 and then
6189 Nkind_In (K2, N_Expanded_Name,
6190 N_Selected_Component,
6191 N_Defining_Program_Unit_Name)
6192 then
6193 return
6194 (Chars (Select_Node (Name1)) = Chars (Select_Node (Name2)))
6195 and then
6196 Designate_Same_Unit (Prefix_Node (Name1), Prefix_Node (Name2));
6198 else
6199 return False;
6200 end if;
6201 end Designate_Same_Unit;
6203 ---------------------------------------------
6204 -- Diagnose_Iterated_Component_Association --
6205 ---------------------------------------------
6207 procedure Diagnose_Iterated_Component_Association (N : Node_Id) is
6208 Def_Id : constant Entity_Id := Defining_Identifier (N);
6209 Aggr : Node_Id;
6211 begin
6212 -- Determine whether the iterated component association appears within
6213 -- an aggregate. If this is the case, raise Program_Error because the
6214 -- iterated component association cannot be left in the tree as is and
6215 -- must always be processed by the related aggregate.
6217 Aggr := N;
6218 while Present (Aggr) loop
6219 if Nkind (Aggr) = N_Aggregate then
6220 raise Program_Error;
6222 -- Prevent the search from going too far
6224 elsif Is_Body_Or_Package_Declaration (Aggr) then
6225 exit;
6226 end if;
6228 Aggr := Parent (Aggr);
6229 end loop;
6231 -- At this point it is known that the iterated component association is
6232 -- not within an aggregate. This is really a quantified expression with
6233 -- a missing "all" or "some" quantifier.
6235 Error_Msg_N ("missing quantifier", Def_Id);
6237 -- Rewrite the iterated component association as True to prevent any
6238 -- cascaded errors.
6240 Rewrite (N, New_Occurrence_Of (Standard_True, Sloc (N)));
6241 Analyze (N);
6242 end Diagnose_Iterated_Component_Association;
6244 ---------------------------------
6245 -- Dynamic_Accessibility_Level --
6246 ---------------------------------
6248 function Dynamic_Accessibility_Level (Expr : Node_Id) return Node_Id is
6249 Loc : constant Source_Ptr := Sloc (Expr);
6251 function Make_Level_Literal (Level : Uint) return Node_Id;
6252 -- Construct an integer literal representing an accessibility level
6253 -- with its type set to Natural.
6255 ------------------------
6256 -- Make_Level_Literal --
6257 ------------------------
6259 function Make_Level_Literal (Level : Uint) return Node_Id is
6260 Result : constant Node_Id := Make_Integer_Literal (Loc, Level);
6262 begin
6263 Set_Etype (Result, Standard_Natural);
6264 return Result;
6265 end Make_Level_Literal;
6267 -- Local variables
6269 E : Entity_Id;
6271 -- Start of processing for Dynamic_Accessibility_Level
6273 begin
6274 if Is_Entity_Name (Expr) then
6275 E := Entity (Expr);
6277 if Present (Renamed_Object (E)) then
6278 return Dynamic_Accessibility_Level (Renamed_Object (E));
6279 end if;
6281 if Is_Formal (E) or else Ekind_In (E, E_Variable, E_Constant) then
6282 if Present (Extra_Accessibility (E)) then
6283 return New_Occurrence_Of (Extra_Accessibility (E), Loc);
6284 end if;
6285 end if;
6286 end if;
6288 -- Unimplemented: Ptr.all'Access, where Ptr has Extra_Accessibility ???
6290 case Nkind (Expr) is
6292 -- For access discriminant, the level of the enclosing object
6294 when N_Selected_Component =>
6295 if Ekind (Entity (Selector_Name (Expr))) = E_Discriminant
6296 and then Ekind (Etype (Entity (Selector_Name (Expr)))) =
6297 E_Anonymous_Access_Type
6298 then
6299 return Make_Level_Literal (Object_Access_Level (Expr));
6300 end if;
6302 when N_Attribute_Reference =>
6303 case Get_Attribute_Id (Attribute_Name (Expr)) is
6305 -- For X'Access, the level of the prefix X
6307 when Attribute_Access =>
6308 return Make_Level_Literal
6309 (Object_Access_Level (Prefix (Expr)));
6311 -- Treat the unchecked attributes as library-level
6313 when Attribute_Unchecked_Access
6314 | Attribute_Unrestricted_Access
6316 return Make_Level_Literal (Scope_Depth (Standard_Standard));
6318 -- No other access-valued attributes
6320 when others =>
6321 raise Program_Error;
6322 end case;
6324 when N_Allocator =>
6326 -- Unimplemented: depends on context. As an actual parameter where
6327 -- formal type is anonymous, use
6328 -- Scope_Depth (Current_Scope) + 1.
6329 -- For other cases, see 3.10.2(14/3) and following. ???
6331 null;
6333 when N_Type_Conversion =>
6334 if not Is_Local_Anonymous_Access (Etype (Expr)) then
6336 -- Handle type conversions introduced for a rename of an
6337 -- Ada 2012 stand-alone object of an anonymous access type.
6339 return Dynamic_Accessibility_Level (Expression (Expr));
6340 end if;
6342 when others =>
6343 null;
6344 end case;
6346 return Make_Level_Literal (Type_Access_Level (Etype (Expr)));
6347 end Dynamic_Accessibility_Level;
6349 ------------------------
6350 -- Discriminated_Size --
6351 ------------------------
6353 function Discriminated_Size (Comp : Entity_Id) return Boolean is
6354 function Non_Static_Bound (Bound : Node_Id) return Boolean;
6355 -- Check whether the bound of an index is non-static and does denote
6356 -- a discriminant, in which case any object of the type (protected or
6357 -- otherwise) will have a non-static size.
6359 ----------------------
6360 -- Non_Static_Bound --
6361 ----------------------
6363 function Non_Static_Bound (Bound : Node_Id) return Boolean is
6364 begin
6365 if Is_OK_Static_Expression (Bound) then
6366 return False;
6368 -- If the bound is given by a discriminant it is non-static
6369 -- (A static constraint replaces the reference with the value).
6370 -- In an protected object the discriminant has been replaced by
6371 -- the corresponding discriminal within the protected operation.
6373 elsif Is_Entity_Name (Bound)
6374 and then
6375 (Ekind (Entity (Bound)) = E_Discriminant
6376 or else Present (Discriminal_Link (Entity (Bound))))
6377 then
6378 return False;
6380 else
6381 return True;
6382 end if;
6383 end Non_Static_Bound;
6385 -- Local variables
6387 Typ : constant Entity_Id := Etype (Comp);
6388 Index : Node_Id;
6390 -- Start of processing for Discriminated_Size
6392 begin
6393 if not Is_Array_Type (Typ) then
6394 return False;
6395 end if;
6397 if Ekind (Typ) = E_Array_Subtype then
6398 Index := First_Index (Typ);
6399 while Present (Index) loop
6400 if Non_Static_Bound (Low_Bound (Index))
6401 or else Non_Static_Bound (High_Bound (Index))
6402 then
6403 return False;
6404 end if;
6406 Next_Index (Index);
6407 end loop;
6409 return True;
6410 end if;
6412 return False;
6413 end Discriminated_Size;
6415 -----------------------------------
6416 -- Effective_Extra_Accessibility --
6417 -----------------------------------
6419 function Effective_Extra_Accessibility (Id : Entity_Id) return Entity_Id is
6420 begin
6421 if Present (Renamed_Object (Id))
6422 and then Is_Entity_Name (Renamed_Object (Id))
6423 then
6424 return Effective_Extra_Accessibility (Entity (Renamed_Object (Id)));
6425 else
6426 return Extra_Accessibility (Id);
6427 end if;
6428 end Effective_Extra_Accessibility;
6430 -----------------------------
6431 -- Effective_Reads_Enabled --
6432 -----------------------------
6434 function Effective_Reads_Enabled (Id : Entity_Id) return Boolean is
6435 begin
6436 return Has_Enabled_Property (Id, Name_Effective_Reads);
6437 end Effective_Reads_Enabled;
6439 ------------------------------
6440 -- Effective_Writes_Enabled --
6441 ------------------------------
6443 function Effective_Writes_Enabled (Id : Entity_Id) return Boolean is
6444 begin
6445 return Has_Enabled_Property (Id, Name_Effective_Writes);
6446 end Effective_Writes_Enabled;
6448 ------------------------------
6449 -- Enclosing_Comp_Unit_Node --
6450 ------------------------------
6452 function Enclosing_Comp_Unit_Node (N : Node_Id) return Node_Id is
6453 Current_Node : Node_Id;
6455 begin
6456 Current_Node := N;
6457 while Present (Current_Node)
6458 and then Nkind (Current_Node) /= N_Compilation_Unit
6459 loop
6460 Current_Node := Parent (Current_Node);
6461 end loop;
6463 if Nkind (Current_Node) /= N_Compilation_Unit then
6464 return Empty;
6465 else
6466 return Current_Node;
6467 end if;
6468 end Enclosing_Comp_Unit_Node;
6470 --------------------------
6471 -- Enclosing_CPP_Parent --
6472 --------------------------
6474 function Enclosing_CPP_Parent (Typ : Entity_Id) return Entity_Id is
6475 Parent_Typ : Entity_Id := Typ;
6477 begin
6478 while not Is_CPP_Class (Parent_Typ)
6479 and then Etype (Parent_Typ) /= Parent_Typ
6480 loop
6481 Parent_Typ := Etype (Parent_Typ);
6483 if Is_Private_Type (Parent_Typ) then
6484 Parent_Typ := Full_View (Base_Type (Parent_Typ));
6485 end if;
6486 end loop;
6488 pragma Assert (Is_CPP_Class (Parent_Typ));
6489 return Parent_Typ;
6490 end Enclosing_CPP_Parent;
6492 ---------------------------
6493 -- Enclosing_Declaration --
6494 ---------------------------
6496 function Enclosing_Declaration (N : Node_Id) return Node_Id is
6497 Decl : Node_Id := N;
6499 begin
6500 while Present (Decl)
6501 and then not (Nkind (Decl) in N_Declaration
6502 or else
6503 Nkind (Decl) in N_Later_Decl_Item)
6504 loop
6505 Decl := Parent (Decl);
6506 end loop;
6508 return Decl;
6509 end Enclosing_Declaration;
6511 ----------------------------
6512 -- Enclosing_Generic_Body --
6513 ----------------------------
6515 function Enclosing_Generic_Body
6516 (N : Node_Id) return Node_Id
6518 P : Node_Id;
6519 Decl : Node_Id;
6520 Spec : Node_Id;
6522 begin
6523 P := Parent (N);
6524 while Present (P) loop
6525 if Nkind (P) = N_Package_Body
6526 or else Nkind (P) = N_Subprogram_Body
6527 then
6528 Spec := Corresponding_Spec (P);
6530 if Present (Spec) then
6531 Decl := Unit_Declaration_Node (Spec);
6533 if Nkind (Decl) = N_Generic_Package_Declaration
6534 or else Nkind (Decl) = N_Generic_Subprogram_Declaration
6535 then
6536 return P;
6537 end if;
6538 end if;
6539 end if;
6541 P := Parent (P);
6542 end loop;
6544 return Empty;
6545 end Enclosing_Generic_Body;
6547 ----------------------------
6548 -- Enclosing_Generic_Unit --
6549 ----------------------------
6551 function Enclosing_Generic_Unit
6552 (N : Node_Id) return Node_Id
6554 P : Node_Id;
6555 Decl : Node_Id;
6556 Spec : Node_Id;
6558 begin
6559 P := Parent (N);
6560 while Present (P) loop
6561 if Nkind (P) = N_Generic_Package_Declaration
6562 or else Nkind (P) = N_Generic_Subprogram_Declaration
6563 then
6564 return P;
6566 elsif Nkind (P) = N_Package_Body
6567 or else Nkind (P) = N_Subprogram_Body
6568 then
6569 Spec := Corresponding_Spec (P);
6571 if Present (Spec) then
6572 Decl := Unit_Declaration_Node (Spec);
6574 if Nkind (Decl) = N_Generic_Package_Declaration
6575 or else Nkind (Decl) = N_Generic_Subprogram_Declaration
6576 then
6577 return Decl;
6578 end if;
6579 end if;
6580 end if;
6582 P := Parent (P);
6583 end loop;
6585 return Empty;
6586 end Enclosing_Generic_Unit;
6588 -------------------------------
6589 -- Enclosing_Lib_Unit_Entity --
6590 -------------------------------
6592 function Enclosing_Lib_Unit_Entity
6593 (E : Entity_Id := Current_Scope) return Entity_Id
6595 Unit_Entity : Entity_Id;
6597 begin
6598 -- Look for enclosing library unit entity by following scope links.
6599 -- Equivalent to, but faster than indexing through the scope stack.
6601 Unit_Entity := E;
6602 while (Present (Scope (Unit_Entity))
6603 and then Scope (Unit_Entity) /= Standard_Standard)
6604 and not Is_Child_Unit (Unit_Entity)
6605 loop
6606 Unit_Entity := Scope (Unit_Entity);
6607 end loop;
6609 return Unit_Entity;
6610 end Enclosing_Lib_Unit_Entity;
6612 -----------------------------
6613 -- Enclosing_Lib_Unit_Node --
6614 -----------------------------
6616 function Enclosing_Lib_Unit_Node (N : Node_Id) return Node_Id is
6617 Encl_Unit : Node_Id;
6619 begin
6620 Encl_Unit := Enclosing_Comp_Unit_Node (N);
6621 while Present (Encl_Unit)
6622 and then Nkind (Unit (Encl_Unit)) = N_Subunit
6623 loop
6624 Encl_Unit := Library_Unit (Encl_Unit);
6625 end loop;
6627 pragma Assert (Nkind (Encl_Unit) = N_Compilation_Unit);
6628 return Encl_Unit;
6629 end Enclosing_Lib_Unit_Node;
6631 -----------------------
6632 -- Enclosing_Package --
6633 -----------------------
6635 function Enclosing_Package (E : Entity_Id) return Entity_Id is
6636 Dynamic_Scope : constant Entity_Id := Enclosing_Dynamic_Scope (E);
6638 begin
6639 if Dynamic_Scope = Standard_Standard then
6640 return Standard_Standard;
6642 elsif Dynamic_Scope = Empty then
6643 return Empty;
6645 elsif Ekind_In (Dynamic_Scope, E_Package, E_Package_Body,
6646 E_Generic_Package)
6647 then
6648 return Dynamic_Scope;
6650 else
6651 return Enclosing_Package (Dynamic_Scope);
6652 end if;
6653 end Enclosing_Package;
6655 -------------------------------------
6656 -- Enclosing_Package_Or_Subprogram --
6657 -------------------------------------
6659 function Enclosing_Package_Or_Subprogram (E : Entity_Id) return Entity_Id is
6660 S : Entity_Id;
6662 begin
6663 S := Scope (E);
6664 while Present (S) loop
6665 if Is_Package_Or_Generic_Package (S)
6666 or else Ekind (S) = E_Package_Body
6667 then
6668 return S;
6670 elsif Is_Subprogram_Or_Generic_Subprogram (S)
6671 or else Ekind (S) = E_Subprogram_Body
6672 then
6673 return S;
6675 else
6676 S := Scope (S);
6677 end if;
6678 end loop;
6680 return Empty;
6681 end Enclosing_Package_Or_Subprogram;
6683 --------------------------
6684 -- Enclosing_Subprogram --
6685 --------------------------
6687 function Enclosing_Subprogram (E : Entity_Id) return Entity_Id is
6688 Dynamic_Scope : constant Entity_Id := Enclosing_Dynamic_Scope (E);
6690 begin
6691 if Dynamic_Scope = Standard_Standard then
6692 return Empty;
6694 elsif Dynamic_Scope = Empty then
6695 return Empty;
6697 elsif Ekind (Dynamic_Scope) = E_Subprogram_Body then
6698 return Corresponding_Spec (Parent (Parent (Dynamic_Scope)));
6700 elsif Ekind (Dynamic_Scope) = E_Block
6701 or else Ekind (Dynamic_Scope) = E_Return_Statement
6702 then
6703 return Enclosing_Subprogram (Dynamic_Scope);
6705 elsif Ekind (Dynamic_Scope) = E_Task_Type then
6706 return Get_Task_Body_Procedure (Dynamic_Scope);
6708 elsif Ekind (Dynamic_Scope) = E_Limited_Private_Type
6709 and then Present (Full_View (Dynamic_Scope))
6710 and then Ekind (Full_View (Dynamic_Scope)) = E_Task_Type
6711 then
6712 return Get_Task_Body_Procedure (Full_View (Dynamic_Scope));
6714 -- No body is generated if the protected operation is eliminated
6716 elsif Convention (Dynamic_Scope) = Convention_Protected
6717 and then not Is_Eliminated (Dynamic_Scope)
6718 and then Present (Protected_Body_Subprogram (Dynamic_Scope))
6719 then
6720 return Protected_Body_Subprogram (Dynamic_Scope);
6722 else
6723 return Dynamic_Scope;
6724 end if;
6725 end Enclosing_Subprogram;
6727 --------------------------
6728 -- End_Keyword_Location --
6729 --------------------------
6731 function End_Keyword_Location (N : Node_Id) return Source_Ptr is
6732 function End_Label_Loc (Nod : Node_Id) return Source_Ptr;
6733 -- Return the source location of Nod's end label according to the
6734 -- following precedence rules:
6736 -- 1) If the end label exists, return its location
6737 -- 2) If Nod exists, return its location
6738 -- 3) Return the location of N
6740 -------------------
6741 -- End_Label_Loc --
6742 -------------------
6744 function End_Label_Loc (Nod : Node_Id) return Source_Ptr is
6745 Label : Node_Id;
6747 begin
6748 if Present (Nod) then
6749 Label := End_Label (Nod);
6751 if Present (Label) then
6752 return Sloc (Label);
6753 else
6754 return Sloc (Nod);
6755 end if;
6757 else
6758 return Sloc (N);
6759 end if;
6760 end End_Label_Loc;
6762 -- Local variables
6764 Owner : Node_Id;
6766 -- Start of processing for End_Keyword_Location
6768 begin
6769 if Nkind_In (N, N_Block_Statement,
6770 N_Entry_Body,
6771 N_Package_Body,
6772 N_Subprogram_Body,
6773 N_Task_Body)
6774 then
6775 Owner := Handled_Statement_Sequence (N);
6777 elsif Nkind (N) = N_Package_Declaration then
6778 Owner := Specification (N);
6780 elsif Nkind (N) = N_Protected_Body then
6781 Owner := N;
6783 elsif Nkind_In (N, N_Protected_Type_Declaration,
6784 N_Single_Protected_Declaration)
6785 then
6786 Owner := Protected_Definition (N);
6788 elsif Nkind_In (N, N_Single_Task_Declaration,
6789 N_Task_Type_Declaration)
6790 then
6791 Owner := Task_Definition (N);
6793 -- This routine should not be called with other contexts
6795 else
6796 pragma Assert (False);
6797 null;
6798 end if;
6800 return End_Label_Loc (Owner);
6801 end End_Keyword_Location;
6803 ------------------------
6804 -- Ensure_Freeze_Node --
6805 ------------------------
6807 procedure Ensure_Freeze_Node (E : Entity_Id) is
6808 FN : Node_Id;
6809 begin
6810 if No (Freeze_Node (E)) then
6811 FN := Make_Freeze_Entity (Sloc (E));
6812 Set_Has_Delayed_Freeze (E);
6813 Set_Freeze_Node (E, FN);
6814 Set_Access_Types_To_Process (FN, No_Elist);
6815 Set_TSS_Elist (FN, No_Elist);
6816 Set_Entity (FN, E);
6817 end if;
6818 end Ensure_Freeze_Node;
6820 ----------------
6821 -- Enter_Name --
6822 ----------------
6824 procedure Enter_Name (Def_Id : Entity_Id) is
6825 C : constant Entity_Id := Current_Entity (Def_Id);
6826 E : constant Entity_Id := Current_Entity_In_Scope (Def_Id);
6827 S : constant Entity_Id := Current_Scope;
6829 begin
6830 Generate_Definition (Def_Id);
6832 -- Add new name to current scope declarations. Check for duplicate
6833 -- declaration, which may or may not be a genuine error.
6835 if Present (E) then
6837 -- Case of previous entity entered because of a missing declaration
6838 -- or else a bad subtype indication. Best is to use the new entity,
6839 -- and make the previous one invisible.
6841 if Etype (E) = Any_Type then
6842 Set_Is_Immediately_Visible (E, False);
6844 -- Case of renaming declaration constructed for package instances.
6845 -- if there is an explicit declaration with the same identifier,
6846 -- the renaming is not immediately visible any longer, but remains
6847 -- visible through selected component notation.
6849 elsif Nkind (Parent (E)) = N_Package_Renaming_Declaration
6850 and then not Comes_From_Source (E)
6851 then
6852 Set_Is_Immediately_Visible (E, False);
6854 -- The new entity may be the package renaming, which has the same
6855 -- same name as a generic formal which has been seen already.
6857 elsif Nkind (Parent (Def_Id)) = N_Package_Renaming_Declaration
6858 and then not Comes_From_Source (Def_Id)
6859 then
6860 Set_Is_Immediately_Visible (E, False);
6862 -- For a fat pointer corresponding to a remote access to subprogram,
6863 -- we use the same identifier as the RAS type, so that the proper
6864 -- name appears in the stub. This type is only retrieved through
6865 -- the RAS type and never by visibility, and is not added to the
6866 -- visibility list (see below).
6868 elsif Nkind (Parent (Def_Id)) = N_Full_Type_Declaration
6869 and then Ekind (Def_Id) = E_Record_Type
6870 and then Present (Corresponding_Remote_Type (Def_Id))
6871 then
6872 null;
6874 -- Case of an implicit operation or derived literal. The new entity
6875 -- hides the implicit one, which is removed from all visibility,
6876 -- i.e. the entity list of its scope, and homonym chain of its name.
6878 elsif (Is_Overloadable (E) and then Is_Inherited_Operation (E))
6879 or else Is_Internal (E)
6880 then
6881 declare
6882 Decl : constant Node_Id := Parent (E);
6883 Prev : Entity_Id;
6884 Prev_Vis : Entity_Id;
6886 begin
6887 -- If E is an implicit declaration, it cannot be the first
6888 -- entity in the scope.
6890 Prev := First_Entity (Current_Scope);
6891 while Present (Prev) and then Next_Entity (Prev) /= E loop
6892 Next_Entity (Prev);
6893 end loop;
6895 if No (Prev) then
6897 -- If E is not on the entity chain of the current scope,
6898 -- it is an implicit declaration in the generic formal
6899 -- part of a generic subprogram. When analyzing the body,
6900 -- the generic formals are visible but not on the entity
6901 -- chain of the subprogram. The new entity will become
6902 -- the visible one in the body.
6904 pragma Assert
6905 (Nkind (Parent (Decl)) = N_Generic_Subprogram_Declaration);
6906 null;
6908 else
6909 Set_Next_Entity (Prev, Next_Entity (E));
6911 if No (Next_Entity (Prev)) then
6912 Set_Last_Entity (Current_Scope, Prev);
6913 end if;
6915 if E = Current_Entity (E) then
6916 Prev_Vis := Empty;
6918 else
6919 Prev_Vis := Current_Entity (E);
6920 while Homonym (Prev_Vis) /= E loop
6921 Prev_Vis := Homonym (Prev_Vis);
6922 end loop;
6923 end if;
6925 if Present (Prev_Vis) then
6927 -- Skip E in the visibility chain
6929 Set_Homonym (Prev_Vis, Homonym (E));
6931 else
6932 Set_Name_Entity_Id (Chars (E), Homonym (E));
6933 end if;
6934 end if;
6935 end;
6937 -- This section of code could use a comment ???
6939 elsif Present (Etype (E))
6940 and then Is_Concurrent_Type (Etype (E))
6941 and then E = Def_Id
6942 then
6943 return;
6945 -- If the homograph is a protected component renaming, it should not
6946 -- be hiding the current entity. Such renamings are treated as weak
6947 -- declarations.
6949 elsif Is_Prival (E) then
6950 Set_Is_Immediately_Visible (E, False);
6952 -- In this case the current entity is a protected component renaming.
6953 -- Perform minimal decoration by setting the scope and return since
6954 -- the prival should not be hiding other visible entities.
6956 elsif Is_Prival (Def_Id) then
6957 Set_Scope (Def_Id, Current_Scope);
6958 return;
6960 -- Analogous to privals, the discriminal generated for an entry index
6961 -- parameter acts as a weak declaration. Perform minimal decoration
6962 -- to avoid bogus errors.
6964 elsif Is_Discriminal (Def_Id)
6965 and then Ekind (Discriminal_Link (Def_Id)) = E_Entry_Index_Parameter
6966 then
6967 Set_Scope (Def_Id, Current_Scope);
6968 return;
6970 -- In the body or private part of an instance, a type extension may
6971 -- introduce a component with the same name as that of an actual. The
6972 -- legality rule is not enforced, but the semantics of the full type
6973 -- with two components of same name are not clear at this point???
6975 elsif In_Instance_Not_Visible then
6976 null;
6978 -- When compiling a package body, some child units may have become
6979 -- visible. They cannot conflict with local entities that hide them.
6981 elsif Is_Child_Unit (E)
6982 and then In_Open_Scopes (Scope (E))
6983 and then not Is_Immediately_Visible (E)
6984 then
6985 null;
6987 -- Conversely, with front-end inlining we may compile the parent body
6988 -- first, and a child unit subsequently. The context is now the
6989 -- parent spec, and body entities are not visible.
6991 elsif Is_Child_Unit (Def_Id)
6992 and then Is_Package_Body_Entity (E)
6993 and then not In_Package_Body (Current_Scope)
6994 then
6995 null;
6997 -- Case of genuine duplicate declaration
6999 else
7000 Error_Msg_Sloc := Sloc (E);
7002 -- If the previous declaration is an incomplete type declaration
7003 -- this may be an attempt to complete it with a private type. The
7004 -- following avoids confusing cascaded errors.
7006 if Nkind (Parent (E)) = N_Incomplete_Type_Declaration
7007 and then Nkind (Parent (Def_Id)) = N_Private_Type_Declaration
7008 then
7009 Error_Msg_N
7010 ("incomplete type cannot be completed with a private " &
7011 "declaration", Parent (Def_Id));
7012 Set_Is_Immediately_Visible (E, False);
7013 Set_Full_View (E, Def_Id);
7015 -- An inherited component of a record conflicts with a new
7016 -- discriminant. The discriminant is inserted first in the scope,
7017 -- but the error should be posted on it, not on the component.
7019 elsif Ekind (E) = E_Discriminant
7020 and then Present (Scope (Def_Id))
7021 and then Scope (Def_Id) /= Current_Scope
7022 then
7023 Error_Msg_Sloc := Sloc (Def_Id);
7024 Error_Msg_N ("& conflicts with declaration#", E);
7025 return;
7027 -- If the name of the unit appears in its own context clause, a
7028 -- dummy package with the name has already been created, and the
7029 -- error emitted. Try to continue quietly.
7031 elsif Error_Posted (E)
7032 and then Sloc (E) = No_Location
7033 and then Nkind (Parent (E)) = N_Package_Specification
7034 and then Current_Scope = Standard_Standard
7035 then
7036 Set_Scope (Def_Id, Current_Scope);
7037 return;
7039 else
7040 Error_Msg_N ("& conflicts with declaration#", Def_Id);
7042 -- Avoid cascaded messages with duplicate components in
7043 -- derived types.
7045 if Ekind_In (E, E_Component, E_Discriminant) then
7046 return;
7047 end if;
7048 end if;
7050 if Nkind (Parent (Parent (Def_Id))) =
7051 N_Generic_Subprogram_Declaration
7052 and then Def_Id =
7053 Defining_Entity (Specification (Parent (Parent (Def_Id))))
7054 then
7055 Error_Msg_N ("\generic units cannot be overloaded", Def_Id);
7056 end if;
7058 -- If entity is in standard, then we are in trouble, because it
7059 -- means that we have a library package with a duplicated name.
7060 -- That's hard to recover from, so abort.
7062 if S = Standard_Standard then
7063 raise Unrecoverable_Error;
7065 -- Otherwise we continue with the declaration. Having two
7066 -- identical declarations should not cause us too much trouble.
7068 else
7069 null;
7070 end if;
7071 end if;
7072 end if;
7074 -- If we fall through, declaration is OK, at least OK enough to continue
7076 -- If Def_Id is a discriminant or a record component we are in the midst
7077 -- of inheriting components in a derived record definition. Preserve
7078 -- their Ekind and Etype.
7080 if Ekind_In (Def_Id, E_Discriminant, E_Component) then
7081 null;
7083 -- If a type is already set, leave it alone (happens when a type
7084 -- declaration is reanalyzed following a call to the optimizer).
7086 elsif Present (Etype (Def_Id)) then
7087 null;
7089 -- Otherwise, the kind E_Void insures that premature uses of the entity
7090 -- will be detected. Any_Type insures that no cascaded errors will occur
7092 else
7093 Set_Ekind (Def_Id, E_Void);
7094 Set_Etype (Def_Id, Any_Type);
7095 end if;
7097 -- Inherited discriminants and components in derived record types are
7098 -- immediately visible. Itypes are not.
7100 -- Unless the Itype is for a record type with a corresponding remote
7101 -- type (what is that about, it was not commented ???)
7103 if Ekind_In (Def_Id, E_Discriminant, E_Component)
7104 or else
7105 ((not Is_Record_Type (Def_Id)
7106 or else No (Corresponding_Remote_Type (Def_Id)))
7107 and then not Is_Itype (Def_Id))
7108 then
7109 Set_Is_Immediately_Visible (Def_Id);
7110 Set_Current_Entity (Def_Id);
7111 end if;
7113 Set_Homonym (Def_Id, C);
7114 Append_Entity (Def_Id, S);
7115 Set_Public_Status (Def_Id);
7117 -- Declaring a homonym is not allowed in SPARK ...
7119 if Present (C) and then Restriction_Check_Required (SPARK_05) then
7120 declare
7121 Enclosing_Subp : constant Node_Id := Enclosing_Subprogram (Def_Id);
7122 Enclosing_Pack : constant Node_Id := Enclosing_Package (Def_Id);
7123 Other_Scope : constant Node_Id := Enclosing_Dynamic_Scope (C);
7125 begin
7126 -- ... unless the new declaration is in a subprogram, and the
7127 -- visible declaration is a variable declaration or a parameter
7128 -- specification outside that subprogram.
7130 if Present (Enclosing_Subp)
7131 and then Nkind_In (Parent (C), N_Object_Declaration,
7132 N_Parameter_Specification)
7133 and then not Scope_Within_Or_Same (Other_Scope, Enclosing_Subp)
7134 then
7135 null;
7137 -- ... or the new declaration is in a package, and the visible
7138 -- declaration occurs outside that package.
7140 elsif Present (Enclosing_Pack)
7141 and then not Scope_Within_Or_Same (Other_Scope, Enclosing_Pack)
7142 then
7143 null;
7145 -- ... or the new declaration is a component declaration in a
7146 -- record type definition.
7148 elsif Nkind (Parent (Def_Id)) = N_Component_Declaration then
7149 null;
7151 -- Don't issue error for non-source entities
7153 elsif Comes_From_Source (Def_Id)
7154 and then Comes_From_Source (C)
7155 then
7156 Error_Msg_Sloc := Sloc (C);
7157 Check_SPARK_05_Restriction
7158 ("redeclaration of identifier &#", Def_Id);
7159 end if;
7160 end;
7161 end if;
7163 -- Warn if new entity hides an old one
7165 if Warn_On_Hiding and then Present (C)
7167 -- Don't warn for record components since they always have a well
7168 -- defined scope which does not confuse other uses. Note that in
7169 -- some cases, Ekind has not been set yet.
7171 and then Ekind (C) /= E_Component
7172 and then Ekind (C) /= E_Discriminant
7173 and then Nkind (Parent (C)) /= N_Component_Declaration
7174 and then Ekind (Def_Id) /= E_Component
7175 and then Ekind (Def_Id) /= E_Discriminant
7176 and then Nkind (Parent (Def_Id)) /= N_Component_Declaration
7178 -- Don't warn for one character variables. It is too common to use
7179 -- such variables as locals and will just cause too many false hits.
7181 and then Length_Of_Name (Chars (C)) /= 1
7183 -- Don't warn for non-source entities
7185 and then Comes_From_Source (C)
7186 and then Comes_From_Source (Def_Id)
7188 -- Don't warn unless entity in question is in extended main source
7190 and then In_Extended_Main_Source_Unit (Def_Id)
7192 -- Finally, the hidden entity must be either immediately visible or
7193 -- use visible (i.e. from a used package).
7195 and then
7196 (Is_Immediately_Visible (C)
7197 or else
7198 Is_Potentially_Use_Visible (C))
7199 then
7200 Error_Msg_Sloc := Sloc (C);
7201 Error_Msg_N ("declaration hides &#?h?", Def_Id);
7202 end if;
7203 end Enter_Name;
7205 ---------------
7206 -- Entity_Of --
7207 ---------------
7209 function Entity_Of (N : Node_Id) return Entity_Id is
7210 Id : Entity_Id;
7211 Ren : Node_Id;
7213 begin
7214 -- Assume that the arbitrary node does not have an entity
7216 Id := Empty;
7218 if Is_Entity_Name (N) then
7219 Id := Entity (N);
7221 -- Follow a possible chain of renamings to reach the earliest renamed
7222 -- source object.
7224 while Present (Id)
7225 and then Is_Object (Id)
7226 and then Present (Renamed_Object (Id))
7227 loop
7228 Ren := Renamed_Object (Id);
7230 -- The reference renames an abstract state or a whole object
7232 -- Obj : ...;
7233 -- Ren : ... renames Obj;
7235 if Is_Entity_Name (Ren) then
7236 Id := Entity (Ren);
7238 -- The reference renames a function result. Check the original
7239 -- node in case expansion relocates the function call.
7241 -- Ren : ... renames Func_Call;
7243 elsif Nkind (Original_Node (Ren)) = N_Function_Call then
7244 exit;
7246 -- Otherwise the reference renames something which does not yield
7247 -- an abstract state or a whole object. Treat the reference as not
7248 -- having a proper entity for SPARK legality purposes.
7250 else
7251 Id := Empty;
7252 exit;
7253 end if;
7254 end loop;
7255 end if;
7257 return Id;
7258 end Entity_Of;
7260 --------------------------
7261 -- Explain_Limited_Type --
7262 --------------------------
7264 procedure Explain_Limited_Type (T : Entity_Id; N : Node_Id) is
7265 C : Entity_Id;
7267 begin
7268 -- For array, component type must be limited
7270 if Is_Array_Type (T) then
7271 Error_Msg_Node_2 := T;
7272 Error_Msg_NE
7273 ("\component type& of type& is limited", N, Component_Type (T));
7274 Explain_Limited_Type (Component_Type (T), N);
7276 elsif Is_Record_Type (T) then
7278 -- No need for extra messages if explicit limited record
7280 if Is_Limited_Record (Base_Type (T)) then
7281 return;
7282 end if;
7284 -- Otherwise find a limited component. Check only components that
7285 -- come from source, or inherited components that appear in the
7286 -- source of the ancestor.
7288 C := First_Component (T);
7289 while Present (C) loop
7290 if Is_Limited_Type (Etype (C))
7291 and then
7292 (Comes_From_Source (C)
7293 or else
7294 (Present (Original_Record_Component (C))
7295 and then
7296 Comes_From_Source (Original_Record_Component (C))))
7297 then
7298 Error_Msg_Node_2 := T;
7299 Error_Msg_NE ("\component& of type& has limited type", N, C);
7300 Explain_Limited_Type (Etype (C), N);
7301 return;
7302 end if;
7304 Next_Component (C);
7305 end loop;
7307 -- The type may be declared explicitly limited, even if no component
7308 -- of it is limited, in which case we fall out of the loop.
7309 return;
7310 end if;
7311 end Explain_Limited_Type;
7313 ---------------------------------------
7314 -- Expression_Of_Expression_Function --
7315 ---------------------------------------
7317 function Expression_Of_Expression_Function
7318 (Subp : Entity_Id) return Node_Id
7320 Expr_Func : Node_Id;
7322 begin
7323 pragma Assert (Is_Expression_Function_Or_Completion (Subp));
7325 if Nkind (Original_Node (Subprogram_Spec (Subp))) =
7326 N_Expression_Function
7327 then
7328 Expr_Func := Original_Node (Subprogram_Spec (Subp));
7330 elsif Nkind (Original_Node (Subprogram_Body (Subp))) =
7331 N_Expression_Function
7332 then
7333 Expr_Func := Original_Node (Subprogram_Body (Subp));
7335 else
7336 pragma Assert (False);
7337 null;
7338 end if;
7340 return Original_Node (Expression (Expr_Func));
7341 end Expression_Of_Expression_Function;
7343 -------------------------------
7344 -- Extensions_Visible_Status --
7345 -------------------------------
7347 function Extensions_Visible_Status
7348 (Id : Entity_Id) return Extensions_Visible_Mode
7350 Arg : Node_Id;
7351 Decl : Node_Id;
7352 Expr : Node_Id;
7353 Prag : Node_Id;
7354 Subp : Entity_Id;
7356 begin
7357 -- When a formal parameter is subject to Extensions_Visible, the pragma
7358 -- is stored in the contract of related subprogram.
7360 if Is_Formal (Id) then
7361 Subp := Scope (Id);
7363 elsif Is_Subprogram_Or_Generic_Subprogram (Id) then
7364 Subp := Id;
7366 -- No other construct carries this pragma
7368 else
7369 return Extensions_Visible_None;
7370 end if;
7372 Prag := Get_Pragma (Subp, Pragma_Extensions_Visible);
7374 -- In certain cases analysis may request the Extensions_Visible status
7375 -- of an expression function before the pragma has been analyzed yet.
7376 -- Inspect the declarative items after the expression function looking
7377 -- for the pragma (if any).
7379 if No (Prag) and then Is_Expression_Function (Subp) then
7380 Decl := Next (Unit_Declaration_Node (Subp));
7381 while Present (Decl) loop
7382 if Nkind (Decl) = N_Pragma
7383 and then Pragma_Name (Decl) = Name_Extensions_Visible
7384 then
7385 Prag := Decl;
7386 exit;
7388 -- A source construct ends the region where Extensions_Visible may
7389 -- appear, stop the traversal. An expanded expression function is
7390 -- no longer a source construct, but it must still be recognized.
7392 elsif Comes_From_Source (Decl)
7393 or else
7394 (Nkind_In (Decl, N_Subprogram_Body,
7395 N_Subprogram_Declaration)
7396 and then Is_Expression_Function (Defining_Entity (Decl)))
7397 then
7398 exit;
7399 end if;
7401 Next (Decl);
7402 end loop;
7403 end if;
7405 -- Extract the value from the Boolean expression (if any)
7407 if Present (Prag) then
7408 Arg := First (Pragma_Argument_Associations (Prag));
7410 if Present (Arg) then
7411 Expr := Get_Pragma_Arg (Arg);
7413 -- When the associated subprogram is an expression function, the
7414 -- argument of the pragma may not have been analyzed.
7416 if not Analyzed (Expr) then
7417 Preanalyze_And_Resolve (Expr, Standard_Boolean);
7418 end if;
7420 -- Guard against cascading errors when the argument of pragma
7421 -- Extensions_Visible is not a valid static Boolean expression.
7423 if Error_Posted (Expr) then
7424 return Extensions_Visible_None;
7426 elsif Is_True (Expr_Value (Expr)) then
7427 return Extensions_Visible_True;
7429 else
7430 return Extensions_Visible_False;
7431 end if;
7433 -- Otherwise the aspect or pragma defaults to True
7435 else
7436 return Extensions_Visible_True;
7437 end if;
7439 -- Otherwise aspect or pragma Extensions_Visible is not inherited or
7440 -- directly specified. In SPARK code, its value defaults to "False".
7442 elsif SPARK_Mode = On then
7443 return Extensions_Visible_False;
7445 -- In non-SPARK code, aspect or pragma Extensions_Visible defaults to
7446 -- "True".
7448 else
7449 return Extensions_Visible_True;
7450 end if;
7451 end Extensions_Visible_Status;
7453 -----------------
7454 -- Find_Actual --
7455 -----------------
7457 procedure Find_Actual
7458 (N : Node_Id;
7459 Formal : out Entity_Id;
7460 Call : out Node_Id)
7462 Context : constant Node_Id := Parent (N);
7463 Actual : Node_Id;
7464 Call_Nam : Node_Id;
7466 begin
7467 if Nkind_In (Context, N_Indexed_Component, N_Selected_Component)
7468 and then N = Prefix (Context)
7469 then
7470 Find_Actual (Context, Formal, Call);
7471 return;
7473 elsif Nkind (Context) = N_Parameter_Association
7474 and then N = Explicit_Actual_Parameter (Context)
7475 then
7476 Call := Parent (Context);
7478 elsif Nkind_In (Context, N_Entry_Call_Statement,
7479 N_Function_Call,
7480 N_Procedure_Call_Statement)
7481 then
7482 Call := Context;
7484 else
7485 Formal := Empty;
7486 Call := Empty;
7487 return;
7488 end if;
7490 -- If we have a call to a subprogram look for the parameter. Note that
7491 -- we exclude overloaded calls, since we don't know enough to be sure
7492 -- of giving the right answer in this case.
7494 if Nkind_In (Call, N_Entry_Call_Statement,
7495 N_Function_Call,
7496 N_Procedure_Call_Statement)
7497 then
7498 Call_Nam := Name (Call);
7500 -- A call to a protected or task entry appears as a selected
7501 -- component rather than an expanded name.
7503 if Nkind (Call_Nam) = N_Selected_Component then
7504 Call_Nam := Selector_Name (Call_Nam);
7505 end if;
7507 if Is_Entity_Name (Call_Nam)
7508 and then Present (Entity (Call_Nam))
7509 and then Is_Overloadable (Entity (Call_Nam))
7510 and then not Is_Overloaded (Call_Nam)
7511 then
7512 -- If node is name in call it is not an actual
7514 if N = Call_Nam then
7515 Formal := Empty;
7516 Call := Empty;
7517 return;
7518 end if;
7520 -- Fall here if we are definitely a parameter
7522 Actual := First_Actual (Call);
7523 Formal := First_Formal (Entity (Call_Nam));
7524 while Present (Formal) and then Present (Actual) loop
7525 if Actual = N then
7526 return;
7528 -- An actual that is the prefix in a prefixed call may have
7529 -- been rewritten in the call, after the deferred reference
7530 -- was collected. Check if sloc and kinds and names match.
7532 elsif Sloc (Actual) = Sloc (N)
7533 and then Nkind (Actual) = N_Identifier
7534 and then Nkind (Actual) = Nkind (N)
7535 and then Chars (Actual) = Chars (N)
7536 then
7537 return;
7539 else
7540 Actual := Next_Actual (Actual);
7541 Formal := Next_Formal (Formal);
7542 end if;
7543 end loop;
7544 end if;
7545 end if;
7547 -- Fall through here if we did not find matching actual
7549 Formal := Empty;
7550 Call := Empty;
7551 end Find_Actual;
7553 ---------------------------
7554 -- Find_Body_Discriminal --
7555 ---------------------------
7557 function Find_Body_Discriminal
7558 (Spec_Discriminant : Entity_Id) return Entity_Id
7560 Tsk : Entity_Id;
7561 Disc : Entity_Id;
7563 begin
7564 -- If expansion is suppressed, then the scope can be the concurrent type
7565 -- itself rather than a corresponding concurrent record type.
7567 if Is_Concurrent_Type (Scope (Spec_Discriminant)) then
7568 Tsk := Scope (Spec_Discriminant);
7570 else
7571 pragma Assert (Is_Concurrent_Record_Type (Scope (Spec_Discriminant)));
7573 Tsk := Corresponding_Concurrent_Type (Scope (Spec_Discriminant));
7574 end if;
7576 -- Find discriminant of original concurrent type, and use its current
7577 -- discriminal, which is the renaming within the task/protected body.
7579 Disc := First_Discriminant (Tsk);
7580 while Present (Disc) loop
7581 if Chars (Disc) = Chars (Spec_Discriminant) then
7582 return Discriminal (Disc);
7583 end if;
7585 Next_Discriminant (Disc);
7586 end loop;
7588 -- That loop should always succeed in finding a matching entry and
7589 -- returning. Fatal error if not.
7591 raise Program_Error;
7592 end Find_Body_Discriminal;
7594 -------------------------------------
7595 -- Find_Corresponding_Discriminant --
7596 -------------------------------------
7598 function Find_Corresponding_Discriminant
7599 (Id : Node_Id;
7600 Typ : Entity_Id) return Entity_Id
7602 Par_Disc : Entity_Id;
7603 Old_Disc : Entity_Id;
7604 New_Disc : Entity_Id;
7606 begin
7607 Par_Disc := Original_Record_Component (Original_Discriminant (Id));
7609 -- The original type may currently be private, and the discriminant
7610 -- only appear on its full view.
7612 if Is_Private_Type (Scope (Par_Disc))
7613 and then not Has_Discriminants (Scope (Par_Disc))
7614 and then Present (Full_View (Scope (Par_Disc)))
7615 then
7616 Old_Disc := First_Discriminant (Full_View (Scope (Par_Disc)));
7617 else
7618 Old_Disc := First_Discriminant (Scope (Par_Disc));
7619 end if;
7621 if Is_Class_Wide_Type (Typ) then
7622 New_Disc := First_Discriminant (Root_Type (Typ));
7623 else
7624 New_Disc := First_Discriminant (Typ);
7625 end if;
7627 while Present (Old_Disc) and then Present (New_Disc) loop
7628 if Old_Disc = Par_Disc then
7629 return New_Disc;
7630 end if;
7632 Next_Discriminant (Old_Disc);
7633 Next_Discriminant (New_Disc);
7634 end loop;
7636 -- Should always find it
7638 raise Program_Error;
7639 end Find_Corresponding_Discriminant;
7641 -------------------
7642 -- Find_DIC_Type --
7643 -------------------
7645 function Find_DIC_Type (Typ : Entity_Id) return Entity_Id is
7646 Curr_Typ : Entity_Id;
7647 -- The current type being examined in the parent hierarchy traversal
7649 DIC_Typ : Entity_Id;
7650 -- The type which carries the DIC pragma. This variable denotes the
7651 -- partial view when private types are involved.
7653 Par_Typ : Entity_Id;
7654 -- The parent type of the current type. This variable denotes the full
7655 -- view when private types are involved.
7657 begin
7658 -- The input type defines its own DIC pragma, therefore it is the owner
7660 if Has_Own_DIC (Typ) then
7661 DIC_Typ := Typ;
7663 -- Otherwise the DIC pragma is inherited from a parent type
7665 else
7666 pragma Assert (Has_Inherited_DIC (Typ));
7668 -- Climb the parent chain
7670 Curr_Typ := Typ;
7671 loop
7672 -- Inspect the parent type. Do not consider subtypes as they
7673 -- inherit the DIC attributes from their base types.
7675 DIC_Typ := Base_Type (Etype (Curr_Typ));
7677 -- Look at the full view of a private type because the type may
7678 -- have a hidden parent introduced in the full view.
7680 Par_Typ := DIC_Typ;
7682 if Is_Private_Type (Par_Typ)
7683 and then Present (Full_View (Par_Typ))
7684 then
7685 Par_Typ := Full_View (Par_Typ);
7686 end if;
7688 -- Stop the climb once the nearest parent type which defines a DIC
7689 -- pragma of its own is encountered or when the root of the parent
7690 -- chain is reached.
7692 exit when Has_Own_DIC (DIC_Typ) or else Curr_Typ = Par_Typ;
7694 Curr_Typ := Par_Typ;
7695 end loop;
7696 end if;
7698 return DIC_Typ;
7699 end Find_DIC_Type;
7701 ----------------------------------
7702 -- Find_Enclosing_Iterator_Loop --
7703 ----------------------------------
7705 function Find_Enclosing_Iterator_Loop (Id : Entity_Id) return Entity_Id is
7706 Constr : Node_Id;
7707 S : Entity_Id;
7709 begin
7710 -- Traverse the scope chain looking for an iterator loop. Such loops are
7711 -- usually transformed into blocks, hence the use of Original_Node.
7713 S := Id;
7714 while Present (S) and then S /= Standard_Standard loop
7715 if Ekind (S) = E_Loop
7716 and then Nkind (Parent (S)) = N_Implicit_Label_Declaration
7717 then
7718 Constr := Original_Node (Label_Construct (Parent (S)));
7720 if Nkind (Constr) = N_Loop_Statement
7721 and then Present (Iteration_Scheme (Constr))
7722 and then Nkind (Iterator_Specification
7723 (Iteration_Scheme (Constr))) =
7724 N_Iterator_Specification
7725 then
7726 return S;
7727 end if;
7728 end if;
7730 S := Scope (S);
7731 end loop;
7733 return Empty;
7734 end Find_Enclosing_Iterator_Loop;
7736 --------------------------
7737 -- Find_Enclosing_Scope --
7738 --------------------------
7740 function Find_Enclosing_Scope (N : Node_Id) return Entity_Id is
7741 Par : Node_Id;
7742 Spec_Id : Entity_Id;
7744 begin
7745 -- Examine the parent chain looking for a construct which defines a
7746 -- scope.
7748 Par := Parent (N);
7749 while Present (Par) loop
7750 case Nkind (Par) is
7752 -- The construct denotes a declaration, the proper scope is its
7753 -- entity.
7755 when N_Entry_Declaration
7756 | N_Expression_Function
7757 | N_Full_Type_Declaration
7758 | N_Generic_Package_Declaration
7759 | N_Generic_Subprogram_Declaration
7760 | N_Package_Declaration
7761 | N_Private_Extension_Declaration
7762 | N_Protected_Type_Declaration
7763 | N_Single_Protected_Declaration
7764 | N_Single_Task_Declaration
7765 | N_Subprogram_Declaration
7766 | N_Task_Type_Declaration
7768 return Defining_Entity (Par);
7770 -- The construct denotes a body, the proper scope is the entity of
7771 -- the corresponding spec.
7773 when N_Entry_Body
7774 | N_Package_Body
7775 | N_Protected_Body
7776 | N_Subprogram_Body
7777 | N_Task_Body
7779 Spec_Id := Corresponding_Spec (Par);
7781 -- The defining entity of a stand-alone subprogram body defines
7782 -- a scope.
7784 if Nkind (Par) = N_Subprogram_Body and then No (Spec_Id) then
7785 return Defining_Entity (Par);
7787 -- Otherwise there should be corresponding spec which defines a
7788 -- scope.
7790 else
7791 pragma Assert (Present (Spec_Id));
7793 return Spec_Id;
7794 end if;
7796 -- Special cases
7798 -- Blocks carry either a source or an internally-generated scope,
7799 -- unless the block is a byproduct of exception handling.
7801 when N_Block_Statement =>
7802 if not Exception_Junk (Par) then
7803 return Entity (Identifier (Par));
7804 end if;
7806 -- Loops carry an internally-generated scope
7808 when N_Loop_Statement =>
7809 return Entity (Identifier (Par));
7811 -- Extended return statements carry an internally-generated scope
7813 when N_Extended_Return_Statement =>
7814 return Return_Statement_Entity (Par);
7816 -- A traversal from a subunit continues via the corresponding stub
7818 when N_Subunit =>
7819 Par := Corresponding_Stub (Par);
7821 when others =>
7822 null;
7823 end case;
7825 Par := Parent (Par);
7826 end loop;
7828 return Standard_Standard;
7829 end Find_Enclosing_Scope;
7831 ------------------------------------
7832 -- Find_Loop_In_Conditional_Block --
7833 ------------------------------------
7835 function Find_Loop_In_Conditional_Block (N : Node_Id) return Node_Id is
7836 Stmt : Node_Id;
7838 begin
7839 Stmt := N;
7841 if Nkind (Stmt) = N_If_Statement then
7842 Stmt := First (Then_Statements (Stmt));
7843 end if;
7845 pragma Assert (Nkind (Stmt) = N_Block_Statement);
7847 -- Inspect the statements of the conditional block. In general the loop
7848 -- should be the first statement in the statement sequence of the block,
7849 -- but the finalization machinery may have introduced extra object
7850 -- declarations.
7852 Stmt := First (Statements (Handled_Statement_Sequence (Stmt)));
7853 while Present (Stmt) loop
7854 if Nkind (Stmt) = N_Loop_Statement then
7855 return Stmt;
7856 end if;
7858 Next (Stmt);
7859 end loop;
7861 -- The expansion of attribute 'Loop_Entry produced a malformed block
7863 raise Program_Error;
7864 end Find_Loop_In_Conditional_Block;
7866 --------------------------
7867 -- Find_Overlaid_Entity --
7868 --------------------------
7870 procedure Find_Overlaid_Entity
7871 (N : Node_Id;
7872 Ent : out Entity_Id;
7873 Off : out Boolean)
7875 Expr : Node_Id;
7877 begin
7878 -- We are looking for one of the two following forms:
7880 -- for X'Address use Y'Address
7882 -- or
7884 -- Const : constant Address := expr;
7885 -- ...
7886 -- for X'Address use Const;
7888 -- In the second case, the expr is either Y'Address, or recursively a
7889 -- constant that eventually references Y'Address.
7891 Ent := Empty;
7892 Off := False;
7894 if Nkind (N) = N_Attribute_Definition_Clause
7895 and then Chars (N) = Name_Address
7896 then
7897 Expr := Expression (N);
7899 -- This loop checks the form of the expression for Y'Address,
7900 -- using recursion to deal with intermediate constants.
7902 loop
7903 -- Check for Y'Address
7905 if Nkind (Expr) = N_Attribute_Reference
7906 and then Attribute_Name (Expr) = Name_Address
7907 then
7908 Expr := Prefix (Expr);
7909 exit;
7911 -- Check for Const where Const is a constant entity
7913 elsif Is_Entity_Name (Expr)
7914 and then Ekind (Entity (Expr)) = E_Constant
7915 then
7916 Expr := Constant_Value (Entity (Expr));
7918 -- Anything else does not need checking
7920 else
7921 return;
7922 end if;
7923 end loop;
7925 -- This loop checks the form of the prefix for an entity, using
7926 -- recursion to deal with intermediate components.
7928 loop
7929 -- Check for Y where Y is an entity
7931 if Is_Entity_Name (Expr) then
7932 Ent := Entity (Expr);
7933 return;
7935 -- Check for components
7937 elsif
7938 Nkind_In (Expr, N_Selected_Component, N_Indexed_Component)
7939 then
7940 Expr := Prefix (Expr);
7941 Off := True;
7943 -- Anything else does not need checking
7945 else
7946 return;
7947 end if;
7948 end loop;
7949 end if;
7950 end Find_Overlaid_Entity;
7952 -------------------------
7953 -- Find_Parameter_Type --
7954 -------------------------
7956 function Find_Parameter_Type (Param : Node_Id) return Entity_Id is
7957 begin
7958 if Nkind (Param) /= N_Parameter_Specification then
7959 return Empty;
7961 -- For an access parameter, obtain the type from the formal entity
7962 -- itself, because access to subprogram nodes do not carry a type.
7963 -- Shouldn't we always use the formal entity ???
7965 elsif Nkind (Parameter_Type (Param)) = N_Access_Definition then
7966 return Etype (Defining_Identifier (Param));
7968 else
7969 return Etype (Parameter_Type (Param));
7970 end if;
7971 end Find_Parameter_Type;
7973 -----------------------------------
7974 -- Find_Placement_In_State_Space --
7975 -----------------------------------
7977 procedure Find_Placement_In_State_Space
7978 (Item_Id : Entity_Id;
7979 Placement : out State_Space_Kind;
7980 Pack_Id : out Entity_Id)
7982 Context : Entity_Id;
7984 begin
7985 -- Assume that the item does not appear in the state space of a package
7987 Placement := Not_In_Package;
7988 Pack_Id := Empty;
7990 -- Climb the scope stack and examine the enclosing context
7992 Context := Scope (Item_Id);
7993 while Present (Context) and then Context /= Standard_Standard loop
7994 if Is_Package_Or_Generic_Package (Context) then
7995 Pack_Id := Context;
7997 -- A package body is a cut off point for the traversal as the item
7998 -- cannot be visible to the outside from this point on. Note that
7999 -- this test must be done first as a body is also classified as a
8000 -- private part.
8002 if In_Package_Body (Context) then
8003 Placement := Body_State_Space;
8004 return;
8006 -- The private part of a package is a cut off point for the
8007 -- traversal as the item cannot be visible to the outside from
8008 -- this point on.
8010 elsif In_Private_Part (Context) then
8011 Placement := Private_State_Space;
8012 return;
8014 -- When the item appears in the visible state space of a package,
8015 -- continue to climb the scope stack as this may not be the final
8016 -- state space.
8018 else
8019 Placement := Visible_State_Space;
8021 -- The visible state space of a child unit acts as the proper
8022 -- placement of an item.
8024 if Is_Child_Unit (Context) then
8025 return;
8026 end if;
8027 end if;
8029 -- The item or its enclosing package appear in a construct that has
8030 -- no state space.
8032 else
8033 Placement := Not_In_Package;
8034 return;
8035 end if;
8037 Context := Scope (Context);
8038 end loop;
8039 end Find_Placement_In_State_Space;
8041 ------------------------
8042 -- Find_Specific_Type --
8043 ------------------------
8045 function Find_Specific_Type (CW : Entity_Id) return Entity_Id is
8046 Typ : Entity_Id := Root_Type (CW);
8048 begin
8049 if Ekind (Typ) = E_Incomplete_Type then
8050 if From_Limited_With (Typ) then
8051 Typ := Non_Limited_View (Typ);
8052 else
8053 Typ := Full_View (Typ);
8054 end if;
8055 end if;
8057 if Is_Private_Type (Typ)
8058 and then not Is_Tagged_Type (Typ)
8059 and then Present (Full_View (Typ))
8060 then
8061 return Full_View (Typ);
8062 else
8063 return Typ;
8064 end if;
8065 end Find_Specific_Type;
8067 -----------------------------
8068 -- Find_Static_Alternative --
8069 -----------------------------
8071 function Find_Static_Alternative (N : Node_Id) return Node_Id is
8072 Expr : constant Node_Id := Expression (N);
8073 Val : constant Uint := Expr_Value (Expr);
8074 Alt : Node_Id;
8075 Choice : Node_Id;
8077 begin
8078 Alt := First (Alternatives (N));
8080 Search : loop
8081 if Nkind (Alt) /= N_Pragma then
8082 Choice := First (Discrete_Choices (Alt));
8083 while Present (Choice) loop
8085 -- Others choice, always matches
8087 if Nkind (Choice) = N_Others_Choice then
8088 exit Search;
8090 -- Range, check if value is in the range
8092 elsif Nkind (Choice) = N_Range then
8093 exit Search when
8094 Val >= Expr_Value (Low_Bound (Choice))
8095 and then
8096 Val <= Expr_Value (High_Bound (Choice));
8098 -- Choice is a subtype name. Note that we know it must
8099 -- be a static subtype, since otherwise it would have
8100 -- been diagnosed as illegal.
8102 elsif Is_Entity_Name (Choice)
8103 and then Is_Type (Entity (Choice))
8104 then
8105 exit Search when Is_In_Range (Expr, Etype (Choice),
8106 Assume_Valid => False);
8108 -- Choice is a subtype indication
8110 elsif Nkind (Choice) = N_Subtype_Indication then
8111 declare
8112 C : constant Node_Id := Constraint (Choice);
8113 R : constant Node_Id := Range_Expression (C);
8115 begin
8116 exit Search when
8117 Val >= Expr_Value (Low_Bound (R))
8118 and then
8119 Val <= Expr_Value (High_Bound (R));
8120 end;
8122 -- Choice is a simple expression
8124 else
8125 exit Search when Val = Expr_Value (Choice);
8126 end if;
8128 Next (Choice);
8129 end loop;
8130 end if;
8132 Next (Alt);
8133 pragma Assert (Present (Alt));
8134 end loop Search;
8136 -- The above loop *must* terminate by finding a match, since we know the
8137 -- case statement is valid, and the value of the expression is known at
8138 -- compile time. When we fall out of the loop, Alt points to the
8139 -- alternative that we know will be selected at run time.
8141 return Alt;
8142 end Find_Static_Alternative;
8144 ------------------
8145 -- First_Actual --
8146 ------------------
8148 function First_Actual (Node : Node_Id) return Node_Id is
8149 N : Node_Id;
8151 begin
8152 if No (Parameter_Associations (Node)) then
8153 return Empty;
8154 end if;
8156 N := First (Parameter_Associations (Node));
8158 if Nkind (N) = N_Parameter_Association then
8159 return First_Named_Actual (Node);
8160 else
8161 return N;
8162 end if;
8163 end First_Actual;
8165 ------------------
8166 -- First_Global --
8167 ------------------
8169 function First_Global
8170 (Subp : Entity_Id;
8171 Global_Mode : Name_Id;
8172 Refined : Boolean := False) return Node_Id
8174 function First_From_Global_List
8175 (List : Node_Id;
8176 Global_Mode : Name_Id := Name_Input) return Entity_Id;
8177 -- Get the first item with suitable mode from List
8179 ----------------------------
8180 -- First_From_Global_List --
8181 ----------------------------
8183 function First_From_Global_List
8184 (List : Node_Id;
8185 Global_Mode : Name_Id := Name_Input) return Entity_Id
8187 Assoc : Node_Id;
8189 begin
8190 -- Empty list (no global items)
8192 if Nkind (List) = N_Null then
8193 return Empty;
8195 -- Single global item declaration (only input items)
8197 elsif Nkind_In (List, N_Expanded_Name,
8198 N_Identifier,
8199 N_Selected_Component)
8200 then
8201 if Global_Mode = Name_Input then
8202 return List;
8203 else
8204 return Empty;
8205 end if;
8207 -- Simple global list (only input items) or moded global list
8208 -- declaration.
8210 elsif Nkind (List) = N_Aggregate then
8211 if Present (Expressions (List)) then
8212 if Global_Mode = Name_Input then
8213 return First (Expressions (List));
8214 else
8215 return Empty;
8216 end if;
8218 else
8219 Assoc := First (Component_Associations (List));
8220 while Present (Assoc) loop
8222 -- When we find the desired mode in an association, call
8223 -- recursively First_From_Global_List as if the mode was
8224 -- Name_Input, in order to reuse the existing machinery
8225 -- for the other cases.
8227 if Chars (First (Choices (Assoc))) = Global_Mode then
8228 return First_From_Global_List (Expression (Assoc));
8229 end if;
8231 Next (Assoc);
8232 end loop;
8234 return Empty;
8235 end if;
8237 -- To accommodate partial decoration of disabled SPARK features,
8238 -- this routine may be called with illegal input. If this is the
8239 -- case, do not raise Program_Error.
8241 else
8242 return Empty;
8243 end if;
8244 end First_From_Global_List;
8246 -- Local variables
8248 Global : Node_Id := Empty;
8249 Body_Id : Entity_Id;
8251 begin
8252 pragma Assert (Global_Mode = Name_Input
8253 or else Global_Mode = Name_Output
8254 or else Global_Mode = Name_In_Out
8255 or else Global_Mode = Name_Proof_In);
8257 -- Retrieve the suitable pragma Global or Refined_Global. In the second
8258 -- case, it can only be located on the body entity.
8260 if Refined then
8261 Body_Id := Subprogram_Body_Entity (Subp);
8262 if Present (Body_Id) then
8263 Global := Get_Pragma (Body_Id, Pragma_Refined_Global);
8264 end if;
8265 else
8266 Global := Get_Pragma (Subp, Pragma_Global);
8267 end if;
8269 -- No corresponding global if pragma is not present
8271 if No (Global) then
8272 return Empty;
8274 -- Otherwise retrieve the corresponding list of items depending on the
8275 -- Global_Mode.
8277 else
8278 return First_From_Global_List
8279 (Expression (Get_Argument (Global, Subp)), Global_Mode);
8280 end if;
8281 end First_Global;
8283 -------------
8284 -- Fix_Msg --
8285 -------------
8287 function Fix_Msg (Id : Entity_Id; Msg : String) return String is
8288 Is_Task : constant Boolean :=
8289 Ekind_In (Id, E_Task_Body, E_Task_Type)
8290 or else Is_Single_Task_Object (Id);
8291 Msg_Last : constant Natural := Msg'Last;
8292 Msg_Index : Natural;
8293 Res : String (Msg'Range) := (others => ' ');
8294 Res_Index : Natural;
8296 begin
8297 -- Copy all characters from the input message Msg to result Res with
8298 -- suitable replacements.
8300 Msg_Index := Msg'First;
8301 Res_Index := Res'First;
8302 while Msg_Index <= Msg_Last loop
8304 -- Replace "subprogram" with a different word
8306 if Msg_Index <= Msg_Last - 10
8307 and then Msg (Msg_Index .. Msg_Index + 9) = "subprogram"
8308 then
8309 if Ekind_In (Id, E_Entry, E_Entry_Family) then
8310 Res (Res_Index .. Res_Index + 4) := "entry";
8311 Res_Index := Res_Index + 5;
8313 elsif Is_Task then
8314 Res (Res_Index .. Res_Index + 8) := "task type";
8315 Res_Index := Res_Index + 9;
8317 else
8318 Res (Res_Index .. Res_Index + 9) := "subprogram";
8319 Res_Index := Res_Index + 10;
8320 end if;
8322 Msg_Index := Msg_Index + 10;
8324 -- Replace "protected" with a different word
8326 elsif Msg_Index <= Msg_Last - 9
8327 and then Msg (Msg_Index .. Msg_Index + 8) = "protected"
8328 and then Is_Task
8329 then
8330 Res (Res_Index .. Res_Index + 3) := "task";
8331 Res_Index := Res_Index + 4;
8332 Msg_Index := Msg_Index + 9;
8334 -- Otherwise copy the character
8336 else
8337 Res (Res_Index) := Msg (Msg_Index);
8338 Msg_Index := Msg_Index + 1;
8339 Res_Index := Res_Index + 1;
8340 end if;
8341 end loop;
8343 return Res (Res'First .. Res_Index - 1);
8344 end Fix_Msg;
8346 -------------------------
8347 -- From_Nested_Package --
8348 -------------------------
8350 function From_Nested_Package (T : Entity_Id) return Boolean is
8351 Pack : constant Entity_Id := Scope (T);
8353 begin
8354 return
8355 Ekind (Pack) = E_Package
8356 and then not Is_Frozen (Pack)
8357 and then not Scope_Within_Or_Same (Current_Scope, Pack)
8358 and then In_Open_Scopes (Scope (Pack));
8359 end From_Nested_Package;
8361 -----------------------
8362 -- Gather_Components --
8363 -----------------------
8365 procedure Gather_Components
8366 (Typ : Entity_Id;
8367 Comp_List : Node_Id;
8368 Governed_By : List_Id;
8369 Into : Elist_Id;
8370 Report_Errors : out Boolean)
8372 Assoc : Node_Id;
8373 Variant : Node_Id;
8374 Discrete_Choice : Node_Id;
8375 Comp_Item : Node_Id;
8377 Discrim : Entity_Id;
8378 Discrim_Name : Node_Id;
8379 Discrim_Value : Node_Id;
8381 begin
8382 Report_Errors := False;
8384 if No (Comp_List) or else Null_Present (Comp_List) then
8385 return;
8387 elsif Present (Component_Items (Comp_List)) then
8388 Comp_Item := First (Component_Items (Comp_List));
8390 else
8391 Comp_Item := Empty;
8392 end if;
8394 while Present (Comp_Item) loop
8396 -- Skip the tag of a tagged record, the interface tags, as well
8397 -- as all items that are not user components (anonymous types,
8398 -- rep clauses, Parent field, controller field).
8400 if Nkind (Comp_Item) = N_Component_Declaration then
8401 declare
8402 Comp : constant Entity_Id := Defining_Identifier (Comp_Item);
8403 begin
8404 if not Is_Tag (Comp) and then Chars (Comp) /= Name_uParent then
8405 Append_Elmt (Comp, Into);
8406 end if;
8407 end;
8408 end if;
8410 Next (Comp_Item);
8411 end loop;
8413 if No (Variant_Part (Comp_List)) then
8414 return;
8415 else
8416 Discrim_Name := Name (Variant_Part (Comp_List));
8417 Variant := First_Non_Pragma (Variants (Variant_Part (Comp_List)));
8418 end if;
8420 -- Look for the discriminant that governs this variant part.
8421 -- The discriminant *must* be in the Governed_By List
8423 Assoc := First (Governed_By);
8424 Find_Constraint : loop
8425 Discrim := First (Choices (Assoc));
8426 exit Find_Constraint when Chars (Discrim_Name) = Chars (Discrim)
8427 or else (Present (Corresponding_Discriminant (Entity (Discrim)))
8428 and then
8429 Chars (Corresponding_Discriminant (Entity (Discrim))) =
8430 Chars (Discrim_Name))
8431 or else Chars (Original_Record_Component (Entity (Discrim)))
8432 = Chars (Discrim_Name);
8434 if No (Next (Assoc)) then
8435 if not Is_Constrained (Typ)
8436 and then Is_Derived_Type (Typ)
8437 and then Present (Stored_Constraint (Typ))
8438 then
8439 -- If the type is a tagged type with inherited discriminants,
8440 -- use the stored constraint on the parent in order to find
8441 -- the values of discriminants that are otherwise hidden by an
8442 -- explicit constraint. Renamed discriminants are handled in
8443 -- the code above.
8445 -- If several parent discriminants are renamed by a single
8446 -- discriminant of the derived type, the call to obtain the
8447 -- Corresponding_Discriminant field only retrieves the last
8448 -- of them. We recover the constraint on the others from the
8449 -- Stored_Constraint as well.
8451 declare
8452 D : Entity_Id;
8453 C : Elmt_Id;
8455 begin
8456 D := First_Discriminant (Etype (Typ));
8457 C := First_Elmt (Stored_Constraint (Typ));
8458 while Present (D) and then Present (C) loop
8459 if Chars (Discrim_Name) = Chars (D) then
8460 if Is_Entity_Name (Node (C))
8461 and then Entity (Node (C)) = Entity (Discrim)
8462 then
8463 -- D is renamed by Discrim, whose value is given in
8464 -- Assoc.
8466 null;
8468 else
8469 Assoc :=
8470 Make_Component_Association (Sloc (Typ),
8471 New_List
8472 (New_Occurrence_Of (D, Sloc (Typ))),
8473 Duplicate_Subexpr_No_Checks (Node (C)));
8474 end if;
8475 exit Find_Constraint;
8476 end if;
8478 Next_Discriminant (D);
8479 Next_Elmt (C);
8480 end loop;
8481 end;
8482 end if;
8483 end if;
8485 if No (Next (Assoc)) then
8486 Error_Msg_NE (" missing value for discriminant&",
8487 First (Governed_By), Discrim_Name);
8488 Report_Errors := True;
8489 return;
8490 end if;
8492 Next (Assoc);
8493 end loop Find_Constraint;
8495 Discrim_Value := Expression (Assoc);
8497 if not Is_OK_Static_Expression (Discrim_Value) then
8499 -- If the variant part is governed by a discriminant of the type
8500 -- this is an error. If the variant part and the discriminant are
8501 -- inherited from an ancestor this is legal (AI05-120) unless the
8502 -- components are being gathered for an aggregate, in which case
8503 -- the caller must check Report_Errors.
8505 if Scope (Original_Record_Component
8506 ((Entity (First (Choices (Assoc)))))) = Typ
8507 then
8508 Error_Msg_FE
8509 ("value for discriminant & must be static!",
8510 Discrim_Value, Discrim);
8511 Why_Not_Static (Discrim_Value);
8512 end if;
8514 Report_Errors := True;
8515 return;
8516 end if;
8518 Search_For_Discriminant_Value : declare
8519 Low : Node_Id;
8520 High : Node_Id;
8522 UI_High : Uint;
8523 UI_Low : Uint;
8524 UI_Discrim_Value : constant Uint := Expr_Value (Discrim_Value);
8526 begin
8527 Find_Discrete_Value : while Present (Variant) loop
8528 Discrete_Choice := First (Discrete_Choices (Variant));
8529 while Present (Discrete_Choice) loop
8530 exit Find_Discrete_Value when
8531 Nkind (Discrete_Choice) = N_Others_Choice;
8533 Get_Index_Bounds (Discrete_Choice, Low, High);
8535 UI_Low := Expr_Value (Low);
8536 UI_High := Expr_Value (High);
8538 exit Find_Discrete_Value when
8539 UI_Low <= UI_Discrim_Value
8540 and then
8541 UI_High >= UI_Discrim_Value;
8543 Next (Discrete_Choice);
8544 end loop;
8546 Next_Non_Pragma (Variant);
8547 end loop Find_Discrete_Value;
8548 end Search_For_Discriminant_Value;
8550 -- The case statement must include a variant that corresponds to the
8551 -- value of the discriminant, unless the discriminant type has a
8552 -- static predicate. In that case the absence of an others_choice that
8553 -- would cover this value becomes a run-time error (3.8,1 (21.1/2)).
8555 if No (Variant)
8556 and then not Has_Static_Predicate (Etype (Discrim_Name))
8557 then
8558 Error_Msg_NE
8559 ("value of discriminant & is out of range", Discrim_Value, Discrim);
8560 Report_Errors := True;
8561 return;
8562 end if;
8564 -- If we have found the corresponding choice, recursively add its
8565 -- components to the Into list. The nested components are part of
8566 -- the same record type.
8568 if Present (Variant) then
8569 Gather_Components
8570 (Typ, Component_List (Variant), Governed_By, Into, Report_Errors);
8571 end if;
8572 end Gather_Components;
8574 ------------------------
8575 -- Get_Actual_Subtype --
8576 ------------------------
8578 function Get_Actual_Subtype (N : Node_Id) return Entity_Id is
8579 Typ : constant Entity_Id := Etype (N);
8580 Utyp : Entity_Id := Underlying_Type (Typ);
8581 Decl : Node_Id;
8582 Atyp : Entity_Id;
8584 begin
8585 if No (Utyp) then
8586 Utyp := Typ;
8587 end if;
8589 -- If what we have is an identifier that references a subprogram
8590 -- formal, or a variable or constant object, then we get the actual
8591 -- subtype from the referenced entity if one has been built.
8593 if Nkind (N) = N_Identifier
8594 and then
8595 (Is_Formal (Entity (N))
8596 or else Ekind (Entity (N)) = E_Constant
8597 or else Ekind (Entity (N)) = E_Variable)
8598 and then Present (Actual_Subtype (Entity (N)))
8599 then
8600 return Actual_Subtype (Entity (N));
8602 -- Actual subtype of unchecked union is always itself. We never need
8603 -- the "real" actual subtype. If we did, we couldn't get it anyway
8604 -- because the discriminant is not available. The restrictions on
8605 -- Unchecked_Union are designed to make sure that this is OK.
8607 elsif Is_Unchecked_Union (Base_Type (Utyp)) then
8608 return Typ;
8610 -- Here for the unconstrained case, we must find actual subtype
8611 -- No actual subtype is available, so we must build it on the fly.
8613 -- Checking the type, not the underlying type, for constrainedness
8614 -- seems to be necessary. Maybe all the tests should be on the type???
8616 elsif (not Is_Constrained (Typ))
8617 and then (Is_Array_Type (Utyp)
8618 or else (Is_Record_Type (Utyp)
8619 and then Has_Discriminants (Utyp)))
8620 and then not Has_Unknown_Discriminants (Utyp)
8621 and then not (Ekind (Utyp) = E_String_Literal_Subtype)
8622 then
8623 -- Nothing to do if in spec expression (why not???)
8625 if In_Spec_Expression then
8626 return Typ;
8628 elsif Is_Private_Type (Typ) and then not Has_Discriminants (Typ) then
8630 -- If the type has no discriminants, there is no subtype to
8631 -- build, even if the underlying type is discriminated.
8633 return Typ;
8635 -- Else build the actual subtype
8637 else
8638 Decl := Build_Actual_Subtype (Typ, N);
8639 Atyp := Defining_Identifier (Decl);
8641 -- If Build_Actual_Subtype generated a new declaration then use it
8643 if Atyp /= Typ then
8645 -- The actual subtype is an Itype, so analyze the declaration,
8646 -- but do not attach it to the tree, to get the type defined.
8648 Set_Parent (Decl, N);
8649 Set_Is_Itype (Atyp);
8650 Analyze (Decl, Suppress => All_Checks);
8651 Set_Associated_Node_For_Itype (Atyp, N);
8652 Set_Has_Delayed_Freeze (Atyp, False);
8654 -- We need to freeze the actual subtype immediately. This is
8655 -- needed, because otherwise this Itype will not get frozen
8656 -- at all, and it is always safe to freeze on creation because
8657 -- any associated types must be frozen at this point.
8659 Freeze_Itype (Atyp, N);
8660 return Atyp;
8662 -- Otherwise we did not build a declaration, so return original
8664 else
8665 return Typ;
8666 end if;
8667 end if;
8669 -- For all remaining cases, the actual subtype is the same as
8670 -- the nominal type.
8672 else
8673 return Typ;
8674 end if;
8675 end Get_Actual_Subtype;
8677 -------------------------------------
8678 -- Get_Actual_Subtype_If_Available --
8679 -------------------------------------
8681 function Get_Actual_Subtype_If_Available (N : Node_Id) return Entity_Id is
8682 Typ : constant Entity_Id := Etype (N);
8684 begin
8685 -- If what we have is an identifier that references a subprogram
8686 -- formal, or a variable or constant object, then we get the actual
8687 -- subtype from the referenced entity if one has been built.
8689 if Nkind (N) = N_Identifier
8690 and then
8691 (Is_Formal (Entity (N))
8692 or else Ekind (Entity (N)) = E_Constant
8693 or else Ekind (Entity (N)) = E_Variable)
8694 and then Present (Actual_Subtype (Entity (N)))
8695 then
8696 return Actual_Subtype (Entity (N));
8698 -- Otherwise the Etype of N is returned unchanged
8700 else
8701 return Typ;
8702 end if;
8703 end Get_Actual_Subtype_If_Available;
8705 ------------------------
8706 -- Get_Body_From_Stub --
8707 ------------------------
8709 function Get_Body_From_Stub (N : Node_Id) return Node_Id is
8710 begin
8711 return Proper_Body (Unit (Library_Unit (N)));
8712 end Get_Body_From_Stub;
8714 ---------------------
8715 -- Get_Cursor_Type --
8716 ---------------------
8718 function Get_Cursor_Type
8719 (Aspect : Node_Id;
8720 Typ : Entity_Id) return Entity_Id
8722 Assoc : Node_Id;
8723 Func : Entity_Id;
8724 First_Op : Entity_Id;
8725 Cursor : Entity_Id;
8727 begin
8728 -- If error already detected, return
8730 if Error_Posted (Aspect) then
8731 return Any_Type;
8732 end if;
8734 -- The cursor type for an Iterable aspect is the return type of a
8735 -- non-overloaded First primitive operation. Locate association for
8736 -- First.
8738 Assoc := First (Component_Associations (Expression (Aspect)));
8739 First_Op := Any_Id;
8740 while Present (Assoc) loop
8741 if Chars (First (Choices (Assoc))) = Name_First then
8742 First_Op := Expression (Assoc);
8743 exit;
8744 end if;
8746 Next (Assoc);
8747 end loop;
8749 if First_Op = Any_Id then
8750 Error_Msg_N ("aspect Iterable must specify First operation", Aspect);
8751 return Any_Type;
8752 end if;
8754 Cursor := Any_Type;
8756 -- Locate function with desired name and profile in scope of type
8757 -- In the rare case where the type is an integer type, a base type
8758 -- is created for it, check that the base type of the first formal
8759 -- of First matches the base type of the domain.
8761 Func := First_Entity (Scope (Typ));
8762 while Present (Func) loop
8763 if Chars (Func) = Chars (First_Op)
8764 and then Ekind (Func) = E_Function
8765 and then Present (First_Formal (Func))
8766 and then Base_Type (Etype (First_Formal (Func))) = Base_Type (Typ)
8767 and then No (Next_Formal (First_Formal (Func)))
8768 then
8769 if Cursor /= Any_Type then
8770 Error_Msg_N
8771 ("Operation First for iterable type must be unique", Aspect);
8772 return Any_Type;
8773 else
8774 Cursor := Etype (Func);
8775 end if;
8776 end if;
8778 Next_Entity (Func);
8779 end loop;
8781 -- If not found, no way to resolve remaining primitives.
8783 if Cursor = Any_Type then
8784 Error_Msg_N
8785 ("No legal primitive operation First for Iterable type", Aspect);
8786 end if;
8788 return Cursor;
8789 end Get_Cursor_Type;
8791 function Get_Cursor_Type (Typ : Entity_Id) return Entity_Id is
8792 begin
8793 return Etype (Get_Iterable_Type_Primitive (Typ, Name_First));
8794 end Get_Cursor_Type;
8796 -------------------------------
8797 -- Get_Default_External_Name --
8798 -------------------------------
8800 function Get_Default_External_Name (E : Node_Or_Entity_Id) return Node_Id is
8801 begin
8802 Get_Decoded_Name_String (Chars (E));
8804 if Opt.External_Name_Imp_Casing = Uppercase then
8805 Set_Casing (All_Upper_Case);
8806 else
8807 Set_Casing (All_Lower_Case);
8808 end if;
8810 return
8811 Make_String_Literal (Sloc (E),
8812 Strval => String_From_Name_Buffer);
8813 end Get_Default_External_Name;
8815 --------------------------
8816 -- Get_Enclosing_Object --
8817 --------------------------
8819 function Get_Enclosing_Object (N : Node_Id) return Entity_Id is
8820 begin
8821 if Is_Entity_Name (N) then
8822 return Entity (N);
8823 else
8824 case Nkind (N) is
8825 when N_Indexed_Component
8826 | N_Selected_Component
8827 | N_Slice
8829 -- If not generating code, a dereference may be left implicit.
8830 -- In thoses cases, return Empty.
8832 if Is_Access_Type (Etype (Prefix (N))) then
8833 return Empty;
8834 else
8835 return Get_Enclosing_Object (Prefix (N));
8836 end if;
8838 when N_Type_Conversion =>
8839 return Get_Enclosing_Object (Expression (N));
8841 when others =>
8842 return Empty;
8843 end case;
8844 end if;
8845 end Get_Enclosing_Object;
8847 ---------------------------
8848 -- Get_Enum_Lit_From_Pos --
8849 ---------------------------
8851 function Get_Enum_Lit_From_Pos
8852 (T : Entity_Id;
8853 Pos : Uint;
8854 Loc : Source_Ptr) return Node_Id
8856 Btyp : Entity_Id := Base_Type (T);
8857 Lit : Node_Id;
8858 LLoc : Source_Ptr;
8860 begin
8861 -- In the case where the literal is of type Character, Wide_Character
8862 -- or Wide_Wide_Character or of a type derived from them, there needs
8863 -- to be some special handling since there is no explicit chain of
8864 -- literals to search. Instead, an N_Character_Literal node is created
8865 -- with the appropriate Char_Code and Chars fields.
8867 if Is_Standard_Character_Type (T) then
8868 Set_Character_Literal_Name (UI_To_CC (Pos));
8870 return
8871 Make_Character_Literal (Loc,
8872 Chars => Name_Find,
8873 Char_Literal_Value => Pos);
8875 -- For all other cases, we have a complete table of literals, and
8876 -- we simply iterate through the chain of literal until the one
8877 -- with the desired position value is found.
8879 else
8880 if Is_Private_Type (Btyp) and then Present (Full_View (Btyp)) then
8881 Btyp := Full_View (Btyp);
8882 end if;
8884 Lit := First_Literal (Btyp);
8886 -- Position in the enumeration type starts at 0
8888 if UI_To_Int (Pos) < 0 then
8889 raise Constraint_Error;
8890 end if;
8892 for J in 1 .. UI_To_Int (Pos) loop
8893 Next_Literal (Lit);
8895 -- If Lit is Empty, Pos is not in range, so raise Constraint_Error
8896 -- inside the loop to avoid calling Next_Literal on Empty.
8898 if No (Lit) then
8899 raise Constraint_Error;
8900 end if;
8901 end loop;
8903 -- Create a new node from Lit, with source location provided by Loc
8904 -- if not equal to No_Location, or by copying the source location of
8905 -- Lit otherwise.
8907 LLoc := Loc;
8909 if LLoc = No_Location then
8910 LLoc := Sloc (Lit);
8911 end if;
8913 return New_Occurrence_Of (Lit, LLoc);
8914 end if;
8915 end Get_Enum_Lit_From_Pos;
8917 ------------------------
8918 -- Get_Generic_Entity --
8919 ------------------------
8921 function Get_Generic_Entity (N : Node_Id) return Entity_Id is
8922 Ent : constant Entity_Id := Entity (Name (N));
8923 begin
8924 if Present (Renamed_Object (Ent)) then
8925 return Renamed_Object (Ent);
8926 else
8927 return Ent;
8928 end if;
8929 end Get_Generic_Entity;
8931 -------------------------------------
8932 -- Get_Incomplete_View_Of_Ancestor --
8933 -------------------------------------
8935 function Get_Incomplete_View_Of_Ancestor (E : Entity_Id) return Entity_Id is
8936 Cur_Unit : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
8937 Par_Scope : Entity_Id;
8938 Par_Type : Entity_Id;
8940 begin
8941 -- The incomplete view of an ancestor is only relevant for private
8942 -- derived types in child units.
8944 if not Is_Derived_Type (E)
8945 or else not Is_Child_Unit (Cur_Unit)
8946 then
8947 return Empty;
8949 else
8950 Par_Scope := Scope (Cur_Unit);
8951 if No (Par_Scope) then
8952 return Empty;
8953 end if;
8955 Par_Type := Etype (Base_Type (E));
8957 -- Traverse list of ancestor types until we find one declared in
8958 -- a parent or grandparent unit (two levels seem sufficient).
8960 while Present (Par_Type) loop
8961 if Scope (Par_Type) = Par_Scope
8962 or else Scope (Par_Type) = Scope (Par_Scope)
8963 then
8964 return Par_Type;
8966 elsif not Is_Derived_Type (Par_Type) then
8967 return Empty;
8969 else
8970 Par_Type := Etype (Base_Type (Par_Type));
8971 end if;
8972 end loop;
8974 -- If none found, there is no relevant ancestor type.
8976 return Empty;
8977 end if;
8978 end Get_Incomplete_View_Of_Ancestor;
8980 ----------------------
8981 -- Get_Index_Bounds --
8982 ----------------------
8984 procedure Get_Index_Bounds
8985 (N : Node_Id;
8986 L : out Node_Id;
8987 H : out Node_Id;
8988 Use_Full_View : Boolean := False)
8990 function Scalar_Range_Of_Type (Typ : Entity_Id) return Node_Id;
8991 -- Obtain the scalar range of type Typ. If flag Use_Full_View is set and
8992 -- Typ qualifies, the scalar range is obtained from the full view of the
8993 -- type.
8995 --------------------------
8996 -- Scalar_Range_Of_Type --
8997 --------------------------
8999 function Scalar_Range_Of_Type (Typ : Entity_Id) return Node_Id is
9000 T : Entity_Id := Typ;
9002 begin
9003 if Use_Full_View and then Present (Full_View (T)) then
9004 T := Full_View (T);
9005 end if;
9007 return Scalar_Range (T);
9008 end Scalar_Range_Of_Type;
9010 -- Local variables
9012 Kind : constant Node_Kind := Nkind (N);
9013 Rng : Node_Id;
9015 -- Start of processing for Get_Index_Bounds
9017 begin
9018 if Kind = N_Range then
9019 L := Low_Bound (N);
9020 H := High_Bound (N);
9022 elsif Kind = N_Subtype_Indication then
9023 Rng := Range_Expression (Constraint (N));
9025 if Rng = Error then
9026 L := Error;
9027 H := Error;
9028 return;
9030 else
9031 L := Low_Bound (Range_Expression (Constraint (N)));
9032 H := High_Bound (Range_Expression (Constraint (N)));
9033 end if;
9035 elsif Is_Entity_Name (N) and then Is_Type (Entity (N)) then
9036 Rng := Scalar_Range_Of_Type (Entity (N));
9038 if Error_Posted (Rng) then
9039 L := Error;
9040 H := Error;
9042 elsif Nkind (Rng) = N_Subtype_Indication then
9043 Get_Index_Bounds (Rng, L, H);
9045 else
9046 L := Low_Bound (Rng);
9047 H := High_Bound (Rng);
9048 end if;
9050 else
9051 -- N is an expression, indicating a range with one value
9053 L := N;
9054 H := N;
9055 end if;
9056 end Get_Index_Bounds;
9058 -----------------------------
9059 -- Get_Interfacing_Aspects --
9060 -----------------------------
9062 procedure Get_Interfacing_Aspects
9063 (Iface_Asp : Node_Id;
9064 Conv_Asp : out Node_Id;
9065 EN_Asp : out Node_Id;
9066 Expo_Asp : out Node_Id;
9067 Imp_Asp : out Node_Id;
9068 LN_Asp : out Node_Id;
9069 Do_Checks : Boolean := False)
9071 procedure Save_Or_Duplication_Error
9072 (Asp : Node_Id;
9073 To : in out Node_Id);
9074 -- Save the value of aspect Asp in node To. If To already has a value,
9075 -- then this is considered a duplicate use of aspect. Emit an error if
9076 -- flag Do_Checks is set.
9078 -------------------------------
9079 -- Save_Or_Duplication_Error --
9080 -------------------------------
9082 procedure Save_Or_Duplication_Error
9083 (Asp : Node_Id;
9084 To : in out Node_Id)
9086 begin
9087 -- Detect an extra aspect and issue an error
9089 if Present (To) then
9090 if Do_Checks then
9091 Error_Msg_Name_1 := Chars (Identifier (Asp));
9092 Error_Msg_Sloc := Sloc (To);
9093 Error_Msg_N ("aspect % previously given #", Asp);
9094 end if;
9096 -- Otherwise capture the aspect
9098 else
9099 To := Asp;
9100 end if;
9101 end Save_Or_Duplication_Error;
9103 -- Local variables
9105 Asp : Node_Id;
9106 Asp_Id : Aspect_Id;
9108 -- The following variables capture each individual aspect
9110 Conv : Node_Id := Empty;
9111 EN : Node_Id := Empty;
9112 Expo : Node_Id := Empty;
9113 Imp : Node_Id := Empty;
9114 LN : Node_Id := Empty;
9116 -- Start of processing for Get_Interfacing_Aspects
9118 begin
9119 -- The input interfacing aspect should reside in an aspect specification
9120 -- list.
9122 pragma Assert (Is_List_Member (Iface_Asp));
9124 -- Examine the aspect specifications of the related entity. Find and
9125 -- capture all interfacing aspects. Detect duplicates and emit errors
9126 -- if applicable.
9128 Asp := First (List_Containing (Iface_Asp));
9129 while Present (Asp) loop
9130 Asp_Id := Get_Aspect_Id (Asp);
9132 if Asp_Id = Aspect_Convention then
9133 Save_Or_Duplication_Error (Asp, Conv);
9135 elsif Asp_Id = Aspect_External_Name then
9136 Save_Or_Duplication_Error (Asp, EN);
9138 elsif Asp_Id = Aspect_Export then
9139 Save_Or_Duplication_Error (Asp, Expo);
9141 elsif Asp_Id = Aspect_Import then
9142 Save_Or_Duplication_Error (Asp, Imp);
9144 elsif Asp_Id = Aspect_Link_Name then
9145 Save_Or_Duplication_Error (Asp, LN);
9146 end if;
9148 Next (Asp);
9149 end loop;
9151 Conv_Asp := Conv;
9152 EN_Asp := EN;
9153 Expo_Asp := Expo;
9154 Imp_Asp := Imp;
9155 LN_Asp := LN;
9156 end Get_Interfacing_Aspects;
9158 ---------------------------------
9159 -- Get_Iterable_Type_Primitive --
9160 ---------------------------------
9162 function Get_Iterable_Type_Primitive
9163 (Typ : Entity_Id;
9164 Nam : Name_Id) return Entity_Id
9166 Funcs : constant Node_Id := Find_Value_Of_Aspect (Typ, Aspect_Iterable);
9167 Assoc : Node_Id;
9169 begin
9170 if No (Funcs) then
9171 return Empty;
9173 else
9174 Assoc := First (Component_Associations (Funcs));
9175 while Present (Assoc) loop
9176 if Chars (First (Choices (Assoc))) = Nam then
9177 return Entity (Expression (Assoc));
9178 end if;
9180 Assoc := Next (Assoc);
9181 end loop;
9183 return Empty;
9184 end if;
9185 end Get_Iterable_Type_Primitive;
9187 ----------------------------------
9188 -- Get_Library_Unit_Name_string --
9189 ----------------------------------
9191 procedure Get_Library_Unit_Name_String (Decl_Node : Node_Id) is
9192 Unit_Name_Id : constant Unit_Name_Type := Get_Unit_Name (Decl_Node);
9194 begin
9195 Get_Unit_Name_String (Unit_Name_Id);
9197 -- Remove seven last character (" (spec)" or " (body)")
9199 Name_Len := Name_Len - 7;
9200 pragma Assert (Name_Buffer (Name_Len + 1) = ' ');
9201 end Get_Library_Unit_Name_String;
9203 --------------------------
9204 -- Get_Max_Queue_Length --
9205 --------------------------
9207 function Get_Max_Queue_Length (Id : Entity_Id) return Uint is
9208 pragma Assert (Is_Entry (Id));
9209 Prag : constant Entity_Id := Get_Pragma (Id, Pragma_Max_Queue_Length);
9211 begin
9212 -- A value of 0 represents no maximum specified, and entries and entry
9213 -- families with no Max_Queue_Length aspect or pragma default to it.
9215 if not Present (Prag) then
9216 return Uint_0;
9217 end if;
9219 return Intval (Expression (First (Pragma_Argument_Associations (Prag))));
9220 end Get_Max_Queue_Length;
9222 ------------------------
9223 -- Get_Name_Entity_Id --
9224 ------------------------
9226 function Get_Name_Entity_Id (Id : Name_Id) return Entity_Id is
9227 begin
9228 return Entity_Id (Get_Name_Table_Int (Id));
9229 end Get_Name_Entity_Id;
9231 ------------------------------
9232 -- Get_Name_From_CTC_Pragma --
9233 ------------------------------
9235 function Get_Name_From_CTC_Pragma (N : Node_Id) return String_Id is
9236 Arg : constant Node_Id :=
9237 Get_Pragma_Arg (First (Pragma_Argument_Associations (N)));
9238 begin
9239 return Strval (Expr_Value_S (Arg));
9240 end Get_Name_From_CTC_Pragma;
9242 -----------------------
9243 -- Get_Parent_Entity --
9244 -----------------------
9246 function Get_Parent_Entity (Unit : Node_Id) return Entity_Id is
9247 begin
9248 if Nkind (Unit) = N_Package_Body
9249 and then Nkind (Original_Node (Unit)) = N_Package_Instantiation
9250 then
9251 return Defining_Entity
9252 (Specification (Instance_Spec (Original_Node (Unit))));
9253 elsif Nkind (Unit) = N_Package_Instantiation then
9254 return Defining_Entity (Specification (Instance_Spec (Unit)));
9255 else
9256 return Defining_Entity (Unit);
9257 end if;
9258 end Get_Parent_Entity;
9260 -------------------
9261 -- Get_Pragma_Id --
9262 -------------------
9264 function Get_Pragma_Id (N : Node_Id) return Pragma_Id is
9265 begin
9266 return Get_Pragma_Id (Pragma_Name_Unmapped (N));
9267 end Get_Pragma_Id;
9269 ------------------------
9270 -- Get_Qualified_Name --
9271 ------------------------
9273 function Get_Qualified_Name
9274 (Id : Entity_Id;
9275 Suffix : Entity_Id := Empty) return Name_Id
9277 Suffix_Nam : Name_Id := No_Name;
9279 begin
9280 if Present (Suffix) then
9281 Suffix_Nam := Chars (Suffix);
9282 end if;
9284 return Get_Qualified_Name (Chars (Id), Suffix_Nam, Scope (Id));
9285 end Get_Qualified_Name;
9287 function Get_Qualified_Name
9288 (Nam : Name_Id;
9289 Suffix : Name_Id := No_Name;
9290 Scop : Entity_Id := Current_Scope) return Name_Id
9292 procedure Add_Scope (S : Entity_Id);
9293 -- Add the fully qualified form of scope S to the name buffer. The
9294 -- format is:
9295 -- s-1__s__
9297 ---------------
9298 -- Add_Scope --
9299 ---------------
9301 procedure Add_Scope (S : Entity_Id) is
9302 begin
9303 if S = Empty then
9304 null;
9306 elsif S = Standard_Standard then
9307 null;
9309 else
9310 Add_Scope (Scope (S));
9311 Get_Name_String_And_Append (Chars (S));
9312 Add_Str_To_Name_Buffer ("__");
9313 end if;
9314 end Add_Scope;
9316 -- Start of processing for Get_Qualified_Name
9318 begin
9319 Name_Len := 0;
9320 Add_Scope (Scop);
9322 -- Append the base name after all scopes have been chained
9324 Get_Name_String_And_Append (Nam);
9326 -- Append the suffix (if present)
9328 if Suffix /= No_Name then
9329 Add_Str_To_Name_Buffer ("__");
9330 Get_Name_String_And_Append (Suffix);
9331 end if;
9333 return Name_Find;
9334 end Get_Qualified_Name;
9336 -----------------------
9337 -- Get_Reason_String --
9338 -----------------------
9340 procedure Get_Reason_String (N : Node_Id) is
9341 begin
9342 if Nkind (N) = N_String_Literal then
9343 Store_String_Chars (Strval (N));
9345 elsif Nkind (N) = N_Op_Concat then
9346 Get_Reason_String (Left_Opnd (N));
9347 Get_Reason_String (Right_Opnd (N));
9349 -- If not of required form, error
9351 else
9352 Error_Msg_N
9353 ("Reason for pragma Warnings has wrong form", N);
9354 Error_Msg_N
9355 ("\must be string literal or concatenation of string literals", N);
9356 return;
9357 end if;
9358 end Get_Reason_String;
9360 --------------------------------
9361 -- Get_Reference_Discriminant --
9362 --------------------------------
9364 function Get_Reference_Discriminant (Typ : Entity_Id) return Entity_Id is
9365 D : Entity_Id;
9367 begin
9368 D := First_Discriminant (Typ);
9369 while Present (D) loop
9370 if Has_Implicit_Dereference (D) then
9371 return D;
9372 end if;
9373 Next_Discriminant (D);
9374 end loop;
9376 return Empty;
9377 end Get_Reference_Discriminant;
9379 ---------------------------
9380 -- Get_Referenced_Object --
9381 ---------------------------
9383 function Get_Referenced_Object (N : Node_Id) return Node_Id is
9384 R : Node_Id;
9386 begin
9387 R := N;
9388 while Is_Entity_Name (R)
9389 and then Present (Renamed_Object (Entity (R)))
9390 loop
9391 R := Renamed_Object (Entity (R));
9392 end loop;
9394 return R;
9395 end Get_Referenced_Object;
9397 ------------------------
9398 -- Get_Renamed_Entity --
9399 ------------------------
9401 function Get_Renamed_Entity (E : Entity_Id) return Entity_Id is
9402 R : Entity_Id;
9404 begin
9405 R := E;
9406 while Present (Renamed_Entity (R)) loop
9407 R := Renamed_Entity (R);
9408 end loop;
9410 return R;
9411 end Get_Renamed_Entity;
9413 -----------------------
9414 -- Get_Return_Object --
9415 -----------------------
9417 function Get_Return_Object (N : Node_Id) return Entity_Id is
9418 Decl : Node_Id;
9420 begin
9421 Decl := First (Return_Object_Declarations (N));
9422 while Present (Decl) loop
9423 exit when Nkind (Decl) = N_Object_Declaration
9424 and then Is_Return_Object (Defining_Identifier (Decl));
9425 Next (Decl);
9426 end loop;
9428 pragma Assert (Present (Decl));
9429 return Defining_Identifier (Decl);
9430 end Get_Return_Object;
9432 ---------------------------
9433 -- Get_Subprogram_Entity --
9434 ---------------------------
9436 function Get_Subprogram_Entity (Nod : Node_Id) return Entity_Id is
9437 Subp : Node_Id;
9438 Subp_Id : Entity_Id;
9440 begin
9441 if Nkind (Nod) = N_Accept_Statement then
9442 Subp := Entry_Direct_Name (Nod);
9444 elsif Nkind (Nod) = N_Slice then
9445 Subp := Prefix (Nod);
9447 else
9448 Subp := Name (Nod);
9449 end if;
9451 -- Strip the subprogram call
9453 loop
9454 if Nkind_In (Subp, N_Explicit_Dereference,
9455 N_Indexed_Component,
9456 N_Selected_Component)
9457 then
9458 Subp := Prefix (Subp);
9460 elsif Nkind_In (Subp, N_Type_Conversion,
9461 N_Unchecked_Type_Conversion)
9462 then
9463 Subp := Expression (Subp);
9465 else
9466 exit;
9467 end if;
9468 end loop;
9470 -- Extract the entity of the subprogram call
9472 if Is_Entity_Name (Subp) then
9473 Subp_Id := Entity (Subp);
9475 if Ekind (Subp_Id) = E_Access_Subprogram_Type then
9476 Subp_Id := Directly_Designated_Type (Subp_Id);
9477 end if;
9479 if Is_Subprogram (Subp_Id) then
9480 return Subp_Id;
9481 else
9482 return Empty;
9483 end if;
9485 -- The search did not find a construct that denotes a subprogram
9487 else
9488 return Empty;
9489 end if;
9490 end Get_Subprogram_Entity;
9492 -----------------------------
9493 -- Get_Task_Body_Procedure --
9494 -----------------------------
9496 function Get_Task_Body_Procedure (E : Entity_Id) return Entity_Id is
9497 begin
9498 -- Note: A task type may be the completion of a private type with
9499 -- discriminants. When performing elaboration checks on a task
9500 -- declaration, the current view of the type may be the private one,
9501 -- and the procedure that holds the body of the task is held in its
9502 -- underlying type.
9504 -- This is an odd function, why not have Task_Body_Procedure do
9505 -- the following digging???
9507 return Task_Body_Procedure (Underlying_Type (Root_Type (E)));
9508 end Get_Task_Body_Procedure;
9510 -------------------------
9511 -- Get_User_Defined_Eq --
9512 -------------------------
9514 function Get_User_Defined_Eq (E : Entity_Id) return Entity_Id is
9515 Prim : Elmt_Id;
9516 Op : Entity_Id;
9518 begin
9519 Prim := First_Elmt (Collect_Primitive_Operations (E));
9520 while Present (Prim) loop
9521 Op := Node (Prim);
9523 if Chars (Op) = Name_Op_Eq
9524 and then Etype (Op) = Standard_Boolean
9525 and then Etype (First_Formal (Op)) = E
9526 and then Etype (Next_Formal (First_Formal (Op))) = E
9527 then
9528 return Op;
9529 end if;
9531 Next_Elmt (Prim);
9532 end loop;
9534 return Empty;
9535 end Get_User_Defined_Eq;
9537 ---------------
9538 -- Get_Views --
9539 ---------------
9541 procedure Get_Views
9542 (Typ : Entity_Id;
9543 Priv_Typ : out Entity_Id;
9544 Full_Typ : out Entity_Id;
9545 Full_Base : out Entity_Id;
9546 CRec_Typ : out Entity_Id)
9548 IP_View : Entity_Id;
9550 begin
9551 -- Assume that none of the views can be recovered
9553 Priv_Typ := Empty;
9554 Full_Typ := Empty;
9555 Full_Base := Empty;
9556 CRec_Typ := Empty;
9558 -- The input type is the corresponding record type of a protected or a
9559 -- task type.
9561 if Ekind (Typ) = E_Record_Type
9562 and then Is_Concurrent_Record_Type (Typ)
9563 then
9564 CRec_Typ := Typ;
9565 Full_Typ := Corresponding_Concurrent_Type (CRec_Typ);
9566 Full_Base := Base_Type (Full_Typ);
9567 Priv_Typ := Incomplete_Or_Partial_View (Full_Typ);
9569 -- Otherwise the input type denotes an arbitrary type
9571 else
9572 IP_View := Incomplete_Or_Partial_View (Typ);
9574 -- The input type denotes the full view of a private type
9576 if Present (IP_View) then
9577 Priv_Typ := IP_View;
9578 Full_Typ := Typ;
9580 -- The input type is a private type
9582 elsif Is_Private_Type (Typ) then
9583 Priv_Typ := Typ;
9584 Full_Typ := Full_View (Priv_Typ);
9586 -- Otherwise the input type does not have any views
9588 else
9589 Full_Typ := Typ;
9590 end if;
9592 if Present (Full_Typ) then
9593 Full_Base := Base_Type (Full_Typ);
9595 if Ekind_In (Full_Typ, E_Protected_Type, E_Task_Type) then
9596 CRec_Typ := Corresponding_Record_Type (Full_Typ);
9597 end if;
9598 end if;
9599 end if;
9600 end Get_Views;
9602 -----------------------
9603 -- Has_Access_Values --
9604 -----------------------
9606 function Has_Access_Values (T : Entity_Id) return Boolean is
9607 Typ : constant Entity_Id := Underlying_Type (T);
9609 begin
9610 -- Case of a private type which is not completed yet. This can only
9611 -- happen in the case of a generic format type appearing directly, or
9612 -- as a component of the type to which this function is being applied
9613 -- at the top level. Return False in this case, since we certainly do
9614 -- not know that the type contains access types.
9616 if No (Typ) then
9617 return False;
9619 elsif Is_Access_Type (Typ) then
9620 return True;
9622 elsif Is_Array_Type (Typ) then
9623 return Has_Access_Values (Component_Type (Typ));
9625 elsif Is_Record_Type (Typ) then
9626 declare
9627 Comp : Entity_Id;
9629 begin
9630 -- Loop to Check components
9632 Comp := First_Component_Or_Discriminant (Typ);
9633 while Present (Comp) loop
9635 -- Check for access component, tag field does not count, even
9636 -- though it is implemented internally using an access type.
9638 if Has_Access_Values (Etype (Comp))
9639 and then Chars (Comp) /= Name_uTag
9640 then
9641 return True;
9642 end if;
9644 Next_Component_Or_Discriminant (Comp);
9645 end loop;
9646 end;
9648 return False;
9650 else
9651 return False;
9652 end if;
9653 end Has_Access_Values;
9655 ------------------------------
9656 -- Has_Compatible_Alignment --
9657 ------------------------------
9659 function Has_Compatible_Alignment
9660 (Obj : Entity_Id;
9661 Expr : Node_Id;
9662 Layout_Done : Boolean) return Alignment_Result
9664 function Has_Compatible_Alignment_Internal
9665 (Obj : Entity_Id;
9666 Expr : Node_Id;
9667 Layout_Done : Boolean;
9668 Default : Alignment_Result) return Alignment_Result;
9669 -- This is the internal recursive function that actually does the work.
9670 -- There is one additional parameter, which says what the result should
9671 -- be if no alignment information is found, and there is no definite
9672 -- indication of compatible alignments. At the outer level, this is set
9673 -- to Unknown, but for internal recursive calls in the case where types
9674 -- are known to be correct, it is set to Known_Compatible.
9676 ---------------------------------------
9677 -- Has_Compatible_Alignment_Internal --
9678 ---------------------------------------
9680 function Has_Compatible_Alignment_Internal
9681 (Obj : Entity_Id;
9682 Expr : Node_Id;
9683 Layout_Done : Boolean;
9684 Default : Alignment_Result) return Alignment_Result
9686 Result : Alignment_Result := Known_Compatible;
9687 -- Holds the current status of the result. Note that once a value of
9688 -- Known_Incompatible is set, it is sticky and does not get changed
9689 -- to Unknown (the value in Result only gets worse as we go along,
9690 -- never better).
9692 Offs : Uint := No_Uint;
9693 -- Set to a factor of the offset from the base object when Expr is a
9694 -- selected or indexed component, based on Component_Bit_Offset and
9695 -- Component_Size respectively. A negative value is used to represent
9696 -- a value which is not known at compile time.
9698 procedure Check_Prefix;
9699 -- Checks the prefix recursively in the case where the expression
9700 -- is an indexed or selected component.
9702 procedure Set_Result (R : Alignment_Result);
9703 -- If R represents a worse outcome (unknown instead of known
9704 -- compatible, or known incompatible), then set Result to R.
9706 ------------------
9707 -- Check_Prefix --
9708 ------------------
9710 procedure Check_Prefix is
9711 begin
9712 -- The subtlety here is that in doing a recursive call to check
9713 -- the prefix, we have to decide what to do in the case where we
9714 -- don't find any specific indication of an alignment problem.
9716 -- At the outer level, we normally set Unknown as the result in
9717 -- this case, since we can only set Known_Compatible if we really
9718 -- know that the alignment value is OK, but for the recursive
9719 -- call, in the case where the types match, and we have not
9720 -- specified a peculiar alignment for the object, we are only
9721 -- concerned about suspicious rep clauses, the default case does
9722 -- not affect us, since the compiler will, in the absence of such
9723 -- rep clauses, ensure that the alignment is correct.
9725 if Default = Known_Compatible
9726 or else
9727 (Etype (Obj) = Etype (Expr)
9728 and then (Unknown_Alignment (Obj)
9729 or else
9730 Alignment (Obj) = Alignment (Etype (Obj))))
9731 then
9732 Set_Result
9733 (Has_Compatible_Alignment_Internal
9734 (Obj, Prefix (Expr), Layout_Done, Known_Compatible));
9736 -- In all other cases, we need a full check on the prefix
9738 else
9739 Set_Result
9740 (Has_Compatible_Alignment_Internal
9741 (Obj, Prefix (Expr), Layout_Done, Unknown));
9742 end if;
9743 end Check_Prefix;
9745 ----------------
9746 -- Set_Result --
9747 ----------------
9749 procedure Set_Result (R : Alignment_Result) is
9750 begin
9751 if R > Result then
9752 Result := R;
9753 end if;
9754 end Set_Result;
9756 -- Start of processing for Has_Compatible_Alignment_Internal
9758 begin
9759 -- If Expr is a selected component, we must make sure there is no
9760 -- potentially troublesome component clause and that the record is
9761 -- not packed if the layout is not done.
9763 if Nkind (Expr) = N_Selected_Component then
9765 -- Packing generates unknown alignment if layout is not done
9767 if Is_Packed (Etype (Prefix (Expr))) and then not Layout_Done then
9768 Set_Result (Unknown);
9769 end if;
9771 -- Check prefix and component offset
9773 Check_Prefix;
9774 Offs := Component_Bit_Offset (Entity (Selector_Name (Expr)));
9776 -- If Expr is an indexed component, we must make sure there is no
9777 -- potentially troublesome Component_Size clause and that the array
9778 -- is not bit-packed if the layout is not done.
9780 elsif Nkind (Expr) = N_Indexed_Component then
9781 declare
9782 Typ : constant Entity_Id := Etype (Prefix (Expr));
9784 begin
9785 -- Packing generates unknown alignment if layout is not done
9787 if Is_Bit_Packed_Array (Typ) and then not Layout_Done then
9788 Set_Result (Unknown);
9789 end if;
9791 -- Check prefix and component offset (or at least size)
9793 Check_Prefix;
9794 Offs := Indexed_Component_Bit_Offset (Expr);
9795 if Offs = No_Uint then
9796 Offs := Component_Size (Typ);
9797 end if;
9798 end;
9799 end if;
9801 -- If we have a null offset, the result is entirely determined by
9802 -- the base object and has already been computed recursively.
9804 if Offs = Uint_0 then
9805 null;
9807 -- Case where we know the alignment of the object
9809 elsif Known_Alignment (Obj) then
9810 declare
9811 ObjA : constant Uint := Alignment (Obj);
9812 ExpA : Uint := No_Uint;
9813 SizA : Uint := No_Uint;
9815 begin
9816 -- If alignment of Obj is 1, then we are always OK
9818 if ObjA = 1 then
9819 Set_Result (Known_Compatible);
9821 -- Alignment of Obj is greater than 1, so we need to check
9823 else
9824 -- If we have an offset, see if it is compatible
9826 if Offs /= No_Uint and Offs > Uint_0 then
9827 if Offs mod (System_Storage_Unit * ObjA) /= 0 then
9828 Set_Result (Known_Incompatible);
9829 end if;
9831 -- See if Expr is an object with known alignment
9833 elsif Is_Entity_Name (Expr)
9834 and then Known_Alignment (Entity (Expr))
9835 then
9836 ExpA := Alignment (Entity (Expr));
9838 -- Otherwise, we can use the alignment of the type of
9839 -- Expr given that we already checked for
9840 -- discombobulating rep clauses for the cases of indexed
9841 -- and selected components above.
9843 elsif Known_Alignment (Etype (Expr)) then
9844 ExpA := Alignment (Etype (Expr));
9846 -- Otherwise the alignment is unknown
9848 else
9849 Set_Result (Default);
9850 end if;
9852 -- If we got an alignment, see if it is acceptable
9854 if ExpA /= No_Uint and then ExpA < ObjA then
9855 Set_Result (Known_Incompatible);
9856 end if;
9858 -- If Expr is not a piece of a larger object, see if size
9859 -- is given. If so, check that it is not too small for the
9860 -- required alignment.
9862 if Offs /= No_Uint then
9863 null;
9865 -- See if Expr is an object with known size
9867 elsif Is_Entity_Name (Expr)
9868 and then Known_Static_Esize (Entity (Expr))
9869 then
9870 SizA := Esize (Entity (Expr));
9872 -- Otherwise, we check the object size of the Expr type
9874 elsif Known_Static_Esize (Etype (Expr)) then
9875 SizA := Esize (Etype (Expr));
9876 end if;
9878 -- If we got a size, see if it is a multiple of the Obj
9879 -- alignment, if not, then the alignment cannot be
9880 -- acceptable, since the size is always a multiple of the
9881 -- alignment.
9883 if SizA /= No_Uint then
9884 if SizA mod (ObjA * Ttypes.System_Storage_Unit) /= 0 then
9885 Set_Result (Known_Incompatible);
9886 end if;
9887 end if;
9888 end if;
9889 end;
9891 -- If we do not know required alignment, any non-zero offset is a
9892 -- potential problem (but certainly may be OK, so result is unknown).
9894 elsif Offs /= No_Uint then
9895 Set_Result (Unknown);
9897 -- If we can't find the result by direct comparison of alignment
9898 -- values, then there is still one case that we can determine known
9899 -- result, and that is when we can determine that the types are the
9900 -- same, and no alignments are specified. Then we known that the
9901 -- alignments are compatible, even if we don't know the alignment
9902 -- value in the front end.
9904 elsif Etype (Obj) = Etype (Expr) then
9906 -- Types are the same, but we have to check for possible size
9907 -- and alignments on the Expr object that may make the alignment
9908 -- different, even though the types are the same.
9910 if Is_Entity_Name (Expr) then
9912 -- First check alignment of the Expr object. Any alignment less
9913 -- than Maximum_Alignment is worrisome since this is the case
9914 -- where we do not know the alignment of Obj.
9916 if Known_Alignment (Entity (Expr))
9917 and then UI_To_Int (Alignment (Entity (Expr))) <
9918 Ttypes.Maximum_Alignment
9919 then
9920 Set_Result (Unknown);
9922 -- Now check size of Expr object. Any size that is not an
9923 -- even multiple of Maximum_Alignment is also worrisome
9924 -- since it may cause the alignment of the object to be less
9925 -- than the alignment of the type.
9927 elsif Known_Static_Esize (Entity (Expr))
9928 and then
9929 (UI_To_Int (Esize (Entity (Expr))) mod
9930 (Ttypes.Maximum_Alignment * Ttypes.System_Storage_Unit))
9931 /= 0
9932 then
9933 Set_Result (Unknown);
9935 -- Otherwise same type is decisive
9937 else
9938 Set_Result (Known_Compatible);
9939 end if;
9940 end if;
9942 -- Another case to deal with is when there is an explicit size or
9943 -- alignment clause when the types are not the same. If so, then the
9944 -- result is Unknown. We don't need to do this test if the Default is
9945 -- Unknown, since that result will be set in any case.
9947 elsif Default /= Unknown
9948 and then (Has_Size_Clause (Etype (Expr))
9949 or else
9950 Has_Alignment_Clause (Etype (Expr)))
9951 then
9952 Set_Result (Unknown);
9954 -- If no indication found, set default
9956 else
9957 Set_Result (Default);
9958 end if;
9960 -- Return worst result found
9962 return Result;
9963 end Has_Compatible_Alignment_Internal;
9965 -- Start of processing for Has_Compatible_Alignment
9967 begin
9968 -- If Obj has no specified alignment, then set alignment from the type
9969 -- alignment. Perhaps we should always do this, but for sure we should
9970 -- do it when there is an address clause since we can do more if the
9971 -- alignment is known.
9973 if Unknown_Alignment (Obj) then
9974 Set_Alignment (Obj, Alignment (Etype (Obj)));
9975 end if;
9977 -- Now do the internal call that does all the work
9979 return
9980 Has_Compatible_Alignment_Internal (Obj, Expr, Layout_Done, Unknown);
9981 end Has_Compatible_Alignment;
9983 ----------------------
9984 -- Has_Declarations --
9985 ----------------------
9987 function Has_Declarations (N : Node_Id) return Boolean is
9988 begin
9989 return Nkind_In (Nkind (N), N_Accept_Statement,
9990 N_Block_Statement,
9991 N_Compilation_Unit_Aux,
9992 N_Entry_Body,
9993 N_Package_Body,
9994 N_Protected_Body,
9995 N_Subprogram_Body,
9996 N_Task_Body,
9997 N_Package_Specification);
9998 end Has_Declarations;
10000 ---------------------------------
10001 -- Has_Defaulted_Discriminants --
10002 ---------------------------------
10004 function Has_Defaulted_Discriminants (Typ : Entity_Id) return Boolean is
10005 begin
10006 return Has_Discriminants (Typ)
10007 and then Present (First_Discriminant (Typ))
10008 and then Present (Discriminant_Default_Value
10009 (First_Discriminant (Typ)));
10010 end Has_Defaulted_Discriminants;
10012 -------------------
10013 -- Has_Denormals --
10014 -------------------
10016 function Has_Denormals (E : Entity_Id) return Boolean is
10017 begin
10018 return Is_Floating_Point_Type (E) and then Denorm_On_Target;
10019 end Has_Denormals;
10021 -------------------------------------------
10022 -- Has_Discriminant_Dependent_Constraint --
10023 -------------------------------------------
10025 function Has_Discriminant_Dependent_Constraint
10026 (Comp : Entity_Id) return Boolean
10028 Comp_Decl : constant Node_Id := Parent (Comp);
10029 Subt_Indic : Node_Id;
10030 Constr : Node_Id;
10031 Assn : Node_Id;
10033 begin
10034 -- Discriminants can't depend on discriminants
10036 if Ekind (Comp) = E_Discriminant then
10037 return False;
10039 else
10040 Subt_Indic := Subtype_Indication (Component_Definition (Comp_Decl));
10042 if Nkind (Subt_Indic) = N_Subtype_Indication then
10043 Constr := Constraint (Subt_Indic);
10045 if Nkind (Constr) = N_Index_Or_Discriminant_Constraint then
10046 Assn := First (Constraints (Constr));
10047 while Present (Assn) loop
10048 case Nkind (Assn) is
10049 when N_Identifier
10050 | N_Range
10051 | N_Subtype_Indication
10053 if Depends_On_Discriminant (Assn) then
10054 return True;
10055 end if;
10057 when N_Discriminant_Association =>
10058 if Depends_On_Discriminant (Expression (Assn)) then
10059 return True;
10060 end if;
10062 when others =>
10063 null;
10064 end case;
10066 Next (Assn);
10067 end loop;
10068 end if;
10069 end if;
10070 end if;
10072 return False;
10073 end Has_Discriminant_Dependent_Constraint;
10075 --------------------------------------
10076 -- Has_Effectively_Volatile_Profile --
10077 --------------------------------------
10079 function Has_Effectively_Volatile_Profile
10080 (Subp_Id : Entity_Id) return Boolean
10082 Formal : Entity_Id;
10084 begin
10085 -- Inspect the formal parameters looking for an effectively volatile
10086 -- type.
10088 Formal := First_Formal (Subp_Id);
10089 while Present (Formal) loop
10090 if Is_Effectively_Volatile (Etype (Formal)) then
10091 return True;
10092 end if;
10094 Next_Formal (Formal);
10095 end loop;
10097 -- Inspect the return type of functions
10099 if Ekind_In (Subp_Id, E_Function, E_Generic_Function)
10100 and then Is_Effectively_Volatile (Etype (Subp_Id))
10101 then
10102 return True;
10103 end if;
10105 return False;
10106 end Has_Effectively_Volatile_Profile;
10108 --------------------------
10109 -- Has_Enabled_Property --
10110 --------------------------
10112 function Has_Enabled_Property
10113 (Item_Id : Entity_Id;
10114 Property : Name_Id) return Boolean
10116 function Protected_Object_Has_Enabled_Property return Boolean;
10117 -- Determine whether a protected object denoted by Item_Id has the
10118 -- property enabled.
10120 function State_Has_Enabled_Property return Boolean;
10121 -- Determine whether a state denoted by Item_Id has the property enabled
10123 function Variable_Has_Enabled_Property return Boolean;
10124 -- Determine whether a variable denoted by Item_Id has the property
10125 -- enabled.
10127 -------------------------------------------
10128 -- Protected_Object_Has_Enabled_Property --
10129 -------------------------------------------
10131 function Protected_Object_Has_Enabled_Property return Boolean is
10132 Constits : constant Elist_Id := Part_Of_Constituents (Item_Id);
10133 Constit_Elmt : Elmt_Id;
10134 Constit_Id : Entity_Id;
10136 begin
10137 -- Protected objects always have the properties Async_Readers and
10138 -- Async_Writers (SPARK RM 7.1.2(16)).
10140 if Property = Name_Async_Readers
10141 or else Property = Name_Async_Writers
10142 then
10143 return True;
10145 -- Protected objects that have Part_Of components also inherit their
10146 -- properties Effective_Reads and Effective_Writes
10147 -- (SPARK RM 7.1.2(16)).
10149 elsif Present (Constits) then
10150 Constit_Elmt := First_Elmt (Constits);
10151 while Present (Constit_Elmt) loop
10152 Constit_Id := Node (Constit_Elmt);
10154 if Has_Enabled_Property (Constit_Id, Property) then
10155 return True;
10156 end if;
10158 Next_Elmt (Constit_Elmt);
10159 end loop;
10160 end if;
10162 return False;
10163 end Protected_Object_Has_Enabled_Property;
10165 --------------------------------
10166 -- State_Has_Enabled_Property --
10167 --------------------------------
10169 function State_Has_Enabled_Property return Boolean is
10170 Decl : constant Node_Id := Parent (Item_Id);
10171 Opt : Node_Id;
10172 Opt_Nam : Node_Id;
10173 Prop : Node_Id;
10174 Prop_Nam : Node_Id;
10175 Props : Node_Id;
10177 begin
10178 -- The declaration of an external abstract state appears as an
10179 -- extension aggregate. If this is not the case, properties can never
10180 -- be set.
10182 if Nkind (Decl) /= N_Extension_Aggregate then
10183 return False;
10184 end if;
10186 -- When External appears as a simple option, it automatically enables
10187 -- all properties.
10189 Opt := First (Expressions (Decl));
10190 while Present (Opt) loop
10191 if Nkind (Opt) = N_Identifier
10192 and then Chars (Opt) = Name_External
10193 then
10194 return True;
10195 end if;
10197 Next (Opt);
10198 end loop;
10200 -- When External specifies particular properties, inspect those and
10201 -- find the desired one (if any).
10203 Opt := First (Component_Associations (Decl));
10204 while Present (Opt) loop
10205 Opt_Nam := First (Choices (Opt));
10207 if Nkind (Opt_Nam) = N_Identifier
10208 and then Chars (Opt_Nam) = Name_External
10209 then
10210 Props := Expression (Opt);
10212 -- Multiple properties appear as an aggregate
10214 if Nkind (Props) = N_Aggregate then
10216 -- Simple property form
10218 Prop := First (Expressions (Props));
10219 while Present (Prop) loop
10220 if Chars (Prop) = Property then
10221 return True;
10222 end if;
10224 Next (Prop);
10225 end loop;
10227 -- Property with expression form
10229 Prop := First (Component_Associations (Props));
10230 while Present (Prop) loop
10231 Prop_Nam := First (Choices (Prop));
10233 -- The property can be represented in two ways:
10234 -- others => <value>
10235 -- <property> => <value>
10237 if Nkind (Prop_Nam) = N_Others_Choice
10238 or else (Nkind (Prop_Nam) = N_Identifier
10239 and then Chars (Prop_Nam) = Property)
10240 then
10241 return Is_True (Expr_Value (Expression (Prop)));
10242 end if;
10244 Next (Prop);
10245 end loop;
10247 -- Single property
10249 else
10250 return Chars (Props) = Property;
10251 end if;
10252 end if;
10254 Next (Opt);
10255 end loop;
10257 return False;
10258 end State_Has_Enabled_Property;
10260 -----------------------------------
10261 -- Variable_Has_Enabled_Property --
10262 -----------------------------------
10264 function Variable_Has_Enabled_Property return Boolean is
10265 function Is_Enabled (Prag : Node_Id) return Boolean;
10266 -- Determine whether property pragma Prag (if present) denotes an
10267 -- enabled property.
10269 ----------------
10270 -- Is_Enabled --
10271 ----------------
10273 function Is_Enabled (Prag : Node_Id) return Boolean is
10274 Arg1 : Node_Id;
10276 begin
10277 if Present (Prag) then
10278 Arg1 := First (Pragma_Argument_Associations (Prag));
10280 -- The pragma has an optional Boolean expression, the related
10281 -- property is enabled only when the expression evaluates to
10282 -- True.
10284 if Present (Arg1) then
10285 return Is_True (Expr_Value (Get_Pragma_Arg (Arg1)));
10287 -- Otherwise the lack of expression enables the property by
10288 -- default.
10290 else
10291 return True;
10292 end if;
10294 -- The property was never set in the first place
10296 else
10297 return False;
10298 end if;
10299 end Is_Enabled;
10301 -- Local variables
10303 AR : constant Node_Id :=
10304 Get_Pragma (Item_Id, Pragma_Async_Readers);
10305 AW : constant Node_Id :=
10306 Get_Pragma (Item_Id, Pragma_Async_Writers);
10307 ER : constant Node_Id :=
10308 Get_Pragma (Item_Id, Pragma_Effective_Reads);
10309 EW : constant Node_Id :=
10310 Get_Pragma (Item_Id, Pragma_Effective_Writes);
10312 -- Start of processing for Variable_Has_Enabled_Property
10314 begin
10315 -- A non-effectively volatile object can never possess external
10316 -- properties.
10318 if not Is_Effectively_Volatile (Item_Id) then
10319 return False;
10321 -- External properties related to variables come in two flavors -
10322 -- explicit and implicit. The explicit case is characterized by the
10323 -- presence of a property pragma with an optional Boolean flag. The
10324 -- property is enabled when the flag evaluates to True or the flag is
10325 -- missing altogether.
10327 elsif Property = Name_Async_Readers and then Is_Enabled (AR) then
10328 return True;
10330 elsif Property = Name_Async_Writers and then Is_Enabled (AW) then
10331 return True;
10333 elsif Property = Name_Effective_Reads and then Is_Enabled (ER) then
10334 return True;
10336 elsif Property = Name_Effective_Writes and then Is_Enabled (EW) then
10337 return True;
10339 -- The implicit case lacks all property pragmas
10341 elsif No (AR) and then No (AW) and then No (ER) and then No (EW) then
10342 if Is_Protected_Type (Etype (Item_Id)) then
10343 return Protected_Object_Has_Enabled_Property;
10344 else
10345 return True;
10346 end if;
10348 else
10349 return False;
10350 end if;
10351 end Variable_Has_Enabled_Property;
10353 -- Start of processing for Has_Enabled_Property
10355 begin
10356 -- Abstract states and variables have a flexible scheme of specifying
10357 -- external properties.
10359 if Ekind (Item_Id) = E_Abstract_State then
10360 return State_Has_Enabled_Property;
10362 elsif Ekind (Item_Id) = E_Variable then
10363 return Variable_Has_Enabled_Property;
10365 -- By default, protected objects only have the properties Async_Readers
10366 -- and Async_Writers. If they have Part_Of components, they also inherit
10367 -- their properties Effective_Reads and Effective_Writes
10368 -- (SPARK RM 7.1.2(16)).
10370 elsif Ekind (Item_Id) = E_Protected_Object then
10371 return Protected_Object_Has_Enabled_Property;
10373 -- Otherwise a property is enabled when the related item is effectively
10374 -- volatile.
10376 else
10377 return Is_Effectively_Volatile (Item_Id);
10378 end if;
10379 end Has_Enabled_Property;
10381 -------------------------------------
10382 -- Has_Full_Default_Initialization --
10383 -------------------------------------
10385 function Has_Full_Default_Initialization (Typ : Entity_Id) return Boolean is
10386 Comp : Entity_Id;
10387 Prag : Node_Id;
10389 begin
10390 -- A type subject to pragma Default_Initial_Condition is fully default
10391 -- initialized when the pragma appears with a non-null argument. Since
10392 -- any type may act as the full view of a private type, this check must
10393 -- be performed prior to the specialized tests below.
10395 if Has_DIC (Typ) then
10396 Prag := Get_Pragma (Typ, Pragma_Default_Initial_Condition);
10397 pragma Assert (Present (Prag));
10399 return Is_Verifiable_DIC_Pragma (Prag);
10400 end if;
10402 -- A scalar type is fully default initialized if it is subject to aspect
10403 -- Default_Value.
10405 if Is_Scalar_Type (Typ) then
10406 return Has_Default_Aspect (Typ);
10408 -- An array type is fully default initialized if its element type is
10409 -- scalar and the array type carries aspect Default_Component_Value or
10410 -- the element type is fully default initialized.
10412 elsif Is_Array_Type (Typ) then
10413 return
10414 Has_Default_Aspect (Typ)
10415 or else Has_Full_Default_Initialization (Component_Type (Typ));
10417 -- A protected type, record type, or type extension is fully default
10418 -- initialized if all its components either carry an initialization
10419 -- expression or have a type that is fully default initialized. The
10420 -- parent type of a type extension must be fully default initialized.
10422 elsif Is_Record_Type (Typ) or else Is_Protected_Type (Typ) then
10424 -- Inspect all entities defined in the scope of the type, looking for
10425 -- uninitialized components.
10427 Comp := First_Entity (Typ);
10428 while Present (Comp) loop
10429 if Ekind (Comp) = E_Component
10430 and then Comes_From_Source (Comp)
10431 and then No (Expression (Parent (Comp)))
10432 and then not Has_Full_Default_Initialization (Etype (Comp))
10433 then
10434 return False;
10435 end if;
10437 Next_Entity (Comp);
10438 end loop;
10440 -- Ensure that the parent type of a type extension is fully default
10441 -- initialized.
10443 if Etype (Typ) /= Typ
10444 and then not Has_Full_Default_Initialization (Etype (Typ))
10445 then
10446 return False;
10447 end if;
10449 -- If we get here, then all components and parent portion are fully
10450 -- default initialized.
10452 return True;
10454 -- A task type is fully default initialized by default
10456 elsif Is_Task_Type (Typ) then
10457 return True;
10459 -- Otherwise the type is not fully default initialized
10461 else
10462 return False;
10463 end if;
10464 end Has_Full_Default_Initialization;
10466 --------------------
10467 -- Has_Infinities --
10468 --------------------
10470 function Has_Infinities (E : Entity_Id) return Boolean is
10471 begin
10472 return
10473 Is_Floating_Point_Type (E)
10474 and then Nkind (Scalar_Range (E)) = N_Range
10475 and then Includes_Infinities (Scalar_Range (E));
10476 end Has_Infinities;
10478 --------------------
10479 -- Has_Interfaces --
10480 --------------------
10482 function Has_Interfaces
10483 (T : Entity_Id;
10484 Use_Full_View : Boolean := True) return Boolean
10486 Typ : Entity_Id := Base_Type (T);
10488 begin
10489 -- Handle concurrent types
10491 if Is_Concurrent_Type (Typ) then
10492 Typ := Corresponding_Record_Type (Typ);
10493 end if;
10495 if not Present (Typ)
10496 or else not Is_Record_Type (Typ)
10497 or else not Is_Tagged_Type (Typ)
10498 then
10499 return False;
10500 end if;
10502 -- Handle private types
10504 if Use_Full_View and then Present (Full_View (Typ)) then
10505 Typ := Full_View (Typ);
10506 end if;
10508 -- Handle concurrent record types
10510 if Is_Concurrent_Record_Type (Typ)
10511 and then Is_Non_Empty_List (Abstract_Interface_List (Typ))
10512 then
10513 return True;
10514 end if;
10516 loop
10517 if Is_Interface (Typ)
10518 or else
10519 (Is_Record_Type (Typ)
10520 and then Present (Interfaces (Typ))
10521 and then not Is_Empty_Elmt_List (Interfaces (Typ)))
10522 then
10523 return True;
10524 end if;
10526 exit when Etype (Typ) = Typ
10528 -- Handle private types
10530 or else (Present (Full_View (Etype (Typ)))
10531 and then Full_View (Etype (Typ)) = Typ)
10533 -- Protect frontend against wrong sources with cyclic derivations
10535 or else Etype (Typ) = T;
10537 -- Climb to the ancestor type handling private types
10539 if Present (Full_View (Etype (Typ))) then
10540 Typ := Full_View (Etype (Typ));
10541 else
10542 Typ := Etype (Typ);
10543 end if;
10544 end loop;
10546 return False;
10547 end Has_Interfaces;
10549 --------------------------
10550 -- Has_Max_Queue_Length --
10551 --------------------------
10553 function Has_Max_Queue_Length (Id : Entity_Id) return Boolean is
10554 begin
10555 return
10556 Ekind (Id) = E_Entry
10557 and then Present (Get_Pragma (Id, Pragma_Max_Queue_Length));
10558 end Has_Max_Queue_Length;
10560 ---------------------------------
10561 -- Has_No_Obvious_Side_Effects --
10562 ---------------------------------
10564 function Has_No_Obvious_Side_Effects (N : Node_Id) return Boolean is
10565 begin
10566 -- For now handle literals, constants, and non-volatile variables and
10567 -- expressions combining these with operators or short circuit forms.
10569 if Nkind (N) in N_Numeric_Or_String_Literal then
10570 return True;
10572 elsif Nkind (N) = N_Character_Literal then
10573 return True;
10575 elsif Nkind (N) in N_Unary_Op then
10576 return Has_No_Obvious_Side_Effects (Right_Opnd (N));
10578 elsif Nkind (N) in N_Binary_Op or else Nkind (N) in N_Short_Circuit then
10579 return Has_No_Obvious_Side_Effects (Left_Opnd (N))
10580 and then
10581 Has_No_Obvious_Side_Effects (Right_Opnd (N));
10583 elsif Nkind (N) = N_Expression_With_Actions
10584 and then Is_Empty_List (Actions (N))
10585 then
10586 return Has_No_Obvious_Side_Effects (Expression (N));
10588 elsif Nkind (N) in N_Has_Entity then
10589 return Present (Entity (N))
10590 and then Ekind_In (Entity (N), E_Variable,
10591 E_Constant,
10592 E_Enumeration_Literal,
10593 E_In_Parameter,
10594 E_Out_Parameter,
10595 E_In_Out_Parameter)
10596 and then not Is_Volatile (Entity (N));
10598 else
10599 return False;
10600 end if;
10601 end Has_No_Obvious_Side_Effects;
10603 -----------------------------
10604 -- Has_Non_Null_Refinement --
10605 -----------------------------
10607 function Has_Non_Null_Refinement (Id : Entity_Id) return Boolean is
10608 Constits : Elist_Id;
10610 begin
10611 pragma Assert (Ekind (Id) = E_Abstract_State);
10612 Constits := Refinement_Constituents (Id);
10614 -- For a refinement to be non-null, the first constituent must be
10615 -- anything other than null.
10617 return
10618 Present (Constits)
10619 and then Nkind (Node (First_Elmt (Constits))) /= N_Null;
10620 end Has_Non_Null_Refinement;
10622 ----------------------------------
10623 -- Has_Non_Trivial_Precondition --
10624 ----------------------------------
10626 function Has_Non_Trivial_Precondition (Subp : Entity_Id) return Boolean is
10627 Pre : constant Node_Id := Find_Aspect (Subp, Aspect_Pre);
10629 begin
10630 return
10631 Present (Pre)
10632 and then Class_Present (Pre)
10633 and then not Is_Entity_Name (Expression (Pre));
10634 end Has_Non_Trivial_Precondition;
10636 -------------------
10637 -- Has_Null_Body --
10638 -------------------
10640 function Has_Null_Body (Proc_Id : Entity_Id) return Boolean is
10641 Body_Id : Entity_Id;
10642 Decl : Node_Id;
10643 Spec : Node_Id;
10644 Stmt1 : Node_Id;
10645 Stmt2 : Node_Id;
10647 begin
10648 Spec := Parent (Proc_Id);
10649 Decl := Parent (Spec);
10651 -- Retrieve the entity of the procedure body (e.g. invariant proc).
10653 if Nkind (Spec) = N_Procedure_Specification
10654 and then Nkind (Decl) = N_Subprogram_Declaration
10655 then
10656 Body_Id := Corresponding_Body (Decl);
10658 -- The body acts as a spec
10660 else
10661 Body_Id := Proc_Id;
10662 end if;
10664 -- The body will be generated later
10666 if No (Body_Id) then
10667 return False;
10668 end if;
10670 Spec := Parent (Body_Id);
10671 Decl := Parent (Spec);
10673 pragma Assert
10674 (Nkind (Spec) = N_Procedure_Specification
10675 and then Nkind (Decl) = N_Subprogram_Body);
10677 Stmt1 := First (Statements (Handled_Statement_Sequence (Decl)));
10679 -- Look for a null statement followed by an optional return
10680 -- statement.
10682 if Nkind (Stmt1) = N_Null_Statement then
10683 Stmt2 := Next (Stmt1);
10685 if Present (Stmt2) then
10686 return Nkind (Stmt2) = N_Simple_Return_Statement;
10687 else
10688 return True;
10689 end if;
10690 end if;
10692 return False;
10693 end Has_Null_Body;
10695 ------------------------
10696 -- Has_Null_Exclusion --
10697 ------------------------
10699 function Has_Null_Exclusion (N : Node_Id) return Boolean is
10700 begin
10701 case Nkind (N) is
10702 when N_Access_Definition
10703 | N_Access_Function_Definition
10704 | N_Access_Procedure_Definition
10705 | N_Access_To_Object_Definition
10706 | N_Allocator
10707 | N_Derived_Type_Definition
10708 | N_Function_Specification
10709 | N_Subtype_Declaration
10711 return Null_Exclusion_Present (N);
10713 when N_Component_Definition
10714 | N_Formal_Object_Declaration
10715 | N_Object_Renaming_Declaration
10717 if Present (Subtype_Mark (N)) then
10718 return Null_Exclusion_Present (N);
10719 else pragma Assert (Present (Access_Definition (N)));
10720 return Null_Exclusion_Present (Access_Definition (N));
10721 end if;
10723 when N_Discriminant_Specification =>
10724 if Nkind (Discriminant_Type (N)) = N_Access_Definition then
10725 return Null_Exclusion_Present (Discriminant_Type (N));
10726 else
10727 return Null_Exclusion_Present (N);
10728 end if;
10730 when N_Object_Declaration =>
10731 if Nkind (Object_Definition (N)) = N_Access_Definition then
10732 return Null_Exclusion_Present (Object_Definition (N));
10733 else
10734 return Null_Exclusion_Present (N);
10735 end if;
10737 when N_Parameter_Specification =>
10738 if Nkind (Parameter_Type (N)) = N_Access_Definition then
10739 return Null_Exclusion_Present (Parameter_Type (N));
10740 else
10741 return Null_Exclusion_Present (N);
10742 end if;
10744 when others =>
10745 return False;
10746 end case;
10747 end Has_Null_Exclusion;
10749 ------------------------
10750 -- Has_Null_Extension --
10751 ------------------------
10753 function Has_Null_Extension (T : Entity_Id) return Boolean is
10754 B : constant Entity_Id := Base_Type (T);
10755 Comps : Node_Id;
10756 Ext : Node_Id;
10758 begin
10759 if Nkind (Parent (B)) = N_Full_Type_Declaration
10760 and then Present (Record_Extension_Part (Type_Definition (Parent (B))))
10761 then
10762 Ext := Record_Extension_Part (Type_Definition (Parent (B)));
10764 if Present (Ext) then
10765 if Null_Present (Ext) then
10766 return True;
10767 else
10768 Comps := Component_List (Ext);
10770 -- The null component list is rewritten during analysis to
10771 -- include the parent component. Any other component indicates
10772 -- that the extension was not originally null.
10774 return Null_Present (Comps)
10775 or else No (Next (First (Component_Items (Comps))));
10776 end if;
10777 else
10778 return False;
10779 end if;
10781 else
10782 return False;
10783 end if;
10784 end Has_Null_Extension;
10786 -------------------------
10787 -- Has_Null_Refinement --
10788 -------------------------
10790 function Has_Null_Refinement (Id : Entity_Id) return Boolean is
10791 Constits : Elist_Id;
10793 begin
10794 pragma Assert (Ekind (Id) = E_Abstract_State);
10795 Constits := Refinement_Constituents (Id);
10797 -- For a refinement to be null, the state's sole constituent must be a
10798 -- null.
10800 return
10801 Present (Constits)
10802 and then Nkind (Node (First_Elmt (Constits))) = N_Null;
10803 end Has_Null_Refinement;
10805 -------------------------------
10806 -- Has_Overriding_Initialize --
10807 -------------------------------
10809 function Has_Overriding_Initialize (T : Entity_Id) return Boolean is
10810 BT : constant Entity_Id := Base_Type (T);
10811 P : Elmt_Id;
10813 begin
10814 if Is_Controlled (BT) then
10815 if Is_RTU (Scope (BT), Ada_Finalization) then
10816 return False;
10818 elsif Present (Primitive_Operations (BT)) then
10819 P := First_Elmt (Primitive_Operations (BT));
10820 while Present (P) loop
10821 declare
10822 Init : constant Entity_Id := Node (P);
10823 Formal : constant Entity_Id := First_Formal (Init);
10824 begin
10825 if Ekind (Init) = E_Procedure
10826 and then Chars (Init) = Name_Initialize
10827 and then Comes_From_Source (Init)
10828 and then Present (Formal)
10829 and then Etype (Formal) = BT
10830 and then No (Next_Formal (Formal))
10831 and then (Ada_Version < Ada_2012
10832 or else not Null_Present (Parent (Init)))
10833 then
10834 return True;
10835 end if;
10836 end;
10838 Next_Elmt (P);
10839 end loop;
10840 end if;
10842 -- Here if type itself does not have a non-null Initialize operation:
10843 -- check immediate ancestor.
10845 if Is_Derived_Type (BT)
10846 and then Has_Overriding_Initialize (Etype (BT))
10847 then
10848 return True;
10849 end if;
10850 end if;
10852 return False;
10853 end Has_Overriding_Initialize;
10855 --------------------------------------
10856 -- Has_Preelaborable_Initialization --
10857 --------------------------------------
10859 function Has_Preelaborable_Initialization (E : Entity_Id) return Boolean is
10860 Has_PE : Boolean;
10862 procedure Check_Components (E : Entity_Id);
10863 -- Check component/discriminant chain, sets Has_PE False if a component
10864 -- or discriminant does not meet the preelaborable initialization rules.
10866 ----------------------
10867 -- Check_Components --
10868 ----------------------
10870 procedure Check_Components (E : Entity_Id) is
10871 Ent : Entity_Id;
10872 Exp : Node_Id;
10874 begin
10875 -- Loop through entities of record or protected type
10877 Ent := E;
10878 while Present (Ent) loop
10880 -- We are interested only in components and discriminants
10882 Exp := Empty;
10884 case Ekind (Ent) is
10885 when E_Component =>
10887 -- Get default expression if any. If there is no declaration
10888 -- node, it means we have an internal entity. The parent and
10889 -- tag fields are examples of such entities. For such cases,
10890 -- we just test the type of the entity.
10892 if Present (Declaration_Node (Ent)) then
10893 Exp := Expression (Declaration_Node (Ent));
10894 end if;
10896 when E_Discriminant =>
10898 -- Note: for a renamed discriminant, the Declaration_Node
10899 -- may point to the one from the ancestor, and have a
10900 -- different expression, so use the proper attribute to
10901 -- retrieve the expression from the derived constraint.
10903 Exp := Discriminant_Default_Value (Ent);
10905 when others =>
10906 goto Check_Next_Entity;
10907 end case;
10909 -- A component has PI if it has no default expression and the
10910 -- component type has PI.
10912 if No (Exp) then
10913 if not Has_Preelaborable_Initialization (Etype (Ent)) then
10914 Has_PE := False;
10915 exit;
10916 end if;
10918 -- Require the default expression to be preelaborable
10920 elsif not Is_Preelaborable_Construct (Exp) then
10921 Has_PE := False;
10922 exit;
10923 end if;
10925 <<Check_Next_Entity>>
10926 Next_Entity (Ent);
10927 end loop;
10928 end Check_Components;
10930 -- Start of processing for Has_Preelaborable_Initialization
10932 begin
10933 -- Immediate return if already marked as known preelaborable init. This
10934 -- covers types for which this function has already been called once
10935 -- and returned True (in which case the result is cached), and also
10936 -- types to which a pragma Preelaborable_Initialization applies.
10938 if Known_To_Have_Preelab_Init (E) then
10939 return True;
10940 end if;
10942 -- If the type is a subtype representing a generic actual type, then
10943 -- test whether its base type has preelaborable initialization since
10944 -- the subtype representing the actual does not inherit this attribute
10945 -- from the actual or formal. (but maybe it should???)
10947 if Is_Generic_Actual_Type (E) then
10948 return Has_Preelaborable_Initialization (Base_Type (E));
10949 end if;
10951 -- All elementary types have preelaborable initialization
10953 if Is_Elementary_Type (E) then
10954 Has_PE := True;
10956 -- Array types have PI if the component type has PI
10958 elsif Is_Array_Type (E) then
10959 Has_PE := Has_Preelaborable_Initialization (Component_Type (E));
10961 -- A derived type has preelaborable initialization if its parent type
10962 -- has preelaborable initialization and (in the case of a derived record
10963 -- extension) if the non-inherited components all have preelaborable
10964 -- initialization. However, a user-defined controlled type with an
10965 -- overriding Initialize procedure does not have preelaborable
10966 -- initialization.
10968 elsif Is_Derived_Type (E) then
10970 -- If the derived type is a private extension then it doesn't have
10971 -- preelaborable initialization.
10973 if Ekind (Base_Type (E)) = E_Record_Type_With_Private then
10974 return False;
10975 end if;
10977 -- First check whether ancestor type has preelaborable initialization
10979 Has_PE := Has_Preelaborable_Initialization (Etype (Base_Type (E)));
10981 -- If OK, check extension components (if any)
10983 if Has_PE and then Is_Record_Type (E) then
10984 Check_Components (First_Entity (E));
10985 end if;
10987 -- Check specifically for 10.2.1(11.4/2) exception: a controlled type
10988 -- with a user defined Initialize procedure does not have PI. If
10989 -- the type is untagged, the control primitives come from a component
10990 -- that has already been checked.
10992 if Has_PE
10993 and then Is_Controlled (E)
10994 and then Is_Tagged_Type (E)
10995 and then Has_Overriding_Initialize (E)
10996 then
10997 Has_PE := False;
10998 end if;
11000 -- Private types not derived from a type having preelaborable init and
11001 -- that are not marked with pragma Preelaborable_Initialization do not
11002 -- have preelaborable initialization.
11004 elsif Is_Private_Type (E) then
11005 return False;
11007 -- Record type has PI if it is non private and all components have PI
11009 elsif Is_Record_Type (E) then
11010 Has_PE := True;
11011 Check_Components (First_Entity (E));
11013 -- Protected types must not have entries, and components must meet
11014 -- same set of rules as for record components.
11016 elsif Is_Protected_Type (E) then
11017 if Has_Entries (E) then
11018 Has_PE := False;
11019 else
11020 Has_PE := True;
11021 Check_Components (First_Entity (E));
11022 Check_Components (First_Private_Entity (E));
11023 end if;
11025 -- Type System.Address always has preelaborable initialization
11027 elsif Is_RTE (E, RE_Address) then
11028 Has_PE := True;
11030 -- In all other cases, type does not have preelaborable initialization
11032 else
11033 return False;
11034 end if;
11036 -- If type has preelaborable initialization, cache result
11038 if Has_PE then
11039 Set_Known_To_Have_Preelab_Init (E);
11040 end if;
11042 return Has_PE;
11043 end Has_Preelaborable_Initialization;
11045 ---------------------------
11046 -- Has_Private_Component --
11047 ---------------------------
11049 function Has_Private_Component (Type_Id : Entity_Id) return Boolean is
11050 Btype : Entity_Id := Base_Type (Type_Id);
11051 Component : Entity_Id;
11053 begin
11054 if Error_Posted (Type_Id)
11055 or else Error_Posted (Btype)
11056 then
11057 return False;
11058 end if;
11060 if Is_Class_Wide_Type (Btype) then
11061 Btype := Root_Type (Btype);
11062 end if;
11064 if Is_Private_Type (Btype) then
11065 declare
11066 UT : constant Entity_Id := Underlying_Type (Btype);
11067 begin
11068 if No (UT) then
11069 if No (Full_View (Btype)) then
11070 return not Is_Generic_Type (Btype)
11071 and then
11072 not Is_Generic_Type (Root_Type (Btype));
11073 else
11074 return not Is_Generic_Type (Root_Type (Full_View (Btype)));
11075 end if;
11076 else
11077 return not Is_Frozen (UT) and then Has_Private_Component (UT);
11078 end if;
11079 end;
11081 elsif Is_Array_Type (Btype) then
11082 return Has_Private_Component (Component_Type (Btype));
11084 elsif Is_Record_Type (Btype) then
11085 Component := First_Component (Btype);
11086 while Present (Component) loop
11087 if Has_Private_Component (Etype (Component)) then
11088 return True;
11089 end if;
11091 Next_Component (Component);
11092 end loop;
11094 return False;
11096 elsif Is_Protected_Type (Btype)
11097 and then Present (Corresponding_Record_Type (Btype))
11098 then
11099 return Has_Private_Component (Corresponding_Record_Type (Btype));
11101 else
11102 return False;
11103 end if;
11104 end Has_Private_Component;
11106 ----------------------
11107 -- Has_Signed_Zeros --
11108 ----------------------
11110 function Has_Signed_Zeros (E : Entity_Id) return Boolean is
11111 begin
11112 return Is_Floating_Point_Type (E) and then Signed_Zeros_On_Target;
11113 end Has_Signed_Zeros;
11115 ------------------------------
11116 -- Has_Significant_Contract --
11117 ------------------------------
11119 function Has_Significant_Contract (Subp_Id : Entity_Id) return Boolean is
11120 Subp_Nam : constant Name_Id := Chars (Subp_Id);
11122 begin
11123 -- _Finalizer procedure
11125 if Subp_Nam = Name_uFinalizer then
11126 return False;
11128 -- _Postconditions procedure
11130 elsif Subp_Nam = Name_uPostconditions then
11131 return False;
11133 -- Predicate function
11135 elsif Ekind (Subp_Id) = E_Function
11136 and then Is_Predicate_Function (Subp_Id)
11137 then
11138 return False;
11140 -- TSS subprogram
11142 elsif Get_TSS_Name (Subp_Id) /= TSS_Null then
11143 return False;
11145 else
11146 return True;
11147 end if;
11148 end Has_Significant_Contract;
11150 -----------------------------
11151 -- Has_Static_Array_Bounds --
11152 -----------------------------
11154 function Has_Static_Array_Bounds (Typ : Node_Id) return Boolean is
11155 Ndims : constant Nat := Number_Dimensions (Typ);
11157 Index : Node_Id;
11158 Low : Node_Id;
11159 High : Node_Id;
11161 begin
11162 -- Unconstrained types do not have static bounds
11164 if not Is_Constrained (Typ) then
11165 return False;
11166 end if;
11168 -- First treat string literals specially, as the lower bound and length
11169 -- of string literals are not stored like those of arrays.
11171 -- A string literal always has static bounds
11173 if Ekind (Typ) = E_String_Literal_Subtype then
11174 return True;
11175 end if;
11177 -- Treat all dimensions in turn
11179 Index := First_Index (Typ);
11180 for Indx in 1 .. Ndims loop
11182 -- In case of an illegal index which is not a discrete type, return
11183 -- that the type is not static.
11185 if not Is_Discrete_Type (Etype (Index))
11186 or else Etype (Index) = Any_Type
11187 then
11188 return False;
11189 end if;
11191 Get_Index_Bounds (Index, Low, High);
11193 if Error_Posted (Low) or else Error_Posted (High) then
11194 return False;
11195 end if;
11197 if Is_OK_Static_Expression (Low)
11198 and then
11199 Is_OK_Static_Expression (High)
11200 then
11201 null;
11202 else
11203 return False;
11204 end if;
11206 Next (Index);
11207 end loop;
11209 -- If we fall through the loop, all indexes matched
11211 return True;
11212 end Has_Static_Array_Bounds;
11214 ----------------
11215 -- Has_Stream --
11216 ----------------
11218 function Has_Stream (T : Entity_Id) return Boolean is
11219 E : Entity_Id;
11221 begin
11222 if No (T) then
11223 return False;
11225 elsif Is_RTE (Root_Type (T), RE_Root_Stream_Type) then
11226 return True;
11228 elsif Is_Array_Type (T) then
11229 return Has_Stream (Component_Type (T));
11231 elsif Is_Record_Type (T) then
11232 E := First_Component (T);
11233 while Present (E) loop
11234 if Has_Stream (Etype (E)) then
11235 return True;
11236 else
11237 Next_Component (E);
11238 end if;
11239 end loop;
11241 return False;
11243 elsif Is_Private_Type (T) then
11244 return Has_Stream (Underlying_Type (T));
11246 else
11247 return False;
11248 end if;
11249 end Has_Stream;
11251 ----------------
11252 -- Has_Suffix --
11253 ----------------
11255 function Has_Suffix (E : Entity_Id; Suffix : Character) return Boolean is
11256 begin
11257 Get_Name_String (Chars (E));
11258 return Name_Buffer (Name_Len) = Suffix;
11259 end Has_Suffix;
11261 ----------------
11262 -- Add_Suffix --
11263 ----------------
11265 function Add_Suffix (E : Entity_Id; Suffix : Character) return Name_Id is
11266 begin
11267 Get_Name_String (Chars (E));
11268 Add_Char_To_Name_Buffer (Suffix);
11269 return Name_Find;
11270 end Add_Suffix;
11272 -------------------
11273 -- Remove_Suffix --
11274 -------------------
11276 function Remove_Suffix (E : Entity_Id; Suffix : Character) return Name_Id is
11277 begin
11278 pragma Assert (Has_Suffix (E, Suffix));
11279 Get_Name_String (Chars (E));
11280 Name_Len := Name_Len - 1;
11281 return Name_Find;
11282 end Remove_Suffix;
11284 ----------------------------------
11285 -- Replace_Null_By_Null_Address --
11286 ----------------------------------
11288 procedure Replace_Null_By_Null_Address (N : Node_Id) is
11289 procedure Replace_Null_Operand (Op : Node_Id; Other_Op : Node_Id);
11290 -- Replace operand Op with a reference to Null_Address when the operand
11291 -- denotes a null Address. Other_Op denotes the other operand.
11293 --------------------------
11294 -- Replace_Null_Operand --
11295 --------------------------
11297 procedure Replace_Null_Operand (Op : Node_Id; Other_Op : Node_Id) is
11298 begin
11299 -- Check the type of the complementary operand since the N_Null node
11300 -- has not been decorated yet.
11302 if Nkind (Op) = N_Null
11303 and then Is_Descendant_Of_Address (Etype (Other_Op))
11304 then
11305 Rewrite (Op, New_Occurrence_Of (RTE (RE_Null_Address), Sloc (Op)));
11306 end if;
11307 end Replace_Null_Operand;
11309 -- Start of processing for Replace_Null_By_Null_Address
11311 begin
11312 pragma Assert (Relaxed_RM_Semantics);
11313 pragma Assert (Nkind_In (N, N_Null,
11314 N_Op_Eq,
11315 N_Op_Ge,
11316 N_Op_Gt,
11317 N_Op_Le,
11318 N_Op_Lt,
11319 N_Op_Ne));
11321 if Nkind (N) = N_Null then
11322 Rewrite (N, New_Occurrence_Of (RTE (RE_Null_Address), Sloc (N)));
11324 else
11325 declare
11326 L : constant Node_Id := Left_Opnd (N);
11327 R : constant Node_Id := Right_Opnd (N);
11329 begin
11330 Replace_Null_Operand (L, Other_Op => R);
11331 Replace_Null_Operand (R, Other_Op => L);
11332 end;
11333 end if;
11334 end Replace_Null_By_Null_Address;
11336 --------------------------
11337 -- Has_Tagged_Component --
11338 --------------------------
11340 function Has_Tagged_Component (Typ : Entity_Id) return Boolean is
11341 Comp : Entity_Id;
11343 begin
11344 if Is_Private_Type (Typ) and then Present (Underlying_Type (Typ)) then
11345 return Has_Tagged_Component (Underlying_Type (Typ));
11347 elsif Is_Array_Type (Typ) then
11348 return Has_Tagged_Component (Component_Type (Typ));
11350 elsif Is_Tagged_Type (Typ) then
11351 return True;
11353 elsif Is_Record_Type (Typ) then
11354 Comp := First_Component (Typ);
11355 while Present (Comp) loop
11356 if Has_Tagged_Component (Etype (Comp)) then
11357 return True;
11358 end if;
11360 Next_Component (Comp);
11361 end loop;
11363 return False;
11365 else
11366 return False;
11367 end if;
11368 end Has_Tagged_Component;
11370 -----------------------------
11371 -- Has_Undefined_Reference --
11372 -----------------------------
11374 function Has_Undefined_Reference (Expr : Node_Id) return Boolean is
11375 Has_Undef_Ref : Boolean := False;
11376 -- Flag set when expression Expr contains at least one undefined
11377 -- reference.
11379 function Is_Undefined_Reference (N : Node_Id) return Traverse_Result;
11380 -- Determine whether N denotes a reference and if it does, whether it is
11381 -- undefined.
11383 ----------------------------
11384 -- Is_Undefined_Reference --
11385 ----------------------------
11387 function Is_Undefined_Reference (N : Node_Id) return Traverse_Result is
11388 begin
11389 if Is_Entity_Name (N)
11390 and then Present (Entity (N))
11391 and then Entity (N) = Any_Id
11392 then
11393 Has_Undef_Ref := True;
11394 return Abandon;
11395 end if;
11397 return OK;
11398 end Is_Undefined_Reference;
11400 procedure Find_Undefined_References is
11401 new Traverse_Proc (Is_Undefined_Reference);
11403 -- Start of processing for Has_Undefined_Reference
11405 begin
11406 Find_Undefined_References (Expr);
11408 return Has_Undef_Ref;
11409 end Has_Undefined_Reference;
11411 ----------------------------
11412 -- Has_Volatile_Component --
11413 ----------------------------
11415 function Has_Volatile_Component (Typ : Entity_Id) return Boolean is
11416 Comp : Entity_Id;
11418 begin
11419 if Has_Volatile_Components (Typ) then
11420 return True;
11422 elsif Is_Array_Type (Typ) then
11423 return Is_Volatile (Component_Type (Typ));
11425 elsif Is_Record_Type (Typ) then
11426 Comp := First_Component (Typ);
11427 while Present (Comp) loop
11428 if Is_Volatile_Object (Comp) then
11429 return True;
11430 end if;
11432 Comp := Next_Component (Comp);
11433 end loop;
11434 end if;
11436 return False;
11437 end Has_Volatile_Component;
11439 -------------------------
11440 -- Implementation_Kind --
11441 -------------------------
11443 function Implementation_Kind (Subp : Entity_Id) return Name_Id is
11444 Impl_Prag : constant Node_Id := Get_Rep_Pragma (Subp, Name_Implemented);
11445 Arg : Node_Id;
11446 begin
11447 pragma Assert (Present (Impl_Prag));
11448 Arg := Last (Pragma_Argument_Associations (Impl_Prag));
11449 return Chars (Get_Pragma_Arg (Arg));
11450 end Implementation_Kind;
11452 --------------------------
11453 -- Implements_Interface --
11454 --------------------------
11456 function Implements_Interface
11457 (Typ_Ent : Entity_Id;
11458 Iface_Ent : Entity_Id;
11459 Exclude_Parents : Boolean := False) return Boolean
11461 Ifaces_List : Elist_Id;
11462 Elmt : Elmt_Id;
11463 Iface : Entity_Id := Base_Type (Iface_Ent);
11464 Typ : Entity_Id := Base_Type (Typ_Ent);
11466 begin
11467 if Is_Class_Wide_Type (Typ) then
11468 Typ := Root_Type (Typ);
11469 end if;
11471 if not Has_Interfaces (Typ) then
11472 return False;
11473 end if;
11475 if Is_Class_Wide_Type (Iface) then
11476 Iface := Root_Type (Iface);
11477 end if;
11479 Collect_Interfaces (Typ, Ifaces_List);
11481 Elmt := First_Elmt (Ifaces_List);
11482 while Present (Elmt) loop
11483 if Is_Ancestor (Node (Elmt), Typ, Use_Full_View => True)
11484 and then Exclude_Parents
11485 then
11486 null;
11488 elsif Node (Elmt) = Iface then
11489 return True;
11490 end if;
11492 Next_Elmt (Elmt);
11493 end loop;
11495 return False;
11496 end Implements_Interface;
11498 ------------------------------------
11499 -- In_Assertion_Expression_Pragma --
11500 ------------------------------------
11502 function In_Assertion_Expression_Pragma (N : Node_Id) return Boolean is
11503 Par : Node_Id;
11504 Prag : Node_Id := Empty;
11506 begin
11507 -- Climb the parent chain looking for an enclosing pragma
11509 Par := N;
11510 while Present (Par) loop
11511 if Nkind (Par) = N_Pragma then
11512 Prag := Par;
11513 exit;
11515 -- Precondition-like pragmas are expanded into if statements, check
11516 -- the original node instead.
11518 elsif Nkind (Original_Node (Par)) = N_Pragma then
11519 Prag := Original_Node (Par);
11520 exit;
11522 -- The expansion of attribute 'Old generates a constant to capture
11523 -- the result of the prefix. If the parent traversal reaches
11524 -- one of these constants, then the node technically came from a
11525 -- postcondition-like pragma. Note that the Ekind is not tested here
11526 -- because N may be the expression of an object declaration which is
11527 -- currently being analyzed. Such objects carry Ekind of E_Void.
11529 elsif Nkind (Par) = N_Object_Declaration
11530 and then Constant_Present (Par)
11531 and then Stores_Attribute_Old_Prefix (Defining_Entity (Par))
11532 then
11533 return True;
11535 -- Prevent the search from going too far
11537 elsif Is_Body_Or_Package_Declaration (Par) then
11538 return False;
11539 end if;
11541 Par := Parent (Par);
11542 end loop;
11544 return
11545 Present (Prag)
11546 and then Assertion_Expression_Pragma (Get_Pragma_Id (Prag));
11547 end In_Assertion_Expression_Pragma;
11549 ----------------------
11550 -- In_Generic_Scope --
11551 ----------------------
11553 function In_Generic_Scope (E : Entity_Id) return Boolean is
11554 S : Entity_Id;
11556 begin
11557 S := Scope (E);
11558 while Present (S) and then S /= Standard_Standard loop
11559 if Is_Generic_Unit (S) then
11560 return True;
11561 end if;
11563 S := Scope (S);
11564 end loop;
11566 return False;
11567 end In_Generic_Scope;
11569 -----------------
11570 -- In_Instance --
11571 -----------------
11573 function In_Instance return Boolean is
11574 Curr_Unit : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
11575 S : Entity_Id;
11577 begin
11578 S := Current_Scope;
11579 while Present (S) and then S /= Standard_Standard loop
11580 if Is_Generic_Instance (S) then
11582 -- A child instance is always compiled in the context of a parent
11583 -- instance. Nevertheless, the actuals are not analyzed in an
11584 -- instance context. We detect this case by examining the current
11585 -- compilation unit, which must be a child instance, and checking
11586 -- that it is not currently on the scope stack.
11588 if Is_Child_Unit (Curr_Unit)
11589 and then Nkind (Unit (Cunit (Current_Sem_Unit))) =
11590 N_Package_Instantiation
11591 and then not In_Open_Scopes (Curr_Unit)
11592 then
11593 return False;
11594 else
11595 return True;
11596 end if;
11597 end if;
11599 S := Scope (S);
11600 end loop;
11602 return False;
11603 end In_Instance;
11605 ----------------------
11606 -- In_Instance_Body --
11607 ----------------------
11609 function In_Instance_Body return Boolean is
11610 S : Entity_Id;
11612 begin
11613 S := Current_Scope;
11614 while Present (S) and then S /= Standard_Standard loop
11615 if Ekind_In (S, E_Function, E_Procedure)
11616 and then Is_Generic_Instance (S)
11617 then
11618 return True;
11620 elsif Ekind (S) = E_Package
11621 and then In_Package_Body (S)
11622 and then Is_Generic_Instance (S)
11623 then
11624 return True;
11625 end if;
11627 S := Scope (S);
11628 end loop;
11630 return False;
11631 end In_Instance_Body;
11633 -----------------------------
11634 -- In_Instance_Not_Visible --
11635 -----------------------------
11637 function In_Instance_Not_Visible return Boolean is
11638 S : Entity_Id;
11640 begin
11641 S := Current_Scope;
11642 while Present (S) and then S /= Standard_Standard loop
11643 if Ekind_In (S, E_Function, E_Procedure)
11644 and then Is_Generic_Instance (S)
11645 then
11646 return True;
11648 elsif Ekind (S) = E_Package
11649 and then (In_Package_Body (S) or else In_Private_Part (S))
11650 and then Is_Generic_Instance (S)
11651 then
11652 return True;
11653 end if;
11655 S := Scope (S);
11656 end loop;
11658 return False;
11659 end In_Instance_Not_Visible;
11661 ------------------------------
11662 -- In_Instance_Visible_Part --
11663 ------------------------------
11665 function In_Instance_Visible_Part
11666 (Id : Entity_Id := Current_Scope) return Boolean
11668 Inst : Entity_Id;
11670 begin
11671 Inst := Id;
11672 while Present (Inst) and then Inst /= Standard_Standard loop
11673 if Ekind (Inst) = E_Package
11674 and then Is_Generic_Instance (Inst)
11675 and then not In_Package_Body (Inst)
11676 and then not In_Private_Part (Inst)
11677 then
11678 return True;
11679 end if;
11681 Inst := Scope (Inst);
11682 end loop;
11684 return False;
11685 end In_Instance_Visible_Part;
11687 ---------------------
11688 -- In_Package_Body --
11689 ---------------------
11691 function In_Package_Body return Boolean is
11692 S : Entity_Id;
11694 begin
11695 S := Current_Scope;
11696 while Present (S) and then S /= Standard_Standard loop
11697 if Ekind (S) = E_Package and then In_Package_Body (S) then
11698 return True;
11699 else
11700 S := Scope (S);
11701 end if;
11702 end loop;
11704 return False;
11705 end In_Package_Body;
11707 --------------------------
11708 -- In_Pragma_Expression --
11709 --------------------------
11711 function In_Pragma_Expression (N : Node_Id; Nam : Name_Id) return Boolean is
11712 P : Node_Id;
11713 begin
11714 P := Parent (N);
11715 loop
11716 if No (P) then
11717 return False;
11718 elsif Nkind (P) = N_Pragma and then Pragma_Name (P) = Nam then
11719 return True;
11720 else
11721 P := Parent (P);
11722 end if;
11723 end loop;
11724 end In_Pragma_Expression;
11726 ---------------------------
11727 -- In_Pre_Post_Condition --
11728 ---------------------------
11730 function In_Pre_Post_Condition (N : Node_Id) return Boolean is
11731 Par : Node_Id;
11732 Prag : Node_Id := Empty;
11733 Prag_Id : Pragma_Id;
11735 begin
11736 -- Climb the parent chain looking for an enclosing pragma
11738 Par := N;
11739 while Present (Par) loop
11740 if Nkind (Par) = N_Pragma then
11741 Prag := Par;
11742 exit;
11744 -- Prevent the search from going too far
11746 elsif Is_Body_Or_Package_Declaration (Par) then
11747 exit;
11748 end if;
11750 Par := Parent (Par);
11751 end loop;
11753 if Present (Prag) then
11754 Prag_Id := Get_Pragma_Id (Prag);
11756 return
11757 Prag_Id = Pragma_Post
11758 or else Prag_Id = Pragma_Post_Class
11759 or else Prag_Id = Pragma_Postcondition
11760 or else Prag_Id = Pragma_Pre
11761 or else Prag_Id = Pragma_Pre_Class
11762 or else Prag_Id = Pragma_Precondition;
11764 -- Otherwise the node is not enclosed by a pre/postcondition pragma
11766 else
11767 return False;
11768 end if;
11769 end In_Pre_Post_Condition;
11771 -------------------------------------
11772 -- In_Reverse_Storage_Order_Object --
11773 -------------------------------------
11775 function In_Reverse_Storage_Order_Object (N : Node_Id) return Boolean is
11776 Pref : Node_Id;
11777 Btyp : Entity_Id := Empty;
11779 begin
11780 -- Climb up indexed components
11782 Pref := N;
11783 loop
11784 case Nkind (Pref) is
11785 when N_Selected_Component =>
11786 Pref := Prefix (Pref);
11787 exit;
11789 when N_Indexed_Component =>
11790 Pref := Prefix (Pref);
11792 when others =>
11793 Pref := Empty;
11794 exit;
11795 end case;
11796 end loop;
11798 if Present (Pref) then
11799 Btyp := Base_Type (Etype (Pref));
11800 end if;
11802 return Present (Btyp)
11803 and then (Is_Record_Type (Btyp) or else Is_Array_Type (Btyp))
11804 and then Reverse_Storage_Order (Btyp);
11805 end In_Reverse_Storage_Order_Object;
11807 --------------------------------------
11808 -- In_Subprogram_Or_Concurrent_Unit --
11809 --------------------------------------
11811 function In_Subprogram_Or_Concurrent_Unit return Boolean is
11812 E : Entity_Id;
11813 K : Entity_Kind;
11815 begin
11816 -- Use scope chain to check successively outer scopes
11818 E := Current_Scope;
11819 loop
11820 K := Ekind (E);
11822 if K in Subprogram_Kind
11823 or else K in Concurrent_Kind
11824 or else K in Generic_Subprogram_Kind
11825 then
11826 return True;
11828 elsif E = Standard_Standard then
11829 return False;
11830 end if;
11832 E := Scope (E);
11833 end loop;
11834 end In_Subprogram_Or_Concurrent_Unit;
11836 ----------------
11837 -- In_Subtree --
11838 ----------------
11840 function In_Subtree (N : Node_Id; Root : Node_Id) return Boolean is
11841 Curr : Node_Id;
11843 begin
11844 Curr := N;
11845 while Present (Curr) loop
11846 if Curr = Root then
11847 return True;
11848 end if;
11850 Curr := Parent (Curr);
11851 end loop;
11853 return False;
11854 end In_Subtree;
11856 ----------------
11857 -- In_Subtree --
11858 ----------------
11860 function In_Subtree
11861 (N : Node_Id;
11862 Root1 : Node_Id;
11863 Root2 : Node_Id) return Boolean
11865 Curr : Node_Id;
11867 begin
11868 Curr := N;
11869 while Present (Curr) loop
11870 if Curr = Root1 or else Curr = Root2 then
11871 return True;
11872 end if;
11874 Curr := Parent (Curr);
11875 end loop;
11877 return False;
11878 end In_Subtree;
11880 ---------------------
11881 -- In_Visible_Part --
11882 ---------------------
11884 function In_Visible_Part (Scope_Id : Entity_Id) return Boolean is
11885 begin
11886 return Is_Package_Or_Generic_Package (Scope_Id)
11887 and then In_Open_Scopes (Scope_Id)
11888 and then not In_Package_Body (Scope_Id)
11889 and then not In_Private_Part (Scope_Id);
11890 end In_Visible_Part;
11892 --------------------------------
11893 -- Incomplete_Or_Partial_View --
11894 --------------------------------
11896 function Incomplete_Or_Partial_View (Id : Entity_Id) return Entity_Id is
11897 function Inspect_Decls
11898 (Decls : List_Id;
11899 Taft : Boolean := False) return Entity_Id;
11900 -- Check whether a declarative region contains the incomplete or partial
11901 -- view of Id.
11903 -------------------
11904 -- Inspect_Decls --
11905 -------------------
11907 function Inspect_Decls
11908 (Decls : List_Id;
11909 Taft : Boolean := False) return Entity_Id
11911 Decl : Node_Id;
11912 Match : Node_Id;
11914 begin
11915 Decl := First (Decls);
11916 while Present (Decl) loop
11917 Match := Empty;
11919 -- The partial view of a Taft-amendment type is an incomplete
11920 -- type.
11922 if Taft then
11923 if Nkind (Decl) = N_Incomplete_Type_Declaration then
11924 Match := Defining_Identifier (Decl);
11925 end if;
11927 -- Otherwise look for a private type whose full view matches the
11928 -- input type. Note that this checks full_type_declaration nodes
11929 -- to account for derivations from a private type where the type
11930 -- declaration hold the partial view and the full view is an
11931 -- itype.
11933 elsif Nkind_In (Decl, N_Full_Type_Declaration,
11934 N_Private_Extension_Declaration,
11935 N_Private_Type_Declaration)
11936 then
11937 Match := Defining_Identifier (Decl);
11938 end if;
11940 -- Guard against unanalyzed entities
11942 if Present (Match)
11943 and then Is_Type (Match)
11944 and then Present (Full_View (Match))
11945 and then Full_View (Match) = Id
11946 then
11947 return Match;
11948 end if;
11950 Next (Decl);
11951 end loop;
11953 return Empty;
11954 end Inspect_Decls;
11956 -- Local variables
11958 Prev : Entity_Id;
11960 -- Start of processing for Incomplete_Or_Partial_View
11962 begin
11963 -- Deferred constant or incomplete type case
11965 Prev := Current_Entity_In_Scope (Id);
11967 if Present (Prev)
11968 and then (Is_Incomplete_Type (Prev) or else Ekind (Prev) = E_Constant)
11969 and then Present (Full_View (Prev))
11970 and then Full_View (Prev) = Id
11971 then
11972 return Prev;
11973 end if;
11975 -- Private or Taft amendment type case
11977 declare
11978 Pkg : constant Entity_Id := Scope (Id);
11979 Pkg_Decl : Node_Id := Pkg;
11981 begin
11982 if Present (Pkg)
11983 and then Ekind_In (Pkg, E_Generic_Package, E_Package)
11984 then
11985 while Nkind (Pkg_Decl) /= N_Package_Specification loop
11986 Pkg_Decl := Parent (Pkg_Decl);
11987 end loop;
11989 -- It is knows that Typ has a private view, look for it in the
11990 -- visible declarations of the enclosing scope. A special case
11991 -- of this is when the two views have been exchanged - the full
11992 -- appears earlier than the private.
11994 if Has_Private_Declaration (Id) then
11995 Prev := Inspect_Decls (Visible_Declarations (Pkg_Decl));
11997 -- Exchanged view case, look in the private declarations
11999 if No (Prev) then
12000 Prev := Inspect_Decls (Private_Declarations (Pkg_Decl));
12001 end if;
12003 return Prev;
12005 -- Otherwise if this is the package body, then Typ is a potential
12006 -- Taft amendment type. The incomplete view should be located in
12007 -- the private declarations of the enclosing scope.
12009 elsif In_Package_Body (Pkg) then
12010 return Inspect_Decls (Private_Declarations (Pkg_Decl), True);
12011 end if;
12012 end if;
12013 end;
12015 -- The type has no incomplete or private view
12017 return Empty;
12018 end Incomplete_Or_Partial_View;
12020 ---------------------------------------
12021 -- Incomplete_View_From_Limited_With --
12022 ---------------------------------------
12024 function Incomplete_View_From_Limited_With
12025 (Typ : Entity_Id) return Entity_Id
12027 begin
12028 -- It might make sense to make this an attribute in Einfo, and set it
12029 -- in Sem_Ch10 in Build_Shadow_Entity. However, we're running short on
12030 -- slots for new attributes, and it seems a bit simpler to just search
12031 -- the Limited_View (if it exists) for an incomplete type whose
12032 -- Non_Limited_View is Typ.
12034 if Ekind (Scope (Typ)) = E_Package
12035 and then Present (Limited_View (Scope (Typ)))
12036 then
12037 declare
12038 Ent : Entity_Id := First_Entity (Limited_View (Scope (Typ)));
12039 begin
12040 while Present (Ent) loop
12041 if Ekind (Ent) in Incomplete_Kind
12042 and then Non_Limited_View (Ent) = Typ
12043 then
12044 return Ent;
12045 end if;
12047 Ent := Next_Entity (Ent);
12048 end loop;
12049 end;
12050 end if;
12052 return Typ;
12053 end Incomplete_View_From_Limited_With;
12055 ----------------------------------
12056 -- Indexed_Component_Bit_Offset --
12057 ----------------------------------
12059 function Indexed_Component_Bit_Offset (N : Node_Id) return Uint is
12060 Exp : constant Node_Id := First (Expressions (N));
12061 Typ : constant Entity_Id := Etype (Prefix (N));
12062 Off : constant Uint := Component_Size (Typ);
12063 Ind : Node_Id;
12065 begin
12066 -- Return early if the component size is not known or variable
12068 if Off = No_Uint or else Off < Uint_0 then
12069 return No_Uint;
12070 end if;
12072 -- Deal with the degenerate case of an empty component
12074 if Off = Uint_0 then
12075 return Off;
12076 end if;
12078 -- Check that both the index value and the low bound are known
12080 if not Compile_Time_Known_Value (Exp) then
12081 return No_Uint;
12082 end if;
12084 Ind := First_Index (Typ);
12085 if No (Ind) then
12086 return No_Uint;
12087 end if;
12089 if Nkind (Ind) = N_Subtype_Indication then
12090 Ind := Constraint (Ind);
12092 if Nkind (Ind) = N_Range_Constraint then
12093 Ind := Range_Expression (Ind);
12094 end if;
12095 end if;
12097 if Nkind (Ind) /= N_Range
12098 or else not Compile_Time_Known_Value (Low_Bound (Ind))
12099 then
12100 return No_Uint;
12101 end if;
12103 -- Return the scaled offset
12105 return Off * (Expr_Value (Exp) - Expr_Value (Low_Bound ((Ind))));
12106 end Indexed_Component_Bit_Offset;
12108 ----------------------------
12109 -- Inherit_Rep_Item_Chain --
12110 ----------------------------
12112 procedure Inherit_Rep_Item_Chain (Typ : Entity_Id; From_Typ : Entity_Id) is
12113 Item : Node_Id;
12114 Next_Item : Node_Id;
12116 begin
12117 -- There are several inheritance scenarios to consider depending on
12118 -- whether both types have rep item chains and whether the destination
12119 -- type already inherits part of the source type's rep item chain.
12121 -- 1) The source type lacks a rep item chain
12122 -- From_Typ ---> Empty
12124 -- Typ --------> Item (or Empty)
12126 -- In this case inheritance cannot take place because there are no items
12127 -- to inherit.
12129 -- 2) The destination type lacks a rep item chain
12130 -- From_Typ ---> Item ---> ...
12132 -- Typ --------> Empty
12134 -- Inheritance takes place by setting the First_Rep_Item of the
12135 -- destination type to the First_Rep_Item of the source type.
12136 -- From_Typ ---> Item ---> ...
12137 -- ^
12138 -- Typ -----------+
12140 -- 3.1) Both source and destination types have at least one rep item.
12141 -- The destination type does NOT inherit a rep item from the source
12142 -- type.
12143 -- From_Typ ---> Item ---> Item
12145 -- Typ --------> Item ---> Item
12147 -- Inheritance takes place by setting the Next_Rep_Item of the last item
12148 -- of the destination type to the First_Rep_Item of the source type.
12149 -- From_Typ -------------------> Item ---> Item
12150 -- ^
12151 -- Typ --------> Item ---> Item --+
12153 -- 3.2) Both source and destination types have at least one rep item.
12154 -- The destination type DOES inherit part of the rep item chain of the
12155 -- source type.
12156 -- From_Typ ---> Item ---> Item ---> Item
12157 -- ^
12158 -- Typ --------> Item ------+
12160 -- This rare case arises when the full view of a private extension must
12161 -- inherit the rep item chain from the full view of its parent type and
12162 -- the full view of the parent type contains extra rep items. Currently
12163 -- only invariants may lead to such form of inheritance.
12165 -- type From_Typ is tagged private
12166 -- with Type_Invariant'Class => Item_2;
12168 -- type Typ is new From_Typ with private
12169 -- with Type_Invariant => Item_4;
12171 -- At this point the rep item chains contain the following items
12173 -- From_Typ -----------> Item_2 ---> Item_3
12174 -- ^
12175 -- Typ --------> Item_4 --+
12177 -- The full views of both types may introduce extra invariants
12179 -- type From_Typ is tagged null record
12180 -- with Type_Invariant => Item_1;
12182 -- type Typ is new From_Typ with null record;
12184 -- The full view of Typ would have to inherit any new rep items added to
12185 -- the full view of From_Typ.
12187 -- From_Typ -----------> Item_1 ---> Item_2 ---> Item_3
12188 -- ^
12189 -- Typ --------> Item_4 --+
12191 -- To achieve this form of inheritance, the destination type must first
12192 -- sever the link between its own rep chain and that of the source type,
12193 -- then inheritance 3.1 takes place.
12195 -- Case 1: The source type lacks a rep item chain
12197 if No (First_Rep_Item (From_Typ)) then
12198 return;
12200 -- Case 2: The destination type lacks a rep item chain
12202 elsif No (First_Rep_Item (Typ)) then
12203 Set_First_Rep_Item (Typ, First_Rep_Item (From_Typ));
12205 -- Case 3: Both the source and destination types have at least one rep
12206 -- item. Traverse the rep item chain of the destination type to find the
12207 -- last rep item.
12209 else
12210 Item := Empty;
12211 Next_Item := First_Rep_Item (Typ);
12212 while Present (Next_Item) loop
12214 -- Detect a link between the destination type's rep chain and that
12215 -- of the source type. There are two possibilities:
12217 -- Variant 1
12218 -- Next_Item
12219 -- V
12220 -- From_Typ ---> Item_1 --->
12221 -- ^
12222 -- Typ -----------+
12224 -- Item is Empty
12226 -- Variant 2
12227 -- Next_Item
12228 -- V
12229 -- From_Typ ---> Item_1 ---> Item_2 --->
12230 -- ^
12231 -- Typ --------> Item_3 ------+
12232 -- ^
12233 -- Item
12235 if Has_Rep_Item (From_Typ, Next_Item) then
12236 exit;
12237 end if;
12239 Item := Next_Item;
12240 Next_Item := Next_Rep_Item (Next_Item);
12241 end loop;
12243 -- Inherit the source type's rep item chain
12245 if Present (Item) then
12246 Set_Next_Rep_Item (Item, First_Rep_Item (From_Typ));
12247 else
12248 Set_First_Rep_Item (Typ, First_Rep_Item (From_Typ));
12249 end if;
12250 end if;
12251 end Inherit_Rep_Item_Chain;
12253 ---------------------------------
12254 -- Insert_Explicit_Dereference --
12255 ---------------------------------
12257 procedure Insert_Explicit_Dereference (N : Node_Id) is
12258 New_Prefix : constant Node_Id := Relocate_Node (N);
12259 Ent : Entity_Id := Empty;
12260 Pref : Node_Id;
12261 I : Interp_Index;
12262 It : Interp;
12263 T : Entity_Id;
12265 begin
12266 Save_Interps (N, New_Prefix);
12268 Rewrite (N,
12269 Make_Explicit_Dereference (Sloc (Parent (N)),
12270 Prefix => New_Prefix));
12272 Set_Etype (N, Designated_Type (Etype (New_Prefix)));
12274 if Is_Overloaded (New_Prefix) then
12276 -- The dereference is also overloaded, and its interpretations are
12277 -- the designated types of the interpretations of the original node.
12279 Set_Etype (N, Any_Type);
12281 Get_First_Interp (New_Prefix, I, It);
12282 while Present (It.Nam) loop
12283 T := It.Typ;
12285 if Is_Access_Type (T) then
12286 Add_One_Interp (N, Designated_Type (T), Designated_Type (T));
12287 end if;
12289 Get_Next_Interp (I, It);
12290 end loop;
12292 End_Interp_List;
12294 else
12295 -- Prefix is unambiguous: mark the original prefix (which might
12296 -- Come_From_Source) as a reference, since the new (relocated) one
12297 -- won't be taken into account.
12299 if Is_Entity_Name (New_Prefix) then
12300 Ent := Entity (New_Prefix);
12301 Pref := New_Prefix;
12303 -- For a retrieval of a subcomponent of some composite object,
12304 -- retrieve the ultimate entity if there is one.
12306 elsif Nkind_In (New_Prefix, N_Selected_Component,
12307 N_Indexed_Component)
12308 then
12309 Pref := Prefix (New_Prefix);
12310 while Present (Pref)
12311 and then Nkind_In (Pref, N_Selected_Component,
12312 N_Indexed_Component)
12313 loop
12314 Pref := Prefix (Pref);
12315 end loop;
12317 if Present (Pref) and then Is_Entity_Name (Pref) then
12318 Ent := Entity (Pref);
12319 end if;
12320 end if;
12322 -- Place the reference on the entity node
12324 if Present (Ent) then
12325 Generate_Reference (Ent, Pref);
12326 end if;
12327 end if;
12328 end Insert_Explicit_Dereference;
12330 ------------------------------------------
12331 -- Inspect_Deferred_Constant_Completion --
12332 ------------------------------------------
12334 procedure Inspect_Deferred_Constant_Completion (Decls : List_Id) is
12335 Decl : Node_Id;
12337 begin
12338 Decl := First (Decls);
12339 while Present (Decl) loop
12341 -- Deferred constant signature
12343 if Nkind (Decl) = N_Object_Declaration
12344 and then Constant_Present (Decl)
12345 and then No (Expression (Decl))
12347 -- No need to check internally generated constants
12349 and then Comes_From_Source (Decl)
12351 -- The constant is not completed. A full object declaration or a
12352 -- pragma Import complete a deferred constant.
12354 and then not Has_Completion (Defining_Identifier (Decl))
12355 then
12356 Error_Msg_N
12357 ("constant declaration requires initialization expression",
12358 Defining_Identifier (Decl));
12359 end if;
12361 Decl := Next (Decl);
12362 end loop;
12363 end Inspect_Deferred_Constant_Completion;
12365 -----------------------------
12366 -- Install_Generic_Formals --
12367 -----------------------------
12369 procedure Install_Generic_Formals (Subp_Id : Entity_Id) is
12370 E : Entity_Id;
12372 begin
12373 pragma Assert (Is_Generic_Subprogram (Subp_Id));
12375 E := First_Entity (Subp_Id);
12376 while Present (E) loop
12377 Install_Entity (E);
12378 Next_Entity (E);
12379 end loop;
12380 end Install_Generic_Formals;
12382 ------------------------
12383 -- Install_SPARK_Mode --
12384 ------------------------
12386 procedure Install_SPARK_Mode (Mode : SPARK_Mode_Type; Prag : Node_Id) is
12387 begin
12388 SPARK_Mode := Mode;
12389 SPARK_Mode_Pragma := Prag;
12390 end Install_SPARK_Mode;
12392 -----------------------------
12393 -- Is_Actual_Out_Parameter --
12394 -----------------------------
12396 function Is_Actual_Out_Parameter (N : Node_Id) return Boolean is
12397 Formal : Entity_Id;
12398 Call : Node_Id;
12399 begin
12400 Find_Actual (N, Formal, Call);
12401 return Present (Formal) and then Ekind (Formal) = E_Out_Parameter;
12402 end Is_Actual_Out_Parameter;
12404 -------------------------
12405 -- Is_Actual_Parameter --
12406 -------------------------
12408 function Is_Actual_Parameter (N : Node_Id) return Boolean is
12409 PK : constant Node_Kind := Nkind (Parent (N));
12411 begin
12412 case PK is
12413 when N_Parameter_Association =>
12414 return N = Explicit_Actual_Parameter (Parent (N));
12416 when N_Subprogram_Call =>
12417 return Is_List_Member (N)
12418 and then
12419 List_Containing (N) = Parameter_Associations (Parent (N));
12421 when others =>
12422 return False;
12423 end case;
12424 end Is_Actual_Parameter;
12426 --------------------------------
12427 -- Is_Actual_Tagged_Parameter --
12428 --------------------------------
12430 function Is_Actual_Tagged_Parameter (N : Node_Id) return Boolean is
12431 Formal : Entity_Id;
12432 Call : Node_Id;
12433 begin
12434 Find_Actual (N, Formal, Call);
12435 return Present (Formal) and then Is_Tagged_Type (Etype (Formal));
12436 end Is_Actual_Tagged_Parameter;
12438 ---------------------
12439 -- Is_Aliased_View --
12440 ---------------------
12442 function Is_Aliased_View (Obj : Node_Id) return Boolean is
12443 E : Entity_Id;
12445 begin
12446 if Is_Entity_Name (Obj) then
12447 E := Entity (Obj);
12449 return
12450 (Is_Object (E)
12451 and then
12452 (Is_Aliased (E)
12453 or else (Present (Renamed_Object (E))
12454 and then Is_Aliased_View (Renamed_Object (E)))))
12456 or else ((Is_Formal (E) or else Is_Formal_Object (E))
12457 and then Is_Tagged_Type (Etype (E)))
12459 or else (Is_Concurrent_Type (E) and then In_Open_Scopes (E))
12461 -- Current instance of type, either directly or as rewritten
12462 -- reference to the current object.
12464 or else (Is_Entity_Name (Original_Node (Obj))
12465 and then Present (Entity (Original_Node (Obj)))
12466 and then Is_Type (Entity (Original_Node (Obj))))
12468 or else (Is_Type (E) and then E = Current_Scope)
12470 or else (Is_Incomplete_Or_Private_Type (E)
12471 and then Full_View (E) = Current_Scope)
12473 -- Ada 2012 AI05-0053: the return object of an extended return
12474 -- statement is aliased if its type is immutably limited.
12476 or else (Is_Return_Object (E)
12477 and then Is_Limited_View (Etype (E)));
12479 elsif Nkind (Obj) = N_Selected_Component then
12480 return Is_Aliased (Entity (Selector_Name (Obj)));
12482 elsif Nkind (Obj) = N_Indexed_Component then
12483 return Has_Aliased_Components (Etype (Prefix (Obj)))
12484 or else
12485 (Is_Access_Type (Etype (Prefix (Obj)))
12486 and then Has_Aliased_Components
12487 (Designated_Type (Etype (Prefix (Obj)))));
12489 elsif Nkind_In (Obj, N_Unchecked_Type_Conversion, N_Type_Conversion) then
12490 return Is_Tagged_Type (Etype (Obj))
12491 and then Is_Aliased_View (Expression (Obj));
12493 elsif Nkind (Obj) = N_Explicit_Dereference then
12494 return Nkind (Original_Node (Obj)) /= N_Function_Call;
12496 else
12497 return False;
12498 end if;
12499 end Is_Aliased_View;
12501 -------------------------
12502 -- Is_Ancestor_Package --
12503 -------------------------
12505 function Is_Ancestor_Package
12506 (E1 : Entity_Id;
12507 E2 : Entity_Id) return Boolean
12509 Par : Entity_Id;
12511 begin
12512 Par := E2;
12513 while Present (Par) and then Par /= Standard_Standard loop
12514 if Par = E1 then
12515 return True;
12516 end if;
12518 Par := Scope (Par);
12519 end loop;
12521 return False;
12522 end Is_Ancestor_Package;
12524 ----------------------
12525 -- Is_Atomic_Object --
12526 ----------------------
12528 function Is_Atomic_Object (N : Node_Id) return Boolean is
12530 function Object_Has_Atomic_Components (N : Node_Id) return Boolean;
12531 -- Determines if given object has atomic components
12533 function Is_Atomic_Prefix (N : Node_Id) return Boolean;
12534 -- If prefix is an implicit dereference, examine designated type
12536 ----------------------
12537 -- Is_Atomic_Prefix --
12538 ----------------------
12540 function Is_Atomic_Prefix (N : Node_Id) return Boolean is
12541 begin
12542 if Is_Access_Type (Etype (N)) then
12543 return
12544 Has_Atomic_Components (Designated_Type (Etype (N)));
12545 else
12546 return Object_Has_Atomic_Components (N);
12547 end if;
12548 end Is_Atomic_Prefix;
12550 ----------------------------------
12551 -- Object_Has_Atomic_Components --
12552 ----------------------------------
12554 function Object_Has_Atomic_Components (N : Node_Id) return Boolean is
12555 begin
12556 if Has_Atomic_Components (Etype (N))
12557 or else Is_Atomic (Etype (N))
12558 then
12559 return True;
12561 elsif Is_Entity_Name (N)
12562 and then (Has_Atomic_Components (Entity (N))
12563 or else Is_Atomic (Entity (N)))
12564 then
12565 return True;
12567 elsif Nkind (N) = N_Selected_Component
12568 and then Is_Atomic (Entity (Selector_Name (N)))
12569 then
12570 return True;
12572 elsif Nkind (N) = N_Indexed_Component
12573 or else Nkind (N) = N_Selected_Component
12574 then
12575 return Is_Atomic_Prefix (Prefix (N));
12577 else
12578 return False;
12579 end if;
12580 end Object_Has_Atomic_Components;
12582 -- Start of processing for Is_Atomic_Object
12584 begin
12585 -- Predicate is not relevant to subprograms
12587 if Is_Entity_Name (N) and then Is_Overloadable (Entity (N)) then
12588 return False;
12590 elsif Is_Atomic (Etype (N))
12591 or else (Is_Entity_Name (N) and then Is_Atomic (Entity (N)))
12592 then
12593 return True;
12595 elsif Nkind (N) = N_Selected_Component
12596 and then Is_Atomic (Entity (Selector_Name (N)))
12597 then
12598 return True;
12600 elsif Nkind (N) = N_Indexed_Component
12601 or else Nkind (N) = N_Selected_Component
12602 then
12603 return Is_Atomic_Prefix (Prefix (N));
12605 else
12606 return False;
12607 end if;
12608 end Is_Atomic_Object;
12610 -----------------------------
12611 -- Is_Atomic_Or_VFA_Object --
12612 -----------------------------
12614 function Is_Atomic_Or_VFA_Object (N : Node_Id) return Boolean is
12615 begin
12616 return Is_Atomic_Object (N)
12617 or else (Is_Object_Reference (N)
12618 and then Is_Entity_Name (N)
12619 and then (Is_Volatile_Full_Access (Entity (N))
12620 or else
12621 Is_Volatile_Full_Access (Etype (Entity (N)))));
12622 end Is_Atomic_Or_VFA_Object;
12624 -------------------------
12625 -- Is_Attribute_Result --
12626 -------------------------
12628 function Is_Attribute_Result (N : Node_Id) return Boolean is
12629 begin
12630 return Nkind (N) = N_Attribute_Reference
12631 and then Attribute_Name (N) = Name_Result;
12632 end Is_Attribute_Result;
12634 -------------------------
12635 -- Is_Attribute_Update --
12636 -------------------------
12638 function Is_Attribute_Update (N : Node_Id) return Boolean is
12639 begin
12640 return Nkind (N) = N_Attribute_Reference
12641 and then Attribute_Name (N) = Name_Update;
12642 end Is_Attribute_Update;
12644 ------------------------------------
12645 -- Is_Body_Or_Package_Declaration --
12646 ------------------------------------
12648 function Is_Body_Or_Package_Declaration (N : Node_Id) return Boolean is
12649 begin
12650 return Nkind_In (N, N_Entry_Body,
12651 N_Package_Body,
12652 N_Package_Declaration,
12653 N_Protected_Body,
12654 N_Subprogram_Body,
12655 N_Task_Body);
12656 end Is_Body_Or_Package_Declaration;
12658 -----------------------
12659 -- Is_Bounded_String --
12660 -----------------------
12662 function Is_Bounded_String (T : Entity_Id) return Boolean is
12663 Under : constant Entity_Id := Underlying_Type (Root_Type (T));
12665 begin
12666 -- Check whether T is ultimately derived from Ada.Strings.Superbounded.
12667 -- Super_String, or one of the [Wide_]Wide_ versions. This will
12668 -- be True for all the Bounded_String types in instances of the
12669 -- Generic_Bounded_Length generics, and for types derived from those.
12671 return Present (Under)
12672 and then (Is_RTE (Root_Type (Under), RO_SU_Super_String) or else
12673 Is_RTE (Root_Type (Under), RO_WI_Super_String) or else
12674 Is_RTE (Root_Type (Under), RO_WW_Super_String));
12675 end Is_Bounded_String;
12677 ---------------------
12678 -- Is_CCT_Instance --
12679 ---------------------
12681 function Is_CCT_Instance
12682 (Ref_Id : Entity_Id;
12683 Context_Id : Entity_Id) return Boolean
12685 begin
12686 pragma Assert (Ekind_In (Ref_Id, E_Protected_Type, E_Task_Type));
12688 if Is_Single_Task_Object (Context_Id) then
12689 return Scope_Within_Or_Same (Etype (Context_Id), Ref_Id);
12691 else
12692 pragma Assert (Ekind_In (Context_Id, E_Entry,
12693 E_Entry_Family,
12694 E_Function,
12695 E_Package,
12696 E_Procedure,
12697 E_Protected_Type,
12698 E_Task_Type)
12699 or else
12700 Is_Record_Type (Context_Id));
12701 return Scope_Within_Or_Same (Context_Id, Ref_Id);
12702 end if;
12703 end Is_CCT_Instance;
12705 -------------------------
12706 -- Is_Child_Or_Sibling --
12707 -------------------------
12709 function Is_Child_Or_Sibling
12710 (Pack_1 : Entity_Id;
12711 Pack_2 : Entity_Id) return Boolean
12713 function Distance_From_Standard (Pack : Entity_Id) return Nat;
12714 -- Given an arbitrary package, return the number of "climbs" necessary
12715 -- to reach scope Standard_Standard.
12717 procedure Equalize_Depths
12718 (Pack : in out Entity_Id;
12719 Depth : in out Nat;
12720 Depth_To_Reach : Nat);
12721 -- Given an arbitrary package, its depth and a target depth to reach,
12722 -- climb the scope chain until the said depth is reached. The pointer
12723 -- to the package and its depth a modified during the climb.
12725 ----------------------------
12726 -- Distance_From_Standard --
12727 ----------------------------
12729 function Distance_From_Standard (Pack : Entity_Id) return Nat is
12730 Dist : Nat;
12731 Scop : Entity_Id;
12733 begin
12734 Dist := 0;
12735 Scop := Pack;
12736 while Present (Scop) and then Scop /= Standard_Standard loop
12737 Dist := Dist + 1;
12738 Scop := Scope (Scop);
12739 end loop;
12741 return Dist;
12742 end Distance_From_Standard;
12744 ---------------------
12745 -- Equalize_Depths --
12746 ---------------------
12748 procedure Equalize_Depths
12749 (Pack : in out Entity_Id;
12750 Depth : in out Nat;
12751 Depth_To_Reach : Nat)
12753 begin
12754 -- The package must be at a greater or equal depth
12756 if Depth < Depth_To_Reach then
12757 raise Program_Error;
12758 end if;
12760 -- Climb the scope chain until the desired depth is reached
12762 while Present (Pack) and then Depth /= Depth_To_Reach loop
12763 Pack := Scope (Pack);
12764 Depth := Depth - 1;
12765 end loop;
12766 end Equalize_Depths;
12768 -- Local variables
12770 P_1 : Entity_Id := Pack_1;
12771 P_1_Child : Boolean := False;
12772 P_1_Depth : Nat := Distance_From_Standard (P_1);
12773 P_2 : Entity_Id := Pack_2;
12774 P_2_Child : Boolean := False;
12775 P_2_Depth : Nat := Distance_From_Standard (P_2);
12777 -- Start of processing for Is_Child_Or_Sibling
12779 begin
12780 pragma Assert
12781 (Ekind (Pack_1) = E_Package and then Ekind (Pack_2) = E_Package);
12783 -- Both packages denote the same entity, therefore they cannot be
12784 -- children or siblings.
12786 if P_1 = P_2 then
12787 return False;
12789 -- One of the packages is at a deeper level than the other. Note that
12790 -- both may still come from different hierarchies.
12792 -- (root) P_2
12793 -- / \ :
12794 -- X P_2 or X
12795 -- : :
12796 -- P_1 P_1
12798 elsif P_1_Depth > P_2_Depth then
12799 Equalize_Depths
12800 (Pack => P_1,
12801 Depth => P_1_Depth,
12802 Depth_To_Reach => P_2_Depth);
12803 P_1_Child := True;
12805 -- (root) P_1
12806 -- / \ :
12807 -- P_1 X or X
12808 -- : :
12809 -- P_2 P_2
12811 elsif P_2_Depth > P_1_Depth then
12812 Equalize_Depths
12813 (Pack => P_2,
12814 Depth => P_2_Depth,
12815 Depth_To_Reach => P_1_Depth);
12816 P_2_Child := True;
12817 end if;
12819 -- At this stage the package pointers have been elevated to the same
12820 -- depth. If the related entities are the same, then one package is a
12821 -- potential child of the other:
12823 -- P_1
12824 -- :
12825 -- X became P_1 P_2 or vice versa
12826 -- :
12827 -- P_2
12829 if P_1 = P_2 then
12830 if P_1_Child then
12831 return Is_Child_Unit (Pack_1);
12833 else pragma Assert (P_2_Child);
12834 return Is_Child_Unit (Pack_2);
12835 end if;
12837 -- The packages may come from the same package chain or from entirely
12838 -- different hierarcies. To determine this, climb the scope stack until
12839 -- a common root is found.
12841 -- (root) (root 1) (root 2)
12842 -- / \ | |
12843 -- P_1 P_2 P_1 P_2
12845 else
12846 while Present (P_1) and then Present (P_2) loop
12848 -- The two packages may be siblings
12850 if P_1 = P_2 then
12851 return Is_Child_Unit (Pack_1) and then Is_Child_Unit (Pack_2);
12852 end if;
12854 P_1 := Scope (P_1);
12855 P_2 := Scope (P_2);
12856 end loop;
12857 end if;
12859 return False;
12860 end Is_Child_Or_Sibling;
12862 -----------------------------
12863 -- Is_Concurrent_Interface --
12864 -----------------------------
12866 function Is_Concurrent_Interface (T : Entity_Id) return Boolean is
12867 begin
12868 return Is_Interface (T)
12869 and then
12870 (Is_Protected_Interface (T)
12871 or else Is_Synchronized_Interface (T)
12872 or else Is_Task_Interface (T));
12873 end Is_Concurrent_Interface;
12875 -----------------------
12876 -- Is_Constant_Bound --
12877 -----------------------
12879 function Is_Constant_Bound (Exp : Node_Id) return Boolean is
12880 begin
12881 if Compile_Time_Known_Value (Exp) then
12882 return True;
12884 elsif Is_Entity_Name (Exp) and then Present (Entity (Exp)) then
12885 return Is_Constant_Object (Entity (Exp))
12886 or else Ekind (Entity (Exp)) = E_Enumeration_Literal;
12888 elsif Nkind (Exp) in N_Binary_Op then
12889 return Is_Constant_Bound (Left_Opnd (Exp))
12890 and then Is_Constant_Bound (Right_Opnd (Exp))
12891 and then Scope (Entity (Exp)) = Standard_Standard;
12893 else
12894 return False;
12895 end if;
12896 end Is_Constant_Bound;
12898 ---------------------------
12899 -- Is_Container_Element --
12900 ---------------------------
12902 function Is_Container_Element (Exp : Node_Id) return Boolean is
12903 Loc : constant Source_Ptr := Sloc (Exp);
12904 Pref : constant Node_Id := Prefix (Exp);
12906 Call : Node_Id;
12907 -- Call to an indexing aspect
12909 Cont_Typ : Entity_Id;
12910 -- The type of the container being accessed
12912 Elem_Typ : Entity_Id;
12913 -- Its element type
12915 Indexing : Entity_Id;
12916 Is_Const : Boolean;
12917 -- Indicates that constant indexing is used, and the element is thus
12918 -- a constant.
12920 Ref_Typ : Entity_Id;
12921 -- The reference type returned by the indexing operation
12923 begin
12924 -- If C is a container, in a context that imposes the element type of
12925 -- that container, the indexing notation C (X) is rewritten as:
12927 -- Indexing (C, X).Discr.all
12929 -- where Indexing is one of the indexing aspects of the container.
12930 -- If the context does not require a reference, the construct can be
12931 -- rewritten as
12933 -- Element (C, X)
12935 -- First, verify that the construct has the proper form
12937 if not Expander_Active then
12938 return False;
12940 elsif Nkind (Pref) /= N_Selected_Component then
12941 return False;
12943 elsif Nkind (Prefix (Pref)) /= N_Function_Call then
12944 return False;
12946 else
12947 Call := Prefix (Pref);
12948 Ref_Typ := Etype (Call);
12949 end if;
12951 if not Has_Implicit_Dereference (Ref_Typ)
12952 or else No (First (Parameter_Associations (Call)))
12953 or else not Is_Entity_Name (Name (Call))
12954 then
12955 return False;
12956 end if;
12958 -- Retrieve type of container object, and its iterator aspects
12960 Cont_Typ := Etype (First (Parameter_Associations (Call)));
12961 Indexing := Find_Value_Of_Aspect (Cont_Typ, Aspect_Constant_Indexing);
12962 Is_Const := False;
12964 if No (Indexing) then
12966 -- Container should have at least one indexing operation
12968 return False;
12970 elsif Entity (Name (Call)) /= Entity (Indexing) then
12972 -- This may be a variable indexing operation
12974 Indexing := Find_Value_Of_Aspect (Cont_Typ, Aspect_Variable_Indexing);
12976 if No (Indexing)
12977 or else Entity (Name (Call)) /= Entity (Indexing)
12978 then
12979 return False;
12980 end if;
12982 else
12983 Is_Const := True;
12984 end if;
12986 Elem_Typ := Find_Value_Of_Aspect (Cont_Typ, Aspect_Iterator_Element);
12988 if No (Elem_Typ) or else Entity (Elem_Typ) /= Etype (Exp) then
12989 return False;
12990 end if;
12992 -- Check that the expression is not the target of an assignment, in
12993 -- which case the rewriting is not possible.
12995 if not Is_Const then
12996 declare
12997 Par : Node_Id;
12999 begin
13000 Par := Exp;
13001 while Present (Par)
13002 loop
13003 if Nkind (Parent (Par)) = N_Assignment_Statement
13004 and then Par = Name (Parent (Par))
13005 then
13006 return False;
13008 -- A renaming produces a reference, and the transformation
13009 -- does not apply.
13011 elsif Nkind (Parent (Par)) = N_Object_Renaming_Declaration then
13012 return False;
13014 elsif Nkind_In
13015 (Nkind (Parent (Par)), N_Function_Call,
13016 N_Procedure_Call_Statement,
13017 N_Entry_Call_Statement)
13018 then
13019 -- Check that the element is not part of an actual for an
13020 -- in-out parameter.
13022 declare
13023 F : Entity_Id;
13024 A : Node_Id;
13026 begin
13027 F := First_Formal (Entity (Name (Parent (Par))));
13028 A := First (Parameter_Associations (Parent (Par)));
13029 while Present (F) loop
13030 if A = Par and then Ekind (F) /= E_In_Parameter then
13031 return False;
13032 end if;
13034 Next_Formal (F);
13035 Next (A);
13036 end loop;
13037 end;
13039 -- E_In_Parameter in a call: element is not modified.
13041 exit;
13042 end if;
13044 Par := Parent (Par);
13045 end loop;
13046 end;
13047 end if;
13049 -- The expression has the proper form and the context requires the
13050 -- element type. Retrieve the Element function of the container and
13051 -- rewrite the construct as a call to it.
13053 declare
13054 Op : Elmt_Id;
13056 begin
13057 Op := First_Elmt (Primitive_Operations (Cont_Typ));
13058 while Present (Op) loop
13059 exit when Chars (Node (Op)) = Name_Element;
13060 Next_Elmt (Op);
13061 end loop;
13063 if No (Op) then
13064 return False;
13066 else
13067 Rewrite (Exp,
13068 Make_Function_Call (Loc,
13069 Name => New_Occurrence_Of (Node (Op), Loc),
13070 Parameter_Associations => Parameter_Associations (Call)));
13071 Analyze_And_Resolve (Exp, Entity (Elem_Typ));
13072 return True;
13073 end if;
13074 end;
13075 end Is_Container_Element;
13077 ----------------------------
13078 -- Is_Contract_Annotation --
13079 ----------------------------
13081 function Is_Contract_Annotation (Item : Node_Id) return Boolean is
13082 begin
13083 return Is_Package_Contract_Annotation (Item)
13084 or else
13085 Is_Subprogram_Contract_Annotation (Item);
13086 end Is_Contract_Annotation;
13088 --------------------------------------
13089 -- Is_Controlling_Limited_Procedure --
13090 --------------------------------------
13092 function Is_Controlling_Limited_Procedure
13093 (Proc_Nam : Entity_Id) return Boolean
13095 Param : Node_Id;
13096 Param_Typ : Entity_Id := Empty;
13098 begin
13099 if Ekind (Proc_Nam) = E_Procedure
13100 and then Present (Parameter_Specifications (Parent (Proc_Nam)))
13101 then
13102 Param :=
13103 Parameter_Type
13104 (First (Parameter_Specifications (Parent (Proc_Nam))));
13106 -- The formal may be an anonymous access type
13108 if Nkind (Param) = N_Access_Definition then
13109 Param_Typ := Entity (Subtype_Mark (Param));
13110 else
13111 Param_Typ := Etype (Param);
13112 end if;
13114 -- In the case where an Itype was created for a dispatchin call, the
13115 -- procedure call has been rewritten. The actual may be an access to
13116 -- interface type in which case it is the designated type that is the
13117 -- controlling type.
13119 elsif Present (Associated_Node_For_Itype (Proc_Nam))
13120 and then Present (Original_Node (Associated_Node_For_Itype (Proc_Nam)))
13121 and then
13122 Present (Parameter_Associations
13123 (Associated_Node_For_Itype (Proc_Nam)))
13124 then
13125 Param_Typ :=
13126 Etype (First (Parameter_Associations
13127 (Associated_Node_For_Itype (Proc_Nam))));
13129 if Ekind (Param_Typ) = E_Anonymous_Access_Type then
13130 Param_Typ := Directly_Designated_Type (Param_Typ);
13131 end if;
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_Non_Preelaborable_Construct --
14445 ------------------------------------
14447 function Is_Non_Preelaborable_Construct (N : Node_Id) return Boolean is
14449 -- NOTE: the routines within Is_Non_Preelaborable_Construct are
14450 -- intentionally unnested to avoid deep indentation of code.
14452 Non_Preelaborable : exception;
14453 -- This exception is raised when the construct violates preelaborability
14454 -- to terminate the recursion.
14456 procedure Visit (Nod : Node_Id);
14457 -- Semantically inspect construct Nod to determine whether it violates
14458 -- preelaborability. This routine raises Non_Preelaborable.
14460 procedure Visit_List (List : List_Id);
14461 pragma Inline (Visit_List);
14462 -- Invoke Visit on each element of list List. This routine raises
14463 -- Non_Preelaborable.
14465 procedure Visit_Pragma (Prag : Node_Id);
14466 pragma Inline (Visit_Pragma);
14467 -- Semantically inspect pragma Prag to determine whether it violates
14468 -- preelaborability. This routine raises Non_Preelaborable.
14470 procedure Visit_Subexpression (Expr : Node_Id);
14471 pragma Inline (Visit_Subexpression);
14472 -- Semantically inspect expression Expr to determine whether it violates
14473 -- preelaborability. This routine raises Non_Preelaborable.
14475 -----------
14476 -- Visit --
14477 -----------
14479 procedure Visit (Nod : Node_Id) is
14480 begin
14481 case Nkind (Nod) is
14483 -- Declarations
14485 when N_Component_Declaration =>
14487 -- Defining_Identifier is left out because it is not relevant
14488 -- for preelaborability.
14490 Visit (Component_Definition (Nod));
14491 Visit (Expression (Nod));
14493 when N_Derived_Type_Definition =>
14495 -- Interface_List is left out because it is not relevant for
14496 -- preelaborability.
14498 Visit (Record_Extension_Part (Nod));
14499 Visit (Subtype_Indication (Nod));
14501 when N_Entry_Declaration =>
14503 -- A protected type with at leat one entry is not preelaborable
14504 -- while task types are never preelaborable. This renders entry
14505 -- declarations non-preelaborable.
14507 raise Non_Preelaborable;
14509 when N_Full_Type_Declaration =>
14511 -- Defining_Identifier and Discriminant_Specifications are left
14512 -- out because they are not relevant for preelaborability.
14514 Visit (Type_Definition (Nod));
14516 when N_Function_Instantiation
14517 | N_Package_Instantiation
14518 | N_Procedure_Instantiation
14520 -- Defining_Unit_Name and Name are left out because they are
14521 -- not relevant for preelaborability.
14523 Visit_List (Generic_Associations (Nod));
14525 when N_Object_Declaration =>
14527 -- Defining_Identifier is left out because it is not relevant
14528 -- for preelaborability.
14530 Visit (Object_Definition (Nod));
14532 if Has_Init_Expression (Nod) then
14533 Visit (Expression (Nod));
14535 elsif not Has_Preelaborable_Initialization
14536 (Etype (Defining_Entity (Nod)))
14537 then
14538 raise Non_Preelaborable;
14539 end if;
14541 when N_Private_Extension_Declaration
14542 | N_Subtype_Declaration
14544 -- Defining_Identifier, Discriminant_Specifications, and
14545 -- Interface_List are left out because they are not relevant
14546 -- for preelaborability.
14548 Visit (Subtype_Indication (Nod));
14550 when N_Protected_Type_Declaration
14551 | N_Single_Protected_Declaration
14553 -- Defining_Identifier, Discriminant_Specifications, and
14554 -- Interface_List are left out because they are not relevant
14555 -- for preelaborability.
14557 Visit (Protected_Definition (Nod));
14559 -- A [single] task type is never preelaborable
14561 when N_Single_Task_Declaration
14562 | N_Task_Type_Declaration
14564 raise Non_Preelaborable;
14566 -- Pragmas
14568 when N_Pragma =>
14569 Visit_Pragma (Nod);
14571 -- Statements
14573 when N_Statement_Other_Than_Procedure_Call =>
14574 if Nkind (Nod) /= N_Null_Statement then
14575 raise Non_Preelaborable;
14576 end if;
14578 -- Subexpressions
14580 when N_Subexpr =>
14581 Visit_Subexpression (Nod);
14583 -- Special
14585 when N_Access_To_Object_Definition =>
14586 Visit (Subtype_Indication (Nod));
14588 when N_Case_Expression_Alternative =>
14589 Visit (Expression (Nod));
14590 Visit_List (Discrete_Choices (Nod));
14592 when N_Component_Definition =>
14593 Visit (Access_Definition (Nod));
14594 Visit (Subtype_Indication (Nod));
14596 when N_Component_List =>
14597 Visit_List (Component_Items (Nod));
14598 Visit (Variant_Part (Nod));
14600 when N_Constrained_Array_Definition =>
14601 Visit_List (Discrete_Subtype_Definitions (Nod));
14602 Visit (Component_Definition (Nod));
14604 when N_Delta_Constraint
14605 | N_Digits_Constraint
14607 -- Delta_Expression and Digits_Expression are left out because
14608 -- they are not relevant for preelaborability.
14610 Visit (Range_Constraint (Nod));
14612 when N_Discriminant_Specification =>
14614 -- Defining_Identifier and Expression are left out because they
14615 -- are not relevant for preelaborability.
14617 Visit (Discriminant_Type (Nod));
14619 when N_Generic_Association =>
14621 -- Selector_Name is left out because it is not relevant for
14622 -- preelaborability.
14624 Visit (Explicit_Generic_Actual_Parameter (Nod));
14626 when N_Index_Or_Discriminant_Constraint =>
14627 Visit_List (Constraints (Nod));
14629 when N_Iterator_Specification =>
14631 -- Defining_Identifier is left out because it is not relevant
14632 -- for preelaborability.
14634 Visit (Name (Nod));
14635 Visit (Subtype_Indication (Nod));
14637 when N_Loop_Parameter_Specification =>
14639 -- Defining_Identifier is left out because it is not relevant
14640 -- for preelaborability.
14642 Visit (Discrete_Subtype_Definition (Nod));
14644 when N_Protected_Definition =>
14646 -- End_Label is left out because it is not relevant for
14647 -- preelaborability.
14649 Visit_List (Private_Declarations (Nod));
14650 Visit_List (Visible_Declarations (Nod));
14652 when N_Range_Constraint =>
14653 Visit (Range_Expression (Nod));
14655 when N_Record_Definition
14656 | N_Variant
14658 -- End_Label, Discrete_Choices, and Interface_List are left out
14659 -- because they are not relevant for preelaborability.
14661 Visit (Component_List (Nod));
14663 when N_Subtype_Indication =>
14665 -- Subtype_Mark is left out because it is not relevant for
14666 -- preelaborability.
14668 Visit (Constraint (Nod));
14670 when N_Unconstrained_Array_Definition =>
14672 -- Subtype_Marks is left out because it is not relevant for
14673 -- preelaborability.
14675 Visit (Component_Definition (Nod));
14677 when N_Variant_Part =>
14679 -- Name is left out because it is not relevant for
14680 -- preelaborability.
14682 Visit_List (Variants (Nod));
14684 -- Default
14686 when others =>
14687 null;
14688 end case;
14689 end Visit;
14691 ----------------
14692 -- Visit_List --
14693 ----------------
14695 procedure Visit_List (List : List_Id) is
14696 Nod : Node_Id;
14698 begin
14699 if Present (List) then
14700 Nod := First (List);
14701 while Present (Nod) loop
14702 Visit (Nod);
14703 Next (Nod);
14704 end loop;
14705 end if;
14706 end Visit_List;
14708 ------------------
14709 -- Visit_Pragma --
14710 ------------------
14712 procedure Visit_Pragma (Prag : Node_Id) is
14713 begin
14714 case Get_Pragma_Id (Prag) is
14715 when Pragma_Assert
14716 | Pragma_Assert_And_Cut
14717 | Pragma_Assume
14718 | Pragma_Async_Readers
14719 | Pragma_Async_Writers
14720 | Pragma_Attribute_Definition
14721 | Pragma_Check
14722 | Pragma_Constant_After_Elaboration
14723 | Pragma_CPU
14724 | Pragma_Deadline_Floor
14725 | Pragma_Dispatching_Domain
14726 | Pragma_Effective_Reads
14727 | Pragma_Effective_Writes
14728 | Pragma_Extensions_Visible
14729 | Pragma_Ghost
14730 | Pragma_Secondary_Stack_Size
14731 | Pragma_Task_Name
14732 | Pragma_Volatile_Function
14734 Visit_List (Pragma_Argument_Associations (Prag));
14736 -- Default
14738 when others =>
14739 null;
14740 end case;
14741 end Visit_Pragma;
14743 -------------------------
14744 -- Visit_Subexpression --
14745 -------------------------
14747 procedure Visit_Subexpression (Expr : Node_Id) is
14748 procedure Visit_Aggregate (Aggr : Node_Id);
14749 pragma Inline (Visit_Aggregate);
14750 -- Semantically inspect aggregate Aggr to determine whether it
14751 -- violates preelaborability.
14753 ---------------------
14754 -- Visit_Aggregate --
14755 ---------------------
14757 procedure Visit_Aggregate (Aggr : Node_Id) is
14758 begin
14759 if not Is_Preelaborable_Aggregate (Aggr) then
14760 raise Non_Preelaborable;
14761 end if;
14762 end Visit_Aggregate;
14764 -- Start of processing for Visit_Subexpression
14766 begin
14767 case Nkind (Expr) is
14768 when N_Allocator
14769 | N_Qualified_Expression
14770 | N_Type_Conversion
14771 | N_Unchecked_Expression
14772 | N_Unchecked_Type_Conversion
14774 -- Subpool_Handle_Name and Subtype_Mark are left out because
14775 -- they are not relevant for preelaborability.
14777 Visit (Expression (Expr));
14779 when N_Aggregate
14780 | N_Extension_Aggregate
14782 Visit_Aggregate (Expr);
14784 when N_Attribute_Reference
14785 | N_Explicit_Dereference
14786 | N_Reference
14788 -- Attribute_Name and Expressions are left out because they are
14789 -- not relevant for preelaborability.
14791 Visit (Prefix (Expr));
14793 when N_Case_Expression =>
14795 -- End_Span is left out because it is not relevant for
14796 -- preelaborability.
14798 Visit_List (Alternatives (Expr));
14799 Visit (Expression (Expr));
14801 when N_Delta_Aggregate =>
14802 Visit_Aggregate (Expr);
14803 Visit (Expression (Expr));
14805 when N_Expression_With_Actions =>
14806 Visit_List (Actions (Expr));
14807 Visit (Expression (Expr));
14809 when N_If_Expression =>
14810 Visit_List (Expressions (Expr));
14812 when N_Quantified_Expression =>
14813 Visit (Condition (Expr));
14814 Visit (Iterator_Specification (Expr));
14815 Visit (Loop_Parameter_Specification (Expr));
14817 when N_Range =>
14818 Visit (High_Bound (Expr));
14819 Visit (Low_Bound (Expr));
14821 when N_Slice =>
14822 Visit (Discrete_Range (Expr));
14823 Visit (Prefix (Expr));
14825 -- Default
14827 when others =>
14829 -- The evaluation of an object name is not preelaborable,
14830 -- unless the name is a static expression (checked further
14831 -- below), or statically denotes a discriminant.
14833 if Is_Entity_Name (Expr) then
14834 Object_Name : declare
14835 Id : constant Entity_Id := Entity (Expr);
14837 begin
14838 if Is_Object (Id) then
14839 if Ekind (Id) = E_Discriminant then
14840 null;
14842 elsif Ekind_In (Id, E_Constant, E_In_Parameter)
14843 and then Present (Discriminal_Link (Id))
14844 then
14845 null;
14847 else
14848 raise Non_Preelaborable;
14849 end if;
14850 end if;
14851 end Object_Name;
14853 -- A non-static expression is not preelaborable
14855 elsif not Is_OK_Static_Expression (Expr) then
14856 raise Non_Preelaborable;
14857 end if;
14858 end case;
14859 end Visit_Subexpression;
14861 -- Start of processing for Is_Non_Preelaborable_Construct
14863 begin
14864 Visit (N);
14866 -- At this point it is known that the construct is preelaborable
14868 return False;
14870 exception
14872 -- The elaboration of the construct performs an action which violates
14873 -- preelaborability.
14875 when Non_Preelaborable =>
14876 return True;
14877 end Is_Non_Preelaborable_Construct;
14879 ---------------------------------
14880 -- Is_Nontrivial_DIC_Procedure --
14881 ---------------------------------
14883 function Is_Nontrivial_DIC_Procedure (Id : Entity_Id) return Boolean is
14884 Body_Decl : Node_Id;
14885 Stmt : Node_Id;
14887 begin
14888 if Ekind (Id) = E_Procedure and then Is_DIC_Procedure (Id) then
14889 Body_Decl :=
14890 Unit_Declaration_Node
14891 (Corresponding_Body (Unit_Declaration_Node (Id)));
14893 -- The body of the Default_Initial_Condition procedure must contain
14894 -- at least one statement, otherwise the generation of the subprogram
14895 -- body failed.
14897 pragma Assert (Present (Handled_Statement_Sequence (Body_Decl)));
14899 -- To qualify as nontrivial, the first statement of the procedure
14900 -- must be a check in the form of an if statement. If the original
14901 -- Default_Initial_Condition expression was folded, then the first
14902 -- statement is not a check.
14904 Stmt := First (Statements (Handled_Statement_Sequence (Body_Decl)));
14906 return
14907 Nkind (Stmt) = N_If_Statement
14908 and then Nkind (Original_Node (Stmt)) = N_Pragma;
14909 end if;
14911 return False;
14912 end Is_Nontrivial_DIC_Procedure;
14914 -------------------------
14915 -- Is_Null_Record_Type --
14916 -------------------------
14918 function Is_Null_Record_Type (T : Entity_Id) return Boolean is
14919 Decl : constant Node_Id := Parent (T);
14920 begin
14921 return Nkind (Decl) = N_Full_Type_Declaration
14922 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
14923 and then
14924 (No (Component_List (Type_Definition (Decl)))
14925 or else Null_Present (Component_List (Type_Definition (Decl))));
14926 end Is_Null_Record_Type;
14928 ---------------------
14929 -- Is_Object_Image --
14930 ---------------------
14932 function Is_Object_Image (Prefix : Node_Id) return Boolean is
14933 begin
14934 -- When the type of the prefix is not scalar, then the prefix is not
14935 -- valid in any scenario.
14937 if not Is_Scalar_Type (Etype (Prefix)) then
14938 return False;
14939 end if;
14941 -- Here we test for the case that the prefix is not a type and assume
14942 -- if it is not then it must be a named value or an object reference.
14943 -- This is because the parser always checks that prefixes of attributes
14944 -- are named.
14946 return not (Is_Entity_Name (Prefix) and then Is_Type (Entity (Prefix)));
14947 end Is_Object_Image;
14949 -------------------------
14950 -- Is_Object_Reference --
14951 -------------------------
14953 function Is_Object_Reference (N : Node_Id) return Boolean is
14954 function Is_Internally_Generated_Renaming (N : Node_Id) return Boolean;
14955 -- Determine whether N is the name of an internally-generated renaming
14957 --------------------------------------
14958 -- Is_Internally_Generated_Renaming --
14959 --------------------------------------
14961 function Is_Internally_Generated_Renaming (N : Node_Id) return Boolean is
14962 P : Node_Id;
14964 begin
14965 P := N;
14966 while Present (P) loop
14967 if Nkind (P) = N_Object_Renaming_Declaration then
14968 return not Comes_From_Source (P);
14969 elsif Is_List_Member (P) then
14970 return False;
14971 end if;
14973 P := Parent (P);
14974 end loop;
14976 return False;
14977 end Is_Internally_Generated_Renaming;
14979 -- Start of processing for Is_Object_Reference
14981 begin
14982 if Is_Entity_Name (N) then
14983 return Present (Entity (N)) and then Is_Object (Entity (N));
14985 else
14986 case Nkind (N) is
14987 when N_Indexed_Component
14988 | N_Slice
14990 return
14991 Is_Object_Reference (Prefix (N))
14992 or else Is_Access_Type (Etype (Prefix (N)));
14994 -- In Ada 95, a function call is a constant object; a procedure
14995 -- call is not.
14997 -- Note that predefined operators are functions as well, and so
14998 -- are attributes that are (can be renamed as) functions.
15000 when N_Binary_Op
15001 | N_Function_Call
15002 | N_Unary_Op
15004 return Etype (N) /= Standard_Void_Type;
15006 -- Attributes references 'Loop_Entry, 'Old, and 'Result yield
15007 -- objects, even though they are not functions.
15009 when N_Attribute_Reference =>
15010 return
15011 Nam_In (Attribute_Name (N), Name_Loop_Entry,
15012 Name_Old,
15013 Name_Result)
15014 or else Is_Function_Attribute_Name (Attribute_Name (N));
15016 when N_Selected_Component =>
15017 return
15018 Is_Object_Reference (Selector_Name (N))
15019 and then
15020 (Is_Object_Reference (Prefix (N))
15021 or else Is_Access_Type (Etype (Prefix (N))));
15023 -- An explicit dereference denotes an object, except that a
15024 -- conditional expression gets turned into an explicit dereference
15025 -- in some cases, and conditional expressions are not object
15026 -- names.
15028 when N_Explicit_Dereference =>
15029 return not Nkind_In (Original_Node (N), N_Case_Expression,
15030 N_If_Expression);
15032 -- A view conversion of a tagged object is an object reference
15034 when N_Type_Conversion =>
15035 return Is_Tagged_Type (Etype (Subtype_Mark (N)))
15036 and then Is_Tagged_Type (Etype (Expression (N)))
15037 and then Is_Object_Reference (Expression (N));
15039 -- An unchecked type conversion is considered to be an object if
15040 -- the operand is an object (this construction arises only as a
15041 -- result of expansion activities).
15043 when N_Unchecked_Type_Conversion =>
15044 return True;
15046 -- Allow string literals to act as objects as long as they appear
15047 -- in internally-generated renamings. The expansion of iterators
15048 -- may generate such renamings when the range involves a string
15049 -- literal.
15051 when N_String_Literal =>
15052 return Is_Internally_Generated_Renaming (Parent (N));
15054 -- AI05-0003: In Ada 2012 a qualified expression is a name.
15055 -- This allows disambiguation of function calls and the use
15056 -- of aggregates in more contexts.
15058 when N_Qualified_Expression =>
15059 if Ada_Version < Ada_2012 then
15060 return False;
15061 else
15062 return Is_Object_Reference (Expression (N))
15063 or else Nkind (Expression (N)) = N_Aggregate;
15064 end if;
15066 when others =>
15067 return False;
15068 end case;
15069 end if;
15070 end Is_Object_Reference;
15072 -----------------------------------
15073 -- Is_OK_Variable_For_Out_Formal --
15074 -----------------------------------
15076 function Is_OK_Variable_For_Out_Formal (AV : Node_Id) return Boolean is
15077 begin
15078 Note_Possible_Modification (AV, Sure => True);
15080 -- We must reject parenthesized variable names. Comes_From_Source is
15081 -- checked because there are currently cases where the compiler violates
15082 -- this rule (e.g. passing a task object to its controlled Initialize
15083 -- routine). This should be properly documented in sinfo???
15085 if Paren_Count (AV) > 0 and then Comes_From_Source (AV) then
15086 return False;
15088 -- A variable is always allowed
15090 elsif Is_Variable (AV) then
15091 return True;
15093 -- Generalized indexing operations are rewritten as explicit
15094 -- dereferences, and it is only during resolution that we can
15095 -- check whether the context requires an access_to_variable type.
15097 elsif Nkind (AV) = N_Explicit_Dereference
15098 and then Ada_Version >= Ada_2012
15099 and then Nkind (Original_Node (AV)) = N_Indexed_Component
15100 and then Present (Etype (Original_Node (AV)))
15101 and then Has_Implicit_Dereference (Etype (Original_Node (AV)))
15102 then
15103 return not Is_Access_Constant (Etype (Prefix (AV)));
15105 -- Unchecked conversions are allowed only if they come from the
15106 -- generated code, which sometimes uses unchecked conversions for out
15107 -- parameters in cases where code generation is unaffected. We tell
15108 -- source unchecked conversions by seeing if they are rewrites of
15109 -- an original Unchecked_Conversion function call, or of an explicit
15110 -- conversion of a function call or an aggregate (as may happen in the
15111 -- expansion of a packed array aggregate).
15113 elsif Nkind (AV) = N_Unchecked_Type_Conversion then
15114 if Nkind_In (Original_Node (AV), N_Function_Call, N_Aggregate) then
15115 return False;
15117 elsif Comes_From_Source (AV)
15118 and then Nkind (Original_Node (Expression (AV))) = N_Function_Call
15119 then
15120 return False;
15122 elsif Nkind (Original_Node (AV)) = N_Type_Conversion then
15123 return Is_OK_Variable_For_Out_Formal (Expression (AV));
15125 else
15126 return True;
15127 end if;
15129 -- Normal type conversions are allowed if argument is a variable
15131 elsif Nkind (AV) = N_Type_Conversion then
15132 if Is_Variable (Expression (AV))
15133 and then Paren_Count (Expression (AV)) = 0
15134 then
15135 Note_Possible_Modification (Expression (AV), Sure => True);
15136 return True;
15138 -- We also allow a non-parenthesized expression that raises
15139 -- constraint error if it rewrites what used to be a variable
15141 elsif Raises_Constraint_Error (Expression (AV))
15142 and then Paren_Count (Expression (AV)) = 0
15143 and then Is_Variable (Original_Node (Expression (AV)))
15144 then
15145 return True;
15147 -- Type conversion of something other than a variable
15149 else
15150 return False;
15151 end if;
15153 -- If this node is rewritten, then test the original form, if that is
15154 -- OK, then we consider the rewritten node OK (for example, if the
15155 -- original node is a conversion, then Is_Variable will not be true
15156 -- but we still want to allow the conversion if it converts a variable).
15158 elsif Original_Node (AV) /= AV then
15160 -- In Ada 2012, the explicit dereference may be a rewritten call to a
15161 -- Reference function.
15163 if Ada_Version >= Ada_2012
15164 and then Nkind (Original_Node (AV)) = N_Function_Call
15165 and then
15166 Has_Implicit_Dereference (Etype (Name (Original_Node (AV))))
15167 then
15169 -- Check that this is not a constant reference.
15171 return not Is_Access_Constant (Etype (Prefix (AV)));
15173 elsif Has_Implicit_Dereference (Etype (Original_Node (AV))) then
15174 return
15175 not Is_Access_Constant (Etype
15176 (Get_Reference_Discriminant (Etype (Original_Node (AV)))));
15178 else
15179 return Is_OK_Variable_For_Out_Formal (Original_Node (AV));
15180 end if;
15182 -- All other non-variables are rejected
15184 else
15185 return False;
15186 end if;
15187 end Is_OK_Variable_For_Out_Formal;
15189 ----------------------------
15190 -- Is_OK_Volatile_Context --
15191 ----------------------------
15193 function Is_OK_Volatile_Context
15194 (Context : Node_Id;
15195 Obj_Ref : Node_Id) return Boolean
15197 function Is_Protected_Operation_Call (Nod : Node_Id) return Boolean;
15198 -- Determine whether an arbitrary node denotes a call to a protected
15199 -- entry, function, or procedure in prefixed form where the prefix is
15200 -- Obj_Ref.
15202 function Within_Check (Nod : Node_Id) return Boolean;
15203 -- Determine whether an arbitrary node appears in a check node
15205 function Within_Volatile_Function (Id : Entity_Id) return Boolean;
15206 -- Determine whether an arbitrary entity appears in a volatile function
15208 ---------------------------------
15209 -- Is_Protected_Operation_Call --
15210 ---------------------------------
15212 function Is_Protected_Operation_Call (Nod : Node_Id) return Boolean is
15213 Pref : Node_Id;
15214 Subp : Node_Id;
15216 begin
15217 -- A call to a protected operations retains its selected component
15218 -- form as opposed to other prefixed calls that are transformed in
15219 -- expanded names.
15221 if Nkind (Nod) = N_Selected_Component then
15222 Pref := Prefix (Nod);
15223 Subp := Selector_Name (Nod);
15225 return
15226 Pref = Obj_Ref
15227 and then Present (Etype (Pref))
15228 and then Is_Protected_Type (Etype (Pref))
15229 and then Is_Entity_Name (Subp)
15230 and then Present (Entity (Subp))
15231 and then Ekind_In (Entity (Subp), E_Entry,
15232 E_Entry_Family,
15233 E_Function,
15234 E_Procedure);
15235 else
15236 return False;
15237 end if;
15238 end Is_Protected_Operation_Call;
15240 ------------------
15241 -- Within_Check --
15242 ------------------
15244 function Within_Check (Nod : Node_Id) return Boolean is
15245 Par : Node_Id;
15247 begin
15248 -- Climb the parent chain looking for a check node
15250 Par := Nod;
15251 while Present (Par) loop
15252 if Nkind (Par) in N_Raise_xxx_Error then
15253 return True;
15255 -- Prevent the search from going too far
15257 elsif Is_Body_Or_Package_Declaration (Par) then
15258 exit;
15259 end if;
15261 Par := Parent (Par);
15262 end loop;
15264 return False;
15265 end Within_Check;
15267 ------------------------------
15268 -- Within_Volatile_Function --
15269 ------------------------------
15271 function Within_Volatile_Function (Id : Entity_Id) return Boolean is
15272 Func_Id : Entity_Id;
15274 begin
15275 -- Traverse the scope stack looking for a [generic] function
15277 Func_Id := Id;
15278 while Present (Func_Id) and then Func_Id /= Standard_Standard loop
15279 if Ekind_In (Func_Id, E_Function, E_Generic_Function) then
15280 return Is_Volatile_Function (Func_Id);
15281 end if;
15283 Func_Id := Scope (Func_Id);
15284 end loop;
15286 return False;
15287 end Within_Volatile_Function;
15289 -- Local variables
15291 Obj_Id : Entity_Id;
15293 -- Start of processing for Is_OK_Volatile_Context
15295 begin
15296 -- The volatile object appears on either side of an assignment
15298 if Nkind (Context) = N_Assignment_Statement then
15299 return True;
15301 -- The volatile object is part of the initialization expression of
15302 -- another object.
15304 elsif Nkind (Context) = N_Object_Declaration
15305 and then Present (Expression (Context))
15306 and then Expression (Context) = Obj_Ref
15307 then
15308 Obj_Id := Defining_Entity (Context);
15310 -- The volatile object acts as the initialization expression of an
15311 -- extended return statement. This is valid context as long as the
15312 -- function is volatile.
15314 if Is_Return_Object (Obj_Id) then
15315 return Within_Volatile_Function (Obj_Id);
15317 -- Otherwise this is a normal object initialization
15319 else
15320 return True;
15321 end if;
15323 -- The volatile object acts as the name of a renaming declaration
15325 elsif Nkind (Context) = N_Object_Renaming_Declaration
15326 and then Name (Context) = Obj_Ref
15327 then
15328 return True;
15330 -- The volatile object appears as an actual parameter in a call to an
15331 -- instance of Unchecked_Conversion whose result is renamed.
15333 elsif Nkind (Context) = N_Function_Call
15334 and then Is_Entity_Name (Name (Context))
15335 and then Is_Unchecked_Conversion_Instance (Entity (Name (Context)))
15336 and then Nkind (Parent (Context)) = N_Object_Renaming_Declaration
15337 then
15338 return True;
15340 -- The volatile object is actually the prefix in a protected entry,
15341 -- function, or procedure call.
15343 elsif Is_Protected_Operation_Call (Context) then
15344 return True;
15346 -- The volatile object appears as the expression of a simple return
15347 -- statement that applies to a volatile function.
15349 elsif Nkind (Context) = N_Simple_Return_Statement
15350 and then Expression (Context) = Obj_Ref
15351 then
15352 return
15353 Within_Volatile_Function (Return_Statement_Entity (Context));
15355 -- The volatile object appears as the prefix of a name occurring in a
15356 -- non-interfering context.
15358 elsif Nkind_In (Context, N_Attribute_Reference,
15359 N_Explicit_Dereference,
15360 N_Indexed_Component,
15361 N_Selected_Component,
15362 N_Slice)
15363 and then Prefix (Context) = Obj_Ref
15364 and then Is_OK_Volatile_Context
15365 (Context => Parent (Context),
15366 Obj_Ref => Context)
15367 then
15368 return True;
15370 -- The volatile object appears as the prefix of attributes Address,
15371 -- Alignment, Component_Size, First_Bit, Last_Bit, Position, Size,
15372 -- Storage_Size.
15374 elsif Nkind (Context) = N_Attribute_Reference
15375 and then Prefix (Context) = Obj_Ref
15376 and then Nam_In (Attribute_Name (Context), Name_Address,
15377 Name_Alignment,
15378 Name_Component_Size,
15379 Name_First_Bit,
15380 Name_Last_Bit,
15381 Name_Position,
15382 Name_Size,
15383 Name_Storage_Size)
15384 then
15385 return True;
15387 -- The volatile object appears as the expression of a type conversion
15388 -- occurring in a non-interfering context.
15390 elsif Nkind_In (Context, N_Type_Conversion,
15391 N_Unchecked_Type_Conversion)
15392 and then Expression (Context) = Obj_Ref
15393 and then Is_OK_Volatile_Context
15394 (Context => Parent (Context),
15395 Obj_Ref => Context)
15396 then
15397 return True;
15399 -- The volatile object appears as the expression in a delay statement
15401 elsif Nkind (Context) in N_Delay_Statement then
15402 return True;
15404 -- Allow references to volatile objects in various checks. This is not a
15405 -- direct SPARK 2014 requirement.
15407 elsif Within_Check (Context) then
15408 return True;
15410 -- Assume that references to effectively volatile objects that appear
15411 -- as actual parameters in a subprogram call are always legal. A full
15412 -- legality check is done when the actuals are resolved (see routine
15413 -- Resolve_Actuals).
15415 elsif Within_Subprogram_Call (Context) then
15416 return True;
15418 -- Otherwise the context is not suitable for an effectively volatile
15419 -- object.
15421 else
15422 return False;
15423 end if;
15424 end Is_OK_Volatile_Context;
15426 ------------------------------------
15427 -- Is_Package_Contract_Annotation --
15428 ------------------------------------
15430 function Is_Package_Contract_Annotation (Item : Node_Id) return Boolean is
15431 Nam : Name_Id;
15433 begin
15434 if Nkind (Item) = N_Aspect_Specification then
15435 Nam := Chars (Identifier (Item));
15437 else pragma Assert (Nkind (Item) = N_Pragma);
15438 Nam := Pragma_Name (Item);
15439 end if;
15441 return Nam = Name_Abstract_State
15442 or else Nam = Name_Initial_Condition
15443 or else Nam = Name_Initializes
15444 or else Nam = Name_Refined_State;
15445 end Is_Package_Contract_Annotation;
15447 -----------------------------------
15448 -- Is_Partially_Initialized_Type --
15449 -----------------------------------
15451 function Is_Partially_Initialized_Type
15452 (Typ : Entity_Id;
15453 Include_Implicit : Boolean := True) return Boolean
15455 begin
15456 if Is_Scalar_Type (Typ) then
15457 return False;
15459 elsif Is_Access_Type (Typ) then
15460 return Include_Implicit;
15462 elsif Is_Array_Type (Typ) then
15464 -- If component type is partially initialized, so is array type
15466 if Is_Partially_Initialized_Type
15467 (Component_Type (Typ), Include_Implicit)
15468 then
15469 return True;
15471 -- Otherwise we are only partially initialized if we are fully
15472 -- initialized (this is the empty array case, no point in us
15473 -- duplicating that code here).
15475 else
15476 return Is_Fully_Initialized_Type (Typ);
15477 end if;
15479 elsif Is_Record_Type (Typ) then
15481 -- A discriminated type is always partially initialized if in
15482 -- all mode
15484 if Has_Discriminants (Typ) and then Include_Implicit then
15485 return True;
15487 -- A tagged type is always partially initialized
15489 elsif Is_Tagged_Type (Typ) then
15490 return True;
15492 -- Case of non-discriminated record
15494 else
15495 declare
15496 Ent : Entity_Id;
15498 Component_Present : Boolean := False;
15499 -- Set True if at least one component is present. If no
15500 -- components are present, then record type is fully
15501 -- initialized (another odd case, like the null array).
15503 begin
15504 -- Loop through components
15506 Ent := First_Entity (Typ);
15507 while Present (Ent) loop
15508 if Ekind (Ent) = E_Component then
15509 Component_Present := True;
15511 -- If a component has an initialization expression then
15512 -- the enclosing record type is partially initialized
15514 if Present (Parent (Ent))
15515 and then Present (Expression (Parent (Ent)))
15516 then
15517 return True;
15519 -- If a component is of a type which is itself partially
15520 -- initialized, then the enclosing record type is also.
15522 elsif Is_Partially_Initialized_Type
15523 (Etype (Ent), Include_Implicit)
15524 then
15525 return True;
15526 end if;
15527 end if;
15529 Next_Entity (Ent);
15530 end loop;
15532 -- No initialized components found. If we found any components
15533 -- they were all uninitialized so the result is false.
15535 if Component_Present then
15536 return False;
15538 -- But if we found no components, then all the components are
15539 -- initialized so we consider the type to be initialized.
15541 else
15542 return True;
15543 end if;
15544 end;
15545 end if;
15547 -- Concurrent types are always fully initialized
15549 elsif Is_Concurrent_Type (Typ) then
15550 return True;
15552 -- For a private type, go to underlying type. If there is no underlying
15553 -- type then just assume this partially initialized. Not clear if this
15554 -- can happen in a non-error case, but no harm in testing for this.
15556 elsif Is_Private_Type (Typ) then
15557 declare
15558 U : constant Entity_Id := Underlying_Type (Typ);
15559 begin
15560 if No (U) then
15561 return True;
15562 else
15563 return Is_Partially_Initialized_Type (U, Include_Implicit);
15564 end if;
15565 end;
15567 -- For any other type (are there any?) assume partially initialized
15569 else
15570 return True;
15571 end if;
15572 end Is_Partially_Initialized_Type;
15574 ------------------------------------
15575 -- Is_Potentially_Persistent_Type --
15576 ------------------------------------
15578 function Is_Potentially_Persistent_Type (T : Entity_Id) return Boolean is
15579 Comp : Entity_Id;
15580 Indx : Node_Id;
15582 begin
15583 -- For private type, test corresponding full type
15585 if Is_Private_Type (T) then
15586 return Is_Potentially_Persistent_Type (Full_View (T));
15588 -- Scalar types are potentially persistent
15590 elsif Is_Scalar_Type (T) then
15591 return True;
15593 -- Record type is potentially persistent if not tagged and the types of
15594 -- all it components are potentially persistent, and no component has
15595 -- an initialization expression.
15597 elsif Is_Record_Type (T)
15598 and then not Is_Tagged_Type (T)
15599 and then not Is_Partially_Initialized_Type (T)
15600 then
15601 Comp := First_Component (T);
15602 while Present (Comp) loop
15603 if not Is_Potentially_Persistent_Type (Etype (Comp)) then
15604 return False;
15605 else
15606 Next_Entity (Comp);
15607 end if;
15608 end loop;
15610 return True;
15612 -- Array type is potentially persistent if its component type is
15613 -- potentially persistent and if all its constraints are static.
15615 elsif Is_Array_Type (T) then
15616 if not Is_Potentially_Persistent_Type (Component_Type (T)) then
15617 return False;
15618 end if;
15620 Indx := First_Index (T);
15621 while Present (Indx) loop
15622 if not Is_OK_Static_Subtype (Etype (Indx)) then
15623 return False;
15624 else
15625 Next_Index (Indx);
15626 end if;
15627 end loop;
15629 return True;
15631 -- All other types are not potentially persistent
15633 else
15634 return False;
15635 end if;
15636 end Is_Potentially_Persistent_Type;
15638 --------------------------------
15639 -- Is_Potentially_Unevaluated --
15640 --------------------------------
15642 function Is_Potentially_Unevaluated (N : Node_Id) return Boolean is
15643 Par : Node_Id;
15644 Expr : Node_Id;
15646 begin
15647 Expr := N;
15648 Par := Parent (N);
15650 -- A postcondition whose expression is a short-circuit is broken down
15651 -- into individual aspects for better exception reporting. The original
15652 -- short-circuit expression is rewritten as the second operand, and an
15653 -- occurrence of 'Old in that operand is potentially unevaluated.
15654 -- See Sem_ch13.adb for details of this transformation.
15656 if Nkind (Original_Node (Par)) = N_And_Then then
15657 return True;
15658 end if;
15660 while not Nkind_In (Par, N_If_Expression,
15661 N_Case_Expression,
15662 N_And_Then,
15663 N_Or_Else,
15664 N_In,
15665 N_Not_In,
15666 N_Quantified_Expression)
15667 loop
15668 Expr := Par;
15669 Par := Parent (Par);
15671 -- If the context is not an expression, or if is the result of
15672 -- expansion of an enclosing construct (such as another attribute)
15673 -- the predicate does not apply.
15675 if Nkind (Par) = N_Case_Expression_Alternative then
15676 null;
15678 elsif Nkind (Par) not in N_Subexpr
15679 or else not Comes_From_Source (Par)
15680 then
15681 return False;
15682 end if;
15683 end loop;
15685 if Nkind (Par) = N_If_Expression then
15686 return Is_Elsif (Par) or else Expr /= First (Expressions (Par));
15688 elsif Nkind (Par) = N_Case_Expression then
15689 return Expr /= Expression (Par);
15691 elsif Nkind_In (Par, N_And_Then, N_Or_Else) then
15692 return Expr = Right_Opnd (Par);
15694 elsif Nkind_In (Par, N_In, N_Not_In) then
15696 -- If the membership includes several alternatives, only the first is
15697 -- definitely evaluated.
15699 if Present (Alternatives (Par)) then
15700 return Expr /= First (Alternatives (Par));
15702 -- If this is a range membership both bounds are evaluated
15704 else
15705 return False;
15706 end if;
15708 elsif Nkind (Par) = N_Quantified_Expression then
15709 return Expr = Condition (Par);
15711 else
15712 return False;
15713 end if;
15714 end Is_Potentially_Unevaluated;
15716 --------------------------------
15717 -- Is_Preelaborable_Aggregate --
15718 --------------------------------
15720 function Is_Preelaborable_Aggregate (Aggr : Node_Id) return Boolean is
15721 Aggr_Typ : constant Entity_Id := Etype (Aggr);
15722 Array_Aggr : constant Boolean := Is_Array_Type (Aggr_Typ);
15724 Anc_Part : Node_Id;
15725 Assoc : Node_Id;
15726 Choice : Node_Id;
15727 Comp_Typ : Entity_Id := Empty; -- init to avoid warning
15728 Expr : Node_Id;
15730 begin
15731 if Array_Aggr then
15732 Comp_Typ := Component_Type (Aggr_Typ);
15733 end if;
15735 -- Inspect the ancestor part
15737 if Nkind (Aggr) = N_Extension_Aggregate then
15738 Anc_Part := Ancestor_Part (Aggr);
15740 -- The ancestor denotes a subtype mark
15742 if Is_Entity_Name (Anc_Part)
15743 and then Is_Type (Entity (Anc_Part))
15744 then
15745 if not Has_Preelaborable_Initialization (Entity (Anc_Part)) then
15746 return False;
15747 end if;
15749 -- Otherwise the ancestor denotes an expression
15751 elsif not Is_Preelaborable_Construct (Anc_Part) then
15752 return False;
15753 end if;
15754 end if;
15756 -- Inspect the positional associations
15758 Expr := First (Expressions (Aggr));
15759 while Present (Expr) loop
15760 if not Is_Preelaborable_Construct (Expr) then
15761 return False;
15762 end if;
15764 Next (Expr);
15765 end loop;
15767 -- Inspect the named associations
15769 Assoc := First (Component_Associations (Aggr));
15770 while Present (Assoc) loop
15772 -- Inspect the choices of the current named association
15774 Choice := First (Choices (Assoc));
15775 while Present (Choice) loop
15776 if Array_Aggr then
15778 -- For a choice to be preelaborable, it must denote either a
15779 -- static range or a static expression.
15781 if Nkind (Choice) = N_Others_Choice then
15782 null;
15784 elsif Nkind (Choice) = N_Range then
15785 if not Is_OK_Static_Range (Choice) then
15786 return False;
15787 end if;
15789 elsif not Is_OK_Static_Expression (Choice) then
15790 return False;
15791 end if;
15793 else
15794 Comp_Typ := Etype (Choice);
15795 end if;
15797 Next (Choice);
15798 end loop;
15800 -- The type of the choice must have preelaborable initialization if
15801 -- the association carries a <>.
15803 pragma Assert (Present (Comp_Typ));
15804 if Box_Present (Assoc) then
15805 if not Has_Preelaborable_Initialization (Comp_Typ) then
15806 return False;
15807 end if;
15809 -- The type of the expression must have preelaborable initialization
15811 elsif not Is_Preelaborable_Construct (Expression (Assoc)) then
15812 return False;
15813 end if;
15815 Next (Assoc);
15816 end loop;
15818 -- At this point the aggregate is preelaborable
15820 return True;
15821 end Is_Preelaborable_Aggregate;
15823 --------------------------------
15824 -- Is_Preelaborable_Construct --
15825 --------------------------------
15827 function Is_Preelaborable_Construct (N : Node_Id) return Boolean is
15828 begin
15829 -- Aggregates
15831 if Nkind_In (N, N_Aggregate, N_Extension_Aggregate) then
15832 return Is_Preelaborable_Aggregate (N);
15834 -- Attributes are allowed in general, even if their prefix is a formal
15835 -- type. It seems that certain attributes known not to be static might
15836 -- not be allowed, but there are no rules to prevent them.
15838 elsif Nkind (N) = N_Attribute_Reference then
15839 return True;
15841 -- Expressions
15843 elsif Nkind (N) in N_Subexpr and then Is_OK_Static_Expression (N) then
15844 return True;
15846 elsif Nkind (N) = N_Qualified_Expression then
15847 return Is_Preelaborable_Construct (Expression (N));
15849 -- Names are preelaborable when they denote a discriminant of an
15850 -- enclosing type. Discriminals are also considered for this check.
15852 elsif Is_Entity_Name (N)
15853 and then Present (Entity (N))
15854 and then
15855 (Ekind (Entity (N)) = E_Discriminant
15856 or else (Ekind_In (Entity (N), E_Constant, E_In_Parameter)
15857 and then Present (Discriminal_Link (Entity (N)))))
15858 then
15859 return True;
15861 -- Statements
15863 elsif Nkind (N) = N_Null then
15864 return True;
15866 -- Otherwise the construct is not preelaborable
15868 else
15869 return False;
15870 end if;
15871 end Is_Preelaborable_Construct;
15873 ---------------------------------
15874 -- Is_Protected_Self_Reference --
15875 ---------------------------------
15877 function Is_Protected_Self_Reference (N : Node_Id) return Boolean is
15879 function In_Access_Definition (N : Node_Id) return Boolean;
15880 -- Returns true if N belongs to an access definition
15882 --------------------------
15883 -- In_Access_Definition --
15884 --------------------------
15886 function In_Access_Definition (N : Node_Id) return Boolean is
15887 P : Node_Id;
15889 begin
15890 P := Parent (N);
15891 while Present (P) loop
15892 if Nkind (P) = N_Access_Definition then
15893 return True;
15894 end if;
15896 P := Parent (P);
15897 end loop;
15899 return False;
15900 end In_Access_Definition;
15902 -- Start of processing for Is_Protected_Self_Reference
15904 begin
15905 -- Verify that prefix is analyzed and has the proper form. Note that
15906 -- the attributes Elab_Spec, Elab_Body, and Elab_Subp_Body, which also
15907 -- produce the address of an entity, do not analyze their prefix
15908 -- because they denote entities that are not necessarily visible.
15909 -- Neither of them can apply to a protected type.
15911 return Ada_Version >= Ada_2005
15912 and then Is_Entity_Name (N)
15913 and then Present (Entity (N))
15914 and then Is_Protected_Type (Entity (N))
15915 and then In_Open_Scopes (Entity (N))
15916 and then not In_Access_Definition (N);
15917 end Is_Protected_Self_Reference;
15919 -----------------------------
15920 -- Is_RCI_Pkg_Spec_Or_Body --
15921 -----------------------------
15923 function Is_RCI_Pkg_Spec_Or_Body (Cunit : Node_Id) return Boolean is
15925 function Is_RCI_Pkg_Decl_Cunit (Cunit : Node_Id) return Boolean;
15926 -- Return True if the unit of Cunit is an RCI package declaration
15928 ---------------------------
15929 -- Is_RCI_Pkg_Decl_Cunit --
15930 ---------------------------
15932 function Is_RCI_Pkg_Decl_Cunit (Cunit : Node_Id) return Boolean is
15933 The_Unit : constant Node_Id := Unit (Cunit);
15935 begin
15936 if Nkind (The_Unit) /= N_Package_Declaration then
15937 return False;
15938 end if;
15940 return Is_Remote_Call_Interface (Defining_Entity (The_Unit));
15941 end Is_RCI_Pkg_Decl_Cunit;
15943 -- Start of processing for Is_RCI_Pkg_Spec_Or_Body
15945 begin
15946 return Is_RCI_Pkg_Decl_Cunit (Cunit)
15947 or else
15948 (Nkind (Unit (Cunit)) = N_Package_Body
15949 and then Is_RCI_Pkg_Decl_Cunit (Library_Unit (Cunit)));
15950 end Is_RCI_Pkg_Spec_Or_Body;
15952 -----------------------------------------
15953 -- Is_Remote_Access_To_Class_Wide_Type --
15954 -----------------------------------------
15956 function Is_Remote_Access_To_Class_Wide_Type
15957 (E : Entity_Id) return Boolean
15959 begin
15960 -- A remote access to class-wide type is a general access to object type
15961 -- declared in the visible part of a Remote_Types or Remote_Call_
15962 -- Interface unit.
15964 return Ekind (E) = E_General_Access_Type
15965 and then (Is_Remote_Call_Interface (E) or else Is_Remote_Types (E));
15966 end Is_Remote_Access_To_Class_Wide_Type;
15968 -----------------------------------------
15969 -- Is_Remote_Access_To_Subprogram_Type --
15970 -----------------------------------------
15972 function Is_Remote_Access_To_Subprogram_Type
15973 (E : Entity_Id) return Boolean
15975 begin
15976 return (Ekind (E) = E_Access_Subprogram_Type
15977 or else (Ekind (E) = E_Record_Type
15978 and then Present (Corresponding_Remote_Type (E))))
15979 and then (Is_Remote_Call_Interface (E) or else Is_Remote_Types (E));
15980 end Is_Remote_Access_To_Subprogram_Type;
15982 --------------------
15983 -- Is_Remote_Call --
15984 --------------------
15986 function Is_Remote_Call (N : Node_Id) return Boolean is
15987 begin
15988 if Nkind (N) not in N_Subprogram_Call then
15990 -- An entry call cannot be remote
15992 return False;
15994 elsif Nkind (Name (N)) in N_Has_Entity
15995 and then Is_Remote_Call_Interface (Entity (Name (N)))
15996 then
15997 -- A subprogram declared in the spec of a RCI package is remote
15999 return True;
16001 elsif Nkind (Name (N)) = N_Explicit_Dereference
16002 and then Is_Remote_Access_To_Subprogram_Type
16003 (Etype (Prefix (Name (N))))
16004 then
16005 -- The dereference of a RAS is a remote call
16007 return True;
16009 elsif Present (Controlling_Argument (N))
16010 and then Is_Remote_Access_To_Class_Wide_Type
16011 (Etype (Controlling_Argument (N)))
16012 then
16013 -- Any primitive operation call with a controlling argument of
16014 -- a RACW type is a remote call.
16016 return True;
16017 end if;
16019 -- All other calls are local calls
16021 return False;
16022 end Is_Remote_Call;
16024 ----------------------
16025 -- Is_Renamed_Entry --
16026 ----------------------
16028 function Is_Renamed_Entry (Proc_Nam : Entity_Id) return Boolean is
16029 Orig_Node : Node_Id := Empty;
16030 Subp_Decl : Node_Id := Parent (Parent (Proc_Nam));
16032 function Is_Entry (Nam : Node_Id) return Boolean;
16033 -- Determine whether Nam is an entry. Traverse selectors if there are
16034 -- nested selected components.
16036 --------------
16037 -- Is_Entry --
16038 --------------
16040 function Is_Entry (Nam : Node_Id) return Boolean is
16041 begin
16042 if Nkind (Nam) = N_Selected_Component then
16043 return Is_Entry (Selector_Name (Nam));
16044 end if;
16046 return Ekind (Entity (Nam)) = E_Entry;
16047 end Is_Entry;
16049 -- Start of processing for Is_Renamed_Entry
16051 begin
16052 if Present (Alias (Proc_Nam)) then
16053 Subp_Decl := Parent (Parent (Alias (Proc_Nam)));
16054 end if;
16056 -- Look for a rewritten subprogram renaming declaration
16058 if Nkind (Subp_Decl) = N_Subprogram_Declaration
16059 and then Present (Original_Node (Subp_Decl))
16060 then
16061 Orig_Node := Original_Node (Subp_Decl);
16062 end if;
16064 -- The rewritten subprogram is actually an entry
16066 if Present (Orig_Node)
16067 and then Nkind (Orig_Node) = N_Subprogram_Renaming_Declaration
16068 and then Is_Entry (Name (Orig_Node))
16069 then
16070 return True;
16071 end if;
16073 return False;
16074 end Is_Renamed_Entry;
16076 -----------------------------
16077 -- Is_Renaming_Declaration --
16078 -----------------------------
16080 function Is_Renaming_Declaration (N : Node_Id) return Boolean is
16081 begin
16082 case Nkind (N) is
16083 when N_Exception_Renaming_Declaration
16084 | N_Generic_Function_Renaming_Declaration
16085 | N_Generic_Package_Renaming_Declaration
16086 | N_Generic_Procedure_Renaming_Declaration
16087 | N_Object_Renaming_Declaration
16088 | N_Package_Renaming_Declaration
16089 | N_Subprogram_Renaming_Declaration
16091 return True;
16093 when others =>
16094 return False;
16095 end case;
16096 end Is_Renaming_Declaration;
16098 ----------------------------
16099 -- Is_Reversible_Iterator --
16100 ----------------------------
16102 function Is_Reversible_Iterator (Typ : Entity_Id) return Boolean is
16103 Ifaces_List : Elist_Id;
16104 Iface_Elmt : Elmt_Id;
16105 Iface : Entity_Id;
16107 begin
16108 if Is_Class_Wide_Type (Typ)
16109 and then Chars (Root_Type (Typ)) = Name_Reversible_Iterator
16110 and then In_Predefined_Unit (Root_Type (Typ))
16111 then
16112 return True;
16114 elsif not Is_Tagged_Type (Typ) or else not Is_Derived_Type (Typ) then
16115 return False;
16117 else
16118 Collect_Interfaces (Typ, Ifaces_List);
16120 Iface_Elmt := First_Elmt (Ifaces_List);
16121 while Present (Iface_Elmt) loop
16122 Iface := Node (Iface_Elmt);
16123 if Chars (Iface) = Name_Reversible_Iterator
16124 and then In_Predefined_Unit (Iface)
16125 then
16126 return True;
16127 end if;
16129 Next_Elmt (Iface_Elmt);
16130 end loop;
16131 end if;
16133 return False;
16134 end Is_Reversible_Iterator;
16136 ----------------------
16137 -- Is_Selector_Name --
16138 ----------------------
16140 function Is_Selector_Name (N : Node_Id) return Boolean is
16141 begin
16142 if not Is_List_Member (N) then
16143 declare
16144 P : constant Node_Id := Parent (N);
16145 begin
16146 return Nkind_In (P, N_Expanded_Name,
16147 N_Generic_Association,
16148 N_Parameter_Association,
16149 N_Selected_Component)
16150 and then Selector_Name (P) = N;
16151 end;
16153 else
16154 declare
16155 L : constant List_Id := List_Containing (N);
16156 P : constant Node_Id := Parent (L);
16157 begin
16158 return (Nkind (P) = N_Discriminant_Association
16159 and then Selector_Names (P) = L)
16160 or else
16161 (Nkind (P) = N_Component_Association
16162 and then Choices (P) = L);
16163 end;
16164 end if;
16165 end Is_Selector_Name;
16167 ---------------------------------
16168 -- Is_Single_Concurrent_Object --
16169 ---------------------------------
16171 function Is_Single_Concurrent_Object (Id : Entity_Id) return Boolean is
16172 begin
16173 return
16174 Is_Single_Protected_Object (Id) or else Is_Single_Task_Object (Id);
16175 end Is_Single_Concurrent_Object;
16177 -------------------------------
16178 -- Is_Single_Concurrent_Type --
16179 -------------------------------
16181 function Is_Single_Concurrent_Type (Id : Entity_Id) return Boolean is
16182 begin
16183 return
16184 Ekind_In (Id, E_Protected_Type, E_Task_Type)
16185 and then Is_Single_Concurrent_Type_Declaration
16186 (Declaration_Node (Id));
16187 end Is_Single_Concurrent_Type;
16189 -------------------------------------------
16190 -- Is_Single_Concurrent_Type_Declaration --
16191 -------------------------------------------
16193 function Is_Single_Concurrent_Type_Declaration
16194 (N : Node_Id) return Boolean
16196 begin
16197 return Nkind_In (Original_Node (N), N_Single_Protected_Declaration,
16198 N_Single_Task_Declaration);
16199 end Is_Single_Concurrent_Type_Declaration;
16201 ---------------------------------------------
16202 -- Is_Single_Precision_Floating_Point_Type --
16203 ---------------------------------------------
16205 function Is_Single_Precision_Floating_Point_Type
16206 (E : Entity_Id) return Boolean is
16207 begin
16208 return Is_Floating_Point_Type (E)
16209 and then Machine_Radix_Value (E) = Uint_2
16210 and then Machine_Mantissa_Value (E) = Uint_24
16211 and then Machine_Emax_Value (E) = Uint_2 ** Uint_7
16212 and then Machine_Emin_Value (E) = Uint_3 - (Uint_2 ** Uint_7);
16213 end Is_Single_Precision_Floating_Point_Type;
16215 --------------------------------
16216 -- Is_Single_Protected_Object --
16217 --------------------------------
16219 function Is_Single_Protected_Object (Id : Entity_Id) return Boolean is
16220 begin
16221 return
16222 Ekind (Id) = E_Variable
16223 and then Ekind (Etype (Id)) = E_Protected_Type
16224 and then Is_Single_Concurrent_Type (Etype (Id));
16225 end Is_Single_Protected_Object;
16227 ---------------------------
16228 -- Is_Single_Task_Object --
16229 ---------------------------
16231 function Is_Single_Task_Object (Id : Entity_Id) return Boolean is
16232 begin
16233 return
16234 Ekind (Id) = E_Variable
16235 and then Ekind (Etype (Id)) = E_Task_Type
16236 and then Is_Single_Concurrent_Type (Etype (Id));
16237 end Is_Single_Task_Object;
16239 -------------------------------------
16240 -- Is_SPARK_05_Initialization_Expr --
16241 -------------------------------------
16243 function Is_SPARK_05_Initialization_Expr (N : Node_Id) return Boolean is
16244 Is_Ok : Boolean;
16245 Expr : Node_Id;
16246 Comp_Assn : Node_Id;
16247 Orig_N : constant Node_Id := Original_Node (N);
16249 begin
16250 Is_Ok := True;
16252 if not Comes_From_Source (Orig_N) then
16253 goto Done;
16254 end if;
16256 pragma Assert (Nkind (Orig_N) in N_Subexpr);
16258 case Nkind (Orig_N) is
16259 when N_Character_Literal
16260 | N_Integer_Literal
16261 | N_Real_Literal
16262 | N_String_Literal
16264 null;
16266 when N_Expanded_Name
16267 | N_Identifier
16269 if Is_Entity_Name (Orig_N)
16270 and then Present (Entity (Orig_N)) -- needed in some cases
16271 then
16272 case Ekind (Entity (Orig_N)) is
16273 when E_Constant
16274 | E_Enumeration_Literal
16275 | E_Named_Integer
16276 | E_Named_Real
16278 null;
16280 when others =>
16281 if Is_Type (Entity (Orig_N)) then
16282 null;
16283 else
16284 Is_Ok := False;
16285 end if;
16286 end case;
16287 end if;
16289 when N_Qualified_Expression
16290 | N_Type_Conversion
16292 Is_Ok := Is_SPARK_05_Initialization_Expr (Expression (Orig_N));
16294 when N_Unary_Op =>
16295 Is_Ok := Is_SPARK_05_Initialization_Expr (Right_Opnd (Orig_N));
16297 when N_Binary_Op
16298 | N_Membership_Test
16299 | N_Short_Circuit
16301 Is_Ok := Is_SPARK_05_Initialization_Expr (Left_Opnd (Orig_N))
16302 and then
16303 Is_SPARK_05_Initialization_Expr (Right_Opnd (Orig_N));
16305 when N_Aggregate
16306 | N_Extension_Aggregate
16308 if Nkind (Orig_N) = N_Extension_Aggregate then
16309 Is_Ok :=
16310 Is_SPARK_05_Initialization_Expr (Ancestor_Part (Orig_N));
16311 end if;
16313 Expr := First (Expressions (Orig_N));
16314 while Present (Expr) loop
16315 if not Is_SPARK_05_Initialization_Expr (Expr) then
16316 Is_Ok := False;
16317 goto Done;
16318 end if;
16320 Next (Expr);
16321 end loop;
16323 Comp_Assn := First (Component_Associations (Orig_N));
16324 while Present (Comp_Assn) loop
16325 Expr := Expression (Comp_Assn);
16327 -- Note: test for Present here needed for box assocation
16329 if Present (Expr)
16330 and then not Is_SPARK_05_Initialization_Expr (Expr)
16331 then
16332 Is_Ok := False;
16333 goto Done;
16334 end if;
16336 Next (Comp_Assn);
16337 end loop;
16339 when N_Attribute_Reference =>
16340 if Nkind (Prefix (Orig_N)) in N_Subexpr then
16341 Is_Ok := Is_SPARK_05_Initialization_Expr (Prefix (Orig_N));
16342 end if;
16344 Expr := First (Expressions (Orig_N));
16345 while Present (Expr) loop
16346 if not Is_SPARK_05_Initialization_Expr (Expr) then
16347 Is_Ok := False;
16348 goto Done;
16349 end if;
16351 Next (Expr);
16352 end loop;
16354 -- Selected components might be expanded named not yet resolved, so
16355 -- default on the safe side. (Eg on sparklex.ads)
16357 when N_Selected_Component =>
16358 null;
16360 when others =>
16361 Is_Ok := False;
16362 end case;
16364 <<Done>>
16365 return Is_Ok;
16366 end Is_SPARK_05_Initialization_Expr;
16368 ----------------------------------
16369 -- Is_SPARK_05_Object_Reference --
16370 ----------------------------------
16372 function Is_SPARK_05_Object_Reference (N : Node_Id) return Boolean is
16373 begin
16374 if Is_Entity_Name (N) then
16375 return Present (Entity (N))
16376 and then
16377 (Ekind_In (Entity (N), E_Constant, E_Variable)
16378 or else Ekind (Entity (N)) in Formal_Kind);
16380 else
16381 case Nkind (N) is
16382 when N_Selected_Component =>
16383 return Is_SPARK_05_Object_Reference (Prefix (N));
16385 when others =>
16386 return False;
16387 end case;
16388 end if;
16389 end Is_SPARK_05_Object_Reference;
16391 -----------------------------
16392 -- Is_Specific_Tagged_Type --
16393 -----------------------------
16395 function Is_Specific_Tagged_Type (Typ : Entity_Id) return Boolean is
16396 Full_Typ : Entity_Id;
16398 begin
16399 -- Handle private types
16401 if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
16402 Full_Typ := Full_View (Typ);
16403 else
16404 Full_Typ := Typ;
16405 end if;
16407 -- A specific tagged type is a non-class-wide tagged type
16409 return Is_Tagged_Type (Full_Typ) and not Is_Class_Wide_Type (Full_Typ);
16410 end Is_Specific_Tagged_Type;
16412 ------------------
16413 -- Is_Statement --
16414 ------------------
16416 function Is_Statement (N : Node_Id) return Boolean is
16417 begin
16418 return
16419 Nkind (N) in N_Statement_Other_Than_Procedure_Call
16420 or else Nkind (N) = N_Procedure_Call_Statement;
16421 end Is_Statement;
16423 ---------------------------------------
16424 -- Is_Subprogram_Contract_Annotation --
16425 ---------------------------------------
16427 function Is_Subprogram_Contract_Annotation
16428 (Item : Node_Id) return Boolean
16430 Nam : Name_Id;
16432 begin
16433 if Nkind (Item) = N_Aspect_Specification then
16434 Nam := Chars (Identifier (Item));
16436 else pragma Assert (Nkind (Item) = N_Pragma);
16437 Nam := Pragma_Name (Item);
16438 end if;
16440 return Nam = Name_Contract_Cases
16441 or else Nam = Name_Depends
16442 or else Nam = Name_Extensions_Visible
16443 or else Nam = Name_Global
16444 or else Nam = Name_Post
16445 or else Nam = Name_Post_Class
16446 or else Nam = Name_Postcondition
16447 or else Nam = Name_Pre
16448 or else Nam = Name_Pre_Class
16449 or else Nam = Name_Precondition
16450 or else Nam = Name_Refined_Depends
16451 or else Nam = Name_Refined_Global
16452 or else Nam = Name_Refined_Post
16453 or else Nam = Name_Test_Case;
16454 end Is_Subprogram_Contract_Annotation;
16456 --------------------------------------------------
16457 -- Is_Subprogram_Stub_Without_Prior_Declaration --
16458 --------------------------------------------------
16460 function Is_Subprogram_Stub_Without_Prior_Declaration
16461 (N : Node_Id) return Boolean
16463 begin
16464 -- A subprogram stub without prior declaration serves as declaration for
16465 -- the actual subprogram body. As such, it has an attached defining
16466 -- entity of E_[Generic_]Function or E_[Generic_]Procedure.
16468 return Nkind (N) = N_Subprogram_Body_Stub
16469 and then Ekind (Defining_Entity (N)) /= E_Subprogram_Body;
16470 end Is_Subprogram_Stub_Without_Prior_Declaration;
16472 --------------------------
16473 -- Is_Suspension_Object --
16474 --------------------------
16476 function Is_Suspension_Object (Id : Entity_Id) return Boolean is
16477 begin
16478 -- This approach does an exact name match rather than to rely on
16479 -- RTSfind. Routine Is_Effectively_Volatile is used by clients of the
16480 -- front end at point where all auxiliary tables are locked and any
16481 -- modifications to them are treated as violations. Do not tamper with
16482 -- the tables, instead examine the Chars fields of all the scopes of Id.
16484 return
16485 Chars (Id) = Name_Suspension_Object
16486 and then Present (Scope (Id))
16487 and then Chars (Scope (Id)) = Name_Synchronous_Task_Control
16488 and then Present (Scope (Scope (Id)))
16489 and then Chars (Scope (Scope (Id))) = Name_Ada
16490 and then Present (Scope (Scope (Scope (Id))))
16491 and then Scope (Scope (Scope (Id))) = Standard_Standard;
16492 end Is_Suspension_Object;
16494 ----------------------------
16495 -- Is_Synchronized_Object --
16496 ----------------------------
16498 function Is_Synchronized_Object (Id : Entity_Id) return Boolean is
16499 Prag : Node_Id;
16501 begin
16502 if Is_Object (Id) then
16504 -- The object is synchronized if it is of a type that yields a
16505 -- synchronized object.
16507 if Yields_Synchronized_Object (Etype (Id)) then
16508 return True;
16510 -- The object is synchronized if it is atomic and Async_Writers is
16511 -- enabled.
16513 elsif Is_Atomic (Id) and then Async_Writers_Enabled (Id) then
16514 return True;
16516 -- A constant is a synchronized object by default
16518 elsif Ekind (Id) = E_Constant then
16519 return True;
16521 -- A variable is a synchronized object if it is subject to pragma
16522 -- Constant_After_Elaboration.
16524 elsif Ekind (Id) = E_Variable then
16525 Prag := Get_Pragma (Id, Pragma_Constant_After_Elaboration);
16527 return Present (Prag) and then Is_Enabled_Pragma (Prag);
16528 end if;
16529 end if;
16531 -- Otherwise the input is not an object or it does not qualify as a
16532 -- synchronized object.
16534 return False;
16535 end Is_Synchronized_Object;
16537 ---------------------------------
16538 -- Is_Synchronized_Tagged_Type --
16539 ---------------------------------
16541 function Is_Synchronized_Tagged_Type (E : Entity_Id) return Boolean is
16542 Kind : constant Entity_Kind := Ekind (Base_Type (E));
16544 begin
16545 -- A task or protected type derived from an interface is a tagged type.
16546 -- Such a tagged type is called a synchronized tagged type, as are
16547 -- synchronized interfaces and private extensions whose declaration
16548 -- includes the reserved word synchronized.
16550 return (Is_Tagged_Type (E)
16551 and then (Kind = E_Task_Type
16552 or else
16553 Kind = E_Protected_Type))
16554 or else
16555 (Is_Interface (E)
16556 and then Is_Synchronized_Interface (E))
16557 or else
16558 (Ekind (E) = E_Record_Type_With_Private
16559 and then Nkind (Parent (E)) = N_Private_Extension_Declaration
16560 and then (Synchronized_Present (Parent (E))
16561 or else Is_Synchronized_Interface (Etype (E))));
16562 end Is_Synchronized_Tagged_Type;
16564 -----------------
16565 -- Is_Transfer --
16566 -----------------
16568 function Is_Transfer (N : Node_Id) return Boolean is
16569 Kind : constant Node_Kind := Nkind (N);
16571 begin
16572 if Kind = N_Simple_Return_Statement
16573 or else
16574 Kind = N_Extended_Return_Statement
16575 or else
16576 Kind = N_Goto_Statement
16577 or else
16578 Kind = N_Raise_Statement
16579 or else
16580 Kind = N_Requeue_Statement
16581 then
16582 return True;
16584 elsif (Kind = N_Exit_Statement or else Kind in N_Raise_xxx_Error)
16585 and then No (Condition (N))
16586 then
16587 return True;
16589 elsif Kind = N_Procedure_Call_Statement
16590 and then Is_Entity_Name (Name (N))
16591 and then Present (Entity (Name (N)))
16592 and then No_Return (Entity (Name (N)))
16593 then
16594 return True;
16596 elsif Nkind (Original_Node (N)) = N_Raise_Statement then
16597 return True;
16599 else
16600 return False;
16601 end if;
16602 end Is_Transfer;
16604 -------------
16605 -- Is_True --
16606 -------------
16608 function Is_True (U : Uint) return Boolean is
16609 begin
16610 return (U /= 0);
16611 end Is_True;
16613 --------------------------------------
16614 -- Is_Unchecked_Conversion_Instance --
16615 --------------------------------------
16617 function Is_Unchecked_Conversion_Instance (Id : Entity_Id) return Boolean is
16618 Par : Node_Id;
16620 begin
16621 -- Look for a function whose generic parent is the predefined intrinsic
16622 -- function Unchecked_Conversion, or for one that renames such an
16623 -- instance.
16625 if Ekind (Id) = E_Function then
16626 Par := Parent (Id);
16628 if Nkind (Par) = N_Function_Specification then
16629 Par := Generic_Parent (Par);
16631 if Present (Par) then
16632 return
16633 Chars (Par) = Name_Unchecked_Conversion
16634 and then Is_Intrinsic_Subprogram (Par)
16635 and then In_Predefined_Unit (Par);
16636 else
16637 return
16638 Present (Alias (Id))
16639 and then Is_Unchecked_Conversion_Instance (Alias (Id));
16640 end if;
16641 end if;
16642 end if;
16644 return False;
16645 end Is_Unchecked_Conversion_Instance;
16647 -------------------------------
16648 -- Is_Universal_Numeric_Type --
16649 -------------------------------
16651 function Is_Universal_Numeric_Type (T : Entity_Id) return Boolean is
16652 begin
16653 return T = Universal_Integer or else T = Universal_Real;
16654 end Is_Universal_Numeric_Type;
16656 ------------------------------
16657 -- Is_User_Defined_Equality --
16658 ------------------------------
16660 function Is_User_Defined_Equality (Id : Entity_Id) return Boolean is
16661 begin
16662 return Ekind (Id) = E_Function
16663 and then Chars (Id) = Name_Op_Eq
16664 and then Comes_From_Source (Id)
16666 -- Internally generated equalities have a full type declaration
16667 -- as their parent.
16669 and then Nkind (Parent (Id)) = N_Function_Specification;
16670 end Is_User_Defined_Equality;
16672 --------------------------------------
16673 -- Is_Validation_Variable_Reference --
16674 --------------------------------------
16676 function Is_Validation_Variable_Reference (N : Node_Id) return Boolean is
16677 Var : constant Node_Id := Unqual_Conv (N);
16678 Var_Id : Entity_Id;
16680 begin
16681 Var_Id := Empty;
16683 if Is_Entity_Name (Var) then
16684 Var_Id := Entity (Var);
16685 end if;
16687 return
16688 Present (Var_Id)
16689 and then Ekind (Var_Id) = E_Variable
16690 and then Present (Validated_Object (Var_Id));
16691 end Is_Validation_Variable_Reference;
16693 ----------------------------
16694 -- Is_Variable_Size_Array --
16695 ----------------------------
16697 function Is_Variable_Size_Array (E : Entity_Id) return Boolean is
16698 Idx : Node_Id;
16700 begin
16701 pragma Assert (Is_Array_Type (E));
16703 -- Check if some index is initialized with a non-constant value
16705 Idx := First_Index (E);
16706 while Present (Idx) loop
16707 if Nkind (Idx) = N_Range then
16708 if not Is_Constant_Bound (Low_Bound (Idx))
16709 or else not Is_Constant_Bound (High_Bound (Idx))
16710 then
16711 return True;
16712 end if;
16713 end if;
16715 Idx := Next_Index (Idx);
16716 end loop;
16718 return False;
16719 end Is_Variable_Size_Array;
16721 -----------------------------
16722 -- Is_Variable_Size_Record --
16723 -----------------------------
16725 function Is_Variable_Size_Record (E : Entity_Id) return Boolean is
16726 Comp : Entity_Id;
16727 Comp_Typ : Entity_Id;
16729 begin
16730 pragma Assert (Is_Record_Type (E));
16732 Comp := First_Entity (E);
16733 while Present (Comp) loop
16734 Comp_Typ := Etype (Comp);
16736 -- Recursive call if the record type has discriminants
16738 if Is_Record_Type (Comp_Typ)
16739 and then Has_Discriminants (Comp_Typ)
16740 and then Is_Variable_Size_Record (Comp_Typ)
16741 then
16742 return True;
16744 elsif Is_Array_Type (Comp_Typ)
16745 and then Is_Variable_Size_Array (Comp_Typ)
16746 then
16747 return True;
16748 end if;
16750 Next_Entity (Comp);
16751 end loop;
16753 return False;
16754 end Is_Variable_Size_Record;
16756 -----------------
16757 -- Is_Variable --
16758 -----------------
16760 function Is_Variable
16761 (N : Node_Id;
16762 Use_Original_Node : Boolean := True) return Boolean
16764 Orig_Node : Node_Id;
16766 function In_Protected_Function (E : Entity_Id) return Boolean;
16767 -- Within a protected function, the private components of the enclosing
16768 -- protected type are constants. A function nested within a (protected)
16769 -- procedure is not itself protected. Within the body of a protected
16770 -- function the current instance of the protected type is a constant.
16772 function Is_Variable_Prefix (P : Node_Id) return Boolean;
16773 -- Prefixes can involve implicit dereferences, in which case we must
16774 -- test for the case of a reference of a constant access type, which can
16775 -- can never be a variable.
16777 ---------------------------
16778 -- In_Protected_Function --
16779 ---------------------------
16781 function In_Protected_Function (E : Entity_Id) return Boolean is
16782 Prot : Entity_Id;
16783 S : Entity_Id;
16785 begin
16786 -- E is the current instance of a type
16788 if Is_Type (E) then
16789 Prot := E;
16791 -- E is an object
16793 else
16794 Prot := Scope (E);
16795 end if;
16797 if not Is_Protected_Type (Prot) then
16798 return False;
16800 else
16801 S := Current_Scope;
16802 while Present (S) and then S /= Prot loop
16803 if Ekind (S) = E_Function and then Scope (S) = Prot then
16804 return True;
16805 end if;
16807 S := Scope (S);
16808 end loop;
16810 return False;
16811 end if;
16812 end In_Protected_Function;
16814 ------------------------
16815 -- Is_Variable_Prefix --
16816 ------------------------
16818 function Is_Variable_Prefix (P : Node_Id) return Boolean is
16819 begin
16820 if Is_Access_Type (Etype (P)) then
16821 return not Is_Access_Constant (Root_Type (Etype (P)));
16823 -- For the case of an indexed component whose prefix has a packed
16824 -- array type, the prefix has been rewritten into a type conversion.
16825 -- Determine variable-ness from the converted expression.
16827 elsif Nkind (P) = N_Type_Conversion
16828 and then not Comes_From_Source (P)
16829 and then Is_Array_Type (Etype (P))
16830 and then Is_Packed (Etype (P))
16831 then
16832 return Is_Variable (Expression (P));
16834 else
16835 return Is_Variable (P);
16836 end if;
16837 end Is_Variable_Prefix;
16839 -- Start of processing for Is_Variable
16841 begin
16842 -- Special check, allow x'Deref(expr) as a variable
16844 if Nkind (N) = N_Attribute_Reference
16845 and then Attribute_Name (N) = Name_Deref
16846 then
16847 return True;
16848 end if;
16850 -- Check if we perform the test on the original node since this may be a
16851 -- test of syntactic categories which must not be disturbed by whatever
16852 -- rewriting might have occurred. For example, an aggregate, which is
16853 -- certainly NOT a variable, could be turned into a variable by
16854 -- expansion.
16856 if Use_Original_Node then
16857 Orig_Node := Original_Node (N);
16858 else
16859 Orig_Node := N;
16860 end if;
16862 -- Definitely OK if Assignment_OK is set. Since this is something that
16863 -- only gets set for expanded nodes, the test is on N, not Orig_Node.
16865 if Nkind (N) in N_Subexpr and then Assignment_OK (N) then
16866 return True;
16868 -- Normally we go to the original node, but there is one exception where
16869 -- we use the rewritten node, namely when it is an explicit dereference.
16870 -- The generated code may rewrite a prefix which is an access type with
16871 -- an explicit dereference. The dereference is a variable, even though
16872 -- the original node may not be (since it could be a constant of the
16873 -- access type).
16875 -- In Ada 2005 we have a further case to consider: the prefix may be a
16876 -- function call given in prefix notation. The original node appears to
16877 -- be a selected component, but we need to examine the call.
16879 elsif Nkind (N) = N_Explicit_Dereference
16880 and then Nkind (Orig_Node) /= N_Explicit_Dereference
16881 and then Present (Etype (Orig_Node))
16882 and then Is_Access_Type (Etype (Orig_Node))
16883 then
16884 -- Note that if the prefix is an explicit dereference that does not
16885 -- come from source, we must check for a rewritten function call in
16886 -- prefixed notation before other forms of rewriting, to prevent a
16887 -- compiler crash.
16889 return
16890 (Nkind (Orig_Node) = N_Function_Call
16891 and then not Is_Access_Constant (Etype (Prefix (N))))
16892 or else
16893 Is_Variable_Prefix (Original_Node (Prefix (N)));
16895 -- in Ada 2012, the dereference may have been added for a type with
16896 -- a declared implicit dereference aspect. Check that it is not an
16897 -- access to constant.
16899 elsif Nkind (N) = N_Explicit_Dereference
16900 and then Present (Etype (Orig_Node))
16901 and then Ada_Version >= Ada_2012
16902 and then Has_Implicit_Dereference (Etype (Orig_Node))
16903 then
16904 return not Is_Access_Constant (Etype (Prefix (N)));
16906 -- A function call is never a variable
16908 elsif Nkind (N) = N_Function_Call then
16909 return False;
16911 -- All remaining checks use the original node
16913 elsif Is_Entity_Name (Orig_Node)
16914 and then Present (Entity (Orig_Node))
16915 then
16916 declare
16917 E : constant Entity_Id := Entity (Orig_Node);
16918 K : constant Entity_Kind := Ekind (E);
16920 begin
16921 return (K = E_Variable
16922 and then Nkind (Parent (E)) /= N_Exception_Handler)
16923 or else (K = E_Component
16924 and then not In_Protected_Function (E))
16925 or else K = E_Out_Parameter
16926 or else K = E_In_Out_Parameter
16927 or else K = E_Generic_In_Out_Parameter
16929 -- Current instance of type. If this is a protected type, check
16930 -- we are not within the body of one of its protected functions.
16932 or else (Is_Type (E)
16933 and then In_Open_Scopes (E)
16934 and then not In_Protected_Function (E))
16936 or else (Is_Incomplete_Or_Private_Type (E)
16937 and then In_Open_Scopes (Full_View (E)));
16938 end;
16940 else
16941 case Nkind (Orig_Node) is
16942 when N_Indexed_Component
16943 | N_Slice
16945 return Is_Variable_Prefix (Prefix (Orig_Node));
16947 when N_Selected_Component =>
16948 return (Is_Variable (Selector_Name (Orig_Node))
16949 and then Is_Variable_Prefix (Prefix (Orig_Node)))
16950 or else
16951 (Nkind (N) = N_Expanded_Name
16952 and then Scope (Entity (N)) = Entity (Prefix (N)));
16954 -- For an explicit dereference, the type of the prefix cannot
16955 -- be an access to constant or an access to subprogram.
16957 when N_Explicit_Dereference =>
16958 declare
16959 Typ : constant Entity_Id := Etype (Prefix (Orig_Node));
16960 begin
16961 return Is_Access_Type (Typ)
16962 and then not Is_Access_Constant (Root_Type (Typ))
16963 and then Ekind (Typ) /= E_Access_Subprogram_Type;
16964 end;
16966 -- The type conversion is the case where we do not deal with the
16967 -- context dependent special case of an actual parameter. Thus
16968 -- the type conversion is only considered a variable for the
16969 -- purposes of this routine if the target type is tagged. However,
16970 -- a type conversion is considered to be a variable if it does not
16971 -- come from source (this deals for example with the conversions
16972 -- of expressions to their actual subtypes).
16974 when N_Type_Conversion =>
16975 return Is_Variable (Expression (Orig_Node))
16976 and then
16977 (not Comes_From_Source (Orig_Node)
16978 or else
16979 (Is_Tagged_Type (Etype (Subtype_Mark (Orig_Node)))
16980 and then
16981 Is_Tagged_Type (Etype (Expression (Orig_Node)))));
16983 -- GNAT allows an unchecked type conversion as a variable. This
16984 -- only affects the generation of internal expanded code, since
16985 -- calls to instantiations of Unchecked_Conversion are never
16986 -- considered variables (since they are function calls).
16988 when N_Unchecked_Type_Conversion =>
16989 return Is_Variable (Expression (Orig_Node));
16991 when others =>
16992 return False;
16993 end case;
16994 end if;
16995 end Is_Variable;
16997 ------------------------------
16998 -- Is_Verifiable_DIC_Pragma --
16999 ------------------------------
17001 function Is_Verifiable_DIC_Pragma (Prag : Node_Id) return Boolean is
17002 Args : constant List_Id := Pragma_Argument_Associations (Prag);
17004 begin
17005 -- To qualify as verifiable, a DIC pragma must have a non-null argument
17007 return
17008 Present (Args)
17009 and then Nkind (Get_Pragma_Arg (First (Args))) /= N_Null;
17010 end Is_Verifiable_DIC_Pragma;
17012 ---------------------------
17013 -- Is_Visibly_Controlled --
17014 ---------------------------
17016 function Is_Visibly_Controlled (T : Entity_Id) return Boolean is
17017 Root : constant Entity_Id := Root_Type (T);
17018 begin
17019 return Chars (Scope (Root)) = Name_Finalization
17020 and then Chars (Scope (Scope (Root))) = Name_Ada
17021 and then Scope (Scope (Scope (Root))) = Standard_Standard;
17022 end Is_Visibly_Controlled;
17024 --------------------------
17025 -- Is_Volatile_Function --
17026 --------------------------
17028 function Is_Volatile_Function (Func_Id : Entity_Id) return Boolean is
17029 begin
17030 pragma Assert (Ekind_In (Func_Id, E_Function, E_Generic_Function));
17032 -- A function declared within a protected type is volatile
17034 if Is_Protected_Type (Scope (Func_Id)) then
17035 return True;
17037 -- An instance of Ada.Unchecked_Conversion is a volatile function if
17038 -- either the source or the target are effectively volatile.
17040 elsif Is_Unchecked_Conversion_Instance (Func_Id)
17041 and then Has_Effectively_Volatile_Profile (Func_Id)
17042 then
17043 return True;
17045 -- Otherwise the function is treated as volatile if it is subject to
17046 -- enabled pragma Volatile_Function.
17048 else
17049 return
17050 Is_Enabled_Pragma (Get_Pragma (Func_Id, Pragma_Volatile_Function));
17051 end if;
17052 end Is_Volatile_Function;
17054 ------------------------
17055 -- Is_Volatile_Object --
17056 ------------------------
17058 function Is_Volatile_Object (N : Node_Id) return Boolean is
17059 function Is_Volatile_Prefix (N : Node_Id) return Boolean;
17060 -- If prefix is an implicit dereference, examine designated type
17062 function Object_Has_Volatile_Components (N : Node_Id) return Boolean;
17063 -- Determines if given object has volatile components
17065 ------------------------
17066 -- Is_Volatile_Prefix --
17067 ------------------------
17069 function Is_Volatile_Prefix (N : Node_Id) return Boolean is
17070 Typ : constant Entity_Id := Etype (N);
17072 begin
17073 if Is_Access_Type (Typ) then
17074 declare
17075 Dtyp : constant Entity_Id := Designated_Type (Typ);
17077 begin
17078 return Is_Volatile (Dtyp)
17079 or else Has_Volatile_Components (Dtyp);
17080 end;
17082 else
17083 return Object_Has_Volatile_Components (N);
17084 end if;
17085 end Is_Volatile_Prefix;
17087 ------------------------------------
17088 -- Object_Has_Volatile_Components --
17089 ------------------------------------
17091 function Object_Has_Volatile_Components (N : Node_Id) return Boolean is
17092 Typ : constant Entity_Id := Etype (N);
17094 begin
17095 if Is_Volatile (Typ)
17096 or else Has_Volatile_Components (Typ)
17097 then
17098 return True;
17100 elsif Is_Entity_Name (N)
17101 and then (Has_Volatile_Components (Entity (N))
17102 or else Is_Volatile (Entity (N)))
17103 then
17104 return True;
17106 elsif Nkind (N) = N_Indexed_Component
17107 or else Nkind (N) = N_Selected_Component
17108 then
17109 return Is_Volatile_Prefix (Prefix (N));
17111 else
17112 return False;
17113 end if;
17114 end Object_Has_Volatile_Components;
17116 -- Start of processing for Is_Volatile_Object
17118 begin
17119 if Nkind (N) = N_Defining_Identifier then
17120 return Is_Volatile (N) or else Is_Volatile (Etype (N));
17122 elsif Nkind (N) = N_Expanded_Name then
17123 return Is_Volatile_Object (Entity (N));
17125 elsif Is_Volatile (Etype (N))
17126 or else (Is_Entity_Name (N) and then Is_Volatile (Entity (N)))
17127 then
17128 return True;
17130 elsif Nkind_In (N, N_Indexed_Component, N_Selected_Component)
17131 and then Is_Volatile_Prefix (Prefix (N))
17132 then
17133 return True;
17135 elsif Nkind (N) = N_Selected_Component
17136 and then Is_Volatile (Entity (Selector_Name (N)))
17137 then
17138 return True;
17140 else
17141 return False;
17142 end if;
17143 end Is_Volatile_Object;
17145 -----------------------------
17146 -- Iterate_Call_Parameters --
17147 -----------------------------
17149 procedure Iterate_Call_Parameters (Call : Node_Id) is
17150 Formal : Entity_Id := First_Formal (Get_Called_Entity (Call));
17151 Actual : Node_Id := First_Actual (Call);
17153 begin
17154 while Present (Formal) and then Present (Actual) loop
17155 Handle_Parameter (Formal, Actual);
17156 Formal := Next_Formal (Formal);
17157 Actual := Next_Actual (Actual);
17158 end loop;
17159 end Iterate_Call_Parameters;
17161 ---------------------------
17162 -- Itype_Has_Declaration --
17163 ---------------------------
17165 function Itype_Has_Declaration (Id : Entity_Id) return Boolean is
17166 begin
17167 pragma Assert (Is_Itype (Id));
17168 return Present (Parent (Id))
17169 and then Nkind_In (Parent (Id), N_Full_Type_Declaration,
17170 N_Subtype_Declaration)
17171 and then Defining_Entity (Parent (Id)) = Id;
17172 end Itype_Has_Declaration;
17174 -------------------------
17175 -- Kill_Current_Values --
17176 -------------------------
17178 procedure Kill_Current_Values
17179 (Ent : Entity_Id;
17180 Last_Assignment_Only : Boolean := False)
17182 begin
17183 if Is_Assignable (Ent) then
17184 Set_Last_Assignment (Ent, Empty);
17185 end if;
17187 if Is_Object (Ent) then
17188 if not Last_Assignment_Only then
17189 Kill_Checks (Ent);
17190 Set_Current_Value (Ent, Empty);
17192 -- Do not reset the Is_Known_[Non_]Null and Is_Known_Valid flags
17193 -- for a constant. Once the constant is elaborated, its value is
17194 -- not changed, therefore the associated flags that describe the
17195 -- value should not be modified either.
17197 if Ekind (Ent) = E_Constant then
17198 null;
17200 -- Non-constant entities
17202 else
17203 if not Can_Never_Be_Null (Ent) then
17204 Set_Is_Known_Non_Null (Ent, False);
17205 end if;
17207 Set_Is_Known_Null (Ent, False);
17209 -- Reset the Is_Known_Valid flag unless the type is always
17210 -- valid. This does not apply to a loop parameter because its
17211 -- bounds are defined by the loop header and therefore always
17212 -- valid.
17214 if not Is_Known_Valid (Etype (Ent))
17215 and then Ekind (Ent) /= E_Loop_Parameter
17216 then
17217 Set_Is_Known_Valid (Ent, False);
17218 end if;
17219 end if;
17220 end if;
17221 end if;
17222 end Kill_Current_Values;
17224 procedure Kill_Current_Values (Last_Assignment_Only : Boolean := False) is
17225 S : Entity_Id;
17227 procedure Kill_Current_Values_For_Entity_Chain (E : Entity_Id);
17228 -- Clear current value for entity E and all entities chained to E
17230 ------------------------------------------
17231 -- Kill_Current_Values_For_Entity_Chain --
17232 ------------------------------------------
17234 procedure Kill_Current_Values_For_Entity_Chain (E : Entity_Id) is
17235 Ent : Entity_Id;
17236 begin
17237 Ent := E;
17238 while Present (Ent) loop
17239 Kill_Current_Values (Ent, Last_Assignment_Only);
17240 Next_Entity (Ent);
17241 end loop;
17242 end Kill_Current_Values_For_Entity_Chain;
17244 -- Start of processing for Kill_Current_Values
17246 begin
17247 -- Kill all saved checks, a special case of killing saved values
17249 if not Last_Assignment_Only then
17250 Kill_All_Checks;
17251 end if;
17253 -- Loop through relevant scopes, which includes the current scope and
17254 -- any parent scopes if the current scope is a block or a package.
17256 S := Current_Scope;
17257 Scope_Loop : loop
17259 -- Clear current values of all entities in current scope
17261 Kill_Current_Values_For_Entity_Chain (First_Entity (S));
17263 -- If scope is a package, also clear current values of all private
17264 -- entities in the scope.
17266 if Is_Package_Or_Generic_Package (S)
17267 or else Is_Concurrent_Type (S)
17268 then
17269 Kill_Current_Values_For_Entity_Chain (First_Private_Entity (S));
17270 end if;
17272 -- If this is a not a subprogram, deal with parents
17274 if not Is_Subprogram (S) then
17275 S := Scope (S);
17276 exit Scope_Loop when S = Standard_Standard;
17277 else
17278 exit Scope_Loop;
17279 end if;
17280 end loop Scope_Loop;
17281 end Kill_Current_Values;
17283 --------------------------
17284 -- Kill_Size_Check_Code --
17285 --------------------------
17287 procedure Kill_Size_Check_Code (E : Entity_Id) is
17288 begin
17289 if (Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
17290 and then Present (Size_Check_Code (E))
17291 then
17292 Remove (Size_Check_Code (E));
17293 Set_Size_Check_Code (E, Empty);
17294 end if;
17295 end Kill_Size_Check_Code;
17297 --------------------
17298 -- Known_Non_Null --
17299 --------------------
17301 function Known_Non_Null (N : Node_Id) return Boolean is
17302 Status : constant Null_Status_Kind := Null_Status (N);
17304 Id : Entity_Id;
17305 Op : Node_Kind;
17306 Val : Node_Id;
17308 begin
17309 -- The expression yields a non-null value ignoring simple flow analysis
17311 if Status = Is_Non_Null then
17312 return True;
17314 -- Otherwise check whether N is a reference to an entity that appears
17315 -- within a conditional construct.
17317 elsif Is_Entity_Name (N) and then Present (Entity (N)) then
17319 -- First check if we are in decisive conditional
17321 Get_Current_Value_Condition (N, Op, Val);
17323 if Known_Null (Val) then
17324 if Op = N_Op_Eq then
17325 return False;
17326 elsif Op = N_Op_Ne then
17327 return True;
17328 end if;
17329 end if;
17331 -- If OK to do replacement, test Is_Known_Non_Null flag
17333 Id := Entity (N);
17335 if OK_To_Do_Constant_Replacement (Id) then
17336 return Is_Known_Non_Null (Id);
17337 end if;
17338 end if;
17340 -- Otherwise it is not possible to determine whether N yields a non-null
17341 -- value.
17343 return False;
17344 end Known_Non_Null;
17346 ----------------
17347 -- Known_Null --
17348 ----------------
17350 function Known_Null (N : Node_Id) return Boolean is
17351 Status : constant Null_Status_Kind := Null_Status (N);
17353 Id : Entity_Id;
17354 Op : Node_Kind;
17355 Val : Node_Id;
17357 begin
17358 -- The expression yields a null value ignoring simple flow analysis
17360 if Status = Is_Null then
17361 return True;
17363 -- Otherwise check whether N is a reference to an entity that appears
17364 -- within a conditional construct.
17366 elsif Is_Entity_Name (N) and then Present (Entity (N)) then
17368 -- First check if we are in decisive conditional
17370 Get_Current_Value_Condition (N, Op, Val);
17372 if Known_Null (Val) then
17373 if Op = N_Op_Eq then
17374 return True;
17375 elsif Op = N_Op_Ne then
17376 return False;
17377 end if;
17378 end if;
17380 -- If OK to do replacement, test Is_Known_Null flag
17382 Id := Entity (N);
17384 if OK_To_Do_Constant_Replacement (Id) then
17385 return Is_Known_Null (Id);
17386 end if;
17387 end if;
17389 -- Otherwise it is not possible to determine whether N yields a null
17390 -- value.
17392 return False;
17393 end Known_Null;
17395 --------------------------
17396 -- Known_To_Be_Assigned --
17397 --------------------------
17399 function Known_To_Be_Assigned (N : Node_Id) return Boolean is
17400 P : constant Node_Id := Parent (N);
17402 begin
17403 case Nkind (P) is
17405 -- Test left side of assignment
17407 when N_Assignment_Statement =>
17408 return N = Name (P);
17410 -- Function call arguments are never lvalues
17412 when N_Function_Call =>
17413 return False;
17415 -- Positional parameter for procedure or accept call
17417 when N_Accept_Statement
17418 | N_Procedure_Call_Statement
17420 declare
17421 Proc : Entity_Id;
17422 Form : Entity_Id;
17423 Act : Node_Id;
17425 begin
17426 Proc := Get_Subprogram_Entity (P);
17428 if No (Proc) then
17429 return False;
17430 end if;
17432 -- If we are not a list member, something is strange, so
17433 -- be conservative and return False.
17435 if not Is_List_Member (N) then
17436 return False;
17437 end if;
17439 -- We are going to find the right formal by stepping forward
17440 -- through the formals, as we step backwards in the actuals.
17442 Form := First_Formal (Proc);
17443 Act := N;
17444 loop
17445 -- If no formal, something is weird, so be conservative
17446 -- and return False.
17448 if No (Form) then
17449 return False;
17450 end if;
17452 Prev (Act);
17453 exit when No (Act);
17454 Next_Formal (Form);
17455 end loop;
17457 return Ekind (Form) /= E_In_Parameter;
17458 end;
17460 -- Named parameter for procedure or accept call
17462 when N_Parameter_Association =>
17463 declare
17464 Proc : Entity_Id;
17465 Form : Entity_Id;
17467 begin
17468 Proc := Get_Subprogram_Entity (Parent (P));
17470 if No (Proc) then
17471 return False;
17472 end if;
17474 -- Loop through formals to find the one that matches
17476 Form := First_Formal (Proc);
17477 loop
17478 -- If no matching formal, that's peculiar, some kind of
17479 -- previous error, so return False to be conservative.
17480 -- Actually this also happens in legal code in the case
17481 -- where P is a parameter association for an Extra_Formal???
17483 if No (Form) then
17484 return False;
17485 end if;
17487 -- Else test for match
17489 if Chars (Form) = Chars (Selector_Name (P)) then
17490 return Ekind (Form) /= E_In_Parameter;
17491 end if;
17493 Next_Formal (Form);
17494 end loop;
17495 end;
17497 -- Test for appearing in a conversion that itself appears
17498 -- in an lvalue context, since this should be an lvalue.
17500 when N_Type_Conversion =>
17501 return Known_To_Be_Assigned (P);
17503 -- All other references are definitely not known to be modifications
17505 when others =>
17506 return False;
17507 end case;
17508 end Known_To_Be_Assigned;
17510 ---------------------------
17511 -- Last_Source_Statement --
17512 ---------------------------
17514 function Last_Source_Statement (HSS : Node_Id) return Node_Id is
17515 N : Node_Id;
17517 begin
17518 N := Last (Statements (HSS));
17519 while Present (N) loop
17520 exit when Comes_From_Source (N);
17521 Prev (N);
17522 end loop;
17524 return N;
17525 end Last_Source_Statement;
17527 -----------------------
17528 -- Mark_Coextensions --
17529 -----------------------
17531 procedure Mark_Coextensions (Context_Nod : Node_Id; Root_Nod : Node_Id) is
17532 Is_Dynamic : Boolean;
17533 -- Indicates whether the context causes nested coextensions to be
17534 -- dynamic or static
17536 function Mark_Allocator (N : Node_Id) return Traverse_Result;
17537 -- Recognize an allocator node and label it as a dynamic coextension
17539 --------------------
17540 -- Mark_Allocator --
17541 --------------------
17543 function Mark_Allocator (N : Node_Id) return Traverse_Result is
17544 begin
17545 if Nkind (N) = N_Allocator then
17546 if Is_Dynamic then
17547 Set_Is_Dynamic_Coextension (N);
17549 -- If the allocator expression is potentially dynamic, it may
17550 -- be expanded out of order and require dynamic allocation
17551 -- anyway, so we treat the coextension itself as dynamic.
17552 -- Potential optimization ???
17554 elsif Nkind (Expression (N)) = N_Qualified_Expression
17555 and then Nkind (Expression (Expression (N))) = N_Op_Concat
17556 then
17557 Set_Is_Dynamic_Coextension (N);
17558 else
17559 Set_Is_Static_Coextension (N);
17560 end if;
17561 end if;
17563 return OK;
17564 end Mark_Allocator;
17566 procedure Mark_Allocators is new Traverse_Proc (Mark_Allocator);
17568 -- Start of processing for Mark_Coextensions
17570 begin
17571 -- An allocator that appears on the right-hand side of an assignment is
17572 -- treated as a potentially dynamic coextension when the right-hand side
17573 -- is an allocator or a qualified expression.
17575 -- Obj := new ...'(new Coextension ...);
17577 if Nkind (Context_Nod) = N_Assignment_Statement then
17578 Is_Dynamic :=
17579 Nkind_In (Expression (Context_Nod), N_Allocator,
17580 N_Qualified_Expression);
17582 -- An allocator that appears within the expression of a simple return
17583 -- statement is treated as a potentially dynamic coextension when the
17584 -- expression is either aggregate, allocator, or qualified expression.
17586 -- return (new Coextension ...);
17587 -- return new ...'(new Coextension ...);
17589 elsif Nkind (Context_Nod) = N_Simple_Return_Statement then
17590 Is_Dynamic :=
17591 Nkind_In (Expression (Context_Nod), N_Aggregate,
17592 N_Allocator,
17593 N_Qualified_Expression);
17595 -- An alloctor that appears within the initialization expression of an
17596 -- object declaration is considered a potentially dynamic coextension
17597 -- when the initialization expression is an allocator or a qualified
17598 -- expression.
17600 -- Obj : ... := new ...'(new Coextension ...);
17602 -- A similar case arises when the object declaration is part of an
17603 -- extended return statement.
17605 -- return Obj : ... := new ...'(new Coextension ...);
17606 -- return Obj : ... := (new Coextension ...);
17608 elsif Nkind (Context_Nod) = N_Object_Declaration then
17609 Is_Dynamic :=
17610 Nkind_In (Root_Nod, N_Allocator, N_Qualified_Expression)
17611 or else
17612 Nkind (Parent (Context_Nod)) = N_Extended_Return_Statement;
17614 -- This routine should not be called with constructs that cannot contain
17615 -- coextensions.
17617 else
17618 raise Program_Error;
17619 end if;
17621 Mark_Allocators (Root_Nod);
17622 end Mark_Coextensions;
17624 ---------------------------------
17625 -- Mark_Elaboration_Attributes --
17626 ---------------------------------
17628 procedure Mark_Elaboration_Attributes
17629 (N_Id : Node_Or_Entity_Id;
17630 Checks : Boolean := False;
17631 Level : Boolean := False;
17632 Modes : Boolean := False;
17633 Warnings : Boolean := False)
17635 function Elaboration_Checks_OK
17636 (Target_Id : Entity_Id;
17637 Context_Id : Entity_Id) return Boolean;
17638 -- Determine whether elaboration checks are enabled for target Target_Id
17639 -- which resides within context Context_Id.
17641 procedure Mark_Elaboration_Attributes_Id (Id : Entity_Id);
17642 -- Preserve relevant attributes of the context in arbitrary entity Id
17644 procedure Mark_Elaboration_Attributes_Node (N : Node_Id);
17645 -- Preserve relevant attributes of the context in arbitrary node N
17647 ---------------------------
17648 -- Elaboration_Checks_OK --
17649 ---------------------------
17651 function Elaboration_Checks_OK
17652 (Target_Id : Entity_Id;
17653 Context_Id : Entity_Id) return Boolean
17655 Encl_Scop : Entity_Id;
17657 begin
17658 -- Elaboration checks are suppressed for the target
17660 if Elaboration_Checks_Suppressed (Target_Id) then
17661 return False;
17662 end if;
17664 -- Otherwise elaboration checks are OK for the target, but may be
17665 -- suppressed for the context where the target is declared.
17667 Encl_Scop := Context_Id;
17668 while Present (Encl_Scop) and then Encl_Scop /= Standard_Standard loop
17669 if Elaboration_Checks_Suppressed (Encl_Scop) then
17670 return False;
17671 end if;
17673 Encl_Scop := Scope (Encl_Scop);
17674 end loop;
17676 -- Neither the target nor its declarative context have elaboration
17677 -- checks suppressed.
17679 return True;
17680 end Elaboration_Checks_OK;
17682 ------------------------------------
17683 -- Mark_Elaboration_Attributes_Id --
17684 ------------------------------------
17686 procedure Mark_Elaboration_Attributes_Id (Id : Entity_Id) is
17687 begin
17688 -- Mark the status of elaboration checks in effect. Do not reset the
17689 -- status in case the entity is reanalyzed with checks suppressed.
17691 if Checks and then not Is_Elaboration_Checks_OK_Id (Id) then
17692 Set_Is_Elaboration_Checks_OK_Id (Id,
17693 Elaboration_Checks_OK
17694 (Target_Id => Id,
17695 Context_Id => Scope (Id)));
17697 -- Entities do not need to capture their enclosing level. The Ghost
17698 -- and SPARK modes in effect are already marked during analysis.
17700 else
17701 null;
17702 end if;
17703 end Mark_Elaboration_Attributes_Id;
17705 --------------------------------------
17706 -- Mark_Elaboration_Attributes_Node --
17707 --------------------------------------
17709 procedure Mark_Elaboration_Attributes_Node (N : Node_Id) is
17710 function Extract_Name (N : Node_Id) return Node_Id;
17711 -- Obtain the Name attribute of call or instantiation N
17713 ------------------
17714 -- Extract_Name --
17715 ------------------
17717 function Extract_Name (N : Node_Id) return Node_Id is
17718 Nam : Node_Id;
17720 begin
17721 Nam := Name (N);
17723 -- A call to an entry family appears in indexed form
17725 if Nkind (Nam) = N_Indexed_Component then
17726 Nam := Prefix (Nam);
17727 end if;
17729 -- The name may also appear in qualified form
17731 if Nkind (Nam) = N_Selected_Component then
17732 Nam := Selector_Name (Nam);
17733 end if;
17735 return Nam;
17736 end Extract_Name;
17738 -- Local variables
17740 Context_Id : Entity_Id;
17741 Nam : Node_Id;
17743 -- Start of processing for Mark_Elaboration_Attributes_Node
17745 begin
17746 -- Mark the status of elaboration checks in effect. Do not reset the
17747 -- status in case the node is reanalyzed with checks suppressed.
17749 if Checks and then not Is_Elaboration_Checks_OK_Node (N) then
17751 -- Assignments, attribute references, and variable references do
17752 -- not have a "declarative" context.
17754 Context_Id := Empty;
17756 -- The status of elaboration checks for calls and instantiations
17757 -- depends on the most recent pragma Suppress/Unsuppress, as well
17758 -- as the suppression status of the context where the target is
17759 -- defined.
17761 -- package Pack is
17762 -- function Func ...;
17763 -- end Pack;
17765 -- with Pack;
17766 -- procedure Main is
17767 -- pragma Suppress (Elaboration_Checks, Pack);
17768 -- X : ... := Pack.Func;
17769 -- ...
17771 -- In the example above, the call to Func has elaboration checks
17772 -- enabled because there is no active general purpose suppression
17773 -- pragma, however the elaboration checks of Pack are explicitly
17774 -- suppressed. As a result the elaboration checks of the call must
17775 -- be disabled in order to preserve this dependency.
17777 if Nkind_In (N, N_Entry_Call_Statement,
17778 N_Function_Call,
17779 N_Function_Instantiation,
17780 N_Package_Instantiation,
17781 N_Procedure_Call_Statement,
17782 N_Procedure_Instantiation)
17783 then
17784 Nam := Extract_Name (N);
17786 if Is_Entity_Name (Nam) and then Present (Entity (Nam)) then
17787 Context_Id := Scope (Entity (Nam));
17788 end if;
17789 end if;
17791 Set_Is_Elaboration_Checks_OK_Node (N,
17792 Elaboration_Checks_OK
17793 (Target_Id => Empty,
17794 Context_Id => Context_Id));
17795 end if;
17797 -- Mark the enclosing level of the node. Do not reset the status in
17798 -- case the node is relocated and reanalyzed.
17800 if Level and then not Is_Declaration_Level_Node (N) then
17801 Set_Is_Declaration_Level_Node (N,
17802 Find_Enclosing_Level (N) = Declaration_Level);
17803 end if;
17805 -- Mark the Ghost and SPARK mode in effect
17807 if Modes then
17808 if Ghost_Mode = Ignore then
17809 Set_Is_Ignored_Ghost_Node (N);
17810 end if;
17812 if SPARK_Mode = On then
17813 Set_Is_SPARK_Mode_On_Node (N);
17814 end if;
17815 end if;
17817 -- Mark the status of elaboration warnings in effect. Do not reset
17818 -- the status in case the node is reanalyzed with warnings off.
17820 if Warnings and then not Is_Elaboration_Warnings_OK_Node (N) then
17821 Set_Is_Elaboration_Warnings_OK_Node (N, Elab_Warnings);
17822 end if;
17823 end Mark_Elaboration_Attributes_Node;
17825 -- Start of processing for Mark_Elaboration_Attributes
17827 begin
17828 -- Do not capture any elaboration-related attributes when switch -gnatH
17829 -- (legacy elaboration checking mode enabled) is in effect because the
17830 -- attributes are useless to the legacy model.
17832 if Legacy_Elaboration_Checks then
17833 return;
17834 end if;
17836 if Nkind (N_Id) in N_Entity then
17837 Mark_Elaboration_Attributes_Id (N_Id);
17838 else
17839 Mark_Elaboration_Attributes_Node (N_Id);
17840 end if;
17841 end Mark_Elaboration_Attributes;
17843 ----------------------------------
17844 -- Matching_Static_Array_Bounds --
17845 ----------------------------------
17847 function Matching_Static_Array_Bounds
17848 (L_Typ : Node_Id;
17849 R_Typ : Node_Id) return Boolean
17851 L_Ndims : constant Nat := Number_Dimensions (L_Typ);
17852 R_Ndims : constant Nat := Number_Dimensions (R_Typ);
17854 L_Index : Node_Id := Empty; -- init to ...
17855 R_Index : Node_Id := Empty; -- ...avoid warnings
17856 L_Low : Node_Id;
17857 L_High : Node_Id;
17858 L_Len : Uint;
17859 R_Low : Node_Id;
17860 R_High : Node_Id;
17861 R_Len : Uint;
17863 begin
17864 if L_Ndims /= R_Ndims then
17865 return False;
17866 end if;
17868 -- Unconstrained types do not have static bounds
17870 if not Is_Constrained (L_Typ) or else not Is_Constrained (R_Typ) then
17871 return False;
17872 end if;
17874 -- First treat specially the first dimension, as the lower bound and
17875 -- length of string literals are not stored like those of arrays.
17877 if Ekind (L_Typ) = E_String_Literal_Subtype then
17878 L_Low := String_Literal_Low_Bound (L_Typ);
17879 L_Len := String_Literal_Length (L_Typ);
17880 else
17881 L_Index := First_Index (L_Typ);
17882 Get_Index_Bounds (L_Index, L_Low, L_High);
17884 if Is_OK_Static_Expression (L_Low)
17885 and then
17886 Is_OK_Static_Expression (L_High)
17887 then
17888 if Expr_Value (L_High) < Expr_Value (L_Low) then
17889 L_Len := Uint_0;
17890 else
17891 L_Len := (Expr_Value (L_High) - Expr_Value (L_Low)) + 1;
17892 end if;
17893 else
17894 return False;
17895 end if;
17896 end if;
17898 if Ekind (R_Typ) = E_String_Literal_Subtype then
17899 R_Low := String_Literal_Low_Bound (R_Typ);
17900 R_Len := String_Literal_Length (R_Typ);
17901 else
17902 R_Index := First_Index (R_Typ);
17903 Get_Index_Bounds (R_Index, R_Low, R_High);
17905 if Is_OK_Static_Expression (R_Low)
17906 and then
17907 Is_OK_Static_Expression (R_High)
17908 then
17909 if Expr_Value (R_High) < Expr_Value (R_Low) then
17910 R_Len := Uint_0;
17911 else
17912 R_Len := (Expr_Value (R_High) - Expr_Value (R_Low)) + 1;
17913 end if;
17914 else
17915 return False;
17916 end if;
17917 end if;
17919 if (Is_OK_Static_Expression (L_Low)
17920 and then
17921 Is_OK_Static_Expression (R_Low))
17922 and then Expr_Value (L_Low) = Expr_Value (R_Low)
17923 and then L_Len = R_Len
17924 then
17925 null;
17926 else
17927 return False;
17928 end if;
17930 -- Then treat all other dimensions
17932 for Indx in 2 .. L_Ndims loop
17933 Next (L_Index);
17934 Next (R_Index);
17936 Get_Index_Bounds (L_Index, L_Low, L_High);
17937 Get_Index_Bounds (R_Index, R_Low, R_High);
17939 if (Is_OK_Static_Expression (L_Low) and then
17940 Is_OK_Static_Expression (L_High) and then
17941 Is_OK_Static_Expression (R_Low) and then
17942 Is_OK_Static_Expression (R_High))
17943 and then (Expr_Value (L_Low) = Expr_Value (R_Low)
17944 and then
17945 Expr_Value (L_High) = Expr_Value (R_High))
17946 then
17947 null;
17948 else
17949 return False;
17950 end if;
17951 end loop;
17953 -- If we fall through the loop, all indexes matched
17955 return True;
17956 end Matching_Static_Array_Bounds;
17958 -------------------
17959 -- May_Be_Lvalue --
17960 -------------------
17962 function May_Be_Lvalue (N : Node_Id) return Boolean is
17963 P : constant Node_Id := Parent (N);
17965 begin
17966 case Nkind (P) is
17968 -- Test left side of assignment
17970 when N_Assignment_Statement =>
17971 return N = Name (P);
17973 -- Test prefix of component or attribute. Note that the prefix of an
17974 -- explicit or implicit dereference cannot be an l-value. In the case
17975 -- of a 'Read attribute, the reference can be an actual in the
17976 -- argument list of the attribute.
17978 when N_Attribute_Reference =>
17979 return (N = Prefix (P)
17980 and then Name_Implies_Lvalue_Prefix (Attribute_Name (P)))
17981 or else
17982 Attribute_Name (P) = Name_Read;
17984 -- For an expanded name, the name is an lvalue if the expanded name
17985 -- is an lvalue, but the prefix is never an lvalue, since it is just
17986 -- the scope where the name is found.
17988 when N_Expanded_Name =>
17989 if N = Prefix (P) then
17990 return May_Be_Lvalue (P);
17991 else
17992 return False;
17993 end if;
17995 -- For a selected component A.B, A is certainly an lvalue if A.B is.
17996 -- B is a little interesting, if we have A.B := 3, there is some
17997 -- discussion as to whether B is an lvalue or not, we choose to say
17998 -- it is. Note however that A is not an lvalue if it is of an access
17999 -- type since this is an implicit dereference.
18001 when N_Selected_Component =>
18002 if N = Prefix (P)
18003 and then Present (Etype (N))
18004 and then Is_Access_Type (Etype (N))
18005 then
18006 return False;
18007 else
18008 return May_Be_Lvalue (P);
18009 end if;
18011 -- For an indexed component or slice, the index or slice bounds is
18012 -- never an lvalue. The prefix is an lvalue if the indexed component
18013 -- or slice is an lvalue, except if it is an access type, where we
18014 -- have an implicit dereference.
18016 when N_Indexed_Component
18017 | N_Slice
18019 if N /= Prefix (P)
18020 or else (Present (Etype (N)) and then Is_Access_Type (Etype (N)))
18021 then
18022 return False;
18023 else
18024 return May_Be_Lvalue (P);
18025 end if;
18027 -- Prefix of a reference is an lvalue if the reference is an lvalue
18029 when N_Reference =>
18030 return May_Be_Lvalue (P);
18032 -- Prefix of explicit dereference is never an lvalue
18034 when N_Explicit_Dereference =>
18035 return False;
18037 -- Positional parameter for subprogram, entry, or accept call.
18038 -- In older versions of Ada function call arguments are never
18039 -- lvalues. In Ada 2012 functions can have in-out parameters.
18041 when N_Accept_Statement
18042 | N_Entry_Call_Statement
18043 | N_Subprogram_Call
18045 if Nkind (P) = N_Function_Call and then Ada_Version < Ada_2012 then
18046 return False;
18047 end if;
18049 -- The following mechanism is clumsy and fragile. A single flag
18050 -- set in Resolve_Actuals would be preferable ???
18052 declare
18053 Proc : Entity_Id;
18054 Form : Entity_Id;
18055 Act : Node_Id;
18057 begin
18058 Proc := Get_Subprogram_Entity (P);
18060 if No (Proc) then
18061 return True;
18062 end if;
18064 -- If we are not a list member, something is strange, so be
18065 -- conservative and return True.
18067 if not Is_List_Member (N) then
18068 return True;
18069 end if;
18071 -- We are going to find the right formal by stepping forward
18072 -- through the formals, as we step backwards in the actuals.
18074 Form := First_Formal (Proc);
18075 Act := N;
18076 loop
18077 -- If no formal, something is weird, so be conservative and
18078 -- return True.
18080 if No (Form) then
18081 return True;
18082 end if;
18084 Prev (Act);
18085 exit when No (Act);
18086 Next_Formal (Form);
18087 end loop;
18089 return Ekind (Form) /= E_In_Parameter;
18090 end;
18092 -- Named parameter for procedure or accept call
18094 when N_Parameter_Association =>
18095 declare
18096 Proc : Entity_Id;
18097 Form : Entity_Id;
18099 begin
18100 Proc := Get_Subprogram_Entity (Parent (P));
18102 if No (Proc) then
18103 return True;
18104 end if;
18106 -- Loop through formals to find the one that matches
18108 Form := First_Formal (Proc);
18109 loop
18110 -- If no matching formal, that's peculiar, some kind of
18111 -- previous error, so return True to be conservative.
18112 -- Actually happens with legal code for an unresolved call
18113 -- where we may get the wrong homonym???
18115 if No (Form) then
18116 return True;
18117 end if;
18119 -- Else test for match
18121 if Chars (Form) = Chars (Selector_Name (P)) then
18122 return Ekind (Form) /= E_In_Parameter;
18123 end if;
18125 Next_Formal (Form);
18126 end loop;
18127 end;
18129 -- Test for appearing in a conversion that itself appears in an
18130 -- lvalue context, since this should be an lvalue.
18132 when N_Type_Conversion =>
18133 return May_Be_Lvalue (P);
18135 -- Test for appearance in object renaming declaration
18137 when N_Object_Renaming_Declaration =>
18138 return True;
18140 -- All other references are definitely not lvalues
18142 when others =>
18143 return False;
18144 end case;
18145 end May_Be_Lvalue;
18147 -----------------
18148 -- Might_Raise --
18149 -----------------
18151 function Might_Raise (N : Node_Id) return Boolean is
18152 Result : Boolean := False;
18154 function Process (N : Node_Id) return Traverse_Result;
18155 -- Set Result to True if we find something that could raise an exception
18157 -------------
18158 -- Process --
18159 -------------
18161 function Process (N : Node_Id) return Traverse_Result is
18162 begin
18163 if Nkind_In (N, N_Procedure_Call_Statement,
18164 N_Function_Call,
18165 N_Raise_Statement,
18166 N_Raise_Constraint_Error,
18167 N_Raise_Program_Error,
18168 N_Raise_Storage_Error)
18169 then
18170 Result := True;
18171 return Abandon;
18172 else
18173 return OK;
18174 end if;
18175 end Process;
18177 procedure Set_Result is new Traverse_Proc (Process);
18179 -- Start of processing for Might_Raise
18181 begin
18182 -- False if exceptions can't be propagated
18184 if No_Exception_Handlers_Set then
18185 return False;
18186 end if;
18188 -- If the checks handled by the back end are not disabled, we cannot
18189 -- ensure that no exception will be raised.
18191 if not Access_Checks_Suppressed (Empty)
18192 or else not Discriminant_Checks_Suppressed (Empty)
18193 or else not Range_Checks_Suppressed (Empty)
18194 or else not Index_Checks_Suppressed (Empty)
18195 or else Opt.Stack_Checking_Enabled
18196 then
18197 return True;
18198 end if;
18200 Set_Result (N);
18201 return Result;
18202 end Might_Raise;
18204 --------------------------------
18205 -- Nearest_Enclosing_Instance --
18206 --------------------------------
18208 function Nearest_Enclosing_Instance (E : Entity_Id) return Entity_Id is
18209 Inst : Entity_Id;
18211 begin
18212 Inst := Scope (E);
18213 while Present (Inst) and then Inst /= Standard_Standard loop
18214 if Is_Generic_Instance (Inst) then
18215 return Inst;
18216 end if;
18218 Inst := Scope (Inst);
18219 end loop;
18221 return Empty;
18222 end Nearest_Enclosing_Instance;
18224 ----------------------
18225 -- Needs_One_Actual --
18226 ----------------------
18228 function Needs_One_Actual (E : Entity_Id) return Boolean is
18229 Formal : Entity_Id;
18231 begin
18232 -- Ada 2005 or later, and formals present. The first formal must be
18233 -- of a type that supports prefix notation: a controlling argument,
18234 -- a class-wide type, or an access to such.
18236 if Ada_Version >= Ada_2005
18237 and then Present (First_Formal (E))
18238 and then No (Default_Value (First_Formal (E)))
18239 and then
18240 (Is_Controlling_Formal (First_Formal (E))
18241 or else Is_Class_Wide_Type (Etype (First_Formal (E)))
18242 or else Is_Anonymous_Access_Type (Etype (First_Formal (E))))
18243 then
18244 Formal := Next_Formal (First_Formal (E));
18245 while Present (Formal) loop
18246 if No (Default_Value (Formal)) then
18247 return False;
18248 end if;
18250 Next_Formal (Formal);
18251 end loop;
18253 return True;
18255 -- Ada 83/95 or no formals
18257 else
18258 return False;
18259 end if;
18260 end Needs_One_Actual;
18262 ------------------------
18263 -- New_Copy_List_Tree --
18264 ------------------------
18266 function New_Copy_List_Tree (List : List_Id) return List_Id is
18267 NL : List_Id;
18268 E : Node_Id;
18270 begin
18271 if List = No_List then
18272 return No_List;
18274 else
18275 NL := New_List;
18276 E := First (List);
18278 while Present (E) loop
18279 Append (New_Copy_Tree (E), NL);
18280 E := Next (E);
18281 end loop;
18283 return NL;
18284 end if;
18285 end New_Copy_List_Tree;
18287 -------------------
18288 -- New_Copy_Tree --
18289 -------------------
18291 -- The following tables play a key role in replicating entities and Itypes.
18292 -- They are intentionally declared at the library level rather than within
18293 -- New_Copy_Tree to avoid elaborating them on each call. This performance
18294 -- optimization saves up to 2% of the entire compilation time spent in the
18295 -- front end. Care should be taken to reset the tables on each new call to
18296 -- New_Copy_Tree.
18298 NCT_Table_Max : constant := 511;
18300 subtype NCT_Table_Index is Nat range 0 .. NCT_Table_Max - 1;
18302 function NCT_Table_Hash (Key : Node_Or_Entity_Id) return NCT_Table_Index;
18303 -- Obtain the hash value of node or entity Key
18305 --------------------
18306 -- NCT_Table_Hash --
18307 --------------------
18309 function NCT_Table_Hash (Key : Node_Or_Entity_Id) return NCT_Table_Index is
18310 begin
18311 return NCT_Table_Index (Key mod NCT_Table_Max);
18312 end NCT_Table_Hash;
18314 ----------------------
18315 -- NCT_New_Entities --
18316 ----------------------
18318 -- The following table maps old entities and Itypes to their corresponding
18319 -- new entities and Itypes.
18321 -- Aaa -> Xxx
18323 package NCT_New_Entities is new Simple_HTable (
18324 Header_Num => NCT_Table_Index,
18325 Element => Entity_Id,
18326 No_Element => Empty,
18327 Key => Entity_Id,
18328 Hash => NCT_Table_Hash,
18329 Equal => "=");
18331 ------------------------
18332 -- NCT_Pending_Itypes --
18333 ------------------------
18335 -- The following table maps old Associated_Node_For_Itype nodes to a set of
18336 -- new itypes. Given a set of old Itypes Aaa, Bbb, and Ccc, where all three
18337 -- have the same Associated_Node_For_Itype Ppp, and their corresponding new
18338 -- Itypes Xxx, Yyy, Zzz, the table contains the following mapping:
18340 -- Ppp -> (Xxx, Yyy, Zzz)
18342 -- The set is expressed as an Elist
18344 package NCT_Pending_Itypes is new Simple_HTable (
18345 Header_Num => NCT_Table_Index,
18346 Element => Elist_Id,
18347 No_Element => No_Elist,
18348 Key => Node_Id,
18349 Hash => NCT_Table_Hash,
18350 Equal => "=");
18352 NCT_Tables_In_Use : Boolean := False;
18353 -- This flag keeps track of whether the two tables NCT_New_Entities and
18354 -- NCT_Pending_Itypes are in use. The flag is part of an optimization
18355 -- where certain operations are not performed if the tables are not in
18356 -- use. This saves up to 8% of the entire compilation time spent in the
18357 -- front end.
18359 -------------------
18360 -- New_Copy_Tree --
18361 -------------------
18363 function New_Copy_Tree
18364 (Source : Node_Id;
18365 Map : Elist_Id := No_Elist;
18366 New_Sloc : Source_Ptr := No_Location;
18367 New_Scope : Entity_Id := Empty) return Node_Id
18369 -- This routine performs low-level tree manipulations and needs access
18370 -- to the internals of the tree.
18372 use Atree.Unchecked_Access;
18373 use Atree_Private_Part;
18375 EWA_Level : Nat := 0;
18376 -- This counter keeps track of how many N_Expression_With_Actions nodes
18377 -- are encountered during a depth-first traversal of the subtree. These
18378 -- nodes may define new entities in their Actions lists and thus require
18379 -- special processing.
18381 EWA_Inner_Scope_Level : Nat := 0;
18382 -- This counter keeps track of how many scoping constructs appear within
18383 -- an N_Expression_With_Actions node.
18385 procedure Add_New_Entity (Old_Id : Entity_Id; New_Id : Entity_Id);
18386 pragma Inline (Add_New_Entity);
18387 -- Add an entry in the NCT_New_Entities table which maps key Old_Id to
18388 -- value New_Id. Old_Id is an entity which appears within the Actions
18389 -- list of an N_Expression_With_Actions node, or within an entity map.
18390 -- New_Id is the corresponding new entity generated during Phase 1.
18392 procedure Add_Pending_Itype (Assoc_Nod : Node_Id; Itype : Entity_Id);
18393 pragma Inline (Add_New_Entity);
18394 -- Add an entry in the NCT_Pending_Itypes which maps key Assoc_Nod to
18395 -- value Itype. Assoc_Nod is the associated node of an itype. Itype is
18396 -- an itype.
18398 procedure Build_NCT_Tables (Entity_Map : Elist_Id);
18399 pragma Inline (Build_NCT_Tables);
18400 -- Populate tables NCT_New_Entities and NCT_Pending_Itypes with the
18401 -- information supplied in entity map Entity_Map. The format of the
18402 -- entity map must be as follows:
18404 -- Old_Id1, New_Id1, Old_Id2, New_Id2, .., Old_IdN, New_IdN
18406 function Copy_Any_Node_With_Replacement
18407 (N : Node_Or_Entity_Id) return Node_Or_Entity_Id;
18408 pragma Inline (Copy_Any_Node_With_Replacement);
18409 -- Replicate entity or node N by invoking one of the following routines:
18411 -- Copy_Node_With_Replacement
18412 -- Corresponding_Entity
18414 function Copy_Elist_With_Replacement (List : Elist_Id) return Elist_Id;
18415 -- Replicate the elements of entity list List
18417 function Copy_Field_With_Replacement
18418 (Field : Union_Id;
18419 Old_Par : Node_Id := Empty;
18420 New_Par : Node_Id := Empty;
18421 Semantic : Boolean := False) return Union_Id;
18422 -- Replicate field Field by invoking one of the following routines:
18424 -- Copy_Elist_With_Replacement
18425 -- Copy_List_With_Replacement
18426 -- Copy_Node_With_Replacement
18427 -- Corresponding_Entity
18429 -- If the field is not an entity list, entity, itype, syntactic list,
18430 -- or node, then the field is returned unchanged. The routine always
18431 -- replicates entities, itypes, and valid syntactic fields. Old_Par is
18432 -- the expected parent of a syntactic field. New_Par is the new parent
18433 -- associated with a replicated syntactic field. Flag Semantic should
18434 -- be set when the input is a semantic field.
18436 function Copy_List_With_Replacement (List : List_Id) return List_Id;
18437 -- Replicate the elements of syntactic list List
18439 function Copy_Node_With_Replacement (N : Node_Id) return Node_Id;
18440 -- Replicate node N
18442 function Corresponding_Entity (Id : Entity_Id) return Entity_Id;
18443 pragma Inline (Corresponding_Entity);
18444 -- Return the corresponding new entity of Id generated during Phase 1.
18445 -- If there is no such entity, return Id.
18447 function In_Entity_Map
18448 (Id : Entity_Id;
18449 Entity_Map : Elist_Id) return Boolean;
18450 pragma Inline (In_Entity_Map);
18451 -- Determine whether entity Id is one of the old ids specified in entity
18452 -- map Entity_Map. The format of the entity map must be as follows:
18454 -- Old_Id1, New_Id1, Old_Id2, New_Id2, .., Old_IdN, New_IdN
18456 procedure Update_CFS_Sloc (N : Node_Or_Entity_Id);
18457 pragma Inline (Update_CFS_Sloc);
18458 -- Update the Comes_From_Source and Sloc attributes of node or entity N
18460 procedure Update_First_Real_Statement
18461 (Old_HSS : Node_Id;
18462 New_HSS : Node_Id);
18463 pragma Inline (Update_First_Real_Statement);
18464 -- Update semantic attribute First_Real_Statement of handled sequence of
18465 -- statements New_HSS based on handled sequence of statements Old_HSS.
18467 procedure Update_Named_Associations
18468 (Old_Call : Node_Id;
18469 New_Call : Node_Id);
18470 pragma Inline (Update_Named_Associations);
18471 -- Update semantic chain First/Next_Named_Association of call New_call
18472 -- based on call Old_Call.
18474 procedure Update_New_Entities (Entity_Map : Elist_Id);
18475 pragma Inline (Update_New_Entities);
18476 -- Update the semantic attributes of all new entities generated during
18477 -- Phase 1 that do not appear in entity map Entity_Map. The format of
18478 -- the entity map must be as follows:
18480 -- Old_Id1, New_Id1, Old_Id2, New_Id2, .., Old_IdN, New_IdN
18482 procedure Update_Pending_Itypes
18483 (Old_Assoc : Node_Id;
18484 New_Assoc : Node_Id);
18485 pragma Inline (Update_Pending_Itypes);
18486 -- Update semantic attribute Associated_Node_For_Itype to refer to node
18487 -- New_Assoc for all itypes whose associated node is Old_Assoc.
18489 procedure Update_Semantic_Fields (Id : Entity_Id);
18490 pragma Inline (Update_Semantic_Fields);
18491 -- Subsidiary to Update_New_Entities. Update semantic fields of entity
18492 -- or itype Id.
18494 procedure Visit_Any_Node (N : Node_Or_Entity_Id);
18495 pragma Inline (Visit_Any_Node);
18496 -- Visit entity of node N by invoking one of the following routines:
18498 -- Visit_Entity
18499 -- Visit_Itype
18500 -- Visit_Node
18502 procedure Visit_Elist (List : Elist_Id);
18503 -- Visit the elements of entity list List
18505 procedure Visit_Entity (Id : Entity_Id);
18506 -- Visit entity Id. This action may create a new entity of Id and save
18507 -- it in table NCT_New_Entities.
18509 procedure Visit_Field
18510 (Field : Union_Id;
18511 Par_Nod : Node_Id := Empty;
18512 Semantic : Boolean := False);
18513 -- Visit field Field by invoking one of the following routines:
18515 -- Visit_Elist
18516 -- Visit_Entity
18517 -- Visit_Itype
18518 -- Visit_List
18519 -- Visit_Node
18521 -- If the field is not an entity list, entity, itype, syntactic list,
18522 -- or node, then the field is not visited. The routine always visits
18523 -- valid syntactic fields. Par_Nod is the expected parent of the
18524 -- syntactic field. Flag Semantic should be set when the input is a
18525 -- semantic field.
18527 procedure Visit_Itype (Itype : Entity_Id);
18528 -- Visit itype Itype. This action may create a new entity for Itype and
18529 -- save it in table NCT_New_Entities. In addition, the routine may map
18530 -- the associated node of Itype to the new itype in NCT_Pending_Itypes.
18532 procedure Visit_List (List : List_Id);
18533 -- Visit the elements of syntactic list List
18535 procedure Visit_Node (N : Node_Id);
18536 -- Visit node N
18538 procedure Visit_Semantic_Fields (Id : Entity_Id);
18539 pragma Inline (Visit_Semantic_Fields);
18540 -- Subsidiary to Visit_Entity and Visit_Itype. Visit common semantic
18541 -- fields of entity or itype Id.
18543 --------------------
18544 -- Add_New_Entity --
18545 --------------------
18547 procedure Add_New_Entity (Old_Id : Entity_Id; New_Id : Entity_Id) is
18548 begin
18549 pragma Assert (Present (Old_Id));
18550 pragma Assert (Present (New_Id));
18551 pragma Assert (Nkind (Old_Id) in N_Entity);
18552 pragma Assert (Nkind (New_Id) in N_Entity);
18554 NCT_Tables_In_Use := True;
18556 -- Sanity check the NCT_New_Entities table. No previous mapping with
18557 -- key Old_Id should exist.
18559 pragma Assert (No (NCT_New_Entities.Get (Old_Id)));
18561 -- Establish the mapping
18563 -- Old_Id -> New_Id
18565 NCT_New_Entities.Set (Old_Id, New_Id);
18566 end Add_New_Entity;
18568 -----------------------
18569 -- Add_Pending_Itype --
18570 -----------------------
18572 procedure Add_Pending_Itype (Assoc_Nod : Node_Id; Itype : Entity_Id) is
18573 Itypes : Elist_Id;
18575 begin
18576 pragma Assert (Present (Assoc_Nod));
18577 pragma Assert (Present (Itype));
18578 pragma Assert (Nkind (Itype) in N_Entity);
18579 pragma Assert (Is_Itype (Itype));
18581 NCT_Tables_In_Use := True;
18583 -- It is not possible to sanity check the NCT_Pendint_Itypes table
18584 -- directly because a single node may act as the associated node for
18585 -- multiple itypes.
18587 Itypes := NCT_Pending_Itypes.Get (Assoc_Nod);
18589 if No (Itypes) then
18590 Itypes := New_Elmt_List;
18591 NCT_Pending_Itypes.Set (Assoc_Nod, Itypes);
18592 end if;
18594 -- Establish the mapping
18596 -- Assoc_Nod -> (Itype, ...)
18598 -- Avoid inserting the same itype multiple times. This involves a
18599 -- linear search, however the set of itypes with the same associated
18600 -- node is very small.
18602 Append_Unique_Elmt (Itype, Itypes);
18603 end Add_Pending_Itype;
18605 ----------------------
18606 -- Build_NCT_Tables --
18607 ----------------------
18609 procedure Build_NCT_Tables (Entity_Map : Elist_Id) is
18610 Elmt : Elmt_Id;
18611 Old_Id : Entity_Id;
18612 New_Id : Entity_Id;
18614 begin
18615 -- Nothing to do when there is no entity map
18617 if No (Entity_Map) then
18618 return;
18619 end if;
18621 Elmt := First_Elmt (Entity_Map);
18622 while Present (Elmt) loop
18624 -- Extract the (Old_Id, New_Id) pair from the entity map
18626 Old_Id := Node (Elmt);
18627 Next_Elmt (Elmt);
18629 New_Id := Node (Elmt);
18630 Next_Elmt (Elmt);
18632 -- Establish the following mapping within table NCT_New_Entities
18634 -- Old_Id -> New_Id
18636 Add_New_Entity (Old_Id, New_Id);
18638 -- Establish the following mapping within table NCT_Pending_Itypes
18639 -- when the new entity is an itype.
18641 -- Assoc_Nod -> (New_Id, ...)
18643 -- IMPORTANT: the associated node is that of the old itype because
18644 -- the node will be replicated in Phase 2.
18646 if Is_Itype (Old_Id) then
18647 Add_Pending_Itype
18648 (Assoc_Nod => Associated_Node_For_Itype (Old_Id),
18649 Itype => New_Id);
18650 end if;
18651 end loop;
18652 end Build_NCT_Tables;
18654 ------------------------------------
18655 -- Copy_Any_Node_With_Replacement --
18656 ------------------------------------
18658 function Copy_Any_Node_With_Replacement
18659 (N : Node_Or_Entity_Id) return Node_Or_Entity_Id
18661 begin
18662 if Nkind (N) in N_Entity then
18663 return Corresponding_Entity (N);
18664 else
18665 return Copy_Node_With_Replacement (N);
18666 end if;
18667 end Copy_Any_Node_With_Replacement;
18669 ---------------------------------
18670 -- Copy_Elist_With_Replacement --
18671 ---------------------------------
18673 function Copy_Elist_With_Replacement (List : Elist_Id) return Elist_Id is
18674 Elmt : Elmt_Id;
18675 Result : Elist_Id;
18677 begin
18678 -- Copy the contents of the old list. Note that the list itself may
18679 -- be empty, in which case the routine returns a new empty list. This
18680 -- avoids sharing lists between subtrees. The element of an entity
18681 -- list could be an entity or a node, hence the invocation of routine
18682 -- Copy_Any_Node_With_Replacement.
18684 if Present (List) then
18685 Result := New_Elmt_List;
18687 Elmt := First_Elmt (List);
18688 while Present (Elmt) loop
18689 Append_Elmt
18690 (Copy_Any_Node_With_Replacement (Node (Elmt)), Result);
18692 Next_Elmt (Elmt);
18693 end loop;
18695 -- Otherwise the list does not exist
18697 else
18698 Result := No_Elist;
18699 end if;
18701 return Result;
18702 end Copy_Elist_With_Replacement;
18704 ---------------------------------
18705 -- Copy_Field_With_Replacement --
18706 ---------------------------------
18708 function Copy_Field_With_Replacement
18709 (Field : Union_Id;
18710 Old_Par : Node_Id := Empty;
18711 New_Par : Node_Id := Empty;
18712 Semantic : Boolean := False) return Union_Id
18714 begin
18715 -- The field is empty
18717 if Field = Union_Id (Empty) then
18718 return Field;
18720 -- The field is an entity/itype/node
18722 elsif Field in Node_Range then
18723 declare
18724 Old_N : constant Node_Id := Node_Id (Field);
18725 Syntactic : constant Boolean := Parent (Old_N) = Old_Par;
18727 New_N : Node_Id;
18729 begin
18730 -- The field is an entity/itype
18732 if Nkind (Old_N) in N_Entity then
18734 -- An entity/itype is always replicated
18736 New_N := Corresponding_Entity (Old_N);
18738 -- Update the parent pointer when the entity is a syntactic
18739 -- field. Note that itypes do not have parent pointers.
18741 if Syntactic and then New_N /= Old_N then
18742 Set_Parent (New_N, New_Par);
18743 end if;
18745 -- The field is a node
18747 else
18748 -- A node is replicated when it is either a syntactic field
18749 -- or when the caller treats it as a semantic attribute.
18751 if Syntactic or else Semantic then
18752 New_N := Copy_Node_With_Replacement (Old_N);
18754 -- Update the parent pointer when the node is a syntactic
18755 -- field.
18757 if Syntactic and then New_N /= Old_N then
18758 Set_Parent (New_N, New_Par);
18759 end if;
18761 -- Otherwise the node is returned unchanged
18763 else
18764 New_N := Old_N;
18765 end if;
18766 end if;
18768 return Union_Id (New_N);
18769 end;
18771 -- The field is an entity list
18773 elsif Field in Elist_Range then
18774 return Union_Id (Copy_Elist_With_Replacement (Elist_Id (Field)));
18776 -- The field is a syntactic list
18778 elsif Field in List_Range then
18779 declare
18780 Old_List : constant List_Id := List_Id (Field);
18781 Syntactic : constant Boolean := Parent (Old_List) = Old_Par;
18783 New_List : List_Id;
18785 begin
18786 -- A list is replicated when it is either a syntactic field or
18787 -- when the caller treats it as a semantic attribute.
18789 if Syntactic or else Semantic then
18790 New_List := Copy_List_With_Replacement (Old_List);
18792 -- Update the parent pointer when the list is a syntactic
18793 -- field.
18795 if Syntactic and then New_List /= Old_List then
18796 Set_Parent (New_List, New_Par);
18797 end if;
18799 -- Otherwise the list is returned unchanged
18801 else
18802 New_List := Old_List;
18803 end if;
18805 return Union_Id (New_List);
18806 end;
18808 -- Otherwise the field denotes an attribute that does not need to be
18809 -- replicated (Chars, literals, etc).
18811 else
18812 return Field;
18813 end if;
18814 end Copy_Field_With_Replacement;
18816 --------------------------------
18817 -- Copy_List_With_Replacement --
18818 --------------------------------
18820 function Copy_List_With_Replacement (List : List_Id) return List_Id is
18821 Elmt : Node_Id;
18822 Result : List_Id;
18824 begin
18825 -- Copy the contents of the old list. Note that the list itself may
18826 -- be empty, in which case the routine returns a new empty list. This
18827 -- avoids sharing lists between subtrees. The element of a syntactic
18828 -- list is always a node, never an entity or itype, hence the call to
18829 -- routine Copy_Node_With_Replacement.
18831 if Present (List) then
18832 Result := New_List;
18834 Elmt := First (List);
18835 while Present (Elmt) loop
18836 Append (Copy_Node_With_Replacement (Elmt), Result);
18838 Next (Elmt);
18839 end loop;
18841 -- Otherwise the list does not exist
18843 else
18844 Result := No_List;
18845 end if;
18847 return Result;
18848 end Copy_List_With_Replacement;
18850 --------------------------------
18851 -- Copy_Node_With_Replacement --
18852 --------------------------------
18854 function Copy_Node_With_Replacement (N : Node_Id) return Node_Id is
18855 Result : Node_Id;
18857 begin
18858 -- Assume that the node must be returned unchanged
18860 Result := N;
18862 if N > Empty_Or_Error then
18863 pragma Assert (Nkind (N) not in N_Entity);
18865 Result := New_Copy (N);
18867 Set_Field1 (Result,
18868 Copy_Field_With_Replacement
18869 (Field => Field1 (Result),
18870 Old_Par => N,
18871 New_Par => Result));
18873 Set_Field2 (Result,
18874 Copy_Field_With_Replacement
18875 (Field => Field2 (Result),
18876 Old_Par => N,
18877 New_Par => Result));
18879 Set_Field3 (Result,
18880 Copy_Field_With_Replacement
18881 (Field => Field3 (Result),
18882 Old_Par => N,
18883 New_Par => Result));
18885 Set_Field4 (Result,
18886 Copy_Field_With_Replacement
18887 (Field => Field4 (Result),
18888 Old_Par => N,
18889 New_Par => Result));
18891 Set_Field5 (Result,
18892 Copy_Field_With_Replacement
18893 (Field => Field5 (Result),
18894 Old_Par => N,
18895 New_Par => Result));
18897 -- Update the Comes_From_Source and Sloc attributes of the node
18898 -- in case the caller has supplied new values.
18900 Update_CFS_Sloc (Result);
18902 -- Update the Associated_Node_For_Itype attribute of all itypes
18903 -- created during Phase 1 whose associated node is N. As a result
18904 -- the Associated_Node_For_Itype refers to the replicated node.
18905 -- No action needs to be taken when the Associated_Node_For_Itype
18906 -- refers to an entity because this was already handled during
18907 -- Phase 1, in Visit_Itype.
18909 Update_Pending_Itypes
18910 (Old_Assoc => N,
18911 New_Assoc => Result);
18913 -- Update the First/Next_Named_Association chain for a replicated
18914 -- call.
18916 if Nkind_In (N, N_Entry_Call_Statement,
18917 N_Function_Call,
18918 N_Procedure_Call_Statement)
18919 then
18920 Update_Named_Associations
18921 (Old_Call => N,
18922 New_Call => Result);
18924 -- Update the Renamed_Object attribute of a replicated object
18925 -- declaration.
18927 elsif Nkind (N) = N_Object_Renaming_Declaration then
18928 Set_Renamed_Object (Defining_Entity (Result), Name (Result));
18930 -- Update the First_Real_Statement attribute of a replicated
18931 -- handled sequence of statements.
18933 elsif Nkind (N) = N_Handled_Sequence_Of_Statements then
18934 Update_First_Real_Statement
18935 (Old_HSS => N,
18936 New_HSS => Result);
18937 end if;
18938 end if;
18940 return Result;
18941 end Copy_Node_With_Replacement;
18943 --------------------------
18944 -- Corresponding_Entity --
18945 --------------------------
18947 function Corresponding_Entity (Id : Entity_Id) return Entity_Id is
18948 New_Id : Entity_Id;
18949 Result : Entity_Id;
18951 begin
18952 -- Assume that the entity must be returned unchanged
18954 Result := Id;
18956 if Id > Empty_Or_Error then
18957 pragma Assert (Nkind (Id) in N_Entity);
18959 -- Determine whether the entity has a corresponding new entity
18960 -- generated during Phase 1 and if it does, use it.
18962 if NCT_Tables_In_Use then
18963 New_Id := NCT_New_Entities.Get (Id);
18965 if Present (New_Id) then
18966 Result := New_Id;
18967 end if;
18968 end if;
18969 end if;
18971 return Result;
18972 end Corresponding_Entity;
18974 -------------------
18975 -- In_Entity_Map --
18976 -------------------
18978 function In_Entity_Map
18979 (Id : Entity_Id;
18980 Entity_Map : Elist_Id) return Boolean
18982 Elmt : Elmt_Id;
18983 Old_Id : Entity_Id;
18985 begin
18986 -- The entity map contains pairs (Old_Id, New_Id). The advancement
18987 -- step always skips the New_Id portion of the pair.
18989 if Present (Entity_Map) then
18990 Elmt := First_Elmt (Entity_Map);
18991 while Present (Elmt) loop
18992 Old_Id := Node (Elmt);
18994 if Old_Id = Id then
18995 return True;
18996 end if;
18998 Next_Elmt (Elmt);
18999 Next_Elmt (Elmt);
19000 end loop;
19001 end if;
19003 return False;
19004 end In_Entity_Map;
19006 ---------------------
19007 -- Update_CFS_Sloc --
19008 ---------------------
19010 procedure Update_CFS_Sloc (N : Node_Or_Entity_Id) is
19011 begin
19012 -- A new source location defaults the Comes_From_Source attribute
19014 if New_Sloc /= No_Location then
19015 Set_Comes_From_Source (N, Default_Node.Comes_From_Source);
19016 Set_Sloc (N, New_Sloc);
19017 end if;
19018 end Update_CFS_Sloc;
19020 ---------------------------------
19021 -- Update_First_Real_Statement --
19022 ---------------------------------
19024 procedure Update_First_Real_Statement
19025 (Old_HSS : Node_Id;
19026 New_HSS : Node_Id)
19028 Old_First_Stmt : constant Node_Id := First_Real_Statement (Old_HSS);
19030 New_Stmt : Node_Id;
19031 Old_Stmt : Node_Id;
19033 begin
19034 -- Recreate the First_Real_Statement attribute of a handled sequence
19035 -- of statements by traversing the statement lists of both sequences
19036 -- in parallel.
19038 if Present (Old_First_Stmt) then
19039 New_Stmt := First (Statements (New_HSS));
19040 Old_Stmt := First (Statements (Old_HSS));
19041 while Present (Old_Stmt) and then Old_Stmt /= Old_First_Stmt loop
19042 Next (New_Stmt);
19043 Next (Old_Stmt);
19044 end loop;
19046 pragma Assert (Present (New_Stmt));
19047 pragma Assert (Present (Old_Stmt));
19049 Set_First_Real_Statement (New_HSS, New_Stmt);
19050 end if;
19051 end Update_First_Real_Statement;
19053 -------------------------------
19054 -- Update_Named_Associations --
19055 -------------------------------
19057 procedure Update_Named_Associations
19058 (Old_Call : Node_Id;
19059 New_Call : Node_Id)
19061 New_Act : Node_Id;
19062 New_Next : Node_Id;
19063 Old_Act : Node_Id;
19064 Old_Next : Node_Id;
19066 begin
19067 -- Recreate the First/Next_Named_Actual chain of a call by traversing
19068 -- the chains of both the old and new calls in parallel.
19070 New_Act := First (Parameter_Associations (New_Call));
19071 Old_Act := First (Parameter_Associations (Old_Call));
19072 while Present (Old_Act) loop
19073 if Nkind (Old_Act) = N_Parameter_Association
19074 and then Present (Next_Named_Actual (Old_Act))
19075 then
19076 if First_Named_Actual (Old_Call) =
19077 Explicit_Actual_Parameter (Old_Act)
19078 then
19079 Set_First_Named_Actual (New_Call,
19080 Explicit_Actual_Parameter (New_Act));
19081 end if;
19083 -- Scan the actual parameter list to find the next suitable
19084 -- named actual. Note that the list may be out of order.
19086 New_Next := First (Parameter_Associations (New_Call));
19087 Old_Next := First (Parameter_Associations (Old_Call));
19088 while Nkind (Old_Next) /= N_Parameter_Association
19089 or else Explicit_Actual_Parameter (Old_Next) /=
19090 Next_Named_Actual (Old_Act)
19091 loop
19092 Next (New_Next);
19093 Next (Old_Next);
19094 end loop;
19096 Set_Next_Named_Actual (New_Act,
19097 Explicit_Actual_Parameter (New_Next));
19098 end if;
19100 Next (New_Act);
19101 Next (Old_Act);
19102 end loop;
19103 end Update_Named_Associations;
19105 -------------------------
19106 -- Update_New_Entities --
19107 -------------------------
19109 procedure Update_New_Entities (Entity_Map : Elist_Id) is
19110 New_Id : Entity_Id := Empty;
19111 Old_Id : Entity_Id := Empty;
19113 begin
19114 if NCT_Tables_In_Use then
19115 NCT_New_Entities.Get_First (Old_Id, New_Id);
19117 -- Update the semantic fields of all new entities created during
19118 -- Phase 1 which were not supplied via an entity map.
19119 -- ??? Is there a better way of distinguishing those?
19121 while Present (Old_Id) and then Present (New_Id) loop
19122 if not (Present (Entity_Map)
19123 and then In_Entity_Map (Old_Id, Entity_Map))
19124 then
19125 Update_Semantic_Fields (New_Id);
19126 end if;
19128 NCT_New_Entities.Get_Next (Old_Id, New_Id);
19129 end loop;
19130 end if;
19131 end Update_New_Entities;
19133 ---------------------------
19134 -- Update_Pending_Itypes --
19135 ---------------------------
19137 procedure Update_Pending_Itypes
19138 (Old_Assoc : Node_Id;
19139 New_Assoc : Node_Id)
19141 Item : Elmt_Id;
19142 Itypes : Elist_Id;
19144 begin
19145 if NCT_Tables_In_Use then
19146 Itypes := NCT_Pending_Itypes.Get (Old_Assoc);
19148 -- Update the Associated_Node_For_Itype attribute for all itypes
19149 -- which originally refer to Old_Assoc to designate New_Assoc.
19151 if Present (Itypes) then
19152 Item := First_Elmt (Itypes);
19153 while Present (Item) loop
19154 Set_Associated_Node_For_Itype (Node (Item), New_Assoc);
19156 Next_Elmt (Item);
19157 end loop;
19158 end if;
19159 end if;
19160 end Update_Pending_Itypes;
19162 ----------------------------
19163 -- Update_Semantic_Fields --
19164 ----------------------------
19166 procedure Update_Semantic_Fields (Id : Entity_Id) is
19167 begin
19168 -- Discriminant_Constraint
19170 if Has_Discriminants (Base_Type (Id)) then
19171 Set_Discriminant_Constraint (Id, Elist_Id (
19172 Copy_Field_With_Replacement
19173 (Field => Union_Id (Discriminant_Constraint (Id)),
19174 Semantic => True)));
19175 end if;
19177 -- Etype
19179 Set_Etype (Id, Node_Id (
19180 Copy_Field_With_Replacement
19181 (Field => Union_Id (Etype (Id)),
19182 Semantic => True)));
19184 -- First_Index
19185 -- Packed_Array_Impl_Type
19187 if Is_Array_Type (Id) then
19188 if Present (First_Index (Id)) then
19189 Set_First_Index (Id, First (List_Id (
19190 Copy_Field_With_Replacement
19191 (Field => Union_Id (List_Containing (First_Index (Id))),
19192 Semantic => True))));
19193 end if;
19195 if Is_Packed (Id) then
19196 Set_Packed_Array_Impl_Type (Id, Node_Id (
19197 Copy_Field_With_Replacement
19198 (Field => Union_Id (Packed_Array_Impl_Type (Id)),
19199 Semantic => True)));
19200 end if;
19201 end if;
19203 -- Next_Entity
19205 Set_Next_Entity (Id, Node_Id (
19206 Copy_Field_With_Replacement
19207 (Field => Union_Id (Next_Entity (Id)),
19208 Semantic => True)));
19210 -- Scalar_Range
19212 if Is_Discrete_Type (Id) then
19213 Set_Scalar_Range (Id, Node_Id (
19214 Copy_Field_With_Replacement
19215 (Field => Union_Id (Scalar_Range (Id)),
19216 Semantic => True)));
19217 end if;
19219 -- Scope
19221 -- Update the scope when the caller specified an explicit one
19223 if Present (New_Scope) then
19224 Set_Scope (Id, New_Scope);
19225 else
19226 Set_Scope (Id, Node_Id (
19227 Copy_Field_With_Replacement
19228 (Field => Union_Id (Scope (Id)),
19229 Semantic => True)));
19230 end if;
19231 end Update_Semantic_Fields;
19233 --------------------
19234 -- Visit_Any_Node --
19235 --------------------
19237 procedure Visit_Any_Node (N : Node_Or_Entity_Id) is
19238 begin
19239 if Nkind (N) in N_Entity then
19240 if Is_Itype (N) then
19241 Visit_Itype (N);
19242 else
19243 Visit_Entity (N);
19244 end if;
19245 else
19246 Visit_Node (N);
19247 end if;
19248 end Visit_Any_Node;
19250 -----------------
19251 -- Visit_Elist --
19252 -----------------
19254 procedure Visit_Elist (List : Elist_Id) is
19255 Elmt : Elmt_Id;
19257 begin
19258 -- The element of an entity list could be an entity, itype, or a
19259 -- node, hence the call to Visit_Any_Node.
19261 if Present (List) then
19262 Elmt := First_Elmt (List);
19263 while Present (Elmt) loop
19264 Visit_Any_Node (Node (Elmt));
19266 Next_Elmt (Elmt);
19267 end loop;
19268 end if;
19269 end Visit_Elist;
19271 ------------------
19272 -- Visit_Entity --
19273 ------------------
19275 procedure Visit_Entity (Id : Entity_Id) is
19276 New_Id : Entity_Id;
19278 begin
19279 pragma Assert (Nkind (Id) in N_Entity);
19280 pragma Assert (not Is_Itype (Id));
19282 -- Nothing to do if the entity is not defined in the Actions list of
19283 -- an N_Expression_With_Actions node.
19285 if EWA_Level = 0 then
19286 return;
19288 -- Nothing to do if the entity is defined within a scoping construct
19289 -- of an N_Expression_With_Actions node.
19291 elsif EWA_Inner_Scope_Level > 0 then
19292 return;
19294 -- Nothing to do if the entity is not an object or a type. Relaxing
19295 -- this restriction leads to a performance penalty.
19297 elsif not Ekind_In (Id, E_Constant, E_Variable)
19298 and then not Is_Type (Id)
19299 then
19300 return;
19302 -- Nothing to do if the entity was already visited
19304 elsif NCT_Tables_In_Use
19305 and then Present (NCT_New_Entities.Get (Id))
19306 then
19307 return;
19309 -- Nothing to do if the declaration node of the entity is not within
19310 -- the subtree being replicated.
19312 elsif not In_Subtree
19313 (N => Declaration_Node (Id),
19314 Root => Source)
19315 then
19316 return;
19317 end if;
19319 -- Create a new entity by directly copying the old entity. This
19320 -- action causes all attributes of the old entity to be inherited.
19322 New_Id := New_Copy (Id);
19324 -- Create a new name for the new entity because the back end needs
19325 -- distinct names for debugging purposes.
19327 Set_Chars (New_Id, New_Internal_Name ('T'));
19329 -- Update the Comes_From_Source and Sloc attributes of the entity in
19330 -- case the caller has supplied new values.
19332 Update_CFS_Sloc (New_Id);
19334 -- Establish the following mapping within table NCT_New_Entities:
19336 -- Id -> New_Id
19338 Add_New_Entity (Id, New_Id);
19340 -- Deal with the semantic fields of entities. The fields are visited
19341 -- because they may mention entities which reside within the subtree
19342 -- being copied.
19344 Visit_Semantic_Fields (Id);
19345 end Visit_Entity;
19347 -----------------
19348 -- Visit_Field --
19349 -----------------
19351 procedure Visit_Field
19352 (Field : Union_Id;
19353 Par_Nod : Node_Id := Empty;
19354 Semantic : Boolean := False)
19356 begin
19357 -- The field is empty
19359 if Field = Union_Id (Empty) then
19360 return;
19362 -- The field is an entity/itype/node
19364 elsif Field in Node_Range then
19365 declare
19366 N : constant Node_Id := Node_Id (Field);
19368 begin
19369 -- The field is an entity/itype
19371 if Nkind (N) in N_Entity then
19373 -- Itypes are always visited
19375 if Is_Itype (N) then
19376 Visit_Itype (N);
19378 -- An entity is visited when it is either a syntactic field
19379 -- or when the caller treats it as a semantic attribute.
19381 elsif Parent (N) = Par_Nod or else Semantic then
19382 Visit_Entity (N);
19383 end if;
19385 -- The field is a node
19387 else
19388 -- A node is visited when it is either a syntactic field or
19389 -- when the caller treats it as a semantic attribute.
19391 if Parent (N) = Par_Nod or else Semantic then
19392 Visit_Node (N);
19393 end if;
19394 end if;
19395 end;
19397 -- The field is an entity list
19399 elsif Field in Elist_Range then
19400 Visit_Elist (Elist_Id (Field));
19402 -- The field is a syntax list
19404 elsif Field in List_Range then
19405 declare
19406 List : constant List_Id := List_Id (Field);
19408 begin
19409 -- A syntax list is visited when it is either a syntactic field
19410 -- or when the caller treats it as a semantic attribute.
19412 if Parent (List) = Par_Nod or else Semantic then
19413 Visit_List (List);
19414 end if;
19415 end;
19417 -- Otherwise the field denotes information which does not need to be
19418 -- visited (chars, literals, etc.).
19420 else
19421 null;
19422 end if;
19423 end Visit_Field;
19425 -----------------
19426 -- Visit_Itype --
19427 -----------------
19429 procedure Visit_Itype (Itype : Entity_Id) is
19430 New_Assoc : Node_Id;
19431 New_Itype : Entity_Id;
19432 Old_Assoc : Node_Id;
19434 begin
19435 pragma Assert (Nkind (Itype) in N_Entity);
19436 pragma Assert (Is_Itype (Itype));
19438 -- Itypes that describe the designated type of access to subprograms
19439 -- have the structure of subprogram declarations, with signatures,
19440 -- etc. Either we duplicate the signatures completely, or choose to
19441 -- share such itypes, which is fine because their elaboration will
19442 -- have no side effects.
19444 if Ekind (Itype) = E_Subprogram_Type then
19445 return;
19447 -- Nothing to do if the itype was already visited
19449 elsif NCT_Tables_In_Use
19450 and then Present (NCT_New_Entities.Get (Itype))
19451 then
19452 return;
19454 -- Nothing to do if the associated node of the itype is not within
19455 -- the subtree being replicated.
19457 elsif not In_Subtree
19458 (N => Associated_Node_For_Itype (Itype),
19459 Root => Source)
19460 then
19461 return;
19462 end if;
19464 -- Create a new itype by directly copying the old itype. This action
19465 -- causes all attributes of the old itype to be inherited.
19467 New_Itype := New_Copy (Itype);
19469 -- Create a new name for the new itype because the back end requires
19470 -- distinct names for debugging purposes.
19472 Set_Chars (New_Itype, New_Internal_Name ('T'));
19474 -- Update the Comes_From_Source and Sloc attributes of the itype in
19475 -- case the caller has supplied new values.
19477 Update_CFS_Sloc (New_Itype);
19479 -- Establish the following mapping within table NCT_New_Entities:
19481 -- Itype -> New_Itype
19483 Add_New_Entity (Itype, New_Itype);
19485 -- The new itype must be unfrozen because the resulting subtree may
19486 -- be inserted anywhere and cause an earlier or later freezing.
19488 if Present (Freeze_Node (New_Itype)) then
19489 Set_Freeze_Node (New_Itype, Empty);
19490 Set_Is_Frozen (New_Itype, False);
19491 end if;
19493 -- If a record subtype is simply copied, the entity list will be
19494 -- shared. Thus cloned_Subtype must be set to indicate the sharing.
19495 -- ??? What does this do?
19497 if Ekind_In (Itype, E_Class_Wide_Subtype, E_Record_Subtype) then
19498 Set_Cloned_Subtype (New_Itype, Itype);
19499 end if;
19501 -- The associated node may denote an entity, in which case it may
19502 -- already have a new corresponding entity created during a prior
19503 -- call to Visit_Entity or Visit_Itype for the same subtree.
19505 -- Given
19506 -- Old_Assoc ---------> New_Assoc
19508 -- Created by Visit_Itype
19509 -- Itype -------------> New_Itype
19510 -- ANFI = Old_Assoc ANFI = Old_Assoc < must be updated
19512 -- In the example above, Old_Assoc is an arbitrary entity that was
19513 -- already visited for the same subtree and has a corresponding new
19514 -- entity New_Assoc. Old_Assoc was inherited by New_Itype by virtue
19515 -- of copying entities, however it must be updated to New_Assoc.
19517 Old_Assoc := Associated_Node_For_Itype (Itype);
19519 if Nkind (Old_Assoc) in N_Entity then
19520 if NCT_Tables_In_Use then
19521 New_Assoc := NCT_New_Entities.Get (Old_Assoc);
19523 if Present (New_Assoc) then
19524 Set_Associated_Node_For_Itype (New_Itype, New_Assoc);
19525 end if;
19526 end if;
19528 -- Otherwise the associated node denotes a node. Postpone the update
19529 -- until Phase 2 when the node is replicated. Establish the following
19530 -- mapping within table NCT_Pending_Itypes:
19532 -- Old_Assoc -> (New_Type, ...)
19534 else
19535 Add_Pending_Itype (Old_Assoc, New_Itype);
19536 end if;
19538 -- Deal with the semantic fields of itypes. The fields are visited
19539 -- because they may mention entities that reside within the subtree
19540 -- being copied.
19542 Visit_Semantic_Fields (Itype);
19543 end Visit_Itype;
19545 ----------------
19546 -- Visit_List --
19547 ----------------
19549 procedure Visit_List (List : List_Id) is
19550 Elmt : Node_Id;
19552 begin
19553 -- Note that the element of a syntactic list is always a node, never
19554 -- an entity or itype, hence the call to Visit_Node.
19556 if Present (List) then
19557 Elmt := First (List);
19558 while Present (Elmt) loop
19559 Visit_Node (Elmt);
19561 Next (Elmt);
19562 end loop;
19563 end if;
19564 end Visit_List;
19566 ----------------
19567 -- Visit_Node --
19568 ----------------
19570 procedure Visit_Node (N : Node_Or_Entity_Id) is
19571 begin
19572 pragma Assert (Nkind (N) not in N_Entity);
19574 if Nkind (N) = N_Expression_With_Actions then
19575 EWA_Level := EWA_Level + 1;
19577 elsif EWA_Level > 0
19578 and then Nkind_In (N, N_Block_Statement,
19579 N_Subprogram_Body,
19580 N_Subprogram_Declaration)
19581 then
19582 EWA_Inner_Scope_Level := EWA_Inner_Scope_Level + 1;
19583 end if;
19585 Visit_Field
19586 (Field => Field1 (N),
19587 Par_Nod => N);
19589 Visit_Field
19590 (Field => Field2 (N),
19591 Par_Nod => N);
19593 Visit_Field
19594 (Field => Field3 (N),
19595 Par_Nod => N);
19597 Visit_Field
19598 (Field => Field4 (N),
19599 Par_Nod => N);
19601 Visit_Field
19602 (Field => Field5 (N),
19603 Par_Nod => N);
19605 if EWA_Level > 0
19606 and then Nkind_In (N, N_Block_Statement,
19607 N_Subprogram_Body,
19608 N_Subprogram_Declaration)
19609 then
19610 EWA_Inner_Scope_Level := EWA_Inner_Scope_Level - 1;
19612 elsif Nkind (N) = N_Expression_With_Actions then
19613 EWA_Level := EWA_Level - 1;
19614 end if;
19615 end Visit_Node;
19617 ---------------------------
19618 -- Visit_Semantic_Fields --
19619 ---------------------------
19621 procedure Visit_Semantic_Fields (Id : Entity_Id) is
19622 begin
19623 pragma Assert (Nkind (Id) in N_Entity);
19625 -- Discriminant_Constraint
19627 if Has_Discriminants (Base_Type (Id)) then
19628 Visit_Field
19629 (Field => Union_Id (Discriminant_Constraint (Id)),
19630 Semantic => True);
19631 end if;
19633 -- Etype
19635 Visit_Field
19636 (Field => Union_Id (Etype (Id)),
19637 Semantic => True);
19639 -- First_Index
19640 -- Packed_Array_Impl_Type
19642 if Is_Array_Type (Id) then
19643 if Present (First_Index (Id)) then
19644 Visit_Field
19645 (Field => Union_Id (List_Containing (First_Index (Id))),
19646 Semantic => True);
19647 end if;
19649 if Is_Packed (Id) then
19650 Visit_Field
19651 (Field => Union_Id (Packed_Array_Impl_Type (Id)),
19652 Semantic => True);
19653 end if;
19654 end if;
19656 -- Scalar_Range
19658 if Is_Discrete_Type (Id) then
19659 Visit_Field
19660 (Field => Union_Id (Scalar_Range (Id)),
19661 Semantic => True);
19662 end if;
19663 end Visit_Semantic_Fields;
19665 -- Start of processing for New_Copy_Tree
19667 begin
19668 -- Routine New_Copy_Tree performs a deep copy of a subtree by creating
19669 -- shallow copies for each node within, and then updating the child and
19670 -- parent pointers accordingly. This process is straightforward, however
19671 -- the routine must deal with the following complications:
19673 -- * Entities defined within N_Expression_With_Actions nodes must be
19674 -- replicated rather than shared to avoid introducing two identical
19675 -- symbols within the same scope. Note that no other expression can
19676 -- currently define entities.
19678 -- do
19679 -- Source_Low : ...;
19680 -- Source_High : ...;
19682 -- <reference to Source_Low>
19683 -- <reference to Source_High>
19684 -- in ... end;
19686 -- New_Copy_Tree handles this case by first creating new entities
19687 -- and then updating all existing references to point to these new
19688 -- entities.
19690 -- do
19691 -- New_Low : ...;
19692 -- New_High : ...;
19694 -- <reference to New_Low>
19695 -- <reference to New_High>
19696 -- in ... end;
19698 -- * Itypes defined within the subtree must be replicated to avoid any
19699 -- dependencies on invalid or inaccessible data.
19701 -- subtype Source_Itype is ... range Source_Low .. Source_High;
19703 -- New_Copy_Tree handles this case by first creating a new itype in
19704 -- the same fashion as entities, and then updating various relevant
19705 -- constraints.
19707 -- subtype New_Itype is ... range New_Low .. New_High;
19709 -- * The Associated_Node_For_Itype field of itypes must be updated to
19710 -- reference the proper replicated entity or node.
19712 -- * Semantic fields of entities such as Etype and Scope must be
19713 -- updated to reference the proper replicated entities.
19715 -- * Semantic fields of nodes such as First_Real_Statement must be
19716 -- updated to reference the proper replicated nodes.
19718 -- To meet all these demands, routine New_Copy_Tree is split into two
19719 -- phases.
19721 -- Phase 1 traverses the tree in order to locate entities and itypes
19722 -- defined within the subtree. New entities are generated and saved in
19723 -- table NCT_New_Entities. The semantic fields of all new entities and
19724 -- itypes are then updated accordingly.
19726 -- Phase 2 traverses the tree in order to replicate each node. Various
19727 -- semantic fields of nodes and entities are updated accordingly.
19729 -- Preparatory phase. Clear the contents of tables NCT_New_Entities and
19730 -- NCT_Pending_Itypes in case a previous call to New_Copy_Tree left some
19731 -- data inside.
19733 if NCT_Tables_In_Use then
19734 NCT_Tables_In_Use := False;
19736 NCT_New_Entities.Reset;
19737 NCT_Pending_Itypes.Reset;
19738 end if;
19740 -- Populate tables NCT_New_Entities and NCT_Pending_Itypes with data
19741 -- supplied by a linear entity map. The tables offer faster access to
19742 -- the same data.
19744 Build_NCT_Tables (Map);
19746 -- Execute Phase 1. Traverse the subtree and generate new entities for
19747 -- the following cases:
19749 -- * An entity defined within an N_Expression_With_Actions node
19751 -- * An itype referenced within the subtree where the associated node
19752 -- is also in the subtree.
19754 -- All new entities are accessible via table NCT_New_Entities, which
19755 -- contains mappings of the form:
19757 -- Old_Entity -> New_Entity
19758 -- Old_Itype -> New_Itype
19760 -- In addition, the associated nodes of all new itypes are mapped in
19761 -- table NCT_Pending_Itypes:
19763 -- Assoc_Nod -> (New_Itype1, New_Itype2, .., New_ItypeN)
19765 Visit_Any_Node (Source);
19767 -- Update the semantic attributes of all new entities generated during
19768 -- Phase 1 before starting Phase 2. The updates could be performed in
19769 -- routine Corresponding_Entity, however this may cause the same entity
19770 -- to be updated multiple times, effectively generating useless nodes.
19771 -- Keeping the updates separates from Phase 2 ensures that only one set
19772 -- of attributes is generated for an entity at any one time.
19774 Update_New_Entities (Map);
19776 -- Execute Phase 2. Replicate the source subtree one node at a time.
19777 -- The following transformations take place:
19779 -- * References to entities and itypes are updated to refer to the
19780 -- new entities and itypes generated during Phase 1.
19782 -- * All Associated_Node_For_Itype attributes of itypes are updated
19783 -- to refer to the new replicated Associated_Node_For_Itype.
19785 return Copy_Node_With_Replacement (Source);
19786 end New_Copy_Tree;
19788 -------------------------
19789 -- New_External_Entity --
19790 -------------------------
19792 function New_External_Entity
19793 (Kind : Entity_Kind;
19794 Scope_Id : Entity_Id;
19795 Sloc_Value : Source_Ptr;
19796 Related_Id : Entity_Id;
19797 Suffix : Character;
19798 Suffix_Index : Nat := 0;
19799 Prefix : Character := ' ') return Entity_Id
19801 N : constant Entity_Id :=
19802 Make_Defining_Identifier (Sloc_Value,
19803 New_External_Name
19804 (Chars (Related_Id), Suffix, Suffix_Index, Prefix));
19806 begin
19807 Set_Ekind (N, Kind);
19808 Set_Is_Internal (N, True);
19809 Append_Entity (N, Scope_Id);
19810 Set_Public_Status (N);
19812 if Kind in Type_Kind then
19813 Init_Size_Align (N);
19814 end if;
19816 return N;
19817 end New_External_Entity;
19819 -------------------------
19820 -- New_Internal_Entity --
19821 -------------------------
19823 function New_Internal_Entity
19824 (Kind : Entity_Kind;
19825 Scope_Id : Entity_Id;
19826 Sloc_Value : Source_Ptr;
19827 Id_Char : Character) return Entity_Id
19829 N : constant Entity_Id := Make_Temporary (Sloc_Value, Id_Char);
19831 begin
19832 Set_Ekind (N, Kind);
19833 Set_Is_Internal (N, True);
19834 Append_Entity (N, Scope_Id);
19836 if Kind in Type_Kind then
19837 Init_Size_Align (N);
19838 end if;
19840 return N;
19841 end New_Internal_Entity;
19843 -----------------
19844 -- Next_Actual --
19845 -----------------
19847 function Next_Actual (Actual_Id : Node_Id) return Node_Id is
19848 N : Node_Id;
19850 begin
19851 -- If we are pointing at a positional parameter, it is a member of a
19852 -- node list (the list of parameters), and the next parameter is the
19853 -- next node on the list, unless we hit a parameter association, then
19854 -- we shift to using the chain whose head is the First_Named_Actual in
19855 -- the parent, and then is threaded using the Next_Named_Actual of the
19856 -- Parameter_Association. All this fiddling is because the original node
19857 -- list is in the textual call order, and what we need is the
19858 -- declaration order.
19860 if Is_List_Member (Actual_Id) then
19861 N := Next (Actual_Id);
19863 if Nkind (N) = N_Parameter_Association then
19865 -- In case of a build-in-place call, the call will no longer be a
19866 -- call; it will have been rewritten.
19868 if Nkind_In (Parent (Actual_Id), N_Entry_Call_Statement,
19869 N_Function_Call,
19870 N_Procedure_Call_Statement)
19871 then
19872 return First_Named_Actual (Parent (Actual_Id));
19873 else
19874 return Empty;
19875 end if;
19876 else
19877 return N;
19878 end if;
19880 else
19881 return Next_Named_Actual (Parent (Actual_Id));
19882 end if;
19883 end Next_Actual;
19885 procedure Next_Actual (Actual_Id : in out Node_Id) is
19886 begin
19887 Actual_Id := Next_Actual (Actual_Id);
19888 end Next_Actual;
19890 -----------------
19891 -- Next_Global --
19892 -----------------
19894 function Next_Global (Node : Node_Id) return Node_Id is
19895 begin
19896 -- The global item may either be in a list, or by itself, in which case
19897 -- there is no next global item with the same mode.
19899 if Is_List_Member (Node) then
19900 return Next (Node);
19901 else
19902 return Empty;
19903 end if;
19904 end Next_Global;
19906 procedure Next_Global (Node : in out Node_Id) is
19907 begin
19908 Node := Next_Global (Node);
19909 end Next_Global;
19911 ----------------------------------
19912 -- New_Requires_Transient_Scope --
19913 ----------------------------------
19915 function New_Requires_Transient_Scope (Id : Entity_Id) return Boolean is
19916 function Caller_Known_Size_Record (Typ : Entity_Id) return Boolean;
19917 -- This is called for untagged records and protected types, with
19918 -- nondefaulted discriminants. Returns True if the size of function
19919 -- results is known at the call site, False otherwise. Returns False
19920 -- if there is a variant part that depends on the discriminants of
19921 -- this type, or if there is an array constrained by the discriminants
19922 -- of this type. ???Currently, this is overly conservative (the array
19923 -- could be nested inside some other record that is constrained by
19924 -- nondiscriminants). That is, the recursive calls are too conservative.
19926 function Large_Max_Size_Mutable (Typ : Entity_Id) return Boolean;
19927 -- Returns True if Typ is a nonlimited record with defaulted
19928 -- discriminants whose max size makes it unsuitable for allocating on
19929 -- the primary stack.
19931 ------------------------------
19932 -- Caller_Known_Size_Record --
19933 ------------------------------
19935 function Caller_Known_Size_Record (Typ : Entity_Id) return Boolean is
19936 pragma Assert (Typ = Underlying_Type (Typ));
19938 begin
19939 if Has_Variant_Part (Typ) and then not Is_Definite_Subtype (Typ) then
19940 return False;
19941 end if;
19943 declare
19944 Comp : Entity_Id;
19946 begin
19947 Comp := First_Entity (Typ);
19948 while Present (Comp) loop
19950 -- Only look at E_Component entities. No need to look at
19951 -- E_Discriminant entities, and we must ignore internal
19952 -- subtypes generated for constrained components.
19954 if Ekind (Comp) = E_Component then
19955 declare
19956 Comp_Type : constant Entity_Id :=
19957 Underlying_Type (Etype (Comp));
19959 begin
19960 if Is_Record_Type (Comp_Type)
19961 or else
19962 Is_Protected_Type (Comp_Type)
19963 then
19964 if not Caller_Known_Size_Record (Comp_Type) then
19965 return False;
19966 end if;
19968 elsif Is_Array_Type (Comp_Type) then
19969 if Size_Depends_On_Discriminant (Comp_Type) then
19970 return False;
19971 end if;
19972 end if;
19973 end;
19974 end if;
19976 Next_Entity (Comp);
19977 end loop;
19978 end;
19980 return True;
19981 end Caller_Known_Size_Record;
19983 ------------------------------
19984 -- Large_Max_Size_Mutable --
19985 ------------------------------
19987 function Large_Max_Size_Mutable (Typ : Entity_Id) return Boolean is
19988 pragma Assert (Typ = Underlying_Type (Typ));
19990 function Is_Large_Discrete_Type (T : Entity_Id) return Boolean;
19991 -- Returns true if the discrete type T has a large range
19993 ----------------------------
19994 -- Is_Large_Discrete_Type --
19995 ----------------------------
19997 function Is_Large_Discrete_Type (T : Entity_Id) return Boolean is
19998 Threshold : constant Int := 16;
19999 -- Arbitrary threshold above which we consider it "large". We want
20000 -- a fairly large threshold, because these large types really
20001 -- shouldn't have default discriminants in the first place, in
20002 -- most cases.
20004 begin
20005 return UI_To_Int (RM_Size (T)) > Threshold;
20006 end Is_Large_Discrete_Type;
20008 -- Start of processing for Large_Max_Size_Mutable
20010 begin
20011 if Is_Record_Type (Typ)
20012 and then not Is_Limited_View (Typ)
20013 and then Has_Defaulted_Discriminants (Typ)
20014 then
20015 -- Loop through the components, looking for an array whose upper
20016 -- bound(s) depends on discriminants, where both the subtype of
20017 -- the discriminant and the index subtype are too large.
20019 declare
20020 Comp : Entity_Id;
20022 begin
20023 Comp := First_Entity (Typ);
20024 while Present (Comp) loop
20025 if Ekind (Comp) = E_Component then
20026 declare
20027 Comp_Type : constant Entity_Id :=
20028 Underlying_Type (Etype (Comp));
20030 Hi : Node_Id;
20031 Indx : Node_Id;
20032 Ityp : Entity_Id;
20034 begin
20035 if Is_Array_Type (Comp_Type) then
20036 Indx := First_Index (Comp_Type);
20038 while Present (Indx) loop
20039 Ityp := Etype (Indx);
20040 Hi := Type_High_Bound (Ityp);
20042 if Nkind (Hi) = N_Identifier
20043 and then Ekind (Entity (Hi)) = E_Discriminant
20044 and then Is_Large_Discrete_Type (Ityp)
20045 and then Is_Large_Discrete_Type
20046 (Etype (Entity (Hi)))
20047 then
20048 return True;
20049 end if;
20051 Next_Index (Indx);
20052 end loop;
20053 end if;
20054 end;
20055 end if;
20057 Next_Entity (Comp);
20058 end loop;
20059 end;
20060 end if;
20062 return False;
20063 end Large_Max_Size_Mutable;
20065 -- Local declarations
20067 Typ : constant Entity_Id := Underlying_Type (Id);
20069 -- Start of processing for New_Requires_Transient_Scope
20071 begin
20072 -- This is a private type which is not completed yet. This can only
20073 -- happen in a default expression (of a formal parameter or of a
20074 -- record component). Do not expand transient scope in this case.
20076 if No (Typ) then
20077 return False;
20079 -- Do not expand transient scope for non-existent procedure return or
20080 -- string literal types.
20082 elsif Typ = Standard_Void_Type
20083 or else Ekind (Typ) = E_String_Literal_Subtype
20084 then
20085 return False;
20087 -- If Typ is a generic formal incomplete type, then we want to look at
20088 -- the actual type.
20090 elsif Ekind (Typ) = E_Record_Subtype
20091 and then Present (Cloned_Subtype (Typ))
20092 then
20093 return New_Requires_Transient_Scope (Cloned_Subtype (Typ));
20095 -- Functions returning specific tagged types may dispatch on result, so
20096 -- their returned value is allocated on the secondary stack, even in the
20097 -- definite case. We must treat nondispatching functions the same way,
20098 -- because access-to-function types can point at both, so the calling
20099 -- conventions must be compatible. Is_Tagged_Type includes controlled
20100 -- types and class-wide types. Controlled type temporaries need
20101 -- finalization.
20103 -- ???It's not clear why we need to return noncontrolled types with
20104 -- controlled components on the secondary stack.
20106 elsif Is_Tagged_Type (Typ) or else Has_Controlled_Component (Typ) then
20107 return True;
20109 -- Untagged definite subtypes are known size. This includes all
20110 -- elementary [sub]types. Tasks are known size even if they have
20111 -- discriminants. So we return False here, with one exception:
20112 -- For a type like:
20113 -- type T (Last : Natural := 0) is
20114 -- X : String (1 .. Last);
20115 -- end record;
20116 -- we return True. That's because for "P(F(...));", where F returns T,
20117 -- we don't know the size of the result at the call site, so if we
20118 -- allocated it on the primary stack, we would have to allocate the
20119 -- maximum size, which is way too big.
20121 elsif Is_Definite_Subtype (Typ) or else Is_Task_Type (Typ) then
20122 return Large_Max_Size_Mutable (Typ);
20124 -- Indefinite (discriminated) untagged record or protected type
20126 elsif Is_Record_Type (Typ) or else Is_Protected_Type (Typ) then
20127 return not Caller_Known_Size_Record (Typ);
20129 -- Unconstrained array
20131 else
20132 pragma Assert (Is_Array_Type (Typ) and not Is_Definite_Subtype (Typ));
20133 return True;
20134 end if;
20135 end New_Requires_Transient_Scope;
20137 --------------------------
20138 -- No_Heap_Finalization --
20139 --------------------------
20141 function No_Heap_Finalization (Typ : Entity_Id) return Boolean is
20142 begin
20143 if Ekind_In (Typ, E_Access_Type, E_General_Access_Type)
20144 and then Is_Library_Level_Entity (Typ)
20145 then
20146 -- A global No_Heap_Finalization pragma applies to all library-level
20147 -- named access-to-object types.
20149 if Present (No_Heap_Finalization_Pragma) then
20150 return True;
20152 -- The library-level named access-to-object type itself is subject to
20153 -- pragma No_Heap_Finalization.
20155 elsif Present (Get_Pragma (Typ, Pragma_No_Heap_Finalization)) then
20156 return True;
20157 end if;
20158 end if;
20160 return False;
20161 end No_Heap_Finalization;
20163 -----------------------
20164 -- Normalize_Actuals --
20165 -----------------------
20167 -- Chain actuals according to formals of subprogram. If there are no named
20168 -- associations, the chain is simply the list of Parameter Associations,
20169 -- since the order is the same as the declaration order. If there are named
20170 -- associations, then the First_Named_Actual field in the N_Function_Call
20171 -- or N_Procedure_Call_Statement node points to the Parameter_Association
20172 -- node for the parameter that comes first in declaration order. The
20173 -- remaining named parameters are then chained in declaration order using
20174 -- Next_Named_Actual.
20176 -- This routine also verifies that the number of actuals is compatible with
20177 -- the number and default values of formals, but performs no type checking
20178 -- (type checking is done by the caller).
20180 -- If the matching succeeds, Success is set to True and the caller proceeds
20181 -- with type-checking. If the match is unsuccessful, then Success is set to
20182 -- False, and the caller attempts a different interpretation, if there is
20183 -- one.
20185 -- If the flag Report is on, the call is not overloaded, and a failure to
20186 -- match can be reported here, rather than in the caller.
20188 procedure Normalize_Actuals
20189 (N : Node_Id;
20190 S : Entity_Id;
20191 Report : Boolean;
20192 Success : out Boolean)
20194 Actuals : constant List_Id := Parameter_Associations (N);
20195 Actual : Node_Id := Empty;
20196 Formal : Entity_Id;
20197 Last : Node_Id := Empty;
20198 First_Named : Node_Id := Empty;
20199 Found : Boolean;
20201 Formals_To_Match : Integer := 0;
20202 Actuals_To_Match : Integer := 0;
20204 procedure Chain (A : Node_Id);
20205 -- Add named actual at the proper place in the list, using the
20206 -- Next_Named_Actual link.
20208 function Reporting return Boolean;
20209 -- Determines if an error is to be reported. To report an error, we
20210 -- need Report to be True, and also we do not report errors caused
20211 -- by calls to init procs that occur within other init procs. Such
20212 -- errors must always be cascaded errors, since if all the types are
20213 -- declared correctly, the compiler will certainly build decent calls.
20215 -----------
20216 -- Chain --
20217 -----------
20219 procedure Chain (A : Node_Id) is
20220 begin
20221 if No (Last) then
20223 -- Call node points to first actual in list
20225 Set_First_Named_Actual (N, Explicit_Actual_Parameter (A));
20227 else
20228 Set_Next_Named_Actual (Last, Explicit_Actual_Parameter (A));
20229 end if;
20231 Last := A;
20232 Set_Next_Named_Actual (Last, Empty);
20233 end Chain;
20235 ---------------
20236 -- Reporting --
20237 ---------------
20239 function Reporting return Boolean is
20240 begin
20241 if not Report then
20242 return False;
20244 elsif not Within_Init_Proc then
20245 return True;
20247 elsif Is_Init_Proc (Entity (Name (N))) then
20248 return False;
20250 else
20251 return True;
20252 end if;
20253 end Reporting;
20255 -- Start of processing for Normalize_Actuals
20257 begin
20258 if Is_Access_Type (S) then
20260 -- The name in the call is a function call that returns an access
20261 -- to subprogram. The designated type has the list of formals.
20263 Formal := First_Formal (Designated_Type (S));
20264 else
20265 Formal := First_Formal (S);
20266 end if;
20268 while Present (Formal) loop
20269 Formals_To_Match := Formals_To_Match + 1;
20270 Next_Formal (Formal);
20271 end loop;
20273 -- Find if there is a named association, and verify that no positional
20274 -- associations appear after named ones.
20276 if Present (Actuals) then
20277 Actual := First (Actuals);
20278 end if;
20280 while Present (Actual)
20281 and then Nkind (Actual) /= N_Parameter_Association
20282 loop
20283 Actuals_To_Match := Actuals_To_Match + 1;
20284 Next (Actual);
20285 end loop;
20287 if No (Actual) and Actuals_To_Match = Formals_To_Match then
20289 -- Most common case: positional notation, no defaults
20291 Success := True;
20292 return;
20294 elsif Actuals_To_Match > Formals_To_Match then
20296 -- Too many actuals: will not work
20298 if Reporting then
20299 if Is_Entity_Name (Name (N)) then
20300 Error_Msg_N ("too many arguments in call to&", Name (N));
20301 else
20302 Error_Msg_N ("too many arguments in call", N);
20303 end if;
20304 end if;
20306 Success := False;
20307 return;
20308 end if;
20310 First_Named := Actual;
20312 while Present (Actual) loop
20313 if Nkind (Actual) /= N_Parameter_Association then
20314 Error_Msg_N
20315 ("positional parameters not allowed after named ones", Actual);
20316 Success := False;
20317 return;
20319 else
20320 Actuals_To_Match := Actuals_To_Match + 1;
20321 end if;
20323 Next (Actual);
20324 end loop;
20326 if Present (Actuals) then
20327 Actual := First (Actuals);
20328 end if;
20330 Formal := First_Formal (S);
20331 while Present (Formal) loop
20333 -- Match the formals in order. If the corresponding actual is
20334 -- positional, nothing to do. Else scan the list of named actuals
20335 -- to find the one with the right name.
20337 if Present (Actual)
20338 and then Nkind (Actual) /= N_Parameter_Association
20339 then
20340 Next (Actual);
20341 Actuals_To_Match := Actuals_To_Match - 1;
20342 Formals_To_Match := Formals_To_Match - 1;
20344 else
20345 -- For named parameters, search the list of actuals to find
20346 -- one that matches the next formal name.
20348 Actual := First_Named;
20349 Found := False;
20350 while Present (Actual) loop
20351 if Chars (Selector_Name (Actual)) = Chars (Formal) then
20352 Found := True;
20353 Chain (Actual);
20354 Actuals_To_Match := Actuals_To_Match - 1;
20355 Formals_To_Match := Formals_To_Match - 1;
20356 exit;
20357 end if;
20359 Next (Actual);
20360 end loop;
20362 if not Found then
20363 if Ekind (Formal) /= E_In_Parameter
20364 or else No (Default_Value (Formal))
20365 then
20366 if Reporting then
20367 if (Comes_From_Source (S)
20368 or else Sloc (S) = Standard_Location)
20369 and then Is_Overloadable (S)
20370 then
20371 if No (Actuals)
20372 and then
20373 Nkind_In (Parent (N), N_Procedure_Call_Statement,
20374 N_Function_Call,
20375 N_Parameter_Association)
20376 and then Ekind (S) /= E_Function
20377 then
20378 Set_Etype (N, Etype (S));
20380 else
20381 Error_Msg_Name_1 := Chars (S);
20382 Error_Msg_Sloc := Sloc (S);
20383 Error_Msg_NE
20384 ("missing argument for parameter & "
20385 & "in call to % declared #", N, Formal);
20386 end if;
20388 elsif Is_Overloadable (S) then
20389 Error_Msg_Name_1 := Chars (S);
20391 -- Point to type derivation that generated the
20392 -- operation.
20394 Error_Msg_Sloc := Sloc (Parent (S));
20396 Error_Msg_NE
20397 ("missing argument for parameter & "
20398 & "in call to % (inherited) #", N, Formal);
20400 else
20401 Error_Msg_NE
20402 ("missing argument for parameter &", N, Formal);
20403 end if;
20404 end if;
20406 Success := False;
20407 return;
20409 else
20410 Formals_To_Match := Formals_To_Match - 1;
20411 end if;
20412 end if;
20413 end if;
20415 Next_Formal (Formal);
20416 end loop;
20418 if Formals_To_Match = 0 and then Actuals_To_Match = 0 then
20419 Success := True;
20420 return;
20422 else
20423 if Reporting then
20425 -- Find some superfluous named actual that did not get
20426 -- attached to the list of associations.
20428 Actual := First (Actuals);
20429 while Present (Actual) loop
20430 if Nkind (Actual) = N_Parameter_Association
20431 and then Actual /= Last
20432 and then No (Next_Named_Actual (Actual))
20433 then
20434 -- A validity check may introduce a copy of a call that
20435 -- includes an extra actual (for example for an unrelated
20436 -- accessibility check). Check that the extra actual matches
20437 -- some extra formal, which must exist already because
20438 -- subprogram must be frozen at this point.
20440 if Present (Extra_Formals (S))
20441 and then not Comes_From_Source (Actual)
20442 and then Nkind (Actual) = N_Parameter_Association
20443 and then Chars (Extra_Formals (S)) =
20444 Chars (Selector_Name (Actual))
20445 then
20446 null;
20447 else
20448 Error_Msg_N
20449 ("unmatched actual & in call", Selector_Name (Actual));
20450 exit;
20451 end if;
20452 end if;
20454 Next (Actual);
20455 end loop;
20456 end if;
20458 Success := False;
20459 return;
20460 end if;
20461 end Normalize_Actuals;
20463 --------------------------------
20464 -- Note_Possible_Modification --
20465 --------------------------------
20467 procedure Note_Possible_Modification (N : Node_Id; Sure : Boolean) is
20468 Modification_Comes_From_Source : constant Boolean :=
20469 Comes_From_Source (Parent (N));
20471 Ent : Entity_Id;
20472 Exp : Node_Id;
20474 begin
20475 -- Loop to find referenced entity, if there is one
20477 Exp := N;
20478 loop
20479 Ent := Empty;
20481 if Is_Entity_Name (Exp) then
20482 Ent := Entity (Exp);
20484 -- If the entity is missing, it is an undeclared identifier,
20485 -- and there is nothing to annotate.
20487 if No (Ent) then
20488 return;
20489 end if;
20491 elsif Nkind (Exp) = N_Explicit_Dereference then
20492 declare
20493 P : constant Node_Id := Prefix (Exp);
20495 begin
20496 -- In formal verification mode, keep track of all reads and
20497 -- writes through explicit dereferences.
20499 if GNATprove_Mode then
20500 SPARK_Specific.Generate_Dereference (N, 'm');
20501 end if;
20503 if Nkind (P) = N_Selected_Component
20504 and then Present (Entry_Formal (Entity (Selector_Name (P))))
20505 then
20506 -- Case of a reference to an entry formal
20508 Ent := Entry_Formal (Entity (Selector_Name (P)));
20510 elsif Nkind (P) = N_Identifier
20511 and then Nkind (Parent (Entity (P))) = N_Object_Declaration
20512 and then Present (Expression (Parent (Entity (P))))
20513 and then Nkind (Expression (Parent (Entity (P)))) =
20514 N_Reference
20515 then
20516 -- Case of a reference to a value on which side effects have
20517 -- been removed.
20519 Exp := Prefix (Expression (Parent (Entity (P))));
20520 goto Continue;
20522 else
20523 return;
20524 end if;
20525 end;
20527 elsif Nkind_In (Exp, N_Type_Conversion,
20528 N_Unchecked_Type_Conversion)
20529 then
20530 Exp := Expression (Exp);
20531 goto Continue;
20533 elsif Nkind_In (Exp, N_Slice,
20534 N_Indexed_Component,
20535 N_Selected_Component)
20536 then
20537 -- Special check, if the prefix is an access type, then return
20538 -- since we are modifying the thing pointed to, not the prefix.
20539 -- When we are expanding, most usually the prefix is replaced
20540 -- by an explicit dereference, and this test is not needed, but
20541 -- in some cases (notably -gnatc mode and generics) when we do
20542 -- not do full expansion, we need this special test.
20544 if Is_Access_Type (Etype (Prefix (Exp))) then
20545 return;
20547 -- Otherwise go to prefix and keep going
20549 else
20550 Exp := Prefix (Exp);
20551 goto Continue;
20552 end if;
20554 -- All other cases, not a modification
20556 else
20557 return;
20558 end if;
20560 -- Now look for entity being referenced
20562 if Present (Ent) then
20563 if Is_Object (Ent) then
20564 if Comes_From_Source (Exp)
20565 or else Modification_Comes_From_Source
20566 then
20567 -- Give warning if pragma unmodified is given and we are
20568 -- sure this is a modification.
20570 if Has_Pragma_Unmodified (Ent) and then Sure then
20572 -- Note that the entity may be present only as a result
20573 -- of pragma Unused.
20575 if Has_Pragma_Unused (Ent) then
20576 Error_Msg_NE ("??pragma Unused given for &!", N, Ent);
20577 else
20578 Error_Msg_NE
20579 ("??pragma Unmodified given for &!", N, Ent);
20580 end if;
20581 end if;
20583 Set_Never_Set_In_Source (Ent, False);
20584 end if;
20586 Set_Is_True_Constant (Ent, False);
20587 Set_Current_Value (Ent, Empty);
20588 Set_Is_Known_Null (Ent, False);
20590 if not Can_Never_Be_Null (Ent) then
20591 Set_Is_Known_Non_Null (Ent, False);
20592 end if;
20594 -- Follow renaming chain
20596 if (Ekind (Ent) = E_Variable or else Ekind (Ent) = E_Constant)
20597 and then Present (Renamed_Object (Ent))
20598 then
20599 Exp := Renamed_Object (Ent);
20601 -- If the entity is the loop variable in an iteration over
20602 -- a container, retrieve container expression to indicate
20603 -- possible modification.
20605 if Present (Related_Expression (Ent))
20606 and then Nkind (Parent (Related_Expression (Ent))) =
20607 N_Iterator_Specification
20608 then
20609 Exp := Original_Node (Related_Expression (Ent));
20610 end if;
20612 goto Continue;
20614 -- The expression may be the renaming of a subcomponent of an
20615 -- array or container. The assignment to the subcomponent is
20616 -- a modification of the container.
20618 elsif Comes_From_Source (Original_Node (Exp))
20619 and then Nkind_In (Original_Node (Exp), N_Selected_Component,
20620 N_Indexed_Component)
20621 then
20622 Exp := Prefix (Original_Node (Exp));
20623 goto Continue;
20624 end if;
20626 -- Generate a reference only if the assignment comes from
20627 -- source. This excludes, for example, calls to a dispatching
20628 -- assignment operation when the left-hand side is tagged. In
20629 -- GNATprove mode, we need those references also on generated
20630 -- code, as these are used to compute the local effects of
20631 -- subprograms.
20633 if Modification_Comes_From_Source or GNATprove_Mode then
20634 Generate_Reference (Ent, Exp, 'm');
20636 -- If the target of the assignment is the bound variable
20637 -- in an iterator, indicate that the corresponding array
20638 -- or container is also modified.
20640 if Ada_Version >= Ada_2012
20641 and then Nkind (Parent (Ent)) = N_Iterator_Specification
20642 then
20643 declare
20644 Domain : constant Node_Id := Name (Parent (Ent));
20646 begin
20647 -- TBD : in the full version of the construct, the
20648 -- domain of iteration can be given by an expression.
20650 if Is_Entity_Name (Domain) then
20651 Generate_Reference (Entity (Domain), Exp, 'm');
20652 Set_Is_True_Constant (Entity (Domain), False);
20653 Set_Never_Set_In_Source (Entity (Domain), False);
20654 end if;
20655 end;
20656 end if;
20657 end if;
20658 end if;
20660 Kill_Checks (Ent);
20662 -- If we are sure this is a modification from source, and we know
20663 -- this modifies a constant, then give an appropriate warning.
20665 if Sure
20666 and then Modification_Comes_From_Source
20667 and then Overlays_Constant (Ent)
20668 and then Address_Clause_Overlay_Warnings
20669 then
20670 declare
20671 Addr : constant Node_Id := Address_Clause (Ent);
20672 O_Ent : Entity_Id;
20673 Off : Boolean;
20675 begin
20676 Find_Overlaid_Entity (Addr, O_Ent, Off);
20678 Error_Msg_Sloc := Sloc (Addr);
20679 Error_Msg_NE
20680 ("??constant& may be modified via address clause#",
20681 N, O_Ent);
20682 end;
20683 end if;
20685 return;
20686 end if;
20688 <<Continue>>
20689 null;
20690 end loop;
20691 end Note_Possible_Modification;
20693 -----------------
20694 -- Null_Status --
20695 -----------------
20697 function Null_Status (N : Node_Id) return Null_Status_Kind is
20698 function Is_Null_Excluding_Def (Def : Node_Id) return Boolean;
20699 -- Determine whether definition Def carries a null exclusion
20701 function Null_Status_Of_Entity (Id : Entity_Id) return Null_Status_Kind;
20702 -- Determine the null status of arbitrary entity Id
20704 function Null_Status_Of_Type (Typ : Entity_Id) return Null_Status_Kind;
20705 -- Determine the null status of type Typ
20707 ---------------------------
20708 -- Is_Null_Excluding_Def --
20709 ---------------------------
20711 function Is_Null_Excluding_Def (Def : Node_Id) return Boolean is
20712 begin
20713 return
20714 Nkind_In (Def, N_Access_Definition,
20715 N_Access_Function_Definition,
20716 N_Access_Procedure_Definition,
20717 N_Access_To_Object_Definition,
20718 N_Component_Definition,
20719 N_Derived_Type_Definition)
20720 and then Null_Exclusion_Present (Def);
20721 end Is_Null_Excluding_Def;
20723 ---------------------------
20724 -- Null_Status_Of_Entity --
20725 ---------------------------
20727 function Null_Status_Of_Entity
20728 (Id : Entity_Id) return Null_Status_Kind
20730 Decl : constant Node_Id := Declaration_Node (Id);
20731 Def : Node_Id;
20733 begin
20734 -- The value of an imported or exported entity may be set externally
20735 -- regardless of a null exclusion. As a result, the value cannot be
20736 -- determined statically.
20738 if Is_Imported (Id) or else Is_Exported (Id) then
20739 return Unknown;
20741 elsif Nkind_In (Decl, N_Component_Declaration,
20742 N_Discriminant_Specification,
20743 N_Formal_Object_Declaration,
20744 N_Object_Declaration,
20745 N_Object_Renaming_Declaration,
20746 N_Parameter_Specification)
20747 then
20748 -- A component declaration yields a non-null value when either
20749 -- its component definition or access definition carries a null
20750 -- exclusion.
20752 if Nkind (Decl) = N_Component_Declaration then
20753 Def := Component_Definition (Decl);
20755 if Is_Null_Excluding_Def (Def) then
20756 return Is_Non_Null;
20757 end if;
20759 Def := Access_Definition (Def);
20761 if Present (Def) and then Is_Null_Excluding_Def (Def) then
20762 return Is_Non_Null;
20763 end if;
20765 -- A formal object declaration yields a non-null value if its
20766 -- access definition carries a null exclusion. If the object is
20767 -- default initialized, then the value depends on the expression.
20769 elsif Nkind (Decl) = N_Formal_Object_Declaration then
20770 Def := Access_Definition (Decl);
20772 if Present (Def) and then Is_Null_Excluding_Def (Def) then
20773 return Is_Non_Null;
20774 end if;
20776 -- A constant may yield a null or non-null value depending on its
20777 -- initialization expression.
20779 elsif Ekind (Id) = E_Constant then
20780 return Null_Status (Constant_Value (Id));
20782 -- The construct yields a non-null value when it has a null
20783 -- exclusion.
20785 elsif Null_Exclusion_Present (Decl) then
20786 return Is_Non_Null;
20788 -- An object renaming declaration yields a non-null value if its
20789 -- access definition carries a null exclusion. Otherwise the value
20790 -- depends on the renamed name.
20792 elsif Nkind (Decl) = N_Object_Renaming_Declaration then
20793 Def := Access_Definition (Decl);
20795 if Present (Def) and then Is_Null_Excluding_Def (Def) then
20796 return Is_Non_Null;
20798 else
20799 return Null_Status (Name (Decl));
20800 end if;
20801 end if;
20802 end if;
20804 -- At this point the declaration of the entity does not carry a null
20805 -- exclusion and lacks an initialization expression. Check the status
20806 -- of its type.
20808 return Null_Status_Of_Type (Etype (Id));
20809 end Null_Status_Of_Entity;
20811 -------------------------
20812 -- Null_Status_Of_Type --
20813 -------------------------
20815 function Null_Status_Of_Type (Typ : Entity_Id) return Null_Status_Kind is
20816 Curr : Entity_Id;
20817 Decl : Node_Id;
20819 begin
20820 -- Traverse the type chain looking for types with null exclusion
20822 Curr := Typ;
20823 while Present (Curr) and then Etype (Curr) /= Curr loop
20824 Decl := Parent (Curr);
20826 -- Guard against itypes which do not always have declarations. A
20827 -- type yields a non-null value if it carries a null exclusion.
20829 if Present (Decl) then
20830 if Nkind (Decl) = N_Full_Type_Declaration
20831 and then Is_Null_Excluding_Def (Type_Definition (Decl))
20832 then
20833 return Is_Non_Null;
20835 elsif Nkind (Decl) = N_Subtype_Declaration
20836 and then Null_Exclusion_Present (Decl)
20837 then
20838 return Is_Non_Null;
20839 end if;
20840 end if;
20842 Curr := Etype (Curr);
20843 end loop;
20845 -- The type chain does not contain any null excluding types
20847 return Unknown;
20848 end Null_Status_Of_Type;
20850 -- Start of processing for Null_Status
20852 begin
20853 -- An allocator always creates a non-null value
20855 if Nkind (N) = N_Allocator then
20856 return Is_Non_Null;
20858 -- Taking the 'Access of something yields a non-null value
20860 elsif Nkind (N) = N_Attribute_Reference
20861 and then Nam_In (Attribute_Name (N), Name_Access,
20862 Name_Unchecked_Access,
20863 Name_Unrestricted_Access)
20864 then
20865 return Is_Non_Null;
20867 -- "null" yields null
20869 elsif Nkind (N) = N_Null then
20870 return Is_Null;
20872 -- Check the status of the operand of a type conversion
20874 elsif Nkind (N) = N_Type_Conversion then
20875 return Null_Status (Expression (N));
20877 -- The input denotes a reference to an entity. Determine whether the
20878 -- entity or its type yields a null or non-null value.
20880 elsif Is_Entity_Name (N) and then Present (Entity (N)) then
20881 return Null_Status_Of_Entity (Entity (N));
20882 end if;
20884 -- Otherwise it is not possible to determine the null status of the
20885 -- subexpression at compile time without resorting to simple flow
20886 -- analysis.
20888 return Unknown;
20889 end Null_Status;
20891 --------------------------------------
20892 -- Null_To_Null_Address_Convert_OK --
20893 --------------------------------------
20895 function Null_To_Null_Address_Convert_OK
20896 (N : Node_Id;
20897 Typ : Entity_Id := Empty) return Boolean
20899 begin
20900 if not Relaxed_RM_Semantics then
20901 return False;
20902 end if;
20904 if Nkind (N) = N_Null then
20905 return Present (Typ) and then Is_Descendant_Of_Address (Typ);
20907 elsif Nkind_In (N, N_Op_Eq, N_Op_Ge, N_Op_Gt, N_Op_Le, N_Op_Lt, N_Op_Ne)
20908 then
20909 declare
20910 L : constant Node_Id := Left_Opnd (N);
20911 R : constant Node_Id := Right_Opnd (N);
20913 begin
20914 -- We check the Etype of the complementary operand since the
20915 -- N_Null node is not decorated at this stage.
20917 return
20918 ((Nkind (L) = N_Null
20919 and then Is_Descendant_Of_Address (Etype (R)))
20920 or else
20921 (Nkind (R) = N_Null
20922 and then Is_Descendant_Of_Address (Etype (L))));
20923 end;
20924 end if;
20926 return False;
20927 end Null_To_Null_Address_Convert_OK;
20929 ---------------------------------
20930 -- Number_Of_Elements_In_Array --
20931 ---------------------------------
20933 function Number_Of_Elements_In_Array (T : Entity_Id) return Int is
20934 Indx : Node_Id;
20935 Typ : Entity_Id;
20936 Low : Node_Id;
20937 High : Node_Id;
20938 Num : Int := 1;
20940 begin
20941 pragma Assert (Is_Array_Type (T));
20943 Indx := First_Index (T);
20944 while Present (Indx) loop
20945 Typ := Underlying_Type (Etype (Indx));
20947 -- Never look at junk bounds of a generic type
20949 if Is_Generic_Type (Typ) then
20950 return 0;
20951 end if;
20953 -- Check the array bounds are known at compile time and return zero
20954 -- if they are not.
20956 Low := Type_Low_Bound (Typ);
20957 High := Type_High_Bound (Typ);
20959 if not Compile_Time_Known_Value (Low) then
20960 return 0;
20961 elsif not Compile_Time_Known_Value (High) then
20962 return 0;
20963 else
20964 Num :=
20965 Num * UI_To_Int ((Expr_Value (High) - Expr_Value (Low) + 1));
20966 end if;
20968 Next_Index (Indx);
20969 end loop;
20971 return Num;
20972 end Number_Of_Elements_In_Array;
20974 -------------------------
20975 -- Object_Access_Level --
20976 -------------------------
20978 -- Returns the static accessibility level of the view denoted by Obj. Note
20979 -- that the value returned is the result of a call to Scope_Depth. Only
20980 -- scope depths associated with dynamic scopes can actually be returned.
20981 -- Since only relative levels matter for accessibility checking, the fact
20982 -- that the distance between successive levels of accessibility is not
20983 -- always one is immaterial (invariant: if level(E2) is deeper than
20984 -- level(E1), then Scope_Depth(E1) < Scope_Depth(E2)).
20986 function Object_Access_Level (Obj : Node_Id) return Uint is
20987 function Is_Interface_Conversion (N : Node_Id) return Boolean;
20988 -- Determine whether N is a construct of the form
20989 -- Some_Type (Operand._tag'Address)
20990 -- This construct appears in the context of dispatching calls.
20992 function Reference_To (Obj : Node_Id) return Node_Id;
20993 -- An explicit dereference is created when removing side effects from
20994 -- expressions for constraint checking purposes. In this case a local
20995 -- access type is created for it. The correct access level is that of
20996 -- the original source node. We detect this case by noting that the
20997 -- prefix of the dereference is created by an object declaration whose
20998 -- initial expression is a reference.
21000 -----------------------------
21001 -- Is_Interface_Conversion --
21002 -----------------------------
21004 function Is_Interface_Conversion (N : Node_Id) return Boolean is
21005 begin
21006 return Nkind (N) = N_Unchecked_Type_Conversion
21007 and then Nkind (Expression (N)) = N_Attribute_Reference
21008 and then Attribute_Name (Expression (N)) = Name_Address;
21009 end Is_Interface_Conversion;
21011 ------------------
21012 -- Reference_To --
21013 ------------------
21015 function Reference_To (Obj : Node_Id) return Node_Id is
21016 Pref : constant Node_Id := Prefix (Obj);
21017 begin
21018 if Is_Entity_Name (Pref)
21019 and then Nkind (Parent (Entity (Pref))) = N_Object_Declaration
21020 and then Present (Expression (Parent (Entity (Pref))))
21021 and then Nkind (Expression (Parent (Entity (Pref)))) = N_Reference
21022 then
21023 return (Prefix (Expression (Parent (Entity (Pref)))));
21024 else
21025 return Empty;
21026 end if;
21027 end Reference_To;
21029 -- Local variables
21031 E : Entity_Id;
21033 -- Start of processing for Object_Access_Level
21035 begin
21036 if Nkind (Obj) = N_Defining_Identifier
21037 or else Is_Entity_Name (Obj)
21038 then
21039 if Nkind (Obj) = N_Defining_Identifier then
21040 E := Obj;
21041 else
21042 E := Entity (Obj);
21043 end if;
21045 if Is_Prival (E) then
21046 E := Prival_Link (E);
21047 end if;
21049 -- If E is a type then it denotes a current instance. For this case
21050 -- we add one to the normal accessibility level of the type to ensure
21051 -- that current instances are treated as always being deeper than
21052 -- than the level of any visible named access type (see 3.10.2(21)).
21054 if Is_Type (E) then
21055 return Type_Access_Level (E) + 1;
21057 elsif Present (Renamed_Object (E)) then
21058 return Object_Access_Level (Renamed_Object (E));
21060 -- Similarly, if E is a component of the current instance of a
21061 -- protected type, any instance of it is assumed to be at a deeper
21062 -- level than the type. For a protected object (whose type is an
21063 -- anonymous protected type) its components are at the same level
21064 -- as the type itself.
21066 elsif not Is_Overloadable (E)
21067 and then Ekind (Scope (E)) = E_Protected_Type
21068 and then Comes_From_Source (Scope (E))
21069 then
21070 return Type_Access_Level (Scope (E)) + 1;
21072 else
21073 -- Aliased formals of functions take their access level from the
21074 -- point of call, i.e. require a dynamic check. For static check
21075 -- purposes, this is smaller than the level of the subprogram
21076 -- itself. For procedures the aliased makes no difference.
21078 if Is_Formal (E)
21079 and then Is_Aliased (E)
21080 and then Ekind (Scope (E)) = E_Function
21081 then
21082 return Type_Access_Level (Etype (E));
21084 else
21085 return Scope_Depth (Enclosing_Dynamic_Scope (E));
21086 end if;
21087 end if;
21089 elsif Nkind_In (Obj, N_Indexed_Component, N_Selected_Component) then
21090 if Is_Access_Type (Etype (Prefix (Obj))) then
21091 return Type_Access_Level (Etype (Prefix (Obj)));
21092 else
21093 return Object_Access_Level (Prefix (Obj));
21094 end if;
21096 elsif Nkind (Obj) = N_Explicit_Dereference then
21098 -- If the prefix is a selected access discriminant then we make a
21099 -- recursive call on the prefix, which will in turn check the level
21100 -- of the prefix object of the selected discriminant.
21102 -- In Ada 2012, if the discriminant has implicit dereference and
21103 -- the context is a selected component, treat this as an object of
21104 -- unknown scope (see below). This is necessary in compile-only mode;
21105 -- otherwise expansion will already have transformed the prefix into
21106 -- a temporary.
21108 if Nkind (Prefix (Obj)) = N_Selected_Component
21109 and then Ekind (Etype (Prefix (Obj))) = E_Anonymous_Access_Type
21110 and then
21111 Ekind (Entity (Selector_Name (Prefix (Obj)))) = E_Discriminant
21112 and then
21113 (not Has_Implicit_Dereference
21114 (Entity (Selector_Name (Prefix (Obj))))
21115 or else Nkind (Parent (Obj)) /= N_Selected_Component)
21116 then
21117 return Object_Access_Level (Prefix (Obj));
21119 -- Detect an interface conversion in the context of a dispatching
21120 -- call. Use the original form of the conversion to find the access
21121 -- level of the operand.
21123 elsif Is_Interface (Etype (Obj))
21124 and then Is_Interface_Conversion (Prefix (Obj))
21125 and then Nkind (Original_Node (Obj)) = N_Type_Conversion
21126 then
21127 return Object_Access_Level (Original_Node (Obj));
21129 elsif not Comes_From_Source (Obj) then
21130 declare
21131 Ref : constant Node_Id := Reference_To (Obj);
21132 begin
21133 if Present (Ref) then
21134 return Object_Access_Level (Ref);
21135 else
21136 return Type_Access_Level (Etype (Prefix (Obj)));
21137 end if;
21138 end;
21140 else
21141 return Type_Access_Level (Etype (Prefix (Obj)));
21142 end if;
21144 elsif Nkind_In (Obj, N_Type_Conversion, N_Unchecked_Type_Conversion) then
21145 return Object_Access_Level (Expression (Obj));
21147 elsif Nkind (Obj) = N_Function_Call then
21149 -- Function results are objects, so we get either the access level of
21150 -- the function or, in the case of an indirect call, the level of the
21151 -- access-to-subprogram type. (This code is used for Ada 95, but it
21152 -- looks wrong, because it seems that we should be checking the level
21153 -- of the call itself, even for Ada 95. However, using the Ada 2005
21154 -- version of the code causes regressions in several tests that are
21155 -- compiled with -gnat95. ???)
21157 if Ada_Version < Ada_2005 then
21158 if Is_Entity_Name (Name (Obj)) then
21159 return Subprogram_Access_Level (Entity (Name (Obj)));
21160 else
21161 return Type_Access_Level (Etype (Prefix (Name (Obj))));
21162 end if;
21164 -- For Ada 2005, the level of the result object of a function call is
21165 -- defined to be the level of the call's innermost enclosing master.
21166 -- We determine that by querying the depth of the innermost enclosing
21167 -- dynamic scope.
21169 else
21170 Return_Master_Scope_Depth_Of_Call : declare
21171 function Innermost_Master_Scope_Depth
21172 (N : Node_Id) return Uint;
21173 -- Returns the scope depth of the given node's innermost
21174 -- enclosing dynamic scope (effectively the accessibility
21175 -- level of the innermost enclosing master).
21177 ----------------------------------
21178 -- Innermost_Master_Scope_Depth --
21179 ----------------------------------
21181 function Innermost_Master_Scope_Depth
21182 (N : Node_Id) return Uint
21184 Node_Par : Node_Id := Parent (N);
21186 begin
21187 -- Locate the nearest enclosing node (by traversing Parents)
21188 -- that Defining_Entity can be applied to, and return the
21189 -- depth of that entity's nearest enclosing dynamic scope.
21191 while Present (Node_Par) loop
21192 case Nkind (Node_Par) is
21193 when N_Abstract_Subprogram_Declaration
21194 | N_Block_Statement
21195 | N_Body_Stub
21196 | N_Component_Declaration
21197 | N_Entry_Body
21198 | N_Entry_Declaration
21199 | N_Exception_Declaration
21200 | N_Formal_Object_Declaration
21201 | N_Formal_Package_Declaration
21202 | N_Formal_Subprogram_Declaration
21203 | N_Formal_Type_Declaration
21204 | N_Full_Type_Declaration
21205 | N_Function_Specification
21206 | N_Generic_Declaration
21207 | N_Generic_Instantiation
21208 | N_Implicit_Label_Declaration
21209 | N_Incomplete_Type_Declaration
21210 | N_Loop_Parameter_Specification
21211 | N_Number_Declaration
21212 | N_Object_Declaration
21213 | N_Package_Declaration
21214 | N_Package_Specification
21215 | N_Parameter_Specification
21216 | N_Private_Extension_Declaration
21217 | N_Private_Type_Declaration
21218 | N_Procedure_Specification
21219 | N_Proper_Body
21220 | N_Protected_Type_Declaration
21221 | N_Renaming_Declaration
21222 | N_Single_Protected_Declaration
21223 | N_Single_Task_Declaration
21224 | N_Subprogram_Declaration
21225 | N_Subtype_Declaration
21226 | N_Subunit
21227 | N_Task_Type_Declaration
21229 return Scope_Depth
21230 (Nearest_Dynamic_Scope
21231 (Defining_Entity (Node_Par)));
21233 -- For a return statement within a function, return
21234 -- the depth of the function itself. This is not just
21235 -- a small optimization, but matters when analyzing
21236 -- the expression in an expression function before
21237 -- the body is created.
21239 when N_Simple_Return_Statement =>
21240 if Ekind (Current_Scope) = E_Function then
21241 return Scope_Depth (Current_Scope);
21242 end if;
21244 when others =>
21245 null;
21246 end case;
21248 Node_Par := Parent (Node_Par);
21249 end loop;
21251 pragma Assert (False);
21253 -- Should never reach the following return
21255 return Scope_Depth (Current_Scope) + 1;
21256 end Innermost_Master_Scope_Depth;
21258 -- Start of processing for Return_Master_Scope_Depth_Of_Call
21260 begin
21261 return Innermost_Master_Scope_Depth (Obj);
21262 end Return_Master_Scope_Depth_Of_Call;
21263 end if;
21265 -- For convenience we handle qualified expressions, even though they
21266 -- aren't technically object names.
21268 elsif Nkind (Obj) = N_Qualified_Expression then
21269 return Object_Access_Level (Expression (Obj));
21271 -- Ditto for aggregates. They have the level of the temporary that
21272 -- will hold their value.
21274 elsif Nkind (Obj) = N_Aggregate then
21275 return Object_Access_Level (Current_Scope);
21277 -- Otherwise return the scope level of Standard. (If there are cases
21278 -- that fall through to this point they will be treated as having
21279 -- global accessibility for now. ???)
21281 else
21282 return Scope_Depth (Standard_Standard);
21283 end if;
21284 end Object_Access_Level;
21286 ----------------------------------
21287 -- Old_Requires_Transient_Scope --
21288 ----------------------------------
21290 function Old_Requires_Transient_Scope (Id : Entity_Id) return Boolean is
21291 Typ : constant Entity_Id := Underlying_Type (Id);
21293 begin
21294 -- This is a private type which is not completed yet. This can only
21295 -- happen in a default expression (of a formal parameter or of a
21296 -- record component). Do not expand transient scope in this case.
21298 if No (Typ) then
21299 return False;
21301 -- Do not expand transient scope for non-existent procedure return
21303 elsif Typ = Standard_Void_Type then
21304 return False;
21306 -- Elementary types do not require a transient scope
21308 elsif Is_Elementary_Type (Typ) then
21309 return False;
21311 -- Generally, indefinite subtypes require a transient scope, since the
21312 -- back end cannot generate temporaries, since this is not a valid type
21313 -- for declaring an object. It might be possible to relax this in the
21314 -- future, e.g. by declaring the maximum possible space for the type.
21316 elsif not Is_Definite_Subtype (Typ) then
21317 return True;
21319 -- Functions returning tagged types may dispatch on result so their
21320 -- returned value is allocated on the secondary stack. Controlled
21321 -- type temporaries need finalization.
21323 elsif Is_Tagged_Type (Typ) or else Has_Controlled_Component (Typ) then
21324 return True;
21326 -- Record type
21328 elsif Is_Record_Type (Typ) then
21329 declare
21330 Comp : Entity_Id;
21332 begin
21333 Comp := First_Entity (Typ);
21334 while Present (Comp) loop
21335 if Ekind (Comp) = E_Component then
21337 -- ???It's not clear we need a full recursive call to
21338 -- Old_Requires_Transient_Scope here. Note that the
21339 -- following can't happen.
21341 pragma Assert (Is_Definite_Subtype (Etype (Comp)));
21342 pragma Assert (not Has_Controlled_Component (Etype (Comp)));
21344 if Old_Requires_Transient_Scope (Etype (Comp)) then
21345 return True;
21346 end if;
21347 end if;
21349 Next_Entity (Comp);
21350 end loop;
21351 end;
21353 return False;
21355 -- String literal types never require transient scope
21357 elsif Ekind (Typ) = E_String_Literal_Subtype then
21358 return False;
21360 -- Array type. Note that we already know that this is a constrained
21361 -- array, since unconstrained arrays will fail the indefinite test.
21363 elsif Is_Array_Type (Typ) then
21365 -- If component type requires a transient scope, the array does too
21367 if Old_Requires_Transient_Scope (Component_Type (Typ)) then
21368 return True;
21370 -- Otherwise, we only need a transient scope if the size depends on
21371 -- the value of one or more discriminants.
21373 else
21374 return Size_Depends_On_Discriminant (Typ);
21375 end if;
21377 -- All other cases do not require a transient scope
21379 else
21380 pragma Assert (Is_Protected_Type (Typ) or else Is_Task_Type (Typ));
21381 return False;
21382 end if;
21383 end Old_Requires_Transient_Scope;
21385 ---------------------------------
21386 -- Original_Aspect_Pragma_Name --
21387 ---------------------------------
21389 function Original_Aspect_Pragma_Name (N : Node_Id) return Name_Id is
21390 Item : Node_Id;
21391 Item_Nam : Name_Id;
21393 begin
21394 pragma Assert (Nkind_In (N, N_Aspect_Specification, N_Pragma));
21396 Item := N;
21398 -- The pragma was generated to emulate an aspect, use the original
21399 -- aspect specification.
21401 if Nkind (Item) = N_Pragma and then From_Aspect_Specification (Item) then
21402 Item := Corresponding_Aspect (Item);
21403 end if;
21405 -- Retrieve the name of the aspect/pragma. Note that Pre, Pre_Class,
21406 -- Post and Post_Class rewrite their pragma identifier to preserve the
21407 -- original name.
21408 -- ??? this is kludgey
21410 if Nkind (Item) = N_Pragma then
21411 Item_Nam := Chars (Original_Node (Pragma_Identifier (Item)));
21413 else
21414 pragma Assert (Nkind (Item) = N_Aspect_Specification);
21415 Item_Nam := Chars (Identifier (Item));
21416 end if;
21418 -- Deal with 'Class by converting the name to its _XXX form
21420 if Class_Present (Item) then
21421 if Item_Nam = Name_Invariant then
21422 Item_Nam := Name_uInvariant;
21424 elsif Item_Nam = Name_Post then
21425 Item_Nam := Name_uPost;
21427 elsif Item_Nam = Name_Pre then
21428 Item_Nam := Name_uPre;
21430 elsif Nam_In (Item_Nam, Name_Type_Invariant,
21431 Name_Type_Invariant_Class)
21432 then
21433 Item_Nam := Name_uType_Invariant;
21435 -- Nothing to do for other cases (e.g. a Check that derived from
21436 -- Pre_Class and has the flag set). Also we do nothing if the name
21437 -- is already in special _xxx form.
21439 end if;
21440 end if;
21442 return Item_Nam;
21443 end Original_Aspect_Pragma_Name;
21445 --------------------------------------
21446 -- Original_Corresponding_Operation --
21447 --------------------------------------
21449 function Original_Corresponding_Operation (S : Entity_Id) return Entity_Id
21451 Typ : constant Entity_Id := Find_Dispatching_Type (S);
21453 begin
21454 -- If S is an inherited primitive S2 the original corresponding
21455 -- operation of S is the original corresponding operation of S2
21457 if Present (Alias (S))
21458 and then Find_Dispatching_Type (Alias (S)) /= Typ
21459 then
21460 return Original_Corresponding_Operation (Alias (S));
21462 -- If S overrides an inherited subprogram S2 the original corresponding
21463 -- operation of S is the original corresponding operation of S2
21465 elsif Present (Overridden_Operation (S)) then
21466 return Original_Corresponding_Operation (Overridden_Operation (S));
21468 -- otherwise it is S itself
21470 else
21471 return S;
21472 end if;
21473 end Original_Corresponding_Operation;
21475 -------------------
21476 -- Output_Entity --
21477 -------------------
21479 procedure Output_Entity (Id : Entity_Id) is
21480 Scop : Entity_Id;
21482 begin
21483 Scop := Scope (Id);
21485 -- The entity may lack a scope when it is in the process of being
21486 -- analyzed. Use the current scope as an approximation.
21488 if No (Scop) then
21489 Scop := Current_Scope;
21490 end if;
21492 Output_Name (Chars (Id), Scop);
21493 end Output_Entity;
21495 -----------------
21496 -- Output_Name --
21497 -----------------
21499 procedure Output_Name (Nam : Name_Id; Scop : Entity_Id := Current_Scope) is
21500 begin
21501 Write_Str
21502 (Get_Name_String
21503 (Get_Qualified_Name
21504 (Nam => Nam,
21505 Suffix => No_Name,
21506 Scop => Scop)));
21507 Write_Eol;
21508 end Output_Name;
21510 ----------------------
21511 -- Policy_In_Effect --
21512 ----------------------
21514 function Policy_In_Effect (Policy : Name_Id) return Name_Id is
21515 function Policy_In_List (List : Node_Id) return Name_Id;
21516 -- Determine the mode of a policy in a N_Pragma list
21518 --------------------
21519 -- Policy_In_List --
21520 --------------------
21522 function Policy_In_List (List : Node_Id) return Name_Id is
21523 Arg1 : Node_Id;
21524 Arg2 : Node_Id;
21525 Prag : Node_Id;
21527 begin
21528 Prag := List;
21529 while Present (Prag) loop
21530 Arg1 := First (Pragma_Argument_Associations (Prag));
21531 Arg2 := Next (Arg1);
21533 Arg1 := Get_Pragma_Arg (Arg1);
21534 Arg2 := Get_Pragma_Arg (Arg2);
21536 -- The current Check_Policy pragma matches the requested policy or
21537 -- appears in the single argument form (Assertion, policy_id).
21539 if Nam_In (Chars (Arg1), Name_Assertion, Policy) then
21540 return Chars (Arg2);
21541 end if;
21543 Prag := Next_Pragma (Prag);
21544 end loop;
21546 return No_Name;
21547 end Policy_In_List;
21549 -- Local variables
21551 Kind : Name_Id;
21553 -- Start of processing for Policy_In_Effect
21555 begin
21556 if not Is_Valid_Assertion_Kind (Policy) then
21557 raise Program_Error;
21558 end if;
21560 -- Inspect all policy pragmas that appear within scopes (if any)
21562 Kind := Policy_In_List (Check_Policy_List);
21564 -- Inspect all configuration policy pragmas (if any)
21566 if Kind = No_Name then
21567 Kind := Policy_In_List (Check_Policy_List_Config);
21568 end if;
21570 -- The context lacks policy pragmas, determine the mode based on whether
21571 -- assertions are enabled at the configuration level. This ensures that
21572 -- the policy is preserved when analyzing generics.
21574 if Kind = No_Name then
21575 if Assertions_Enabled_Config then
21576 Kind := Name_Check;
21577 else
21578 Kind := Name_Ignore;
21579 end if;
21580 end if;
21582 return Kind;
21583 end Policy_In_Effect;
21585 ----------------------------------
21586 -- Predicate_Tests_On_Arguments --
21587 ----------------------------------
21589 function Predicate_Tests_On_Arguments (Subp : Entity_Id) return Boolean is
21590 begin
21591 -- Always test predicates on indirect call
21593 if Ekind (Subp) = E_Subprogram_Type then
21594 return True;
21596 -- Do not test predicates on call to generated default Finalize, since
21597 -- we are not interested in whether something we are finalizing (and
21598 -- typically destroying) satisfies its predicates.
21600 elsif Chars (Subp) = Name_Finalize
21601 and then not Comes_From_Source (Subp)
21602 then
21603 return False;
21605 -- Do not test predicates on any internally generated routines
21607 elsif Is_Internal_Name (Chars (Subp)) then
21608 return False;
21610 -- Do not test predicates on call to Init_Proc, since if needed the
21611 -- predicate test will occur at some other point.
21613 elsif Is_Init_Proc (Subp) then
21614 return False;
21616 -- Do not test predicates on call to predicate function, since this
21617 -- would cause infinite recursion.
21619 elsif Ekind (Subp) = E_Function
21620 and then (Is_Predicate_Function (Subp)
21621 or else
21622 Is_Predicate_Function_M (Subp))
21623 then
21624 return False;
21626 -- For now, no other exceptions
21628 else
21629 return True;
21630 end if;
21631 end Predicate_Tests_On_Arguments;
21633 -----------------------
21634 -- Private_Component --
21635 -----------------------
21637 function Private_Component (Type_Id : Entity_Id) return Entity_Id is
21638 Ancestor : constant Entity_Id := Base_Type (Type_Id);
21640 function Trace_Components
21641 (T : Entity_Id;
21642 Check : Boolean) return Entity_Id;
21643 -- Recursive function that does the work, and checks against circular
21644 -- definition for each subcomponent type.
21646 ----------------------
21647 -- Trace_Components --
21648 ----------------------
21650 function Trace_Components
21651 (T : Entity_Id;
21652 Check : Boolean) return Entity_Id
21654 Btype : constant Entity_Id := Base_Type (T);
21655 Component : Entity_Id;
21656 P : Entity_Id;
21657 Candidate : Entity_Id := Empty;
21659 begin
21660 if Check and then Btype = Ancestor then
21661 Error_Msg_N ("circular type definition", Type_Id);
21662 return Any_Type;
21663 end if;
21665 if Is_Private_Type (Btype) and then not Is_Generic_Type (Btype) then
21666 if Present (Full_View (Btype))
21667 and then Is_Record_Type (Full_View (Btype))
21668 and then not Is_Frozen (Btype)
21669 then
21670 -- To indicate that the ancestor depends on a private type, the
21671 -- current Btype is sufficient. However, to check for circular
21672 -- definition we must recurse on the full view.
21674 Candidate := Trace_Components (Full_View (Btype), True);
21676 if Candidate = Any_Type then
21677 return Any_Type;
21678 else
21679 return Btype;
21680 end if;
21682 else
21683 return Btype;
21684 end if;
21686 elsif Is_Array_Type (Btype) then
21687 return Trace_Components (Component_Type (Btype), True);
21689 elsif Is_Record_Type (Btype) then
21690 Component := First_Entity (Btype);
21691 while Present (Component)
21692 and then Comes_From_Source (Component)
21693 loop
21694 -- Skip anonymous types generated by constrained components
21696 if not Is_Type (Component) then
21697 P := Trace_Components (Etype (Component), True);
21699 if Present (P) then
21700 if P = Any_Type then
21701 return P;
21702 else
21703 Candidate := P;
21704 end if;
21705 end if;
21706 end if;
21708 Next_Entity (Component);
21709 end loop;
21711 return Candidate;
21713 else
21714 return Empty;
21715 end if;
21716 end Trace_Components;
21718 -- Start of processing for Private_Component
21720 begin
21721 return Trace_Components (Type_Id, False);
21722 end Private_Component;
21724 ---------------------------
21725 -- Primitive_Names_Match --
21726 ---------------------------
21728 function Primitive_Names_Match (E1, E2 : Entity_Id) return Boolean is
21729 function Non_Internal_Name (E : Entity_Id) return Name_Id;
21730 -- Given an internal name, returns the corresponding non-internal name
21732 ------------------------
21733 -- Non_Internal_Name --
21734 ------------------------
21736 function Non_Internal_Name (E : Entity_Id) return Name_Id is
21737 begin
21738 Get_Name_String (Chars (E));
21739 Name_Len := Name_Len - 1;
21740 return Name_Find;
21741 end Non_Internal_Name;
21743 -- Start of processing for Primitive_Names_Match
21745 begin
21746 pragma Assert (Present (E1) and then Present (E2));
21748 return Chars (E1) = Chars (E2)
21749 or else
21750 (not Is_Internal_Name (Chars (E1))
21751 and then Is_Internal_Name (Chars (E2))
21752 and then Non_Internal_Name (E2) = Chars (E1))
21753 or else
21754 (not Is_Internal_Name (Chars (E2))
21755 and then Is_Internal_Name (Chars (E1))
21756 and then Non_Internal_Name (E1) = Chars (E2))
21757 or else
21758 (Is_Predefined_Dispatching_Operation (E1)
21759 and then Is_Predefined_Dispatching_Operation (E2)
21760 and then Same_TSS (E1, E2))
21761 or else
21762 (Is_Init_Proc (E1) and then Is_Init_Proc (E2));
21763 end Primitive_Names_Match;
21765 -----------------------
21766 -- Process_End_Label --
21767 -----------------------
21769 procedure Process_End_Label
21770 (N : Node_Id;
21771 Typ : Character;
21772 Ent : Entity_Id)
21774 Loc : Source_Ptr;
21775 Nam : Node_Id;
21776 Scop : Entity_Id;
21778 Label_Ref : Boolean;
21779 -- Set True if reference to end label itself is required
21781 Endl : Node_Id;
21782 -- Gets set to the operator symbol or identifier that references the
21783 -- entity Ent. For the child unit case, this is the identifier from the
21784 -- designator. For other cases, this is simply Endl.
21786 procedure Generate_Parent_Ref (N : Node_Id; E : Entity_Id);
21787 -- N is an identifier node that appears as a parent unit reference in
21788 -- the case where Ent is a child unit. This procedure generates an
21789 -- appropriate cross-reference entry. E is the corresponding entity.
21791 -------------------------
21792 -- Generate_Parent_Ref --
21793 -------------------------
21795 procedure Generate_Parent_Ref (N : Node_Id; E : Entity_Id) is
21796 begin
21797 -- If names do not match, something weird, skip reference
21799 if Chars (E) = Chars (N) then
21801 -- Generate the reference. We do NOT consider this as a reference
21802 -- for unreferenced symbol purposes.
21804 Generate_Reference (E, N, 'r', Set_Ref => False, Force => True);
21806 if Style_Check then
21807 Style.Check_Identifier (N, E);
21808 end if;
21809 end if;
21810 end Generate_Parent_Ref;
21812 -- Start of processing for Process_End_Label
21814 begin
21815 -- If no node, ignore. This happens in some error situations, and
21816 -- also for some internally generated structures where no end label
21817 -- references are required in any case.
21819 if No (N) then
21820 return;
21821 end if;
21823 -- Nothing to do if no End_Label, happens for internally generated
21824 -- constructs where we don't want an end label reference anyway. Also
21825 -- nothing to do if Endl is a string literal, which means there was
21826 -- some prior error (bad operator symbol)
21828 Endl := End_Label (N);
21830 if No (Endl) or else Nkind (Endl) = N_String_Literal then
21831 return;
21832 end if;
21834 -- Reference node is not in extended main source unit
21836 if not In_Extended_Main_Source_Unit (N) then
21838 -- Generally we do not collect references except for the extended
21839 -- main source unit. The one exception is the 'e' entry for a
21840 -- package spec, where it is useful for a client to have the
21841 -- ending information to define scopes.
21843 if Typ /= 'e' then
21844 return;
21846 else
21847 Label_Ref := False;
21849 -- For this case, we can ignore any parent references, but we
21850 -- need the package name itself for the 'e' entry.
21852 if Nkind (Endl) = N_Designator then
21853 Endl := Identifier (Endl);
21854 end if;
21855 end if;
21857 -- Reference is in extended main source unit
21859 else
21860 Label_Ref := True;
21862 -- For designator, generate references for the parent entries
21864 if Nkind (Endl) = N_Designator then
21866 -- Generate references for the prefix if the END line comes from
21867 -- source (otherwise we do not need these references) We climb the
21868 -- scope stack to find the expected entities.
21870 if Comes_From_Source (Endl) then
21871 Nam := Name (Endl);
21872 Scop := Current_Scope;
21873 while Nkind (Nam) = N_Selected_Component loop
21874 Scop := Scope (Scop);
21875 exit when No (Scop);
21876 Generate_Parent_Ref (Selector_Name (Nam), Scop);
21877 Nam := Prefix (Nam);
21878 end loop;
21880 if Present (Scop) then
21881 Generate_Parent_Ref (Nam, Scope (Scop));
21882 end if;
21883 end if;
21885 Endl := Identifier (Endl);
21886 end if;
21887 end if;
21889 -- If the end label is not for the given entity, then either we have
21890 -- some previous error, or this is a generic instantiation for which
21891 -- we do not need to make a cross-reference in this case anyway. In
21892 -- either case we simply ignore the call.
21894 if Chars (Ent) /= Chars (Endl) then
21895 return;
21896 end if;
21898 -- If label was really there, then generate a normal reference and then
21899 -- adjust the location in the end label to point past the name (which
21900 -- should almost always be the semicolon).
21902 Loc := Sloc (Endl);
21904 if Comes_From_Source (Endl) then
21906 -- If a label reference is required, then do the style check and
21907 -- generate an l-type cross-reference entry for the label
21909 if Label_Ref then
21910 if Style_Check then
21911 Style.Check_Identifier (Endl, Ent);
21912 end if;
21914 Generate_Reference (Ent, Endl, 'l', Set_Ref => False);
21915 end if;
21917 -- Set the location to point past the label (normally this will
21918 -- mean the semicolon immediately following the label). This is
21919 -- done for the sake of the 'e' or 't' entry generated below.
21921 Get_Decoded_Name_String (Chars (Endl));
21922 Set_Sloc (Endl, Sloc (Endl) + Source_Ptr (Name_Len));
21924 else
21925 -- In SPARK mode, no missing label is allowed for packages and
21926 -- subprogram bodies. Detect those cases by testing whether
21927 -- Process_End_Label was called for a body (Typ = 't') or a package.
21929 if Restriction_Check_Required (SPARK_05)
21930 and then (Typ = 't' or else Ekind (Ent) = E_Package)
21931 then
21932 Error_Msg_Node_1 := Endl;
21933 Check_SPARK_05_Restriction
21934 ("`END &` required", Endl, Force => True);
21935 end if;
21936 end if;
21938 -- Now generate the e/t reference
21940 Generate_Reference (Ent, Endl, Typ, Set_Ref => False, Force => True);
21942 -- Restore Sloc, in case modified above, since we have an identifier
21943 -- and the normal Sloc should be left set in the tree.
21945 Set_Sloc (Endl, Loc);
21946 end Process_End_Label;
21948 --------------------------------
21949 -- Propagate_Concurrent_Flags --
21950 --------------------------------
21952 procedure Propagate_Concurrent_Flags
21953 (Typ : Entity_Id;
21954 Comp_Typ : Entity_Id)
21956 begin
21957 if Has_Task (Comp_Typ) then
21958 Set_Has_Task (Typ);
21959 end if;
21961 if Has_Protected (Comp_Typ) then
21962 Set_Has_Protected (Typ);
21963 end if;
21965 if Has_Timing_Event (Comp_Typ) then
21966 Set_Has_Timing_Event (Typ);
21967 end if;
21968 end Propagate_Concurrent_Flags;
21970 ------------------------------
21971 -- Propagate_DIC_Attributes --
21972 ------------------------------
21974 procedure Propagate_DIC_Attributes
21975 (Typ : Entity_Id;
21976 From_Typ : Entity_Id)
21978 DIC_Proc : Entity_Id;
21980 begin
21981 if Present (Typ) and then Present (From_Typ) then
21982 pragma Assert (Is_Type (Typ) and then Is_Type (From_Typ));
21984 -- Nothing to do if both the source and the destination denote the
21985 -- same type.
21987 if From_Typ = Typ then
21988 return;
21989 end if;
21991 DIC_Proc := DIC_Procedure (From_Typ);
21993 -- The setting of the attributes is intentionally conservative. This
21994 -- prevents accidental clobbering of enabled attributes.
21996 if Has_Inherited_DIC (From_Typ)
21997 and then not Has_Inherited_DIC (Typ)
21998 then
21999 Set_Has_Inherited_DIC (Typ);
22000 end if;
22002 if Has_Own_DIC (From_Typ) and then not Has_Own_DIC (Typ) then
22003 Set_Has_Own_DIC (Typ);
22004 end if;
22006 if Present (DIC_Proc) and then No (DIC_Procedure (Typ)) then
22007 Set_DIC_Procedure (Typ, DIC_Proc);
22008 end if;
22009 end if;
22010 end Propagate_DIC_Attributes;
22012 ------------------------------------
22013 -- Propagate_Invariant_Attributes --
22014 ------------------------------------
22016 procedure Propagate_Invariant_Attributes
22017 (Typ : Entity_Id;
22018 From_Typ : Entity_Id)
22020 Full_IP : Entity_Id;
22021 Part_IP : Entity_Id;
22023 begin
22024 if Present (Typ) and then Present (From_Typ) then
22025 pragma Assert (Is_Type (Typ) and then Is_Type (From_Typ));
22027 -- Nothing to do if both the source and the destination denote the
22028 -- same type.
22030 if From_Typ = Typ then
22031 return;
22032 end if;
22034 Full_IP := Invariant_Procedure (From_Typ);
22035 Part_IP := Partial_Invariant_Procedure (From_Typ);
22037 -- The setting of the attributes is intentionally conservative. This
22038 -- prevents accidental clobbering of enabled attributes.
22040 if Has_Inheritable_Invariants (From_Typ)
22041 and then not Has_Inheritable_Invariants (Typ)
22042 then
22043 Set_Has_Inheritable_Invariants (Typ, True);
22044 end if;
22046 if Has_Inherited_Invariants (From_Typ)
22047 and then not Has_Inherited_Invariants (Typ)
22048 then
22049 Set_Has_Inherited_Invariants (Typ, True);
22050 end if;
22052 if Has_Own_Invariants (From_Typ)
22053 and then not Has_Own_Invariants (Typ)
22054 then
22055 Set_Has_Own_Invariants (Typ, True);
22056 end if;
22058 if Present (Full_IP) and then No (Invariant_Procedure (Typ)) then
22059 Set_Invariant_Procedure (Typ, Full_IP);
22060 end if;
22062 if Present (Part_IP) and then No (Partial_Invariant_Procedure (Typ))
22063 then
22064 Set_Partial_Invariant_Procedure (Typ, Part_IP);
22065 end if;
22066 end if;
22067 end Propagate_Invariant_Attributes;
22069 ---------------------------------------
22070 -- Record_Possible_Part_Of_Reference --
22071 ---------------------------------------
22073 procedure Record_Possible_Part_Of_Reference
22074 (Var_Id : Entity_Id;
22075 Ref : Node_Id)
22077 Encap : constant Entity_Id := Encapsulating_State (Var_Id);
22078 Refs : Elist_Id;
22080 begin
22081 -- The variable is a constituent of a single protected/task type. Such
22082 -- a variable acts as a component of the type and must appear within a
22083 -- specific region (SPARK RM 9.3). Instead of recording the reference,
22084 -- verify its legality now.
22086 if Present (Encap) and then Is_Single_Concurrent_Object (Encap) then
22087 Check_Part_Of_Reference (Var_Id, Ref);
22089 -- The variable is subject to pragma Part_Of and may eventually become a
22090 -- constituent of a single protected/task type. Record the reference to
22091 -- verify its placement when the contract of the variable is analyzed.
22093 elsif Present (Get_Pragma (Var_Id, Pragma_Part_Of)) then
22094 Refs := Part_Of_References (Var_Id);
22096 if No (Refs) then
22097 Refs := New_Elmt_List;
22098 Set_Part_Of_References (Var_Id, Refs);
22099 end if;
22101 Append_Elmt (Ref, Refs);
22102 end if;
22103 end Record_Possible_Part_Of_Reference;
22105 ----------------
22106 -- Referenced --
22107 ----------------
22109 function Referenced (Id : Entity_Id; Expr : Node_Id) return Boolean is
22110 Seen : Boolean := False;
22112 function Is_Reference (N : Node_Id) return Traverse_Result;
22113 -- Determine whether node N denotes a reference to Id. If this is the
22114 -- case, set global flag Seen to True and stop the traversal.
22116 ------------------
22117 -- Is_Reference --
22118 ------------------
22120 function Is_Reference (N : Node_Id) return Traverse_Result is
22121 begin
22122 if Is_Entity_Name (N)
22123 and then Present (Entity (N))
22124 and then Entity (N) = Id
22125 then
22126 Seen := True;
22127 return Abandon;
22128 else
22129 return OK;
22130 end if;
22131 end Is_Reference;
22133 procedure Inspect_Expression is new Traverse_Proc (Is_Reference);
22135 -- Start of processing for Referenced
22137 begin
22138 Inspect_Expression (Expr);
22139 return Seen;
22140 end Referenced;
22142 ------------------------------------
22143 -- References_Generic_Formal_Type --
22144 ------------------------------------
22146 function References_Generic_Formal_Type (N : Node_Id) return Boolean is
22148 function Process (N : Node_Id) return Traverse_Result;
22149 -- Process one node in search for generic formal type
22151 -------------
22152 -- Process --
22153 -------------
22155 function Process (N : Node_Id) return Traverse_Result is
22156 begin
22157 if Nkind (N) in N_Has_Entity then
22158 declare
22159 E : constant Entity_Id := Entity (N);
22160 begin
22161 if Present (E) then
22162 if Is_Generic_Type (E) then
22163 return Abandon;
22164 elsif Present (Etype (E))
22165 and then Is_Generic_Type (Etype (E))
22166 then
22167 return Abandon;
22168 end if;
22169 end if;
22170 end;
22171 end if;
22173 return Atree.OK;
22174 end Process;
22176 function Traverse is new Traverse_Func (Process);
22177 -- Traverse tree to look for generic type
22179 begin
22180 if Inside_A_Generic then
22181 return Traverse (N) = Abandon;
22182 else
22183 return False;
22184 end if;
22185 end References_Generic_Formal_Type;
22187 -------------------
22188 -- Remove_Entity --
22189 -------------------
22191 procedure Remove_Entity (Id : Entity_Id) is
22192 Scop : constant Entity_Id := Scope (Id);
22193 Prev_Id : Entity_Id;
22195 begin
22196 -- Remove the entity from the homonym chain. When the entity is the
22197 -- head of the chain, associate the entry in the name table with its
22198 -- homonym effectively making it the new head of the chain.
22200 if Current_Entity (Id) = Id then
22201 Set_Name_Entity_Id (Chars (Id), Homonym (Id));
22203 -- Otherwise link the previous and next homonyms
22205 else
22206 Prev_Id := Current_Entity (Id);
22207 while Present (Prev_Id) and then Homonym (Prev_Id) /= Id loop
22208 Prev_Id := Homonym (Prev_Id);
22209 end loop;
22211 Set_Homonym (Prev_Id, Homonym (Id));
22212 end if;
22214 -- Remove the entity from the scope entity chain. When the entity is
22215 -- the head of the chain, set the next entity as the new head of the
22216 -- chain.
22218 if First_Entity (Scop) = Id then
22219 Prev_Id := Empty;
22220 Set_First_Entity (Scop, Next_Entity (Id));
22222 -- Otherwise the entity is either in the middle of the chain or it acts
22223 -- as its tail. Traverse and link the previous and next entities.
22225 else
22226 Prev_Id := First_Entity (Scop);
22227 while Present (Prev_Id) and then Next_Entity (Prev_Id) /= Id loop
22228 Next_Entity (Prev_Id);
22229 end loop;
22231 Set_Next_Entity (Prev_Id, Next_Entity (Id));
22232 end if;
22234 -- Handle the case where the entity acts as the tail of the scope entity
22235 -- chain.
22237 if Last_Entity (Scop) = Id then
22238 Set_Last_Entity (Scop, Prev_Id);
22239 end if;
22240 end Remove_Entity;
22242 --------------------
22243 -- Remove_Homonym --
22244 --------------------
22246 procedure Remove_Homonym (E : Entity_Id) is
22247 Prev : Entity_Id := Empty;
22248 H : Entity_Id;
22250 begin
22251 if E = Current_Entity (E) then
22252 if Present (Homonym (E)) then
22253 Set_Current_Entity (Homonym (E));
22254 else
22255 Set_Name_Entity_Id (Chars (E), Empty);
22256 end if;
22258 else
22259 H := Current_Entity (E);
22260 while Present (H) and then H /= E loop
22261 Prev := H;
22262 H := Homonym (H);
22263 end loop;
22265 -- If E is not on the homonym chain, nothing to do
22267 if Present (H) then
22268 Set_Homonym (Prev, Homonym (E));
22269 end if;
22270 end if;
22271 end Remove_Homonym;
22273 ------------------------------
22274 -- Remove_Overloaded_Entity --
22275 ------------------------------
22277 procedure Remove_Overloaded_Entity (Id : Entity_Id) is
22278 procedure Remove_Primitive_Of (Typ : Entity_Id);
22279 -- Remove primitive subprogram Id from the list of primitives that
22280 -- belong to type Typ.
22282 -------------------------
22283 -- Remove_Primitive_Of --
22284 -------------------------
22286 procedure Remove_Primitive_Of (Typ : Entity_Id) is
22287 Prims : Elist_Id;
22289 begin
22290 if Is_Tagged_Type (Typ) then
22291 Prims := Direct_Primitive_Operations (Typ);
22293 if Present (Prims) then
22294 Remove (Prims, Id);
22295 end if;
22296 end if;
22297 end Remove_Primitive_Of;
22299 -- Local variables
22301 Formal : Entity_Id;
22303 -- Start of processing for Remove_Overloaded_Entity
22305 begin
22306 -- Remove the entity from both the homonym and scope chains
22308 Remove_Entity (Id);
22310 -- The entity denotes a primitive subprogram. Remove it from the list of
22311 -- primitives of the associated controlling type.
22313 if Ekind_In (Id, E_Function, E_Procedure) and then Is_Primitive (Id) then
22314 Formal := First_Formal (Id);
22315 while Present (Formal) loop
22316 if Is_Controlling_Formal (Formal) then
22317 Remove_Primitive_Of (Etype (Formal));
22318 exit;
22319 end if;
22321 Next_Formal (Formal);
22322 end loop;
22324 if Ekind (Id) = E_Function and then Has_Controlling_Result (Id) then
22325 Remove_Primitive_Of (Etype (Id));
22326 end if;
22327 end if;
22328 end Remove_Overloaded_Entity;
22330 ---------------------
22331 -- Rep_To_Pos_Flag --
22332 ---------------------
22334 function Rep_To_Pos_Flag (E : Entity_Id; Loc : Source_Ptr) return Node_Id is
22335 begin
22336 return New_Occurrence_Of
22337 (Boolean_Literals (not Range_Checks_Suppressed (E)), Loc);
22338 end Rep_To_Pos_Flag;
22340 --------------------
22341 -- Require_Entity --
22342 --------------------
22344 procedure Require_Entity (N : Node_Id) is
22345 begin
22346 if Is_Entity_Name (N) and then No (Entity (N)) then
22347 if Total_Errors_Detected /= 0 then
22348 Set_Entity (N, Any_Id);
22349 else
22350 raise Program_Error;
22351 end if;
22352 end if;
22353 end Require_Entity;
22355 ------------------------------
22356 -- Requires_Transient_Scope --
22357 ------------------------------
22359 -- A transient scope is required when variable-sized temporaries are
22360 -- allocated on the secondary stack, or when finalization actions must be
22361 -- generated before the next instruction.
22363 function Requires_Transient_Scope (Id : Entity_Id) return Boolean is
22364 Old_Result : constant Boolean := Old_Requires_Transient_Scope (Id);
22366 begin
22367 if Debug_Flag_QQ then
22368 return Old_Result;
22369 end if;
22371 declare
22372 New_Result : constant Boolean := New_Requires_Transient_Scope (Id);
22374 begin
22375 -- Assert that we're not putting things on the secondary stack if we
22376 -- didn't before; we are trying to AVOID secondary stack when
22377 -- possible.
22379 if not Old_Result then
22380 pragma Assert (not New_Result);
22381 null;
22382 end if;
22384 if New_Result /= Old_Result then
22385 Results_Differ (Id, Old_Result, New_Result);
22386 end if;
22388 return New_Result;
22389 end;
22390 end Requires_Transient_Scope;
22392 --------------------
22393 -- Results_Differ --
22394 --------------------
22396 procedure Results_Differ
22397 (Id : Entity_Id;
22398 Old_Val : Boolean;
22399 New_Val : Boolean)
22401 begin
22402 if False then -- False to disable; True for debugging
22403 Treepr.Print_Tree_Node (Id);
22405 if Old_Val = New_Val then
22406 raise Program_Error;
22407 end if;
22408 end if;
22409 end Results_Differ;
22411 --------------------------
22412 -- Reset_Analyzed_Flags --
22413 --------------------------
22415 procedure Reset_Analyzed_Flags (N : Node_Id) is
22416 function Clear_Analyzed (N : Node_Id) return Traverse_Result;
22417 -- Function used to reset Analyzed flags in tree. Note that we do
22418 -- not reset Analyzed flags in entities, since there is no need to
22419 -- reanalyze entities, and indeed, it is wrong to do so, since it
22420 -- can result in generating auxiliary stuff more than once.
22422 --------------------
22423 -- Clear_Analyzed --
22424 --------------------
22426 function Clear_Analyzed (N : Node_Id) return Traverse_Result is
22427 begin
22428 if Nkind (N) not in N_Entity then
22429 Set_Analyzed (N, False);
22430 end if;
22432 return OK;
22433 end Clear_Analyzed;
22435 procedure Reset_Analyzed is new Traverse_Proc (Clear_Analyzed);
22437 -- Start of processing for Reset_Analyzed_Flags
22439 begin
22440 Reset_Analyzed (N);
22441 end Reset_Analyzed_Flags;
22443 ------------------------
22444 -- Restore_SPARK_Mode --
22445 ------------------------
22447 procedure Restore_SPARK_Mode
22448 (Mode : SPARK_Mode_Type;
22449 Prag : Node_Id)
22451 begin
22452 SPARK_Mode := Mode;
22453 SPARK_Mode_Pragma := Prag;
22454 end Restore_SPARK_Mode;
22456 --------------------------------
22457 -- Returns_Unconstrained_Type --
22458 --------------------------------
22460 function Returns_Unconstrained_Type (Subp : Entity_Id) return Boolean is
22461 begin
22462 return Ekind (Subp) = E_Function
22463 and then not Is_Scalar_Type (Etype (Subp))
22464 and then not Is_Access_Type (Etype (Subp))
22465 and then not Is_Constrained (Etype (Subp));
22466 end Returns_Unconstrained_Type;
22468 ----------------------------
22469 -- Root_Type_Of_Full_View --
22470 ----------------------------
22472 function Root_Type_Of_Full_View (T : Entity_Id) return Entity_Id is
22473 Rtyp : constant Entity_Id := Root_Type (T);
22475 begin
22476 -- The root type of the full view may itself be a private type. Keep
22477 -- looking for the ultimate derivation parent.
22479 if Is_Private_Type (Rtyp) and then Present (Full_View (Rtyp)) then
22480 return Root_Type_Of_Full_View (Full_View (Rtyp));
22481 else
22482 return Rtyp;
22483 end if;
22484 end Root_Type_Of_Full_View;
22486 ---------------------------
22487 -- Safe_To_Capture_Value --
22488 ---------------------------
22490 function Safe_To_Capture_Value
22491 (N : Node_Id;
22492 Ent : Entity_Id;
22493 Cond : Boolean := False) return Boolean
22495 begin
22496 -- The only entities for which we track constant values are variables
22497 -- which are not renamings, constants, out parameters, and in out
22498 -- parameters, so check if we have this case.
22500 -- Note: it may seem odd to track constant values for constants, but in
22501 -- fact this routine is used for other purposes than simply capturing
22502 -- the value. In particular, the setting of Known[_Non]_Null.
22504 if (Ekind (Ent) = E_Variable and then No (Renamed_Object (Ent)))
22505 or else
22506 Ekind_In (Ent, E_Constant, E_Out_Parameter, E_In_Out_Parameter)
22507 then
22508 null;
22510 -- For conditionals, we also allow loop parameters and all formals,
22511 -- including in parameters.
22513 elsif Cond and then Ekind_In (Ent, E_Loop_Parameter, E_In_Parameter) then
22514 null;
22516 -- For all other cases, not just unsafe, but impossible to capture
22517 -- Current_Value, since the above are the only entities which have
22518 -- Current_Value fields.
22520 else
22521 return False;
22522 end if;
22524 -- Skip if volatile or aliased, since funny things might be going on in
22525 -- these cases which we cannot necessarily track. Also skip any variable
22526 -- for which an address clause is given, or whose address is taken. Also
22527 -- never capture value of library level variables (an attempt to do so
22528 -- can occur in the case of package elaboration code).
22530 if Treat_As_Volatile (Ent)
22531 or else Is_Aliased (Ent)
22532 or else Present (Address_Clause (Ent))
22533 or else Address_Taken (Ent)
22534 or else (Is_Library_Level_Entity (Ent)
22535 and then Ekind (Ent) = E_Variable)
22536 then
22537 return False;
22538 end if;
22540 -- OK, all above conditions are met. We also require that the scope of
22541 -- the reference be the same as the scope of the entity, not counting
22542 -- packages and blocks and loops.
22544 declare
22545 E_Scope : constant Entity_Id := Scope (Ent);
22546 R_Scope : Entity_Id;
22548 begin
22549 R_Scope := Current_Scope;
22550 while R_Scope /= Standard_Standard loop
22551 exit when R_Scope = E_Scope;
22553 if not Ekind_In (R_Scope, E_Package, E_Block, E_Loop) then
22554 return False;
22555 else
22556 R_Scope := Scope (R_Scope);
22557 end if;
22558 end loop;
22559 end;
22561 -- We also require that the reference does not appear in a context
22562 -- where it is not sure to be executed (i.e. a conditional context
22563 -- or an exception handler). We skip this if Cond is True, since the
22564 -- capturing of values from conditional tests handles this ok.
22566 if Cond then
22567 return True;
22568 end if;
22570 declare
22571 Desc : Node_Id;
22572 P : Node_Id;
22574 begin
22575 Desc := N;
22577 -- Seems dubious that case expressions are not handled here ???
22579 P := Parent (N);
22580 while Present (P) loop
22581 if Nkind (P) = N_If_Statement
22582 or else Nkind (P) = N_Case_Statement
22583 or else (Nkind (P) in N_Short_Circuit
22584 and then Desc = Right_Opnd (P))
22585 or else (Nkind (P) = N_If_Expression
22586 and then Desc /= First (Expressions (P)))
22587 or else Nkind (P) = N_Exception_Handler
22588 or else Nkind (P) = N_Selective_Accept
22589 or else Nkind (P) = N_Conditional_Entry_Call
22590 or else Nkind (P) = N_Timed_Entry_Call
22591 or else Nkind (P) = N_Asynchronous_Select
22592 then
22593 return False;
22595 else
22596 Desc := P;
22597 P := Parent (P);
22599 -- A special Ada 2012 case: the original node may be part
22600 -- of the else_actions of a conditional expression, in which
22601 -- case it might not have been expanded yet, and appears in
22602 -- a non-syntactic list of actions. In that case it is clearly
22603 -- not safe to save a value.
22605 if No (P)
22606 and then Is_List_Member (Desc)
22607 and then No (Parent (List_Containing (Desc)))
22608 then
22609 return False;
22610 end if;
22611 end if;
22612 end loop;
22613 end;
22615 -- OK, looks safe to set value
22617 return True;
22618 end Safe_To_Capture_Value;
22620 ---------------
22621 -- Same_Name --
22622 ---------------
22624 function Same_Name (N1, N2 : Node_Id) return Boolean is
22625 K1 : constant Node_Kind := Nkind (N1);
22626 K2 : constant Node_Kind := Nkind (N2);
22628 begin
22629 if (K1 = N_Identifier or else K1 = N_Defining_Identifier)
22630 and then (K2 = N_Identifier or else K2 = N_Defining_Identifier)
22631 then
22632 return Chars (N1) = Chars (N2);
22634 elsif (K1 = N_Selected_Component or else K1 = N_Expanded_Name)
22635 and then (K2 = N_Selected_Component or else K2 = N_Expanded_Name)
22636 then
22637 return Same_Name (Selector_Name (N1), Selector_Name (N2))
22638 and then Same_Name (Prefix (N1), Prefix (N2));
22640 else
22641 return False;
22642 end if;
22643 end Same_Name;
22645 -----------------
22646 -- Same_Object --
22647 -----------------
22649 function Same_Object (Node1, Node2 : Node_Id) return Boolean is
22650 N1 : constant Node_Id := Original_Node (Node1);
22651 N2 : constant Node_Id := Original_Node (Node2);
22652 -- We do the tests on original nodes, since we are most interested
22653 -- in the original source, not any expansion that got in the way.
22655 K1 : constant Node_Kind := Nkind (N1);
22656 K2 : constant Node_Kind := Nkind (N2);
22658 begin
22659 -- First case, both are entities with same entity
22661 if K1 in N_Has_Entity and then K2 in N_Has_Entity then
22662 declare
22663 EN1 : constant Entity_Id := Entity (N1);
22664 EN2 : constant Entity_Id := Entity (N2);
22665 begin
22666 if Present (EN1) and then Present (EN2)
22667 and then (Ekind_In (EN1, E_Variable, E_Constant)
22668 or else Is_Formal (EN1))
22669 and then EN1 = EN2
22670 then
22671 return True;
22672 end if;
22673 end;
22674 end if;
22676 -- Second case, selected component with same selector, same record
22678 if K1 = N_Selected_Component
22679 and then K2 = N_Selected_Component
22680 and then Chars (Selector_Name (N1)) = Chars (Selector_Name (N2))
22681 then
22682 return Same_Object (Prefix (N1), Prefix (N2));
22684 -- Third case, indexed component with same subscripts, same array
22686 elsif K1 = N_Indexed_Component
22687 and then K2 = N_Indexed_Component
22688 and then Same_Object (Prefix (N1), Prefix (N2))
22689 then
22690 declare
22691 E1, E2 : Node_Id;
22692 begin
22693 E1 := First (Expressions (N1));
22694 E2 := First (Expressions (N2));
22695 while Present (E1) loop
22696 if not Same_Value (E1, E2) then
22697 return False;
22698 else
22699 Next (E1);
22700 Next (E2);
22701 end if;
22702 end loop;
22704 return True;
22705 end;
22707 -- Fourth case, slice of same array with same bounds
22709 elsif K1 = N_Slice
22710 and then K2 = N_Slice
22711 and then Nkind (Discrete_Range (N1)) = N_Range
22712 and then Nkind (Discrete_Range (N2)) = N_Range
22713 and then Same_Value (Low_Bound (Discrete_Range (N1)),
22714 Low_Bound (Discrete_Range (N2)))
22715 and then Same_Value (High_Bound (Discrete_Range (N1)),
22716 High_Bound (Discrete_Range (N2)))
22717 then
22718 return Same_Name (Prefix (N1), Prefix (N2));
22720 -- All other cases, not clearly the same object
22722 else
22723 return False;
22724 end if;
22725 end Same_Object;
22727 ---------------
22728 -- Same_Type --
22729 ---------------
22731 function Same_Type (T1, T2 : Entity_Id) return Boolean is
22732 begin
22733 if T1 = T2 then
22734 return True;
22736 elsif not Is_Constrained (T1)
22737 and then not Is_Constrained (T2)
22738 and then Base_Type (T1) = Base_Type (T2)
22739 then
22740 return True;
22742 -- For now don't bother with case of identical constraints, to be
22743 -- fiddled with later on perhaps (this is only used for optimization
22744 -- purposes, so it is not critical to do a best possible job)
22746 else
22747 return False;
22748 end if;
22749 end Same_Type;
22751 ----------------
22752 -- Same_Value --
22753 ----------------
22755 function Same_Value (Node1, Node2 : Node_Id) return Boolean is
22756 begin
22757 if Compile_Time_Known_Value (Node1)
22758 and then Compile_Time_Known_Value (Node2)
22759 then
22760 -- Handle properly compile-time expressions that are not
22761 -- scalar.
22763 if Is_String_Type (Etype (Node1)) then
22764 return Expr_Value_S (Node1) = Expr_Value_S (Node2);
22766 else
22767 return Expr_Value (Node1) = Expr_Value (Node2);
22768 end if;
22770 elsif Same_Object (Node1, Node2) then
22771 return True;
22772 else
22773 return False;
22774 end if;
22775 end Same_Value;
22777 --------------------
22778 -- Set_SPARK_Mode --
22779 --------------------
22781 procedure Set_SPARK_Mode (Context : Entity_Id) is
22782 begin
22783 -- Do not consider illegal or partially decorated constructs
22785 if Ekind (Context) = E_Void or else Error_Posted (Context) then
22786 null;
22788 elsif Present (SPARK_Pragma (Context)) then
22789 Install_SPARK_Mode
22790 (Mode => Get_SPARK_Mode_From_Annotation (SPARK_Pragma (Context)),
22791 Prag => SPARK_Pragma (Context));
22792 end if;
22793 end Set_SPARK_Mode;
22795 -------------------------
22796 -- Scalar_Part_Present --
22797 -------------------------
22799 function Scalar_Part_Present (T : Entity_Id) return Boolean is
22800 C : Entity_Id;
22802 begin
22803 if Is_Scalar_Type (T) then
22804 return True;
22806 elsif Is_Array_Type (T) then
22807 return Scalar_Part_Present (Component_Type (T));
22809 elsif Is_Record_Type (T) or else Has_Discriminants (T) then
22810 C := First_Component_Or_Discriminant (T);
22811 while Present (C) loop
22812 if Scalar_Part_Present (Etype (C)) then
22813 return True;
22814 else
22815 Next_Component_Or_Discriminant (C);
22816 end if;
22817 end loop;
22818 end if;
22820 return False;
22821 end Scalar_Part_Present;
22823 ------------------------
22824 -- Scope_Is_Transient --
22825 ------------------------
22827 function Scope_Is_Transient return Boolean is
22828 begin
22829 return Scope_Stack.Table (Scope_Stack.Last).Is_Transient;
22830 end Scope_Is_Transient;
22832 ------------------
22833 -- Scope_Within --
22834 ------------------
22836 function Scope_Within
22837 (Inner : Entity_Id;
22838 Outer : Entity_Id) return Boolean
22840 Curr : Entity_Id;
22842 begin
22843 Curr := Inner;
22844 while Present (Curr) and then Curr /= Standard_Standard loop
22845 Curr := Scope (Curr);
22847 if Curr = Outer then
22848 return True;
22849 end if;
22850 end loop;
22852 return False;
22853 end Scope_Within;
22855 --------------------------
22856 -- Scope_Within_Or_Same --
22857 --------------------------
22859 function Scope_Within_Or_Same
22860 (Inner : Entity_Id;
22861 Outer : Entity_Id) return Boolean
22863 Curr : Entity_Id;
22865 begin
22866 Curr := Inner;
22867 while Present (Curr) and then Curr /= Standard_Standard loop
22868 if Curr = Outer then
22869 return True;
22870 end if;
22872 Curr := Scope (Curr);
22873 end loop;
22875 return False;
22876 end Scope_Within_Or_Same;
22878 --------------------
22879 -- Set_Convention --
22880 --------------------
22882 procedure Set_Convention (E : Entity_Id; Val : Snames.Convention_Id) is
22883 begin
22884 Basic_Set_Convention (E, Val);
22886 if Is_Type (E)
22887 and then Is_Access_Subprogram_Type (Base_Type (E))
22888 and then Has_Foreign_Convention (E)
22889 then
22890 Set_Can_Use_Internal_Rep (E, False);
22891 end if;
22893 -- If E is an object, including a component, and the type of E is an
22894 -- anonymous access type with no convention set, then also set the
22895 -- convention of the anonymous access type. We do not do this for
22896 -- anonymous protected types, since protected types always have the
22897 -- default convention.
22899 if Present (Etype (E))
22900 and then (Is_Object (E)
22902 -- Allow E_Void (happens for pragma Convention appearing
22903 -- in the middle of a record applying to a component)
22905 or else Ekind (E) = E_Void)
22906 then
22907 declare
22908 Typ : constant Entity_Id := Etype (E);
22910 begin
22911 if Ekind_In (Typ, E_Anonymous_Access_Type,
22912 E_Anonymous_Access_Subprogram_Type)
22913 and then not Has_Convention_Pragma (Typ)
22914 then
22915 Basic_Set_Convention (Typ, Val);
22916 Set_Has_Convention_Pragma (Typ);
22918 -- And for the access subprogram type, deal similarly with the
22919 -- designated E_Subprogram_Type, which is always internal.
22921 if Ekind (Typ) = E_Anonymous_Access_Subprogram_Type then
22922 declare
22923 Dtype : constant Entity_Id := Designated_Type (Typ);
22924 begin
22925 if Ekind (Dtype) = E_Subprogram_Type
22926 and then not Has_Convention_Pragma (Dtype)
22927 then
22928 Basic_Set_Convention (Dtype, Val);
22929 Set_Has_Convention_Pragma (Dtype);
22930 end if;
22931 end;
22932 end if;
22933 end if;
22934 end;
22935 end if;
22936 end Set_Convention;
22938 ------------------------
22939 -- Set_Current_Entity --
22940 ------------------------
22942 -- The given entity is to be set as the currently visible definition of its
22943 -- associated name (i.e. the Node_Id associated with its name). All we have
22944 -- to do is to get the name from the identifier, and then set the
22945 -- associated Node_Id to point to the given entity.
22947 procedure Set_Current_Entity (E : Entity_Id) is
22948 begin
22949 Set_Name_Entity_Id (Chars (E), E);
22950 end Set_Current_Entity;
22952 ---------------------------
22953 -- Set_Debug_Info_Needed --
22954 ---------------------------
22956 procedure Set_Debug_Info_Needed (T : Entity_Id) is
22958 procedure Set_Debug_Info_Needed_If_Not_Set (E : Entity_Id);
22959 pragma Inline (Set_Debug_Info_Needed_If_Not_Set);
22960 -- Used to set debug info in a related node if not set already
22962 --------------------------------------
22963 -- Set_Debug_Info_Needed_If_Not_Set --
22964 --------------------------------------
22966 procedure Set_Debug_Info_Needed_If_Not_Set (E : Entity_Id) is
22967 begin
22968 if Present (E) and then not Needs_Debug_Info (E) then
22969 Set_Debug_Info_Needed (E);
22971 -- For a private type, indicate that the full view also needs
22972 -- debug information.
22974 if Is_Type (E)
22975 and then Is_Private_Type (E)
22976 and then Present (Full_View (E))
22977 then
22978 Set_Debug_Info_Needed (Full_View (E));
22979 end if;
22980 end if;
22981 end Set_Debug_Info_Needed_If_Not_Set;
22983 -- Start of processing for Set_Debug_Info_Needed
22985 begin
22986 -- Nothing to do if argument is Empty or has Debug_Info_Off set, which
22987 -- indicates that Debug_Info_Needed is never required for the entity.
22988 -- Nothing to do if entity comes from a predefined file. Library files
22989 -- are compiled without debug information, but inlined bodies of these
22990 -- routines may appear in user code, and debug information on them ends
22991 -- up complicating debugging the user code.
22993 if No (T)
22994 or else Debug_Info_Off (T)
22995 then
22996 return;
22998 elsif In_Inlined_Body and then In_Predefined_Unit (T) then
22999 Set_Needs_Debug_Info (T, False);
23000 end if;
23002 -- Set flag in entity itself. Note that we will go through the following
23003 -- circuitry even if the flag is already set on T. That's intentional,
23004 -- it makes sure that the flag will be set in subsidiary entities.
23006 Set_Needs_Debug_Info (T);
23008 -- Set flag on subsidiary entities if not set already
23010 if Is_Object (T) then
23011 Set_Debug_Info_Needed_If_Not_Set (Etype (T));
23013 elsif Is_Type (T) then
23014 Set_Debug_Info_Needed_If_Not_Set (Etype (T));
23016 if Is_Record_Type (T) then
23017 declare
23018 Ent : Entity_Id := First_Entity (T);
23019 begin
23020 while Present (Ent) loop
23021 Set_Debug_Info_Needed_If_Not_Set (Ent);
23022 Next_Entity (Ent);
23023 end loop;
23024 end;
23026 -- For a class wide subtype, we also need debug information
23027 -- for the equivalent type.
23029 if Ekind (T) = E_Class_Wide_Subtype then
23030 Set_Debug_Info_Needed_If_Not_Set (Equivalent_Type (T));
23031 end if;
23033 elsif Is_Array_Type (T) then
23034 Set_Debug_Info_Needed_If_Not_Set (Component_Type (T));
23036 declare
23037 Indx : Node_Id := First_Index (T);
23038 begin
23039 while Present (Indx) loop
23040 Set_Debug_Info_Needed_If_Not_Set (Etype (Indx));
23041 Indx := Next_Index (Indx);
23042 end loop;
23043 end;
23045 -- For a packed array type, we also need debug information for
23046 -- the type used to represent the packed array. Conversely, we
23047 -- also need it for the former if we need it for the latter.
23049 if Is_Packed (T) then
23050 Set_Debug_Info_Needed_If_Not_Set (Packed_Array_Impl_Type (T));
23051 end if;
23053 if Is_Packed_Array_Impl_Type (T) then
23054 Set_Debug_Info_Needed_If_Not_Set (Original_Array_Type (T));
23055 end if;
23057 elsif Is_Access_Type (T) then
23058 Set_Debug_Info_Needed_If_Not_Set (Directly_Designated_Type (T));
23060 elsif Is_Private_Type (T) then
23061 declare
23062 FV : constant Entity_Id := Full_View (T);
23064 begin
23065 Set_Debug_Info_Needed_If_Not_Set (FV);
23067 -- If the full view is itself a derived private type, we need
23068 -- debug information on its underlying type.
23070 if Present (FV)
23071 and then Is_Private_Type (FV)
23072 and then Present (Underlying_Full_View (FV))
23073 then
23074 Set_Needs_Debug_Info (Underlying_Full_View (FV));
23075 end if;
23076 end;
23078 elsif Is_Protected_Type (T) then
23079 Set_Debug_Info_Needed_If_Not_Set (Corresponding_Record_Type (T));
23081 elsif Is_Scalar_Type (T) then
23083 -- If the subrange bounds are materialized by dedicated constant
23084 -- objects, also include them in the debug info to make sure the
23085 -- debugger can properly use them.
23087 if Present (Scalar_Range (T))
23088 and then Nkind (Scalar_Range (T)) = N_Range
23089 then
23090 declare
23091 Low_Bnd : constant Node_Id := Type_Low_Bound (T);
23092 High_Bnd : constant Node_Id := Type_High_Bound (T);
23094 begin
23095 if Is_Entity_Name (Low_Bnd) then
23096 Set_Debug_Info_Needed_If_Not_Set (Entity (Low_Bnd));
23097 end if;
23099 if Is_Entity_Name (High_Bnd) then
23100 Set_Debug_Info_Needed_If_Not_Set (Entity (High_Bnd));
23101 end if;
23102 end;
23103 end if;
23104 end if;
23105 end if;
23106 end Set_Debug_Info_Needed;
23108 ----------------------------
23109 -- Set_Entity_With_Checks --
23110 ----------------------------
23112 procedure Set_Entity_With_Checks (N : Node_Id; Val : Entity_Id) is
23113 Val_Actual : Entity_Id;
23114 Nod : Node_Id;
23115 Post_Node : Node_Id;
23117 begin
23118 -- Unconditionally set the entity
23120 Set_Entity (N, Val);
23122 -- The node to post on is the selector in the case of an expanded name,
23123 -- and otherwise the node itself.
23125 if Nkind (N) = N_Expanded_Name then
23126 Post_Node := Selector_Name (N);
23127 else
23128 Post_Node := N;
23129 end if;
23131 -- Check for violation of No_Fixed_IO
23133 if Restriction_Check_Required (No_Fixed_IO)
23134 and then
23135 ((RTU_Loaded (Ada_Text_IO)
23136 and then (Is_RTE (Val, RE_Decimal_IO)
23137 or else
23138 Is_RTE (Val, RE_Fixed_IO)))
23140 or else
23141 (RTU_Loaded (Ada_Wide_Text_IO)
23142 and then (Is_RTE (Val, RO_WT_Decimal_IO)
23143 or else
23144 Is_RTE (Val, RO_WT_Fixed_IO)))
23146 or else
23147 (RTU_Loaded (Ada_Wide_Wide_Text_IO)
23148 and then (Is_RTE (Val, RO_WW_Decimal_IO)
23149 or else
23150 Is_RTE (Val, RO_WW_Fixed_IO))))
23152 -- A special extra check, don't complain about a reference from within
23153 -- the Ada.Interrupts package itself!
23155 and then not In_Same_Extended_Unit (N, Val)
23156 then
23157 Check_Restriction (No_Fixed_IO, Post_Node);
23158 end if;
23160 -- Remaining checks are only done on source nodes. Note that we test
23161 -- for violation of No_Fixed_IO even on non-source nodes, because the
23162 -- cases for checking violations of this restriction are instantiations
23163 -- where the reference in the instance has Comes_From_Source False.
23165 if not Comes_From_Source (N) then
23166 return;
23167 end if;
23169 -- Check for violation of No_Abort_Statements, which is triggered by
23170 -- call to Ada.Task_Identification.Abort_Task.
23172 if Restriction_Check_Required (No_Abort_Statements)
23173 and then (Is_RTE (Val, RE_Abort_Task))
23175 -- A special extra check, don't complain about a reference from within
23176 -- the Ada.Task_Identification package itself!
23178 and then not In_Same_Extended_Unit (N, Val)
23179 then
23180 Check_Restriction (No_Abort_Statements, Post_Node);
23181 end if;
23183 if Val = Standard_Long_Long_Integer then
23184 Check_Restriction (No_Long_Long_Integers, Post_Node);
23185 end if;
23187 -- Check for violation of No_Dynamic_Attachment
23189 if Restriction_Check_Required (No_Dynamic_Attachment)
23190 and then RTU_Loaded (Ada_Interrupts)
23191 and then (Is_RTE (Val, RE_Is_Reserved) or else
23192 Is_RTE (Val, RE_Is_Attached) or else
23193 Is_RTE (Val, RE_Current_Handler) or else
23194 Is_RTE (Val, RE_Attach_Handler) or else
23195 Is_RTE (Val, RE_Exchange_Handler) or else
23196 Is_RTE (Val, RE_Detach_Handler) or else
23197 Is_RTE (Val, RE_Reference))
23199 -- A special extra check, don't complain about a reference from within
23200 -- the Ada.Interrupts package itself!
23202 and then not In_Same_Extended_Unit (N, Val)
23203 then
23204 Check_Restriction (No_Dynamic_Attachment, Post_Node);
23205 end if;
23207 -- Check for No_Implementation_Identifiers
23209 if Restriction_Check_Required (No_Implementation_Identifiers) then
23211 -- We have an implementation defined entity if it is marked as
23212 -- implementation defined, or is defined in a package marked as
23213 -- implementation defined. However, library packages themselves
23214 -- are excluded (we don't want to flag Interfaces itself, just
23215 -- the entities within it).
23217 if (Is_Implementation_Defined (Val)
23218 or else
23219 (Present (Scope (Val))
23220 and then Is_Implementation_Defined (Scope (Val))))
23221 and then not (Ekind_In (Val, E_Package, E_Generic_Package)
23222 and then Is_Library_Level_Entity (Val))
23223 then
23224 Check_Restriction (No_Implementation_Identifiers, Post_Node);
23225 end if;
23226 end if;
23228 -- Do the style check
23230 if Style_Check
23231 and then not Suppress_Style_Checks (Val)
23232 and then not In_Instance
23233 then
23234 if Nkind (N) = N_Identifier then
23235 Nod := N;
23236 elsif Nkind (N) = N_Expanded_Name then
23237 Nod := Selector_Name (N);
23238 else
23239 return;
23240 end if;
23242 -- A special situation arises for derived operations, where we want
23243 -- to do the check against the parent (since the Sloc of the derived
23244 -- operation points to the derived type declaration itself).
23246 Val_Actual := Val;
23247 while not Comes_From_Source (Val_Actual)
23248 and then Nkind (Val_Actual) in N_Entity
23249 and then (Ekind (Val_Actual) = E_Enumeration_Literal
23250 or else Is_Subprogram_Or_Generic_Subprogram (Val_Actual))
23251 and then Present (Alias (Val_Actual))
23252 loop
23253 Val_Actual := Alias (Val_Actual);
23254 end loop;
23256 -- Renaming declarations for generic actuals do not come from source,
23257 -- and have a different name from that of the entity they rename, so
23258 -- there is no style check to perform here.
23260 if Chars (Nod) = Chars (Val_Actual) then
23261 Style.Check_Identifier (Nod, Val_Actual);
23262 end if;
23263 end if;
23265 Set_Entity (N, Val);
23266 end Set_Entity_With_Checks;
23268 ------------------------
23269 -- Set_Name_Entity_Id --
23270 ------------------------
23272 procedure Set_Name_Entity_Id (Id : Name_Id; Val : Entity_Id) is
23273 begin
23274 Set_Name_Table_Int (Id, Int (Val));
23275 end Set_Name_Entity_Id;
23277 ---------------------
23278 -- Set_Next_Actual --
23279 ---------------------
23281 procedure Set_Next_Actual (Ass1_Id : Node_Id; Ass2_Id : Node_Id) is
23282 begin
23283 if Nkind (Parent (Ass1_Id)) = N_Parameter_Association then
23284 Set_First_Named_Actual (Parent (Ass1_Id), Ass2_Id);
23285 end if;
23286 end Set_Next_Actual;
23288 ----------------------------------
23289 -- Set_Optimize_Alignment_Flags --
23290 ----------------------------------
23292 procedure Set_Optimize_Alignment_Flags (E : Entity_Id) is
23293 begin
23294 if Optimize_Alignment = 'S' then
23295 Set_Optimize_Alignment_Space (E);
23296 elsif Optimize_Alignment = 'T' then
23297 Set_Optimize_Alignment_Time (E);
23298 end if;
23299 end Set_Optimize_Alignment_Flags;
23301 -----------------------
23302 -- Set_Public_Status --
23303 -----------------------
23305 procedure Set_Public_Status (Id : Entity_Id) is
23306 S : constant Entity_Id := Current_Scope;
23308 function Within_HSS_Or_If (E : Entity_Id) return Boolean;
23309 -- Determines if E is defined within handled statement sequence or
23310 -- an if statement, returns True if so, False otherwise.
23312 ----------------------
23313 -- Within_HSS_Or_If --
23314 ----------------------
23316 function Within_HSS_Or_If (E : Entity_Id) return Boolean is
23317 N : Node_Id;
23318 begin
23319 N := Declaration_Node (E);
23320 loop
23321 N := Parent (N);
23323 if No (N) then
23324 return False;
23326 elsif Nkind_In (N, N_Handled_Sequence_Of_Statements,
23327 N_If_Statement)
23328 then
23329 return True;
23330 end if;
23331 end loop;
23332 end Within_HSS_Or_If;
23334 -- Start of processing for Set_Public_Status
23336 begin
23337 -- Everything in the scope of Standard is public
23339 if S = Standard_Standard then
23340 Set_Is_Public (Id);
23342 -- Entity is definitely not public if enclosing scope is not public
23344 elsif not Is_Public (S) then
23345 return;
23347 -- An object or function declaration that occurs in a handled sequence
23348 -- of statements or within an if statement is the declaration for a
23349 -- temporary object or local subprogram generated by the expander. It
23350 -- never needs to be made public and furthermore, making it public can
23351 -- cause back end problems.
23353 elsif Nkind_In (Parent (Id), N_Object_Declaration,
23354 N_Function_Specification)
23355 and then Within_HSS_Or_If (Id)
23356 then
23357 return;
23359 -- Entities in public packages or records are public
23361 elsif Ekind (S) = E_Package or Is_Record_Type (S) then
23362 Set_Is_Public (Id);
23364 -- The bounds of an entry family declaration can generate object
23365 -- declarations that are visible to the back-end, e.g. in the
23366 -- the declaration of a composite type that contains tasks.
23368 elsif Is_Concurrent_Type (S)
23369 and then not Has_Completion (S)
23370 and then Nkind (Parent (Id)) = N_Object_Declaration
23371 then
23372 Set_Is_Public (Id);
23373 end if;
23374 end Set_Public_Status;
23376 -----------------------------
23377 -- Set_Referenced_Modified --
23378 -----------------------------
23380 procedure Set_Referenced_Modified (N : Node_Id; Out_Param : Boolean) is
23381 Pref : Node_Id;
23383 begin
23384 -- Deal with indexed or selected component where prefix is modified
23386 if Nkind_In (N, N_Indexed_Component, N_Selected_Component) then
23387 Pref := Prefix (N);
23389 -- If prefix is access type, then it is the designated object that is
23390 -- being modified, which means we have no entity to set the flag on.
23392 if No (Etype (Pref)) or else Is_Access_Type (Etype (Pref)) then
23393 return;
23395 -- Otherwise chase the prefix
23397 else
23398 Set_Referenced_Modified (Pref, Out_Param);
23399 end if;
23401 -- Otherwise see if we have an entity name (only other case to process)
23403 elsif Is_Entity_Name (N) and then Present (Entity (N)) then
23404 Set_Referenced_As_LHS (Entity (N), not Out_Param);
23405 Set_Referenced_As_Out_Parameter (Entity (N), Out_Param);
23406 end if;
23407 end Set_Referenced_Modified;
23409 ------------------
23410 -- Set_Rep_Info --
23411 ------------------
23413 procedure Set_Rep_Info (T1 : Entity_Id; T2 : Entity_Id) is
23414 begin
23415 Set_Is_Atomic (T1, Is_Atomic (T2));
23416 Set_Is_Independent (T1, Is_Independent (T2));
23417 Set_Is_Volatile_Full_Access (T1, Is_Volatile_Full_Access (T2));
23419 if Is_Base_Type (T1) then
23420 Set_Is_Volatile (T1, Is_Volatile (T2));
23421 end if;
23422 end Set_Rep_Info;
23424 ----------------------------
23425 -- Set_Scope_Is_Transient --
23426 ----------------------------
23428 procedure Set_Scope_Is_Transient (V : Boolean := True) is
23429 begin
23430 Scope_Stack.Table (Scope_Stack.Last).Is_Transient := V;
23431 end Set_Scope_Is_Transient;
23433 -------------------
23434 -- Set_Size_Info --
23435 -------------------
23437 procedure Set_Size_Info (T1, T2 : Entity_Id) is
23438 begin
23439 -- We copy Esize, but not RM_Size, since in general RM_Size is
23440 -- subtype specific and does not get inherited by all subtypes.
23442 Set_Esize (T1, Esize (T2));
23443 Set_Has_Biased_Representation (T1, Has_Biased_Representation (T2));
23445 if Is_Discrete_Or_Fixed_Point_Type (T1)
23446 and then
23447 Is_Discrete_Or_Fixed_Point_Type (T2)
23448 then
23449 Set_Is_Unsigned_Type (T1, Is_Unsigned_Type (T2));
23450 end if;
23452 Set_Alignment (T1, Alignment (T2));
23453 end Set_Size_Info;
23455 ------------------------------
23456 -- Should_Ignore_Pragma_Par --
23457 ------------------------------
23459 function Should_Ignore_Pragma_Par (Prag_Name : Name_Id) return Boolean is
23460 pragma Assert (Compiler_State = Parsing);
23461 -- This one can't work during semantic analysis, because we don't have a
23462 -- correct Current_Source_File.
23464 Result : constant Boolean :=
23465 Get_Name_Table_Boolean3 (Prag_Name)
23466 and then not Is_Internal_File_Name
23467 (File_Name (Current_Source_File));
23468 begin
23469 return Result;
23470 end Should_Ignore_Pragma_Par;
23472 ------------------------------
23473 -- Should_Ignore_Pragma_Sem --
23474 ------------------------------
23476 function Should_Ignore_Pragma_Sem (N : Node_Id) return Boolean is
23477 pragma Assert (Compiler_State = Analyzing);
23478 Prag_Name : constant Name_Id := Pragma_Name (N);
23479 Result : constant Boolean :=
23480 Get_Name_Table_Boolean3 (Prag_Name)
23481 and then not In_Internal_Unit (N);
23483 begin
23484 return Result;
23485 end Should_Ignore_Pragma_Sem;
23487 --------------------
23488 -- Static_Boolean --
23489 --------------------
23491 function Static_Boolean (N : Node_Id) return Uint is
23492 begin
23493 Analyze_And_Resolve (N, Standard_Boolean);
23495 if N = Error
23496 or else Error_Posted (N)
23497 or else Etype (N) = Any_Type
23498 then
23499 return No_Uint;
23500 end if;
23502 if Is_OK_Static_Expression (N) then
23503 if not Raises_Constraint_Error (N) then
23504 return Expr_Value (N);
23505 else
23506 return No_Uint;
23507 end if;
23509 elsif Etype (N) = Any_Type then
23510 return No_Uint;
23512 else
23513 Flag_Non_Static_Expr
23514 ("static boolean expression required here", N);
23515 return No_Uint;
23516 end if;
23517 end Static_Boolean;
23519 --------------------
23520 -- Static_Integer --
23521 --------------------
23523 function Static_Integer (N : Node_Id) return Uint is
23524 begin
23525 Analyze_And_Resolve (N, Any_Integer);
23527 if N = Error
23528 or else Error_Posted (N)
23529 or else Etype (N) = Any_Type
23530 then
23531 return No_Uint;
23532 end if;
23534 if Is_OK_Static_Expression (N) then
23535 if not Raises_Constraint_Error (N) then
23536 return Expr_Value (N);
23537 else
23538 return No_Uint;
23539 end if;
23541 elsif Etype (N) = Any_Type then
23542 return No_Uint;
23544 else
23545 Flag_Non_Static_Expr
23546 ("static integer expression required here", N);
23547 return No_Uint;
23548 end if;
23549 end Static_Integer;
23551 --------------------------
23552 -- Statically_Different --
23553 --------------------------
23555 function Statically_Different (E1, E2 : Node_Id) return Boolean is
23556 R1 : constant Node_Id := Get_Referenced_Object (E1);
23557 R2 : constant Node_Id := Get_Referenced_Object (E2);
23558 begin
23559 return Is_Entity_Name (R1)
23560 and then Is_Entity_Name (R2)
23561 and then Entity (R1) /= Entity (R2)
23562 and then not Is_Formal (Entity (R1))
23563 and then not Is_Formal (Entity (R2));
23564 end Statically_Different;
23566 --------------------------------------
23567 -- Subject_To_Loop_Entry_Attributes --
23568 --------------------------------------
23570 function Subject_To_Loop_Entry_Attributes (N : Node_Id) return Boolean is
23571 Stmt : Node_Id;
23573 begin
23574 Stmt := N;
23576 -- The expansion mechanism transform a loop subject to at least one
23577 -- 'Loop_Entry attribute into a conditional block. Infinite loops lack
23578 -- the conditional part.
23580 if Nkind_In (Stmt, N_Block_Statement, N_If_Statement)
23581 and then Nkind (Original_Node (N)) = N_Loop_Statement
23582 then
23583 Stmt := Original_Node (N);
23584 end if;
23586 return
23587 Nkind (Stmt) = N_Loop_Statement
23588 and then Present (Identifier (Stmt))
23589 and then Present (Entity (Identifier (Stmt)))
23590 and then Has_Loop_Entry_Attributes (Entity (Identifier (Stmt)));
23591 end Subject_To_Loop_Entry_Attributes;
23593 -----------------------------
23594 -- Subprogram_Access_Level --
23595 -----------------------------
23597 function Subprogram_Access_Level (Subp : Entity_Id) return Uint is
23598 begin
23599 if Present (Alias (Subp)) then
23600 return Subprogram_Access_Level (Alias (Subp));
23601 else
23602 return Scope_Depth (Enclosing_Dynamic_Scope (Subp));
23603 end if;
23604 end Subprogram_Access_Level;
23606 ---------------------
23607 -- Subprogram_Name --
23608 ---------------------
23610 function Subprogram_Name (N : Node_Id) return String is
23611 Buf : Bounded_String;
23612 Ent : Node_Id := N;
23613 Nod : Node_Id;
23615 begin
23616 while Present (Ent) loop
23617 case Nkind (Ent) is
23618 when N_Subprogram_Body =>
23619 Ent := Defining_Unit_Name (Specification (Ent));
23620 exit;
23622 when N_Subprogram_Declaration =>
23623 Nod := Corresponding_Body (Ent);
23625 if Present (Nod) then
23626 Ent := Nod;
23627 else
23628 Ent := Defining_Unit_Name (Specification (Ent));
23629 end if;
23631 exit;
23633 when N_Subprogram_Instantiation
23634 | N_Package_Body
23635 | N_Package_Specification
23637 Ent := Defining_Unit_Name (Ent);
23638 exit;
23640 when N_Protected_Type_Declaration =>
23641 Ent := Corresponding_Body (Ent);
23642 exit;
23644 when N_Protected_Body
23645 | N_Task_Body
23647 Ent := Defining_Identifier (Ent);
23648 exit;
23650 when others =>
23651 null;
23652 end case;
23654 Ent := Parent (Ent);
23655 end loop;
23657 if No (Ent) then
23658 return "unknown subprogram:unknown file:0:0";
23659 end if;
23661 -- If the subprogram is a child unit, use its simple name to start the
23662 -- construction of the fully qualified name.
23664 if Nkind (Ent) = N_Defining_Program_Unit_Name then
23665 Ent := Defining_Identifier (Ent);
23666 end if;
23668 Append_Entity_Name (Buf, Ent);
23670 -- Append homonym number if needed
23672 if Nkind (N) in N_Entity and then Has_Homonym (N) then
23673 declare
23674 H : Entity_Id := Homonym (N);
23675 Nr : Nat := 1;
23677 begin
23678 while Present (H) loop
23679 if Scope (H) = Scope (N) then
23680 Nr := Nr + 1;
23681 end if;
23683 H := Homonym (H);
23684 end loop;
23686 if Nr > 1 then
23687 Append (Buf, '#');
23688 Append (Buf, Nr);
23689 end if;
23690 end;
23691 end if;
23693 -- Append source location of Ent to Buf so that the string will
23694 -- look like "subp:file:line:col".
23696 declare
23697 Loc : constant Source_Ptr := Sloc (Ent);
23698 begin
23699 Append (Buf, ':');
23700 Append (Buf, Reference_Name (Get_Source_File_Index (Loc)));
23701 Append (Buf, ':');
23702 Append (Buf, Nat (Get_Logical_Line_Number (Loc)));
23703 Append (Buf, ':');
23704 Append (Buf, Nat (Get_Column_Number (Loc)));
23705 end;
23707 return +Buf;
23708 end Subprogram_Name;
23710 -------------------------------
23711 -- Support_Atomic_Primitives --
23712 -------------------------------
23714 function Support_Atomic_Primitives (Typ : Entity_Id) return Boolean is
23715 Size : Int;
23717 begin
23718 -- Verify the alignment of Typ is known
23720 if not Known_Alignment (Typ) then
23721 return False;
23722 end if;
23724 if Known_Static_Esize (Typ) then
23725 Size := UI_To_Int (Esize (Typ));
23727 -- If the Esize (Object_Size) is unknown at compile time, look at the
23728 -- RM_Size (Value_Size) which may have been set by an explicit rep item.
23730 elsif Known_Static_RM_Size (Typ) then
23731 Size := UI_To_Int (RM_Size (Typ));
23733 -- Otherwise, the size is considered to be unknown.
23735 else
23736 return False;
23737 end if;
23739 -- Check that the size of the component is 8, 16, 32, or 64 bits and
23740 -- that Typ is properly aligned.
23742 case Size is
23743 when 8 | 16 | 32 | 64 =>
23744 return Size = UI_To_Int (Alignment (Typ)) * 8;
23746 when others =>
23747 return False;
23748 end case;
23749 end Support_Atomic_Primitives;
23751 -----------------
23752 -- Trace_Scope --
23753 -----------------
23755 procedure Trace_Scope (N : Node_Id; E : Entity_Id; Msg : String) is
23756 begin
23757 if Debug_Flag_W then
23758 for J in 0 .. Scope_Stack.Last loop
23759 Write_Str (" ");
23760 end loop;
23762 Write_Str (Msg);
23763 Write_Name (Chars (E));
23764 Write_Str (" from ");
23765 Write_Location (Sloc (N));
23766 Write_Eol;
23767 end if;
23768 end Trace_Scope;
23770 -----------------------
23771 -- Transfer_Entities --
23772 -----------------------
23774 procedure Transfer_Entities (From : Entity_Id; To : Entity_Id) is
23775 procedure Set_Public_Status_Of (Id : Entity_Id);
23776 -- Set the Is_Public attribute of arbitrary entity Id by calling routine
23777 -- Set_Public_Status. If successful and Id denotes a record type, set
23778 -- the Is_Public attribute of its fields.
23780 --------------------------
23781 -- Set_Public_Status_Of --
23782 --------------------------
23784 procedure Set_Public_Status_Of (Id : Entity_Id) is
23785 Field : Entity_Id;
23787 begin
23788 if not Is_Public (Id) then
23789 Set_Public_Status (Id);
23791 -- When the input entity is a public record type, ensure that all
23792 -- its internal fields are also exposed to the linker. The fields
23793 -- of a class-wide type are never made public.
23795 if Is_Public (Id)
23796 and then Is_Record_Type (Id)
23797 and then not Is_Class_Wide_Type (Id)
23798 then
23799 Field := First_Entity (Id);
23800 while Present (Field) loop
23801 Set_Is_Public (Field);
23802 Next_Entity (Field);
23803 end loop;
23804 end if;
23805 end if;
23806 end Set_Public_Status_Of;
23808 -- Local variables
23810 Full_Id : Entity_Id;
23811 Id : Entity_Id;
23813 -- Start of processing for Transfer_Entities
23815 begin
23816 Id := First_Entity (From);
23818 if Present (Id) then
23820 -- Merge the entity chain of the source scope with that of the
23821 -- destination scope.
23823 if Present (Last_Entity (To)) then
23824 Set_Next_Entity (Last_Entity (To), Id);
23825 else
23826 Set_First_Entity (To, Id);
23827 end if;
23829 Set_Last_Entity (To, Last_Entity (From));
23831 -- Inspect the entities of the source scope and update their Scope
23832 -- attribute.
23834 while Present (Id) loop
23835 Set_Scope (Id, To);
23836 Set_Public_Status_Of (Id);
23838 -- Handle an internally generated full view for a private type
23840 if Is_Private_Type (Id)
23841 and then Present (Full_View (Id))
23842 and then Is_Itype (Full_View (Id))
23843 then
23844 Full_Id := Full_View (Id);
23846 Set_Scope (Full_Id, To);
23847 Set_Public_Status_Of (Full_Id);
23848 end if;
23850 Next_Entity (Id);
23851 end loop;
23853 Set_First_Entity (From, Empty);
23854 Set_Last_Entity (From, Empty);
23855 end if;
23856 end Transfer_Entities;
23858 -----------------------
23859 -- Type_Access_Level --
23860 -----------------------
23862 function Type_Access_Level (Typ : Entity_Id) return Uint is
23863 Btyp : Entity_Id;
23865 begin
23866 Btyp := Base_Type (Typ);
23868 -- Ada 2005 (AI-230): For most cases of anonymous access types, we
23869 -- simply use the level where the type is declared. This is true for
23870 -- stand-alone object declarations, and for anonymous access types
23871 -- associated with components the level is the same as that of the
23872 -- enclosing composite type. However, special treatment is needed for
23873 -- the cases of access parameters, return objects of an anonymous access
23874 -- type, and, in Ada 95, access discriminants of limited types.
23876 if Is_Access_Type (Btyp) then
23877 if Ekind (Btyp) = E_Anonymous_Access_Type then
23879 -- If the type is a nonlocal anonymous access type (such as for
23880 -- an access parameter) we treat it as being declared at the
23881 -- library level to ensure that names such as X.all'access don't
23882 -- fail static accessibility checks.
23884 if not Is_Local_Anonymous_Access (Typ) then
23885 return Scope_Depth (Standard_Standard);
23887 -- If this is a return object, the accessibility level is that of
23888 -- the result subtype of the enclosing function. The test here is
23889 -- little complicated, because we have to account for extended
23890 -- return statements that have been rewritten as blocks, in which
23891 -- case we have to find and the Is_Return_Object attribute of the
23892 -- itype's associated object. It would be nice to find a way to
23893 -- simplify this test, but it doesn't seem worthwhile to add a new
23894 -- flag just for purposes of this test. ???
23896 elsif Ekind (Scope (Btyp)) = E_Return_Statement
23897 or else
23898 (Is_Itype (Btyp)
23899 and then Nkind (Associated_Node_For_Itype (Btyp)) =
23900 N_Object_Declaration
23901 and then Is_Return_Object
23902 (Defining_Identifier
23903 (Associated_Node_For_Itype (Btyp))))
23904 then
23905 declare
23906 Scop : Entity_Id;
23908 begin
23909 Scop := Scope (Scope (Btyp));
23910 while Present (Scop) loop
23911 exit when Ekind (Scop) = E_Function;
23912 Scop := Scope (Scop);
23913 end loop;
23915 -- Treat the return object's type as having the level of the
23916 -- function's result subtype (as per RM05-6.5(5.3/2)).
23918 return Type_Access_Level (Etype (Scop));
23919 end;
23920 end if;
23921 end if;
23923 Btyp := Root_Type (Btyp);
23925 -- The accessibility level of anonymous access types associated with
23926 -- discriminants is that of the current instance of the type, and
23927 -- that's deeper than the type itself (AARM 3.10.2 (12.3.21)).
23929 -- AI-402: access discriminants have accessibility based on the
23930 -- object rather than the type in Ada 2005, so the above paragraph
23931 -- doesn't apply.
23933 -- ??? Needs completion with rules from AI-416
23935 if Ada_Version <= Ada_95
23936 and then Ekind (Typ) = E_Anonymous_Access_Type
23937 and then Present (Associated_Node_For_Itype (Typ))
23938 and then Nkind (Associated_Node_For_Itype (Typ)) =
23939 N_Discriminant_Specification
23940 then
23941 return Scope_Depth (Enclosing_Dynamic_Scope (Btyp)) + 1;
23942 end if;
23943 end if;
23945 -- Return library level for a generic formal type. This is done because
23946 -- RM(10.3.2) says that "The statically deeper relationship does not
23947 -- apply to ... a descendant of a generic formal type". Rather than
23948 -- checking at each point where a static accessibility check is
23949 -- performed to see if we are dealing with a formal type, this rule is
23950 -- implemented by having Type_Access_Level and Deepest_Type_Access_Level
23951 -- return extreme values for a formal type; Deepest_Type_Access_Level
23952 -- returns Int'Last. By calling the appropriate function from among the
23953 -- two, we ensure that the static accessibility check will pass if we
23954 -- happen to run into a formal type. More specifically, we should call
23955 -- Deepest_Type_Access_Level instead of Type_Access_Level whenever the
23956 -- call occurs as part of a static accessibility check and the error
23957 -- case is the case where the type's level is too shallow (as opposed
23958 -- to too deep).
23960 if Is_Generic_Type (Root_Type (Btyp)) then
23961 return Scope_Depth (Standard_Standard);
23962 end if;
23964 return Scope_Depth (Enclosing_Dynamic_Scope (Btyp));
23965 end Type_Access_Level;
23967 ------------------------------------
23968 -- Type_Without_Stream_Operation --
23969 ------------------------------------
23971 function Type_Without_Stream_Operation
23972 (T : Entity_Id;
23973 Op : TSS_Name_Type := TSS_Null) return Entity_Id
23975 BT : constant Entity_Id := Base_Type (T);
23976 Op_Missing : Boolean;
23978 begin
23979 if not Restriction_Active (No_Default_Stream_Attributes) then
23980 return Empty;
23981 end if;
23983 if Is_Elementary_Type (T) then
23984 if Op = TSS_Null then
23985 Op_Missing :=
23986 No (TSS (BT, TSS_Stream_Read))
23987 or else No (TSS (BT, TSS_Stream_Write));
23989 else
23990 Op_Missing := No (TSS (BT, Op));
23991 end if;
23993 if Op_Missing then
23994 return T;
23995 else
23996 return Empty;
23997 end if;
23999 elsif Is_Array_Type (T) then
24000 return Type_Without_Stream_Operation (Component_Type (T), Op);
24002 elsif Is_Record_Type (T) then
24003 declare
24004 Comp : Entity_Id;
24005 C_Typ : Entity_Id;
24007 begin
24008 Comp := First_Component (T);
24009 while Present (Comp) loop
24010 C_Typ := Type_Without_Stream_Operation (Etype (Comp), Op);
24012 if Present (C_Typ) then
24013 return C_Typ;
24014 end if;
24016 Next_Component (Comp);
24017 end loop;
24019 return Empty;
24020 end;
24022 elsif Is_Private_Type (T) and then Present (Full_View (T)) then
24023 return Type_Without_Stream_Operation (Full_View (T), Op);
24024 else
24025 return Empty;
24026 end if;
24027 end Type_Without_Stream_Operation;
24029 ----------------------------
24030 -- Unique_Defining_Entity --
24031 ----------------------------
24033 function Unique_Defining_Entity (N : Node_Id) return Entity_Id is
24034 begin
24035 return Unique_Entity (Defining_Entity (N));
24036 end Unique_Defining_Entity;
24038 -------------------
24039 -- Unique_Entity --
24040 -------------------
24042 function Unique_Entity (E : Entity_Id) return Entity_Id is
24043 U : Entity_Id := E;
24044 P : Node_Id;
24046 begin
24047 case Ekind (E) is
24048 when E_Constant =>
24049 if Present (Full_View (E)) then
24050 U := Full_View (E);
24051 end if;
24053 when Entry_Kind =>
24054 if Nkind (Parent (E)) = N_Entry_Body then
24055 declare
24056 Prot_Item : Entity_Id;
24057 Prot_Type : Entity_Id;
24059 begin
24060 if Ekind (E) = E_Entry then
24061 Prot_Type := Scope (E);
24063 -- Bodies of entry families are nested within an extra scope
24064 -- that contains an entry index declaration.
24066 else
24067 Prot_Type := Scope (Scope (E));
24068 end if;
24070 -- A protected type may be declared as a private type, in
24071 -- which case we need to get its full view.
24073 if Is_Private_Type (Prot_Type) then
24074 Prot_Type := Full_View (Prot_Type);
24075 end if;
24077 -- Full view may not be present on error, in which case
24078 -- return E by default.
24080 if Present (Prot_Type) then
24081 pragma Assert (Ekind (Prot_Type) = E_Protected_Type);
24083 -- Traverse the entity list of the protected type and
24084 -- locate an entry declaration which matches the entry
24085 -- body.
24087 Prot_Item := First_Entity (Prot_Type);
24088 while Present (Prot_Item) loop
24089 if Ekind (Prot_Item) in Entry_Kind
24090 and then Corresponding_Body (Parent (Prot_Item)) = E
24091 then
24092 U := Prot_Item;
24093 exit;
24094 end if;
24096 Next_Entity (Prot_Item);
24097 end loop;
24098 end if;
24099 end;
24100 end if;
24102 when Formal_Kind =>
24103 if Present (Spec_Entity (E)) then
24104 U := Spec_Entity (E);
24105 end if;
24107 when E_Package_Body =>
24108 P := Parent (E);
24110 if Nkind (P) = N_Defining_Program_Unit_Name then
24111 P := Parent (P);
24112 end if;
24114 if Nkind (P) = N_Package_Body
24115 and then Present (Corresponding_Spec (P))
24116 then
24117 U := Corresponding_Spec (P);
24119 elsif Nkind (P) = N_Package_Body_Stub
24120 and then Present (Corresponding_Spec_Of_Stub (P))
24121 then
24122 U := Corresponding_Spec_Of_Stub (P);
24123 end if;
24125 when E_Protected_Body =>
24126 P := Parent (E);
24128 if Nkind (P) = N_Protected_Body
24129 and then Present (Corresponding_Spec (P))
24130 then
24131 U := Corresponding_Spec (P);
24133 elsif Nkind (P) = N_Protected_Body_Stub
24134 and then Present (Corresponding_Spec_Of_Stub (P))
24135 then
24136 U := Corresponding_Spec_Of_Stub (P);
24138 if Is_Single_Protected_Object (U) then
24139 U := Etype (U);
24140 end if;
24141 end if;
24143 if Is_Private_Type (U) then
24144 U := Full_View (U);
24145 end if;
24147 when E_Subprogram_Body =>
24148 P := Parent (E);
24150 if Nkind (P) = N_Defining_Program_Unit_Name then
24151 P := Parent (P);
24152 end if;
24154 P := Parent (P);
24156 if Nkind (P) = N_Subprogram_Body
24157 and then Present (Corresponding_Spec (P))
24158 then
24159 U := Corresponding_Spec (P);
24161 elsif Nkind (P) = N_Subprogram_Body_Stub
24162 and then Present (Corresponding_Spec_Of_Stub (P))
24163 then
24164 U := Corresponding_Spec_Of_Stub (P);
24166 elsif Nkind (P) = N_Subprogram_Renaming_Declaration then
24167 U := Corresponding_Spec (P);
24168 end if;
24170 when E_Task_Body =>
24171 P := Parent (E);
24173 if Nkind (P) = N_Task_Body
24174 and then Present (Corresponding_Spec (P))
24175 then
24176 U := Corresponding_Spec (P);
24178 elsif Nkind (P) = N_Task_Body_Stub
24179 and then Present (Corresponding_Spec_Of_Stub (P))
24180 then
24181 U := Corresponding_Spec_Of_Stub (P);
24183 if Is_Single_Task_Object (U) then
24184 U := Etype (U);
24185 end if;
24186 end if;
24188 if Is_Private_Type (U) then
24189 U := Full_View (U);
24190 end if;
24192 when Type_Kind =>
24193 if Present (Full_View (E)) then
24194 U := Full_View (E);
24195 end if;
24197 when others =>
24198 null;
24199 end case;
24201 return U;
24202 end Unique_Entity;
24204 -----------------
24205 -- Unique_Name --
24206 -----------------
24208 function Unique_Name (E : Entity_Id) return String is
24210 -- Names in E_Subprogram_Body or E_Package_Body entities are not
24211 -- reliable, as they may not include the overloading suffix. Instead,
24212 -- when looking for the name of E or one of its enclosing scope, we get
24213 -- the name of the corresponding Unique_Entity.
24215 U : constant Entity_Id := Unique_Entity (E);
24217 function This_Name return String;
24219 ---------------
24220 -- This_Name --
24221 ---------------
24223 function This_Name return String is
24224 begin
24225 return Get_Name_String (Chars (U));
24226 end This_Name;
24228 -- Start of processing for Unique_Name
24230 begin
24231 if E = Standard_Standard
24232 or else Has_Fully_Qualified_Name (E)
24233 then
24234 return This_Name;
24236 elsif Ekind (E) = E_Enumeration_Literal then
24237 return Unique_Name (Etype (E)) & "__" & This_Name;
24239 else
24240 declare
24241 S : constant Entity_Id := Scope (U);
24242 pragma Assert (Present (S));
24244 begin
24245 -- Prefix names of predefined types with standard__, but leave
24246 -- names of user-defined packages and subprograms without prefix
24247 -- (even if technically they are nested in the Standard package).
24249 if S = Standard_Standard then
24250 if Ekind (U) = E_Package or else Is_Subprogram (U) then
24251 return This_Name;
24252 else
24253 return Unique_Name (S) & "__" & This_Name;
24254 end if;
24256 -- For intances of generic subprograms use the name of the related
24257 -- instace and skip the scope of its wrapper package.
24259 elsif Is_Wrapper_Package (S) then
24260 pragma Assert (Scope (S) = Scope (Related_Instance (S)));
24261 -- Wrapper package and the instantiation are in the same scope
24263 declare
24264 Enclosing_Name : constant String :=
24265 Unique_Name (Scope (S)) & "__" &
24266 Get_Name_String (Chars (Related_Instance (S)));
24268 begin
24269 if Is_Subprogram (U)
24270 and then not Is_Generic_Actual_Subprogram (U)
24271 then
24272 return Enclosing_Name;
24273 else
24274 return Enclosing_Name & "__" & This_Name;
24275 end if;
24276 end;
24278 else
24279 return Unique_Name (S) & "__" & This_Name;
24280 end if;
24281 end;
24282 end if;
24283 end Unique_Name;
24285 ---------------------
24286 -- Unit_Is_Visible --
24287 ---------------------
24289 function Unit_Is_Visible (U : Entity_Id) return Boolean is
24290 Curr : constant Node_Id := Cunit (Current_Sem_Unit);
24291 Curr_Entity : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
24293 function Unit_In_Parent_Context (Par_Unit : Node_Id) return Boolean;
24294 -- For a child unit, check whether unit appears in a with_clause
24295 -- of a parent.
24297 function Unit_In_Context (Comp_Unit : Node_Id) return Boolean;
24298 -- Scan the context clause of one compilation unit looking for a
24299 -- with_clause for the unit in question.
24301 ----------------------------
24302 -- Unit_In_Parent_Context --
24303 ----------------------------
24305 function Unit_In_Parent_Context (Par_Unit : Node_Id) return Boolean is
24306 begin
24307 if Unit_In_Context (Par_Unit) then
24308 return True;
24310 elsif Is_Child_Unit (Defining_Entity (Unit (Par_Unit))) then
24311 return Unit_In_Parent_Context (Parent_Spec (Unit (Par_Unit)));
24313 else
24314 return False;
24315 end if;
24316 end Unit_In_Parent_Context;
24318 ---------------------
24319 -- Unit_In_Context --
24320 ---------------------
24322 function Unit_In_Context (Comp_Unit : Node_Id) return Boolean is
24323 Clause : Node_Id;
24325 begin
24326 Clause := First (Context_Items (Comp_Unit));
24327 while Present (Clause) loop
24328 if Nkind (Clause) = N_With_Clause then
24329 if Library_Unit (Clause) = U then
24330 return True;
24332 -- The with_clause may denote a renaming of the unit we are
24333 -- looking for, eg. Text_IO which renames Ada.Text_IO.
24335 elsif
24336 Renamed_Entity (Entity (Name (Clause))) =
24337 Defining_Entity (Unit (U))
24338 then
24339 return True;
24340 end if;
24341 end if;
24343 Next (Clause);
24344 end loop;
24346 return False;
24347 end Unit_In_Context;
24349 -- Start of processing for Unit_Is_Visible
24351 begin
24352 -- The currrent unit is directly visible
24354 if Curr = U then
24355 return True;
24357 elsif Unit_In_Context (Curr) then
24358 return True;
24360 -- If the current unit is a body, check the context of the spec
24362 elsif Nkind (Unit (Curr)) = N_Package_Body
24363 or else
24364 (Nkind (Unit (Curr)) = N_Subprogram_Body
24365 and then not Acts_As_Spec (Unit (Curr)))
24366 then
24367 if Unit_In_Context (Library_Unit (Curr)) then
24368 return True;
24369 end if;
24370 end if;
24372 -- If the spec is a child unit, examine the parents
24374 if Is_Child_Unit (Curr_Entity) then
24375 if Nkind (Unit (Curr)) in N_Unit_Body then
24376 return
24377 Unit_In_Parent_Context
24378 (Parent_Spec (Unit (Library_Unit (Curr))));
24379 else
24380 return Unit_In_Parent_Context (Parent_Spec (Unit (Curr)));
24381 end if;
24383 else
24384 return False;
24385 end if;
24386 end Unit_Is_Visible;
24388 ------------------------------
24389 -- Universal_Interpretation --
24390 ------------------------------
24392 function Universal_Interpretation (Opnd : Node_Id) return Entity_Id is
24393 Index : Interp_Index;
24394 It : Interp;
24396 begin
24397 -- The argument may be a formal parameter of an operator or subprogram
24398 -- with multiple interpretations, or else an expression for an actual.
24400 if Nkind (Opnd) = N_Defining_Identifier
24401 or else not Is_Overloaded (Opnd)
24402 then
24403 if Etype (Opnd) = Universal_Integer
24404 or else Etype (Opnd) = Universal_Real
24405 then
24406 return Etype (Opnd);
24407 else
24408 return Empty;
24409 end if;
24411 else
24412 Get_First_Interp (Opnd, Index, It);
24413 while Present (It.Typ) loop
24414 if It.Typ = Universal_Integer
24415 or else It.Typ = Universal_Real
24416 then
24417 return It.Typ;
24418 end if;
24420 Get_Next_Interp (Index, It);
24421 end loop;
24423 return Empty;
24424 end if;
24425 end Universal_Interpretation;
24427 ---------------
24428 -- Unqualify --
24429 ---------------
24431 function Unqualify (Expr : Node_Id) return Node_Id is
24432 begin
24433 -- Recurse to handle unlikely case of multiple levels of qualification
24435 if Nkind (Expr) = N_Qualified_Expression then
24436 return Unqualify (Expression (Expr));
24438 -- Normal case, not a qualified expression
24440 else
24441 return Expr;
24442 end if;
24443 end Unqualify;
24445 -----------------
24446 -- Unqual_Conv --
24447 -----------------
24449 function Unqual_Conv (Expr : Node_Id) return Node_Id is
24450 begin
24451 -- Recurse to handle unlikely case of multiple levels of qualification
24452 -- and/or conversion.
24454 if Nkind_In (Expr, N_Qualified_Expression,
24455 N_Type_Conversion,
24456 N_Unchecked_Type_Conversion)
24457 then
24458 return Unqual_Conv (Expression (Expr));
24460 -- Normal case, not a qualified expression
24462 else
24463 return Expr;
24464 end if;
24465 end Unqual_Conv;
24467 -----------------------
24468 -- Visible_Ancestors --
24469 -----------------------
24471 function Visible_Ancestors (Typ : Entity_Id) return Elist_Id is
24472 List_1 : Elist_Id;
24473 List_2 : Elist_Id;
24474 Elmt : Elmt_Id;
24476 begin
24477 pragma Assert (Is_Record_Type (Typ) and then Is_Tagged_Type (Typ));
24479 -- Collect all the parents and progenitors of Typ. If the full-view of
24480 -- private parents and progenitors is available then it is used to
24481 -- generate the list of visible ancestors; otherwise their partial
24482 -- view is added to the resulting list.
24484 Collect_Parents
24485 (T => Typ,
24486 List => List_1,
24487 Use_Full_View => True);
24489 Collect_Interfaces
24490 (T => Typ,
24491 Ifaces_List => List_2,
24492 Exclude_Parents => True,
24493 Use_Full_View => True);
24495 -- Join the two lists. Avoid duplications because an interface may
24496 -- simultaneously be parent and progenitor of a type.
24498 Elmt := First_Elmt (List_2);
24499 while Present (Elmt) loop
24500 Append_Unique_Elmt (Node (Elmt), List_1);
24501 Next_Elmt (Elmt);
24502 end loop;
24504 return List_1;
24505 end Visible_Ancestors;
24507 ----------------------
24508 -- Within_Init_Proc --
24509 ----------------------
24511 function Within_Init_Proc return Boolean is
24512 S : Entity_Id;
24514 begin
24515 S := Current_Scope;
24516 while not Is_Overloadable (S) loop
24517 if S = Standard_Standard then
24518 return False;
24519 else
24520 S := Scope (S);
24521 end if;
24522 end loop;
24524 return Is_Init_Proc (S);
24525 end Within_Init_Proc;
24527 ---------------------------
24528 -- Within_Protected_Type --
24529 ---------------------------
24531 function Within_Protected_Type (E : Entity_Id) return Boolean is
24532 Scop : Entity_Id := Scope (E);
24534 begin
24535 while Present (Scop) loop
24536 if Ekind (Scop) = E_Protected_Type then
24537 return True;
24538 end if;
24540 Scop := Scope (Scop);
24541 end loop;
24543 return False;
24544 end Within_Protected_Type;
24546 ------------------
24547 -- Within_Scope --
24548 ------------------
24550 function Within_Scope (E : Entity_Id; S : Entity_Id) return Boolean is
24551 begin
24552 return Scope_Within_Or_Same (Scope (E), S);
24553 end Within_Scope;
24555 ----------------------------
24556 -- Within_Subprogram_Call --
24557 ----------------------------
24559 function Within_Subprogram_Call (N : Node_Id) return Boolean is
24560 Par : Node_Id;
24562 begin
24563 -- Climb the parent chain looking for a function or procedure call
24565 Par := N;
24566 while Present (Par) loop
24567 if Nkind_In (Par, N_Entry_Call_Statement,
24568 N_Function_Call,
24569 N_Procedure_Call_Statement)
24570 then
24571 return True;
24573 -- Prevent the search from going too far
24575 elsif Is_Body_Or_Package_Declaration (Par) then
24576 exit;
24577 end if;
24579 Par := Parent (Par);
24580 end loop;
24582 return False;
24583 end Within_Subprogram_Call;
24585 ----------------
24586 -- Wrong_Type --
24587 ----------------
24589 procedure Wrong_Type (Expr : Node_Id; Expected_Type : Entity_Id) is
24590 Found_Type : constant Entity_Id := First_Subtype (Etype (Expr));
24591 Expec_Type : constant Entity_Id := First_Subtype (Expected_Type);
24593 Matching_Field : Entity_Id;
24594 -- Entity to give a more precise suggestion on how to write a one-
24595 -- element positional aggregate.
24597 function Has_One_Matching_Field return Boolean;
24598 -- Determines if Expec_Type is a record type with a single component or
24599 -- discriminant whose type matches the found type or is one dimensional
24600 -- array whose component type matches the found type. In the case of
24601 -- one discriminant, we ignore the variant parts. That's not accurate,
24602 -- but good enough for the warning.
24604 ----------------------------
24605 -- Has_One_Matching_Field --
24606 ----------------------------
24608 function Has_One_Matching_Field return Boolean is
24609 E : Entity_Id;
24611 begin
24612 Matching_Field := Empty;
24614 if Is_Array_Type (Expec_Type)
24615 and then Number_Dimensions (Expec_Type) = 1
24616 and then Covers (Etype (Component_Type (Expec_Type)), Found_Type)
24617 then
24618 -- Use type name if available. This excludes multidimensional
24619 -- arrays and anonymous arrays.
24621 if Comes_From_Source (Expec_Type) then
24622 Matching_Field := Expec_Type;
24624 -- For an assignment, use name of target
24626 elsif Nkind (Parent (Expr)) = N_Assignment_Statement
24627 and then Is_Entity_Name (Name (Parent (Expr)))
24628 then
24629 Matching_Field := Entity (Name (Parent (Expr)));
24630 end if;
24632 return True;
24634 elsif not Is_Record_Type (Expec_Type) then
24635 return False;
24637 else
24638 E := First_Entity (Expec_Type);
24639 loop
24640 if No (E) then
24641 return False;
24643 elsif not Ekind_In (E, E_Discriminant, E_Component)
24644 or else Nam_In (Chars (E), Name_uTag, Name_uParent)
24645 then
24646 Next_Entity (E);
24648 else
24649 exit;
24650 end if;
24651 end loop;
24653 if not Covers (Etype (E), Found_Type) then
24654 return False;
24656 elsif Present (Next_Entity (E))
24657 and then (Ekind (E) = E_Component
24658 or else Ekind (Next_Entity (E)) = E_Discriminant)
24659 then
24660 return False;
24662 else
24663 Matching_Field := E;
24664 return True;
24665 end if;
24666 end if;
24667 end Has_One_Matching_Field;
24669 -- Start of processing for Wrong_Type
24671 begin
24672 -- Don't output message if either type is Any_Type, or if a message
24673 -- has already been posted for this node. We need to do the latter
24674 -- check explicitly (it is ordinarily done in Errout), because we
24675 -- are using ! to force the output of the error messages.
24677 if Expec_Type = Any_Type
24678 or else Found_Type = Any_Type
24679 or else Error_Posted (Expr)
24680 then
24681 return;
24683 -- If one of the types is a Taft-Amendment type and the other it its
24684 -- completion, it must be an illegal use of a TAT in the spec, for
24685 -- which an error was already emitted. Avoid cascaded errors.
24687 elsif Is_Incomplete_Type (Expec_Type)
24688 and then Has_Completion_In_Body (Expec_Type)
24689 and then Full_View (Expec_Type) = Etype (Expr)
24690 then
24691 return;
24693 elsif Is_Incomplete_Type (Etype (Expr))
24694 and then Has_Completion_In_Body (Etype (Expr))
24695 and then Full_View (Etype (Expr)) = Expec_Type
24696 then
24697 return;
24699 -- In an instance, there is an ongoing problem with completion of
24700 -- type derived from private types. Their structure is what Gigi
24701 -- expects, but the Etype is the parent type rather than the
24702 -- derived private type itself. Do not flag error in this case. The
24703 -- private completion is an entity without a parent, like an Itype.
24704 -- Similarly, full and partial views may be incorrect in the instance.
24705 -- There is no simple way to insure that it is consistent ???
24707 -- A similar view discrepancy can happen in an inlined body, for the
24708 -- same reason: inserted body may be outside of the original package
24709 -- and only partial views are visible at the point of insertion.
24711 elsif In_Instance or else In_Inlined_Body then
24712 if Etype (Etype (Expr)) = Etype (Expected_Type)
24713 and then
24714 (Has_Private_Declaration (Expected_Type)
24715 or else Has_Private_Declaration (Etype (Expr)))
24716 and then No (Parent (Expected_Type))
24717 then
24718 return;
24720 elsif Nkind (Parent (Expr)) = N_Qualified_Expression
24721 and then Entity (Subtype_Mark (Parent (Expr))) = Expected_Type
24722 then
24723 return;
24725 elsif Is_Private_Type (Expected_Type)
24726 and then Present (Full_View (Expected_Type))
24727 and then Covers (Full_View (Expected_Type), Etype (Expr))
24728 then
24729 return;
24731 -- Conversely, type of expression may be the private one
24733 elsif Is_Private_Type (Base_Type (Etype (Expr)))
24734 and then Full_View (Base_Type (Etype (Expr))) = Expected_Type
24735 then
24736 return;
24737 end if;
24738 end if;
24740 -- An interesting special check. If the expression is parenthesized
24741 -- and its type corresponds to the type of the sole component of the
24742 -- expected record type, or to the component type of the expected one
24743 -- dimensional array type, then assume we have a bad aggregate attempt.
24745 if Nkind (Expr) in N_Subexpr
24746 and then Paren_Count (Expr) /= 0
24747 and then Has_One_Matching_Field
24748 then
24749 Error_Msg_N ("positional aggregate cannot have one component", Expr);
24751 if Present (Matching_Field) then
24752 if Is_Array_Type (Expec_Type) then
24753 Error_Msg_NE
24754 ("\write instead `&''First ='> ...`", Expr, Matching_Field);
24755 else
24756 Error_Msg_NE
24757 ("\write instead `& ='> ...`", Expr, Matching_Field);
24758 end if;
24759 end if;
24761 -- Another special check, if we are looking for a pool-specific access
24762 -- type and we found an E_Access_Attribute_Type, then we have the case
24763 -- of an Access attribute being used in a context which needs a pool-
24764 -- specific type, which is never allowed. The one extra check we make
24765 -- is that the expected designated type covers the Found_Type.
24767 elsif Is_Access_Type (Expec_Type)
24768 and then Ekind (Found_Type) = E_Access_Attribute_Type
24769 and then Ekind (Base_Type (Expec_Type)) /= E_General_Access_Type
24770 and then Ekind (Base_Type (Expec_Type)) /= E_Anonymous_Access_Type
24771 and then Covers
24772 (Designated_Type (Expec_Type), Designated_Type (Found_Type))
24773 then
24774 Error_Msg_N -- CODEFIX
24775 ("result must be general access type!", Expr);
24776 Error_Msg_NE -- CODEFIX
24777 ("add ALL to }!", Expr, Expec_Type);
24779 -- Another special check, if the expected type is an integer type,
24780 -- but the expression is of type System.Address, and the parent is
24781 -- an addition or subtraction operation whose left operand is the
24782 -- expression in question and whose right operand is of an integral
24783 -- type, then this is an attempt at address arithmetic, so give
24784 -- appropriate message.
24786 elsif Is_Integer_Type (Expec_Type)
24787 and then Is_RTE (Found_Type, RE_Address)
24788 and then Nkind_In (Parent (Expr), N_Op_Add, N_Op_Subtract)
24789 and then Expr = Left_Opnd (Parent (Expr))
24790 and then Is_Integer_Type (Etype (Right_Opnd (Parent (Expr))))
24791 then
24792 Error_Msg_N
24793 ("address arithmetic not predefined in package System",
24794 Parent (Expr));
24795 Error_Msg_N
24796 ("\possible missing with/use of System.Storage_Elements",
24797 Parent (Expr));
24798 return;
24800 -- If the expected type is an anonymous access type, as for access
24801 -- parameters and discriminants, the error is on the designated types.
24803 elsif Ekind (Expec_Type) = E_Anonymous_Access_Type then
24804 if Comes_From_Source (Expec_Type) then
24805 Error_Msg_NE ("expected}!", Expr, Expec_Type);
24806 else
24807 Error_Msg_NE
24808 ("expected an access type with designated}",
24809 Expr, Designated_Type (Expec_Type));
24810 end if;
24812 if Is_Access_Type (Found_Type)
24813 and then not Comes_From_Source (Found_Type)
24814 then
24815 Error_Msg_NE
24816 ("\\found an access type with designated}!",
24817 Expr, Designated_Type (Found_Type));
24818 else
24819 if From_Limited_With (Found_Type) then
24820 Error_Msg_NE ("\\found incomplete}!", Expr, Found_Type);
24821 Error_Msg_Qual_Level := 99;
24822 Error_Msg_NE -- CODEFIX
24823 ("\\missing `WITH &;", Expr, Scope (Found_Type));
24824 Error_Msg_Qual_Level := 0;
24825 else
24826 Error_Msg_NE ("found}!", Expr, Found_Type);
24827 end if;
24828 end if;
24830 -- Normal case of one type found, some other type expected
24832 else
24833 -- If the names of the two types are the same, see if some number
24834 -- of levels of qualification will help. Don't try more than three
24835 -- levels, and if we get to standard, it's no use (and probably
24836 -- represents an error in the compiler) Also do not bother with
24837 -- internal scope names.
24839 declare
24840 Expec_Scope : Entity_Id;
24841 Found_Scope : Entity_Id;
24843 begin
24844 Expec_Scope := Expec_Type;
24845 Found_Scope := Found_Type;
24847 for Levels in Nat range 0 .. 3 loop
24848 if Chars (Expec_Scope) /= Chars (Found_Scope) then
24849 Error_Msg_Qual_Level := Levels;
24850 exit;
24851 end if;
24853 Expec_Scope := Scope (Expec_Scope);
24854 Found_Scope := Scope (Found_Scope);
24856 exit when Expec_Scope = Standard_Standard
24857 or else Found_Scope = Standard_Standard
24858 or else not Comes_From_Source (Expec_Scope)
24859 or else not Comes_From_Source (Found_Scope);
24860 end loop;
24861 end;
24863 if Is_Record_Type (Expec_Type)
24864 and then Present (Corresponding_Remote_Type (Expec_Type))
24865 then
24866 Error_Msg_NE ("expected}!", Expr,
24867 Corresponding_Remote_Type (Expec_Type));
24868 else
24869 Error_Msg_NE ("expected}!", Expr, Expec_Type);
24870 end if;
24872 if Is_Entity_Name (Expr)
24873 and then Is_Package_Or_Generic_Package (Entity (Expr))
24874 then
24875 Error_Msg_N ("\\found package name!", Expr);
24877 elsif Is_Entity_Name (Expr)
24878 and then Ekind_In (Entity (Expr), E_Procedure, E_Generic_Procedure)
24879 then
24880 if Ekind (Expec_Type) = E_Access_Subprogram_Type then
24881 Error_Msg_N
24882 ("found procedure name, possibly missing Access attribute!",
24883 Expr);
24884 else
24885 Error_Msg_N
24886 ("\\found procedure name instead of function!", Expr);
24887 end if;
24889 elsif Nkind (Expr) = N_Function_Call
24890 and then Ekind (Expec_Type) = E_Access_Subprogram_Type
24891 and then Etype (Designated_Type (Expec_Type)) = Etype (Expr)
24892 and then No (Parameter_Associations (Expr))
24893 then
24894 Error_Msg_N
24895 ("found function name, possibly missing Access attribute!",
24896 Expr);
24898 -- Catch common error: a prefix or infix operator which is not
24899 -- directly visible because the type isn't.
24901 elsif Nkind (Expr) in N_Op
24902 and then Is_Overloaded (Expr)
24903 and then not Is_Immediately_Visible (Expec_Type)
24904 and then not Is_Potentially_Use_Visible (Expec_Type)
24905 and then not In_Use (Expec_Type)
24906 and then Has_Compatible_Type (Right_Opnd (Expr), Expec_Type)
24907 then
24908 Error_Msg_N
24909 ("operator of the type is not directly visible!", Expr);
24911 elsif Ekind (Found_Type) = E_Void
24912 and then Present (Parent (Found_Type))
24913 and then Nkind (Parent (Found_Type)) = N_Full_Type_Declaration
24914 then
24915 Error_Msg_NE ("\\found premature usage of}!", Expr, Found_Type);
24917 else
24918 Error_Msg_NE ("\\found}!", Expr, Found_Type);
24919 end if;
24921 -- A special check for cases like M1 and M2 = 0 where M1 and M2 are
24922 -- of the same modular type, and (M1 and M2) = 0 was intended.
24924 if Expec_Type = Standard_Boolean
24925 and then Is_Modular_Integer_Type (Found_Type)
24926 and then Nkind_In (Parent (Expr), N_Op_And, N_Op_Or, N_Op_Xor)
24927 and then Nkind (Right_Opnd (Parent (Expr))) in N_Op_Compare
24928 then
24929 declare
24930 Op : constant Node_Id := Right_Opnd (Parent (Expr));
24931 L : constant Node_Id := Left_Opnd (Op);
24932 R : constant Node_Id := Right_Opnd (Op);
24934 begin
24935 -- The case for the message is when the left operand of the
24936 -- comparison is the same modular type, or when it is an
24937 -- integer literal (or other universal integer expression),
24938 -- which would have been typed as the modular type if the
24939 -- parens had been there.
24941 if (Etype (L) = Found_Type
24942 or else
24943 Etype (L) = Universal_Integer)
24944 and then Is_Integer_Type (Etype (R))
24945 then
24946 Error_Msg_N
24947 ("\\possible missing parens for modular operation", Expr);
24948 end if;
24949 end;
24950 end if;
24952 -- Reset error message qualification indication
24954 Error_Msg_Qual_Level := 0;
24955 end if;
24956 end Wrong_Type;
24958 --------------------------------
24959 -- Yields_Synchronized_Object --
24960 --------------------------------
24962 function Yields_Synchronized_Object (Typ : Entity_Id) return Boolean is
24963 Has_Sync_Comp : Boolean := False;
24964 Id : Entity_Id;
24966 begin
24967 -- An array type yields a synchronized object if its component type
24968 -- yields a synchronized object.
24970 if Is_Array_Type (Typ) then
24971 return Yields_Synchronized_Object (Component_Type (Typ));
24973 -- A descendant of type Ada.Synchronous_Task_Control.Suspension_Object
24974 -- yields a synchronized object by default.
24976 elsif Is_Descendant_Of_Suspension_Object (Typ) then
24977 return True;
24979 -- A protected type yields a synchronized object by default
24981 elsif Is_Protected_Type (Typ) then
24982 return True;
24984 -- A record type or type extension yields a synchronized object when its
24985 -- discriminants (if any) lack default values and all components are of
24986 -- a type that yelds a synchronized object.
24988 elsif Is_Record_Type (Typ) then
24990 -- Inspect all entities defined in the scope of the type, looking for
24991 -- components of a type that does not yeld a synchronized object or
24992 -- for discriminants with default values.
24994 Id := First_Entity (Typ);
24995 while Present (Id) loop
24996 if Comes_From_Source (Id) then
24997 if Ekind (Id) = E_Component then
24998 if Yields_Synchronized_Object (Etype (Id)) then
24999 Has_Sync_Comp := True;
25001 -- The component does not yield a synchronized object
25003 else
25004 return False;
25005 end if;
25007 elsif Ekind (Id) = E_Discriminant
25008 and then Present (Expression (Parent (Id)))
25009 then
25010 return False;
25011 end if;
25012 end if;
25014 Next_Entity (Id);
25015 end loop;
25017 -- Ensure that the parent type of a type extension yields a
25018 -- synchronized object.
25020 if Etype (Typ) /= Typ
25021 and then not Yields_Synchronized_Object (Etype (Typ))
25022 then
25023 return False;
25024 end if;
25026 -- If we get here, then all discriminants lack default values and all
25027 -- components are of a type that yields a synchronized object.
25029 return Has_Sync_Comp;
25031 -- A synchronized interface type yields a synchronized object by default
25033 elsif Is_Synchronized_Interface (Typ) then
25034 return True;
25036 -- A task type yelds a synchronized object by default
25038 elsif Is_Task_Type (Typ) then
25039 return True;
25041 -- Otherwise the type does not yield a synchronized object
25043 else
25044 return False;
25045 end if;
25046 end Yields_Synchronized_Object;
25048 ---------------------------
25049 -- Yields_Universal_Type --
25050 ---------------------------
25052 function Yields_Universal_Type (N : Node_Id) return Boolean is
25053 begin
25054 -- Integer and real literals are of a universal type
25056 if Nkind_In (N, N_Integer_Literal, N_Real_Literal) then
25057 return True;
25059 -- The values of certain attributes are of a universal type
25061 elsif Nkind (N) = N_Attribute_Reference then
25062 return
25063 Universal_Type_Attribute (Get_Attribute_Id (Attribute_Name (N)));
25065 -- ??? There are possibly other cases to consider
25067 else
25068 return False;
25069 end if;
25070 end Yields_Universal_Type;
25072 begin
25073 Erroutc.Subprogram_Name_Ptr := Subprogram_Name'Access;
25074 end Sem_Util;