1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2017, Free Software Foundation, Inc. --
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. --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
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
;
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
;
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
;
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
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
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
105 type Null_Status_Kind
is
107 -- This value indicates that a subexpression is known to have a null
108 -- value at compile time.
111 -- This value indicates that a subexpression is known to have a non-null
112 -- value at compile time.
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
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
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
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
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
))
176 Nkind
(Parent
(Full_View
(Typ
))) = N_Full_Type_Declaration
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).
187 -- Support for generic formals with interfaces is still missing ???
189 elsif Nkind
(Parent
(Typ
)) = N_Formal_Type_Declaration
then
194 (Nkind
(Parent
(Typ
)) = N_Private_Extension_Declaration
);
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
));
213 Nod
:= Type_Definition
(Parent
(Typ
));
216 -- Otherwise the type is of a kind which does not implement interfaces
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
233 Ensure_Freeze_Node
(E
);
234 L
:= Access_Types_To_Process
(Freeze_Node
(E
));
238 Set_Access_Types_To_Process
(Freeze_Node
(E
), 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
);
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
262 Id
:= New_Internal_Entity
(E_Block
, Current_Scope
, Loc
, 'B');
263 Set_Etype
(Id
, Standard_Void_Type
);
266 Set_Identifier
(N
, New_Occurrence_Of
(Id
, Loc
));
267 Set_Block_Node
(Id
, Identifier
(N
));
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
));
279 if No
(Declarations
(Aux_Node
)) then
280 Set_Declarations
(Aux_Node
, New_List
);
283 Append_To
(Declarations
(Aux_Node
), 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
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
))
298 (Is_Descendant_Of_Address
(T2
)
299 and then Is_Private_Type
(T2
)
300 and then Is_Integer_Type
(T1
)))
306 end Address_Integer_Convert_OK
;
312 function Address_Value
(N
: Node_Id
) return Node_Id
is
317 -- For constant, get constant expression
319 if Is_Entity_Name
(Expr
)
320 and then Ekind
(Entity
(Expr
)) = E_Constant
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
)
335 Expr
:= First
(Parameter_Associations
(Expr
));
337 if Nkind
(Expr
) = N_Parameter_Association
then
338 Expr
:= Explicit_Actual_Parameter
(Expr
);
341 -- We finally have the real expression
355 -- For now, just 8/16/32/64
357 function Addressable
(V
: Uint
) return Boolean is
359 return V
= Uint_8
or else
365 function Addressable
(V
: Int
) return Boolean is
373 ---------------------------------
374 -- Aggregate_Constraint_Checks --
375 ---------------------------------
377 procedure Aggregate_Constraint_Checks
379 Check_Typ
: Entity_Id
)
381 Exp_Typ
: constant Entity_Id
:= Etype
(Exp
);
384 if Raises_Constraint_Error
(Exp
) then
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
)
397 Rewrite
(Exp
, Convert_To
(Check_Typ
, Relocate_Node
(Exp
)));
398 Analyze_And_Resolve
(Exp
, Check_Typ
);
399 Check_Unset_Reference
(Exp
);
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
)
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
)
420 Install_Null_Excluding_Check
(Exp
);
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
)
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
,
452 elsif not Range_Checks_Suppressed
(Check_Typ
) then
453 Apply_Scalar_Range_Check
(Exp
, Check_Typ
);
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
464 if Is_Entity_Name
(Exp
)
465 and then Ekind
(Entity
(Exp
)) = E_Constant
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
)))
473 (Is_Entity_Name
(Type_High_Bound
(Check_Typ
))
474 and then Entity
(Exp
) = Entity
(Type_High_Bound
(Check_Typ
)))
479 Rewrite
(Exp
, Convert_To
(Check_Typ
, Relocate_Node
(Exp
)));
480 Analyze_And_Resolve
(Exp
, Check_Typ
);
481 Check_Unset_Reference
(Exp
);
484 -- Could use a comment on this case ???
487 Rewrite
(Exp
, Convert_To
(Check_Typ
, Relocate_Node
(Exp
)));
488 Analyze_And_Resolve
(Exp
, Check_Typ
);
489 Check_Unset_Reference
(Exp
);
493 end Aggregate_Constraint_Checks
;
495 -----------------------
496 -- Alignment_In_Bits --
497 -----------------------
499 function Alignment_In_Bits
(E
: Entity_Id
) return Uint
is
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
512 if No
(Constr
) or else Error_Posted
(Constr
) then
516 case Nkind
(Constr
) is
518 if Nkind
(Constr
) in N_Has_Entity
519 and then Present
(Entity
(Constr
))
521 if Is_Type
(Entity
(Constr
)) then
523 not Is_Discrete_Type
(Entity
(Constr
))
524 or else Is_OK_Static_Subtype
(Entity
(Constr
));
527 elsif Nkind
(Constr
) = N_Range
then
529 Is_OK_Static_Expression
(Low_Bound
(Constr
))
531 Is_OK_Static_Expression
(High_Bound
(Constr
));
533 elsif Nkind
(Constr
) = N_Attribute_Reference
534 and then Attribute_Name
(Constr
) = Name_Range
537 Is_OK_Static_Expression
538 (Type_Low_Bound
(Etype
(Prefix
(Constr
))))
540 Is_OK_Static_Expression
541 (Type_High_Bound
(Etype
(Prefix
(Constr
))));
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
=>
554 All_Composite_Constraints_Static
(Range_Expression
(Constr
));
556 when N_Index_Or_Discriminant_Constraint
=>
558 One_Cstr
: Entity_Id
;
560 One_Cstr
:= First
(Constraints
(Constr
));
561 while Present
(One_Cstr
) loop
562 if not All_Composite_Constraints_Static
(One_Cstr
) then
572 when N_Subtype_Indication
=>
574 All_Composite_Constraints_Static
(Subtype_Mark
(Constr
))
576 All_Composite_Constraints_Static
(Constraint
(Constr
));
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.
598 procedure Inner
(E
: Entity_Id
) is
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.
607 E_Name
: Bounded_String
;
610 Append
(E_Name
, Chars
(E
));
612 if E_Name
.Chars
(E_Name
.Length
) = 'R' then
613 E_Name
.Length
:= E_Name
.Length
- 1;
616 if Is_Internal_Name
(E_Name
) then
624 -- Just print entity name if its scope is at the outer level
626 if Scop
= Standard_Standard
then
629 -- If scope comes from source, write scope and entity
631 elsif Comes_From_Source
(Scop
) then
632 Append_Entity_Name
(Temp
, Scop
);
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
));
641 -- Otherwise nothing to output (happens in unnamed block statements)
650 E_Name
: Bounded_String
;
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'
662 E_Name
.Length
:= E_Name
.Length
- 1;
665 -- Adjust casing appropriately (gets name from source if possible)
667 Adjust_Name_Case
(E_Name
, Sloc
(E
));
668 Append
(Temp
, E_Name
);
672 -- Start of processing for Append_Entity_Name
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
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
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.
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
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
);
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
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
);
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
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.
779 Set_Analyzed
(N
, True);
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.
793 Set_Is_Static_Expression
(N
);
795 end Apply_Compile_Time_Constraint_Error
;
797 ---------------------------
798 -- Async_Readers_Enabled --
799 ---------------------------
801 function Async_Readers_Enabled
(Id
: Entity_Id
) return Boolean is
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
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
));
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
;
832 procedure Bad_Attribute
835 Warn
: Boolean := False)
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
);
851 Error_Msg_Name_1
:= Error_Msg_Name_1
+ 1;
855 --------------------------------
856 -- Bad_Predicated_Subtype_Use --
857 --------------------------------
859 procedure Bad_Predicated_Subtype_Use
863 Suggest_Static
: Boolean := False)
868 -- Avoid cascaded errors
870 if Error_Posted
(N
) then
874 if Inside_A_Generic
then
875 Gen
:= Current_Scope
;
876 while Present
(Gen
) and then Ekind
(Gen
) /= E_Generic_Package
loop
884 if Is_Generic_Formal
(Typ
) and then Is_Discrete_Type
(Typ
) then
885 Set_No_Predicate_On_Actual
(Typ
);
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
)
901 Gen
:= Current_Scope
;
902 while not Is_Generic_Instance
(Gen
) 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
);
914 Make_Raise_Program_Error
(Sloc
(N
),
915 Reason
=> PE_Bad_Predicated_Generic_Type
));
918 Error_Msg_FE
(Msg
& "<<", N
, Typ
);
922 Error_Msg_FE
(Msg
, N
, Typ
);
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
);
932 end Bad_Predicated_Subtype_Use
;
934 -----------------------------------------
935 -- Bad_Unordered_Enumeration_Reference --
936 -----------------------------------------
938 function Bad_Unordered_Enumeration_Reference
940 T
: Entity_Id
) return Boolean
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
959 pragma Assert
(Nkind_In
(N
, N_Block_Statement
,
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
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
982 -- Otherwise the construct is internal and should carry the location of
983 -- the original construct which prompted its creation.
988 end Begin_Keyword_Location
;
990 --------------------------
991 -- Build_Actual_Subtype --
992 --------------------------
994 function Build_Actual_Subtype
996 N
: Node_Or_Entity_Id
) return Node_Id
999 -- Normally Sloc (N), but may point to corresponding body in some cases
1001 Constraints
: List_Id
;
1007 Disc_Type
: Entity_Id
;
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
1023 Decl
: constant Node_Id
:= Unit_Declaration_Node
(Scope
(N
));
1025 if Nkind
(Decl
) = N_Subprogram_Declaration
1026 and then Present
(Corresponding_Body
(Decl
))
1028 Loc
:= Sloc
(Corresponding_Body
(Decl
));
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.
1047 Make_Attribute_Reference
(Loc
,
1049 Duplicate_Subexpr_No_Checks
(Obj
, Name_Req
=> True),
1050 Attribute_Name
=> Name_First
,
1051 Expressions
=> New_List
(
1052 Make_Integer_Literal
(Loc
, J
)));
1055 Make_Attribute_Reference
(Loc
,
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
);
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
1073 Constraints
:= New_List
;
1075 -- Type T is a generic derived type, inherit the discriminants from
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
)
1088 Disc_Type
:= Etype
(Base_Type
(T
));
1093 Discr
:= First_Discriminant
(Disc_Type
);
1094 while Present
(Discr
) loop
1095 Append_To
(Constraints
,
1096 Make_Selected_Component
(Loc
,
1098 Duplicate_Subexpr_No_Checks
(Obj
),
1099 Selector_Name
=> New_Occurrence_Of
(Discr
, Loc
)));
1100 Next_Discriminant
(Discr
);
1104 Subt
:= Make_Temporary
(Loc
, 'S', Related_Node
=> N
);
1105 Set_Is_Internal
(Subt
);
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
),
1114 Make_Index_Or_Discriminant_Constraint
(Loc
,
1115 Constraints
=> Constraints
)));
1117 Mark_Rewrite_Insertion
(Decl
);
1119 end Build_Actual_Subtype
;
1121 ---------------------------------------
1122 -- Build_Actual_Subtype_Of_Component --
1123 ---------------------------------------
1125 function Build_Actual_Subtype_Of_Component
1127 N
: Node_Id
) return Node_Id
1129 Loc
: constant Source_Ptr
:= Sloc
(N
);
1130 P
: constant Node_Id
:= Prefix
(N
);
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
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
;
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
1168 Make_Selected_Component
(Loc
,
1169 Prefix
=> New_Copy_Tree
(P
),
1170 Selector_Name
=> New_Occurrence_Of
(Entity
(Old_Lo
), Loc
));
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);
1184 if Denotes_Discriminant
(Old_Hi
) then
1186 Make_Selected_Component
(Loc
,
1187 Prefix
=> New_Copy_Tree
(P
),
1188 Selector_Name
=> New_Occurrence_Of
(Entity
(Old_Hi
), Loc
));
1191 Hi
:= New_Copy_Tree
(Old_Hi
);
1192 Set_Analyzed
(Hi
, False);
1195 Append
(Make_Range
(Loc
, Lo
, Hi
), 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
;
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
));
1220 D_Val
:= New_Copy_Tree
(Node
(D
));
1223 Append
(D_Val
, Constraints
);
1228 end Build_Actual_Record_Constraint
;
1230 -- Start of processing for Build_Actual_Subtype_Of_Component
1233 -- Why the test for Spec_Expression mode here???
1235 if In_Spec_Expression
then
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
)
1247 -- If the type of the dereference is already constrained, it is an
1250 if Is_Array_Type
(Etype
(N
))
1251 and then Is_Constrained
(Etype
(N
))
1255 Remove_Side_Effects
(P
);
1256 return Build_Actual_Subtype
(T
, N
);
1263 if Ekind
(T
) = E_Access_Subtype
then
1264 Desig_Typ
:= Designated_Type
(T
);
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
))
1276 Denotes_Discriminant
(Type_High_Bound
(Index_Typ
))
1278 Remove_Side_Effects
(P
);
1280 Build_Component_Subtype
1281 (Build_Actual_Array_Constraint
, Loc
, Base_Type
(T
));
1287 elsif Is_Composite_Type
(Desig_Typ
)
1288 and then Has_Discriminants
(Desig_Typ
)
1289 and then not Has_Unknown_Discriminants
(Desig_Typ
)
1291 if Is_Private_Type
(Desig_Typ
)
1292 and then No
(Discriminant_Constraint
(Desig_Typ
))
1294 Desig_Typ
:= Full_View
(Desig_Typ
);
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
);
1302 Build_Component_Subtype
(
1303 Build_Actual_Record_Constraint
, Loc
, Base_Type
(T
));
1310 -- If none of the above, the actual and nominal subtypes are the same
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
;
1323 Loc
: constant Source_Ptr
:= Sloc
(Bod
);
1324 Clone_Id
: constant Entity_Id
:= Class_Wide_Clone
(Spec_Id
);
1325 Clone_Body
: Node_Id
;
1328 -- The declaration of the class-wide clone was created when the
1329 -- corresponding class-wide condition was analyzed.
1332 Make_Subprogram_Body
(Loc
,
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
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
);
1363 New_F_Spec
: Entity_Id
;
1364 New_Formal
: Entity_Id
;
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
)
1383 Make_Type_Conversion
(Loc
,
1384 New_Occurrence_Of
(Par_Type
, Loc
),
1385 New_Occurrence_Of
(New_Formal
, Loc
)));
1388 Append_To
(Actuals
, New_Occurrence_Of
(New_Formal
, Loc
));
1391 Next_Formal
(Formal
);
1395 if Ekind
(Spec_Id
) = E_Procedure
then
1397 Make_Procedure_Call_Statement
(Loc
,
1398 Name
=> New_Occurrence_Of
(Clone_Id
, Loc
),
1399 Parameter_Associations
=> Actuals
);
1402 Make_Simple_Return_Statement
(Loc
,
1404 Make_Function_Call
(Loc
,
1405 Name
=> New_Occurrence_Of
(Clone_Id
, Loc
),
1406 Parameter_Associations
=> Actuals
));
1410 Make_Subprogram_Body
(Loc
,
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
))));
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"));
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
1457 T
: Entity_Id
) return Node_Id
1463 -- Unchecked_Union components do not require component subtypes
1465 if Is_Unchecked_Union
(T
) then
1469 Subt
:= Make_Temporary
(Loc
, 'S');
1470 Set_Is_Internal
(Subt
);
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
),
1479 Make_Index_Or_Discriminant_Constraint
(Loc
,
1480 Constraints
=> C
)));
1482 Mark_Rewrite_Insertion
(Decl
);
1484 end Build_Component_Subtype
;
1486 ---------------------------
1487 -- Build_Default_Subtype --
1488 ---------------------------
1490 function Build_Default_Subtype
1492 N
: Node_Id
) return Entity_Id
1494 Loc
: constant Source_Ptr
:= Sloc
(N
);
1498 -- The base type that is to be constrained by the defaults
1501 if not Has_Discriminants
(T
) or else Is_Constrained
(T
) then
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
))
1517 Bas
:= Full_View
(Bas
);
1520 Disc
:= First_Discriminant
(T
);
1522 if No
(Discriminant_Default_Value
(Disc
)) then
1527 Act
: constant Entity_Id
:= Make_Temporary
(Loc
, 'S');
1528 Constraints
: constant List_Id
:= New_List
;
1532 while Present
(Disc
) loop
1533 Append_To
(Constraints
,
1534 New_Copy_Tree
(Discriminant_Default_Value
(Disc
)));
1535 Next_Discriminant
(Disc
);
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
),
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
1554 if Ekind
(Current_Scope
) /= E_Record_Type
then
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
);
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
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
;
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
);
1604 Lo
:= New_Copy_Tree
(Old_Lo
);
1607 if Denotes_Discriminant
(Old_Hi
) then
1608 Hi
:= New_Occurrence_Of
(Discriminal
(Entity
(Old_Hi
)), Loc
);
1611 Hi
:= New_Copy_Tree
(Old_Hi
);
1614 Append
(Make_Range
(Loc
, Lo
, Hi
), 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
;
1631 D
:= First_Elmt
(Discriminant_Constraint
(T
));
1632 while Present
(D
) loop
1633 if Denotes_Discriminant
(Node
(D
)) then
1635 New_Occurrence_Of
(Discriminal
(Entity
(Node
(D
))), Loc
);
1637 D_Val
:= New_Copy_Tree
(Node
(D
));
1640 Append
(D_Val
, Constraints
);
1645 end Build_Discriminal_Record_Constraint
;
1647 -- Start of processing for Build_Discriminal_Subtype_Of_Component
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
)))
1655 Denotes_Discriminant
(Type_High_Bound
(Etype
(Id
)))
1657 return Build_Component_Subtype
1658 (Build_Discriminal_Array_Constraint
, Loc
, T
);
1664 elsif Ekind
(T
) = E_Record_Subtype
1665 and then Has_Discriminants
(T
)
1666 and then not Has_Unknown_Discriminants
(T
)
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
);
1679 -- If none of the above, the actual and nominal subtypes are the same
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
);
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
1704 if Scope
(Ent
) /= Standard_Standard
then
1705 Set_Package_Name
(Scope
(Ent
));
1708 Nam
: constant String := Get_Name_String
(Chars
(Ent
));
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;
1717 Get_Name_String
(Chars
(Ent
));
1719 end Set_Package_Name
;
1721 -- Start of processing for Build_Elaboration_Entity
1724 -- Ignore call if already constructed
1726 if Present
(Elaboration_Entity
(Spec_Id
)) then
1729 -- Ignore in ASIS mode, elaboration entity is not in source and plays
1730 -- no role in analysis.
1732 elsif ASIS_Mode
then
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
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
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
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
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
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
);
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
);
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
1824 Loc
: constant Source_Ptr
:= Sloc
(Expr
);
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
1856 Set_Entity
(Name
(Expr
), It
.Nam
);
1857 Set_Etype
(Name
(Expr
), Etype
(It
.Nam
));
1861 Get_Next_Interp
(I
, It
);
1865 -- Set type of call from resolved function name.
1867 Set_Etype
(Expr
, Etype
(Name
(Expr
)));
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
))
1879 Set_Is_Overloaded
(Generalized_Indexing
(Expr
), False);
1883 Make_Explicit_Dereference
(Loc
,
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
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
;
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
1918 Rewrite
(Formal_Type
, New_Occurrence_Of
(Typ
, Loc
));
1921 -- Nothing needs to be done for access parameters
1927 end Build_Overriding_Spec
;
1929 -----------------------------------
1930 -- Cannot_Raise_Constraint_Error --
1931 -----------------------------------
1933 function Cannot_Raise_Constraint_Error
(Expr
: Node_Id
) return Boolean is
1935 if Compile_Time_Known_Value
(Expr
) then
1938 elsif Do_Range_Check
(Expr
) then
1941 elsif Raises_Constraint_Error
(Expr
) then
1945 case Nkind
(Expr
) is
1946 when N_Identifier
=>
1949 when N_Expanded_Name
=>
1952 when N_Selected_Component
=>
1953 return not Do_Discriminant_Check
(Expr
);
1955 when N_Attribute_Reference
=>
1956 if Do_Overflow_Check
(Expr
) then
1959 elsif No
(Expressions
(Expr
)) then
1967 N
:= First
(Expressions
(Expr
));
1968 while Present
(N
) loop
1969 if Cannot_Raise_Constraint_Error
(N
) then
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
)
1987 return Cannot_Raise_Constraint_Error
(Expression
(Expr
));
1990 when N_Unchecked_Type_Conversion
=>
1991 return Cannot_Raise_Constraint_Error
(Expression
(Expr
));
1994 if Do_Overflow_Check
(Expr
) then
1997 return Cannot_Raise_Constraint_Error
(Right_Opnd
(Expr
));
2004 if Do_Division_Check
(Expr
)
2006 Do_Overflow_Check
(Expr
)
2011 Cannot_Raise_Constraint_Error
(Left_Opnd
(Expr
))
2013 Cannot_Raise_Constraint_Error
(Right_Opnd
(Expr
));
2032 | N_Op_Shift_Right_Arithmetic
2036 if Do_Overflow_Check
(Expr
) then
2040 Cannot_Raise_Constraint_Error
(Left_Opnd
(Expr
))
2042 Cannot_Raise_Constraint_Error
(Right_Opnd
(Expr
));
2049 end Cannot_Raise_Constraint_Error
;
2051 -----------------------------------------
2052 -- Check_Dynamically_Tagged_Expression --
2053 -----------------------------------------
2055 procedure Check_Dynamically_Tagged_Expression
2058 Related_Nod
: Node_Id
)
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
)
2073 Error_Msg_N
("dynamically tagged expression not allowed!", Expr
);
2075 end Check_Dynamically_Tagged_Expression
;
2077 --------------------------
2078 -- Check_Fully_Declared --
2079 --------------------------
2081 procedure Check_Fully_Declared
(T
: Entity_Id
; N
: Node_Id
) is
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
2092 -- The non-limited view is fully declared
2098 ("premature usage of incomplete}", N
, First_Subtype
(T
));
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
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
2115 ("type of& has incomplete component",
2116 N
, Defining_Identifier
(N
));
2119 ("premature usage of incomplete}",
2120 N
, First_Subtype
(T
));
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
2134 F
:= First_Formal
(Subp_Id
);
2135 while Present
(F
) loop
2138 if Is_Private_Type
(T
) and then Present
(Full_View
(T
)) then
2142 if Is_Descendant_Of_Address
(T
) or else Is_Limited_Type
(T
) then
2143 Set_Is_Pure
(Subp_Id
, False);
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
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)
2192 function Check_Node
(N
: Node_Id
) return Traverse_Result
is
2193 Is_Writable_Actual
: Boolean := False;
2197 if Nkind
(N
) = N_Identifier
then
2199 -- No analysis possible if the entity is not decorated
2201 if No
(Entity
(N
)) then
2204 -- Don't collect identifiers of packages, called functions, etc
2206 elsif Ekind_In
(Entity
(N
), E_Package
,
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
));
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
)),
2231 N_Extension_Aggregate
)
2234 Choice
: constant Node_Id
:= First
(Choices
(Parent
(N
)));
2237 if Ekind
(Entity
(N
)) = E_Discriminant
then
2240 elsif Expression
(Parent
(N
)) = N
2241 and then Nkind
(Choice
) = N_Identifier
2242 and then Ekind
(Entity
(Choice
)) = E_Discriminant
2248 -- Analyze if N is a writable actual of a function
2250 elsif Nkind
(Parent
(N
)) = N_Function_Call
then
2252 Call
: constant Node_Id
:= Parent
(N
);
2257 Id
:= Get_Called_Entity
(Call
);
2259 -- In case of previous error, no check is possible
2265 if Ekind_In
(Id
, E_Function
, E_Generic_Function
)
2266 and then Has_Out_Or_In_Out_Parameter
(Id
)
2268 Formal
:= First_Formal
(Id
);
2269 Actual
:= First_Actual
(Call
);
2270 while Present
(Actual
) and then Present
(Formal
) loop
2272 if Ekind_In
(Formal
, E_Out_Parameter
,
2275 Is_Writable_Actual
:= True;
2281 Next_Formal
(Formal
);
2282 Next_Actual
(Actual
);
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
);
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).
2315 Elmt
:= First_Elmt
(Writable_Actuals_List
);
2316 while Present
(Elmt
)
2317 and then Entity
(Node
(Elmt
)) /= Entity
(N
)
2322 if Sloc
(N
) > Sloc
(Node
(Elmt
)) then
2325 Error_Node
:= Node
(Elmt
);
2329 ("value may be affected by call to & "
2330 & "because order of evaluation is arbitrary",
2335 -- First occurrence of a elementary type writable actual
2338 Append_New_Elmt
(N
, To
=> Writable_Actuals_List
);
2342 if Identifiers_List
= No_Elist
then
2343 Identifiers_List
:= New_Elmt_List
;
2346 Append_Unique_Elmt
(N
, Identifiers_List
);
2359 N
: Node_Id
) return Boolean
2361 pragma Assert
(Nkind
(N
) in N_Has_Entity
);
2366 if List
= No_Elist
then
2370 Elmt
:= First_Elmt
(List
);
2371 while Present
(Elmt
) loop
2372 if Entity
(Node
(Elmt
)) = Entity
(N
) then
2386 procedure Do_Traversal
is new Traverse_Proc
(Check_Node
);
2387 -- The traversal procedure
2389 -- Start of processing for Collect_Identifiers
2392 if Present
(Error_Node
) then
2396 if Nkind
(N
) in N_Subexpr
and then Is_OK_Static_Expression
(N
) then
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
;
2410 Set_Ignore_Errors
(True);
2412 Set_Ignore_Errors
(Status
);
2413 end Preanalyze_Without_Errors
;
2415 -- Start of processing for Check_Function_Writable_Actuals
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
,
2428 N_Extension_Aggregate
,
2429 N_Full_Type_Declaration
,
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
)
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)).
2456 Collect_Identifiers
(Low_Bound
(N
));
2457 Collect_Identifiers
(High_Bound
(N
));
2459 when N_Membership_Test
2466 Collect_Identifiers
(Left_Opnd
(N
));
2468 if Present
(Right_Opnd
(N
)) then
2469 Collect_Identifiers
(Right_Opnd
(N
));
2472 if Nkind_In
(N
, N_In
, N_Not_In
)
2473 and then Present
(Alternatives
(N
))
2475 Expr
:= First
(Alternatives
(N
));
2476 while Present
(Expr
) loop
2477 Collect_Identifiers
(Expr
);
2484 when N_Full_Type_Declaration
=>
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
);
2492 if Nkind
(Type_Def
) = N_Derived_Type_Definition
then
2493 return Record_Extension_Part
(Type_Def
);
2497 end Get_Record_Part
;
2500 Def_Id
: Entity_Id
:= Defining_Identifier
(N
);
2501 Rec
: Node_Id
:= Get_Record_Part
(N
);
2504 -- No need to perform any analysis if the record has no
2507 if No
(Rec
) or else No
(Component_List
(Rec
)) then
2511 -- Collect the identifiers starting from the deepest
2512 -- derivation. Done to report the error in the deepest
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
))
2522 Collect_Identifiers
(Expression
(Comp
));
2529 exit when No
(Underlying_Type
(Etype
(Def_Id
)))
2530 or else Base_Type
(Underlying_Type
(Etype
(Def_Id
)))
2533 Def_Id
:= Base_Type
(Underlying_Type
(Etype
(Def_Id
)));
2534 Rec
:= Get_Record_Part
(Parent
(Def_Id
));
2538 when N_Entry_Call_Statement
2542 Id
: constant Entity_Id
:= Get_Called_Entity
(N
);
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
,
2553 Collect_Identifiers
(Actual
);
2556 Next_Formal
(Formal
);
2557 Next_Actual
(Actual
);
2562 | N_Extension_Aggregate
2567 Comp_Expr
: Node_Id
;
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
)))
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;
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;
2604 -- Count the rest of elements and locate the N_Others
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
)))
2626 Get_Index_Bounds
(Choice
, L
, H
);
2628 (Compile_Time_Known_Value
(L
)
2629 and then Compile_Time_Known_Value
(H
));
2632 + Expr_Value
(H
) - Expr_Value
(L
) + 1;
2635 -- Count single component. No other case available
2636 -- since we are handling an aggregate with static
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;
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
2662 if Present
(Others_Choice
)
2663 and then (Num_Components
- Count_Components
) > 1
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
2674 if not Expander_Active
then
2675 Comp_Expr
:= Expression
(Others_Assoc
);
2678 New_Copy_Tree
(Expression
(Others_Assoc
));
2679 Preanalyze_Without_Errors
(Comp_Expr
);
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.
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
)));
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
))
2708 -- Collect identifiers found in the dynamic bounds
2711 Count_Components
: Natural := 0;
2712 Low
, High
: Node_Id
;
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
)))
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
;
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
;
2742 -- The RM rule is violated if there is more than
2743 -- a single choice in a component association.
2746 Count_Components
:= Count_Components
+ 1;
2748 if No
(Aggr_Error_Node
)
2749 and then Count_Components
> 1
2751 Aggr_Error_Node
:= Choice
;
2754 if not Compile_Time_Known_Value
(Choice
) then
2755 Collect_Identifiers
(Choice
);
2767 -- Handle ancestor part of extension aggregates
2769 if Nkind
(N
) = N_Extension_Aggregate
then
2770 Collect_Identifiers
(Ancestor_Part
(N
));
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
);
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
2809 elsif Box_Present
(Assoc
) then
2813 if not Analyzed
(Expression
(Assoc
)) then
2815 New_Copy_Tree
(Expression
(Assoc
));
2816 Set_Parent
(Comp_Expr
, Parent
(N
));
2817 Preanalyze_Without_Errors
(Comp_Expr
);
2819 Comp_Expr
:= Expression
(Assoc
);
2822 Collect_Identifiers
(Comp_Expr
);
2838 -- No further action needed if we already reported an error
2840 if Present
(Error_Node
) then
2844 -- Check violation of RM 6.20/3 in aggregates
2846 if Present
(Aggr_Error_Node
)
2847 and then Writable_Actuals_List
/= No_Elist
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
)));
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
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
2873 | N_Component_Association
2874 | N_Component_Declaration
2877 ("value may be affected by call in other "
2878 & "component because they are evaluated "
2879 & "in unspecified order",
2886 ("value may be affected by call in other "
2887 & "alternative because they are evaluated "
2888 & "in unspecified order",
2893 ("value of actual may be affected by call in "
2894 & "other actual because they are evaluated "
2895 & "in unspecified order",
2907 end Check_Function_Writable_Actuals
;
2909 --------------------------------
2910 -- Check_Implicit_Dereference --
2911 --------------------------------
2913 procedure Check_Implicit_Dereference
(N
: Node_Id
; Typ
: Entity_Id
) is
2919 if Nkind
(N
) = N_Indexed_Component
2920 and then Present
(Generalized_Indexing
(N
))
2922 Nam
:= Generalized_Indexing
(N
);
2927 if Ada_Version
< Ada_2012
2928 or else not Has_Implicit_Dereference
(Base_Type
(Typ
))
2932 elsif not Comes_From_Source
(N
)
2933 and then Nkind
(N
) /= N_Indexed_Component
2937 elsif Is_Entity_Name
(Nam
) and then Is_Type
(Entity
(Nam
)) then
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
);
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.
2961 and then Nkind
(Parent
(Nam
)) = N_Selected_Component
2963 Set_Entity
(Selector_Name
(Parent
(Nam
)), Empty
);
2969 Next_Discriminant
(Disc
);
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
2986 while Present
(S
) loop
2987 if S
= Standard_Standard
then
2990 elsif Ekind
(S
) = E_Function
2991 and then Ekind
(Scope
(S
)) = E_Protected_Type
3001 and then Scope
(Nam
) = Prot
3002 and then Ekind
(Nam
) /= E_Function
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
3015 elsif Nkind
(N
) = N_Subprogram_Renaming_Declaration
then
3017 ("within protected function cannot use protected procedure in "
3018 & "renaming or as generic actual", N
);
3020 elsif Nkind
(N
) = N_Attribute_Reference
then
3022 ("within protected function cannot take access of protected "
3027 ("within protected function, protected object is constant", N
);
3029 ("\cannot call operation that may modify it", N
);
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
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
)
3050 Scope
(Entity
(Corresponding_Aspect
(P
))) = Scope
(Nam
)
3053 ("internal call cannot appear in precondition of "
3054 & "protected operation", N
);
3057 elsif Nkind
(P
) = N_Pragma
3058 and then Chars
(Pragma_Identifier
(P
)) = Name_Contract_Cases
3060 -- Check whether call is in a case guard. It is legal in a
3064 while Present
(P
) loop
3065 if Nkind
(Parent
(P
)) = N_Component_Association
3066 and then P
/= Expression
(Parent
(P
))
3069 ("internal call cannot appear in case guard in a "
3070 & "contract case", N
);
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
)
3084 ("internal call cannot appear in default for formal of "
3085 & "protected operation", N
);
3093 end Check_Internal_Protected_Use
;
3095 ---------------------------------------
3096 -- Check_Later_Vs_Basic_Declarations --
3097 ---------------------------------------
3099 procedure Check_Later_Vs_Basic_Declarations
3101 During_Parsing
: Boolean)
3103 Body_Sloc
: Source_Ptr
;
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
3117 if Nkind
(Decl
) in N_Later_Decl_Item
then
3120 elsif Nkind
(Decl
) = N_Pragma
then
3123 elsif During_Parsing
then
3126 -- In SPARK, a package declaration is not considered as a later
3127 -- declarative item.
3129 elsif Nkind
(Decl
) = N_Package_Declaration
then
3132 -- In SPARK, a renaming is considered as a later declarative item
3134 elsif Nkind
(Decl
) in N_Renaming_Declaration
then
3140 end Is_Later_Declarative_Item
;
3142 -- Start of processing for Check_Later_Vs_Basic_Declarations
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
3155 -- Once a body is encountered, we only allow later declarative
3156 -- items. The inner loop checks the rest of the list.
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
;
3167 ("(Ada 83) decl cannot appear after body#", Decl
);
3170 Error_Msg_Sloc
:= Body_Sloc
;
3171 Check_SPARK_05_Restriction
3172 ("decl cannot appear after body#", Decl
);
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;
3192 pragma Assert
(Ekind_In
(Id
, E_Abstract_State
, E_Variable
));
3194 -- Find the proper context where the object or state appears
3197 while Present
(Scop
) loop
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
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
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
);
3223 -- Stop the traversal when a package subject to a null abstract state
3226 if Ekind_In
(Context
, E_Generic_Package
, E_Package
)
3227 and then Has_Null_Abstract_State
(Context
)
3232 Scop
:= Scope
(Scop
);
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
)
3244 Error_Msg_N
("cannot introduce hidden state &", Id
);
3245 Error_Msg_NE
("\package & has null abstract state", Id
, Context
);
3247 end Check_No_Hidden_State
;
3249 ----------------------------------------
3250 -- Check_Nonvolatile_Function_Profile --
3251 ----------------------------------------
3253 procedure Check_Nonvolatile_Function_Profile
(Func_Id
: Entity_Id
) is
3257 -- Inspect all formal parameters
3259 Formal
:= First_Formal
(Func_Id
);
3260 while Present
(Formal
) loop
3261 if Is_Effectively_Volatile
(Etype
(Formal
)) then
3263 ("nonvolatile function & cannot have a volatile parameter",
3267 Next_Formal
(Formal
);
3270 -- Inspect the return type
3272 if Is_Effectively_Volatile
(Etype
(Func_Id
)) then
3274 ("nonvolatile function & cannot have a volatile return type",
3275 Result_Definition
(Parent
(Func_Id
)), Func_Id
);
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
);
3286 OK_Use
: Boolean := False;
3289 Spec_Id
: Entity_Id
;
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
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
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
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
,
3340 N_Task_Type_Declaration
)
3342 Spec_Id
:= Unique_Defining_Entity
(Par
);
3344 if Present
(Anonymous_Object
(Spec_Id
))
3345 and then Anonymous_Object
(Spec_Id
) = Conc_Obj
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
3356 elsif Nkind_In
(Par
, N_Package_Body
,
3357 N_Package_Declaration
,
3359 N_Subprogram_Declaration
)
3360 and then not Comes_From_Source
(Par
)
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
3373 -- Otherwise the reference is legal
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
3392 Par
:= Parent
(Par
);
3395 -- The reference is illegal as it appears outside the definition or
3396 -- body of the single protected/task type.
3400 ("reference to variable & cannot appear in this context",
3402 Error_Msg_Name_1
:= Chars
(Var_Id
);
3404 if Is_Single_Protected_Object
(Conc_Obj
) then
3406 ("\% is constituent of single protected type &", Ref
, Conc_Obj
);
3410 ("\% is constituent of single task type &", Ref
, Conc_Obj
);
3413 end Check_Part_Of_Reference
;
3415 ------------------------------------------
3416 -- Check_Potentially_Blocking_Operation --
3417 ------------------------------------------
3419 procedure Check_Potentially_Blocking_Operation
(N
: Node_Id
) is
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
3429 -- Indirect blocking through a subprogram call cannot be diagnosed
3430 -- statically without interprocedural analysis, so we do not attempt
3433 S
:= Scope
(Current_Scope
);
3434 while Present
(S
) and then S
/= Standard_Standard
loop
3435 if Is_Protected_Type
(S
) then
3437 ("potentially blocking operation in protected operation??", N
);
3443 end Check_Potentially_Blocking_Operation
;
3445 ------------------------------------
3446 -- Check_Previous_Null_Procedure --
3447 ------------------------------------
3449 procedure Check_Previous_Null_Procedure
3454 if Ekind
(Prev
) = E_Procedure
3455 and then Nkind
(Parent
(Prev
)) = N_Procedure_Specification
3456 and then Null_Present
(Parent
(Prev
))
3458 Error_Msg_Sloc
:= Sloc
(Prev
);
3460 ("declaration cannot complete previous null procedure#", Decl
);
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
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
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
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
3536 --------------------
3537 -- Adjust_Message --
3538 --------------------
3540 function Adjust_Message
(Msg
: String) return String is
3542 if Applied_On_Conjunct
then
3543 return "conjunct in " & Msg
;
3549 -------------------------
3550 -- Applied_On_Conjunct --
3551 -------------------------
3553 function Applied_On_Conjunct
return Boolean is
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
);
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
,
3591 N_Selected_Component
)
3595 -- Simple global list (only input items) or moded global list
3598 elsif Nkind
(List
) = N_Aggregate
then
3599 if Present
(Expressions
(List
)) then
3603 Assoc
:= First
(Component_Associations
(List
));
3604 while Present
(Assoc
) loop
3605 if Chars
(First
(Choices
(Assoc
))) /= Name_Input
then
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.
3622 end Has_Global_Output
;
3628 function Has_No_Output
(Subp
: Entity_Id
) return Boolean is
3632 -- A function has its result as output
3634 if Ekind
(Subp
) = E_Function
then
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
3646 Next_Formal
(Param
);
3649 -- An item of mode Output or In_Out in the Global contract is
3652 if Has_Global_Output
(Subp
) then
3662 -- Error node when reporting a warning on a (refined)
3665 -- Start of processing for Check_Conjunct
3668 if Applied_On_Conjunct
then
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
))
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
);
3694 Error_Msg_NE
(Adjust_Message
3695 ("postcondition does not check the outcome of calling "
3696 & "&?T?"), Err_Node
, Subp_Id
);
3701 ---------------------
3702 -- Check_Conjuncts --
3703 ---------------------
3705 procedure Check_Conjuncts
(Expr
: Node_Id
) is
3707 if Nkind_In
(Expr
, N_Op_And
, N_And_Then
) then
3708 Check_Conjuncts
(Left_Opnd
(Expr
));
3709 Check_Conjuncts
(Right_Opnd
(Expr
));
3711 Check_Conjunct
(Expr
);
3713 end Check_Conjuncts
;
3715 ----------------------
3716 -- Check_Expression --
3717 ----------------------
3719 procedure Check_Expression
(Expr
: Node_Id
) is
3721 if not Is_Trivial_Boolean
(Expr
) then
3722 Check_Function_Result
(Expr
);
3723 Check_Conjuncts
(Expr
);
3725 end Check_Expression
;
3727 ------------------------
3728 -- Is_Function_Result --
3729 ------------------------
3731 function Is_Function_Result
(N
: Node_Id
) return Traverse_Result
is
3733 if Is_Attribute_Result
(N
) then
3734 Result_Seen
:= True;
3737 -- Continue the traversal
3742 end Is_Function_Result
;
3744 ------------------------
3745 -- Is_Trivial_Boolean --
3746 ------------------------
3748 function Is_Trivial_Boolean
(N
: Node_Id
) return Boolean is
3751 Comes_From_Source
(N
)
3752 and then Is_Entity_Name
(N
)
3753 and then (Entity
(N
) = Standard_True
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.
3773 function Is_Post_State
(N
: Node_Id
) return Traverse_Result
is
3777 if Nkind_In
(N
, N_Explicit_Dereference
, N_Function_Call
) then
3778 Post_State_Seen
:= True;
3781 elsif Nkind_In
(N
, N_Expanded_Name
, N_Identifier
) then
3784 -- Treat an undecorated reference as OK
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
,
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
)
3802 Post_State_Seen
:= True;
3806 elsif Nkind
(N
) = N_Attribute_Reference
then
3807 if Attribute_Name
(N
) = Name_Old
then
3810 elsif Attribute_Name
(N
) = Name_Result
then
3811 Post_State_Seen
:= True;
3819 procedure Find_Post_State
is new Traverse_Proc
(Is_Post_State
);
3821 -- Start of processing for Mentions_Post_State
3824 Find_Post_State
(N
);
3826 return Post_State_Seen
;
3827 end Mentions_Post_State
;
3831 Expr
: constant Node_Id
:=
3833 (First
(Pragma_Argument_Associations
(Prag
)));
3834 Nam
: constant Name_Id
:= Pragma_Name
(Prag
);
3837 -- Start of processing for Check_Result_And_Post_State_In_Pragma
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
));
3850 -- Examine the expression of a postcondition
3852 else pragma Assert
(Nam_In
(Nam
, Name_Postcondition
,
3853 Name_Refined_Post
));
3854 Check_Expression
(Expr
);
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
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
3874 Next_Formal
(Formal
);
3878 end Has_In_Out_Parameter
;
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
;
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
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
3901 -- Nothing to do if there is no contract
3903 elsif No
(Items
) then
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
))
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
))
3917 Spec_Id
:= Corresponding_Spec_Of_Stub
(Subp_Decl
);
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
)
3932 Check_Result_And_Post_State_In_Pragma
(Prag
, Seen_In_Post
);
3935 Prag
:= Next_Pragma
(Prag
);
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
)
3947 Check_Result_And_Post_State_In_Pragma
(Prag
, Seen_In_Case
);
3950 Prag
:= Next_Pragma
(Prag
);
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
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
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
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
3988 ("postcondition does not mention function result?T?", Post_Prag
);
3990 end Check_Result_And_Post_State
;
3992 -----------------------------
3993 -- Check_State_Refinements --
3994 -----------------------------
3996 procedure Check_State_Refinements
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
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
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
;
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
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
))
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
4050 -- Otherwise examine the contents of the package
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
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
)
4065 Error_Msg_N
("state & requires refinement", State_Id
);
4068 Next_Elmt
(State_Elmt
);
4072 Check_Packages_In
(Visible_Declarations
(Spec
));
4073 Check_Packages_In
(Private_Declarations
(Spec
));
4077 -----------------------
4078 -- Check_Packages_In --
4079 -----------------------
4081 procedure Check_Packages_In
(Decls
: List_Id
) is
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
)
4091 Check_Package
(Decl
);
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
);
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
4117 and then Get_SPARK_Mode_From_Annotation
(Prag
) = Off
;
4119 end SPARK_Mode_Is_Off
;
4121 -- Start of processing for Check_State_Refinements
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
4132 elsif Nkind_In
(Context
, N_Entry_Body
,
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
));
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
));
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
4164 Check_Package
(Context
);
4166 end Check_State_Refinements
;
4168 ------------------------------
4169 -- Check_Unprotected_Access --
4170 ------------------------------
4172 procedure Check_Unprotected_Access
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
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
4194 if Is_Entity_Name
(Obj
) then
4196 Ent
: Entity_Id
:= Entity
(Obj
);
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
);
4206 if Is_Protected_Type
(Scope
(Ent
)) then
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
4222 end Enclosing_Protected_Type
;
4224 -------------------------
4225 -- Is_Public_Operation --
4226 -------------------------
4228 function Is_Public_Operation
return Boolean is
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
);
4238 and then E
/= First_Private_Entity
(Pref_Encl_Typ
)
4252 end Is_Public_Operation
;
4254 -- Start of processing for Check_Unprotected_Access
4257 if Nkind
(Expr
) = N_Attribute_Reference
4258 and then Attribute_Name
(Expr
) = Name_Unchecked_Access
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
)
4273 ("??possible unprotected access to protected data", Expr
);
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
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
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
;
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
,
4322 Remove
(States
, Constit_Id
);
4325 end Process_Constituent
;
4331 -- Start of processing for Process_Refinement_Clause
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
);
4346 -- Various forms of a single constituent
4349 Process_Constituent
(Constit
);
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
;
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
4376 if Ekind
(State_Id
) = E_Constant
then
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 ...
4389 ("body of package & has unused hidden states", Body_Id
);
4392 Error_Msg_Sloc
:= Sloc
(State_Id
);
4394 if Ekind
(State_Id
) = E_Abstract_State
then
4396 ("\abstract state & defined #", Body_Id
, State_Id
);
4399 SPARK_Msg_NE
("\variable & defined #", Body_Id
, State_Id
);
4403 Next_Elmt
(State_Elmt
);
4406 end Report_Unused_Body_States
;
4410 Prag
: constant Node_Id
:= Get_Pragma
(Body_Id
, Pragma_Refined_State
);
4411 Spec_Id
: constant Entity_Id
:= Spec_Entity
(Body_Id
);
4415 -- Start of processing for Check_Unused_Body_States
4418 -- Inspect the clauses of pragma Refined_State and determine whether all
4419 -- visible states declared within the package body participate in the
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
);
4435 -- Various forms of a single state refinement
4438 Process_Refinement_Clause
(Clause
, States
);
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
);
4446 end Check_Unused_Body_States
;
4452 function Choice_List
(N
: Node_Id
) return List_Id
is
4454 if Nkind
(N
) = N_Iterated_Component_Association
then
4455 return Discrete_Choices
(N
);
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
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
;
4487 -- Traverse the entity chain of the package and inspect all visible
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
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
)
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
);
4513 Next_Entity
(Item_Id
);
4515 end Collect_Visible_States
;
4517 -----------------------
4518 -- Is_Visible_Object --
4519 -----------------------
4521 function Is_Visible_Object
(Obj_Id
: Entity_Id
) return Boolean is
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
)))
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
))
4543 end Is_Visible_Object
;
4547 Body_Decl
: constant Node_Id
:= Unit_Declaration_Node
(Body_Id
);
4549 Item_Id
: Entity_Id
;
4550 States
: Elist_Id
:= No_Elist
;
4552 -- Start of processing for Collect_Body_States
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
)
4572 Append_New_Elmt
(Item_Id
, States
);
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
);
4590 end Collect_Body_States
;
4592 ------------------------
4593 -- Collect_Interfaces --
4594 ------------------------
4596 procedure Collect_Interfaces
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
4610 procedure Collect
(Typ
: Entity_Id
) is
4611 Ancestor
: Entity_Id
;
4619 -- Handle private types and subtypes
4622 and then Is_Private_Type
(Typ
)
4623 and then Present
(Full_View
(Typ
))
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
);
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:
4644 -- type A is tagged null record;
4645 -- type B is new A with private;
4646 -- type C is new A with private;
4648 -- type B is new C with null record;
4649 -- type C is new B with null record;
4652 and then Etype
(Full_T
) /= T
4654 Ancestor
:= Etype
(Full_T
);
4657 if Is_Interface
(Ancestor
) and then not Exclude_Parents
then
4658 Append_Unique_Elmt
(Ancestor
, Ifaces_List
);
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
4676 and then Etype
(T
) /= T
4677 and then Interface_Present_In_Ancestor
(Etype
(T
), Iface
)
4682 Append_Unique_Elmt
(Iface
, Ifaces_List
);
4691 -- Start of processing for Collect_Interfaces
4694 pragma Assert
(Is_Tagged_Type
(T
) or else Is_Concurrent_Type
(T
));
4695 Ifaces_List
:= New_Elmt_List
;
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
4714 procedure Collect
(Typ
: Entity_Id
) is
4715 Tag_Comp
: Entity_Id
;
4716 Parent_Typ
: Entity_Id
;
4719 -- Handle private types
4721 if Present
(Full_View
(Etype
(Typ
))) then
4722 Parent_Typ
:= Full_View
(Etype
(Typ
));
4724 Parent_Typ
:= Etype
(Typ
);
4727 if Parent_Typ
/= Typ
4729 -- Protect the frontend against wrong sources. For example:
4732 -- type A is tagged null record;
4733 -- type B is new A with private;
4734 -- type C is new A with private;
4736 -- type B is new C with null record;
4737 -- type C is new B with null record;
4740 and then Parent_Typ
/= Tagged_Type
4742 Collect
(Parent_Typ
);
4745 -- Collect the components containing tags of secondary dispatch
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
);
4757 -- Start of processing for Collect_Interface_Components
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
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
;
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.
4791 function Search_Tag
(Iface
: Entity_Id
) return Entity_Id
is
4794 if not Is_CPP_Class
(T
) then
4795 ADT
:= Next_Elmt
(Next_Elmt
(First_Elmt
(Access_Disp_Table
(T
))));
4797 ADT
:= Next_Elmt
(First_Elmt
(Access_Disp_Table
(T
)));
4801 and then Is_Tag
(Node
(ADT
))
4802 and then Related_Type
(Node
(ADT
)) /= Iface
4804 -- Skip secondary dispatch table referencing thunks to user
4805 -- defined primitives covered by this interface.
4807 pragma Assert
(Has_Suffix
(Node
(ADT
), 'P'));
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'));
4820 -- Skip secondary dispatch table referencing user-defined
4821 -- primitives covered by this interface.
4823 pragma Assert
(Has_Suffix
(Node
(ADT
), 'D'));
4826 -- Skip secondary dispatch table referencing predefined
4829 pragma Assert
(Has_Suffix
(Node
(ADT
), 'Z'));
4834 pragma Assert
(Is_Tag
(Node
(ADT
)));
4838 -- Start of processing for Collect_Interfaces_Info
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
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)
4872 Append_Elmt
(Node
(Comp_Elmt
), Components_List
);
4873 Append_Elmt
(Search_Tag
(Comp_Iface
), Tags_List
);
4877 Next_Elmt
(Comp_Elmt
);
4879 pragma Assert
(Present
(Comp_Elmt
));
4882 Next_Elmt
(Iface_Elmt
);
4884 end Collect_Interfaces_Info
;
4886 ---------------------
4887 -- Collect_Parents --
4888 ---------------------
4890 procedure Collect_Parents
4892 List
: out Elist_Id
;
4893 Use_Full_View
: Boolean := True)
4895 Current_Typ
: Entity_Id
:= T
;
4896 Parent_Typ
: Entity_Id
;
4899 List
:= New_Elmt_List
;
4901 -- No action if the if the type has no parents
4903 if T
= Etype
(T
) then
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
4914 Parent_Typ
:= Full_View
(Base_Type
(Parent_Typ
));
4917 Append_Elmt
(Parent_Typ
, List
);
4919 exit when Parent_Typ
= Current_Typ
;
4920 Current_Typ
:= Parent_Typ
;
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
);
4935 Is_Type_In_Pkg
: Boolean;
4936 Formal_Derived
: Boolean := False;
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.
4947 function Match
(E
: Entity_Id
) return Boolean is
4948 Etyp
: Entity_Id
:= Etype
(E
);
4951 if Ekind
(Etyp
) = E_Anonymous_Access_Type
then
4952 Etyp
:= Designated_Type
(Etyp
);
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
4960 (Ada_Version
>= Ada_2012
4961 and then Ekind
(Etyp
) = E_Incomplete_Type
4962 and then Full_View
(Etyp
) = B_Type
);
4965 -- Start of processing for Collect_Primitive_Operations
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
4983 Formal_Derived
:= True;
4985 return New_Elmt_List
;
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
);
5002 -- Locate the primitive subprograms of the type
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
)
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
)))
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
);
5036 Id
:= Next_Entity
(B_Type
);
5039 -- Set flag if this is a type in a package spec
5042 Is_Package_Or_Generic_Package
(B_Scope
)
5044 Nkind
(Parent
(Declaration_Node
(First_Subtype
(T
)))) /=
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
5072 Formal
:= First_Formal
(Id
);
5073 while Present
(Formal
) loop
5074 if Match
(Formal
) then
5079 Next_Formal
(Formal
);
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.
5088 and then (not Formal_Derived
or else Present
(Alias
(Id
)))
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
))))
5109 -- Include the subprogram in the list of primitives
5112 Append_Elmt
(Id
, Op_List
);
5119 -- For a type declared in System, some of its operations may
5120 -- appear in the target-specific extension to System.
5123 and then B_Scope
= RTU_Entity
(System
)
5124 and then Present_System_Aux
5126 B_Scope
:= System_Aux_Id
;
5127 Id
:= First_Entity
(System_Aux_Id
);
5133 end Collect_Primitive_Operations
;
5135 -----------------------------------
5136 -- Compile_Time_Constraint_Error --
5137 -----------------------------------
5139 function Compile_Time_Constraint_Error
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
5153 -- Start of processing for Compile_Time_Constraint_Error
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
5182 -- Copy message to Msgc, converting any ? in the message into <
5183 -- instead, so that we have an error in GNATprove mode.
5187 for J
in 1 .. Msgl
loop
5188 if Msg
(J
) = '?' and then (J
= 1 or else Msg
(J
- 1) /= ''') then
5191 Msgc
(J
) := Msg
(J
);
5195 -- Message is a warning, even in Ada 95 case
5197 if Msg
(Msg
'Last) = '?' or else Msg
(Msg
'Last) = '<' then
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.
5205 or else (Ada_Version
= Ada_83
and then Comes_From_Source
(N
))
5206 or else In_Instance_Not_Visible
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)
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
5231 if not Is_Statically_Unevaluated
(N
) then
5232 if Present
(Ent
) then
5233 Error_Msg_NEL
(Msgc
(1 .. Msgl
), N
, Ent
, Eloc
);
5235 Error_Msg_NEL
(Msgc
(1 .. Msgl
), N
, Etype
(N
), Eloc
);
5240 -- Check whether the context is an Init_Proc
5242 if Inside_Init_Proc
then
5244 Conc_Typ
: constant Entity_Id
:=
5245 Corresponding_Concurrent_Type
5246 (Entity
(Parameter_Type
(First
5247 (Parameter_Specifications
5248 (Parent
(Current_Scope
))))));
5251 -- Don't complain if the corresponding concurrent type
5252 -- doesn't come from source (i.e. a single task/protected
5255 if Present
(Conc_Typ
)
5256 and then not Comes_From_Source
(Conc_Typ
)
5259 ("\& [<<", N
, Standard_Constraint_Error
, Eloc
);
5262 if GNATprove_Mode
then
5264 ("\& would have been raised for objects of this "
5265 & "type", N
, Standard_Constraint_Error
, Eloc
);
5268 ("\& will be raised for objects of this type??",
5269 N
, Standard_Constraint_Error
, Eloc
);
5275 Error_Msg_NEL
("\& [<<", N
, Standard_Constraint_Error
, Eloc
);
5279 Error_Msg
("\static expression fails Constraint_Check", Eloc
);
5280 Set_Error_Posted
(N
);
5286 end Compile_Time_Constraint_Error
;
5288 -----------------------
5289 -- Conditional_Delay --
5290 -----------------------
5292 procedure Conditional_Delay
(New_Ent
, Old_Ent
: Entity_Id
) is
5294 if Has_Delayed_Freeze
(Old_Ent
) and then not Is_Frozen
(Old_Ent
) then
5295 Set_Has_Delayed_Freeze
(New_Ent
);
5297 end Conditional_Delay
;
5299 ----------------------------
5300 -- Contains_Refined_State --
5301 ----------------------------
5303 function Contains_Refined_State
(Prag
: Node_Id
) return Boolean is
5304 function Has_State_In_Dependency
(List
: Node_Id
) return Boolean;
5305 -- Determine whether a dependency list mentions a state with a visible
5308 function Has_State_In_Global
(List
: Node_Id
) return Boolean;
5309 -- Determine whether a global list mentions a state with a visible
5312 function Is_Refined_State
(Item
: Node_Id
) return Boolean;
5313 -- Determine whether Item is a reference to an abstract state with a
5314 -- visible refinement.
5316 -----------------------------
5317 -- Has_State_In_Dependency --
5318 -----------------------------
5320 function Has_State_In_Dependency
(List
: Node_Id
) return Boolean is
5325 -- A null dependency list does not mention any states
5327 if Nkind
(List
) = N_Null
then
5330 -- Dependency clauses appear as component associations of an
5333 elsif Nkind
(List
) = N_Aggregate
5334 and then Present
(Component_Associations
(List
))
5336 Clause
:= First
(Component_Associations
(List
));
5337 while Present
(Clause
) loop
5339 -- Inspect the outputs of a dependency clause
5341 Output
:= First
(Choices
(Clause
));
5342 while Present
(Output
) loop
5343 if Is_Refined_State
(Output
) then
5350 -- Inspect the outputs of a dependency clause
5352 if Is_Refined_State
(Expression
(Clause
)) then
5359 -- If we get here, then none of the dependency clauses mention a
5360 -- state with visible refinement.
5364 -- An illegal pragma managed to sneak in
5367 raise Program_Error
;
5369 end Has_State_In_Dependency
;
5371 -------------------------
5372 -- Has_State_In_Global --
5373 -------------------------
5375 function Has_State_In_Global
(List
: Node_Id
) return Boolean is
5379 -- A null global list does not mention any states
5381 if Nkind
(List
) = N_Null
then
5384 -- Simple global list or moded global list declaration
5386 elsif Nkind
(List
) = N_Aggregate
then
5388 -- The declaration of a simple global list appear as a collection
5391 if Present
(Expressions
(List
)) then
5392 Item
:= First
(Expressions
(List
));
5393 while Present
(Item
) loop
5394 if Is_Refined_State
(Item
) then
5401 -- The declaration of a moded global list appears as a collection
5402 -- of component associations where individual choices denote
5406 Item
:= First
(Component_Associations
(List
));
5407 while Present
(Item
) loop
5408 if Has_State_In_Global
(Expression
(Item
)) then
5416 -- If we get here, then the simple/moded global list did not
5417 -- mention any states with a visible refinement.
5421 -- Single global item declaration
5423 elsif Is_Entity_Name
(List
) then
5424 return Is_Refined_State
(List
);
5426 -- An illegal pragma managed to sneak in
5429 raise Program_Error
;
5431 end Has_State_In_Global
;
5433 ----------------------
5434 -- Is_Refined_State --
5435 ----------------------
5437 function Is_Refined_State
(Item
: Node_Id
) return Boolean is
5439 Item_Id
: Entity_Id
;
5442 if Nkind
(Item
) = N_Null
then
5445 -- States cannot be subject to attribute 'Result. This case arises
5446 -- in dependency relations.
5448 elsif Nkind
(Item
) = N_Attribute_Reference
5449 and then Attribute_Name
(Item
) = Name_Result
5453 -- Multiple items appear as an aggregate. This case arises in
5454 -- dependency relations.
5456 elsif Nkind
(Item
) = N_Aggregate
5457 and then Present
(Expressions
(Item
))
5459 Elmt
:= First
(Expressions
(Item
));
5460 while Present
(Elmt
) loop
5461 if Is_Refined_State
(Elmt
) then
5468 -- If we get here, then none of the inputs or outputs reference a
5469 -- state with visible refinement.
5476 Item_Id
:= Entity_Of
(Item
);
5480 and then Ekind
(Item_Id
) = E_Abstract_State
5481 and then Has_Visible_Refinement
(Item_Id
);
5483 end Is_Refined_State
;
5487 Arg
: constant Node_Id
:=
5488 Get_Pragma_Arg
(First
(Pragma_Argument_Associations
(Prag
)));
5489 Nam
: constant Name_Id
:= Pragma_Name
(Prag
);
5491 -- Start of processing for Contains_Refined_State
5494 if Nam
= Name_Depends
then
5495 return Has_State_In_Dependency
(Arg
);
5497 else pragma Assert
(Nam
= Name_Global
);
5498 return Has_State_In_Global
(Arg
);
5500 end Contains_Refined_State
;
5502 -------------------------
5503 -- Copy_Component_List --
5504 -------------------------
5506 function Copy_Component_List
5508 Loc
: Source_Ptr
) return List_Id
5511 Comps
: constant List_Id
:= New_List
;
5514 Comp
:= First_Component
(Underlying_Type
(R_Typ
));
5515 while Present
(Comp
) loop
5516 if Comes_From_Source
(Comp
) then
5518 Comp_Decl
: constant Node_Id
:= Declaration_Node
(Comp
);
5521 Make_Component_Declaration
(Loc
,
5522 Defining_Identifier
=>
5523 Make_Defining_Identifier
(Loc
, Chars
(Comp
)),
5524 Component_Definition
=>
5526 (Component_Definition
(Comp_Decl
), New_Sloc
=> Loc
)));
5530 Next_Component
(Comp
);
5534 end Copy_Component_List
;
5536 -------------------------
5537 -- Copy_Parameter_List --
5538 -------------------------
5540 function Copy_Parameter_List
(Subp_Id
: Entity_Id
) return List_Id
is
5541 Loc
: constant Source_Ptr
:= Sloc
(Subp_Id
);
5546 if No
(First_Formal
(Subp_Id
)) then
5550 Formal
:= First_Formal
(Subp_Id
);
5551 while Present
(Formal
) loop
5553 Make_Parameter_Specification
(Loc
,
5554 Defining_Identifier
=>
5555 Make_Defining_Identifier
(Sloc
(Formal
), Chars
(Formal
)),
5556 In_Present
=> In_Present
(Parent
(Formal
)),
5557 Out_Present
=> Out_Present
(Parent
(Formal
)),
5559 New_Occurrence_Of
(Etype
(Formal
), Loc
),
5561 New_Copy_Tree
(Expression
(Parent
(Formal
)))));
5563 Next_Formal
(Formal
);
5568 end Copy_Parameter_List
;
5570 ----------------------------
5571 -- Copy_SPARK_Mode_Aspect --
5572 ----------------------------
5574 procedure Copy_SPARK_Mode_Aspect
(From
: Node_Id
; To
: Node_Id
) is
5575 pragma Assert
(not Has_Aspects
(To
));
5579 if Has_Aspects
(From
) then
5580 Asp
:= Find_Aspect
(Defining_Entity
(From
), Aspect_SPARK_Mode
);
5582 if Present
(Asp
) then
5583 Set_Aspect_Specifications
(To
, New_List
(New_Copy_Tree
(Asp
)));
5584 Set_Has_Aspects
(To
, True);
5587 end Copy_SPARK_Mode_Aspect
;
5589 --------------------------
5590 -- Copy_Subprogram_Spec --
5591 --------------------------
5593 function Copy_Subprogram_Spec
(Spec
: Node_Id
) return Node_Id
is
5595 Formal_Spec
: Node_Id
;
5599 -- The structure of the original tree must be replicated without any
5600 -- alterations. Use New_Copy_Tree for this purpose.
5602 Result
:= New_Copy_Tree
(Spec
);
5604 -- However, the spec of a null procedure carries the corresponding null
5605 -- statement of the body (created by the parser), and this cannot be
5606 -- shared with the new subprogram spec.
5608 if Nkind
(Result
) = N_Procedure_Specification
then
5609 Set_Null_Statement
(Result
, Empty
);
5612 -- Create a new entity for the defining unit name
5614 Def_Id
:= Defining_Unit_Name
(Result
);
5615 Set_Defining_Unit_Name
(Result
,
5616 Make_Defining_Identifier
(Sloc
(Def_Id
), Chars
(Def_Id
)));
5618 -- Create new entities for the formal parameters
5620 if Present
(Parameter_Specifications
(Result
)) then
5621 Formal_Spec
:= First
(Parameter_Specifications
(Result
));
5622 while Present
(Formal_Spec
) loop
5623 Def_Id
:= Defining_Identifier
(Formal_Spec
);
5624 Set_Defining_Identifier
(Formal_Spec
,
5625 Make_Defining_Identifier
(Sloc
(Def_Id
), Chars
(Def_Id
)));
5632 end Copy_Subprogram_Spec
;
5634 --------------------------------
5635 -- Corresponding_Generic_Type --
5636 --------------------------------
5638 function Corresponding_Generic_Type
(T
: Entity_Id
) return Entity_Id
is
5644 if not Is_Generic_Actual_Type
(T
) then
5647 -- If the actual is the actual of an enclosing instance, resolution
5648 -- was correct in the generic.
5650 elsif Nkind
(Parent
(T
)) = N_Subtype_Declaration
5651 and then Is_Entity_Name
(Subtype_Indication
(Parent
(T
)))
5653 Is_Generic_Actual_Type
(Entity
(Subtype_Indication
(Parent
(T
))))
5660 if Is_Wrapper_Package
(Inst
) then
5661 Inst
:= Related_Instance
(Inst
);
5666 (Specification
(Unit_Declaration_Node
(Inst
)));
5668 -- Generic actual has the same name as the corresponding formal
5670 Typ
:= First_Entity
(Gen
);
5671 while Present
(Typ
) loop
5672 if Chars
(Typ
) = Chars
(T
) then
5681 end Corresponding_Generic_Type
;
5683 --------------------
5684 -- Current_Entity --
5685 --------------------
5687 -- The currently visible definition for a given identifier is the
5688 -- one most chained at the start of the visibility chain, i.e. the
5689 -- one that is referenced by the Node_Id value of the name of the
5690 -- given identifier.
5692 function Current_Entity
(N
: Node_Id
) return Entity_Id
is
5694 return Get_Name_Entity_Id
(Chars
(N
));
5697 -----------------------------
5698 -- Current_Entity_In_Scope --
5699 -----------------------------
5701 function Current_Entity_In_Scope
(N
: Node_Id
) return Entity_Id
is
5703 CS
: constant Entity_Id
:= Current_Scope
;
5705 Transient_Case
: constant Boolean := Scope_Is_Transient
;
5708 E
:= Get_Name_Entity_Id
(Chars
(N
));
5710 and then Scope
(E
) /= CS
5711 and then (not Transient_Case
or else Scope
(E
) /= Scope
(CS
))
5717 end Current_Entity_In_Scope
;
5723 function Current_Scope
return Entity_Id
is
5725 if Scope_Stack
.Last
= -1 then
5726 return Standard_Standard
;
5729 C
: constant Entity_Id
:=
5730 Scope_Stack
.Table
(Scope_Stack
.Last
).Entity
;
5735 return Standard_Standard
;
5741 ----------------------------
5742 -- Current_Scope_No_Loops --
5743 ----------------------------
5745 function Current_Scope_No_Loops
return Entity_Id
is
5749 -- Examine the scope stack starting from the current scope and skip any
5750 -- internally generated loops.
5753 while Present
(S
) and then S
/= Standard_Standard
loop
5754 if Ekind
(S
) = E_Loop
and then not Comes_From_Source
(S
) then
5762 end Current_Scope_No_Loops
;
5764 ------------------------
5765 -- Current_Subprogram --
5766 ------------------------
5768 function Current_Subprogram
return Entity_Id
is
5769 Scop
: constant Entity_Id
:= Current_Scope
;
5771 if Is_Subprogram_Or_Generic_Subprogram
(Scop
) then
5774 return Enclosing_Subprogram
(Scop
);
5776 end Current_Subprogram
;
5778 ----------------------------------
5779 -- Deepest_Type_Access_Level --
5780 ----------------------------------
5782 function Deepest_Type_Access_Level
(Typ
: Entity_Id
) return Uint
is
5784 if Ekind
(Typ
) = E_Anonymous_Access_Type
5785 and then not Is_Local_Anonymous_Access
(Typ
)
5786 and then Nkind
(Associated_Node_For_Itype
(Typ
)) = N_Object_Declaration
5788 -- Typ is the type of an Ada 2012 stand-alone object of an anonymous
5792 Scope_Depth
(Enclosing_Dynamic_Scope
5793 (Defining_Identifier
5794 (Associated_Node_For_Itype
(Typ
))));
5796 -- For generic formal type, return Int'Last (infinite).
5797 -- See comment preceding Is_Generic_Type call in Type_Access_Level.
5799 elsif Is_Generic_Type
(Root_Type
(Typ
)) then
5800 return UI_From_Int
(Int
'Last);
5803 return Type_Access_Level
(Typ
);
5805 end Deepest_Type_Access_Level
;
5807 ---------------------
5808 -- Defining_Entity --
5809 ---------------------
5811 function Defining_Entity
5813 Empty_On_Errors
: Boolean := False;
5814 Concurrent_Subunit
: Boolean := False) return Entity_Id
5818 when N_Abstract_Subprogram_Declaration
5819 | N_Expression_Function
5820 | N_Formal_Subprogram_Declaration
5821 | N_Generic_Package_Declaration
5822 | N_Generic_Subprogram_Declaration
5823 | N_Package_Declaration
5825 | N_Subprogram_Body_Stub
5826 | N_Subprogram_Declaration
5827 | N_Subprogram_Renaming_Declaration
5829 return Defining_Entity
(Specification
(N
));
5831 when N_Component_Declaration
5832 | N_Defining_Program_Unit_Name
5833 | N_Discriminant_Specification
5835 | N_Entry_Declaration
5836 | N_Entry_Index_Specification
5837 | N_Exception_Declaration
5838 | N_Exception_Renaming_Declaration
5839 | N_Formal_Object_Declaration
5840 | N_Formal_Package_Declaration
5841 | N_Formal_Type_Declaration
5842 | N_Full_Type_Declaration
5843 | N_Implicit_Label_Declaration
5844 | N_Incomplete_Type_Declaration
5845 | N_Iterator_Specification
5846 | N_Loop_Parameter_Specification
5847 | N_Number_Declaration
5848 | N_Object_Declaration
5849 | N_Object_Renaming_Declaration
5850 | N_Package_Body_Stub
5851 | N_Parameter_Specification
5852 | N_Private_Extension_Declaration
5853 | N_Private_Type_Declaration
5855 | N_Protected_Body_Stub
5856 | N_Protected_Type_Declaration
5857 | N_Single_Protected_Declaration
5858 | N_Single_Task_Declaration
5859 | N_Subtype_Declaration
5862 | N_Task_Type_Declaration
5864 return Defining_Identifier
(N
);
5868 Bod
: constant Node_Id
:= Proper_Body
(N
);
5869 Orig_Bod
: constant Node_Id
:= Original_Node
(Bod
);
5872 -- Retrieve the entity of the original protected or task body
5873 -- if requested by the caller.
5875 if Concurrent_Subunit
5876 and then Nkind
(Bod
) = N_Null_Statement
5877 and then Nkind_In
(Orig_Bod
, N_Protected_Body
, N_Task_Body
)
5879 return Defining_Entity
(Orig_Bod
);
5881 return Defining_Entity
(Bod
);
5885 when N_Function_Instantiation
5886 | N_Function_Specification
5887 | N_Generic_Function_Renaming_Declaration
5888 | N_Generic_Package_Renaming_Declaration
5889 | N_Generic_Procedure_Renaming_Declaration
5891 | N_Package_Instantiation
5892 | N_Package_Renaming_Declaration
5893 | N_Package_Specification
5894 | N_Procedure_Instantiation
5895 | N_Procedure_Specification
5898 Nam
: constant Node_Id
:= Defining_Unit_Name
(N
);
5899 Err
: Entity_Id
:= Empty
;
5902 if Nkind
(Nam
) in N_Entity
then
5905 -- For Error, make up a name and attach to declaration so we
5906 -- can continue semantic analysis.
5908 elsif Nam
= Error
then
5909 if Empty_On_Errors
then
5912 Err
:= Make_Temporary
(Sloc
(N
), 'T');
5913 Set_Defining_Unit_Name
(N
, Err
);
5918 -- If not an entity, get defining identifier
5921 return Defining_Identifier
(Nam
);
5925 when N_Block_Statement
5928 return Entity
(Identifier
(N
));
5931 if Empty_On_Errors
then
5934 raise Program_Error
;
5937 end Defining_Entity
;
5939 --------------------------
5940 -- Denotes_Discriminant --
5941 --------------------------
5943 function Denotes_Discriminant
5945 Check_Concurrent
: Boolean := False) return Boolean
5950 if not Is_Entity_Name
(N
) or else No
(Entity
(N
)) then
5956 -- If we are checking for a protected type, the discriminant may have
5957 -- been rewritten as the corresponding discriminal of the original type
5958 -- or of the corresponding concurrent record, depending on whether we
5959 -- are in the spec or body of the protected type.
5961 return Ekind
(E
) = E_Discriminant
5964 and then Ekind
(E
) = E_In_Parameter
5965 and then Present
(Discriminal_Link
(E
))
5967 (Is_Concurrent_Type
(Scope
(Discriminal_Link
(E
)))
5969 Is_Concurrent_Record_Type
(Scope
(Discriminal_Link
(E
)))));
5970 end Denotes_Discriminant
;
5972 -------------------------
5973 -- Denotes_Same_Object --
5974 -------------------------
5976 function Denotes_Same_Object
(A1
, A2
: Node_Id
) return Boolean is
5977 Obj1
: Node_Id
:= A1
;
5978 Obj2
: Node_Id
:= A2
;
5980 function Has_Prefix
(N
: Node_Id
) return Boolean;
5981 -- Return True if N has attribute Prefix
5983 function Is_Renaming
(N
: Node_Id
) return Boolean;
5984 -- Return true if N names a renaming entity
5986 function Is_Valid_Renaming
(N
: Node_Id
) return Boolean;
5987 -- For renamings, return False if the prefix of any dereference within
5988 -- the renamed object_name is a variable, or any expression within the
5989 -- renamed object_name contains references to variables or calls on
5990 -- nonstatic functions; otherwise return True (RM 6.4.1(6.10/3))
5996 function Has_Prefix
(N
: Node_Id
) return Boolean is
6000 N_Attribute_Reference
,
6002 N_Explicit_Dereference
,
6003 N_Indexed_Component
,
6005 N_Selected_Component
,
6013 function Is_Renaming
(N
: Node_Id
) return Boolean is
6015 return Is_Entity_Name
(N
)
6016 and then Present
(Renamed_Entity
(Entity
(N
)));
6019 -----------------------
6020 -- Is_Valid_Renaming --
6021 -----------------------
6023 function Is_Valid_Renaming
(N
: Node_Id
) return Boolean is
6025 function Check_Renaming
(N
: Node_Id
) return Boolean;
6026 -- Recursive function used to traverse all the prefixes of N
6028 function Check_Renaming
(N
: Node_Id
) return Boolean is
6031 and then not Check_Renaming
(Renamed_Entity
(Entity
(N
)))
6036 if Nkind
(N
) = N_Indexed_Component
then
6041 Indx
:= First
(Expressions
(N
));
6042 while Present
(Indx
) loop
6043 if not Is_OK_Static_Expression
(Indx
) then
6052 if Has_Prefix
(N
) then
6054 P
: constant Node_Id
:= Prefix
(N
);
6057 if Nkind
(N
) = N_Explicit_Dereference
6058 and then Is_Variable
(P
)
6062 elsif Is_Entity_Name
(P
)
6063 and then Ekind
(Entity
(P
)) = E_Function
6067 elsif Nkind
(P
) = N_Function_Call
then
6071 -- Recursion to continue traversing the prefix of the
6072 -- renaming expression
6074 return Check_Renaming
(P
);
6081 -- Start of processing for Is_Valid_Renaming
6084 return Check_Renaming
(N
);
6085 end Is_Valid_Renaming
;
6087 -- Start of processing for Denotes_Same_Object
6090 -- Both names statically denote the same stand-alone object or parameter
6091 -- (RM 6.4.1(6.5/3))
6093 if Is_Entity_Name
(Obj1
)
6094 and then Is_Entity_Name
(Obj2
)
6095 and then Entity
(Obj1
) = Entity
(Obj2
)
6100 -- For renamings, the prefix of any dereference within the renamed
6101 -- object_name is not a variable, and any expression within the
6102 -- renamed object_name contains no references to variables nor
6103 -- calls on nonstatic functions (RM 6.4.1(6.10/3)).
6105 if Is_Renaming
(Obj1
) then
6106 if Is_Valid_Renaming
(Obj1
) then
6107 Obj1
:= Renamed_Entity
(Entity
(Obj1
));
6113 if Is_Renaming
(Obj2
) then
6114 if Is_Valid_Renaming
(Obj2
) then
6115 Obj2
:= Renamed_Entity
(Entity
(Obj2
));
6121 -- No match if not same node kind (such cases are handled by
6122 -- Denotes_Same_Prefix)
6124 if Nkind
(Obj1
) /= Nkind
(Obj2
) then
6127 -- After handling valid renamings, one of the two names statically
6128 -- denoted a renaming declaration whose renamed object_name is known
6129 -- to denote the same object as the other (RM 6.4.1(6.10/3))
6131 elsif Is_Entity_Name
(Obj1
) then
6132 if Is_Entity_Name
(Obj2
) then
6133 return Entity
(Obj1
) = Entity
(Obj2
);
6138 -- Both names are selected_components, their prefixes are known to
6139 -- denote the same object, and their selector_names denote the same
6140 -- component (RM 6.4.1(6.6/3)).
6142 elsif Nkind
(Obj1
) = N_Selected_Component
then
6143 return Denotes_Same_Object
(Prefix
(Obj1
), Prefix
(Obj2
))
6145 Entity
(Selector_Name
(Obj1
)) = Entity
(Selector_Name
(Obj2
));
6147 -- Both names are dereferences and the dereferenced names are known to
6148 -- denote the same object (RM 6.4.1(6.7/3))
6150 elsif Nkind
(Obj1
) = N_Explicit_Dereference
then
6151 return Denotes_Same_Object
(Prefix
(Obj1
), Prefix
(Obj2
));
6153 -- Both names are indexed_components, their prefixes are known to denote
6154 -- the same object, and each of the pairs of corresponding index values
6155 -- are either both static expressions with the same static value or both
6156 -- names that are known to denote the same object (RM 6.4.1(6.8/3))
6158 elsif Nkind
(Obj1
) = N_Indexed_Component
then
6159 if not Denotes_Same_Object
(Prefix
(Obj1
), Prefix
(Obj2
)) then
6167 Indx1
:= First
(Expressions
(Obj1
));
6168 Indx2
:= First
(Expressions
(Obj2
));
6169 while Present
(Indx1
) loop
6171 -- Indexes must denote the same static value or same object
6173 if Is_OK_Static_Expression
(Indx1
) then
6174 if not Is_OK_Static_Expression
(Indx2
) then
6177 elsif Expr_Value
(Indx1
) /= Expr_Value
(Indx2
) then
6181 elsif not Denotes_Same_Object
(Indx1
, Indx2
) then
6193 -- Both names are slices, their prefixes are known to denote the same
6194 -- object, and the two slices have statically matching index constraints
6195 -- (RM 6.4.1(6.9/3))
6197 elsif Nkind
(Obj1
) = N_Slice
6198 and then Denotes_Same_Object
(Prefix
(Obj1
), Prefix
(Obj2
))
6201 Lo1
, Lo2
, Hi1
, Hi2
: Node_Id
;
6204 Get_Index_Bounds
(Etype
(Obj1
), Lo1
, Hi1
);
6205 Get_Index_Bounds
(Etype
(Obj2
), Lo2
, Hi2
);
6207 -- Check whether bounds are statically identical. There is no
6208 -- attempt to detect partial overlap of slices.
6210 return Denotes_Same_Object
(Lo1
, Lo2
)
6212 Denotes_Same_Object
(Hi1
, Hi2
);
6215 -- In the recursion, literals appear as indexes
6217 elsif Nkind
(Obj1
) = N_Integer_Literal
6219 Nkind
(Obj2
) = N_Integer_Literal
6221 return Intval
(Obj1
) = Intval
(Obj2
);
6226 end Denotes_Same_Object
;
6228 -------------------------
6229 -- Denotes_Same_Prefix --
6230 -------------------------
6232 function Denotes_Same_Prefix
(A1
, A2
: Node_Id
) return Boolean is
6234 if Is_Entity_Name
(A1
) then
6235 if Nkind_In
(A2
, N_Selected_Component
, N_Indexed_Component
)
6236 and then not Is_Access_Type
(Etype
(A1
))
6238 return Denotes_Same_Object
(A1
, Prefix
(A2
))
6239 or else Denotes_Same_Prefix
(A1
, Prefix
(A2
));
6244 elsif Is_Entity_Name
(A2
) then
6245 return Denotes_Same_Prefix
(A1
=> A2
, A2
=> A1
);
6247 elsif Nkind_In
(A1
, N_Selected_Component
, N_Indexed_Component
, N_Slice
)
6249 Nkind_In
(A2
, N_Selected_Component
, N_Indexed_Component
, N_Slice
)
6252 Root1
, Root2
: Node_Id
;
6253 Depth1
, Depth2
: Nat
:= 0;
6256 Root1
:= Prefix
(A1
);
6257 while not Is_Entity_Name
(Root1
) loop
6259 (Root1
, N_Selected_Component
, N_Indexed_Component
)
6263 Root1
:= Prefix
(Root1
);
6266 Depth1
:= Depth1
+ 1;
6269 Root2
:= Prefix
(A2
);
6270 while not Is_Entity_Name
(Root2
) loop
6271 if not Nkind_In
(Root2
, N_Selected_Component
,
6272 N_Indexed_Component
)
6276 Root2
:= Prefix
(Root2
);
6279 Depth2
:= Depth2
+ 1;
6282 -- If both have the same depth and they do not denote the same
6283 -- object, they are disjoint and no warning is needed.
6285 if Depth1
= Depth2
then
6288 elsif Depth1
> Depth2
then
6289 Root1
:= Prefix
(A1
);
6290 for J
in 1 .. Depth1
- Depth2
- 1 loop
6291 Root1
:= Prefix
(Root1
);
6294 return Denotes_Same_Object
(Root1
, A2
);
6297 Root2
:= Prefix
(A2
);
6298 for J
in 1 .. Depth2
- Depth1
- 1 loop
6299 Root2
:= Prefix
(Root2
);
6302 return Denotes_Same_Object
(A1
, Root2
);
6309 end Denotes_Same_Prefix
;
6311 ----------------------
6312 -- Denotes_Variable --
6313 ----------------------
6315 function Denotes_Variable
(N
: Node_Id
) return Boolean is
6317 return Is_Variable
(N
) and then Paren_Count
(N
) = 0;
6318 end Denotes_Variable
;
6320 -----------------------------
6321 -- Depends_On_Discriminant --
6322 -----------------------------
6324 function Depends_On_Discriminant
(N
: Node_Id
) return Boolean is
6329 Get_Index_Bounds
(N
, L
, H
);
6330 return Denotes_Discriminant
(L
) or else Denotes_Discriminant
(H
);
6331 end Depends_On_Discriminant
;
6333 -------------------------
6334 -- Designate_Same_Unit --
6335 -------------------------
6337 function Designate_Same_Unit
6339 Name2
: Node_Id
) return Boolean
6341 K1
: constant Node_Kind
:= Nkind
(Name1
);
6342 K2
: constant Node_Kind
:= Nkind
(Name2
);
6344 function Prefix_Node
(N
: Node_Id
) return Node_Id
;
6345 -- Returns the parent unit name node of a defining program unit name
6346 -- or the prefix if N is a selected component or an expanded name.
6348 function Select_Node
(N
: Node_Id
) return Node_Id
;
6349 -- Returns the defining identifier node of a defining program unit
6350 -- name or the selector node if N is a selected component or an
6357 function Prefix_Node
(N
: Node_Id
) return Node_Id
is
6359 if Nkind
(N
) = N_Defining_Program_Unit_Name
then
6370 function Select_Node
(N
: Node_Id
) return Node_Id
is
6372 if Nkind
(N
) = N_Defining_Program_Unit_Name
then
6373 return Defining_Identifier
(N
);
6375 return Selector_Name
(N
);
6379 -- Start of processing for Designate_Same_Unit
6382 if Nkind_In
(K1
, N_Identifier
, N_Defining_Identifier
)
6384 Nkind_In
(K2
, N_Identifier
, N_Defining_Identifier
)
6386 return Chars
(Name1
) = Chars
(Name2
);
6388 elsif Nkind_In
(K1
, N_Expanded_Name
,
6389 N_Selected_Component
,
6390 N_Defining_Program_Unit_Name
)
6392 Nkind_In
(K2
, N_Expanded_Name
,
6393 N_Selected_Component
,
6394 N_Defining_Program_Unit_Name
)
6397 (Chars
(Select_Node
(Name1
)) = Chars
(Select_Node
(Name2
)))
6399 Designate_Same_Unit
(Prefix_Node
(Name1
), Prefix_Node
(Name2
));
6404 end Designate_Same_Unit
;
6406 ---------------------------------------------
6407 -- Diagnose_Iterated_Component_Association --
6408 ---------------------------------------------
6410 procedure Diagnose_Iterated_Component_Association
(N
: Node_Id
) is
6411 Def_Id
: constant Entity_Id
:= Defining_Identifier
(N
);
6415 -- Determine whether the iterated component association appears within
6416 -- an aggregate. If this is the case, raise Program_Error because the
6417 -- iterated component association cannot be left in the tree as is and
6418 -- must always be processed by the related aggregate.
6421 while Present
(Aggr
) loop
6422 if Nkind
(Aggr
) = N_Aggregate
then
6423 raise Program_Error
;
6425 -- Prevent the search from going too far
6427 elsif Is_Body_Or_Package_Declaration
(Aggr
) then
6431 Aggr
:= Parent
(Aggr
);
6434 -- At this point it is known that the iterated component association is
6435 -- not within an aggregate. This is really a quantified expression with
6436 -- a missing "all" or "some" quantifier.
6438 Error_Msg_N
("missing quantifier", Def_Id
);
6440 -- Rewrite the iterated component association as True to prevent any
6443 Rewrite
(N
, New_Occurrence_Of
(Standard_True
, Sloc
(N
)));
6445 end Diagnose_Iterated_Component_Association
;
6447 ---------------------------------
6448 -- Dynamic_Accessibility_Level --
6449 ---------------------------------
6451 function Dynamic_Accessibility_Level
(Expr
: Node_Id
) return Node_Id
is
6452 Loc
: constant Source_Ptr
:= Sloc
(Expr
);
6454 function Make_Level_Literal
(Level
: Uint
) return Node_Id
;
6455 -- Construct an integer literal representing an accessibility level
6456 -- with its type set to Natural.
6458 ------------------------
6459 -- Make_Level_Literal --
6460 ------------------------
6462 function Make_Level_Literal
(Level
: Uint
) return Node_Id
is
6463 Result
: constant Node_Id
:= Make_Integer_Literal
(Loc
, Level
);
6466 Set_Etype
(Result
, Standard_Natural
);
6468 end Make_Level_Literal
;
6474 -- Start of processing for Dynamic_Accessibility_Level
6477 if Is_Entity_Name
(Expr
) then
6480 if Present
(Renamed_Object
(E
)) then
6481 return Dynamic_Accessibility_Level
(Renamed_Object
(E
));
6484 if Is_Formal
(E
) or else Ekind_In
(E
, E_Variable
, E_Constant
) then
6485 if Present
(Extra_Accessibility
(E
)) then
6486 return New_Occurrence_Of
(Extra_Accessibility
(E
), Loc
);
6491 -- Unimplemented: Ptr.all'Access, where Ptr has Extra_Accessibility ???
6493 case Nkind
(Expr
) is
6495 -- For access discriminant, the level of the enclosing object
6497 when N_Selected_Component
=>
6498 if Ekind
(Entity
(Selector_Name
(Expr
))) = E_Discriminant
6499 and then Ekind
(Etype
(Entity
(Selector_Name
(Expr
)))) =
6500 E_Anonymous_Access_Type
6502 return Make_Level_Literal
(Object_Access_Level
(Expr
));
6505 when N_Attribute_Reference
=>
6506 case Get_Attribute_Id
(Attribute_Name
(Expr
)) is
6508 -- For X'Access, the level of the prefix X
6510 when Attribute_Access
=>
6511 return Make_Level_Literal
6512 (Object_Access_Level
(Prefix
(Expr
)));
6514 -- Treat the unchecked attributes as library-level
6516 when Attribute_Unchecked_Access
6517 | Attribute_Unrestricted_Access
6519 return Make_Level_Literal
(Scope_Depth
(Standard_Standard
));
6521 -- No other access-valued attributes
6524 raise Program_Error
;
6529 -- Unimplemented: depends on context. As an actual parameter where
6530 -- formal type is anonymous, use
6531 -- Scope_Depth (Current_Scope) + 1.
6532 -- For other cases, see 3.10.2(14/3) and following. ???
6536 when N_Type_Conversion
=>
6537 if not Is_Local_Anonymous_Access
(Etype
(Expr
)) then
6539 -- Handle type conversions introduced for a rename of an
6540 -- Ada 2012 stand-alone object of an anonymous access type.
6542 return Dynamic_Accessibility_Level
(Expression
(Expr
));
6549 return Make_Level_Literal
(Type_Access_Level
(Etype
(Expr
)));
6550 end Dynamic_Accessibility_Level
;
6552 ------------------------
6553 -- Discriminated_Size --
6554 ------------------------
6556 function Discriminated_Size
(Comp
: Entity_Id
) return Boolean is
6557 function Non_Static_Bound
(Bound
: Node_Id
) return Boolean;
6558 -- Check whether the bound of an index is non-static and does denote
6559 -- a discriminant, in which case any object of the type (protected or
6560 -- otherwise) will have a non-static size.
6562 ----------------------
6563 -- Non_Static_Bound --
6564 ----------------------
6566 function Non_Static_Bound
(Bound
: Node_Id
) return Boolean is
6568 if Is_OK_Static_Expression
(Bound
) then
6571 -- If the bound is given by a discriminant it is non-static
6572 -- (A static constraint replaces the reference with the value).
6573 -- In an protected object the discriminant has been replaced by
6574 -- the corresponding discriminal within the protected operation.
6576 elsif Is_Entity_Name
(Bound
)
6578 (Ekind
(Entity
(Bound
)) = E_Discriminant
6579 or else Present
(Discriminal_Link
(Entity
(Bound
))))
6586 end Non_Static_Bound
;
6590 Typ
: constant Entity_Id
:= Etype
(Comp
);
6593 -- Start of processing for Discriminated_Size
6596 if not Is_Array_Type
(Typ
) then
6600 if Ekind
(Typ
) = E_Array_Subtype
then
6601 Index
:= First_Index
(Typ
);
6602 while Present
(Index
) loop
6603 if Non_Static_Bound
(Low_Bound
(Index
))
6604 or else Non_Static_Bound
(High_Bound
(Index
))
6616 end Discriminated_Size
;
6618 -----------------------------------
6619 -- Effective_Extra_Accessibility --
6620 -----------------------------------
6622 function Effective_Extra_Accessibility
(Id
: Entity_Id
) return Entity_Id
is
6624 if Present
(Renamed_Object
(Id
))
6625 and then Is_Entity_Name
(Renamed_Object
(Id
))
6627 return Effective_Extra_Accessibility
(Entity
(Renamed_Object
(Id
)));
6629 return Extra_Accessibility
(Id
);
6631 end Effective_Extra_Accessibility
;
6633 -----------------------------
6634 -- Effective_Reads_Enabled --
6635 -----------------------------
6637 function Effective_Reads_Enabled
(Id
: Entity_Id
) return Boolean is
6639 return Has_Enabled_Property
(Id
, Name_Effective_Reads
);
6640 end Effective_Reads_Enabled
;
6642 ------------------------------
6643 -- Effective_Writes_Enabled --
6644 ------------------------------
6646 function Effective_Writes_Enabled
(Id
: Entity_Id
) return Boolean is
6648 return Has_Enabled_Property
(Id
, Name_Effective_Writes
);
6649 end Effective_Writes_Enabled
;
6651 ------------------------------
6652 -- Enclosing_Comp_Unit_Node --
6653 ------------------------------
6655 function Enclosing_Comp_Unit_Node
(N
: Node_Id
) return Node_Id
is
6656 Current_Node
: Node_Id
;
6660 while Present
(Current_Node
)
6661 and then Nkind
(Current_Node
) /= N_Compilation_Unit
6663 Current_Node
:= Parent
(Current_Node
);
6666 if Nkind
(Current_Node
) /= N_Compilation_Unit
then
6669 return Current_Node
;
6671 end Enclosing_Comp_Unit_Node
;
6673 --------------------------
6674 -- Enclosing_CPP_Parent --
6675 --------------------------
6677 function Enclosing_CPP_Parent
(Typ
: Entity_Id
) return Entity_Id
is
6678 Parent_Typ
: Entity_Id
:= Typ
;
6681 while not Is_CPP_Class
(Parent_Typ
)
6682 and then Etype
(Parent_Typ
) /= Parent_Typ
6684 Parent_Typ
:= Etype
(Parent_Typ
);
6686 if Is_Private_Type
(Parent_Typ
) then
6687 Parent_Typ
:= Full_View
(Base_Type
(Parent_Typ
));
6691 pragma Assert
(Is_CPP_Class
(Parent_Typ
));
6693 end Enclosing_CPP_Parent
;
6695 ---------------------------
6696 -- Enclosing_Declaration --
6697 ---------------------------
6699 function Enclosing_Declaration
(N
: Node_Id
) return Node_Id
is
6700 Decl
: Node_Id
:= N
;
6703 while Present
(Decl
)
6704 and then not (Nkind
(Decl
) in N_Declaration
6706 Nkind
(Decl
) in N_Later_Decl_Item
)
6708 Decl
:= Parent
(Decl
);
6712 end Enclosing_Declaration
;
6714 ----------------------------
6715 -- Enclosing_Generic_Body --
6716 ----------------------------
6718 function Enclosing_Generic_Body
6719 (N
: Node_Id
) return Node_Id
6727 while Present
(P
) loop
6728 if Nkind
(P
) = N_Package_Body
6729 or else Nkind
(P
) = N_Subprogram_Body
6731 Spec
:= Corresponding_Spec
(P
);
6733 if Present
(Spec
) then
6734 Decl
:= Unit_Declaration_Node
(Spec
);
6736 if Nkind
(Decl
) = N_Generic_Package_Declaration
6737 or else Nkind
(Decl
) = N_Generic_Subprogram_Declaration
6748 end Enclosing_Generic_Body
;
6750 ----------------------------
6751 -- Enclosing_Generic_Unit --
6752 ----------------------------
6754 function Enclosing_Generic_Unit
6755 (N
: Node_Id
) return Node_Id
6763 while Present
(P
) loop
6764 if Nkind
(P
) = N_Generic_Package_Declaration
6765 or else Nkind
(P
) = N_Generic_Subprogram_Declaration
6769 elsif Nkind
(P
) = N_Package_Body
6770 or else Nkind
(P
) = N_Subprogram_Body
6772 Spec
:= Corresponding_Spec
(P
);
6774 if Present
(Spec
) then
6775 Decl
:= Unit_Declaration_Node
(Spec
);
6777 if Nkind
(Decl
) = N_Generic_Package_Declaration
6778 or else Nkind
(Decl
) = N_Generic_Subprogram_Declaration
6789 end Enclosing_Generic_Unit
;
6791 -------------------------------
6792 -- Enclosing_Lib_Unit_Entity --
6793 -------------------------------
6795 function Enclosing_Lib_Unit_Entity
6796 (E
: Entity_Id
:= Current_Scope
) return Entity_Id
6798 Unit_Entity
: Entity_Id
;
6801 -- Look for enclosing library unit entity by following scope links.
6802 -- Equivalent to, but faster than indexing through the scope stack.
6805 while (Present
(Scope
(Unit_Entity
))
6806 and then Scope
(Unit_Entity
) /= Standard_Standard
)
6807 and not Is_Child_Unit
(Unit_Entity
)
6809 Unit_Entity
:= Scope
(Unit_Entity
);
6813 end Enclosing_Lib_Unit_Entity
;
6815 -----------------------------
6816 -- Enclosing_Lib_Unit_Node --
6817 -----------------------------
6819 function Enclosing_Lib_Unit_Node
(N
: Node_Id
) return Node_Id
is
6820 Encl_Unit
: Node_Id
;
6823 Encl_Unit
:= Enclosing_Comp_Unit_Node
(N
);
6824 while Present
(Encl_Unit
)
6825 and then Nkind
(Unit
(Encl_Unit
)) = N_Subunit
6827 Encl_Unit
:= Library_Unit
(Encl_Unit
);
6830 pragma Assert
(Nkind
(Encl_Unit
) = N_Compilation_Unit
);
6832 end Enclosing_Lib_Unit_Node
;
6834 -----------------------
6835 -- Enclosing_Package --
6836 -----------------------
6838 function Enclosing_Package
(E
: Entity_Id
) return Entity_Id
is
6839 Dynamic_Scope
: constant Entity_Id
:= Enclosing_Dynamic_Scope
(E
);
6842 if Dynamic_Scope
= Standard_Standard
then
6843 return Standard_Standard
;
6845 elsif Dynamic_Scope
= Empty
then
6848 elsif Ekind_In
(Dynamic_Scope
, E_Package
, E_Package_Body
,
6851 return Dynamic_Scope
;
6854 return Enclosing_Package
(Dynamic_Scope
);
6856 end Enclosing_Package
;
6858 -------------------------------------
6859 -- Enclosing_Package_Or_Subprogram --
6860 -------------------------------------
6862 function Enclosing_Package_Or_Subprogram
(E
: Entity_Id
) return Entity_Id
is
6867 while Present
(S
) loop
6868 if Is_Package_Or_Generic_Package
(S
)
6869 or else Ekind
(S
) = E_Package_Body
6873 elsif Is_Subprogram_Or_Generic_Subprogram
(S
)
6874 or else Ekind
(S
) = E_Subprogram_Body
6884 end Enclosing_Package_Or_Subprogram
;
6886 --------------------------
6887 -- Enclosing_Subprogram --
6888 --------------------------
6890 function Enclosing_Subprogram
(E
: Entity_Id
) return Entity_Id
is
6891 Dynamic_Scope
: constant Entity_Id
:= Enclosing_Dynamic_Scope
(E
);
6894 if Dynamic_Scope
= Standard_Standard
then
6897 elsif Dynamic_Scope
= Empty
then
6900 elsif Ekind
(Dynamic_Scope
) = E_Subprogram_Body
then
6901 return Corresponding_Spec
(Parent
(Parent
(Dynamic_Scope
)));
6903 elsif Ekind
(Dynamic_Scope
) = E_Block
6904 or else Ekind
(Dynamic_Scope
) = E_Return_Statement
6906 return Enclosing_Subprogram
(Dynamic_Scope
);
6908 elsif Ekind
(Dynamic_Scope
) = E_Task_Type
then
6909 return Get_Task_Body_Procedure
(Dynamic_Scope
);
6911 elsif Ekind
(Dynamic_Scope
) = E_Limited_Private_Type
6912 and then Present
(Full_View
(Dynamic_Scope
))
6913 and then Ekind
(Full_View
(Dynamic_Scope
)) = E_Task_Type
6915 return Get_Task_Body_Procedure
(Full_View
(Dynamic_Scope
));
6917 -- No body is generated if the protected operation is eliminated
6919 elsif Convention
(Dynamic_Scope
) = Convention_Protected
6920 and then not Is_Eliminated
(Dynamic_Scope
)
6921 and then Present
(Protected_Body_Subprogram
(Dynamic_Scope
))
6923 return Protected_Body_Subprogram
(Dynamic_Scope
);
6926 return Dynamic_Scope
;
6928 end Enclosing_Subprogram
;
6930 --------------------------
6931 -- End_Keyword_Location --
6932 --------------------------
6934 function End_Keyword_Location
(N
: Node_Id
) return Source_Ptr
is
6935 function End_Label_Loc
(Nod
: Node_Id
) return Source_Ptr
;
6936 -- Return the source location of Nod's end label according to the
6937 -- following precedence rules:
6939 -- 1) If the end label exists, return its location
6940 -- 2) If Nod exists, return its location
6941 -- 3) Return the location of N
6947 function End_Label_Loc
(Nod
: Node_Id
) return Source_Ptr
is
6951 if Present
(Nod
) then
6952 Label
:= End_Label
(Nod
);
6954 if Present
(Label
) then
6955 return Sloc
(Label
);
6969 -- Start of processing for End_Keyword_Location
6972 if Nkind_In
(N
, N_Block_Statement
,
6978 Owner
:= Handled_Statement_Sequence
(N
);
6980 elsif Nkind
(N
) = N_Package_Declaration
then
6981 Owner
:= Specification
(N
);
6983 elsif Nkind
(N
) = N_Protected_Body
then
6986 elsif Nkind_In
(N
, N_Protected_Type_Declaration
,
6987 N_Single_Protected_Declaration
)
6989 Owner
:= Protected_Definition
(N
);
6991 elsif Nkind_In
(N
, N_Single_Task_Declaration
,
6992 N_Task_Type_Declaration
)
6994 Owner
:= Task_Definition
(N
);
6996 -- This routine should not be called with other contexts
6999 pragma Assert
(False);
7003 return End_Label_Loc
(Owner
);
7004 end End_Keyword_Location
;
7006 ------------------------
7007 -- Ensure_Freeze_Node --
7008 ------------------------
7010 procedure Ensure_Freeze_Node
(E
: Entity_Id
) is
7013 if No
(Freeze_Node
(E
)) then
7014 FN
:= Make_Freeze_Entity
(Sloc
(E
));
7015 Set_Has_Delayed_Freeze
(E
);
7016 Set_Freeze_Node
(E
, FN
);
7017 Set_Access_Types_To_Process
(FN
, No_Elist
);
7018 Set_TSS_Elist
(FN
, No_Elist
);
7021 end Ensure_Freeze_Node
;
7027 procedure Enter_Name
(Def_Id
: Entity_Id
) is
7028 C
: constant Entity_Id
:= Current_Entity
(Def_Id
);
7029 E
: constant Entity_Id
:= Current_Entity_In_Scope
(Def_Id
);
7030 S
: constant Entity_Id
:= Current_Scope
;
7033 Generate_Definition
(Def_Id
);
7035 -- Add new name to current scope declarations. Check for duplicate
7036 -- declaration, which may or may not be a genuine error.
7040 -- Case of previous entity entered because of a missing declaration
7041 -- or else a bad subtype indication. Best is to use the new entity,
7042 -- and make the previous one invisible.
7044 if Etype
(E
) = Any_Type
then
7045 Set_Is_Immediately_Visible
(E
, False);
7047 -- Case of renaming declaration constructed for package instances.
7048 -- if there is an explicit declaration with the same identifier,
7049 -- the renaming is not immediately visible any longer, but remains
7050 -- visible through selected component notation.
7052 elsif Nkind
(Parent
(E
)) = N_Package_Renaming_Declaration
7053 and then not Comes_From_Source
(E
)
7055 Set_Is_Immediately_Visible
(E
, False);
7057 -- The new entity may be the package renaming, which has the same
7058 -- same name as a generic formal which has been seen already.
7060 elsif Nkind
(Parent
(Def_Id
)) = N_Package_Renaming_Declaration
7061 and then not Comes_From_Source
(Def_Id
)
7063 Set_Is_Immediately_Visible
(E
, False);
7065 -- For a fat pointer corresponding to a remote access to subprogram,
7066 -- we use the same identifier as the RAS type, so that the proper
7067 -- name appears in the stub. This type is only retrieved through
7068 -- the RAS type and never by visibility, and is not added to the
7069 -- visibility list (see below).
7071 elsif Nkind
(Parent
(Def_Id
)) = N_Full_Type_Declaration
7072 and then Ekind
(Def_Id
) = E_Record_Type
7073 and then Present
(Corresponding_Remote_Type
(Def_Id
))
7077 -- Case of an implicit operation or derived literal. The new entity
7078 -- hides the implicit one, which is removed from all visibility,
7079 -- i.e. the entity list of its scope, and homonym chain of its name.
7081 elsif (Is_Overloadable
(E
) and then Is_Inherited_Operation
(E
))
7082 or else Is_Internal
(E
)
7085 Decl
: constant Node_Id
:= Parent
(E
);
7087 Prev_Vis
: Entity_Id
;
7090 -- If E is an implicit declaration, it cannot be the first
7091 -- entity in the scope.
7093 Prev
:= First_Entity
(Current_Scope
);
7094 while Present
(Prev
) and then Next_Entity
(Prev
) /= E
loop
7100 -- If E is not on the entity chain of the current scope,
7101 -- it is an implicit declaration in the generic formal
7102 -- part of a generic subprogram. When analyzing the body,
7103 -- the generic formals are visible but not on the entity
7104 -- chain of the subprogram. The new entity will become
7105 -- the visible one in the body.
7108 (Nkind
(Parent
(Decl
)) = N_Generic_Subprogram_Declaration
);
7112 Set_Next_Entity
(Prev
, Next_Entity
(E
));
7114 if No
(Next_Entity
(Prev
)) then
7115 Set_Last_Entity
(Current_Scope
, Prev
);
7118 if E
= Current_Entity
(E
) then
7122 Prev_Vis
:= Current_Entity
(E
);
7123 while Homonym
(Prev_Vis
) /= E
loop
7124 Prev_Vis
:= Homonym
(Prev_Vis
);
7128 if Present
(Prev_Vis
) then
7130 -- Skip E in the visibility chain
7132 Set_Homonym
(Prev_Vis
, Homonym
(E
));
7135 Set_Name_Entity_Id
(Chars
(E
), Homonym
(E
));
7140 -- This section of code could use a comment ???
7142 elsif Present
(Etype
(E
))
7143 and then Is_Concurrent_Type
(Etype
(E
))
7148 -- If the homograph is a protected component renaming, it should not
7149 -- be hiding the current entity. Such renamings are treated as weak
7152 elsif Is_Prival
(E
) then
7153 Set_Is_Immediately_Visible
(E
, False);
7155 -- In this case the current entity is a protected component renaming.
7156 -- Perform minimal decoration by setting the scope and return since
7157 -- the prival should not be hiding other visible entities.
7159 elsif Is_Prival
(Def_Id
) then
7160 Set_Scope
(Def_Id
, Current_Scope
);
7163 -- Analogous to privals, the discriminal generated for an entry index
7164 -- parameter acts as a weak declaration. Perform minimal decoration
7165 -- to avoid bogus errors.
7167 elsif Is_Discriminal
(Def_Id
)
7168 and then Ekind
(Discriminal_Link
(Def_Id
)) = E_Entry_Index_Parameter
7170 Set_Scope
(Def_Id
, Current_Scope
);
7173 -- In the body or private part of an instance, a type extension may
7174 -- introduce a component with the same name as that of an actual. The
7175 -- legality rule is not enforced, but the semantics of the full type
7176 -- with two components of same name are not clear at this point???
7178 elsif In_Instance_Not_Visible
then
7181 -- When compiling a package body, some child units may have become
7182 -- visible. They cannot conflict with local entities that hide them.
7184 elsif Is_Child_Unit
(E
)
7185 and then In_Open_Scopes
(Scope
(E
))
7186 and then not Is_Immediately_Visible
(E
)
7190 -- Conversely, with front-end inlining we may compile the parent body
7191 -- first, and a child unit subsequently. The context is now the
7192 -- parent spec, and body entities are not visible.
7194 elsif Is_Child_Unit
(Def_Id
)
7195 and then Is_Package_Body_Entity
(E
)
7196 and then not In_Package_Body
(Current_Scope
)
7200 -- Case of genuine duplicate declaration
7203 Error_Msg_Sloc
:= Sloc
(E
);
7205 -- If the previous declaration is an incomplete type declaration
7206 -- this may be an attempt to complete it with a private type. The
7207 -- following avoids confusing cascaded errors.
7209 if Nkind
(Parent
(E
)) = N_Incomplete_Type_Declaration
7210 and then Nkind
(Parent
(Def_Id
)) = N_Private_Type_Declaration
7213 ("incomplete type cannot be completed with a private " &
7214 "declaration", Parent
(Def_Id
));
7215 Set_Is_Immediately_Visible
(E
, False);
7216 Set_Full_View
(E
, Def_Id
);
7218 -- An inherited component of a record conflicts with a new
7219 -- discriminant. The discriminant is inserted first in the scope,
7220 -- but the error should be posted on it, not on the component.
7222 elsif Ekind
(E
) = E_Discriminant
7223 and then Present
(Scope
(Def_Id
))
7224 and then Scope
(Def_Id
) /= Current_Scope
7226 Error_Msg_Sloc
:= Sloc
(Def_Id
);
7227 Error_Msg_N
("& conflicts with declaration#", E
);
7230 -- If the name of the unit appears in its own context clause, a
7231 -- dummy package with the name has already been created, and the
7232 -- error emitted. Try to continue quietly.
7234 elsif Error_Posted
(E
)
7235 and then Sloc
(E
) = No_Location
7236 and then Nkind
(Parent
(E
)) = N_Package_Specification
7237 and then Current_Scope
= Standard_Standard
7239 Set_Scope
(Def_Id
, Current_Scope
);
7243 Error_Msg_N
("& conflicts with declaration#", Def_Id
);
7245 -- Avoid cascaded messages with duplicate components in
7248 if Ekind_In
(E
, E_Component
, E_Discriminant
) then
7253 if Nkind
(Parent
(Parent
(Def_Id
))) =
7254 N_Generic_Subprogram_Declaration
7256 Defining_Entity
(Specification
(Parent
(Parent
(Def_Id
))))
7258 Error_Msg_N
("\generic units cannot be overloaded", Def_Id
);
7261 -- If entity is in standard, then we are in trouble, because it
7262 -- means that we have a library package with a duplicated name.
7263 -- That's hard to recover from, so abort.
7265 if S
= Standard_Standard
then
7266 raise Unrecoverable_Error
;
7268 -- Otherwise we continue with the declaration. Having two
7269 -- identical declarations should not cause us too much trouble.
7277 -- If we fall through, declaration is OK, at least OK enough to continue
7279 -- If Def_Id is a discriminant or a record component we are in the midst
7280 -- of inheriting components in a derived record definition. Preserve
7281 -- their Ekind and Etype.
7283 if Ekind_In
(Def_Id
, E_Discriminant
, E_Component
) then
7286 -- If a type is already set, leave it alone (happens when a type
7287 -- declaration is reanalyzed following a call to the optimizer).
7289 elsif Present
(Etype
(Def_Id
)) then
7292 -- Otherwise, the kind E_Void insures that premature uses of the entity
7293 -- will be detected. Any_Type insures that no cascaded errors will occur
7296 Set_Ekind
(Def_Id
, E_Void
);
7297 Set_Etype
(Def_Id
, Any_Type
);
7300 -- Inherited discriminants and components in derived record types are
7301 -- immediately visible. Itypes are not.
7303 -- Unless the Itype is for a record type with a corresponding remote
7304 -- type (what is that about, it was not commented ???)
7306 if Ekind_In
(Def_Id
, E_Discriminant
, E_Component
)
7308 ((not Is_Record_Type
(Def_Id
)
7309 or else No
(Corresponding_Remote_Type
(Def_Id
)))
7310 and then not Is_Itype
(Def_Id
))
7312 Set_Is_Immediately_Visible
(Def_Id
);
7313 Set_Current_Entity
(Def_Id
);
7316 Set_Homonym
(Def_Id
, C
);
7317 Append_Entity
(Def_Id
, S
);
7318 Set_Public_Status
(Def_Id
);
7320 -- Declaring a homonym is not allowed in SPARK ...
7322 if Present
(C
) and then Restriction_Check_Required
(SPARK_05
) then
7324 Enclosing_Subp
: constant Node_Id
:= Enclosing_Subprogram
(Def_Id
);
7325 Enclosing_Pack
: constant Node_Id
:= Enclosing_Package
(Def_Id
);
7326 Other_Scope
: constant Node_Id
:= Enclosing_Dynamic_Scope
(C
);
7329 -- ... unless the new declaration is in a subprogram, and the
7330 -- visible declaration is a variable declaration or a parameter
7331 -- specification outside that subprogram.
7333 if Present
(Enclosing_Subp
)
7334 and then Nkind_In
(Parent
(C
), N_Object_Declaration
,
7335 N_Parameter_Specification
)
7336 and then not Scope_Within_Or_Same
(Other_Scope
, Enclosing_Subp
)
7340 -- ... or the new declaration is in a package, and the visible
7341 -- declaration occurs outside that package.
7343 elsif Present
(Enclosing_Pack
)
7344 and then not Scope_Within_Or_Same
(Other_Scope
, Enclosing_Pack
)
7348 -- ... or the new declaration is a component declaration in a
7349 -- record type definition.
7351 elsif Nkind
(Parent
(Def_Id
)) = N_Component_Declaration
then
7354 -- Don't issue error for non-source entities
7356 elsif Comes_From_Source
(Def_Id
)
7357 and then Comes_From_Source
(C
)
7359 Error_Msg_Sloc
:= Sloc
(C
);
7360 Check_SPARK_05_Restriction
7361 ("redeclaration of identifier &#", Def_Id
);
7366 -- Warn if new entity hides an old one
7368 if Warn_On_Hiding
and then Present
(C
)
7370 -- Don't warn for record components since they always have a well
7371 -- defined scope which does not confuse other uses. Note that in
7372 -- some cases, Ekind has not been set yet.
7374 and then Ekind
(C
) /= E_Component
7375 and then Ekind
(C
) /= E_Discriminant
7376 and then Nkind
(Parent
(C
)) /= N_Component_Declaration
7377 and then Ekind
(Def_Id
) /= E_Component
7378 and then Ekind
(Def_Id
) /= E_Discriminant
7379 and then Nkind
(Parent
(Def_Id
)) /= N_Component_Declaration
7381 -- Don't warn for one character variables. It is too common to use
7382 -- such variables as locals and will just cause too many false hits.
7384 and then Length_Of_Name
(Chars
(C
)) /= 1
7386 -- Don't warn for non-source entities
7388 and then Comes_From_Source
(C
)
7389 and then Comes_From_Source
(Def_Id
)
7391 -- Don't warn unless entity in question is in extended main source
7393 and then In_Extended_Main_Source_Unit
(Def_Id
)
7395 -- Finally, the hidden entity must be either immediately visible or
7396 -- use visible (i.e. from a used package).
7399 (Is_Immediately_Visible
(C
)
7401 Is_Potentially_Use_Visible
(C
))
7403 Error_Msg_Sloc
:= Sloc
(C
);
7404 Error_Msg_N
("declaration hides &#?h?", Def_Id
);
7412 function Entity_Of
(N
: Node_Id
) return Entity_Id
is
7417 -- Assume that the arbitrary node does not have an entity
7421 if Is_Entity_Name
(N
) then
7424 -- Follow a possible chain of renamings to reach the earliest renamed
7428 and then Is_Object
(Id
)
7429 and then Present
(Renamed_Object
(Id
))
7431 Ren
:= Renamed_Object
(Id
);
7433 -- The reference renames an abstract state or a whole object
7436 -- Ren : ... renames Obj;
7438 if Is_Entity_Name
(Ren
) then
7441 -- The reference renames a function result. Check the original
7442 -- node in case expansion relocates the function call.
7444 -- Ren : ... renames Func_Call;
7446 elsif Nkind
(Original_Node
(Ren
)) = N_Function_Call
then
7449 -- Otherwise the reference renames something which does not yield
7450 -- an abstract state or a whole object. Treat the reference as not
7451 -- having a proper entity for SPARK legality purposes.
7463 --------------------------
7464 -- Explain_Limited_Type --
7465 --------------------------
7467 procedure Explain_Limited_Type
(T
: Entity_Id
; N
: Node_Id
) is
7471 -- For array, component type must be limited
7473 if Is_Array_Type
(T
) then
7474 Error_Msg_Node_2
:= T
;
7476 ("\component type& of type& is limited", N
, Component_Type
(T
));
7477 Explain_Limited_Type
(Component_Type
(T
), N
);
7479 elsif Is_Record_Type
(T
) then
7481 -- No need for extra messages if explicit limited record
7483 if Is_Limited_Record
(Base_Type
(T
)) then
7487 -- Otherwise find a limited component. Check only components that
7488 -- come from source, or inherited components that appear in the
7489 -- source of the ancestor.
7491 C
:= First_Component
(T
);
7492 while Present
(C
) loop
7493 if Is_Limited_Type
(Etype
(C
))
7495 (Comes_From_Source
(C
)
7497 (Present
(Original_Record_Component
(C
))
7499 Comes_From_Source
(Original_Record_Component
(C
))))
7501 Error_Msg_Node_2
:= T
;
7502 Error_Msg_NE
("\component& of type& has limited type", N
, C
);
7503 Explain_Limited_Type
(Etype
(C
), N
);
7510 -- The type may be declared explicitly limited, even if no component
7511 -- of it is limited, in which case we fall out of the loop.
7514 end Explain_Limited_Type
;
7516 ---------------------------------------
7517 -- Expression_Of_Expression_Function --
7518 ---------------------------------------
7520 function Expression_Of_Expression_Function
7521 (Subp
: Entity_Id
) return Node_Id
7523 Expr_Func
: Node_Id
;
7526 pragma Assert
(Is_Expression_Function_Or_Completion
(Subp
));
7528 if Nkind
(Original_Node
(Subprogram_Spec
(Subp
))) =
7529 N_Expression_Function
7531 Expr_Func
:= Original_Node
(Subprogram_Spec
(Subp
));
7533 elsif Nkind
(Original_Node
(Subprogram_Body
(Subp
))) =
7534 N_Expression_Function
7536 Expr_Func
:= Original_Node
(Subprogram_Body
(Subp
));
7539 pragma Assert
(False);
7543 return Original_Node
(Expression
(Expr_Func
));
7544 end Expression_Of_Expression_Function
;
7546 -------------------------------
7547 -- Extensions_Visible_Status --
7548 -------------------------------
7550 function Extensions_Visible_Status
7551 (Id
: Entity_Id
) return Extensions_Visible_Mode
7560 -- When a formal parameter is subject to Extensions_Visible, the pragma
7561 -- is stored in the contract of related subprogram.
7563 if Is_Formal
(Id
) then
7566 elsif Is_Subprogram_Or_Generic_Subprogram
(Id
) then
7569 -- No other construct carries this pragma
7572 return Extensions_Visible_None
;
7575 Prag
:= Get_Pragma
(Subp
, Pragma_Extensions_Visible
);
7577 -- In certain cases analysis may request the Extensions_Visible status
7578 -- of an expression function before the pragma has been analyzed yet.
7579 -- Inspect the declarative items after the expression function looking
7580 -- for the pragma (if any).
7582 if No
(Prag
) and then Is_Expression_Function
(Subp
) then
7583 Decl
:= Next
(Unit_Declaration_Node
(Subp
));
7584 while Present
(Decl
) loop
7585 if Nkind
(Decl
) = N_Pragma
7586 and then Pragma_Name
(Decl
) = Name_Extensions_Visible
7591 -- A source construct ends the region where Extensions_Visible may
7592 -- appear, stop the traversal. An expanded expression function is
7593 -- no longer a source construct, but it must still be recognized.
7595 elsif Comes_From_Source
(Decl
)
7597 (Nkind_In
(Decl
, N_Subprogram_Body
,
7598 N_Subprogram_Declaration
)
7599 and then Is_Expression_Function
(Defining_Entity
(Decl
)))
7608 -- Extract the value from the Boolean expression (if any)
7610 if Present
(Prag
) then
7611 Arg
:= First
(Pragma_Argument_Associations
(Prag
));
7613 if Present
(Arg
) then
7614 Expr
:= Get_Pragma_Arg
(Arg
);
7616 -- When the associated subprogram is an expression function, the
7617 -- argument of the pragma may not have been analyzed.
7619 if not Analyzed
(Expr
) then
7620 Preanalyze_And_Resolve
(Expr
, Standard_Boolean
);
7623 -- Guard against cascading errors when the argument of pragma
7624 -- Extensions_Visible is not a valid static Boolean expression.
7626 if Error_Posted
(Expr
) then
7627 return Extensions_Visible_None
;
7629 elsif Is_True
(Expr_Value
(Expr
)) then
7630 return Extensions_Visible_True
;
7633 return Extensions_Visible_False
;
7636 -- Otherwise the aspect or pragma defaults to True
7639 return Extensions_Visible_True
;
7642 -- Otherwise aspect or pragma Extensions_Visible is not inherited or
7643 -- directly specified. In SPARK code, its value defaults to "False".
7645 elsif SPARK_Mode
= On
then
7646 return Extensions_Visible_False
;
7648 -- In non-SPARK code, aspect or pragma Extensions_Visible defaults to
7652 return Extensions_Visible_True
;
7654 end Extensions_Visible_Status
;
7660 procedure Find_Actual
7662 Formal
: out Entity_Id
;
7665 Context
: constant Node_Id
:= Parent
(N
);
7670 if Nkind_In
(Context
, N_Indexed_Component
, N_Selected_Component
)
7671 and then N
= Prefix
(Context
)
7673 Find_Actual
(Context
, Formal
, Call
);
7676 elsif Nkind
(Context
) = N_Parameter_Association
7677 and then N
= Explicit_Actual_Parameter
(Context
)
7679 Call
:= Parent
(Context
);
7681 elsif Nkind_In
(Context
, N_Entry_Call_Statement
,
7683 N_Procedure_Call_Statement
)
7693 -- If we have a call to a subprogram look for the parameter. Note that
7694 -- we exclude overloaded calls, since we don't know enough to be sure
7695 -- of giving the right answer in this case.
7697 if Nkind_In
(Call
, N_Entry_Call_Statement
,
7699 N_Procedure_Call_Statement
)
7701 Call_Nam
:= Name
(Call
);
7703 -- A call to a protected or task entry appears as a selected
7704 -- component rather than an expanded name.
7706 if Nkind
(Call_Nam
) = N_Selected_Component
then
7707 Call_Nam
:= Selector_Name
(Call_Nam
);
7710 if Is_Entity_Name
(Call_Nam
)
7711 and then Present
(Entity
(Call_Nam
))
7712 and then Is_Overloadable
(Entity
(Call_Nam
))
7713 and then not Is_Overloaded
(Call_Nam
)
7715 -- If node is name in call it is not an actual
7717 if N
= Call_Nam
then
7723 -- Fall here if we are definitely a parameter
7725 Actual
:= First_Actual
(Call
);
7726 Formal
:= First_Formal
(Entity
(Call_Nam
));
7727 while Present
(Formal
) and then Present
(Actual
) loop
7731 -- An actual that is the prefix in a prefixed call may have
7732 -- been rewritten in the call, after the deferred reference
7733 -- was collected. Check if sloc and kinds and names match.
7735 elsif Sloc
(Actual
) = Sloc
(N
)
7736 and then Nkind
(Actual
) = N_Identifier
7737 and then Nkind
(Actual
) = Nkind
(N
)
7738 and then Chars
(Actual
) = Chars
(N
)
7743 Actual
:= Next_Actual
(Actual
);
7744 Formal
:= Next_Formal
(Formal
);
7750 -- Fall through here if we did not find matching actual
7756 ---------------------------
7757 -- Find_Body_Discriminal --
7758 ---------------------------
7760 function Find_Body_Discriminal
7761 (Spec_Discriminant
: Entity_Id
) return Entity_Id
7767 -- If expansion is suppressed, then the scope can be the concurrent type
7768 -- itself rather than a corresponding concurrent record type.
7770 if Is_Concurrent_Type
(Scope
(Spec_Discriminant
)) then
7771 Tsk
:= Scope
(Spec_Discriminant
);
7774 pragma Assert
(Is_Concurrent_Record_Type
(Scope
(Spec_Discriminant
)));
7776 Tsk
:= Corresponding_Concurrent_Type
(Scope
(Spec_Discriminant
));
7779 -- Find discriminant of original concurrent type, and use its current
7780 -- discriminal, which is the renaming within the task/protected body.
7782 Disc
:= First_Discriminant
(Tsk
);
7783 while Present
(Disc
) loop
7784 if Chars
(Disc
) = Chars
(Spec_Discriminant
) then
7785 return Discriminal
(Disc
);
7788 Next_Discriminant
(Disc
);
7791 -- That loop should always succeed in finding a matching entry and
7792 -- returning. Fatal error if not.
7794 raise Program_Error
;
7795 end Find_Body_Discriminal
;
7797 -------------------------------------
7798 -- Find_Corresponding_Discriminant --
7799 -------------------------------------
7801 function Find_Corresponding_Discriminant
7803 Typ
: Entity_Id
) return Entity_Id
7805 Par_Disc
: Entity_Id
;
7806 Old_Disc
: Entity_Id
;
7807 New_Disc
: Entity_Id
;
7810 Par_Disc
:= Original_Record_Component
(Original_Discriminant
(Id
));
7812 -- The original type may currently be private, and the discriminant
7813 -- only appear on its full view.
7815 if Is_Private_Type
(Scope
(Par_Disc
))
7816 and then not Has_Discriminants
(Scope
(Par_Disc
))
7817 and then Present
(Full_View
(Scope
(Par_Disc
)))
7819 Old_Disc
:= First_Discriminant
(Full_View
(Scope
(Par_Disc
)));
7821 Old_Disc
:= First_Discriminant
(Scope
(Par_Disc
));
7824 if Is_Class_Wide_Type
(Typ
) then
7825 New_Disc
:= First_Discriminant
(Root_Type
(Typ
));
7827 New_Disc
:= First_Discriminant
(Typ
);
7830 while Present
(Old_Disc
) and then Present
(New_Disc
) loop
7831 if Old_Disc
= Par_Disc
then
7835 Next_Discriminant
(Old_Disc
);
7836 Next_Discriminant
(New_Disc
);
7839 -- Should always find it
7841 raise Program_Error
;
7842 end Find_Corresponding_Discriminant
;
7848 function Find_DIC_Type
(Typ
: Entity_Id
) return Entity_Id
is
7849 Curr_Typ
: Entity_Id
;
7850 -- The current type being examined in the parent hierarchy traversal
7852 DIC_Typ
: Entity_Id
;
7853 -- The type which carries the DIC pragma. This variable denotes the
7854 -- partial view when private types are involved.
7856 Par_Typ
: Entity_Id
;
7857 -- The parent type of the current type. This variable denotes the full
7858 -- view when private types are involved.
7861 -- The input type defines its own DIC pragma, therefore it is the owner
7863 if Has_Own_DIC
(Typ
) then
7866 -- Otherwise the DIC pragma is inherited from a parent type
7869 pragma Assert
(Has_Inherited_DIC
(Typ
));
7871 -- Climb the parent chain
7875 -- Inspect the parent type. Do not consider subtypes as they
7876 -- inherit the DIC attributes from their base types.
7878 DIC_Typ
:= Base_Type
(Etype
(Curr_Typ
));
7880 -- Look at the full view of a private type because the type may
7881 -- have a hidden parent introduced in the full view.
7885 if Is_Private_Type
(Par_Typ
)
7886 and then Present
(Full_View
(Par_Typ
))
7888 Par_Typ
:= Full_View
(Par_Typ
);
7891 -- Stop the climb once the nearest parent type which defines a DIC
7892 -- pragma of its own is encountered or when the root of the parent
7893 -- chain is reached.
7895 exit when Has_Own_DIC
(DIC_Typ
) or else Curr_Typ
= Par_Typ
;
7897 Curr_Typ
:= Par_Typ
;
7904 ----------------------------------
7905 -- Find_Enclosing_Iterator_Loop --
7906 ----------------------------------
7908 function Find_Enclosing_Iterator_Loop
(Id
: Entity_Id
) return Entity_Id
is
7913 -- Traverse the scope chain looking for an iterator loop. Such loops are
7914 -- usually transformed into blocks, hence the use of Original_Node.
7917 while Present
(S
) and then S
/= Standard_Standard
loop
7918 if Ekind
(S
) = E_Loop
7919 and then Nkind
(Parent
(S
)) = N_Implicit_Label_Declaration
7921 Constr
:= Original_Node
(Label_Construct
(Parent
(S
)));
7923 if Nkind
(Constr
) = N_Loop_Statement
7924 and then Present
(Iteration_Scheme
(Constr
))
7925 and then Nkind
(Iterator_Specification
7926 (Iteration_Scheme
(Constr
))) =
7927 N_Iterator_Specification
7937 end Find_Enclosing_Iterator_Loop
;
7939 --------------------------
7940 -- Find_Enclosing_Scope --
7941 --------------------------
7943 function Find_Enclosing_Scope
(N
: Node_Id
) return Entity_Id
is
7945 Spec_Id
: Entity_Id
;
7948 -- Examine the parent chain looking for a construct which defines a
7952 while Present
(Par
) loop
7955 -- The construct denotes a declaration, the proper scope is its
7958 when N_Entry_Declaration
7959 | N_Expression_Function
7960 | N_Full_Type_Declaration
7961 | N_Generic_Package_Declaration
7962 | N_Generic_Subprogram_Declaration
7963 | N_Package_Declaration
7964 | N_Private_Extension_Declaration
7965 | N_Protected_Type_Declaration
7966 | N_Single_Protected_Declaration
7967 | N_Single_Task_Declaration
7968 | N_Subprogram_Declaration
7969 | N_Task_Type_Declaration
7971 return Defining_Entity
(Par
);
7973 -- The construct denotes a body, the proper scope is the entity of
7974 -- the corresponding spec.
7982 Spec_Id
:= Corresponding_Spec
(Par
);
7984 -- The defining entity of a stand-alone subprogram body defines
7987 if Nkind
(Par
) = N_Subprogram_Body
and then No
(Spec_Id
) then
7988 return Defining_Entity
(Par
);
7990 -- Otherwise there should be corresponding spec which defines a
7994 pragma Assert
(Present
(Spec_Id
));
8001 -- Blocks carry either a source or an internally-generated scope,
8002 -- unless the block is a byproduct of exception handling.
8004 when N_Block_Statement
=>
8005 if not Exception_Junk
(Par
) then
8006 return Entity
(Identifier
(Par
));
8009 -- Loops carry an internally-generated scope
8011 when N_Loop_Statement
=>
8012 return Entity
(Identifier
(Par
));
8014 -- Extended return statements carry an internally-generated scope
8016 when N_Extended_Return_Statement
=>
8017 return Return_Statement_Entity
(Par
);
8019 -- A traversal from a subunit continues via the corresponding stub
8022 Par
:= Corresponding_Stub
(Par
);
8028 Par
:= Parent
(Par
);
8031 return Standard_Standard
;
8032 end Find_Enclosing_Scope
;
8034 ------------------------------------
8035 -- Find_Loop_In_Conditional_Block --
8036 ------------------------------------
8038 function Find_Loop_In_Conditional_Block
(N
: Node_Id
) return Node_Id
is
8044 if Nkind
(Stmt
) = N_If_Statement
then
8045 Stmt
:= First
(Then_Statements
(Stmt
));
8048 pragma Assert
(Nkind
(Stmt
) = N_Block_Statement
);
8050 -- Inspect the statements of the conditional block. In general the loop
8051 -- should be the first statement in the statement sequence of the block,
8052 -- but the finalization machinery may have introduced extra object
8055 Stmt
:= First
(Statements
(Handled_Statement_Sequence
(Stmt
)));
8056 while Present
(Stmt
) loop
8057 if Nkind
(Stmt
) = N_Loop_Statement
then
8064 -- The expansion of attribute 'Loop_Entry produced a malformed block
8066 raise Program_Error
;
8067 end Find_Loop_In_Conditional_Block
;
8069 --------------------------
8070 -- Find_Overlaid_Entity --
8071 --------------------------
8073 procedure Find_Overlaid_Entity
8075 Ent
: out Entity_Id
;
8081 -- We are looking for one of the two following forms:
8083 -- for X'Address use Y'Address
8087 -- Const : constant Address := expr;
8089 -- for X'Address use Const;
8091 -- In the second case, the expr is either Y'Address, or recursively a
8092 -- constant that eventually references Y'Address.
8097 if Nkind
(N
) = N_Attribute_Definition_Clause
8098 and then Chars
(N
) = Name_Address
8100 Expr
:= Expression
(N
);
8102 -- This loop checks the form of the expression for Y'Address,
8103 -- using recursion to deal with intermediate constants.
8106 -- Check for Y'Address
8108 if Nkind
(Expr
) = N_Attribute_Reference
8109 and then Attribute_Name
(Expr
) = Name_Address
8111 Expr
:= Prefix
(Expr
);
8114 -- Check for Const where Const is a constant entity
8116 elsif Is_Entity_Name
(Expr
)
8117 and then Ekind
(Entity
(Expr
)) = E_Constant
8119 Expr
:= Constant_Value
(Entity
(Expr
));
8121 -- Anything else does not need checking
8128 -- This loop checks the form of the prefix for an entity, using
8129 -- recursion to deal with intermediate components.
8132 -- Check for Y where Y is an entity
8134 if Is_Entity_Name
(Expr
) then
8135 Ent
:= Entity
(Expr
);
8138 -- Check for components
8141 Nkind_In
(Expr
, N_Selected_Component
, N_Indexed_Component
)
8143 Expr
:= Prefix
(Expr
);
8146 -- Anything else does not need checking
8153 end Find_Overlaid_Entity
;
8155 -------------------------
8156 -- Find_Parameter_Type --
8157 -------------------------
8159 function Find_Parameter_Type
(Param
: Node_Id
) return Entity_Id
is
8161 if Nkind
(Param
) /= N_Parameter_Specification
then
8164 -- For an access parameter, obtain the type from the formal entity
8165 -- itself, because access to subprogram nodes do not carry a type.
8166 -- Shouldn't we always use the formal entity ???
8168 elsif Nkind
(Parameter_Type
(Param
)) = N_Access_Definition
then
8169 return Etype
(Defining_Identifier
(Param
));
8172 return Etype
(Parameter_Type
(Param
));
8174 end Find_Parameter_Type
;
8176 -----------------------------------
8177 -- Find_Placement_In_State_Space --
8178 -----------------------------------
8180 procedure Find_Placement_In_State_Space
8181 (Item_Id
: Entity_Id
;
8182 Placement
: out State_Space_Kind
;
8183 Pack_Id
: out Entity_Id
)
8185 Context
: Entity_Id
;
8188 -- Assume that the item does not appear in the state space of a package
8190 Placement
:= Not_In_Package
;
8193 -- Climb the scope stack and examine the enclosing context
8195 Context
:= Scope
(Item_Id
);
8196 while Present
(Context
) and then Context
/= Standard_Standard
loop
8197 if Is_Package_Or_Generic_Package
(Context
) then
8200 -- A package body is a cut off point for the traversal as the item
8201 -- cannot be visible to the outside from this point on. Note that
8202 -- this test must be done first as a body is also classified as a
8205 if In_Package_Body
(Context
) then
8206 Placement
:= Body_State_Space
;
8209 -- The private part of a package is a cut off point for the
8210 -- traversal as the item cannot be visible to the outside from
8213 elsif In_Private_Part
(Context
) then
8214 Placement
:= Private_State_Space
;
8217 -- When the item appears in the visible state space of a package,
8218 -- continue to climb the scope stack as this may not be the final
8222 Placement
:= Visible_State_Space
;
8224 -- The visible state space of a child unit acts as the proper
8225 -- placement of an item.
8227 if Is_Child_Unit
(Context
) then
8232 -- The item or its enclosing package appear in a construct that has
8236 Placement
:= Not_In_Package
;
8240 Context
:= Scope
(Context
);
8242 end Find_Placement_In_State_Space
;
8244 ------------------------
8245 -- Find_Specific_Type --
8246 ------------------------
8248 function Find_Specific_Type
(CW
: Entity_Id
) return Entity_Id
is
8249 Typ
: Entity_Id
:= Root_Type
(CW
);
8252 if Ekind
(Typ
) = E_Incomplete_Type
then
8253 if From_Limited_With
(Typ
) then
8254 Typ
:= Non_Limited_View
(Typ
);
8256 Typ
:= Full_View
(Typ
);
8260 if Is_Private_Type
(Typ
)
8261 and then not Is_Tagged_Type
(Typ
)
8262 and then Present
(Full_View
(Typ
))
8264 return Full_View
(Typ
);
8268 end Find_Specific_Type
;
8270 -----------------------------
8271 -- Find_Static_Alternative --
8272 -----------------------------
8274 function Find_Static_Alternative
(N
: Node_Id
) return Node_Id
is
8275 Expr
: constant Node_Id
:= Expression
(N
);
8276 Val
: constant Uint
:= Expr_Value
(Expr
);
8281 Alt
:= First
(Alternatives
(N
));
8284 if Nkind
(Alt
) /= N_Pragma
then
8285 Choice
:= First
(Discrete_Choices
(Alt
));
8286 while Present
(Choice
) loop
8288 -- Others choice, always matches
8290 if Nkind
(Choice
) = N_Others_Choice
then
8293 -- Range, check if value is in the range
8295 elsif Nkind
(Choice
) = N_Range
then
8297 Val
>= Expr_Value
(Low_Bound
(Choice
))
8299 Val
<= Expr_Value
(High_Bound
(Choice
));
8301 -- Choice is a subtype name. Note that we know it must
8302 -- be a static subtype, since otherwise it would have
8303 -- been diagnosed as illegal.
8305 elsif Is_Entity_Name
(Choice
)
8306 and then Is_Type
(Entity
(Choice
))
8308 exit Search
when Is_In_Range
(Expr
, Etype
(Choice
),
8309 Assume_Valid
=> False);
8311 -- Choice is a subtype indication
8313 elsif Nkind
(Choice
) = N_Subtype_Indication
then
8315 C
: constant Node_Id
:= Constraint
(Choice
);
8316 R
: constant Node_Id
:= Range_Expression
(C
);
8320 Val
>= Expr_Value
(Low_Bound
(R
))
8322 Val
<= Expr_Value
(High_Bound
(R
));
8325 -- Choice is a simple expression
8328 exit Search
when Val
= Expr_Value
(Choice
);
8336 pragma Assert
(Present
(Alt
));
8339 -- The above loop *must* terminate by finding a match, since we know the
8340 -- case statement is valid, and the value of the expression is known at
8341 -- compile time. When we fall out of the loop, Alt points to the
8342 -- alternative that we know will be selected at run time.
8345 end Find_Static_Alternative
;
8351 function First_Actual
(Node
: Node_Id
) return Node_Id
is
8355 if No
(Parameter_Associations
(Node
)) then
8359 N
:= First
(Parameter_Associations
(Node
));
8361 if Nkind
(N
) = N_Parameter_Association
then
8362 return First_Named_Actual
(Node
);
8372 function First_Global
8374 Global_Mode
: Name_Id
;
8375 Refined
: Boolean := False) return Node_Id
8377 function First_From_Global_List
8379 Global_Mode
: Name_Id
:= Name_Input
) return Entity_Id
;
8380 -- Get the first item with suitable mode from List
8382 ----------------------------
8383 -- First_From_Global_List --
8384 ----------------------------
8386 function First_From_Global_List
8388 Global_Mode
: Name_Id
:= Name_Input
) return Entity_Id
8393 -- Empty list (no global items)
8395 if Nkind
(List
) = N_Null
then
8398 -- Single global item declaration (only input items)
8400 elsif Nkind_In
(List
, N_Expanded_Name
,
8402 N_Selected_Component
)
8404 if Global_Mode
= Name_Input
then
8410 -- Simple global list (only input items) or moded global list
8413 elsif Nkind
(List
) = N_Aggregate
then
8414 if Present
(Expressions
(List
)) then
8415 if Global_Mode
= Name_Input
then
8416 return First
(Expressions
(List
));
8422 Assoc
:= First
(Component_Associations
(List
));
8423 while Present
(Assoc
) loop
8425 -- When we find the desired mode in an association, call
8426 -- recursively First_From_Global_List as if the mode was
8427 -- Name_Input, in order to reuse the existing machinery
8428 -- for the other cases.
8430 if Chars
(First
(Choices
(Assoc
))) = Global_Mode
then
8431 return First_From_Global_List
(Expression
(Assoc
));
8440 -- To accommodate partial decoration of disabled SPARK features,
8441 -- this routine may be called with illegal input. If this is the
8442 -- case, do not raise Program_Error.
8447 end First_From_Global_List
;
8451 Global
: Node_Id
:= Empty
;
8452 Body_Id
: Entity_Id
;
8455 pragma Assert
(Global_Mode
= Name_Input
8456 or else Global_Mode
= Name_Output
8457 or else Global_Mode
= Name_In_Out
8458 or else Global_Mode
= Name_Proof_In
);
8460 -- Retrieve the suitable pragma Global or Refined_Global. In the second
8461 -- case, it can only be located on the body entity.
8464 Body_Id
:= Subprogram_Body_Entity
(Subp
);
8465 if Present
(Body_Id
) then
8466 Global
:= Get_Pragma
(Body_Id
, Pragma_Refined_Global
);
8469 Global
:= Get_Pragma
(Subp
, Pragma_Global
);
8472 -- No corresponding global if pragma is not present
8477 -- Otherwise retrieve the corresponding list of items depending on the
8481 return First_From_Global_List
8482 (Expression
(Get_Argument
(Global
, Subp
)), Global_Mode
);
8490 function Fix_Msg
(Id
: Entity_Id
; Msg
: String) return String is
8491 Is_Task
: constant Boolean :=
8492 Ekind_In
(Id
, E_Task_Body
, E_Task_Type
)
8493 or else Is_Single_Task_Object
(Id
);
8494 Msg_Last
: constant Natural := Msg
'Last;
8495 Msg_Index
: Natural;
8496 Res
: String (Msg
'Range) := (others => ' ');
8497 Res_Index
: Natural;
8500 -- Copy all characters from the input message Msg to result Res with
8501 -- suitable replacements.
8503 Msg_Index
:= Msg
'First;
8504 Res_Index
:= Res
'First;
8505 while Msg_Index
<= Msg_Last
loop
8507 -- Replace "subprogram" with a different word
8509 if Msg_Index
<= Msg_Last
- 10
8510 and then Msg
(Msg_Index
.. Msg_Index
+ 9) = "subprogram"
8512 if Ekind_In
(Id
, E_Entry
, E_Entry_Family
) then
8513 Res
(Res_Index
.. Res_Index
+ 4) := "entry";
8514 Res_Index
:= Res_Index
+ 5;
8517 Res
(Res_Index
.. Res_Index
+ 8) := "task type";
8518 Res_Index
:= Res_Index
+ 9;
8521 Res
(Res_Index
.. Res_Index
+ 9) := "subprogram";
8522 Res_Index
:= Res_Index
+ 10;
8525 Msg_Index
:= Msg_Index
+ 10;
8527 -- Replace "protected" with a different word
8529 elsif Msg_Index
<= Msg_Last
- 9
8530 and then Msg
(Msg_Index
.. Msg_Index
+ 8) = "protected"
8533 Res
(Res_Index
.. Res_Index
+ 3) := "task";
8534 Res_Index
:= Res_Index
+ 4;
8535 Msg_Index
:= Msg_Index
+ 9;
8537 -- Otherwise copy the character
8540 Res
(Res_Index
) := Msg
(Msg_Index
);
8541 Msg_Index
:= Msg_Index
+ 1;
8542 Res_Index
:= Res_Index
+ 1;
8546 return Res
(Res
'First .. Res_Index
- 1);
8549 -------------------------
8550 -- From_Nested_Package --
8551 -------------------------
8553 function From_Nested_Package
(T
: Entity_Id
) return Boolean is
8554 Pack
: constant Entity_Id
:= Scope
(T
);
8558 Ekind
(Pack
) = E_Package
8559 and then not Is_Frozen
(Pack
)
8560 and then not Scope_Within_Or_Same
(Current_Scope
, Pack
)
8561 and then In_Open_Scopes
(Scope
(Pack
));
8562 end From_Nested_Package
;
8564 -----------------------
8565 -- Gather_Components --
8566 -----------------------
8568 procedure Gather_Components
8570 Comp_List
: Node_Id
;
8571 Governed_By
: List_Id
;
8573 Report_Errors
: out Boolean)
8577 Discrete_Choice
: Node_Id
;
8578 Comp_Item
: Node_Id
;
8580 Discrim
: Entity_Id
;
8581 Discrim_Name
: Node_Id
;
8582 Discrim_Value
: Node_Id
;
8585 Report_Errors
:= False;
8587 if No
(Comp_List
) or else Null_Present
(Comp_List
) then
8590 elsif Present
(Component_Items
(Comp_List
)) then
8591 Comp_Item
:= First
(Component_Items
(Comp_List
));
8597 while Present
(Comp_Item
) loop
8599 -- Skip the tag of a tagged record, the interface tags, as well
8600 -- as all items that are not user components (anonymous types,
8601 -- rep clauses, Parent field, controller field).
8603 if Nkind
(Comp_Item
) = N_Component_Declaration
then
8605 Comp
: constant Entity_Id
:= Defining_Identifier
(Comp_Item
);
8607 if not Is_Tag
(Comp
) and then Chars
(Comp
) /= Name_uParent
then
8608 Append_Elmt
(Comp
, Into
);
8616 if No
(Variant_Part
(Comp_List
)) then
8619 Discrim_Name
:= Name
(Variant_Part
(Comp_List
));
8620 Variant
:= First_Non_Pragma
(Variants
(Variant_Part
(Comp_List
)));
8623 -- Look for the discriminant that governs this variant part.
8624 -- The discriminant *must* be in the Governed_By List
8626 Assoc
:= First
(Governed_By
);
8627 Find_Constraint
: loop
8628 Discrim
:= First
(Choices
(Assoc
));
8629 exit Find_Constraint
when Chars
(Discrim_Name
) = Chars
(Discrim
)
8630 or else (Present
(Corresponding_Discriminant
(Entity
(Discrim
)))
8632 Chars
(Corresponding_Discriminant
(Entity
(Discrim
))) =
8633 Chars
(Discrim_Name
))
8634 or else Chars
(Original_Record_Component
(Entity
(Discrim
)))
8635 = Chars
(Discrim_Name
);
8637 if No
(Next
(Assoc
)) then
8638 if not Is_Constrained
(Typ
)
8639 and then Is_Derived_Type
(Typ
)
8640 and then Present
(Stored_Constraint
(Typ
))
8642 -- If the type is a tagged type with inherited discriminants,
8643 -- use the stored constraint on the parent in order to find
8644 -- the values of discriminants that are otherwise hidden by an
8645 -- explicit constraint. Renamed discriminants are handled in
8648 -- If several parent discriminants are renamed by a single
8649 -- discriminant of the derived type, the call to obtain the
8650 -- Corresponding_Discriminant field only retrieves the last
8651 -- of them. We recover the constraint on the others from the
8652 -- Stored_Constraint as well.
8659 D
:= First_Discriminant
(Etype
(Typ
));
8660 C
:= First_Elmt
(Stored_Constraint
(Typ
));
8661 while Present
(D
) and then Present
(C
) loop
8662 if Chars
(Discrim_Name
) = Chars
(D
) then
8663 if Is_Entity_Name
(Node
(C
))
8664 and then Entity
(Node
(C
)) = Entity
(Discrim
)
8666 -- D is renamed by Discrim, whose value is given in
8673 Make_Component_Association
(Sloc
(Typ
),
8675 (New_Occurrence_Of
(D
, Sloc
(Typ
))),
8676 Duplicate_Subexpr_No_Checks
(Node
(C
)));
8678 exit Find_Constraint
;
8681 Next_Discriminant
(D
);
8688 if No
(Next
(Assoc
)) then
8689 Error_Msg_NE
(" missing value for discriminant&",
8690 First
(Governed_By
), Discrim_Name
);
8691 Report_Errors
:= True;
8696 end loop Find_Constraint
;
8698 Discrim_Value
:= Expression
(Assoc
);
8700 if not Is_OK_Static_Expression
(Discrim_Value
) then
8702 -- If the variant part is governed by a discriminant of the type
8703 -- this is an error. If the variant part and the discriminant are
8704 -- inherited from an ancestor this is legal (AI05-120) unless the
8705 -- components are being gathered for an aggregate, in which case
8706 -- the caller must check Report_Errors.
8708 if Scope
(Original_Record_Component
8709 ((Entity
(First
(Choices
(Assoc
)))))) = Typ
8712 ("value for discriminant & must be static!",
8713 Discrim_Value
, Discrim
);
8714 Why_Not_Static
(Discrim_Value
);
8717 Report_Errors
:= True;
8721 Search_For_Discriminant_Value
: declare
8727 UI_Discrim_Value
: constant Uint
:= Expr_Value
(Discrim_Value
);
8730 Find_Discrete_Value
: while Present
(Variant
) loop
8731 Discrete_Choice
:= First
(Discrete_Choices
(Variant
));
8732 while Present
(Discrete_Choice
) loop
8733 exit Find_Discrete_Value
when
8734 Nkind
(Discrete_Choice
) = N_Others_Choice
;
8736 Get_Index_Bounds
(Discrete_Choice
, Low
, High
);
8738 UI_Low
:= Expr_Value
(Low
);
8739 UI_High
:= Expr_Value
(High
);
8741 exit Find_Discrete_Value
when
8742 UI_Low
<= UI_Discrim_Value
8744 UI_High
>= UI_Discrim_Value
;
8746 Next
(Discrete_Choice
);
8749 Next_Non_Pragma
(Variant
);
8750 end loop Find_Discrete_Value
;
8751 end Search_For_Discriminant_Value
;
8753 -- The case statement must include a variant that corresponds to the
8754 -- value of the discriminant, unless the discriminant type has a
8755 -- static predicate. In that case the absence of an others_choice that
8756 -- would cover this value becomes a run-time error (3.8,1 (21.1/2)).
8759 and then not Has_Static_Predicate
(Etype
(Discrim_Name
))
8762 ("value of discriminant & is out of range", Discrim_Value
, Discrim
);
8763 Report_Errors
:= True;
8767 -- If we have found the corresponding choice, recursively add its
8768 -- components to the Into list. The nested components are part of
8769 -- the same record type.
8771 if Present
(Variant
) then
8773 (Typ
, Component_List
(Variant
), Governed_By
, Into
, Report_Errors
);
8775 end Gather_Components
;
8777 ------------------------
8778 -- Get_Actual_Subtype --
8779 ------------------------
8781 function Get_Actual_Subtype
(N
: Node_Id
) return Entity_Id
is
8782 Typ
: constant Entity_Id
:= Etype
(N
);
8783 Utyp
: Entity_Id
:= Underlying_Type
(Typ
);
8792 -- If what we have is an identifier that references a subprogram
8793 -- formal, or a variable or constant object, then we get the actual
8794 -- subtype from the referenced entity if one has been built.
8796 if Nkind
(N
) = N_Identifier
8798 (Is_Formal
(Entity
(N
))
8799 or else Ekind
(Entity
(N
)) = E_Constant
8800 or else Ekind
(Entity
(N
)) = E_Variable
)
8801 and then Present
(Actual_Subtype
(Entity
(N
)))
8803 return Actual_Subtype
(Entity
(N
));
8805 -- Actual subtype of unchecked union is always itself. We never need
8806 -- the "real" actual subtype. If we did, we couldn't get it anyway
8807 -- because the discriminant is not available. The restrictions on
8808 -- Unchecked_Union are designed to make sure that this is OK.
8810 elsif Is_Unchecked_Union
(Base_Type
(Utyp
)) then
8813 -- Here for the unconstrained case, we must find actual subtype
8814 -- No actual subtype is available, so we must build it on the fly.
8816 -- Checking the type, not the underlying type, for constrainedness
8817 -- seems to be necessary. Maybe all the tests should be on the type???
8819 elsif (not Is_Constrained
(Typ
))
8820 and then (Is_Array_Type
(Utyp
)
8821 or else (Is_Record_Type
(Utyp
)
8822 and then Has_Discriminants
(Utyp
)))
8823 and then not Has_Unknown_Discriminants
(Utyp
)
8824 and then not (Ekind
(Utyp
) = E_String_Literal_Subtype
)
8826 -- Nothing to do if in spec expression (why not???)
8828 if In_Spec_Expression
then
8831 elsif Is_Private_Type
(Typ
) and then not Has_Discriminants
(Typ
) then
8833 -- If the type has no discriminants, there is no subtype to
8834 -- build, even if the underlying type is discriminated.
8838 -- Else build the actual subtype
8841 Decl
:= Build_Actual_Subtype
(Typ
, N
);
8842 Atyp
:= Defining_Identifier
(Decl
);
8844 -- If Build_Actual_Subtype generated a new declaration then use it
8848 -- The actual subtype is an Itype, so analyze the declaration,
8849 -- but do not attach it to the tree, to get the type defined.
8851 Set_Parent
(Decl
, N
);
8852 Set_Is_Itype
(Atyp
);
8853 Analyze
(Decl
, Suppress
=> All_Checks
);
8854 Set_Associated_Node_For_Itype
(Atyp
, N
);
8855 Set_Has_Delayed_Freeze
(Atyp
, False);
8857 -- We need to freeze the actual subtype immediately. This is
8858 -- needed, because otherwise this Itype will not get frozen
8859 -- at all, and it is always safe to freeze on creation because
8860 -- any associated types must be frozen at this point.
8862 Freeze_Itype
(Atyp
, N
);
8865 -- Otherwise we did not build a declaration, so return original
8872 -- For all remaining cases, the actual subtype is the same as
8873 -- the nominal type.
8878 end Get_Actual_Subtype
;
8880 -------------------------------------
8881 -- Get_Actual_Subtype_If_Available --
8882 -------------------------------------
8884 function Get_Actual_Subtype_If_Available
(N
: Node_Id
) return Entity_Id
is
8885 Typ
: constant Entity_Id
:= Etype
(N
);
8888 -- If what we have is an identifier that references a subprogram
8889 -- formal, or a variable or constant object, then we get the actual
8890 -- subtype from the referenced entity if one has been built.
8892 if Nkind
(N
) = N_Identifier
8894 (Is_Formal
(Entity
(N
))
8895 or else Ekind
(Entity
(N
)) = E_Constant
8896 or else Ekind
(Entity
(N
)) = E_Variable
)
8897 and then Present
(Actual_Subtype
(Entity
(N
)))
8899 return Actual_Subtype
(Entity
(N
));
8901 -- Otherwise the Etype of N is returned unchanged
8906 end Get_Actual_Subtype_If_Available
;
8908 ------------------------
8909 -- Get_Body_From_Stub --
8910 ------------------------
8912 function Get_Body_From_Stub
(N
: Node_Id
) return Node_Id
is
8914 return Proper_Body
(Unit
(Library_Unit
(N
)));
8915 end Get_Body_From_Stub
;
8917 ---------------------
8918 -- Get_Cursor_Type --
8919 ---------------------
8921 function Get_Cursor_Type
8923 Typ
: Entity_Id
) return Entity_Id
8927 First_Op
: Entity_Id
;
8931 -- If error already detected, return
8933 if Error_Posted
(Aspect
) then
8937 -- The cursor type for an Iterable aspect is the return type of a
8938 -- non-overloaded First primitive operation. Locate association for
8941 Assoc
:= First
(Component_Associations
(Expression
(Aspect
)));
8943 while Present
(Assoc
) loop
8944 if Chars
(First
(Choices
(Assoc
))) = Name_First
then
8945 First_Op
:= Expression
(Assoc
);
8952 if First_Op
= Any_Id
then
8953 Error_Msg_N
("aspect Iterable must specify First operation", Aspect
);
8959 -- Locate function with desired name and profile in scope of type
8960 -- In the rare case where the type is an integer type, a base type
8961 -- is created for it, check that the base type of the first formal
8962 -- of First matches the base type of the domain.
8964 Func
:= First_Entity
(Scope
(Typ
));
8965 while Present
(Func
) loop
8966 if Chars
(Func
) = Chars
(First_Op
)
8967 and then Ekind
(Func
) = E_Function
8968 and then Present
(First_Formal
(Func
))
8969 and then Base_Type
(Etype
(First_Formal
(Func
))) = Base_Type
(Typ
)
8970 and then No
(Next_Formal
(First_Formal
(Func
)))
8972 if Cursor
/= Any_Type
then
8974 ("Operation First for iterable type must be unique", Aspect
);
8977 Cursor
:= Etype
(Func
);
8984 -- If not found, no way to resolve remaining primitives.
8986 if Cursor
= Any_Type
then
8988 ("No legal primitive operation First for Iterable type", Aspect
);
8992 end Get_Cursor_Type
;
8994 function Get_Cursor_Type
(Typ
: Entity_Id
) return Entity_Id
is
8996 return Etype
(Get_Iterable_Type_Primitive
(Typ
, Name_First
));
8997 end Get_Cursor_Type
;
8999 -------------------------------
9000 -- Get_Default_External_Name --
9001 -------------------------------
9003 function Get_Default_External_Name
(E
: Node_Or_Entity_Id
) return Node_Id
is
9005 Get_Decoded_Name_String
(Chars
(E
));
9007 if Opt
.External_Name_Imp_Casing
= Uppercase
then
9008 Set_Casing
(All_Upper_Case
);
9010 Set_Casing
(All_Lower_Case
);
9014 Make_String_Literal
(Sloc
(E
),
9015 Strval
=> String_From_Name_Buffer
);
9016 end Get_Default_External_Name
;
9018 --------------------------
9019 -- Get_Enclosing_Object --
9020 --------------------------
9022 function Get_Enclosing_Object
(N
: Node_Id
) return Entity_Id
is
9024 if Is_Entity_Name
(N
) then
9028 when N_Indexed_Component
9029 | N_Selected_Component
9032 -- If not generating code, a dereference may be left implicit.
9033 -- In thoses cases, return Empty.
9035 if Is_Access_Type
(Etype
(Prefix
(N
))) then
9038 return Get_Enclosing_Object
(Prefix
(N
));
9041 when N_Type_Conversion
=>
9042 return Get_Enclosing_Object
(Expression
(N
));
9048 end Get_Enclosing_Object
;
9050 ---------------------------
9051 -- Get_Enum_Lit_From_Pos --
9052 ---------------------------
9054 function Get_Enum_Lit_From_Pos
9057 Loc
: Source_Ptr
) return Node_Id
9059 Btyp
: Entity_Id
:= Base_Type
(T
);
9064 -- In the case where the literal is of type Character, Wide_Character
9065 -- or Wide_Wide_Character or of a type derived from them, there needs
9066 -- to be some special handling since there is no explicit chain of
9067 -- literals to search. Instead, an N_Character_Literal node is created
9068 -- with the appropriate Char_Code and Chars fields.
9070 if Is_Standard_Character_Type
(T
) then
9071 Set_Character_Literal_Name
(UI_To_CC
(Pos
));
9074 Make_Character_Literal
(Loc
,
9076 Char_Literal_Value
=> Pos
);
9078 -- For all other cases, we have a complete table of literals, and
9079 -- we simply iterate through the chain of literal until the one
9080 -- with the desired position value is found.
9083 if Is_Private_Type
(Btyp
) and then Present
(Full_View
(Btyp
)) then
9084 Btyp
:= Full_View
(Btyp
);
9087 Lit
:= First_Literal
(Btyp
);
9088 for J
in 1 .. UI_To_Int
(Pos
) loop
9091 -- If Lit is Empty, Pos is not in range, so raise Constraint_Error
9092 -- inside the loop to avoid calling Next_Literal on Empty.
9095 raise Constraint_Error
;
9099 -- Create a new node from Lit, with source location provided by Loc
9100 -- if not equal to No_Location, or by copying the source location of
9105 if LLoc
= No_Location
then
9109 return New_Occurrence_Of
(Lit
, LLoc
);
9111 end Get_Enum_Lit_From_Pos
;
9113 ------------------------
9114 -- Get_Generic_Entity --
9115 ------------------------
9117 function Get_Generic_Entity
(N
: Node_Id
) return Entity_Id
is
9118 Ent
: constant Entity_Id
:= Entity
(Name
(N
));
9120 if Present
(Renamed_Object
(Ent
)) then
9121 return Renamed_Object
(Ent
);
9125 end Get_Generic_Entity
;
9127 -------------------------------------
9128 -- Get_Incomplete_View_Of_Ancestor --
9129 -------------------------------------
9131 function Get_Incomplete_View_Of_Ancestor
(E
: Entity_Id
) return Entity_Id
is
9132 Cur_Unit
: constant Entity_Id
:= Cunit_Entity
(Current_Sem_Unit
);
9133 Par_Scope
: Entity_Id
;
9134 Par_Type
: Entity_Id
;
9137 -- The incomplete view of an ancestor is only relevant for private
9138 -- derived types in child units.
9140 if not Is_Derived_Type
(E
)
9141 or else not Is_Child_Unit
(Cur_Unit
)
9146 Par_Scope
:= Scope
(Cur_Unit
);
9147 if No
(Par_Scope
) then
9151 Par_Type
:= Etype
(Base_Type
(E
));
9153 -- Traverse list of ancestor types until we find one declared in
9154 -- a parent or grandparent unit (two levels seem sufficient).
9156 while Present
(Par_Type
) loop
9157 if Scope
(Par_Type
) = Par_Scope
9158 or else Scope
(Par_Type
) = Scope
(Par_Scope
)
9162 elsif not Is_Derived_Type
(Par_Type
) then
9166 Par_Type
:= Etype
(Base_Type
(Par_Type
));
9170 -- If none found, there is no relevant ancestor type.
9174 end Get_Incomplete_View_Of_Ancestor
;
9176 ----------------------
9177 -- Get_Index_Bounds --
9178 ----------------------
9180 procedure Get_Index_Bounds
9184 Use_Full_View
: Boolean := False)
9186 function Scalar_Range_Of_Type
(Typ
: Entity_Id
) return Node_Id
;
9187 -- Obtain the scalar range of type Typ. If flag Use_Full_View is set and
9188 -- Typ qualifies, the scalar range is obtained from the full view of the
9191 --------------------------
9192 -- Scalar_Range_Of_Type --
9193 --------------------------
9195 function Scalar_Range_Of_Type
(Typ
: Entity_Id
) return Node_Id
is
9196 T
: Entity_Id
:= Typ
;
9199 if Use_Full_View
and then Present
(Full_View
(T
)) then
9203 return Scalar_Range
(T
);
9204 end Scalar_Range_Of_Type
;
9208 Kind
: constant Node_Kind
:= Nkind
(N
);
9211 -- Start of processing for Get_Index_Bounds
9214 if Kind
= N_Range
then
9216 H
:= High_Bound
(N
);
9218 elsif Kind
= N_Subtype_Indication
then
9219 Rng
:= Range_Expression
(Constraint
(N
));
9227 L
:= Low_Bound
(Range_Expression
(Constraint
(N
)));
9228 H
:= High_Bound
(Range_Expression
(Constraint
(N
)));
9231 elsif Is_Entity_Name
(N
) and then Is_Type
(Entity
(N
)) then
9232 Rng
:= Scalar_Range_Of_Type
(Entity
(N
));
9234 if Error_Posted
(Rng
) then
9238 elsif Nkind
(Rng
) = N_Subtype_Indication
then
9239 Get_Index_Bounds
(Rng
, L
, H
);
9242 L
:= Low_Bound
(Rng
);
9243 H
:= High_Bound
(Rng
);
9247 -- N is an expression, indicating a range with one value
9252 end Get_Index_Bounds
;
9254 -----------------------------
9255 -- Get_Interfacing_Aspects --
9256 -----------------------------
9258 procedure Get_Interfacing_Aspects
9259 (Iface_Asp
: Node_Id
;
9260 Conv_Asp
: out Node_Id
;
9261 EN_Asp
: out Node_Id
;
9262 Expo_Asp
: out Node_Id
;
9263 Imp_Asp
: out Node_Id
;
9264 LN_Asp
: out Node_Id
;
9265 Do_Checks
: Boolean := False)
9267 procedure Save_Or_Duplication_Error
9269 To
: in out Node_Id
);
9270 -- Save the value of aspect Asp in node To. If To already has a value,
9271 -- then this is considered a duplicate use of aspect. Emit an error if
9272 -- flag Do_Checks is set.
9274 -------------------------------
9275 -- Save_Or_Duplication_Error --
9276 -------------------------------
9278 procedure Save_Or_Duplication_Error
9280 To
: in out Node_Id
)
9283 -- Detect an extra aspect and issue an error
9285 if Present
(To
) then
9287 Error_Msg_Name_1
:= Chars
(Identifier
(Asp
));
9288 Error_Msg_Sloc
:= Sloc
(To
);
9289 Error_Msg_N
("aspect % previously given #", Asp
);
9292 -- Otherwise capture the aspect
9297 end Save_Or_Duplication_Error
;
9304 -- The following variables capture each individual aspect
9306 Conv
: Node_Id
:= Empty
;
9307 EN
: Node_Id
:= Empty
;
9308 Expo
: Node_Id
:= Empty
;
9309 Imp
: Node_Id
:= Empty
;
9310 LN
: Node_Id
:= Empty
;
9312 -- Start of processing for Get_Interfacing_Aspects
9315 -- The input interfacing aspect should reside in an aspect specification
9318 pragma Assert
(Is_List_Member
(Iface_Asp
));
9320 -- Examine the aspect specifications of the related entity. Find and
9321 -- capture all interfacing aspects. Detect duplicates and emit errors
9324 Asp
:= First
(List_Containing
(Iface_Asp
));
9325 while Present
(Asp
) loop
9326 Asp_Id
:= Get_Aspect_Id
(Asp
);
9328 if Asp_Id
= Aspect_Convention
then
9329 Save_Or_Duplication_Error
(Asp
, Conv
);
9331 elsif Asp_Id
= Aspect_External_Name
then
9332 Save_Or_Duplication_Error
(Asp
, EN
);
9334 elsif Asp_Id
= Aspect_Export
then
9335 Save_Or_Duplication_Error
(Asp
, Expo
);
9337 elsif Asp_Id
= Aspect_Import
then
9338 Save_Or_Duplication_Error
(Asp
, Imp
);
9340 elsif Asp_Id
= Aspect_Link_Name
then
9341 Save_Or_Duplication_Error
(Asp
, LN
);
9352 end Get_Interfacing_Aspects
;
9354 ---------------------------------
9355 -- Get_Iterable_Type_Primitive --
9356 ---------------------------------
9358 function Get_Iterable_Type_Primitive
9360 Nam
: Name_Id
) return Entity_Id
9362 Funcs
: constant Node_Id
:= Find_Value_Of_Aspect
(Typ
, Aspect_Iterable
);
9370 Assoc
:= First
(Component_Associations
(Funcs
));
9371 while Present
(Assoc
) loop
9372 if Chars
(First
(Choices
(Assoc
))) = Nam
then
9373 return Entity
(Expression
(Assoc
));
9376 Assoc
:= Next
(Assoc
);
9381 end Get_Iterable_Type_Primitive
;
9383 ----------------------------------
9384 -- Get_Library_Unit_Name_string --
9385 ----------------------------------
9387 procedure Get_Library_Unit_Name_String
(Decl_Node
: Node_Id
) is
9388 Unit_Name_Id
: constant Unit_Name_Type
:= Get_Unit_Name
(Decl_Node
);
9391 Get_Unit_Name_String
(Unit_Name_Id
);
9393 -- Remove seven last character (" (spec)" or " (body)")
9395 Name_Len
:= Name_Len
- 7;
9396 pragma Assert
(Name_Buffer
(Name_Len
+ 1) = ' ');
9397 end Get_Library_Unit_Name_String
;
9399 --------------------------
9400 -- Get_Max_Queue_Length --
9401 --------------------------
9403 function Get_Max_Queue_Length
(Id
: Entity_Id
) return Uint
is
9404 pragma Assert
(Is_Entry
(Id
));
9405 Prag
: constant Entity_Id
:= Get_Pragma
(Id
, Pragma_Max_Queue_Length
);
9408 -- A value of 0 represents no maximum specified, and entries and entry
9409 -- families with no Max_Queue_Length aspect or pragma default to it.
9411 if not Present
(Prag
) then
9415 return Intval
(Expression
(First
(Pragma_Argument_Associations
(Prag
))));
9416 end Get_Max_Queue_Length
;
9418 ------------------------
9419 -- Get_Name_Entity_Id --
9420 ------------------------
9422 function Get_Name_Entity_Id
(Id
: Name_Id
) return Entity_Id
is
9424 return Entity_Id
(Get_Name_Table_Int
(Id
));
9425 end Get_Name_Entity_Id
;
9427 ------------------------------
9428 -- Get_Name_From_CTC_Pragma --
9429 ------------------------------
9431 function Get_Name_From_CTC_Pragma
(N
: Node_Id
) return String_Id
is
9432 Arg
: constant Node_Id
:=
9433 Get_Pragma_Arg
(First
(Pragma_Argument_Associations
(N
)));
9435 return Strval
(Expr_Value_S
(Arg
));
9436 end Get_Name_From_CTC_Pragma
;
9438 -----------------------
9439 -- Get_Parent_Entity --
9440 -----------------------
9442 function Get_Parent_Entity
(Unit
: Node_Id
) return Entity_Id
is
9444 if Nkind
(Unit
) = N_Package_Body
9445 and then Nkind
(Original_Node
(Unit
)) = N_Package_Instantiation
9447 return Defining_Entity
9448 (Specification
(Instance_Spec
(Original_Node
(Unit
))));
9449 elsif Nkind
(Unit
) = N_Package_Instantiation
then
9450 return Defining_Entity
(Specification
(Instance_Spec
(Unit
)));
9452 return Defining_Entity
(Unit
);
9454 end Get_Parent_Entity
;
9460 function Get_Pragma_Id
(N
: Node_Id
) return Pragma_Id
is
9462 return Get_Pragma_Id
(Pragma_Name_Unmapped
(N
));
9465 ------------------------
9466 -- Get_Qualified_Name --
9467 ------------------------
9469 function Get_Qualified_Name
9471 Suffix
: Entity_Id
:= Empty
) return Name_Id
9473 Suffix_Nam
: Name_Id
:= No_Name
;
9476 if Present
(Suffix
) then
9477 Suffix_Nam
:= Chars
(Suffix
);
9480 return Get_Qualified_Name
(Chars
(Id
), Suffix_Nam
, Scope
(Id
));
9481 end Get_Qualified_Name
;
9483 function Get_Qualified_Name
9485 Suffix
: Name_Id
:= No_Name
;
9486 Scop
: Entity_Id
:= Current_Scope
) return Name_Id
9488 procedure Add_Scope
(S
: Entity_Id
);
9489 -- Add the fully qualified form of scope S to the name buffer. The
9497 procedure Add_Scope
(S
: Entity_Id
) is
9502 elsif S
= Standard_Standard
then
9506 Add_Scope
(Scope
(S
));
9507 Get_Name_String_And_Append
(Chars
(S
));
9508 Add_Str_To_Name_Buffer
("__");
9512 -- Start of processing for Get_Qualified_Name
9518 -- Append the base name after all scopes have been chained
9520 Get_Name_String_And_Append
(Nam
);
9522 -- Append the suffix (if present)
9524 if Suffix
/= No_Name
then
9525 Add_Str_To_Name_Buffer
("__");
9526 Get_Name_String_And_Append
(Suffix
);
9530 end Get_Qualified_Name
;
9532 -----------------------
9533 -- Get_Reason_String --
9534 -----------------------
9536 procedure Get_Reason_String
(N
: Node_Id
) is
9538 if Nkind
(N
) = N_String_Literal
then
9539 Store_String_Chars
(Strval
(N
));
9541 elsif Nkind
(N
) = N_Op_Concat
then
9542 Get_Reason_String
(Left_Opnd
(N
));
9543 Get_Reason_String
(Right_Opnd
(N
));
9545 -- If not of required form, error
9549 ("Reason for pragma Warnings has wrong form", N
);
9551 ("\must be string literal or concatenation of string literals", N
);
9554 end Get_Reason_String
;
9556 --------------------------------
9557 -- Get_Reference_Discriminant --
9558 --------------------------------
9560 function Get_Reference_Discriminant
(Typ
: Entity_Id
) return Entity_Id
is
9564 D
:= First_Discriminant
(Typ
);
9565 while Present
(D
) loop
9566 if Has_Implicit_Dereference
(D
) then
9569 Next_Discriminant
(D
);
9573 end Get_Reference_Discriminant
;
9575 ---------------------------
9576 -- Get_Referenced_Object --
9577 ---------------------------
9579 function Get_Referenced_Object
(N
: Node_Id
) return Node_Id
is
9584 while Is_Entity_Name
(R
)
9585 and then Present
(Renamed_Object
(Entity
(R
)))
9587 R
:= Renamed_Object
(Entity
(R
));
9591 end Get_Referenced_Object
;
9593 ------------------------
9594 -- Get_Renamed_Entity --
9595 ------------------------
9597 function Get_Renamed_Entity
(E
: Entity_Id
) return Entity_Id
is
9602 while Present
(Renamed_Entity
(R
)) loop
9603 R
:= Renamed_Entity
(R
);
9607 end Get_Renamed_Entity
;
9609 -----------------------
9610 -- Get_Return_Object --
9611 -----------------------
9613 function Get_Return_Object
(N
: Node_Id
) return Entity_Id
is
9617 Decl
:= First
(Return_Object_Declarations
(N
));
9618 while Present
(Decl
) loop
9619 exit when Nkind
(Decl
) = N_Object_Declaration
9620 and then Is_Return_Object
(Defining_Identifier
(Decl
));
9624 pragma Assert
(Present
(Decl
));
9625 return Defining_Identifier
(Decl
);
9626 end Get_Return_Object
;
9628 ---------------------------
9629 -- Get_Subprogram_Entity --
9630 ---------------------------
9632 function Get_Subprogram_Entity
(Nod
: Node_Id
) return Entity_Id
is
9634 Subp_Id
: Entity_Id
;
9637 if Nkind
(Nod
) = N_Accept_Statement
then
9638 Subp
:= Entry_Direct_Name
(Nod
);
9640 elsif Nkind
(Nod
) = N_Slice
then
9641 Subp
:= Prefix
(Nod
);
9647 -- Strip the subprogram call
9650 if Nkind_In
(Subp
, N_Explicit_Dereference
,
9651 N_Indexed_Component
,
9652 N_Selected_Component
)
9654 Subp
:= Prefix
(Subp
);
9656 elsif Nkind_In
(Subp
, N_Type_Conversion
,
9657 N_Unchecked_Type_Conversion
)
9659 Subp
:= Expression
(Subp
);
9666 -- Extract the entity of the subprogram call
9668 if Is_Entity_Name
(Subp
) then
9669 Subp_Id
:= Entity
(Subp
);
9671 if Ekind
(Subp_Id
) = E_Access_Subprogram_Type
then
9672 Subp_Id
:= Directly_Designated_Type
(Subp_Id
);
9675 if Is_Subprogram
(Subp_Id
) then
9681 -- The search did not find a construct that denotes a subprogram
9686 end Get_Subprogram_Entity
;
9688 -----------------------------
9689 -- Get_Task_Body_Procedure --
9690 -----------------------------
9692 function Get_Task_Body_Procedure
(E
: Entity_Id
) return Entity_Id
is
9694 -- Note: A task type may be the completion of a private type with
9695 -- discriminants. When performing elaboration checks on a task
9696 -- declaration, the current view of the type may be the private one,
9697 -- and the procedure that holds the body of the task is held in its
9700 -- This is an odd function, why not have Task_Body_Procedure do
9701 -- the following digging???
9703 return Task_Body_Procedure
(Underlying_Type
(Root_Type
(E
)));
9704 end Get_Task_Body_Procedure
;
9706 -------------------------
9707 -- Get_User_Defined_Eq --
9708 -------------------------
9710 function Get_User_Defined_Eq
(E
: Entity_Id
) return Entity_Id
is
9715 Prim
:= First_Elmt
(Collect_Primitive_Operations
(E
));
9716 while Present
(Prim
) loop
9719 if Chars
(Op
) = Name_Op_Eq
9720 and then Etype
(Op
) = Standard_Boolean
9721 and then Etype
(First_Formal
(Op
)) = E
9722 and then Etype
(Next_Formal
(First_Formal
(Op
))) = E
9731 end Get_User_Defined_Eq
;
9739 Priv_Typ
: out Entity_Id
;
9740 Full_Typ
: out Entity_Id
;
9741 Full_Base
: out Entity_Id
;
9742 CRec_Typ
: out Entity_Id
)
9744 IP_View
: Entity_Id
;
9747 -- Assume that none of the views can be recovered
9754 -- The input type is the corresponding record type of a protected or a
9757 if Ekind
(Typ
) = E_Record_Type
9758 and then Is_Concurrent_Record_Type
(Typ
)
9761 Full_Typ
:= Corresponding_Concurrent_Type
(CRec_Typ
);
9762 Full_Base
:= Base_Type
(Full_Typ
);
9763 Priv_Typ
:= Incomplete_Or_Partial_View
(Full_Typ
);
9765 -- Otherwise the input type denotes an arbitrary type
9768 IP_View
:= Incomplete_Or_Partial_View
(Typ
);
9770 -- The input type denotes the full view of a private type
9772 if Present
(IP_View
) then
9773 Priv_Typ
:= IP_View
;
9776 -- The input type is a private type
9778 elsif Is_Private_Type
(Typ
) then
9780 Full_Typ
:= Full_View
(Priv_Typ
);
9782 -- Otherwise the input type does not have any views
9788 if Present
(Full_Typ
) then
9789 Full_Base
:= Base_Type
(Full_Typ
);
9791 if Ekind_In
(Full_Typ
, E_Protected_Type
, E_Task_Type
) then
9792 CRec_Typ
:= Corresponding_Record_Type
(Full_Typ
);
9798 -----------------------
9799 -- Has_Access_Values --
9800 -----------------------
9802 function Has_Access_Values
(T
: Entity_Id
) return Boolean is
9803 Typ
: constant Entity_Id
:= Underlying_Type
(T
);
9806 -- Case of a private type which is not completed yet. This can only
9807 -- happen in the case of a generic format type appearing directly, or
9808 -- as a component of the type to which this function is being applied
9809 -- at the top level. Return False in this case, since we certainly do
9810 -- not know that the type contains access types.
9815 elsif Is_Access_Type
(Typ
) then
9818 elsif Is_Array_Type
(Typ
) then
9819 return Has_Access_Values
(Component_Type
(Typ
));
9821 elsif Is_Record_Type
(Typ
) then
9826 -- Loop to Check components
9828 Comp
:= First_Component_Or_Discriminant
(Typ
);
9829 while Present
(Comp
) loop
9831 -- Check for access component, tag field does not count, even
9832 -- though it is implemented internally using an access type.
9834 if Has_Access_Values
(Etype
(Comp
))
9835 and then Chars
(Comp
) /= Name_uTag
9840 Next_Component_Or_Discriminant
(Comp
);
9849 end Has_Access_Values
;
9851 ------------------------------
9852 -- Has_Compatible_Alignment --
9853 ------------------------------
9855 function Has_Compatible_Alignment
9858 Layout_Done
: Boolean) return Alignment_Result
9860 function Has_Compatible_Alignment_Internal
9863 Layout_Done
: Boolean;
9864 Default
: Alignment_Result
) return Alignment_Result
;
9865 -- This is the internal recursive function that actually does the work.
9866 -- There is one additional parameter, which says what the result should
9867 -- be if no alignment information is found, and there is no definite
9868 -- indication of compatible alignments. At the outer level, this is set
9869 -- to Unknown, but for internal recursive calls in the case where types
9870 -- are known to be correct, it is set to Known_Compatible.
9872 ---------------------------------------
9873 -- Has_Compatible_Alignment_Internal --
9874 ---------------------------------------
9876 function Has_Compatible_Alignment_Internal
9879 Layout_Done
: Boolean;
9880 Default
: Alignment_Result
) return Alignment_Result
9882 Result
: Alignment_Result
:= Known_Compatible
;
9883 -- Holds the current status of the result. Note that once a value of
9884 -- Known_Incompatible is set, it is sticky and does not get changed
9885 -- to Unknown (the value in Result only gets worse as we go along,
9888 Offs
: Uint
:= No_Uint
;
9889 -- Set to a factor of the offset from the base object when Expr is a
9890 -- selected or indexed component, based on Component_Bit_Offset and
9891 -- Component_Size respectively. A negative value is used to represent
9892 -- a value which is not known at compile time.
9894 procedure Check_Prefix
;
9895 -- Checks the prefix recursively in the case where the expression
9896 -- is an indexed or selected component.
9898 procedure Set_Result
(R
: Alignment_Result
);
9899 -- If R represents a worse outcome (unknown instead of known
9900 -- compatible, or known incompatible), then set Result to R.
9906 procedure Check_Prefix
is
9908 -- The subtlety here is that in doing a recursive call to check
9909 -- the prefix, we have to decide what to do in the case where we
9910 -- don't find any specific indication of an alignment problem.
9912 -- At the outer level, we normally set Unknown as the result in
9913 -- this case, since we can only set Known_Compatible if we really
9914 -- know that the alignment value is OK, but for the recursive
9915 -- call, in the case where the types match, and we have not
9916 -- specified a peculiar alignment for the object, we are only
9917 -- concerned about suspicious rep clauses, the default case does
9918 -- not affect us, since the compiler will, in the absence of such
9919 -- rep clauses, ensure that the alignment is correct.
9921 if Default
= Known_Compatible
9923 (Etype
(Obj
) = Etype
(Expr
)
9924 and then (Unknown_Alignment
(Obj
)
9926 Alignment
(Obj
) = Alignment
(Etype
(Obj
))))
9929 (Has_Compatible_Alignment_Internal
9930 (Obj
, Prefix
(Expr
), Layout_Done
, Known_Compatible
));
9932 -- In all other cases, we need a full check on the prefix
9936 (Has_Compatible_Alignment_Internal
9937 (Obj
, Prefix
(Expr
), Layout_Done
, Unknown
));
9945 procedure Set_Result
(R
: Alignment_Result
) is
9952 -- Start of processing for Has_Compatible_Alignment_Internal
9955 -- If Expr is a selected component, we must make sure there is no
9956 -- potentially troublesome component clause and that the record is
9957 -- not packed if the layout is not done.
9959 if Nkind
(Expr
) = N_Selected_Component
then
9961 -- Packing generates unknown alignment if layout is not done
9963 if Is_Packed
(Etype
(Prefix
(Expr
))) and then not Layout_Done
then
9964 Set_Result
(Unknown
);
9967 -- Check prefix and component offset
9970 Offs
:= Component_Bit_Offset
(Entity
(Selector_Name
(Expr
)));
9972 -- If Expr is an indexed component, we must make sure there is no
9973 -- potentially troublesome Component_Size clause and that the array
9974 -- is not bit-packed if the layout is not done.
9976 elsif Nkind
(Expr
) = N_Indexed_Component
then
9978 Typ
: constant Entity_Id
:= Etype
(Prefix
(Expr
));
9981 -- Packing generates unknown alignment if layout is not done
9983 if Is_Bit_Packed_Array
(Typ
) and then not Layout_Done
then
9984 Set_Result
(Unknown
);
9987 -- Check prefix and component offset (or at least size)
9990 Offs
:= Indexed_Component_Bit_Offset
(Expr
);
9991 if Offs
= No_Uint
then
9992 Offs
:= Component_Size
(Typ
);
9997 -- If we have a null offset, the result is entirely determined by
9998 -- the base object and has already been computed recursively.
10000 if Offs
= Uint_0
then
10003 -- Case where we know the alignment of the object
10005 elsif Known_Alignment
(Obj
) then
10007 ObjA
: constant Uint
:= Alignment
(Obj
);
10008 ExpA
: Uint
:= No_Uint
;
10009 SizA
: Uint
:= No_Uint
;
10012 -- If alignment of Obj is 1, then we are always OK
10015 Set_Result
(Known_Compatible
);
10017 -- Alignment of Obj is greater than 1, so we need to check
10020 -- If we have an offset, see if it is compatible
10022 if Offs
/= No_Uint
and Offs
> Uint_0
then
10023 if Offs
mod (System_Storage_Unit
* ObjA
) /= 0 then
10024 Set_Result
(Known_Incompatible
);
10027 -- See if Expr is an object with known alignment
10029 elsif Is_Entity_Name
(Expr
)
10030 and then Known_Alignment
(Entity
(Expr
))
10032 ExpA
:= Alignment
(Entity
(Expr
));
10034 -- Otherwise, we can use the alignment of the type of
10035 -- Expr given that we already checked for
10036 -- discombobulating rep clauses for the cases of indexed
10037 -- and selected components above.
10039 elsif Known_Alignment
(Etype
(Expr
)) then
10040 ExpA
:= Alignment
(Etype
(Expr
));
10042 -- Otherwise the alignment is unknown
10045 Set_Result
(Default
);
10048 -- If we got an alignment, see if it is acceptable
10050 if ExpA
/= No_Uint
and then ExpA
< ObjA
then
10051 Set_Result
(Known_Incompatible
);
10054 -- If Expr is not a piece of a larger object, see if size
10055 -- is given. If so, check that it is not too small for the
10056 -- required alignment.
10058 if Offs
/= No_Uint
then
10061 -- See if Expr is an object with known size
10063 elsif Is_Entity_Name
(Expr
)
10064 and then Known_Static_Esize
(Entity
(Expr
))
10066 SizA
:= Esize
(Entity
(Expr
));
10068 -- Otherwise, we check the object size of the Expr type
10070 elsif Known_Static_Esize
(Etype
(Expr
)) then
10071 SizA
:= Esize
(Etype
(Expr
));
10074 -- If we got a size, see if it is a multiple of the Obj
10075 -- alignment, if not, then the alignment cannot be
10076 -- acceptable, since the size is always a multiple of the
10079 if SizA
/= No_Uint
then
10080 if SizA
mod (ObjA
* Ttypes
.System_Storage_Unit
) /= 0 then
10081 Set_Result
(Known_Incompatible
);
10087 -- If we do not know required alignment, any non-zero offset is a
10088 -- potential problem (but certainly may be OK, so result is unknown).
10090 elsif Offs
/= No_Uint
then
10091 Set_Result
(Unknown
);
10093 -- If we can't find the result by direct comparison of alignment
10094 -- values, then there is still one case that we can determine known
10095 -- result, and that is when we can determine that the types are the
10096 -- same, and no alignments are specified. Then we known that the
10097 -- alignments are compatible, even if we don't know the alignment
10098 -- value in the front end.
10100 elsif Etype
(Obj
) = Etype
(Expr
) then
10102 -- Types are the same, but we have to check for possible size
10103 -- and alignments on the Expr object that may make the alignment
10104 -- different, even though the types are the same.
10106 if Is_Entity_Name
(Expr
) then
10108 -- First check alignment of the Expr object. Any alignment less
10109 -- than Maximum_Alignment is worrisome since this is the case
10110 -- where we do not know the alignment of Obj.
10112 if Known_Alignment
(Entity
(Expr
))
10113 and then UI_To_Int
(Alignment
(Entity
(Expr
))) <
10114 Ttypes
.Maximum_Alignment
10116 Set_Result
(Unknown
);
10118 -- Now check size of Expr object. Any size that is not an
10119 -- even multiple of Maximum_Alignment is also worrisome
10120 -- since it may cause the alignment of the object to be less
10121 -- than the alignment of the type.
10123 elsif Known_Static_Esize
(Entity
(Expr
))
10125 (UI_To_Int
(Esize
(Entity
(Expr
))) mod
10126 (Ttypes
.Maximum_Alignment
* Ttypes
.System_Storage_Unit
))
10129 Set_Result
(Unknown
);
10131 -- Otherwise same type is decisive
10134 Set_Result
(Known_Compatible
);
10138 -- Another case to deal with is when there is an explicit size or
10139 -- alignment clause when the types are not the same. If so, then the
10140 -- result is Unknown. We don't need to do this test if the Default is
10141 -- Unknown, since that result will be set in any case.
10143 elsif Default
/= Unknown
10144 and then (Has_Size_Clause
(Etype
(Expr
))
10146 Has_Alignment_Clause
(Etype
(Expr
)))
10148 Set_Result
(Unknown
);
10150 -- If no indication found, set default
10153 Set_Result
(Default
);
10156 -- Return worst result found
10159 end Has_Compatible_Alignment_Internal
;
10161 -- Start of processing for Has_Compatible_Alignment
10164 -- If Obj has no specified alignment, then set alignment from the type
10165 -- alignment. Perhaps we should always do this, but for sure we should
10166 -- do it when there is an address clause since we can do more if the
10167 -- alignment is known.
10169 if Unknown_Alignment
(Obj
) then
10170 Set_Alignment
(Obj
, Alignment
(Etype
(Obj
)));
10173 -- Now do the internal call that does all the work
10176 Has_Compatible_Alignment_Internal
(Obj
, Expr
, Layout_Done
, Unknown
);
10177 end Has_Compatible_Alignment
;
10179 ----------------------
10180 -- Has_Declarations --
10181 ----------------------
10183 function Has_Declarations
(N
: Node_Id
) return Boolean is
10185 return Nkind_In
(Nkind
(N
), N_Accept_Statement
,
10187 N_Compilation_Unit_Aux
,
10193 N_Package_Specification
);
10194 end Has_Declarations
;
10196 ---------------------------------
10197 -- Has_Defaulted_Discriminants --
10198 ---------------------------------
10200 function Has_Defaulted_Discriminants
(Typ
: Entity_Id
) return Boolean is
10202 return Has_Discriminants
(Typ
)
10203 and then Present
(First_Discriminant
(Typ
))
10204 and then Present
(Discriminant_Default_Value
10205 (First_Discriminant
(Typ
)));
10206 end Has_Defaulted_Discriminants
;
10208 -------------------
10209 -- Has_Denormals --
10210 -------------------
10212 function Has_Denormals
(E
: Entity_Id
) return Boolean is
10214 return Is_Floating_Point_Type
(E
) and then Denorm_On_Target
;
10217 -------------------------------------------
10218 -- Has_Discriminant_Dependent_Constraint --
10219 -------------------------------------------
10221 function Has_Discriminant_Dependent_Constraint
10222 (Comp
: Entity_Id
) return Boolean
10224 Comp_Decl
: constant Node_Id
:= Parent
(Comp
);
10225 Subt_Indic
: Node_Id
;
10230 -- Discriminants can't depend on discriminants
10232 if Ekind
(Comp
) = E_Discriminant
then
10236 Subt_Indic
:= Subtype_Indication
(Component_Definition
(Comp_Decl
));
10238 if Nkind
(Subt_Indic
) = N_Subtype_Indication
then
10239 Constr
:= Constraint
(Subt_Indic
);
10241 if Nkind
(Constr
) = N_Index_Or_Discriminant_Constraint
then
10242 Assn
:= First
(Constraints
(Constr
));
10243 while Present
(Assn
) loop
10244 case Nkind
(Assn
) is
10247 | N_Subtype_Indication
10249 if Depends_On_Discriminant
(Assn
) then
10253 when N_Discriminant_Association
=>
10254 if Depends_On_Discriminant
(Expression
(Assn
)) then
10269 end Has_Discriminant_Dependent_Constraint
;
10271 --------------------------------------
10272 -- Has_Effectively_Volatile_Profile --
10273 --------------------------------------
10275 function Has_Effectively_Volatile_Profile
10276 (Subp_Id
: Entity_Id
) return Boolean
10278 Formal
: Entity_Id
;
10281 -- Inspect the formal parameters looking for an effectively volatile
10284 Formal
:= First_Formal
(Subp_Id
);
10285 while Present
(Formal
) loop
10286 if Is_Effectively_Volatile
(Etype
(Formal
)) then
10290 Next_Formal
(Formal
);
10293 -- Inspect the return type of functions
10295 if Ekind_In
(Subp_Id
, E_Function
, E_Generic_Function
)
10296 and then Is_Effectively_Volatile
(Etype
(Subp_Id
))
10302 end Has_Effectively_Volatile_Profile
;
10304 --------------------------
10305 -- Has_Enabled_Property --
10306 --------------------------
10308 function Has_Enabled_Property
10309 (Item_Id
: Entity_Id
;
10310 Property
: Name_Id
) return Boolean
10312 function Protected_Object_Has_Enabled_Property
return Boolean;
10313 -- Determine whether a protected object denoted by Item_Id has the
10314 -- property enabled.
10316 function State_Has_Enabled_Property
return Boolean;
10317 -- Determine whether a state denoted by Item_Id has the property enabled
10319 function Variable_Has_Enabled_Property
return Boolean;
10320 -- Determine whether a variable denoted by Item_Id has the property
10323 -------------------------------------------
10324 -- Protected_Object_Has_Enabled_Property --
10325 -------------------------------------------
10327 function Protected_Object_Has_Enabled_Property
return Boolean is
10328 Constits
: constant Elist_Id
:= Part_Of_Constituents
(Item_Id
);
10329 Constit_Elmt
: Elmt_Id
;
10330 Constit_Id
: Entity_Id
;
10333 -- Protected objects always have the properties Async_Readers and
10334 -- Async_Writers (SPARK RM 7.1.2(16)).
10336 if Property
= Name_Async_Readers
10337 or else Property
= Name_Async_Writers
10341 -- Protected objects that have Part_Of components also inherit their
10342 -- properties Effective_Reads and Effective_Writes
10343 -- (SPARK RM 7.1.2(16)).
10345 elsif Present
(Constits
) then
10346 Constit_Elmt
:= First_Elmt
(Constits
);
10347 while Present
(Constit_Elmt
) loop
10348 Constit_Id
:= Node
(Constit_Elmt
);
10350 if Has_Enabled_Property
(Constit_Id
, Property
) then
10354 Next_Elmt
(Constit_Elmt
);
10359 end Protected_Object_Has_Enabled_Property
;
10361 --------------------------------
10362 -- State_Has_Enabled_Property --
10363 --------------------------------
10365 function State_Has_Enabled_Property
return Boolean is
10366 Decl
: constant Node_Id
:= Parent
(Item_Id
);
10370 Prop_Nam
: Node_Id
;
10374 -- The declaration of an external abstract state appears as an
10375 -- extension aggregate. If this is not the case, properties can never
10378 if Nkind
(Decl
) /= N_Extension_Aggregate
then
10382 -- When External appears as a simple option, it automatically enables
10385 Opt
:= First
(Expressions
(Decl
));
10386 while Present
(Opt
) loop
10387 if Nkind
(Opt
) = N_Identifier
10388 and then Chars
(Opt
) = Name_External
10396 -- When External specifies particular properties, inspect those and
10397 -- find the desired one (if any).
10399 Opt
:= First
(Component_Associations
(Decl
));
10400 while Present
(Opt
) loop
10401 Opt_Nam
:= First
(Choices
(Opt
));
10403 if Nkind
(Opt_Nam
) = N_Identifier
10404 and then Chars
(Opt_Nam
) = Name_External
10406 Props
:= Expression
(Opt
);
10408 -- Multiple properties appear as an aggregate
10410 if Nkind
(Props
) = N_Aggregate
then
10412 -- Simple property form
10414 Prop
:= First
(Expressions
(Props
));
10415 while Present
(Prop
) loop
10416 if Chars
(Prop
) = Property
then
10423 -- Property with expression form
10425 Prop
:= First
(Component_Associations
(Props
));
10426 while Present
(Prop
) loop
10427 Prop_Nam
:= First
(Choices
(Prop
));
10429 -- The property can be represented in two ways:
10430 -- others => <value>
10431 -- <property> => <value>
10433 if Nkind
(Prop_Nam
) = N_Others_Choice
10434 or else (Nkind
(Prop_Nam
) = N_Identifier
10435 and then Chars
(Prop_Nam
) = Property
)
10437 return Is_True
(Expr_Value
(Expression
(Prop
)));
10446 return Chars
(Props
) = Property
;
10454 end State_Has_Enabled_Property
;
10456 -----------------------------------
10457 -- Variable_Has_Enabled_Property --
10458 -----------------------------------
10460 function Variable_Has_Enabled_Property
return Boolean is
10461 function Is_Enabled
(Prag
: Node_Id
) return Boolean;
10462 -- Determine whether property pragma Prag (if present) denotes an
10463 -- enabled property.
10469 function Is_Enabled
(Prag
: Node_Id
) return Boolean is
10473 if Present
(Prag
) then
10474 Arg1
:= First
(Pragma_Argument_Associations
(Prag
));
10476 -- The pragma has an optional Boolean expression, the related
10477 -- property is enabled only when the expression evaluates to
10480 if Present
(Arg1
) then
10481 return Is_True
(Expr_Value
(Get_Pragma_Arg
(Arg1
)));
10483 -- Otherwise the lack of expression enables the property by
10490 -- The property was never set in the first place
10499 AR
: constant Node_Id
:=
10500 Get_Pragma
(Item_Id
, Pragma_Async_Readers
);
10501 AW
: constant Node_Id
:=
10502 Get_Pragma
(Item_Id
, Pragma_Async_Writers
);
10503 ER
: constant Node_Id
:=
10504 Get_Pragma
(Item_Id
, Pragma_Effective_Reads
);
10505 EW
: constant Node_Id
:=
10506 Get_Pragma
(Item_Id
, Pragma_Effective_Writes
);
10508 -- Start of processing for Variable_Has_Enabled_Property
10511 -- A non-effectively volatile object can never possess external
10514 if not Is_Effectively_Volatile
(Item_Id
) then
10517 -- External properties related to variables come in two flavors -
10518 -- explicit and implicit. The explicit case is characterized by the
10519 -- presence of a property pragma with an optional Boolean flag. The
10520 -- property is enabled when the flag evaluates to True or the flag is
10521 -- missing altogether.
10523 elsif Property
= Name_Async_Readers
and then Is_Enabled
(AR
) then
10526 elsif Property
= Name_Async_Writers
and then Is_Enabled
(AW
) then
10529 elsif Property
= Name_Effective_Reads
and then Is_Enabled
(ER
) then
10532 elsif Property
= Name_Effective_Writes
and then Is_Enabled
(EW
) then
10535 -- The implicit case lacks all property pragmas
10537 elsif No
(AR
) and then No
(AW
) and then No
(ER
) and then No
(EW
) then
10538 if Is_Protected_Type
(Etype
(Item_Id
)) then
10539 return Protected_Object_Has_Enabled_Property
;
10547 end Variable_Has_Enabled_Property
;
10549 -- Start of processing for Has_Enabled_Property
10552 -- Abstract states and variables have a flexible scheme of specifying
10553 -- external properties.
10555 if Ekind
(Item_Id
) = E_Abstract_State
then
10556 return State_Has_Enabled_Property
;
10558 elsif Ekind
(Item_Id
) = E_Variable
then
10559 return Variable_Has_Enabled_Property
;
10561 -- By default, protected objects only have the properties Async_Readers
10562 -- and Async_Writers. If they have Part_Of components, they also inherit
10563 -- their properties Effective_Reads and Effective_Writes
10564 -- (SPARK RM 7.1.2(16)).
10566 elsif Ekind
(Item_Id
) = E_Protected_Object
then
10567 return Protected_Object_Has_Enabled_Property
;
10569 -- Otherwise a property is enabled when the related item is effectively
10573 return Is_Effectively_Volatile
(Item_Id
);
10575 end Has_Enabled_Property
;
10577 -------------------------------------
10578 -- Has_Full_Default_Initialization --
10579 -------------------------------------
10581 function Has_Full_Default_Initialization
(Typ
: Entity_Id
) return Boolean is
10586 -- A type subject to pragma Default_Initial_Condition is fully default
10587 -- initialized when the pragma appears with a non-null argument. Since
10588 -- any type may act as the full view of a private type, this check must
10589 -- be performed prior to the specialized tests below.
10591 if Has_DIC
(Typ
) then
10592 Prag
:= Get_Pragma
(Typ
, Pragma_Default_Initial_Condition
);
10593 pragma Assert
(Present
(Prag
));
10595 return Is_Verifiable_DIC_Pragma
(Prag
);
10598 -- A scalar type is fully default initialized if it is subject to aspect
10601 if Is_Scalar_Type
(Typ
) then
10602 return Has_Default_Aspect
(Typ
);
10604 -- An array type is fully default initialized if its element type is
10605 -- scalar and the array type carries aspect Default_Component_Value or
10606 -- the element type is fully default initialized.
10608 elsif Is_Array_Type
(Typ
) then
10610 Has_Default_Aspect
(Typ
)
10611 or else Has_Full_Default_Initialization
(Component_Type
(Typ
));
10613 -- A protected type, record type, or type extension is fully default
10614 -- initialized if all its components either carry an initialization
10615 -- expression or have a type that is fully default initialized. The
10616 -- parent type of a type extension must be fully default initialized.
10618 elsif Is_Record_Type
(Typ
) or else Is_Protected_Type
(Typ
) then
10620 -- Inspect all entities defined in the scope of the type, looking for
10621 -- uninitialized components.
10623 Comp
:= First_Entity
(Typ
);
10624 while Present
(Comp
) loop
10625 if Ekind
(Comp
) = E_Component
10626 and then Comes_From_Source
(Comp
)
10627 and then No
(Expression
(Parent
(Comp
)))
10628 and then not Has_Full_Default_Initialization
(Etype
(Comp
))
10633 Next_Entity
(Comp
);
10636 -- Ensure that the parent type of a type extension is fully default
10639 if Etype
(Typ
) /= Typ
10640 and then not Has_Full_Default_Initialization
(Etype
(Typ
))
10645 -- If we get here, then all components and parent portion are fully
10646 -- default initialized.
10650 -- A task type is fully default initialized by default
10652 elsif Is_Task_Type
(Typ
) then
10655 -- Otherwise the type is not fully default initialized
10660 end Has_Full_Default_Initialization
;
10662 --------------------
10663 -- Has_Infinities --
10664 --------------------
10666 function Has_Infinities
(E
: Entity_Id
) return Boolean is
10669 Is_Floating_Point_Type
(E
)
10670 and then Nkind
(Scalar_Range
(E
)) = N_Range
10671 and then Includes_Infinities
(Scalar_Range
(E
));
10672 end Has_Infinities
;
10674 --------------------
10675 -- Has_Interfaces --
10676 --------------------
10678 function Has_Interfaces
10680 Use_Full_View
: Boolean := True) return Boolean
10682 Typ
: Entity_Id
:= Base_Type
(T
);
10685 -- Handle concurrent types
10687 if Is_Concurrent_Type
(Typ
) then
10688 Typ
:= Corresponding_Record_Type
(Typ
);
10691 if not Present
(Typ
)
10692 or else not Is_Record_Type
(Typ
)
10693 or else not Is_Tagged_Type
(Typ
)
10698 -- Handle private types
10700 if Use_Full_View
and then Present
(Full_View
(Typ
)) then
10701 Typ
:= Full_View
(Typ
);
10704 -- Handle concurrent record types
10706 if Is_Concurrent_Record_Type
(Typ
)
10707 and then Is_Non_Empty_List
(Abstract_Interface_List
(Typ
))
10713 if Is_Interface
(Typ
)
10715 (Is_Record_Type
(Typ
)
10716 and then Present
(Interfaces
(Typ
))
10717 and then not Is_Empty_Elmt_List
(Interfaces
(Typ
)))
10722 exit when Etype
(Typ
) = Typ
10724 -- Handle private types
10726 or else (Present
(Full_View
(Etype
(Typ
)))
10727 and then Full_View
(Etype
(Typ
)) = Typ
)
10729 -- Protect frontend against wrong sources with cyclic derivations
10731 or else Etype
(Typ
) = T
;
10733 -- Climb to the ancestor type handling private types
10735 if Present
(Full_View
(Etype
(Typ
))) then
10736 Typ
:= Full_View
(Etype
(Typ
));
10738 Typ
:= Etype
(Typ
);
10743 end Has_Interfaces
;
10745 --------------------------
10746 -- Has_Max_Queue_Length --
10747 --------------------------
10749 function Has_Max_Queue_Length
(Id
: Entity_Id
) return Boolean is
10752 Ekind
(Id
) = E_Entry
10753 and then Present
(Get_Pragma
(Id
, Pragma_Max_Queue_Length
));
10754 end Has_Max_Queue_Length
;
10756 ---------------------------------
10757 -- Has_No_Obvious_Side_Effects --
10758 ---------------------------------
10760 function Has_No_Obvious_Side_Effects
(N
: Node_Id
) return Boolean is
10762 -- For now handle literals, constants, and non-volatile variables and
10763 -- expressions combining these with operators or short circuit forms.
10765 if Nkind
(N
) in N_Numeric_Or_String_Literal
then
10768 elsif Nkind
(N
) = N_Character_Literal
then
10771 elsif Nkind
(N
) in N_Unary_Op
then
10772 return Has_No_Obvious_Side_Effects
(Right_Opnd
(N
));
10774 elsif Nkind
(N
) in N_Binary_Op
or else Nkind
(N
) in N_Short_Circuit
then
10775 return Has_No_Obvious_Side_Effects
(Left_Opnd
(N
))
10777 Has_No_Obvious_Side_Effects
(Right_Opnd
(N
));
10779 elsif Nkind
(N
) = N_Expression_With_Actions
10780 and then Is_Empty_List
(Actions
(N
))
10782 return Has_No_Obvious_Side_Effects
(Expression
(N
));
10784 elsif Nkind
(N
) in N_Has_Entity
then
10785 return Present
(Entity
(N
))
10786 and then Ekind_In
(Entity
(N
), E_Variable
,
10788 E_Enumeration_Literal
,
10791 E_In_Out_Parameter
)
10792 and then not Is_Volatile
(Entity
(N
));
10797 end Has_No_Obvious_Side_Effects
;
10799 -----------------------------
10800 -- Has_Non_Null_Refinement --
10801 -----------------------------
10803 function Has_Non_Null_Refinement
(Id
: Entity_Id
) return Boolean is
10804 Constits
: Elist_Id
;
10807 pragma Assert
(Ekind
(Id
) = E_Abstract_State
);
10808 Constits
:= Refinement_Constituents
(Id
);
10810 -- For a refinement to be non-null, the first constituent must be
10811 -- anything other than null.
10815 and then Nkind
(Node
(First_Elmt
(Constits
))) /= N_Null
;
10816 end Has_Non_Null_Refinement
;
10818 ----------------------------------
10819 -- Has_Non_Trivial_Precondition --
10820 ----------------------------------
10822 function Has_Non_Trivial_Precondition
(Subp
: Entity_Id
) return Boolean is
10823 Pre
: constant Node_Id
:= Find_Aspect
(Subp
, Aspect_Pre
);
10828 and then Class_Present
(Pre
)
10829 and then not Is_Entity_Name
(Expression
(Pre
));
10830 end Has_Non_Trivial_Precondition
;
10832 -------------------
10833 -- Has_Null_Body --
10834 -------------------
10836 function Has_Null_Body
(Proc_Id
: Entity_Id
) return Boolean is
10837 Body_Id
: Entity_Id
;
10844 Spec
:= Parent
(Proc_Id
);
10845 Decl
:= Parent
(Spec
);
10847 -- Retrieve the entity of the procedure body (e.g. invariant proc).
10849 if Nkind
(Spec
) = N_Procedure_Specification
10850 and then Nkind
(Decl
) = N_Subprogram_Declaration
10852 Body_Id
:= Corresponding_Body
(Decl
);
10854 -- The body acts as a spec
10857 Body_Id
:= Proc_Id
;
10860 -- The body will be generated later
10862 if No
(Body_Id
) then
10866 Spec
:= Parent
(Body_Id
);
10867 Decl
:= Parent
(Spec
);
10870 (Nkind
(Spec
) = N_Procedure_Specification
10871 and then Nkind
(Decl
) = N_Subprogram_Body
);
10873 Stmt1
:= First
(Statements
(Handled_Statement_Sequence
(Decl
)));
10875 -- Look for a null statement followed by an optional return
10878 if Nkind
(Stmt1
) = N_Null_Statement
then
10879 Stmt2
:= Next
(Stmt1
);
10881 if Present
(Stmt2
) then
10882 return Nkind
(Stmt2
) = N_Simple_Return_Statement
;
10891 ------------------------
10892 -- Has_Null_Exclusion --
10893 ------------------------
10895 function Has_Null_Exclusion
(N
: Node_Id
) return Boolean is
10898 when N_Access_Definition
10899 | N_Access_Function_Definition
10900 | N_Access_Procedure_Definition
10901 | N_Access_To_Object_Definition
10903 | N_Derived_Type_Definition
10904 | N_Function_Specification
10905 | N_Subtype_Declaration
10907 return Null_Exclusion_Present
(N
);
10909 when N_Component_Definition
10910 | N_Formal_Object_Declaration
10911 | N_Object_Renaming_Declaration
10913 if Present
(Subtype_Mark
(N
)) then
10914 return Null_Exclusion_Present
(N
);
10915 else pragma Assert
(Present
(Access_Definition
(N
)));
10916 return Null_Exclusion_Present
(Access_Definition
(N
));
10919 when N_Discriminant_Specification
=>
10920 if Nkind
(Discriminant_Type
(N
)) = N_Access_Definition
then
10921 return Null_Exclusion_Present
(Discriminant_Type
(N
));
10923 return Null_Exclusion_Present
(N
);
10926 when N_Object_Declaration
=>
10927 if Nkind
(Object_Definition
(N
)) = N_Access_Definition
then
10928 return Null_Exclusion_Present
(Object_Definition
(N
));
10930 return Null_Exclusion_Present
(N
);
10933 when N_Parameter_Specification
=>
10934 if Nkind
(Parameter_Type
(N
)) = N_Access_Definition
then
10935 return Null_Exclusion_Present
(Parameter_Type
(N
));
10937 return Null_Exclusion_Present
(N
);
10943 end Has_Null_Exclusion
;
10945 ------------------------
10946 -- Has_Null_Extension --
10947 ------------------------
10949 function Has_Null_Extension
(T
: Entity_Id
) return Boolean is
10950 B
: constant Entity_Id
:= Base_Type
(T
);
10955 if Nkind
(Parent
(B
)) = N_Full_Type_Declaration
10956 and then Present
(Record_Extension_Part
(Type_Definition
(Parent
(B
))))
10958 Ext
:= Record_Extension_Part
(Type_Definition
(Parent
(B
)));
10960 if Present
(Ext
) then
10961 if Null_Present
(Ext
) then
10964 Comps
:= Component_List
(Ext
);
10966 -- The null component list is rewritten during analysis to
10967 -- include the parent component. Any other component indicates
10968 -- that the extension was not originally null.
10970 return Null_Present
(Comps
)
10971 or else No
(Next
(First
(Component_Items
(Comps
))));
10980 end Has_Null_Extension
;
10982 -------------------------
10983 -- Has_Null_Refinement --
10984 -------------------------
10986 function Has_Null_Refinement
(Id
: Entity_Id
) return Boolean is
10987 Constits
: Elist_Id
;
10990 pragma Assert
(Ekind
(Id
) = E_Abstract_State
);
10991 Constits
:= Refinement_Constituents
(Id
);
10993 -- For a refinement to be null, the state's sole constituent must be a
10998 and then Nkind
(Node
(First_Elmt
(Constits
))) = N_Null
;
10999 end Has_Null_Refinement
;
11001 -------------------------------
11002 -- Has_Overriding_Initialize --
11003 -------------------------------
11005 function Has_Overriding_Initialize
(T
: Entity_Id
) return Boolean is
11006 BT
: constant Entity_Id
:= Base_Type
(T
);
11010 if Is_Controlled
(BT
) then
11011 if Is_RTU
(Scope
(BT
), Ada_Finalization
) then
11014 elsif Present
(Primitive_Operations
(BT
)) then
11015 P
:= First_Elmt
(Primitive_Operations
(BT
));
11016 while Present
(P
) loop
11018 Init
: constant Entity_Id
:= Node
(P
);
11019 Formal
: constant Entity_Id
:= First_Formal
(Init
);
11021 if Ekind
(Init
) = E_Procedure
11022 and then Chars
(Init
) = Name_Initialize
11023 and then Comes_From_Source
(Init
)
11024 and then Present
(Formal
)
11025 and then Etype
(Formal
) = BT
11026 and then No
(Next_Formal
(Formal
))
11027 and then (Ada_Version
< Ada_2012
11028 or else not Null_Present
(Parent
(Init
)))
11038 -- Here if type itself does not have a non-null Initialize operation:
11039 -- check immediate ancestor.
11041 if Is_Derived_Type
(BT
)
11042 and then Has_Overriding_Initialize
(Etype
(BT
))
11049 end Has_Overriding_Initialize
;
11051 --------------------------------------
11052 -- Has_Preelaborable_Initialization --
11053 --------------------------------------
11055 function Has_Preelaborable_Initialization
(E
: Entity_Id
) return Boolean is
11058 procedure Check_Components
(E
: Entity_Id
);
11059 -- Check component/discriminant chain, sets Has_PE False if a component
11060 -- or discriminant does not meet the preelaborable initialization rules.
11062 ----------------------
11063 -- Check_Components --
11064 ----------------------
11066 procedure Check_Components
(E
: Entity_Id
) is
11071 -- Loop through entities of record or protected type
11074 while Present
(Ent
) loop
11076 -- We are interested only in components and discriminants
11080 case Ekind
(Ent
) is
11081 when E_Component
=>
11083 -- Get default expression if any. If there is no declaration
11084 -- node, it means we have an internal entity. The parent and
11085 -- tag fields are examples of such entities. For such cases,
11086 -- we just test the type of the entity.
11088 if Present
(Declaration_Node
(Ent
)) then
11089 Exp
:= Expression
(Declaration_Node
(Ent
));
11092 when E_Discriminant
=>
11094 -- Note: for a renamed discriminant, the Declaration_Node
11095 -- may point to the one from the ancestor, and have a
11096 -- different expression, so use the proper attribute to
11097 -- retrieve the expression from the derived constraint.
11099 Exp
:= Discriminant_Default_Value
(Ent
);
11102 goto Check_Next_Entity
;
11105 -- A component has PI if it has no default expression and the
11106 -- component type has PI.
11109 if not Has_Preelaborable_Initialization
(Etype
(Ent
)) then
11114 -- Require the default expression to be preelaborable
11116 elsif not Is_Preelaborable_Construct
(Exp
) then
11121 <<Check_Next_Entity
>>
11124 end Check_Components
;
11126 -- Start of processing for Has_Preelaborable_Initialization
11129 -- Immediate return if already marked as known preelaborable init. This
11130 -- covers types for which this function has already been called once
11131 -- and returned True (in which case the result is cached), and also
11132 -- types to which a pragma Preelaborable_Initialization applies.
11134 if Known_To_Have_Preelab_Init
(E
) then
11138 -- If the type is a subtype representing a generic actual type, then
11139 -- test whether its base type has preelaborable initialization since
11140 -- the subtype representing the actual does not inherit this attribute
11141 -- from the actual or formal. (but maybe it should???)
11143 if Is_Generic_Actual_Type
(E
) then
11144 return Has_Preelaborable_Initialization
(Base_Type
(E
));
11147 -- All elementary types have preelaborable initialization
11149 if Is_Elementary_Type
(E
) then
11152 -- Array types have PI if the component type has PI
11154 elsif Is_Array_Type
(E
) then
11155 Has_PE
:= Has_Preelaborable_Initialization
(Component_Type
(E
));
11157 -- A derived type has preelaborable initialization if its parent type
11158 -- has preelaborable initialization and (in the case of a derived record
11159 -- extension) if the non-inherited components all have preelaborable
11160 -- initialization. However, a user-defined controlled type with an
11161 -- overriding Initialize procedure does not have preelaborable
11164 elsif Is_Derived_Type
(E
) then
11166 -- If the derived type is a private extension then it doesn't have
11167 -- preelaborable initialization.
11169 if Ekind
(Base_Type
(E
)) = E_Record_Type_With_Private
then
11173 -- First check whether ancestor type has preelaborable initialization
11175 Has_PE
:= Has_Preelaborable_Initialization
(Etype
(Base_Type
(E
)));
11177 -- If OK, check extension components (if any)
11179 if Has_PE
and then Is_Record_Type
(E
) then
11180 Check_Components
(First_Entity
(E
));
11183 -- Check specifically for 10.2.1(11.4/2) exception: a controlled type
11184 -- with a user defined Initialize procedure does not have PI. If
11185 -- the type is untagged, the control primitives come from a component
11186 -- that has already been checked.
11189 and then Is_Controlled
(E
)
11190 and then Is_Tagged_Type
(E
)
11191 and then Has_Overriding_Initialize
(E
)
11196 -- Private types not derived from a type having preelaborable init and
11197 -- that are not marked with pragma Preelaborable_Initialization do not
11198 -- have preelaborable initialization.
11200 elsif Is_Private_Type
(E
) then
11203 -- Record type has PI if it is non private and all components have PI
11205 elsif Is_Record_Type
(E
) then
11207 Check_Components
(First_Entity
(E
));
11209 -- Protected types must not have entries, and components must meet
11210 -- same set of rules as for record components.
11212 elsif Is_Protected_Type
(E
) then
11213 if Has_Entries
(E
) then
11217 Check_Components
(First_Entity
(E
));
11218 Check_Components
(First_Private_Entity
(E
));
11221 -- Type System.Address always has preelaborable initialization
11223 elsif Is_RTE
(E
, RE_Address
) then
11226 -- In all other cases, type does not have preelaborable initialization
11232 -- If type has preelaborable initialization, cache result
11235 Set_Known_To_Have_Preelab_Init
(E
);
11239 end Has_Preelaborable_Initialization
;
11241 ---------------------------
11242 -- Has_Private_Component --
11243 ---------------------------
11245 function Has_Private_Component
(Type_Id
: Entity_Id
) return Boolean is
11246 Btype
: Entity_Id
:= Base_Type
(Type_Id
);
11247 Component
: Entity_Id
;
11250 if Error_Posted
(Type_Id
)
11251 or else Error_Posted
(Btype
)
11256 if Is_Class_Wide_Type
(Btype
) then
11257 Btype
:= Root_Type
(Btype
);
11260 if Is_Private_Type
(Btype
) then
11262 UT
: constant Entity_Id
:= Underlying_Type
(Btype
);
11265 if No
(Full_View
(Btype
)) then
11266 return not Is_Generic_Type
(Btype
)
11268 not Is_Generic_Type
(Root_Type
(Btype
));
11270 return not Is_Generic_Type
(Root_Type
(Full_View
(Btype
)));
11273 return not Is_Frozen
(UT
) and then Has_Private_Component
(UT
);
11277 elsif Is_Array_Type
(Btype
) then
11278 return Has_Private_Component
(Component_Type
(Btype
));
11280 elsif Is_Record_Type
(Btype
) then
11281 Component
:= First_Component
(Btype
);
11282 while Present
(Component
) loop
11283 if Has_Private_Component
(Etype
(Component
)) then
11287 Next_Component
(Component
);
11292 elsif Is_Protected_Type
(Btype
)
11293 and then Present
(Corresponding_Record_Type
(Btype
))
11295 return Has_Private_Component
(Corresponding_Record_Type
(Btype
));
11300 end Has_Private_Component
;
11302 ----------------------
11303 -- Has_Signed_Zeros --
11304 ----------------------
11306 function Has_Signed_Zeros
(E
: Entity_Id
) return Boolean is
11308 return Is_Floating_Point_Type
(E
) and then Signed_Zeros_On_Target
;
11309 end Has_Signed_Zeros
;
11311 ------------------------------
11312 -- Has_Significant_Contract --
11313 ------------------------------
11315 function Has_Significant_Contract
(Subp_Id
: Entity_Id
) return Boolean is
11316 Subp_Nam
: constant Name_Id
:= Chars
(Subp_Id
);
11319 -- _Finalizer procedure
11321 if Subp_Nam
= Name_uFinalizer
then
11324 -- _Postconditions procedure
11326 elsif Subp_Nam
= Name_uPostconditions
then
11329 -- Predicate function
11331 elsif Ekind
(Subp_Id
) = E_Function
11332 and then Is_Predicate_Function
(Subp_Id
)
11338 elsif Get_TSS_Name
(Subp_Id
) /= TSS_Null
then
11344 end Has_Significant_Contract
;
11346 -----------------------------
11347 -- Has_Static_Array_Bounds --
11348 -----------------------------
11350 function Has_Static_Array_Bounds
(Typ
: Node_Id
) return Boolean is
11351 Ndims
: constant Nat
:= Number_Dimensions
(Typ
);
11358 -- Unconstrained types do not have static bounds
11360 if not Is_Constrained
(Typ
) then
11364 -- First treat string literals specially, as the lower bound and length
11365 -- of string literals are not stored like those of arrays.
11367 -- A string literal always has static bounds
11369 if Ekind
(Typ
) = E_String_Literal_Subtype
then
11373 -- Treat all dimensions in turn
11375 Index
:= First_Index
(Typ
);
11376 for Indx
in 1 .. Ndims
loop
11378 -- In case of an illegal index which is not a discrete type, return
11379 -- that the type is not static.
11381 if not Is_Discrete_Type
(Etype
(Index
))
11382 or else Etype
(Index
) = Any_Type
11387 Get_Index_Bounds
(Index
, Low
, High
);
11389 if Error_Posted
(Low
) or else Error_Posted
(High
) then
11393 if Is_OK_Static_Expression
(Low
)
11395 Is_OK_Static_Expression
(High
)
11405 -- If we fall through the loop, all indexes matched
11408 end Has_Static_Array_Bounds
;
11414 function Has_Stream
(T
: Entity_Id
) return Boolean is
11421 elsif Is_RTE
(Root_Type
(T
), RE_Root_Stream_Type
) then
11424 elsif Is_Array_Type
(T
) then
11425 return Has_Stream
(Component_Type
(T
));
11427 elsif Is_Record_Type
(T
) then
11428 E
:= First_Component
(T
);
11429 while Present
(E
) loop
11430 if Has_Stream
(Etype
(E
)) then
11433 Next_Component
(E
);
11439 elsif Is_Private_Type
(T
) then
11440 return Has_Stream
(Underlying_Type
(T
));
11451 function Has_Suffix
(E
: Entity_Id
; Suffix
: Character) return Boolean is
11453 Get_Name_String
(Chars
(E
));
11454 return Name_Buffer
(Name_Len
) = Suffix
;
11461 function Add_Suffix
(E
: Entity_Id
; Suffix
: Character) return Name_Id
is
11463 Get_Name_String
(Chars
(E
));
11464 Add_Char_To_Name_Buffer
(Suffix
);
11468 -------------------
11469 -- Remove_Suffix --
11470 -------------------
11472 function Remove_Suffix
(E
: Entity_Id
; Suffix
: Character) return Name_Id
is
11474 pragma Assert
(Has_Suffix
(E
, Suffix
));
11475 Get_Name_String
(Chars
(E
));
11476 Name_Len
:= Name_Len
- 1;
11480 ----------------------------------
11481 -- Replace_Null_By_Null_Address --
11482 ----------------------------------
11484 procedure Replace_Null_By_Null_Address
(N
: Node_Id
) is
11485 procedure Replace_Null_Operand
(Op
: Node_Id
; Other_Op
: Node_Id
);
11486 -- Replace operand Op with a reference to Null_Address when the operand
11487 -- denotes a null Address. Other_Op denotes the other operand.
11489 --------------------------
11490 -- Replace_Null_Operand --
11491 --------------------------
11493 procedure Replace_Null_Operand
(Op
: Node_Id
; Other_Op
: Node_Id
) is
11495 -- Check the type of the complementary operand since the N_Null node
11496 -- has not been decorated yet.
11498 if Nkind
(Op
) = N_Null
11499 and then Is_Descendant_Of_Address
(Etype
(Other_Op
))
11501 Rewrite
(Op
, New_Occurrence_Of
(RTE
(RE_Null_Address
), Sloc
(Op
)));
11503 end Replace_Null_Operand
;
11505 -- Start of processing for Replace_Null_By_Null_Address
11508 pragma Assert
(Relaxed_RM_Semantics
);
11509 pragma Assert
(Nkind_In
(N
, N_Null
,
11517 if Nkind
(N
) = N_Null
then
11518 Rewrite
(N
, New_Occurrence_Of
(RTE
(RE_Null_Address
), Sloc
(N
)));
11522 L
: constant Node_Id
:= Left_Opnd
(N
);
11523 R
: constant Node_Id
:= Right_Opnd
(N
);
11526 Replace_Null_Operand
(L
, Other_Op
=> R
);
11527 Replace_Null_Operand
(R
, Other_Op
=> L
);
11530 end Replace_Null_By_Null_Address
;
11532 --------------------------
11533 -- Has_Tagged_Component --
11534 --------------------------
11536 function Has_Tagged_Component
(Typ
: Entity_Id
) return Boolean is
11540 if Is_Private_Type
(Typ
) and then Present
(Underlying_Type
(Typ
)) then
11541 return Has_Tagged_Component
(Underlying_Type
(Typ
));
11543 elsif Is_Array_Type
(Typ
) then
11544 return Has_Tagged_Component
(Component_Type
(Typ
));
11546 elsif Is_Tagged_Type
(Typ
) then
11549 elsif Is_Record_Type
(Typ
) then
11550 Comp
:= First_Component
(Typ
);
11551 while Present
(Comp
) loop
11552 if Has_Tagged_Component
(Etype
(Comp
)) then
11556 Next_Component
(Comp
);
11564 end Has_Tagged_Component
;
11566 -----------------------------
11567 -- Has_Undefined_Reference --
11568 -----------------------------
11570 function Has_Undefined_Reference
(Expr
: Node_Id
) return Boolean is
11571 Has_Undef_Ref
: Boolean := False;
11572 -- Flag set when expression Expr contains at least one undefined
11575 function Is_Undefined_Reference
(N
: Node_Id
) return Traverse_Result
;
11576 -- Determine whether N denotes a reference and if it does, whether it is
11579 ----------------------------
11580 -- Is_Undefined_Reference --
11581 ----------------------------
11583 function Is_Undefined_Reference
(N
: Node_Id
) return Traverse_Result
is
11585 if Is_Entity_Name
(N
)
11586 and then Present
(Entity
(N
))
11587 and then Entity
(N
) = Any_Id
11589 Has_Undef_Ref
:= True;
11594 end Is_Undefined_Reference
;
11596 procedure Find_Undefined_References
is
11597 new Traverse_Proc
(Is_Undefined_Reference
);
11599 -- Start of processing for Has_Undefined_Reference
11602 Find_Undefined_References
(Expr
);
11604 return Has_Undef_Ref
;
11605 end Has_Undefined_Reference
;
11607 ----------------------------
11608 -- Has_Volatile_Component --
11609 ----------------------------
11611 function Has_Volatile_Component
(Typ
: Entity_Id
) return Boolean is
11615 if Has_Volatile_Components
(Typ
) then
11618 elsif Is_Array_Type
(Typ
) then
11619 return Is_Volatile
(Component_Type
(Typ
));
11621 elsif Is_Record_Type
(Typ
) then
11622 Comp
:= First_Component
(Typ
);
11623 while Present
(Comp
) loop
11624 if Is_Volatile_Object
(Comp
) then
11628 Comp
:= Next_Component
(Comp
);
11633 end Has_Volatile_Component
;
11635 -------------------------
11636 -- Implementation_Kind --
11637 -------------------------
11639 function Implementation_Kind
(Subp
: Entity_Id
) return Name_Id
is
11640 Impl_Prag
: constant Node_Id
:= Get_Rep_Pragma
(Subp
, Name_Implemented
);
11643 pragma Assert
(Present
(Impl_Prag
));
11644 Arg
:= Last
(Pragma_Argument_Associations
(Impl_Prag
));
11645 return Chars
(Get_Pragma_Arg
(Arg
));
11646 end Implementation_Kind
;
11648 --------------------------
11649 -- Implements_Interface --
11650 --------------------------
11652 function Implements_Interface
11653 (Typ_Ent
: Entity_Id
;
11654 Iface_Ent
: Entity_Id
;
11655 Exclude_Parents
: Boolean := False) return Boolean
11657 Ifaces_List
: Elist_Id
;
11659 Iface
: Entity_Id
:= Base_Type
(Iface_Ent
);
11660 Typ
: Entity_Id
:= Base_Type
(Typ_Ent
);
11663 if Is_Class_Wide_Type
(Typ
) then
11664 Typ
:= Root_Type
(Typ
);
11667 if not Has_Interfaces
(Typ
) then
11671 if Is_Class_Wide_Type
(Iface
) then
11672 Iface
:= Root_Type
(Iface
);
11675 Collect_Interfaces
(Typ
, Ifaces_List
);
11677 Elmt
:= First_Elmt
(Ifaces_List
);
11678 while Present
(Elmt
) loop
11679 if Is_Ancestor
(Node
(Elmt
), Typ
, Use_Full_View
=> True)
11680 and then Exclude_Parents
11684 elsif Node
(Elmt
) = Iface
then
11692 end Implements_Interface
;
11694 ------------------------------------
11695 -- In_Assertion_Expression_Pragma --
11696 ------------------------------------
11698 function In_Assertion_Expression_Pragma
(N
: Node_Id
) return Boolean is
11700 Prag
: Node_Id
:= Empty
;
11703 -- Climb the parent chain looking for an enclosing pragma
11706 while Present
(Par
) loop
11707 if Nkind
(Par
) = N_Pragma
then
11711 -- Precondition-like pragmas are expanded into if statements, check
11712 -- the original node instead.
11714 elsif Nkind
(Original_Node
(Par
)) = N_Pragma
then
11715 Prag
:= Original_Node
(Par
);
11718 -- The expansion of attribute 'Old generates a constant to capture
11719 -- the result of the prefix. If the parent traversal reaches
11720 -- one of these constants, then the node technically came from a
11721 -- postcondition-like pragma. Note that the Ekind is not tested here
11722 -- because N may be the expression of an object declaration which is
11723 -- currently being analyzed. Such objects carry Ekind of E_Void.
11725 elsif Nkind
(Par
) = N_Object_Declaration
11726 and then Constant_Present
(Par
)
11727 and then Stores_Attribute_Old_Prefix
(Defining_Entity
(Par
))
11731 -- Prevent the search from going too far
11733 elsif Is_Body_Or_Package_Declaration
(Par
) then
11737 Par
:= Parent
(Par
);
11742 and then Assertion_Expression_Pragma
(Get_Pragma_Id
(Prag
));
11743 end In_Assertion_Expression_Pragma
;
11745 ----------------------
11746 -- In_Generic_Scope --
11747 ----------------------
11749 function In_Generic_Scope
(E
: Entity_Id
) return Boolean is
11754 while Present
(S
) and then S
/= Standard_Standard
loop
11755 if Is_Generic_Unit
(S
) then
11763 end In_Generic_Scope
;
11769 function In_Instance
return Boolean is
11770 Curr_Unit
: constant Entity_Id
:= Cunit_Entity
(Current_Sem_Unit
);
11774 S
:= Current_Scope
;
11775 while Present
(S
) and then S
/= Standard_Standard
loop
11776 if Is_Generic_Instance
(S
) then
11778 -- A child instance is always compiled in the context of a parent
11779 -- instance. Nevertheless, the actuals are not analyzed in an
11780 -- instance context. We detect this case by examining the current
11781 -- compilation unit, which must be a child instance, and checking
11782 -- that it is not currently on the scope stack.
11784 if Is_Child_Unit
(Curr_Unit
)
11785 and then Nkind
(Unit
(Cunit
(Current_Sem_Unit
))) =
11786 N_Package_Instantiation
11787 and then not In_Open_Scopes
(Curr_Unit
)
11801 ----------------------
11802 -- In_Instance_Body --
11803 ----------------------
11805 function In_Instance_Body
return Boolean is
11809 S
:= Current_Scope
;
11810 while Present
(S
) and then S
/= Standard_Standard
loop
11811 if Ekind_In
(S
, E_Function
, E_Procedure
)
11812 and then Is_Generic_Instance
(S
)
11816 elsif Ekind
(S
) = E_Package
11817 and then In_Package_Body
(S
)
11818 and then Is_Generic_Instance
(S
)
11827 end In_Instance_Body
;
11829 -----------------------------
11830 -- In_Instance_Not_Visible --
11831 -----------------------------
11833 function In_Instance_Not_Visible
return Boolean is
11837 S
:= Current_Scope
;
11838 while Present
(S
) and then S
/= Standard_Standard
loop
11839 if Ekind_In
(S
, E_Function
, E_Procedure
)
11840 and then Is_Generic_Instance
(S
)
11844 elsif Ekind
(S
) = E_Package
11845 and then (In_Package_Body
(S
) or else In_Private_Part
(S
))
11846 and then Is_Generic_Instance
(S
)
11855 end In_Instance_Not_Visible
;
11857 ------------------------------
11858 -- In_Instance_Visible_Part --
11859 ------------------------------
11861 function In_Instance_Visible_Part
11862 (Id
: Entity_Id
:= Current_Scope
) return Boolean
11868 while Present
(Inst
) and then Inst
/= Standard_Standard
loop
11869 if Ekind
(Inst
) = E_Package
11870 and then Is_Generic_Instance
(Inst
)
11871 and then not In_Package_Body
(Inst
)
11872 and then not In_Private_Part
(Inst
)
11877 Inst
:= Scope
(Inst
);
11881 end In_Instance_Visible_Part
;
11883 ---------------------
11884 -- In_Package_Body --
11885 ---------------------
11887 function In_Package_Body
return Boolean is
11891 S
:= Current_Scope
;
11892 while Present
(S
) and then S
/= Standard_Standard
loop
11893 if Ekind
(S
) = E_Package
and then In_Package_Body
(S
) then
11901 end In_Package_Body
;
11903 --------------------------
11904 -- In_Pragma_Expression --
11905 --------------------------
11907 function In_Pragma_Expression
(N
: Node_Id
; Nam
: Name_Id
) return Boolean is
11914 elsif Nkind
(P
) = N_Pragma
and then Pragma_Name
(P
) = Nam
then
11920 end In_Pragma_Expression
;
11922 ---------------------------
11923 -- In_Pre_Post_Condition --
11924 ---------------------------
11926 function In_Pre_Post_Condition
(N
: Node_Id
) return Boolean is
11928 Prag
: Node_Id
:= Empty
;
11929 Prag_Id
: Pragma_Id
;
11932 -- Climb the parent chain looking for an enclosing pragma
11935 while Present
(Par
) loop
11936 if Nkind
(Par
) = N_Pragma
then
11940 -- Prevent the search from going too far
11942 elsif Is_Body_Or_Package_Declaration
(Par
) then
11946 Par
:= Parent
(Par
);
11949 if Present
(Prag
) then
11950 Prag_Id
:= Get_Pragma_Id
(Prag
);
11953 Prag_Id
= Pragma_Post
11954 or else Prag_Id
= Pragma_Post_Class
11955 or else Prag_Id
= Pragma_Postcondition
11956 or else Prag_Id
= Pragma_Pre
11957 or else Prag_Id
= Pragma_Pre_Class
11958 or else Prag_Id
= Pragma_Precondition
;
11960 -- Otherwise the node is not enclosed by a pre/postcondition pragma
11965 end In_Pre_Post_Condition
;
11967 -------------------------------------
11968 -- In_Reverse_Storage_Order_Object --
11969 -------------------------------------
11971 function In_Reverse_Storage_Order_Object
(N
: Node_Id
) return Boolean is
11973 Btyp
: Entity_Id
:= Empty
;
11976 -- Climb up indexed components
11980 case Nkind
(Pref
) is
11981 when N_Selected_Component
=>
11982 Pref
:= Prefix
(Pref
);
11985 when N_Indexed_Component
=>
11986 Pref
:= Prefix
(Pref
);
11994 if Present
(Pref
) then
11995 Btyp
:= Base_Type
(Etype
(Pref
));
11998 return Present
(Btyp
)
11999 and then (Is_Record_Type
(Btyp
) or else Is_Array_Type
(Btyp
))
12000 and then Reverse_Storage_Order
(Btyp
);
12001 end In_Reverse_Storage_Order_Object
;
12003 --------------------------------------
12004 -- In_Subprogram_Or_Concurrent_Unit --
12005 --------------------------------------
12007 function In_Subprogram_Or_Concurrent_Unit
return Boolean is
12012 -- Use scope chain to check successively outer scopes
12014 E
:= Current_Scope
;
12018 if K
in Subprogram_Kind
12019 or else K
in Concurrent_Kind
12020 or else K
in Generic_Subprogram_Kind
12024 elsif E
= Standard_Standard
then
12030 end In_Subprogram_Or_Concurrent_Unit
;
12036 function In_Subtree
(N
: Node_Id
; Root
: Node_Id
) return Boolean is
12041 while Present
(Curr
) loop
12042 if Curr
= Root
then
12046 Curr
:= Parent
(Curr
);
12056 function In_Subtree
12059 Root2
: Node_Id
) return Boolean
12065 while Present
(Curr
) loop
12066 if Curr
= Root1
or else Curr
= Root2
then
12070 Curr
:= Parent
(Curr
);
12076 ---------------------
12077 -- In_Visible_Part --
12078 ---------------------
12080 function In_Visible_Part
(Scope_Id
: Entity_Id
) return Boolean is
12082 return Is_Package_Or_Generic_Package
(Scope_Id
)
12083 and then In_Open_Scopes
(Scope_Id
)
12084 and then not In_Package_Body
(Scope_Id
)
12085 and then not In_Private_Part
(Scope_Id
);
12086 end In_Visible_Part
;
12088 --------------------------------
12089 -- Incomplete_Or_Partial_View --
12090 --------------------------------
12092 function Incomplete_Or_Partial_View
(Id
: Entity_Id
) return Entity_Id
is
12093 function Inspect_Decls
12095 Taft
: Boolean := False) return Entity_Id
;
12096 -- Check whether a declarative region contains the incomplete or partial
12099 -------------------
12100 -- Inspect_Decls --
12101 -------------------
12103 function Inspect_Decls
12105 Taft
: Boolean := False) return Entity_Id
12111 Decl
:= First
(Decls
);
12112 while Present
(Decl
) loop
12115 -- The partial view of a Taft-amendment type is an incomplete
12119 if Nkind
(Decl
) = N_Incomplete_Type_Declaration
then
12120 Match
:= Defining_Identifier
(Decl
);
12123 -- Otherwise look for a private type whose full view matches the
12124 -- input type. Note that this checks full_type_declaration nodes
12125 -- to account for derivations from a private type where the type
12126 -- declaration hold the partial view and the full view is an
12129 elsif Nkind_In
(Decl
, N_Full_Type_Declaration
,
12130 N_Private_Extension_Declaration
,
12131 N_Private_Type_Declaration
)
12133 Match
:= Defining_Identifier
(Decl
);
12136 -- Guard against unanalyzed entities
12139 and then Is_Type
(Match
)
12140 and then Present
(Full_View
(Match
))
12141 and then Full_View
(Match
) = Id
12156 -- Start of processing for Incomplete_Or_Partial_View
12159 -- Deferred constant or incomplete type case
12161 Prev
:= Current_Entity_In_Scope
(Id
);
12164 and then (Is_Incomplete_Type
(Prev
) or else Ekind
(Prev
) = E_Constant
)
12165 and then Present
(Full_View
(Prev
))
12166 and then Full_View
(Prev
) = Id
12171 -- Private or Taft amendment type case
12174 Pkg
: constant Entity_Id
:= Scope
(Id
);
12175 Pkg_Decl
: Node_Id
:= Pkg
;
12179 and then Ekind_In
(Pkg
, E_Generic_Package
, E_Package
)
12181 while Nkind
(Pkg_Decl
) /= N_Package_Specification
loop
12182 Pkg_Decl
:= Parent
(Pkg_Decl
);
12185 -- It is knows that Typ has a private view, look for it in the
12186 -- visible declarations of the enclosing scope. A special case
12187 -- of this is when the two views have been exchanged - the full
12188 -- appears earlier than the private.
12190 if Has_Private_Declaration
(Id
) then
12191 Prev
:= Inspect_Decls
(Visible_Declarations
(Pkg_Decl
));
12193 -- Exchanged view case, look in the private declarations
12196 Prev
:= Inspect_Decls
(Private_Declarations
(Pkg_Decl
));
12201 -- Otherwise if this is the package body, then Typ is a potential
12202 -- Taft amendment type. The incomplete view should be located in
12203 -- the private declarations of the enclosing scope.
12205 elsif In_Package_Body
(Pkg
) then
12206 return Inspect_Decls
(Private_Declarations
(Pkg_Decl
), True);
12211 -- The type has no incomplete or private view
12214 end Incomplete_Or_Partial_View
;
12216 ---------------------------------------
12217 -- Incomplete_View_From_Limited_With --
12218 ---------------------------------------
12220 function Incomplete_View_From_Limited_With
12221 (Typ
: Entity_Id
) return Entity_Id
is
12223 -- It might make sense to make this an attribute in Einfo, and set it
12224 -- in Sem_Ch10 in Build_Shadow_Entity. However, we're running short on
12225 -- slots for new attributes, and it seems a bit simpler to just search
12226 -- the Limited_View (if it exists) for an incomplete type whose
12227 -- Non_Limited_View is Typ.
12229 if Ekind
(Scope
(Typ
)) = E_Package
12230 and then Present
(Limited_View
(Scope
(Typ
)))
12233 Ent
: Entity_Id
:= First_Entity
(Limited_View
(Scope
(Typ
)));
12235 while Present
(Ent
) loop
12236 if Ekind
(Ent
) in Incomplete_Kind
12237 and then Non_Limited_View
(Ent
) = Typ
12242 Ent
:= Next_Entity
(Ent
);
12248 end Incomplete_View_From_Limited_With
;
12250 ----------------------------------
12251 -- Indexed_Component_Bit_Offset --
12252 ----------------------------------
12254 function Indexed_Component_Bit_Offset
(N
: Node_Id
) return Uint
is
12255 Exp
: constant Node_Id
:= First
(Expressions
(N
));
12256 Typ
: constant Entity_Id
:= Etype
(Prefix
(N
));
12257 Off
: constant Uint
:= Component_Size
(Typ
);
12261 -- Return early if the component size is not known or variable
12263 if Off
= No_Uint
or else Off
< Uint_0
then
12267 -- Deal with the degenerate case of an empty component
12269 if Off
= Uint_0
then
12273 -- Check that both the index value and the low bound are known
12275 if not Compile_Time_Known_Value
(Exp
) then
12279 Ind
:= First_Index
(Typ
);
12284 if Nkind
(Ind
) = N_Subtype_Indication
then
12285 Ind
:= Constraint
(Ind
);
12287 if Nkind
(Ind
) = N_Range_Constraint
then
12288 Ind
:= Range_Expression
(Ind
);
12292 if Nkind
(Ind
) /= N_Range
12293 or else not Compile_Time_Known_Value
(Low_Bound
(Ind
))
12298 -- Return the scaled offset
12300 return Off
* (Expr_Value
(Exp
) - Expr_Value
(Low_Bound
((Ind
))));
12301 end Indexed_Component_Bit_Offset
;
12303 ----------------------------
12304 -- Inherit_Rep_Item_Chain --
12305 ----------------------------
12307 procedure Inherit_Rep_Item_Chain
(Typ
: Entity_Id
; From_Typ
: Entity_Id
) is
12309 Next_Item
: Node_Id
;
12312 -- There are several inheritance scenarios to consider depending on
12313 -- whether both types have rep item chains and whether the destination
12314 -- type already inherits part of the source type's rep item chain.
12316 -- 1) The source type lacks a rep item chain
12317 -- From_Typ ---> Empty
12319 -- Typ --------> Item (or Empty)
12321 -- In this case inheritance cannot take place because there are no items
12324 -- 2) The destination type lacks a rep item chain
12325 -- From_Typ ---> Item ---> ...
12327 -- Typ --------> Empty
12329 -- Inheritance takes place by setting the First_Rep_Item of the
12330 -- destination type to the First_Rep_Item of the source type.
12331 -- From_Typ ---> Item ---> ...
12333 -- Typ -----------+
12335 -- 3.1) Both source and destination types have at least one rep item.
12336 -- The destination type does NOT inherit a rep item from the source
12338 -- From_Typ ---> Item ---> Item
12340 -- Typ --------> Item ---> Item
12342 -- Inheritance takes place by setting the Next_Rep_Item of the last item
12343 -- of the destination type to the First_Rep_Item of the source type.
12344 -- From_Typ -------------------> Item ---> Item
12346 -- Typ --------> Item ---> Item --+
12348 -- 3.2) Both source and destination types have at least one rep item.
12349 -- The destination type DOES inherit part of the rep item chain of the
12351 -- From_Typ ---> Item ---> Item ---> Item
12353 -- Typ --------> Item ------+
12355 -- This rare case arises when the full view of a private extension must
12356 -- inherit the rep item chain from the full view of its parent type and
12357 -- the full view of the parent type contains extra rep items. Currently
12358 -- only invariants may lead to such form of inheritance.
12360 -- type From_Typ is tagged private
12361 -- with Type_Invariant'Class => Item_2;
12363 -- type Typ is new From_Typ with private
12364 -- with Type_Invariant => Item_4;
12366 -- At this point the rep item chains contain the following items
12368 -- From_Typ -----------> Item_2 ---> Item_3
12370 -- Typ --------> Item_4 --+
12372 -- The full views of both types may introduce extra invariants
12374 -- type From_Typ is tagged null record
12375 -- with Type_Invariant => Item_1;
12377 -- type Typ is new From_Typ with null record;
12379 -- The full view of Typ would have to inherit any new rep items added to
12380 -- the full view of From_Typ.
12382 -- From_Typ -----------> Item_1 ---> Item_2 ---> Item_3
12384 -- Typ --------> Item_4 --+
12386 -- To achieve this form of inheritance, the destination type must first
12387 -- sever the link between its own rep chain and that of the source type,
12388 -- then inheritance 3.1 takes place.
12390 -- Case 1: The source type lacks a rep item chain
12392 if No
(First_Rep_Item
(From_Typ
)) then
12395 -- Case 2: The destination type lacks a rep item chain
12397 elsif No
(First_Rep_Item
(Typ
)) then
12398 Set_First_Rep_Item
(Typ
, First_Rep_Item
(From_Typ
));
12400 -- Case 3: Both the source and destination types have at least one rep
12401 -- item. Traverse the rep item chain of the destination type to find the
12406 Next_Item
:= First_Rep_Item
(Typ
);
12407 while Present
(Next_Item
) loop
12409 -- Detect a link between the destination type's rep chain and that
12410 -- of the source type. There are two possibilities:
12415 -- From_Typ ---> Item_1 --->
12417 -- Typ -----------+
12424 -- From_Typ ---> Item_1 ---> Item_2 --->
12426 -- Typ --------> Item_3 ------+
12430 if Has_Rep_Item
(From_Typ
, Next_Item
) then
12435 Next_Item
:= Next_Rep_Item
(Next_Item
);
12438 -- Inherit the source type's rep item chain
12440 if Present
(Item
) then
12441 Set_Next_Rep_Item
(Item
, First_Rep_Item
(From_Typ
));
12443 Set_First_Rep_Item
(Typ
, First_Rep_Item
(From_Typ
));
12446 end Inherit_Rep_Item_Chain
;
12448 ---------------------------------
12449 -- Insert_Explicit_Dereference --
12450 ---------------------------------
12452 procedure Insert_Explicit_Dereference
(N
: Node_Id
) is
12453 New_Prefix
: constant Node_Id
:= Relocate_Node
(N
);
12454 Ent
: Entity_Id
:= Empty
;
12461 Save_Interps
(N
, New_Prefix
);
12464 Make_Explicit_Dereference
(Sloc
(Parent
(N
)),
12465 Prefix
=> New_Prefix
));
12467 Set_Etype
(N
, Designated_Type
(Etype
(New_Prefix
)));
12469 if Is_Overloaded
(New_Prefix
) then
12471 -- The dereference is also overloaded, and its interpretations are
12472 -- the designated types of the interpretations of the original node.
12474 Set_Etype
(N
, Any_Type
);
12476 Get_First_Interp
(New_Prefix
, I
, It
);
12477 while Present
(It
.Nam
) loop
12480 if Is_Access_Type
(T
) then
12481 Add_One_Interp
(N
, Designated_Type
(T
), Designated_Type
(T
));
12484 Get_Next_Interp
(I
, It
);
12490 -- Prefix is unambiguous: mark the original prefix (which might
12491 -- Come_From_Source) as a reference, since the new (relocated) one
12492 -- won't be taken into account.
12494 if Is_Entity_Name
(New_Prefix
) then
12495 Ent
:= Entity
(New_Prefix
);
12496 Pref
:= New_Prefix
;
12498 -- For a retrieval of a subcomponent of some composite object,
12499 -- retrieve the ultimate entity if there is one.
12501 elsif Nkind_In
(New_Prefix
, N_Selected_Component
,
12502 N_Indexed_Component
)
12504 Pref
:= Prefix
(New_Prefix
);
12505 while Present
(Pref
)
12506 and then Nkind_In
(Pref
, N_Selected_Component
,
12507 N_Indexed_Component
)
12509 Pref
:= Prefix
(Pref
);
12512 if Present
(Pref
) and then Is_Entity_Name
(Pref
) then
12513 Ent
:= Entity
(Pref
);
12517 -- Place the reference on the entity node
12519 if Present
(Ent
) then
12520 Generate_Reference
(Ent
, Pref
);
12523 end Insert_Explicit_Dereference
;
12525 ------------------------------------------
12526 -- Inspect_Deferred_Constant_Completion --
12527 ------------------------------------------
12529 procedure Inspect_Deferred_Constant_Completion
(Decls
: List_Id
) is
12533 Decl
:= First
(Decls
);
12534 while Present
(Decl
) loop
12536 -- Deferred constant signature
12538 if Nkind
(Decl
) = N_Object_Declaration
12539 and then Constant_Present
(Decl
)
12540 and then No
(Expression
(Decl
))
12542 -- No need to check internally generated constants
12544 and then Comes_From_Source
(Decl
)
12546 -- The constant is not completed. A full object declaration or a
12547 -- pragma Import complete a deferred constant.
12549 and then not Has_Completion
(Defining_Identifier
(Decl
))
12552 ("constant declaration requires initialization expression",
12553 Defining_Identifier
(Decl
));
12556 Decl
:= Next
(Decl
);
12558 end Inspect_Deferred_Constant_Completion
;
12560 -----------------------------
12561 -- Install_Generic_Formals --
12562 -----------------------------
12564 procedure Install_Generic_Formals
(Subp_Id
: Entity_Id
) is
12568 pragma Assert
(Is_Generic_Subprogram
(Subp_Id
));
12570 E
:= First_Entity
(Subp_Id
);
12571 while Present
(E
) loop
12572 Install_Entity
(E
);
12575 end Install_Generic_Formals
;
12577 ------------------------
12578 -- Install_SPARK_Mode --
12579 ------------------------
12581 procedure Install_SPARK_Mode
(Mode
: SPARK_Mode_Type
; Prag
: Node_Id
) is
12583 SPARK_Mode
:= Mode
;
12584 SPARK_Mode_Pragma
:= Prag
;
12585 end Install_SPARK_Mode
;
12587 -----------------------------
12588 -- Is_Actual_Out_Parameter --
12589 -----------------------------
12591 function Is_Actual_Out_Parameter
(N
: Node_Id
) return Boolean is
12592 Formal
: Entity_Id
;
12595 Find_Actual
(N
, Formal
, Call
);
12596 return Present
(Formal
) and then Ekind
(Formal
) = E_Out_Parameter
;
12597 end Is_Actual_Out_Parameter
;
12599 -------------------------
12600 -- Is_Actual_Parameter --
12601 -------------------------
12603 function Is_Actual_Parameter
(N
: Node_Id
) return Boolean is
12604 PK
: constant Node_Kind
:= Nkind
(Parent
(N
));
12608 when N_Parameter_Association
=>
12609 return N
= Explicit_Actual_Parameter
(Parent
(N
));
12611 when N_Subprogram_Call
=>
12612 return Is_List_Member
(N
)
12614 List_Containing
(N
) = Parameter_Associations
(Parent
(N
));
12619 end Is_Actual_Parameter
;
12621 --------------------------------
12622 -- Is_Actual_Tagged_Parameter --
12623 --------------------------------
12625 function Is_Actual_Tagged_Parameter
(N
: Node_Id
) return Boolean is
12626 Formal
: Entity_Id
;
12629 Find_Actual
(N
, Formal
, Call
);
12630 return Present
(Formal
) and then Is_Tagged_Type
(Etype
(Formal
));
12631 end Is_Actual_Tagged_Parameter
;
12633 ---------------------
12634 -- Is_Aliased_View --
12635 ---------------------
12637 function Is_Aliased_View
(Obj
: Node_Id
) return Boolean is
12641 if Is_Entity_Name
(Obj
) then
12648 or else (Present
(Renamed_Object
(E
))
12649 and then Is_Aliased_View
(Renamed_Object
(E
)))))
12651 or else ((Is_Formal
(E
) or else Is_Formal_Object
(E
))
12652 and then Is_Tagged_Type
(Etype
(E
)))
12654 or else (Is_Concurrent_Type
(E
) and then In_Open_Scopes
(E
))
12656 -- Current instance of type, either directly or as rewritten
12657 -- reference to the current object.
12659 or else (Is_Entity_Name
(Original_Node
(Obj
))
12660 and then Present
(Entity
(Original_Node
(Obj
)))
12661 and then Is_Type
(Entity
(Original_Node
(Obj
))))
12663 or else (Is_Type
(E
) and then E
= Current_Scope
)
12665 or else (Is_Incomplete_Or_Private_Type
(E
)
12666 and then Full_View
(E
) = Current_Scope
)
12668 -- Ada 2012 AI05-0053: the return object of an extended return
12669 -- statement is aliased if its type is immutably limited.
12671 or else (Is_Return_Object
(E
)
12672 and then Is_Limited_View
(Etype
(E
)));
12674 elsif Nkind
(Obj
) = N_Selected_Component
then
12675 return Is_Aliased
(Entity
(Selector_Name
(Obj
)));
12677 elsif Nkind
(Obj
) = N_Indexed_Component
then
12678 return Has_Aliased_Components
(Etype
(Prefix
(Obj
)))
12680 (Is_Access_Type
(Etype
(Prefix
(Obj
)))
12681 and then Has_Aliased_Components
12682 (Designated_Type
(Etype
(Prefix
(Obj
)))));
12684 elsif Nkind_In
(Obj
, N_Unchecked_Type_Conversion
, N_Type_Conversion
) then
12685 return Is_Tagged_Type
(Etype
(Obj
))
12686 and then Is_Aliased_View
(Expression
(Obj
));
12688 elsif Nkind
(Obj
) = N_Explicit_Dereference
then
12689 return Nkind
(Original_Node
(Obj
)) /= N_Function_Call
;
12694 end Is_Aliased_View
;
12696 -------------------------
12697 -- Is_Ancestor_Package --
12698 -------------------------
12700 function Is_Ancestor_Package
12702 E2
: Entity_Id
) return Boolean
12708 while Present
(Par
) and then Par
/= Standard_Standard
loop
12713 Par
:= Scope
(Par
);
12717 end Is_Ancestor_Package
;
12719 ----------------------
12720 -- Is_Atomic_Object --
12721 ----------------------
12723 function Is_Atomic_Object
(N
: Node_Id
) return Boolean is
12725 function Object_Has_Atomic_Components
(N
: Node_Id
) return Boolean;
12726 -- Determines if given object has atomic components
12728 function Is_Atomic_Prefix
(N
: Node_Id
) return Boolean;
12729 -- If prefix is an implicit dereference, examine designated type
12731 ----------------------
12732 -- Is_Atomic_Prefix --
12733 ----------------------
12735 function Is_Atomic_Prefix
(N
: Node_Id
) return Boolean is
12737 if Is_Access_Type
(Etype
(N
)) then
12739 Has_Atomic_Components
(Designated_Type
(Etype
(N
)));
12741 return Object_Has_Atomic_Components
(N
);
12743 end Is_Atomic_Prefix
;
12745 ----------------------------------
12746 -- Object_Has_Atomic_Components --
12747 ----------------------------------
12749 function Object_Has_Atomic_Components
(N
: Node_Id
) return Boolean is
12751 if Has_Atomic_Components
(Etype
(N
))
12752 or else Is_Atomic
(Etype
(N
))
12756 elsif Is_Entity_Name
(N
)
12757 and then (Has_Atomic_Components
(Entity
(N
))
12758 or else Is_Atomic
(Entity
(N
)))
12762 elsif Nkind
(N
) = N_Selected_Component
12763 and then Is_Atomic
(Entity
(Selector_Name
(N
)))
12767 elsif Nkind
(N
) = N_Indexed_Component
12768 or else Nkind
(N
) = N_Selected_Component
12770 return Is_Atomic_Prefix
(Prefix
(N
));
12775 end Object_Has_Atomic_Components
;
12777 -- Start of processing for Is_Atomic_Object
12780 -- Predicate is not relevant to subprograms
12782 if Is_Entity_Name
(N
) and then Is_Overloadable
(Entity
(N
)) then
12785 elsif Is_Atomic
(Etype
(N
))
12786 or else (Is_Entity_Name
(N
) and then Is_Atomic
(Entity
(N
)))
12790 elsif Nkind
(N
) = N_Selected_Component
12791 and then Is_Atomic
(Entity
(Selector_Name
(N
)))
12795 elsif Nkind
(N
) = N_Indexed_Component
12796 or else Nkind
(N
) = N_Selected_Component
12798 return Is_Atomic_Prefix
(Prefix
(N
));
12803 end Is_Atomic_Object
;
12805 -----------------------------
12806 -- Is_Atomic_Or_VFA_Object --
12807 -----------------------------
12809 function Is_Atomic_Or_VFA_Object
(N
: Node_Id
) return Boolean is
12811 return Is_Atomic_Object
(N
)
12812 or else (Is_Object_Reference
(N
)
12813 and then Is_Entity_Name
(N
)
12814 and then (Is_Volatile_Full_Access
(Entity
(N
))
12816 Is_Volatile_Full_Access
(Etype
(Entity
(N
)))));
12817 end Is_Atomic_Or_VFA_Object
;
12819 -------------------------
12820 -- Is_Attribute_Result --
12821 -------------------------
12823 function Is_Attribute_Result
(N
: Node_Id
) return Boolean is
12825 return Nkind
(N
) = N_Attribute_Reference
12826 and then Attribute_Name
(N
) = Name_Result
;
12827 end Is_Attribute_Result
;
12829 -------------------------
12830 -- Is_Attribute_Update --
12831 -------------------------
12833 function Is_Attribute_Update
(N
: Node_Id
) return Boolean is
12835 return Nkind
(N
) = N_Attribute_Reference
12836 and then Attribute_Name
(N
) = Name_Update
;
12837 end Is_Attribute_Update
;
12839 ------------------------------------
12840 -- Is_Body_Or_Package_Declaration --
12841 ------------------------------------
12843 function Is_Body_Or_Package_Declaration
(N
: Node_Id
) return Boolean is
12845 return Nkind_In
(N
, N_Entry_Body
,
12847 N_Package_Declaration
,
12851 end Is_Body_Or_Package_Declaration
;
12853 -----------------------
12854 -- Is_Bounded_String --
12855 -----------------------
12857 function Is_Bounded_String
(T
: Entity_Id
) return Boolean is
12858 Under
: constant Entity_Id
:= Underlying_Type
(Root_Type
(T
));
12861 -- Check whether T is ultimately derived from Ada.Strings.Superbounded.
12862 -- Super_String, or one of the [Wide_]Wide_ versions. This will
12863 -- be True for all the Bounded_String types in instances of the
12864 -- Generic_Bounded_Length generics, and for types derived from those.
12866 return Present
(Under
)
12867 and then (Is_RTE
(Root_Type
(Under
), RO_SU_Super_String
) or else
12868 Is_RTE
(Root_Type
(Under
), RO_WI_Super_String
) or else
12869 Is_RTE
(Root_Type
(Under
), RO_WW_Super_String
));
12870 end Is_Bounded_String
;
12872 ---------------------
12873 -- Is_CCT_Instance --
12874 ---------------------
12876 function Is_CCT_Instance
12877 (Ref_Id
: Entity_Id
;
12878 Context_Id
: Entity_Id
) return Boolean
12881 pragma Assert
(Ekind_In
(Ref_Id
, E_Protected_Type
, E_Task_Type
));
12883 if Is_Single_Task_Object
(Context_Id
) then
12884 return Scope_Within_Or_Same
(Etype
(Context_Id
), Ref_Id
);
12887 pragma Assert
(Ekind_In
(Context_Id
, E_Entry
,
12895 Is_Record_Type
(Context_Id
));
12896 return Scope_Within_Or_Same
(Context_Id
, Ref_Id
);
12898 end Is_CCT_Instance
;
12900 -------------------------
12901 -- Is_Child_Or_Sibling --
12902 -------------------------
12904 function Is_Child_Or_Sibling
12905 (Pack_1
: Entity_Id
;
12906 Pack_2
: Entity_Id
) return Boolean
12908 function Distance_From_Standard
(Pack
: Entity_Id
) return Nat
;
12909 -- Given an arbitrary package, return the number of "climbs" necessary
12910 -- to reach scope Standard_Standard.
12912 procedure Equalize_Depths
12913 (Pack
: in out Entity_Id
;
12914 Depth
: in out Nat
;
12915 Depth_To_Reach
: Nat
);
12916 -- Given an arbitrary package, its depth and a target depth to reach,
12917 -- climb the scope chain until the said depth is reached. The pointer
12918 -- to the package and its depth a modified during the climb.
12920 ----------------------------
12921 -- Distance_From_Standard --
12922 ----------------------------
12924 function Distance_From_Standard
(Pack
: Entity_Id
) return Nat
is
12931 while Present
(Scop
) and then Scop
/= Standard_Standard
loop
12933 Scop
:= Scope
(Scop
);
12937 end Distance_From_Standard
;
12939 ---------------------
12940 -- Equalize_Depths --
12941 ---------------------
12943 procedure Equalize_Depths
12944 (Pack
: in out Entity_Id
;
12945 Depth
: in out Nat
;
12946 Depth_To_Reach
: Nat
)
12949 -- The package must be at a greater or equal depth
12951 if Depth
< Depth_To_Reach
then
12952 raise Program_Error
;
12955 -- Climb the scope chain until the desired depth is reached
12957 while Present
(Pack
) and then Depth
/= Depth_To_Reach
loop
12958 Pack
:= Scope
(Pack
);
12959 Depth
:= Depth
- 1;
12961 end Equalize_Depths
;
12965 P_1
: Entity_Id
:= Pack_1
;
12966 P_1_Child
: Boolean := False;
12967 P_1_Depth
: Nat
:= Distance_From_Standard
(P_1
);
12968 P_2
: Entity_Id
:= Pack_2
;
12969 P_2_Child
: Boolean := False;
12970 P_2_Depth
: Nat
:= Distance_From_Standard
(P_2
);
12972 -- Start of processing for Is_Child_Or_Sibling
12976 (Ekind
(Pack_1
) = E_Package
and then Ekind
(Pack_2
) = E_Package
);
12978 -- Both packages denote the same entity, therefore they cannot be
12979 -- children or siblings.
12984 -- One of the packages is at a deeper level than the other. Note that
12985 -- both may still come from different hierarchies.
12993 elsif P_1_Depth
> P_2_Depth
then
12996 Depth
=> P_1_Depth
,
12997 Depth_To_Reach
=> P_2_Depth
);
13006 elsif P_2_Depth
> P_1_Depth
then
13009 Depth
=> P_2_Depth
,
13010 Depth_To_Reach
=> P_1_Depth
);
13014 -- At this stage the package pointers have been elevated to the same
13015 -- depth. If the related entities are the same, then one package is a
13016 -- potential child of the other:
13020 -- X became P_1 P_2 or vice versa
13026 return Is_Child_Unit
(Pack_1
);
13028 else pragma Assert
(P_2_Child
);
13029 return Is_Child_Unit
(Pack_2
);
13032 -- The packages may come from the same package chain or from entirely
13033 -- different hierarcies. To determine this, climb the scope stack until
13034 -- a common root is found.
13036 -- (root) (root 1) (root 2)
13041 while Present
(P_1
) and then Present
(P_2
) loop
13043 -- The two packages may be siblings
13046 return Is_Child_Unit
(Pack_1
) and then Is_Child_Unit
(Pack_2
);
13049 P_1
:= Scope
(P_1
);
13050 P_2
:= Scope
(P_2
);
13055 end Is_Child_Or_Sibling
;
13057 -----------------------------
13058 -- Is_Concurrent_Interface --
13059 -----------------------------
13061 function Is_Concurrent_Interface
(T
: Entity_Id
) return Boolean is
13063 return Is_Interface
(T
)
13065 (Is_Protected_Interface
(T
)
13066 or else Is_Synchronized_Interface
(T
)
13067 or else Is_Task_Interface
(T
));
13068 end Is_Concurrent_Interface
;
13070 -----------------------
13071 -- Is_Constant_Bound --
13072 -----------------------
13074 function Is_Constant_Bound
(Exp
: Node_Id
) return Boolean is
13076 if Compile_Time_Known_Value
(Exp
) then
13079 elsif Is_Entity_Name
(Exp
) and then Present
(Entity
(Exp
)) then
13080 return Is_Constant_Object
(Entity
(Exp
))
13081 or else Ekind
(Entity
(Exp
)) = E_Enumeration_Literal
;
13083 elsif Nkind
(Exp
) in N_Binary_Op
then
13084 return Is_Constant_Bound
(Left_Opnd
(Exp
))
13085 and then Is_Constant_Bound
(Right_Opnd
(Exp
))
13086 and then Scope
(Entity
(Exp
)) = Standard_Standard
;
13091 end Is_Constant_Bound
;
13093 ---------------------------
13094 -- Is_Container_Element --
13095 ---------------------------
13097 function Is_Container_Element
(Exp
: Node_Id
) return Boolean is
13098 Loc
: constant Source_Ptr
:= Sloc
(Exp
);
13099 Pref
: constant Node_Id
:= Prefix
(Exp
);
13102 -- Call to an indexing aspect
13104 Cont_Typ
: Entity_Id
;
13105 -- The type of the container being accessed
13107 Elem_Typ
: Entity_Id
;
13108 -- Its element type
13110 Indexing
: Entity_Id
;
13111 Is_Const
: Boolean;
13112 -- Indicates that constant indexing is used, and the element is thus
13115 Ref_Typ
: Entity_Id
;
13116 -- The reference type returned by the indexing operation
13119 -- If C is a container, in a context that imposes the element type of
13120 -- that container, the indexing notation C (X) is rewritten as:
13122 -- Indexing (C, X).Discr.all
13124 -- where Indexing is one of the indexing aspects of the container.
13125 -- If the context does not require a reference, the construct can be
13130 -- First, verify that the construct has the proper form
13132 if not Expander_Active
then
13135 elsif Nkind
(Pref
) /= N_Selected_Component
then
13138 elsif Nkind
(Prefix
(Pref
)) /= N_Function_Call
then
13142 Call
:= Prefix
(Pref
);
13143 Ref_Typ
:= Etype
(Call
);
13146 if not Has_Implicit_Dereference
(Ref_Typ
)
13147 or else No
(First
(Parameter_Associations
(Call
)))
13148 or else not Is_Entity_Name
(Name
(Call
))
13153 -- Retrieve type of container object, and its iterator aspects
13155 Cont_Typ
:= Etype
(First
(Parameter_Associations
(Call
)));
13156 Indexing
:= Find_Value_Of_Aspect
(Cont_Typ
, Aspect_Constant_Indexing
);
13159 if No
(Indexing
) then
13161 -- Container should have at least one indexing operation
13165 elsif Entity
(Name
(Call
)) /= Entity
(Indexing
) then
13167 -- This may be a variable indexing operation
13169 Indexing
:= Find_Value_Of_Aspect
(Cont_Typ
, Aspect_Variable_Indexing
);
13172 or else Entity
(Name
(Call
)) /= Entity
(Indexing
)
13181 Elem_Typ
:= Find_Value_Of_Aspect
(Cont_Typ
, Aspect_Iterator_Element
);
13183 if No
(Elem_Typ
) or else Entity
(Elem_Typ
) /= Etype
(Exp
) then
13187 -- Check that the expression is not the target of an assignment, in
13188 -- which case the rewriting is not possible.
13190 if not Is_Const
then
13196 while Present
(Par
)
13198 if Nkind
(Parent
(Par
)) = N_Assignment_Statement
13199 and then Par
= Name
(Parent
(Par
))
13203 -- A renaming produces a reference, and the transformation
13206 elsif Nkind
(Parent
(Par
)) = N_Object_Renaming_Declaration
then
13210 (Nkind
(Parent
(Par
)), N_Function_Call
,
13211 N_Procedure_Call_Statement
,
13212 N_Entry_Call_Statement
)
13214 -- Check that the element is not part of an actual for an
13215 -- in-out parameter.
13222 F
:= First_Formal
(Entity
(Name
(Parent
(Par
))));
13223 A
:= First
(Parameter_Associations
(Parent
(Par
)));
13224 while Present
(F
) loop
13225 if A
= Par
and then Ekind
(F
) /= E_In_Parameter
then
13234 -- E_In_Parameter in a call: element is not modified.
13239 Par
:= Parent
(Par
);
13244 -- The expression has the proper form and the context requires the
13245 -- element type. Retrieve the Element function of the container and
13246 -- rewrite the construct as a call to it.
13252 Op
:= First_Elmt
(Primitive_Operations
(Cont_Typ
));
13253 while Present
(Op
) loop
13254 exit when Chars
(Node
(Op
)) = Name_Element
;
13263 Make_Function_Call
(Loc
,
13264 Name
=> New_Occurrence_Of
(Node
(Op
), Loc
),
13265 Parameter_Associations
=> Parameter_Associations
(Call
)));
13266 Analyze_And_Resolve
(Exp
, Entity
(Elem_Typ
));
13270 end Is_Container_Element
;
13272 ----------------------------
13273 -- Is_Contract_Annotation --
13274 ----------------------------
13276 function Is_Contract_Annotation
(Item
: Node_Id
) return Boolean is
13278 return Is_Package_Contract_Annotation
(Item
)
13280 Is_Subprogram_Contract_Annotation
(Item
);
13281 end Is_Contract_Annotation
;
13283 --------------------------------------
13284 -- Is_Controlling_Limited_Procedure --
13285 --------------------------------------
13287 function Is_Controlling_Limited_Procedure
13288 (Proc_Nam
: Entity_Id
) return Boolean
13291 Param_Typ
: Entity_Id
:= Empty
;
13294 if Ekind
(Proc_Nam
) = E_Procedure
13295 and then Present
(Parameter_Specifications
(Parent
(Proc_Nam
)))
13299 (First
(Parameter_Specifications
(Parent
(Proc_Nam
))));
13301 -- The formal may be an anonymous access type
13303 if Nkind
(Param
) = N_Access_Definition
then
13304 Param_Typ
:= Entity
(Subtype_Mark
(Param
));
13306 Param_Typ
:= Etype
(Param
);
13309 -- In the case where an Itype was created for a dispatchin call, the
13310 -- procedure call has been rewritten. The actual may be an access to
13311 -- interface type in which case it is the designated type that is the
13312 -- controlling type.
13314 elsif Present
(Associated_Node_For_Itype
(Proc_Nam
))
13315 and then Present
(Original_Node
(Associated_Node_For_Itype
(Proc_Nam
)))
13317 Present
(Parameter_Associations
13318 (Associated_Node_For_Itype
(Proc_Nam
)))
13321 Etype
(First
(Parameter_Associations
13322 (Associated_Node_For_Itype
(Proc_Nam
))));
13324 if Ekind
(Param_Typ
) = E_Anonymous_Access_Type
then
13325 Param_Typ
:= Directly_Designated_Type
(Param_Typ
);
13329 if Present
(Param_Typ
) then
13331 Is_Interface
(Param_Typ
)
13332 and then Is_Limited_Record
(Param_Typ
);
13336 end Is_Controlling_Limited_Procedure
;
13338 -----------------------------
13339 -- Is_CPP_Constructor_Call --
13340 -----------------------------
13342 function Is_CPP_Constructor_Call
(N
: Node_Id
) return Boolean is
13344 return Nkind
(N
) = N_Function_Call
13345 and then Is_CPP_Class
(Etype
(Etype
(N
)))
13346 and then Is_Constructor
(Entity
(Name
(N
)))
13347 and then Is_Imported
(Entity
(Name
(N
)));
13348 end Is_CPP_Constructor_Call
;
13350 -------------------------
13351 -- Is_Current_Instance --
13352 -------------------------
13354 function Is_Current_Instance
(N
: Node_Id
) return Boolean is
13355 Typ
: constant Entity_Id
:= Entity
(N
);
13359 -- Simplest case: entity is a concurrent type and we are currently
13360 -- inside the body. This will eventually be expanded into a
13361 -- call to Self (for tasks) or _object (for protected objects).
13363 if Is_Concurrent_Type
(Typ
) and then In_Open_Scopes
(Typ
) then
13367 -- Check whether the context is a (sub)type declaration for the
13371 while Present
(P
) loop
13372 if Nkind_In
(P
, N_Full_Type_Declaration
,
13373 N_Private_Type_Declaration
,
13374 N_Subtype_Declaration
)
13375 and then Comes_From_Source
(P
)
13376 and then Defining_Entity
(P
) = Typ
13380 -- A subtype name may appear in an aspect specification for a
13381 -- Predicate_Failure aspect, for which we do not construct a
13382 -- wrapper procedure. The subtype will be replaced by the
13383 -- expression being tested when the corresponding predicate
13384 -- check is expanded.
13386 elsif Nkind
(P
) = N_Aspect_Specification
13387 and then Nkind
(Parent
(P
)) = N_Subtype_Declaration
13391 elsif Nkind
(P
) = N_Pragma
13393 Get_Pragma_Id
(P
) = Pragma_Predicate_Failure
13402 -- In any other context this is not a current occurrence
13405 end Is_Current_Instance
;
13407 --------------------
13408 -- Is_Declaration --
13409 --------------------
13411 function Is_Declaration
(N
: Node_Id
) return Boolean is
13414 Is_Declaration_Other_Than_Renaming
(N
)
13415 or else Is_Renaming_Declaration
(N
);
13416 end Is_Declaration
;
13418 ----------------------------------------
13419 -- Is_Declaration_Other_Than_Renaming --
13420 ----------------------------------------
13422 function Is_Declaration_Other_Than_Renaming
(N
: Node_Id
) return Boolean is
13425 when N_Abstract_Subprogram_Declaration
13426 | N_Exception_Declaration
13427 | N_Expression_Function
13428 | N_Full_Type_Declaration
13429 | N_Generic_Package_Declaration
13430 | N_Generic_Subprogram_Declaration
13431 | N_Number_Declaration
13432 | N_Object_Declaration
13433 | N_Package_Declaration
13434 | N_Private_Extension_Declaration
13435 | N_Private_Type_Declaration
13436 | N_Subprogram_Declaration
13437 | N_Subtype_Declaration
13444 end Is_Declaration_Other_Than_Renaming
;
13446 --------------------------------
13447 -- Is_Declared_Within_Variant --
13448 --------------------------------
13450 function Is_Declared_Within_Variant
(Comp
: Entity_Id
) return Boolean is
13451 Comp_Decl
: constant Node_Id
:= Parent
(Comp
);
13452 Comp_List
: constant Node_Id
:= Parent
(Comp_Decl
);
13454 return Nkind
(Parent
(Comp_List
)) = N_Variant
;
13455 end Is_Declared_Within_Variant
;
13457 ----------------------------------------------
13458 -- Is_Dependent_Component_Of_Mutable_Object --
13459 ----------------------------------------------
13461 function Is_Dependent_Component_Of_Mutable_Object
13462 (Object
: Node_Id
) return Boolean
13465 Prefix_Type
: Entity_Id
;
13466 P_Aliased
: Boolean := False;
13469 Deref
: Node_Id
:= Object
;
13470 -- Dereference node, in something like X.all.Y(2)
13472 -- Start of processing for Is_Dependent_Component_Of_Mutable_Object
13475 -- Find the dereference node if any
13477 while Nkind_In
(Deref
, N_Indexed_Component
,
13478 N_Selected_Component
,
13481 Deref
:= Prefix
(Deref
);
13484 -- Ada 2005: If we have a component or slice of a dereference,
13485 -- something like X.all.Y (2), and the type of X is access-to-constant,
13486 -- Is_Variable will return False, because it is indeed a constant
13487 -- view. But it might be a view of a variable object, so we want the
13488 -- following condition to be True in that case.
13490 if Is_Variable
(Object
)
13491 or else (Ada_Version
>= Ada_2005
13492 and then Nkind
(Deref
) = N_Explicit_Dereference
)
13494 if Nkind
(Object
) = N_Selected_Component
then
13495 P
:= Prefix
(Object
);
13496 Prefix_Type
:= Etype
(P
);
13498 if Is_Entity_Name
(P
) then
13499 if Ekind
(Entity
(P
)) = E_Generic_In_Out_Parameter
then
13500 Prefix_Type
:= Base_Type
(Prefix_Type
);
13503 if Is_Aliased
(Entity
(P
)) then
13507 -- A discriminant check on a selected component may be expanded
13508 -- into a dereference when removing side effects. Recover the
13509 -- original node and its type, which may be unconstrained.
13511 elsif Nkind
(P
) = N_Explicit_Dereference
13512 and then not (Comes_From_Source
(P
))
13514 P
:= Original_Node
(P
);
13515 Prefix_Type
:= Etype
(P
);
13518 -- Check for prefix being an aliased component???
13524 -- A heap object is constrained by its initial value
13526 -- Ada 2005 (AI-363): Always assume the object could be mutable in
13527 -- the dereferenced case, since the access value might denote an
13528 -- unconstrained aliased object, whereas in Ada 95 the designated
13529 -- object is guaranteed to be constrained. A worst-case assumption
13530 -- has to apply in Ada 2005 because we can't tell at compile
13531 -- time whether the object is "constrained by its initial value",
13532 -- despite the fact that 3.10.2(26/2) and 8.5.1(5/2) are semantic
13533 -- rules (these rules are acknowledged to need fixing). We don't
13534 -- impose this more stringent checking for earlier Ada versions or
13535 -- when Relaxed_RM_Semantics applies (the latter for CodePeer's
13536 -- benefit, though it's unclear on why using -gnat95 would not be
13539 if Ada_Version
< Ada_2005
or else Relaxed_RM_Semantics
then
13540 if Is_Access_Type
(Prefix_Type
)
13541 or else Nkind
(P
) = N_Explicit_Dereference
13546 else pragma Assert
(Ada_Version
>= Ada_2005
);
13547 if Is_Access_Type
(Prefix_Type
) then
13549 -- If the access type is pool-specific, and there is no
13550 -- constrained partial view of the designated type, then the
13551 -- designated object is known to be constrained.
13553 if Ekind
(Prefix_Type
) = E_Access_Type
13554 and then not Object_Type_Has_Constrained_Partial_View
13555 (Typ
=> Designated_Type
(Prefix_Type
),
13556 Scop
=> Current_Scope
)
13560 -- Otherwise (general access type, or there is a constrained
13561 -- partial view of the designated type), we need to check
13562 -- based on the designated type.
13565 Prefix_Type
:= Designated_Type
(Prefix_Type
);
13571 Original_Record_Component
(Entity
(Selector_Name
(Object
)));
13573 -- As per AI-0017, the renaming is illegal in a generic body, even
13574 -- if the subtype is indefinite.
13576 -- Ada 2005 (AI-363): In Ada 2005 an aliased object can be mutable
13578 if not Is_Constrained
(Prefix_Type
)
13579 and then (Is_Definite_Subtype
(Prefix_Type
)
13581 (Is_Generic_Type
(Prefix_Type
)
13582 and then Ekind
(Current_Scope
) = E_Generic_Package
13583 and then In_Package_Body
(Current_Scope
)))
13585 and then (Is_Declared_Within_Variant
(Comp
)
13586 or else Has_Discriminant_Dependent_Constraint
(Comp
))
13587 and then (not P_Aliased
or else Ada_Version
>= Ada_2005
)
13591 -- If the prefix is of an access type at this point, then we want
13592 -- to return False, rather than calling this function recursively
13593 -- on the access object (which itself might be a discriminant-
13594 -- dependent component of some other object, but that isn't
13595 -- relevant to checking the object passed to us). This avoids
13596 -- issuing wrong errors when compiling with -gnatc, where there
13597 -- can be implicit dereferences that have not been expanded.
13599 elsif Is_Access_Type
(Etype
(Prefix
(Object
))) then
13604 Is_Dependent_Component_Of_Mutable_Object
(Prefix
(Object
));
13607 elsif Nkind
(Object
) = N_Indexed_Component
13608 or else Nkind
(Object
) = N_Slice
13610 return Is_Dependent_Component_Of_Mutable_Object
(Prefix
(Object
));
13612 -- A type conversion that Is_Variable is a view conversion:
13613 -- go back to the denoted object.
13615 elsif Nkind
(Object
) = N_Type_Conversion
then
13617 Is_Dependent_Component_Of_Mutable_Object
(Expression
(Object
));
13622 end Is_Dependent_Component_Of_Mutable_Object
;
13624 ---------------------
13625 -- Is_Dereferenced --
13626 ---------------------
13628 function Is_Dereferenced
(N
: Node_Id
) return Boolean is
13629 P
: constant Node_Id
:= Parent
(N
);
13631 return Nkind_In
(P
, N_Selected_Component
,
13632 N_Explicit_Dereference
,
13633 N_Indexed_Component
,
13635 and then Prefix
(P
) = N
;
13636 end Is_Dereferenced
;
13638 ----------------------
13639 -- Is_Descendant_Of --
13640 ----------------------
13642 function Is_Descendant_Of
(T1
: Entity_Id
; T2
: Entity_Id
) return Boolean is
13647 pragma Assert
(Nkind
(T1
) in N_Entity
);
13648 pragma Assert
(Nkind
(T2
) in N_Entity
);
13650 T
:= Base_Type
(T1
);
13652 -- Immediate return if the types match
13657 -- Comment needed here ???
13659 elsif Ekind
(T
) = E_Class_Wide_Type
then
13660 return Etype
(T
) = T2
;
13668 -- Done if we found the type we are looking for
13673 -- Done if no more derivations to check
13680 -- Following test catches error cases resulting from prev errors
13682 elsif No
(Etyp
) then
13685 elsif Is_Private_Type
(T
) and then Etyp
= Full_View
(T
) then
13688 elsif Is_Private_Type
(Etyp
) and then Full_View
(Etyp
) = T
then
13692 T
:= Base_Type
(Etyp
);
13695 end Is_Descendant_Of
;
13697 ----------------------------------------
13698 -- Is_Descendant_Of_Suspension_Object --
13699 ----------------------------------------
13701 function Is_Descendant_Of_Suspension_Object
13702 (Typ
: Entity_Id
) return Boolean
13704 Cur_Typ
: Entity_Id
;
13705 Par_Typ
: Entity_Id
;
13708 -- Climb the type derivation chain checking each parent type against
13709 -- Suspension_Object.
13711 Cur_Typ
:= Base_Type
(Typ
);
13712 while Present
(Cur_Typ
) loop
13713 Par_Typ
:= Etype
(Cur_Typ
);
13715 -- The current type is a match
13717 if Is_Suspension_Object
(Cur_Typ
) then
13720 -- Stop the traversal once the root of the derivation chain has been
13721 -- reached. In that case the current type is its own base type.
13723 elsif Cur_Typ
= Par_Typ
then
13727 Cur_Typ
:= Base_Type
(Par_Typ
);
13731 end Is_Descendant_Of_Suspension_Object
;
13733 ---------------------------------------------
13734 -- Is_Double_Precision_Floating_Point_Type --
13735 ---------------------------------------------
13737 function Is_Double_Precision_Floating_Point_Type
13738 (E
: Entity_Id
) return Boolean is
13740 return Is_Floating_Point_Type
(E
)
13741 and then Machine_Radix_Value
(E
) = Uint_2
13742 and then Machine_Mantissa_Value
(E
) = UI_From_Int
(53)
13743 and then Machine_Emax_Value
(E
) = Uint_2
** Uint_10
13744 and then Machine_Emin_Value
(E
) = Uint_3
- (Uint_2
** Uint_10
);
13745 end Is_Double_Precision_Floating_Point_Type
;
13747 -----------------------------
13748 -- Is_Effectively_Volatile --
13749 -----------------------------
13751 function Is_Effectively_Volatile
(Id
: Entity_Id
) return Boolean is
13753 if Is_Type
(Id
) then
13755 -- An arbitrary type is effectively volatile when it is subject to
13756 -- pragma Atomic or Volatile.
13758 if Is_Volatile
(Id
) then
13761 -- An array type is effectively volatile when it is subject to pragma
13762 -- Atomic_Components or Volatile_Components or its component type is
13763 -- effectively volatile.
13765 elsif Is_Array_Type
(Id
) then
13767 Anc
: Entity_Id
:= Base_Type
(Id
);
13769 if Is_Private_Type
(Anc
) then
13770 Anc
:= Full_View
(Anc
);
13773 -- Test for presence of ancestor, as the full view of a private
13774 -- type may be missing in case of error.
13777 Has_Volatile_Components
(Id
)
13780 and then Is_Effectively_Volatile
(Component_Type
(Anc
)));
13783 -- A protected type is always volatile
13785 elsif Is_Protected_Type
(Id
) then
13788 -- A descendant of Ada.Synchronous_Task_Control.Suspension_Object is
13789 -- automatically volatile.
13791 elsif Is_Descendant_Of_Suspension_Object
(Id
) then
13794 -- Otherwise the type is not effectively volatile
13800 -- Otherwise Id denotes an object
13805 or else Has_Volatile_Components
(Id
)
13806 or else Is_Effectively_Volatile
(Etype
(Id
));
13808 end Is_Effectively_Volatile
;
13810 ------------------------------------
13811 -- Is_Effectively_Volatile_Object --
13812 ------------------------------------
13814 function Is_Effectively_Volatile_Object
(N
: Node_Id
) return Boolean is
13816 if Is_Entity_Name
(N
) then
13817 return Is_Effectively_Volatile
(Entity
(N
));
13819 elsif Nkind
(N
) = N_Indexed_Component
then
13820 return Is_Effectively_Volatile_Object
(Prefix
(N
));
13822 elsif Nkind
(N
) = N_Selected_Component
then
13824 Is_Effectively_Volatile_Object
(Prefix
(N
))
13826 Is_Effectively_Volatile_Object
(Selector_Name
(N
));
13831 end Is_Effectively_Volatile_Object
;
13833 -------------------
13834 -- Is_Entry_Body --
13835 -------------------
13837 function Is_Entry_Body
(Id
: Entity_Id
) return Boolean is
13840 Ekind_In
(Id
, E_Entry
, E_Entry_Family
)
13841 and then Nkind
(Unit_Declaration_Node
(Id
)) = N_Entry_Body
;
13844 --------------------------
13845 -- Is_Entry_Declaration --
13846 --------------------------
13848 function Is_Entry_Declaration
(Id
: Entity_Id
) return Boolean is
13851 Ekind_In
(Id
, E_Entry
, E_Entry_Family
)
13852 and then Nkind
(Unit_Declaration_Node
(Id
)) = N_Entry_Declaration
;
13853 end Is_Entry_Declaration
;
13855 ------------------------------------
13856 -- Is_Expanded_Priority_Attribute --
13857 ------------------------------------
13859 function Is_Expanded_Priority_Attribute
(E
: Entity_Id
) return Boolean is
13862 Nkind
(E
) = N_Function_Call
13863 and then not Configurable_Run_Time_Mode
13864 and then (Entity
(Name
(E
)) = RTE
(RE_Get_Ceiling
)
13865 or else Entity
(Name
(E
)) = RTE
(RO_PE_Get_Ceiling
));
13866 end Is_Expanded_Priority_Attribute
;
13868 ----------------------------
13869 -- Is_Expression_Function --
13870 ----------------------------
13872 function Is_Expression_Function
(Subp
: Entity_Id
) return Boolean is
13874 if Ekind_In
(Subp
, E_Function
, E_Subprogram_Body
) then
13876 Nkind
(Original_Node
(Unit_Declaration_Node
(Subp
))) =
13877 N_Expression_Function
;
13881 end Is_Expression_Function
;
13883 ------------------------------------------
13884 -- Is_Expression_Function_Or_Completion --
13885 ------------------------------------------
13887 function Is_Expression_Function_Or_Completion
13888 (Subp
: Entity_Id
) return Boolean
13890 Subp_Decl
: Node_Id
;
13893 if Ekind
(Subp
) = E_Function
then
13894 Subp_Decl
:= Unit_Declaration_Node
(Subp
);
13896 -- The function declaration is either an expression function or is
13897 -- completed by an expression function body.
13900 Is_Expression_Function
(Subp
)
13901 or else (Nkind
(Subp_Decl
) = N_Subprogram_Declaration
13902 and then Present
(Corresponding_Body
(Subp_Decl
))
13903 and then Is_Expression_Function
13904 (Corresponding_Body
(Subp_Decl
)));
13906 elsif Ekind
(Subp
) = E_Subprogram_Body
then
13907 return Is_Expression_Function
(Subp
);
13912 end Is_Expression_Function_Or_Completion
;
13914 -----------------------
13915 -- Is_EVF_Expression --
13916 -----------------------
13918 function Is_EVF_Expression
(N
: Node_Id
) return Boolean is
13919 Orig_N
: constant Node_Id
:= Original_Node
(N
);
13925 -- Detect a reference to a formal parameter of a specific tagged type
13926 -- whose related subprogram is subject to pragma Expresions_Visible with
13929 if Is_Entity_Name
(N
) and then Present
(Entity
(N
)) then
13934 and then Is_Specific_Tagged_Type
(Etype
(Id
))
13935 and then Extensions_Visible_Status
(Id
) =
13936 Extensions_Visible_False
;
13938 -- A case expression is an EVF expression when it contains at least one
13939 -- EVF dependent_expression. Note that a case expression may have been
13940 -- expanded, hence the use of Original_Node.
13942 elsif Nkind
(Orig_N
) = N_Case_Expression
then
13943 Alt
:= First
(Alternatives
(Orig_N
));
13944 while Present
(Alt
) loop
13945 if Is_EVF_Expression
(Expression
(Alt
)) then
13952 -- An if expression is an EVF expression when it contains at least one
13953 -- EVF dependent_expression. Note that an if expression may have been
13954 -- expanded, hence the use of Original_Node.
13956 elsif Nkind
(Orig_N
) = N_If_Expression
then
13957 Expr
:= Next
(First
(Expressions
(Orig_N
)));
13958 while Present
(Expr
) loop
13959 if Is_EVF_Expression
(Expr
) then
13966 -- A qualified expression or a type conversion is an EVF expression when
13967 -- its operand is an EVF expression.
13969 elsif Nkind_In
(N
, N_Qualified_Expression
,
13970 N_Unchecked_Type_Conversion
,
13973 return Is_EVF_Expression
(Expression
(N
));
13975 -- Attributes 'Loop_Entry, 'Old, and 'Update are EVF expressions when
13976 -- their prefix denotes an EVF expression.
13978 elsif Nkind
(N
) = N_Attribute_Reference
13979 and then Nam_In
(Attribute_Name
(N
), Name_Loop_Entry
,
13983 return Is_EVF_Expression
(Prefix
(N
));
13987 end Is_EVF_Expression
;
13993 function Is_False
(U
: Uint
) return Boolean is
13998 ---------------------------
13999 -- Is_Fixed_Model_Number --
14000 ---------------------------
14002 function Is_Fixed_Model_Number
(U
: Ureal
; T
: Entity_Id
) return Boolean is
14003 S
: constant Ureal
:= Small_Value
(T
);
14004 M
: Urealp
.Save_Mark
;
14009 R
:= (U
= UR_Trunc
(U
/ S
) * S
);
14010 Urealp
.Release
(M
);
14012 end Is_Fixed_Model_Number
;
14014 -------------------------------
14015 -- Is_Fully_Initialized_Type --
14016 -------------------------------
14018 function Is_Fully_Initialized_Type
(Typ
: Entity_Id
) return Boolean is
14022 if Is_Scalar_Type
(Typ
) then
14024 -- A scalar type with an aspect Default_Value is fully initialized
14026 -- Note: Iniitalize/Normalize_Scalars also ensure full initialization
14027 -- of a scalar type, but we don't take that into account here, since
14028 -- we don't want these to affect warnings.
14030 return Has_Default_Aspect
(Typ
);
14032 elsif Is_Access_Type
(Typ
) then
14035 elsif Is_Array_Type
(Typ
) then
14036 if Is_Fully_Initialized_Type
(Component_Type
(Typ
))
14037 or else (Ada_Version
>= Ada_2012
and then Has_Default_Aspect
(Typ
))
14042 -- An interesting case, if we have a constrained type one of whose
14043 -- bounds is known to be null, then there are no elements to be
14044 -- initialized, so all the elements are initialized.
14046 if Is_Constrained
(Typ
) then
14049 Indx_Typ
: Entity_Id
;
14050 Lbd
, Hbd
: Node_Id
;
14053 Indx
:= First_Index
(Typ
);
14054 while Present
(Indx
) loop
14055 if Etype
(Indx
) = Any_Type
then
14058 -- If index is a range, use directly
14060 elsif Nkind
(Indx
) = N_Range
then
14061 Lbd
:= Low_Bound
(Indx
);
14062 Hbd
:= High_Bound
(Indx
);
14065 Indx_Typ
:= Etype
(Indx
);
14067 if Is_Private_Type
(Indx_Typ
) then
14068 Indx_Typ
:= Full_View
(Indx_Typ
);
14071 if No
(Indx_Typ
) or else Etype
(Indx_Typ
) = Any_Type
then
14074 Lbd
:= Type_Low_Bound
(Indx_Typ
);
14075 Hbd
:= Type_High_Bound
(Indx_Typ
);
14079 if Compile_Time_Known_Value
(Lbd
)
14081 Compile_Time_Known_Value
(Hbd
)
14083 if Expr_Value
(Hbd
) < Expr_Value
(Lbd
) then
14093 -- If no null indexes, then type is not fully initialized
14099 elsif Is_Record_Type
(Typ
) then
14100 if Has_Discriminants
(Typ
)
14102 Present
(Discriminant_Default_Value
(First_Discriminant
(Typ
)))
14103 and then Is_Fully_Initialized_Variant
(Typ
)
14108 -- We consider bounded string types to be fully initialized, because
14109 -- otherwise we get false alarms when the Data component is not
14110 -- default-initialized.
14112 if Is_Bounded_String
(Typ
) then
14116 -- Controlled records are considered to be fully initialized if
14117 -- there is a user defined Initialize routine. This may not be
14118 -- entirely correct, but as the spec notes, we are guessing here
14119 -- what is best from the point of view of issuing warnings.
14121 if Is_Controlled
(Typ
) then
14123 Utyp
: constant Entity_Id
:= Underlying_Type
(Typ
);
14126 if Present
(Utyp
) then
14128 Init
: constant Entity_Id
:=
14129 (Find_Optional_Prim_Op
14130 (Underlying_Type
(Typ
), Name_Initialize
));
14134 and then Comes_From_Source
(Init
)
14135 and then not In_Predefined_Unit
(Init
)
14139 elsif Has_Null_Extension
(Typ
)
14141 Is_Fully_Initialized_Type
14142 (Etype
(Base_Type
(Typ
)))
14151 -- Otherwise see if all record components are initialized
14157 Ent
:= First_Entity
(Typ
);
14158 while Present
(Ent
) loop
14159 if Ekind
(Ent
) = E_Component
14160 and then (No
(Parent
(Ent
))
14161 or else No
(Expression
(Parent
(Ent
))))
14162 and then not Is_Fully_Initialized_Type
(Etype
(Ent
))
14164 -- Special VM case for tag components, which need to be
14165 -- defined in this case, but are never initialized as VMs
14166 -- are using other dispatching mechanisms. Ignore this
14167 -- uninitialized case. Note that this applies both to the
14168 -- uTag entry and the main vtable pointer (CPP_Class case).
14170 and then (Tagged_Type_Expansion
or else not Is_Tag
(Ent
))
14179 -- No uninitialized components, so type is fully initialized.
14180 -- Note that this catches the case of no components as well.
14184 elsif Is_Concurrent_Type
(Typ
) then
14187 elsif Is_Private_Type
(Typ
) then
14189 U
: constant Entity_Id
:= Underlying_Type
(Typ
);
14195 return Is_Fully_Initialized_Type
(U
);
14202 end Is_Fully_Initialized_Type
;
14204 ----------------------------------
14205 -- Is_Fully_Initialized_Variant --
14206 ----------------------------------
14208 function Is_Fully_Initialized_Variant
(Typ
: Entity_Id
) return Boolean is
14209 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
14210 Constraints
: constant List_Id
:= New_List
;
14211 Components
: constant Elist_Id
:= New_Elmt_List
;
14212 Comp_Elmt
: Elmt_Id
;
14214 Comp_List
: Node_Id
;
14216 Discr_Val
: Node_Id
;
14218 Report_Errors
: Boolean;
14219 pragma Warnings
(Off
, Report_Errors
);
14222 if Serious_Errors_Detected
> 0 then
14226 if Is_Record_Type
(Typ
)
14227 and then Nkind
(Parent
(Typ
)) = N_Full_Type_Declaration
14228 and then Nkind
(Type_Definition
(Parent
(Typ
))) = N_Record_Definition
14230 Comp_List
:= Component_List
(Type_Definition
(Parent
(Typ
)));
14232 Discr
:= First_Discriminant
(Typ
);
14233 while Present
(Discr
) loop
14234 if Nkind
(Parent
(Discr
)) = N_Discriminant_Specification
then
14235 Discr_Val
:= Expression
(Parent
(Discr
));
14237 if Present
(Discr_Val
)
14238 and then Is_OK_Static_Expression
(Discr_Val
)
14240 Append_To
(Constraints
,
14241 Make_Component_Association
(Loc
,
14242 Choices
=> New_List
(New_Occurrence_Of
(Discr
, Loc
)),
14243 Expression
=> New_Copy
(Discr_Val
)));
14251 Next_Discriminant
(Discr
);
14256 Comp_List
=> Comp_List
,
14257 Governed_By
=> Constraints
,
14258 Into
=> Components
,
14259 Report_Errors
=> Report_Errors
);
14261 -- Check that each component present is fully initialized
14263 Comp_Elmt
:= First_Elmt
(Components
);
14264 while Present
(Comp_Elmt
) loop
14265 Comp_Id
:= Node
(Comp_Elmt
);
14267 if Ekind
(Comp_Id
) = E_Component
14268 and then (No
(Parent
(Comp_Id
))
14269 or else No
(Expression
(Parent
(Comp_Id
))))
14270 and then not Is_Fully_Initialized_Type
(Etype
(Comp_Id
))
14275 Next_Elmt
(Comp_Elmt
);
14280 elsif Is_Private_Type
(Typ
) then
14282 U
: constant Entity_Id
:= Underlying_Type
(Typ
);
14288 return Is_Fully_Initialized_Variant
(U
);
14295 end Is_Fully_Initialized_Variant
;
14297 ------------------------------------
14298 -- Is_Generic_Declaration_Or_Body --
14299 ------------------------------------
14301 function Is_Generic_Declaration_Or_Body
(Decl
: Node_Id
) return Boolean is
14302 Spec_Decl
: Node_Id
;
14305 -- Package/subprogram body
14307 if Nkind_In
(Decl
, N_Package_Body
, N_Subprogram_Body
)
14308 and then Present
(Corresponding_Spec
(Decl
))
14310 Spec_Decl
:= Unit_Declaration_Node
(Corresponding_Spec
(Decl
));
14312 -- Package/subprogram body stub
14314 elsif Nkind_In
(Decl
, N_Package_Body_Stub
, N_Subprogram_Body_Stub
)
14315 and then Present
(Corresponding_Spec_Of_Stub
(Decl
))
14318 Unit_Declaration_Node
(Corresponding_Spec_Of_Stub
(Decl
));
14326 -- Rather than inspecting the defining entity of the spec declaration,
14327 -- look at its Nkind. This takes care of the case where the analysis of
14328 -- a generic body modifies the Ekind of its spec to allow for recursive
14332 Nkind_In
(Spec_Decl
, N_Generic_Package_Declaration
,
14333 N_Generic_Subprogram_Declaration
);
14334 end Is_Generic_Declaration_Or_Body
;
14336 ----------------------------
14337 -- Is_Inherited_Operation --
14338 ----------------------------
14340 function Is_Inherited_Operation
(E
: Entity_Id
) return Boolean is
14341 pragma Assert
(Is_Overloadable
(E
));
14342 Kind
: constant Node_Kind
:= Nkind
(Parent
(E
));
14344 return Kind
= N_Full_Type_Declaration
14345 or else Kind
= N_Private_Extension_Declaration
14346 or else Kind
= N_Subtype_Declaration
14347 or else (Ekind
(E
) = E_Enumeration_Literal
14348 and then Is_Derived_Type
(Etype
(E
)));
14349 end Is_Inherited_Operation
;
14351 -------------------------------------
14352 -- Is_Inherited_Operation_For_Type --
14353 -------------------------------------
14355 function Is_Inherited_Operation_For_Type
14357 Typ
: Entity_Id
) return Boolean
14360 -- Check that the operation has been created by the type declaration
14362 return Is_Inherited_Operation
(E
)
14363 and then Defining_Identifier
(Parent
(E
)) = Typ
;
14364 end Is_Inherited_Operation_For_Type
;
14366 --------------------------------------
14367 -- Is_Inlinable_Expression_Function --
14368 --------------------------------------
14370 function Is_Inlinable_Expression_Function
14371 (Subp
: Entity_Id
) return Boolean
14373 Return_Expr
: Node_Id
;
14376 if Is_Expression_Function_Or_Completion
(Subp
)
14377 and then Has_Pragma_Inline_Always
(Subp
)
14378 and then Needs_No_Actuals
(Subp
)
14379 and then No
(Contract
(Subp
))
14380 and then not Is_Dispatching_Operation
(Subp
)
14381 and then Needs_Finalization
(Etype
(Subp
))
14382 and then not Is_Class_Wide_Type
(Etype
(Subp
))
14383 and then not (Has_Invariants
(Etype
(Subp
)))
14384 and then Present
(Subprogram_Body
(Subp
))
14385 and then Was_Expression_Function
(Subprogram_Body
(Subp
))
14387 Return_Expr
:= Expression_Of_Expression_Function
(Subp
);
14389 -- The returned object must not have a qualified expression and its
14390 -- nominal subtype must be statically compatible with the result
14391 -- subtype of the expression function.
14394 Nkind
(Return_Expr
) = N_Identifier
14395 and then Etype
(Return_Expr
) = Etype
(Subp
);
14399 end Is_Inlinable_Expression_Function
;
14405 function Is_Iterator
(Typ
: Entity_Id
) return Boolean is
14406 function Denotes_Iterator
(Iter_Typ
: Entity_Id
) return Boolean;
14407 -- Determine whether type Iter_Typ is a predefined forward or reversible
14410 ----------------------
14411 -- Denotes_Iterator --
14412 ----------------------
14414 function Denotes_Iterator
(Iter_Typ
: Entity_Id
) return Boolean is
14416 -- Check that the name matches, and that the ultimate ancestor is in
14417 -- a predefined unit, i.e the one that declares iterator interfaces.
14420 Nam_In
(Chars
(Iter_Typ
), Name_Forward_Iterator
,
14421 Name_Reversible_Iterator
)
14422 and then In_Predefined_Unit
(Root_Type
(Iter_Typ
));
14423 end Denotes_Iterator
;
14427 Iface_Elmt
: Elmt_Id
;
14430 -- Start of processing for Is_Iterator
14433 -- The type may be a subtype of a descendant of the proper instance of
14434 -- the predefined interface type, so we must use the root type of the
14435 -- given type. The same is done for Is_Reversible_Iterator.
14437 if Is_Class_Wide_Type
(Typ
)
14438 and then Denotes_Iterator
(Root_Type
(Typ
))
14442 elsif not Is_Tagged_Type
(Typ
) or else not Is_Derived_Type
(Typ
) then
14445 elsif Present
(Find_Value_Of_Aspect
(Typ
, Aspect_Iterable
)) then
14449 Collect_Interfaces
(Typ
, Ifaces
);
14451 Iface_Elmt
:= First_Elmt
(Ifaces
);
14452 while Present
(Iface_Elmt
) loop
14453 if Denotes_Iterator
(Node
(Iface_Elmt
)) then
14457 Next_Elmt
(Iface_Elmt
);
14464 ----------------------------
14465 -- Is_Iterator_Over_Array --
14466 ----------------------------
14468 function Is_Iterator_Over_Array
(N
: Node_Id
) return Boolean is
14469 Container
: constant Node_Id
:= Name
(N
);
14470 Container_Typ
: constant Entity_Id
:= Base_Type
(Etype
(Container
));
14472 return Is_Array_Type
(Container_Typ
);
14473 end Is_Iterator_Over_Array
;
14479 -- We seem to have a lot of overlapping functions that do similar things
14480 -- (testing for left hand sides or lvalues???).
14482 function Is_LHS
(N
: Node_Id
) return Is_LHS_Result
is
14483 P
: constant Node_Id
:= Parent
(N
);
14486 -- Return True if we are the left hand side of an assignment statement
14488 if Nkind
(P
) = N_Assignment_Statement
then
14489 if Name
(P
) = N
then
14495 -- Case of prefix of indexed or selected component or slice
14497 elsif Nkind_In
(P
, N_Indexed_Component
, N_Selected_Component
, N_Slice
)
14498 and then N
= Prefix
(P
)
14500 -- Here we have the case where the parent P is N.Q or N(Q .. R).
14501 -- If P is an LHS, then N is also effectively an LHS, but there
14502 -- is an important exception. If N is of an access type, then
14503 -- what we really have is N.all.Q (or N.all(Q .. R)). In either
14504 -- case this makes N.all a left hand side but not N itself.
14506 -- If we don't know the type yet, this is the case where we return
14507 -- Unknown, since the answer depends on the type which is unknown.
14509 if No
(Etype
(N
)) then
14512 -- We have an Etype set, so we can check it
14514 elsif Is_Access_Type
(Etype
(N
)) then
14517 -- OK, not access type case, so just test whole expression
14523 -- All other cases are not left hand sides
14530 -----------------------------
14531 -- Is_Library_Level_Entity --
14532 -----------------------------
14534 function Is_Library_Level_Entity
(E
: Entity_Id
) return Boolean is
14536 -- The following is a small optimization, and it also properly handles
14537 -- discriminals, which in task bodies might appear in expressions before
14538 -- the corresponding procedure has been created, and which therefore do
14539 -- not have an assigned scope.
14541 if Is_Formal
(E
) then
14545 -- Normal test is simply that the enclosing dynamic scope is Standard
14547 return Enclosing_Dynamic_Scope
(E
) = Standard_Standard
;
14548 end Is_Library_Level_Entity
;
14550 --------------------------------
14551 -- Is_Limited_Class_Wide_Type --
14552 --------------------------------
14554 function Is_Limited_Class_Wide_Type
(Typ
: Entity_Id
) return Boolean is
14557 Is_Class_Wide_Type
(Typ
)
14558 and then (Is_Limited_Type
(Typ
) or else From_Limited_With
(Typ
));
14559 end Is_Limited_Class_Wide_Type
;
14561 ---------------------------------
14562 -- Is_Local_Variable_Reference --
14563 ---------------------------------
14565 function Is_Local_Variable_Reference
(Expr
: Node_Id
) return Boolean is
14567 if not Is_Entity_Name
(Expr
) then
14572 Ent
: constant Entity_Id
:= Entity
(Expr
);
14573 Sub
: constant Entity_Id
:= Enclosing_Subprogram
(Ent
);
14575 if not Ekind_In
(Ent
, E_Variable
, E_In_Out_Parameter
) then
14578 return Present
(Sub
) and then Sub
= Current_Subprogram
;
14582 end Is_Local_Variable_Reference
;
14584 -----------------------
14585 -- Is_Name_Reference --
14586 -----------------------
14588 function Is_Name_Reference
(N
: Node_Id
) return Boolean is
14590 if Is_Entity_Name
(N
) then
14591 return Present
(Entity
(N
)) and then Is_Object
(Entity
(N
));
14595 when N_Indexed_Component
14599 Is_Name_Reference
(Prefix
(N
))
14600 or else Is_Access_Type
(Etype
(Prefix
(N
)));
14602 -- Attributes 'Input, 'Old and 'Result produce objects
14604 when N_Attribute_Reference
=>
14606 Nam_In
(Attribute_Name
(N
), Name_Input
, Name_Old
, Name_Result
);
14608 when N_Selected_Component
=>
14610 Is_Name_Reference
(Selector_Name
(N
))
14612 (Is_Name_Reference
(Prefix
(N
))
14613 or else Is_Access_Type
(Etype
(Prefix
(N
))));
14615 when N_Explicit_Dereference
=>
14618 -- A view conversion of a tagged name is a name reference
14620 when N_Type_Conversion
=>
14622 Is_Tagged_Type
(Etype
(Subtype_Mark
(N
)))
14623 and then Is_Tagged_Type
(Etype
(Expression
(N
)))
14624 and then Is_Name_Reference
(Expression
(N
));
14626 -- An unchecked type conversion is considered to be a name if the
14627 -- operand is a name (this construction arises only as a result of
14628 -- expansion activities).
14630 when N_Unchecked_Type_Conversion
=>
14631 return Is_Name_Reference
(Expression
(N
));
14636 end Is_Name_Reference
;
14638 ------------------------------------
14639 -- Is_Non_Preelaborable_Construct --
14640 ------------------------------------
14642 function Is_Non_Preelaborable_Construct
(N
: Node_Id
) return Boolean is
14644 -- NOTE: the routines within Is_Non_Preelaborable_Construct are
14645 -- intentionally unnested to avoid deep indentation of code.
14647 Non_Preelaborable
: exception;
14648 -- This exception is raised when the construct violates preelaborability
14649 -- to terminate the recursion.
14651 procedure Visit
(Nod
: Node_Id
);
14652 -- Semantically inspect construct Nod to determine whether it violates
14653 -- preelaborability. This routine raises Non_Preelaborable.
14655 procedure Visit_List
(List
: List_Id
);
14656 pragma Inline
(Visit_List
);
14657 -- Invoke Visit on each element of list List. This routine raises
14658 -- Non_Preelaborable.
14660 procedure Visit_Pragma
(Prag
: Node_Id
);
14661 pragma Inline
(Visit_Pragma
);
14662 -- Semantically inspect pragma Prag to determine whether it violates
14663 -- preelaborability. This routine raises Non_Preelaborable.
14665 procedure Visit_Subexpression
(Expr
: Node_Id
);
14666 pragma Inline
(Visit_Subexpression
);
14667 -- Semantically inspect expression Expr to determine whether it violates
14668 -- preelaborability. This routine raises Non_Preelaborable.
14674 procedure Visit
(Nod
: Node_Id
) is
14676 case Nkind
(Nod
) is
14680 when N_Component_Declaration
=>
14682 -- Defining_Identifier is left out because it is not relevant
14683 -- for preelaborability.
14685 Visit
(Component_Definition
(Nod
));
14686 Visit
(Expression
(Nod
));
14688 when N_Derived_Type_Definition
=>
14690 -- Interface_List is left out because it is not relevant for
14691 -- preelaborability.
14693 Visit
(Record_Extension_Part
(Nod
));
14694 Visit
(Subtype_Indication
(Nod
));
14696 when N_Entry_Declaration
=>
14698 -- A protected type with at leat one entry is not preelaborable
14699 -- while task types are never preelaborable. This renders entry
14700 -- declarations non-preelaborable.
14702 raise Non_Preelaborable
;
14704 when N_Full_Type_Declaration
=>
14706 -- Defining_Identifier and Discriminant_Specifications are left
14707 -- out because they are not relevant for preelaborability.
14709 Visit
(Type_Definition
(Nod
));
14711 when N_Function_Instantiation
14712 | N_Package_Instantiation
14713 | N_Procedure_Instantiation
14715 -- Defining_Unit_Name and Name are left out because they are
14716 -- not relevant for preelaborability.
14718 Visit_List
(Generic_Associations
(Nod
));
14720 when N_Object_Declaration
=>
14722 -- Defining_Identifier is left out because it is not relevant
14723 -- for preelaborability.
14725 Visit
(Object_Definition
(Nod
));
14727 if Has_Init_Expression
(Nod
) then
14728 Visit
(Expression
(Nod
));
14730 elsif not Has_Preelaborable_Initialization
14731 (Etype
(Defining_Entity
(Nod
)))
14733 raise Non_Preelaborable
;
14736 when N_Private_Extension_Declaration
14737 | N_Subtype_Declaration
14739 -- Defining_Identifier, Discriminant_Specifications, and
14740 -- Interface_List are left out because they are not relevant
14741 -- for preelaborability.
14743 Visit
(Subtype_Indication
(Nod
));
14745 when N_Protected_Type_Declaration
14746 | N_Single_Protected_Declaration
14748 -- Defining_Identifier, Discriminant_Specifications, and
14749 -- Interface_List are left out because they are not relevant
14750 -- for preelaborability.
14752 Visit
(Protected_Definition
(Nod
));
14754 -- A [single] task type is never preelaborable
14756 when N_Single_Task_Declaration
14757 | N_Task_Type_Declaration
14759 raise Non_Preelaborable
;
14764 Visit_Pragma
(Nod
);
14768 when N_Statement_Other_Than_Procedure_Call
=>
14769 if Nkind
(Nod
) /= N_Null_Statement
then
14770 raise Non_Preelaborable
;
14776 Visit_Subexpression
(Nod
);
14780 when N_Access_To_Object_Definition
=>
14781 Visit
(Subtype_Indication
(Nod
));
14783 when N_Case_Expression_Alternative
=>
14784 Visit
(Expression
(Nod
));
14785 Visit_List
(Discrete_Choices
(Nod
));
14787 when N_Component_Definition
=>
14788 Visit
(Access_Definition
(Nod
));
14789 Visit
(Subtype_Indication
(Nod
));
14791 when N_Component_List
=>
14792 Visit_List
(Component_Items
(Nod
));
14793 Visit
(Variant_Part
(Nod
));
14795 when N_Constrained_Array_Definition
=>
14796 Visit_List
(Discrete_Subtype_Definitions
(Nod
));
14797 Visit
(Component_Definition
(Nod
));
14799 when N_Delta_Constraint
14800 | N_Digits_Constraint
14802 -- Delta_Expression and Digits_Expression are left out because
14803 -- they are not relevant for preelaborability.
14805 Visit
(Range_Constraint
(Nod
));
14807 when N_Discriminant_Specification
=>
14809 -- Defining_Identifier and Expression are left out because they
14810 -- are not relevant for preelaborability.
14812 Visit
(Discriminant_Type
(Nod
));
14814 when N_Generic_Association
=>
14816 -- Selector_Name is left out because it is not relevant for
14817 -- preelaborability.
14819 Visit
(Explicit_Generic_Actual_Parameter
(Nod
));
14821 when N_Index_Or_Discriminant_Constraint
=>
14822 Visit_List
(Constraints
(Nod
));
14824 when N_Iterator_Specification
=>
14826 -- Defining_Identifier is left out because it is not relevant
14827 -- for preelaborability.
14829 Visit
(Name
(Nod
));
14830 Visit
(Subtype_Indication
(Nod
));
14832 when N_Loop_Parameter_Specification
=>
14834 -- Defining_Identifier is left out because it is not relevant
14835 -- for preelaborability.
14837 Visit
(Discrete_Subtype_Definition
(Nod
));
14839 when N_Protected_Definition
=>
14841 -- End_Label is left out because it is not relevant for
14842 -- preelaborability.
14844 Visit_List
(Private_Declarations
(Nod
));
14845 Visit_List
(Visible_Declarations
(Nod
));
14847 when N_Range_Constraint
=>
14848 Visit
(Range_Expression
(Nod
));
14850 when N_Record_Definition
14853 -- End_Label, Discrete_Choices, and Interface_List are left out
14854 -- because they are not relevant for preelaborability.
14856 Visit
(Component_List
(Nod
));
14858 when N_Subtype_Indication
=>
14860 -- Subtype_Mark is left out because it is not relevant for
14861 -- preelaborability.
14863 Visit
(Constraint
(Nod
));
14865 when N_Unconstrained_Array_Definition
=>
14867 -- Subtype_Marks is left out because it is not relevant for
14868 -- preelaborability.
14870 Visit
(Component_Definition
(Nod
));
14872 when N_Variant_Part
=>
14874 -- Name is left out because it is not relevant for
14875 -- preelaborability.
14877 Visit_List
(Variants
(Nod
));
14890 procedure Visit_List
(List
: List_Id
) is
14894 if Present
(List
) then
14895 Nod
:= First
(List
);
14896 while Present
(Nod
) loop
14907 procedure Visit_Pragma
(Prag
: Node_Id
) is
14909 case Get_Pragma_Id
(Prag
) is
14911 | Pragma_Assert_And_Cut
14913 | Pragma_Async_Readers
14914 | Pragma_Async_Writers
14915 | Pragma_Attribute_Definition
14917 | Pragma_Constant_After_Elaboration
14919 | Pragma_Deadline_Floor
14920 | Pragma_Dispatching_Domain
14921 | Pragma_Effective_Reads
14922 | Pragma_Effective_Writes
14923 | Pragma_Extensions_Visible
14925 | Pragma_Secondary_Stack_Size
14927 | Pragma_Volatile_Function
14929 Visit_List
(Pragma_Argument_Associations
(Prag
));
14938 -------------------------
14939 -- Visit_Subexpression --
14940 -------------------------
14942 procedure Visit_Subexpression
(Expr
: Node_Id
) is
14943 procedure Visit_Aggregate
(Aggr
: Node_Id
);
14944 pragma Inline
(Visit_Aggregate
);
14945 -- Semantically inspect aggregate Aggr to determine whether it
14946 -- violates preelaborability.
14948 ---------------------
14949 -- Visit_Aggregate --
14950 ---------------------
14952 procedure Visit_Aggregate
(Aggr
: Node_Id
) is
14954 if not Is_Preelaborable_Aggregate
(Aggr
) then
14955 raise Non_Preelaborable
;
14957 end Visit_Aggregate
;
14959 -- Start of processing for Visit_Subexpression
14962 case Nkind
(Expr
) is
14964 | N_Qualified_Expression
14965 | N_Type_Conversion
14966 | N_Unchecked_Expression
14967 | N_Unchecked_Type_Conversion
14969 -- Subpool_Handle_Name and Subtype_Mark are left out because
14970 -- they are not relevant for preelaborability.
14972 Visit
(Expression
(Expr
));
14975 | N_Extension_Aggregate
14977 Visit_Aggregate
(Expr
);
14979 when N_Attribute_Reference
14980 | N_Explicit_Dereference
14983 -- Attribute_Name and Expressions are left out because they are
14984 -- not relevant for preelaborability.
14986 Visit
(Prefix
(Expr
));
14988 when N_Case_Expression
=>
14990 -- End_Span is left out because it is not relevant for
14991 -- preelaborability.
14993 Visit_List
(Alternatives
(Expr
));
14994 Visit
(Expression
(Expr
));
14996 when N_Delta_Aggregate
=>
14997 Visit_Aggregate
(Expr
);
14998 Visit
(Expression
(Expr
));
15000 when N_Expression_With_Actions
=>
15001 Visit_List
(Actions
(Expr
));
15002 Visit
(Expression
(Expr
));
15004 when N_If_Expression
=>
15005 Visit_List
(Expressions
(Expr
));
15007 when N_Quantified_Expression
=>
15008 Visit
(Condition
(Expr
));
15009 Visit
(Iterator_Specification
(Expr
));
15010 Visit
(Loop_Parameter_Specification
(Expr
));
15013 Visit
(High_Bound
(Expr
));
15014 Visit
(Low_Bound
(Expr
));
15017 Visit
(Discrete_Range
(Expr
));
15018 Visit
(Prefix
(Expr
));
15024 -- The evaluation of an object name is not preelaborable,
15025 -- unless the name is a static expression (checked further
15026 -- below), or statically denotes a discriminant.
15028 if Is_Entity_Name
(Expr
) then
15029 Object_Name
: declare
15030 Id
: constant Entity_Id
:= Entity
(Expr
);
15033 if Is_Object
(Id
) then
15034 if Ekind
(Id
) = E_Discriminant
then
15037 elsif Ekind_In
(Id
, E_Constant
, E_In_Parameter
)
15038 and then Present
(Discriminal_Link
(Id
))
15043 raise Non_Preelaborable
;
15048 -- A non-static expression is not preelaborable
15050 elsif not Is_OK_Static_Expression
(Expr
) then
15051 raise Non_Preelaborable
;
15054 end Visit_Subexpression
;
15056 -- Start of processing for Is_Non_Preelaborable_Construct
15061 -- At this point it is known that the construct is preelaborable
15067 -- The elaboration of the construct performs an action which violates
15068 -- preelaborability.
15070 when Non_Preelaborable
=>
15072 end Is_Non_Preelaborable_Construct
;
15074 ---------------------------------
15075 -- Is_Nontrivial_DIC_Procedure --
15076 ---------------------------------
15078 function Is_Nontrivial_DIC_Procedure
(Id
: Entity_Id
) return Boolean is
15079 Body_Decl
: Node_Id
;
15083 if Ekind
(Id
) = E_Procedure
and then Is_DIC_Procedure
(Id
) then
15085 Unit_Declaration_Node
15086 (Corresponding_Body
(Unit_Declaration_Node
(Id
)));
15088 -- The body of the Default_Initial_Condition procedure must contain
15089 -- at least one statement, otherwise the generation of the subprogram
15092 pragma Assert
(Present
(Handled_Statement_Sequence
(Body_Decl
)));
15094 -- To qualify as nontrivial, the first statement of the procedure
15095 -- must be a check in the form of an if statement. If the original
15096 -- Default_Initial_Condition expression was folded, then the first
15097 -- statement is not a check.
15099 Stmt
:= First
(Statements
(Handled_Statement_Sequence
(Body_Decl
)));
15102 Nkind
(Stmt
) = N_If_Statement
15103 and then Nkind
(Original_Node
(Stmt
)) = N_Pragma
;
15107 end Is_Nontrivial_DIC_Procedure
;
15109 -------------------------
15110 -- Is_Null_Record_Type --
15111 -------------------------
15113 function Is_Null_Record_Type
(T
: Entity_Id
) return Boolean is
15114 Decl
: constant Node_Id
:= Parent
(T
);
15116 return Nkind
(Decl
) = N_Full_Type_Declaration
15117 and then Nkind
(Type_Definition
(Decl
)) = N_Record_Definition
15119 (No
(Component_List
(Type_Definition
(Decl
)))
15120 or else Null_Present
(Component_List
(Type_Definition
(Decl
))));
15121 end Is_Null_Record_Type
;
15123 ---------------------
15124 -- Is_Object_Image --
15125 ---------------------
15127 function Is_Object_Image
(Prefix
: Node_Id
) return Boolean is
15129 -- When the type of the prefix is not scalar, then the prefix is not
15130 -- valid in any scenario.
15132 if not Is_Scalar_Type
(Etype
(Prefix
)) then
15136 -- Here we test for the case that the prefix is not a type and assume
15137 -- if it is not then it must be a named value or an object reference.
15138 -- This is because the parser always checks that prefixes of attributes
15141 return not (Is_Entity_Name
(Prefix
) and then Is_Type
(Entity
(Prefix
)));
15142 end Is_Object_Image
;
15144 -------------------------
15145 -- Is_Object_Reference --
15146 -------------------------
15148 function Is_Object_Reference
(N
: Node_Id
) return Boolean is
15149 function Is_Internally_Generated_Renaming
(N
: Node_Id
) return Boolean;
15150 -- Determine whether N is the name of an internally-generated renaming
15152 --------------------------------------
15153 -- Is_Internally_Generated_Renaming --
15154 --------------------------------------
15156 function Is_Internally_Generated_Renaming
(N
: Node_Id
) return Boolean is
15161 while Present
(P
) loop
15162 if Nkind
(P
) = N_Object_Renaming_Declaration
then
15163 return not Comes_From_Source
(P
);
15164 elsif Is_List_Member
(P
) then
15172 end Is_Internally_Generated_Renaming
;
15174 -- Start of processing for Is_Object_Reference
15177 if Is_Entity_Name
(N
) then
15178 return Present
(Entity
(N
)) and then Is_Object
(Entity
(N
));
15182 when N_Indexed_Component
15186 Is_Object_Reference
(Prefix
(N
))
15187 or else Is_Access_Type
(Etype
(Prefix
(N
)));
15189 -- In Ada 95, a function call is a constant object; a procedure
15192 -- Note that predefined operators are functions as well, and so
15193 -- are attributes that are (can be renamed as) functions.
15199 return Etype
(N
) /= Standard_Void_Type
;
15201 -- Attributes references 'Loop_Entry, 'Old, and 'Result yield
15202 -- objects, even though they are not functions.
15204 when N_Attribute_Reference
=>
15206 Nam_In
(Attribute_Name
(N
), Name_Loop_Entry
,
15209 or else Is_Function_Attribute_Name
(Attribute_Name
(N
));
15211 when N_Selected_Component
=>
15213 Is_Object_Reference
(Selector_Name
(N
))
15215 (Is_Object_Reference
(Prefix
(N
))
15216 or else Is_Access_Type
(Etype
(Prefix
(N
))));
15218 -- An explicit dereference denotes an object, except that a
15219 -- conditional expression gets turned into an explicit dereference
15220 -- in some cases, and conditional expressions are not object
15223 when N_Explicit_Dereference
=>
15224 return not Nkind_In
(Original_Node
(N
), N_Case_Expression
,
15227 -- A view conversion of a tagged object is an object reference
15229 when N_Type_Conversion
=>
15230 return Is_Tagged_Type
(Etype
(Subtype_Mark
(N
)))
15231 and then Is_Tagged_Type
(Etype
(Expression
(N
)))
15232 and then Is_Object_Reference
(Expression
(N
));
15234 -- An unchecked type conversion is considered to be an object if
15235 -- the operand is an object (this construction arises only as a
15236 -- result of expansion activities).
15238 when N_Unchecked_Type_Conversion
=>
15241 -- Allow string literals to act as objects as long as they appear
15242 -- in internally-generated renamings. The expansion of iterators
15243 -- may generate such renamings when the range involves a string
15246 when N_String_Literal
=>
15247 return Is_Internally_Generated_Renaming
(Parent
(N
));
15249 -- AI05-0003: In Ada 2012 a qualified expression is a name.
15250 -- This allows disambiguation of function calls and the use
15251 -- of aggregates in more contexts.
15253 when N_Qualified_Expression
=>
15254 if Ada_Version
< Ada_2012
then
15257 return Is_Object_Reference
(Expression
(N
))
15258 or else Nkind
(Expression
(N
)) = N_Aggregate
;
15265 end Is_Object_Reference
;
15267 -----------------------------------
15268 -- Is_OK_Variable_For_Out_Formal --
15269 -----------------------------------
15271 function Is_OK_Variable_For_Out_Formal
(AV
: Node_Id
) return Boolean is
15273 Note_Possible_Modification
(AV
, Sure
=> True);
15275 -- We must reject parenthesized variable names. Comes_From_Source is
15276 -- checked because there are currently cases where the compiler violates
15277 -- this rule (e.g. passing a task object to its controlled Initialize
15278 -- routine). This should be properly documented in sinfo???
15280 if Paren_Count
(AV
) > 0 and then Comes_From_Source
(AV
) then
15283 -- A variable is always allowed
15285 elsif Is_Variable
(AV
) then
15288 -- Generalized indexing operations are rewritten as explicit
15289 -- dereferences, and it is only during resolution that we can
15290 -- check whether the context requires an access_to_variable type.
15292 elsif Nkind
(AV
) = N_Explicit_Dereference
15293 and then Ada_Version
>= Ada_2012
15294 and then Nkind
(Original_Node
(AV
)) = N_Indexed_Component
15295 and then Present
(Etype
(Original_Node
(AV
)))
15296 and then Has_Implicit_Dereference
(Etype
(Original_Node
(AV
)))
15298 return not Is_Access_Constant
(Etype
(Prefix
(AV
)));
15300 -- Unchecked conversions are allowed only if they come from the
15301 -- generated code, which sometimes uses unchecked conversions for out
15302 -- parameters in cases where code generation is unaffected. We tell
15303 -- source unchecked conversions by seeing if they are rewrites of
15304 -- an original Unchecked_Conversion function call, or of an explicit
15305 -- conversion of a function call or an aggregate (as may happen in the
15306 -- expansion of a packed array aggregate).
15308 elsif Nkind
(AV
) = N_Unchecked_Type_Conversion
then
15309 if Nkind_In
(Original_Node
(AV
), N_Function_Call
, N_Aggregate
) then
15312 elsif Comes_From_Source
(AV
)
15313 and then Nkind
(Original_Node
(Expression
(AV
))) = N_Function_Call
15317 elsif Nkind
(Original_Node
(AV
)) = N_Type_Conversion
then
15318 return Is_OK_Variable_For_Out_Formal
(Expression
(AV
));
15324 -- Normal type conversions are allowed if argument is a variable
15326 elsif Nkind
(AV
) = N_Type_Conversion
then
15327 if Is_Variable
(Expression
(AV
))
15328 and then Paren_Count
(Expression
(AV
)) = 0
15330 Note_Possible_Modification
(Expression
(AV
), Sure
=> True);
15333 -- We also allow a non-parenthesized expression that raises
15334 -- constraint error if it rewrites what used to be a variable
15336 elsif Raises_Constraint_Error
(Expression
(AV
))
15337 and then Paren_Count
(Expression
(AV
)) = 0
15338 and then Is_Variable
(Original_Node
(Expression
(AV
)))
15342 -- Type conversion of something other than a variable
15348 -- If this node is rewritten, then test the original form, if that is
15349 -- OK, then we consider the rewritten node OK (for example, if the
15350 -- original node is a conversion, then Is_Variable will not be true
15351 -- but we still want to allow the conversion if it converts a variable).
15353 elsif Original_Node
(AV
) /= AV
then
15355 -- In Ada 2012, the explicit dereference may be a rewritten call to a
15356 -- Reference function.
15358 if Ada_Version
>= Ada_2012
15359 and then Nkind
(Original_Node
(AV
)) = N_Function_Call
15361 Has_Implicit_Dereference
(Etype
(Name
(Original_Node
(AV
))))
15364 -- Check that this is not a constant reference.
15366 return not Is_Access_Constant
(Etype
(Prefix
(AV
)));
15368 elsif Has_Implicit_Dereference
(Etype
(Original_Node
(AV
))) then
15370 not Is_Access_Constant
(Etype
15371 (Get_Reference_Discriminant
(Etype
(Original_Node
(AV
)))));
15374 return Is_OK_Variable_For_Out_Formal
(Original_Node
(AV
));
15377 -- All other non-variables are rejected
15382 end Is_OK_Variable_For_Out_Formal
;
15384 ----------------------------
15385 -- Is_OK_Volatile_Context --
15386 ----------------------------
15388 function Is_OK_Volatile_Context
15389 (Context
: Node_Id
;
15390 Obj_Ref
: Node_Id
) return Boolean
15392 function Is_Protected_Operation_Call
(Nod
: Node_Id
) return Boolean;
15393 -- Determine whether an arbitrary node denotes a call to a protected
15394 -- entry, function, or procedure in prefixed form where the prefix is
15397 function Within_Check
(Nod
: Node_Id
) return Boolean;
15398 -- Determine whether an arbitrary node appears in a check node
15400 function Within_Volatile_Function
(Id
: Entity_Id
) return Boolean;
15401 -- Determine whether an arbitrary entity appears in a volatile function
15403 ---------------------------------
15404 -- Is_Protected_Operation_Call --
15405 ---------------------------------
15407 function Is_Protected_Operation_Call
(Nod
: Node_Id
) return Boolean is
15412 -- A call to a protected operations retains its selected component
15413 -- form as opposed to other prefixed calls that are transformed in
15416 if Nkind
(Nod
) = N_Selected_Component
then
15417 Pref
:= Prefix
(Nod
);
15418 Subp
:= Selector_Name
(Nod
);
15422 and then Present
(Etype
(Pref
))
15423 and then Is_Protected_Type
(Etype
(Pref
))
15424 and then Is_Entity_Name
(Subp
)
15425 and then Present
(Entity
(Subp
))
15426 and then Ekind_In
(Entity
(Subp
), E_Entry
,
15433 end Is_Protected_Operation_Call
;
15439 function Within_Check
(Nod
: Node_Id
) return Boolean is
15443 -- Climb the parent chain looking for a check node
15446 while Present
(Par
) loop
15447 if Nkind
(Par
) in N_Raise_xxx_Error
then
15450 -- Prevent the search from going too far
15452 elsif Is_Body_Or_Package_Declaration
(Par
) then
15456 Par
:= Parent
(Par
);
15462 ------------------------------
15463 -- Within_Volatile_Function --
15464 ------------------------------
15466 function Within_Volatile_Function
(Id
: Entity_Id
) return Boolean is
15467 Func_Id
: Entity_Id
;
15470 -- Traverse the scope stack looking for a [generic] function
15473 while Present
(Func_Id
) and then Func_Id
/= Standard_Standard
loop
15474 if Ekind_In
(Func_Id
, E_Function
, E_Generic_Function
) then
15475 return Is_Volatile_Function
(Func_Id
);
15478 Func_Id
:= Scope
(Func_Id
);
15482 end Within_Volatile_Function
;
15486 Obj_Id
: Entity_Id
;
15488 -- Start of processing for Is_OK_Volatile_Context
15491 -- The volatile object appears on either side of an assignment
15493 if Nkind
(Context
) = N_Assignment_Statement
then
15496 -- The volatile object is part of the initialization expression of
15499 elsif Nkind
(Context
) = N_Object_Declaration
15500 and then Present
(Expression
(Context
))
15501 and then Expression
(Context
) = Obj_Ref
15503 Obj_Id
:= Defining_Entity
(Context
);
15505 -- The volatile object acts as the initialization expression of an
15506 -- extended return statement. This is valid context as long as the
15507 -- function is volatile.
15509 if Is_Return_Object
(Obj_Id
) then
15510 return Within_Volatile_Function
(Obj_Id
);
15512 -- Otherwise this is a normal object initialization
15518 -- The volatile object acts as the name of a renaming declaration
15520 elsif Nkind
(Context
) = N_Object_Renaming_Declaration
15521 and then Name
(Context
) = Obj_Ref
15525 -- The volatile object appears as an actual parameter in a call to an
15526 -- instance of Unchecked_Conversion whose result is renamed.
15528 elsif Nkind
(Context
) = N_Function_Call
15529 and then Is_Entity_Name
(Name
(Context
))
15530 and then Is_Unchecked_Conversion_Instance
(Entity
(Name
(Context
)))
15531 and then Nkind
(Parent
(Context
)) = N_Object_Renaming_Declaration
15535 -- The volatile object is actually the prefix in a protected entry,
15536 -- function, or procedure call.
15538 elsif Is_Protected_Operation_Call
(Context
) then
15541 -- The volatile object appears as the expression of a simple return
15542 -- statement that applies to a volatile function.
15544 elsif Nkind
(Context
) = N_Simple_Return_Statement
15545 and then Expression
(Context
) = Obj_Ref
15548 Within_Volatile_Function
(Return_Statement_Entity
(Context
));
15550 -- The volatile object appears as the prefix of a name occurring in a
15551 -- non-interfering context.
15553 elsif Nkind_In
(Context
, N_Attribute_Reference
,
15554 N_Explicit_Dereference
,
15555 N_Indexed_Component
,
15556 N_Selected_Component
,
15558 and then Prefix
(Context
) = Obj_Ref
15559 and then Is_OK_Volatile_Context
15560 (Context
=> Parent
(Context
),
15561 Obj_Ref
=> Context
)
15565 -- The volatile object appears as the prefix of attributes Address,
15566 -- Alignment, Component_Size, First_Bit, Last_Bit, Position, Size,
15569 elsif Nkind
(Context
) = N_Attribute_Reference
15570 and then Prefix
(Context
) = Obj_Ref
15571 and then Nam_In
(Attribute_Name
(Context
), Name_Address
,
15573 Name_Component_Size
,
15582 -- The volatile object appears as the expression of a type conversion
15583 -- occurring in a non-interfering context.
15585 elsif Nkind_In
(Context
, N_Type_Conversion
,
15586 N_Unchecked_Type_Conversion
)
15587 and then Expression
(Context
) = Obj_Ref
15588 and then Is_OK_Volatile_Context
15589 (Context
=> Parent
(Context
),
15590 Obj_Ref
=> Context
)
15594 -- The volatile object appears as the expression in a delay statement
15596 elsif Nkind
(Context
) in N_Delay_Statement
then
15599 -- Allow references to volatile objects in various checks. This is not a
15600 -- direct SPARK 2014 requirement.
15602 elsif Within_Check
(Context
) then
15605 -- Assume that references to effectively volatile objects that appear
15606 -- as actual parameters in a subprogram call are always legal. A full
15607 -- legality check is done when the actuals are resolved (see routine
15608 -- Resolve_Actuals).
15610 elsif Within_Subprogram_Call
(Context
) then
15613 -- Otherwise the context is not suitable for an effectively volatile
15619 end Is_OK_Volatile_Context
;
15621 ------------------------------------
15622 -- Is_Package_Contract_Annotation --
15623 ------------------------------------
15625 function Is_Package_Contract_Annotation
(Item
: Node_Id
) return Boolean is
15629 if Nkind
(Item
) = N_Aspect_Specification
then
15630 Nam
:= Chars
(Identifier
(Item
));
15632 else pragma Assert
(Nkind
(Item
) = N_Pragma
);
15633 Nam
:= Pragma_Name
(Item
);
15636 return Nam
= Name_Abstract_State
15637 or else Nam
= Name_Initial_Condition
15638 or else Nam
= Name_Initializes
15639 or else Nam
= Name_Refined_State
;
15640 end Is_Package_Contract_Annotation
;
15642 -----------------------------------
15643 -- Is_Partially_Initialized_Type --
15644 -----------------------------------
15646 function Is_Partially_Initialized_Type
15648 Include_Implicit
: Boolean := True) return Boolean
15651 if Is_Scalar_Type
(Typ
) then
15654 elsif Is_Access_Type
(Typ
) then
15655 return Include_Implicit
;
15657 elsif Is_Array_Type
(Typ
) then
15659 -- If component type is partially initialized, so is array type
15661 if Is_Partially_Initialized_Type
15662 (Component_Type
(Typ
), Include_Implicit
)
15666 -- Otherwise we are only partially initialized if we are fully
15667 -- initialized (this is the empty array case, no point in us
15668 -- duplicating that code here).
15671 return Is_Fully_Initialized_Type
(Typ
);
15674 elsif Is_Record_Type
(Typ
) then
15676 -- A discriminated type is always partially initialized if in
15679 if Has_Discriminants
(Typ
) and then Include_Implicit
then
15682 -- A tagged type is always partially initialized
15684 elsif Is_Tagged_Type
(Typ
) then
15687 -- Case of non-discriminated record
15693 Component_Present
: Boolean := False;
15694 -- Set True if at least one component is present. If no
15695 -- components are present, then record type is fully
15696 -- initialized (another odd case, like the null array).
15699 -- Loop through components
15701 Ent
:= First_Entity
(Typ
);
15702 while Present
(Ent
) loop
15703 if Ekind
(Ent
) = E_Component
then
15704 Component_Present
:= True;
15706 -- If a component has an initialization expression then
15707 -- the enclosing record type is partially initialized
15709 if Present
(Parent
(Ent
))
15710 and then Present
(Expression
(Parent
(Ent
)))
15714 -- If a component is of a type which is itself partially
15715 -- initialized, then the enclosing record type is also.
15717 elsif Is_Partially_Initialized_Type
15718 (Etype
(Ent
), Include_Implicit
)
15727 -- No initialized components found. If we found any components
15728 -- they were all uninitialized so the result is false.
15730 if Component_Present
then
15733 -- But if we found no components, then all the components are
15734 -- initialized so we consider the type to be initialized.
15742 -- Concurrent types are always fully initialized
15744 elsif Is_Concurrent_Type
(Typ
) then
15747 -- For a private type, go to underlying type. If there is no underlying
15748 -- type then just assume this partially initialized. Not clear if this
15749 -- can happen in a non-error case, but no harm in testing for this.
15751 elsif Is_Private_Type
(Typ
) then
15753 U
: constant Entity_Id
:= Underlying_Type
(Typ
);
15758 return Is_Partially_Initialized_Type
(U
, Include_Implicit
);
15762 -- For any other type (are there any?) assume partially initialized
15767 end Is_Partially_Initialized_Type
;
15769 ------------------------------------
15770 -- Is_Potentially_Persistent_Type --
15771 ------------------------------------
15773 function Is_Potentially_Persistent_Type
(T
: Entity_Id
) return Boolean is
15778 -- For private type, test corresponding full type
15780 if Is_Private_Type
(T
) then
15781 return Is_Potentially_Persistent_Type
(Full_View
(T
));
15783 -- Scalar types are potentially persistent
15785 elsif Is_Scalar_Type
(T
) then
15788 -- Record type is potentially persistent if not tagged and the types of
15789 -- all it components are potentially persistent, and no component has
15790 -- an initialization expression.
15792 elsif Is_Record_Type
(T
)
15793 and then not Is_Tagged_Type
(T
)
15794 and then not Is_Partially_Initialized_Type
(T
)
15796 Comp
:= First_Component
(T
);
15797 while Present
(Comp
) loop
15798 if not Is_Potentially_Persistent_Type
(Etype
(Comp
)) then
15801 Next_Entity
(Comp
);
15807 -- Array type is potentially persistent if its component type is
15808 -- potentially persistent and if all its constraints are static.
15810 elsif Is_Array_Type
(T
) then
15811 if not Is_Potentially_Persistent_Type
(Component_Type
(T
)) then
15815 Indx
:= First_Index
(T
);
15816 while Present
(Indx
) loop
15817 if not Is_OK_Static_Subtype
(Etype
(Indx
)) then
15826 -- All other types are not potentially persistent
15831 end Is_Potentially_Persistent_Type
;
15833 --------------------------------
15834 -- Is_Potentially_Unevaluated --
15835 --------------------------------
15837 function Is_Potentially_Unevaluated
(N
: Node_Id
) return Boolean is
15845 -- A postcondition whose expression is a short-circuit is broken down
15846 -- into individual aspects for better exception reporting. The original
15847 -- short-circuit expression is rewritten as the second operand, and an
15848 -- occurrence of 'Old in that operand is potentially unevaluated.
15849 -- See Sem_ch13.adb for details of this transformation.
15851 if Nkind
(Original_Node
(Par
)) = N_And_Then
then
15855 while not Nkind_In
(Par
, N_If_Expression
,
15861 N_Quantified_Expression
)
15864 Par
:= Parent
(Par
);
15866 -- If the context is not an expression, or if is the result of
15867 -- expansion of an enclosing construct (such as another attribute)
15868 -- the predicate does not apply.
15870 if Nkind
(Par
) = N_Case_Expression_Alternative
then
15873 elsif Nkind
(Par
) not in N_Subexpr
15874 or else not Comes_From_Source
(Par
)
15880 if Nkind
(Par
) = N_If_Expression
then
15881 return Is_Elsif
(Par
) or else Expr
/= First
(Expressions
(Par
));
15883 elsif Nkind
(Par
) = N_Case_Expression
then
15884 return Expr
/= Expression
(Par
);
15886 elsif Nkind_In
(Par
, N_And_Then
, N_Or_Else
) then
15887 return Expr
= Right_Opnd
(Par
);
15889 elsif Nkind_In
(Par
, N_In
, N_Not_In
) then
15891 -- If the membership includes several alternatives, only the first is
15892 -- definitely evaluated.
15894 if Present
(Alternatives
(Par
)) then
15895 return Expr
/= First
(Alternatives
(Par
));
15897 -- If this is a range membership both bounds are evaluated
15903 elsif Nkind
(Par
) = N_Quantified_Expression
then
15904 return Expr
= Condition
(Par
);
15909 end Is_Potentially_Unevaluated
;
15911 --------------------------------
15912 -- Is_Preelaborable_Aggregate --
15913 --------------------------------
15915 function Is_Preelaborable_Aggregate
(Aggr
: Node_Id
) return Boolean is
15916 Aggr_Typ
: constant Entity_Id
:= Etype
(Aggr
);
15917 Array_Aggr
: constant Boolean := Is_Array_Type
(Aggr_Typ
);
15919 Anc_Part
: Node_Id
;
15922 Comp_Typ
: Entity_Id
:= Empty
; -- init to avoid warning
15927 Comp_Typ
:= Component_Type
(Aggr_Typ
);
15930 -- Inspect the ancestor part
15932 if Nkind
(Aggr
) = N_Extension_Aggregate
then
15933 Anc_Part
:= Ancestor_Part
(Aggr
);
15935 -- The ancestor denotes a subtype mark
15937 if Is_Entity_Name
(Anc_Part
)
15938 and then Is_Type
(Entity
(Anc_Part
))
15940 if not Has_Preelaborable_Initialization
(Entity
(Anc_Part
)) then
15944 -- Otherwise the ancestor denotes an expression
15946 elsif not Is_Preelaborable_Construct
(Anc_Part
) then
15951 -- Inspect the positional associations
15953 Expr
:= First
(Expressions
(Aggr
));
15954 while Present
(Expr
) loop
15955 if not Is_Preelaborable_Construct
(Expr
) then
15962 -- Inspect the named associations
15964 Assoc
:= First
(Component_Associations
(Aggr
));
15965 while Present
(Assoc
) loop
15967 -- Inspect the choices of the current named association
15969 Choice
:= First
(Choices
(Assoc
));
15970 while Present
(Choice
) loop
15973 -- For a choice to be preelaborable, it must denote either a
15974 -- static range or a static expression.
15976 if Nkind
(Choice
) = N_Others_Choice
then
15979 elsif Nkind
(Choice
) = N_Range
then
15980 if not Is_OK_Static_Range
(Choice
) then
15984 elsif not Is_OK_Static_Expression
(Choice
) then
15989 Comp_Typ
:= Etype
(Choice
);
15995 -- The type of the choice must have preelaborable initialization if
15996 -- the association carries a <>.
15998 pragma Assert
(Present
(Comp_Typ
));
15999 if Box_Present
(Assoc
) then
16000 if not Has_Preelaborable_Initialization
(Comp_Typ
) then
16004 -- The type of the expression must have preelaborable initialization
16006 elsif not Is_Preelaborable_Construct
(Expression
(Assoc
)) then
16013 -- At this point the aggregate is preelaborable
16016 end Is_Preelaborable_Aggregate
;
16018 --------------------------------
16019 -- Is_Preelaborable_Construct --
16020 --------------------------------
16022 function Is_Preelaborable_Construct
(N
: Node_Id
) return Boolean is
16026 if Nkind_In
(N
, N_Aggregate
, N_Extension_Aggregate
) then
16027 return Is_Preelaborable_Aggregate
(N
);
16029 -- Attributes are allowed in general, even if their prefix is a formal
16030 -- type. It seems that certain attributes known not to be static might
16031 -- not be allowed, but there are no rules to prevent them.
16033 elsif Nkind
(N
) = N_Attribute_Reference
then
16038 elsif Nkind
(N
) in N_Subexpr
and then Is_OK_Static_Expression
(N
) then
16041 elsif Nkind
(N
) = N_Qualified_Expression
then
16042 return Is_Preelaborable_Construct
(Expression
(N
));
16044 -- Names are preelaborable when they denote a discriminant of an
16045 -- enclosing type. Discriminals are also considered for this check.
16047 elsif Is_Entity_Name
(N
)
16048 and then Present
(Entity
(N
))
16050 (Ekind
(Entity
(N
)) = E_Discriminant
16051 or else (Ekind_In
(Entity
(N
), E_Constant
, E_In_Parameter
)
16052 and then Present
(Discriminal_Link
(Entity
(N
)))))
16058 elsif Nkind
(N
) = N_Null
then
16061 -- Otherwise the construct is not preelaborable
16066 end Is_Preelaborable_Construct
;
16068 ---------------------------------
16069 -- Is_Protected_Self_Reference --
16070 ---------------------------------
16072 function Is_Protected_Self_Reference
(N
: Node_Id
) return Boolean is
16074 function In_Access_Definition
(N
: Node_Id
) return Boolean;
16075 -- Returns true if N belongs to an access definition
16077 --------------------------
16078 -- In_Access_Definition --
16079 --------------------------
16081 function In_Access_Definition
(N
: Node_Id
) return Boolean is
16086 while Present
(P
) loop
16087 if Nkind
(P
) = N_Access_Definition
then
16095 end In_Access_Definition
;
16097 -- Start of processing for Is_Protected_Self_Reference
16100 -- Verify that prefix is analyzed and has the proper form. Note that
16101 -- the attributes Elab_Spec, Elab_Body, and Elab_Subp_Body, which also
16102 -- produce the address of an entity, do not analyze their prefix
16103 -- because they denote entities that are not necessarily visible.
16104 -- Neither of them can apply to a protected type.
16106 return Ada_Version
>= Ada_2005
16107 and then Is_Entity_Name
(N
)
16108 and then Present
(Entity
(N
))
16109 and then Is_Protected_Type
(Entity
(N
))
16110 and then In_Open_Scopes
(Entity
(N
))
16111 and then not In_Access_Definition
(N
);
16112 end Is_Protected_Self_Reference
;
16114 -----------------------------
16115 -- Is_RCI_Pkg_Spec_Or_Body --
16116 -----------------------------
16118 function Is_RCI_Pkg_Spec_Or_Body
(Cunit
: Node_Id
) return Boolean is
16120 function Is_RCI_Pkg_Decl_Cunit
(Cunit
: Node_Id
) return Boolean;
16121 -- Return True if the unit of Cunit is an RCI package declaration
16123 ---------------------------
16124 -- Is_RCI_Pkg_Decl_Cunit --
16125 ---------------------------
16127 function Is_RCI_Pkg_Decl_Cunit
(Cunit
: Node_Id
) return Boolean is
16128 The_Unit
: constant Node_Id
:= Unit
(Cunit
);
16131 if Nkind
(The_Unit
) /= N_Package_Declaration
then
16135 return Is_Remote_Call_Interface
(Defining_Entity
(The_Unit
));
16136 end Is_RCI_Pkg_Decl_Cunit
;
16138 -- Start of processing for Is_RCI_Pkg_Spec_Or_Body
16141 return Is_RCI_Pkg_Decl_Cunit
(Cunit
)
16143 (Nkind
(Unit
(Cunit
)) = N_Package_Body
16144 and then Is_RCI_Pkg_Decl_Cunit
(Library_Unit
(Cunit
)));
16145 end Is_RCI_Pkg_Spec_Or_Body
;
16147 -----------------------------------------
16148 -- Is_Remote_Access_To_Class_Wide_Type --
16149 -----------------------------------------
16151 function Is_Remote_Access_To_Class_Wide_Type
16152 (E
: Entity_Id
) return Boolean
16155 -- A remote access to class-wide type is a general access to object type
16156 -- declared in the visible part of a Remote_Types or Remote_Call_
16159 return Ekind
(E
) = E_General_Access_Type
16160 and then (Is_Remote_Call_Interface
(E
) or else Is_Remote_Types
(E
));
16161 end Is_Remote_Access_To_Class_Wide_Type
;
16163 -----------------------------------------
16164 -- Is_Remote_Access_To_Subprogram_Type --
16165 -----------------------------------------
16167 function Is_Remote_Access_To_Subprogram_Type
16168 (E
: Entity_Id
) return Boolean
16171 return (Ekind
(E
) = E_Access_Subprogram_Type
16172 or else (Ekind
(E
) = E_Record_Type
16173 and then Present
(Corresponding_Remote_Type
(E
))))
16174 and then (Is_Remote_Call_Interface
(E
) or else Is_Remote_Types
(E
));
16175 end Is_Remote_Access_To_Subprogram_Type
;
16177 --------------------
16178 -- Is_Remote_Call --
16179 --------------------
16181 function Is_Remote_Call
(N
: Node_Id
) return Boolean is
16183 if Nkind
(N
) not in N_Subprogram_Call
then
16185 -- An entry call cannot be remote
16189 elsif Nkind
(Name
(N
)) in N_Has_Entity
16190 and then Is_Remote_Call_Interface
(Entity
(Name
(N
)))
16192 -- A subprogram declared in the spec of a RCI package is remote
16196 elsif Nkind
(Name
(N
)) = N_Explicit_Dereference
16197 and then Is_Remote_Access_To_Subprogram_Type
16198 (Etype
(Prefix
(Name
(N
))))
16200 -- The dereference of a RAS is a remote call
16204 elsif Present
(Controlling_Argument
(N
))
16205 and then Is_Remote_Access_To_Class_Wide_Type
16206 (Etype
(Controlling_Argument
(N
)))
16208 -- Any primitive operation call with a controlling argument of
16209 -- a RACW type is a remote call.
16214 -- All other calls are local calls
16217 end Is_Remote_Call
;
16219 ----------------------
16220 -- Is_Renamed_Entry --
16221 ----------------------
16223 function Is_Renamed_Entry
(Proc_Nam
: Entity_Id
) return Boolean is
16224 Orig_Node
: Node_Id
:= Empty
;
16225 Subp_Decl
: Node_Id
:= Parent
(Parent
(Proc_Nam
));
16227 function Is_Entry
(Nam
: Node_Id
) return Boolean;
16228 -- Determine whether Nam is an entry. Traverse selectors if there are
16229 -- nested selected components.
16235 function Is_Entry
(Nam
: Node_Id
) return Boolean is
16237 if Nkind
(Nam
) = N_Selected_Component
then
16238 return Is_Entry
(Selector_Name
(Nam
));
16241 return Ekind
(Entity
(Nam
)) = E_Entry
;
16244 -- Start of processing for Is_Renamed_Entry
16247 if Present
(Alias
(Proc_Nam
)) then
16248 Subp_Decl
:= Parent
(Parent
(Alias
(Proc_Nam
)));
16251 -- Look for a rewritten subprogram renaming declaration
16253 if Nkind
(Subp_Decl
) = N_Subprogram_Declaration
16254 and then Present
(Original_Node
(Subp_Decl
))
16256 Orig_Node
:= Original_Node
(Subp_Decl
);
16259 -- The rewritten subprogram is actually an entry
16261 if Present
(Orig_Node
)
16262 and then Nkind
(Orig_Node
) = N_Subprogram_Renaming_Declaration
16263 and then Is_Entry
(Name
(Orig_Node
))
16269 end Is_Renamed_Entry
;
16271 -----------------------------
16272 -- Is_Renaming_Declaration --
16273 -----------------------------
16275 function Is_Renaming_Declaration
(N
: Node_Id
) return Boolean is
16278 when N_Exception_Renaming_Declaration
16279 | N_Generic_Function_Renaming_Declaration
16280 | N_Generic_Package_Renaming_Declaration
16281 | N_Generic_Procedure_Renaming_Declaration
16282 | N_Object_Renaming_Declaration
16283 | N_Package_Renaming_Declaration
16284 | N_Subprogram_Renaming_Declaration
16291 end Is_Renaming_Declaration
;
16293 ----------------------------
16294 -- Is_Reversible_Iterator --
16295 ----------------------------
16297 function Is_Reversible_Iterator
(Typ
: Entity_Id
) return Boolean is
16298 Ifaces_List
: Elist_Id
;
16299 Iface_Elmt
: Elmt_Id
;
16303 if Is_Class_Wide_Type
(Typ
)
16304 and then Chars
(Root_Type
(Typ
)) = Name_Reversible_Iterator
16305 and then In_Predefined_Unit
(Root_Type
(Typ
))
16309 elsif not Is_Tagged_Type
(Typ
) or else not Is_Derived_Type
(Typ
) then
16313 Collect_Interfaces
(Typ
, Ifaces_List
);
16315 Iface_Elmt
:= First_Elmt
(Ifaces_List
);
16316 while Present
(Iface_Elmt
) loop
16317 Iface
:= Node
(Iface_Elmt
);
16318 if Chars
(Iface
) = Name_Reversible_Iterator
16319 and then In_Predefined_Unit
(Iface
)
16324 Next_Elmt
(Iface_Elmt
);
16329 end Is_Reversible_Iterator
;
16331 ----------------------
16332 -- Is_Selector_Name --
16333 ----------------------
16335 function Is_Selector_Name
(N
: Node_Id
) return Boolean is
16337 if not Is_List_Member
(N
) then
16339 P
: constant Node_Id
:= Parent
(N
);
16341 return Nkind_In
(P
, N_Expanded_Name
,
16342 N_Generic_Association
,
16343 N_Parameter_Association
,
16344 N_Selected_Component
)
16345 and then Selector_Name
(P
) = N
;
16350 L
: constant List_Id
:= List_Containing
(N
);
16351 P
: constant Node_Id
:= Parent
(L
);
16353 return (Nkind
(P
) = N_Discriminant_Association
16354 and then Selector_Names
(P
) = L
)
16356 (Nkind
(P
) = N_Component_Association
16357 and then Choices
(P
) = L
);
16360 end Is_Selector_Name
;
16362 ---------------------------------
16363 -- Is_Single_Concurrent_Object --
16364 ---------------------------------
16366 function Is_Single_Concurrent_Object
(Id
: Entity_Id
) return Boolean is
16369 Is_Single_Protected_Object
(Id
) or else Is_Single_Task_Object
(Id
);
16370 end Is_Single_Concurrent_Object
;
16372 -------------------------------
16373 -- Is_Single_Concurrent_Type --
16374 -------------------------------
16376 function Is_Single_Concurrent_Type
(Id
: Entity_Id
) return Boolean is
16379 Ekind_In
(Id
, E_Protected_Type
, E_Task_Type
)
16380 and then Is_Single_Concurrent_Type_Declaration
16381 (Declaration_Node
(Id
));
16382 end Is_Single_Concurrent_Type
;
16384 -------------------------------------------
16385 -- Is_Single_Concurrent_Type_Declaration --
16386 -------------------------------------------
16388 function Is_Single_Concurrent_Type_Declaration
16389 (N
: Node_Id
) return Boolean
16392 return Nkind_In
(Original_Node
(N
), N_Single_Protected_Declaration
,
16393 N_Single_Task_Declaration
);
16394 end Is_Single_Concurrent_Type_Declaration
;
16396 ---------------------------------------------
16397 -- Is_Single_Precision_Floating_Point_Type --
16398 ---------------------------------------------
16400 function Is_Single_Precision_Floating_Point_Type
16401 (E
: Entity_Id
) return Boolean is
16403 return Is_Floating_Point_Type
(E
)
16404 and then Machine_Radix_Value
(E
) = Uint_2
16405 and then Machine_Mantissa_Value
(E
) = Uint_24
16406 and then Machine_Emax_Value
(E
) = Uint_2
** Uint_7
16407 and then Machine_Emin_Value
(E
) = Uint_3
- (Uint_2
** Uint_7
);
16408 end Is_Single_Precision_Floating_Point_Type
;
16410 --------------------------------
16411 -- Is_Single_Protected_Object --
16412 --------------------------------
16414 function Is_Single_Protected_Object
(Id
: Entity_Id
) return Boolean is
16417 Ekind
(Id
) = E_Variable
16418 and then Ekind
(Etype
(Id
)) = E_Protected_Type
16419 and then Is_Single_Concurrent_Type
(Etype
(Id
));
16420 end Is_Single_Protected_Object
;
16422 ---------------------------
16423 -- Is_Single_Task_Object --
16424 ---------------------------
16426 function Is_Single_Task_Object
(Id
: Entity_Id
) return Boolean is
16429 Ekind
(Id
) = E_Variable
16430 and then Ekind
(Etype
(Id
)) = E_Task_Type
16431 and then Is_Single_Concurrent_Type
(Etype
(Id
));
16432 end Is_Single_Task_Object
;
16434 -------------------------------------
16435 -- Is_SPARK_05_Initialization_Expr --
16436 -------------------------------------
16438 function Is_SPARK_05_Initialization_Expr
(N
: Node_Id
) return Boolean is
16441 Comp_Assn
: Node_Id
;
16442 Orig_N
: constant Node_Id
:= Original_Node
(N
);
16447 if not Comes_From_Source
(Orig_N
) then
16451 pragma Assert
(Nkind
(Orig_N
) in N_Subexpr
);
16453 case Nkind
(Orig_N
) is
16454 when N_Character_Literal
16455 | N_Integer_Literal
16461 when N_Expanded_Name
16464 if Is_Entity_Name
(Orig_N
)
16465 and then Present
(Entity
(Orig_N
)) -- needed in some cases
16467 case Ekind
(Entity
(Orig_N
)) is
16469 | E_Enumeration_Literal
16476 if Is_Type
(Entity
(Orig_N
)) then
16484 when N_Qualified_Expression
16485 | N_Type_Conversion
16487 Is_Ok
:= Is_SPARK_05_Initialization_Expr
(Expression
(Orig_N
));
16490 Is_Ok
:= Is_SPARK_05_Initialization_Expr
(Right_Opnd
(Orig_N
));
16493 | N_Membership_Test
16496 Is_Ok
:= Is_SPARK_05_Initialization_Expr
(Left_Opnd
(Orig_N
))
16498 Is_SPARK_05_Initialization_Expr
(Right_Opnd
(Orig_N
));
16501 | N_Extension_Aggregate
16503 if Nkind
(Orig_N
) = N_Extension_Aggregate
then
16505 Is_SPARK_05_Initialization_Expr
(Ancestor_Part
(Orig_N
));
16508 Expr
:= First
(Expressions
(Orig_N
));
16509 while Present
(Expr
) loop
16510 if not Is_SPARK_05_Initialization_Expr
(Expr
) then
16518 Comp_Assn
:= First
(Component_Associations
(Orig_N
));
16519 while Present
(Comp_Assn
) loop
16520 Expr
:= Expression
(Comp_Assn
);
16522 -- Note: test for Present here needed for box assocation
16525 and then not Is_SPARK_05_Initialization_Expr
(Expr
)
16534 when N_Attribute_Reference
=>
16535 if Nkind
(Prefix
(Orig_N
)) in N_Subexpr
then
16536 Is_Ok
:= Is_SPARK_05_Initialization_Expr
(Prefix
(Orig_N
));
16539 Expr
:= First
(Expressions
(Orig_N
));
16540 while Present
(Expr
) loop
16541 if not Is_SPARK_05_Initialization_Expr
(Expr
) then
16549 -- Selected components might be expanded named not yet resolved, so
16550 -- default on the safe side. (Eg on sparklex.ads)
16552 when N_Selected_Component
=>
16561 end Is_SPARK_05_Initialization_Expr
;
16563 ----------------------------------
16564 -- Is_SPARK_05_Object_Reference --
16565 ----------------------------------
16567 function Is_SPARK_05_Object_Reference
(N
: Node_Id
) return Boolean is
16569 if Is_Entity_Name
(N
) then
16570 return Present
(Entity
(N
))
16572 (Ekind_In
(Entity
(N
), E_Constant
, E_Variable
)
16573 or else Ekind
(Entity
(N
)) in Formal_Kind
);
16577 when N_Selected_Component
=>
16578 return Is_SPARK_05_Object_Reference
(Prefix
(N
));
16584 end Is_SPARK_05_Object_Reference
;
16586 -----------------------------
16587 -- Is_Specific_Tagged_Type --
16588 -----------------------------
16590 function Is_Specific_Tagged_Type
(Typ
: Entity_Id
) return Boolean is
16591 Full_Typ
: Entity_Id
;
16594 -- Handle private types
16596 if Is_Private_Type
(Typ
) and then Present
(Full_View
(Typ
)) then
16597 Full_Typ
:= Full_View
(Typ
);
16602 -- A specific tagged type is a non-class-wide tagged type
16604 return Is_Tagged_Type
(Full_Typ
) and not Is_Class_Wide_Type
(Full_Typ
);
16605 end Is_Specific_Tagged_Type
;
16611 function Is_Statement
(N
: Node_Id
) return Boolean is
16614 Nkind
(N
) in N_Statement_Other_Than_Procedure_Call
16615 or else Nkind
(N
) = N_Procedure_Call_Statement
;
16618 ---------------------------------------
16619 -- Is_Subprogram_Contract_Annotation --
16620 ---------------------------------------
16622 function Is_Subprogram_Contract_Annotation
16623 (Item
: Node_Id
) return Boolean
16628 if Nkind
(Item
) = N_Aspect_Specification
then
16629 Nam
:= Chars
(Identifier
(Item
));
16631 else pragma Assert
(Nkind
(Item
) = N_Pragma
);
16632 Nam
:= Pragma_Name
(Item
);
16635 return Nam
= Name_Contract_Cases
16636 or else Nam
= Name_Depends
16637 or else Nam
= Name_Extensions_Visible
16638 or else Nam
= Name_Global
16639 or else Nam
= Name_Post
16640 or else Nam
= Name_Post_Class
16641 or else Nam
= Name_Postcondition
16642 or else Nam
= Name_Pre
16643 or else Nam
= Name_Pre_Class
16644 or else Nam
= Name_Precondition
16645 or else Nam
= Name_Refined_Depends
16646 or else Nam
= Name_Refined_Global
16647 or else Nam
= Name_Refined_Post
16648 or else Nam
= Name_Test_Case
;
16649 end Is_Subprogram_Contract_Annotation
;
16651 --------------------------------------------------
16652 -- Is_Subprogram_Stub_Without_Prior_Declaration --
16653 --------------------------------------------------
16655 function Is_Subprogram_Stub_Without_Prior_Declaration
16656 (N
: Node_Id
) return Boolean
16659 -- A subprogram stub without prior declaration serves as declaration for
16660 -- the actual subprogram body. As such, it has an attached defining
16661 -- entity of E_[Generic_]Function or E_[Generic_]Procedure.
16663 return Nkind
(N
) = N_Subprogram_Body_Stub
16664 and then Ekind
(Defining_Entity
(N
)) /= E_Subprogram_Body
;
16665 end Is_Subprogram_Stub_Without_Prior_Declaration
;
16667 --------------------------
16668 -- Is_Suspension_Object --
16669 --------------------------
16671 function Is_Suspension_Object
(Id
: Entity_Id
) return Boolean is
16673 -- This approach does an exact name match rather than to rely on
16674 -- RTSfind. Routine Is_Effectively_Volatile is used by clients of the
16675 -- front end at point where all auxiliary tables are locked and any
16676 -- modifications to them are treated as violations. Do not tamper with
16677 -- the tables, instead examine the Chars fields of all the scopes of Id.
16680 Chars
(Id
) = Name_Suspension_Object
16681 and then Present
(Scope
(Id
))
16682 and then Chars
(Scope
(Id
)) = Name_Synchronous_Task_Control
16683 and then Present
(Scope
(Scope
(Id
)))
16684 and then Chars
(Scope
(Scope
(Id
))) = Name_Ada
16685 and then Present
(Scope
(Scope
(Scope
(Id
))))
16686 and then Scope
(Scope
(Scope
(Id
))) = Standard_Standard
;
16687 end Is_Suspension_Object
;
16689 ----------------------------
16690 -- Is_Synchronized_Object --
16691 ----------------------------
16693 function Is_Synchronized_Object
(Id
: Entity_Id
) return Boolean is
16697 if Is_Object
(Id
) then
16699 -- The object is synchronized if it is of a type that yields a
16700 -- synchronized object.
16702 if Yields_Synchronized_Object
(Etype
(Id
)) then
16705 -- The object is synchronized if it is atomic and Async_Writers is
16708 elsif Is_Atomic
(Id
) and then Async_Writers_Enabled
(Id
) then
16711 -- A constant is a synchronized object by default
16713 elsif Ekind
(Id
) = E_Constant
then
16716 -- A variable is a synchronized object if it is subject to pragma
16717 -- Constant_After_Elaboration.
16719 elsif Ekind
(Id
) = E_Variable
then
16720 Prag
:= Get_Pragma
(Id
, Pragma_Constant_After_Elaboration
);
16722 return Present
(Prag
) and then Is_Enabled_Pragma
(Prag
);
16726 -- Otherwise the input is not an object or it does not qualify as a
16727 -- synchronized object.
16730 end Is_Synchronized_Object
;
16732 ---------------------------------
16733 -- Is_Synchronized_Tagged_Type --
16734 ---------------------------------
16736 function Is_Synchronized_Tagged_Type
(E
: Entity_Id
) return Boolean is
16737 Kind
: constant Entity_Kind
:= Ekind
(Base_Type
(E
));
16740 -- A task or protected type derived from an interface is a tagged type.
16741 -- Such a tagged type is called a synchronized tagged type, as are
16742 -- synchronized interfaces and private extensions whose declaration
16743 -- includes the reserved word synchronized.
16745 return (Is_Tagged_Type
(E
)
16746 and then (Kind
= E_Task_Type
16748 Kind
= E_Protected_Type
))
16751 and then Is_Synchronized_Interface
(E
))
16753 (Ekind
(E
) = E_Record_Type_With_Private
16754 and then Nkind
(Parent
(E
)) = N_Private_Extension_Declaration
16755 and then (Synchronized_Present
(Parent
(E
))
16756 or else Is_Synchronized_Interface
(Etype
(E
))));
16757 end Is_Synchronized_Tagged_Type
;
16763 function Is_Transfer
(N
: Node_Id
) return Boolean is
16764 Kind
: constant Node_Kind
:= Nkind
(N
);
16767 if Kind
= N_Simple_Return_Statement
16769 Kind
= N_Extended_Return_Statement
16771 Kind
= N_Goto_Statement
16773 Kind
= N_Raise_Statement
16775 Kind
= N_Requeue_Statement
16779 elsif (Kind
= N_Exit_Statement
or else Kind
in N_Raise_xxx_Error
)
16780 and then No
(Condition
(N
))
16784 elsif Kind
= N_Procedure_Call_Statement
16785 and then Is_Entity_Name
(Name
(N
))
16786 and then Present
(Entity
(Name
(N
)))
16787 and then No_Return
(Entity
(Name
(N
)))
16791 elsif Nkind
(Original_Node
(N
)) = N_Raise_Statement
then
16803 function Is_True
(U
: Uint
) return Boolean is
16808 --------------------------------------
16809 -- Is_Unchecked_Conversion_Instance --
16810 --------------------------------------
16812 function Is_Unchecked_Conversion_Instance
(Id
: Entity_Id
) return Boolean is
16816 -- Look for a function whose generic parent is the predefined intrinsic
16817 -- function Unchecked_Conversion, or for one that renames such an
16820 if Ekind
(Id
) = E_Function
then
16821 Par
:= Parent
(Id
);
16823 if Nkind
(Par
) = N_Function_Specification
then
16824 Par
:= Generic_Parent
(Par
);
16826 if Present
(Par
) then
16828 Chars
(Par
) = Name_Unchecked_Conversion
16829 and then Is_Intrinsic_Subprogram
(Par
)
16830 and then In_Predefined_Unit
(Par
);
16833 Present
(Alias
(Id
))
16834 and then Is_Unchecked_Conversion_Instance
(Alias
(Id
));
16840 end Is_Unchecked_Conversion_Instance
;
16842 -------------------------------
16843 -- Is_Universal_Numeric_Type --
16844 -------------------------------
16846 function Is_Universal_Numeric_Type
(T
: Entity_Id
) return Boolean is
16848 return T
= Universal_Integer
or else T
= Universal_Real
;
16849 end Is_Universal_Numeric_Type
;
16851 ------------------------------
16852 -- Is_User_Defined_Equality --
16853 ------------------------------
16855 function Is_User_Defined_Equality
(Id
: Entity_Id
) return Boolean is
16857 return Ekind
(Id
) = E_Function
16858 and then Chars
(Id
) = Name_Op_Eq
16859 and then Comes_From_Source
(Id
)
16861 -- Internally generated equalities have a full type declaration
16862 -- as their parent.
16864 and then Nkind
(Parent
(Id
)) = N_Function_Specification
;
16865 end Is_User_Defined_Equality
;
16867 --------------------------------------
16868 -- Is_Validation_Variable_Reference --
16869 --------------------------------------
16871 function Is_Validation_Variable_Reference
(N
: Node_Id
) return Boolean is
16872 Var
: constant Node_Id
:= Unqual_Conv
(N
);
16873 Var_Id
: Entity_Id
;
16878 if Is_Entity_Name
(Var
) then
16879 Var_Id
:= Entity
(Var
);
16884 and then Ekind
(Var_Id
) = E_Variable
16885 and then Present
(Validated_Object
(Var_Id
));
16886 end Is_Validation_Variable_Reference
;
16888 ----------------------------
16889 -- Is_Variable_Size_Array --
16890 ----------------------------
16892 function Is_Variable_Size_Array
(E
: Entity_Id
) return Boolean is
16896 pragma Assert
(Is_Array_Type
(E
));
16898 -- Check if some index is initialized with a non-constant value
16900 Idx
:= First_Index
(E
);
16901 while Present
(Idx
) loop
16902 if Nkind
(Idx
) = N_Range
then
16903 if not Is_Constant_Bound
(Low_Bound
(Idx
))
16904 or else not Is_Constant_Bound
(High_Bound
(Idx
))
16910 Idx
:= Next_Index
(Idx
);
16914 end Is_Variable_Size_Array
;
16916 -----------------------------
16917 -- Is_Variable_Size_Record --
16918 -----------------------------
16920 function Is_Variable_Size_Record
(E
: Entity_Id
) return Boolean is
16922 Comp_Typ
: Entity_Id
;
16925 pragma Assert
(Is_Record_Type
(E
));
16927 Comp
:= First_Entity
(E
);
16928 while Present
(Comp
) loop
16929 Comp_Typ
:= Etype
(Comp
);
16931 -- Recursive call if the record type has discriminants
16933 if Is_Record_Type
(Comp_Typ
)
16934 and then Has_Discriminants
(Comp_Typ
)
16935 and then Is_Variable_Size_Record
(Comp_Typ
)
16939 elsif Is_Array_Type
(Comp_Typ
)
16940 and then Is_Variable_Size_Array
(Comp_Typ
)
16945 Next_Entity
(Comp
);
16949 end Is_Variable_Size_Record
;
16955 function Is_Variable
16957 Use_Original_Node
: Boolean := True) return Boolean
16959 Orig_Node
: Node_Id
;
16961 function In_Protected_Function
(E
: Entity_Id
) return Boolean;
16962 -- Within a protected function, the private components of the enclosing
16963 -- protected type are constants. A function nested within a (protected)
16964 -- procedure is not itself protected. Within the body of a protected
16965 -- function the current instance of the protected type is a constant.
16967 function Is_Variable_Prefix
(P
: Node_Id
) return Boolean;
16968 -- Prefixes can involve implicit dereferences, in which case we must
16969 -- test for the case of a reference of a constant access type, which can
16970 -- can never be a variable.
16972 ---------------------------
16973 -- In_Protected_Function --
16974 ---------------------------
16976 function In_Protected_Function
(E
: Entity_Id
) return Boolean is
16981 -- E is the current instance of a type
16983 if Is_Type
(E
) then
16992 if not Is_Protected_Type
(Prot
) then
16996 S
:= Current_Scope
;
16997 while Present
(S
) and then S
/= Prot
loop
16998 if Ekind
(S
) = E_Function
and then Scope
(S
) = Prot
then
17007 end In_Protected_Function
;
17009 ------------------------
17010 -- Is_Variable_Prefix --
17011 ------------------------
17013 function Is_Variable_Prefix
(P
: Node_Id
) return Boolean is
17015 if Is_Access_Type
(Etype
(P
)) then
17016 return not Is_Access_Constant
(Root_Type
(Etype
(P
)));
17018 -- For the case of an indexed component whose prefix has a packed
17019 -- array type, the prefix has been rewritten into a type conversion.
17020 -- Determine variable-ness from the converted expression.
17022 elsif Nkind
(P
) = N_Type_Conversion
17023 and then not Comes_From_Source
(P
)
17024 and then Is_Array_Type
(Etype
(P
))
17025 and then Is_Packed
(Etype
(P
))
17027 return Is_Variable
(Expression
(P
));
17030 return Is_Variable
(P
);
17032 end Is_Variable_Prefix
;
17034 -- Start of processing for Is_Variable
17037 -- Special check, allow x'Deref(expr) as a variable
17039 if Nkind
(N
) = N_Attribute_Reference
17040 and then Attribute_Name
(N
) = Name_Deref
17045 -- Check if we perform the test on the original node since this may be a
17046 -- test of syntactic categories which must not be disturbed by whatever
17047 -- rewriting might have occurred. For example, an aggregate, which is
17048 -- certainly NOT a variable, could be turned into a variable by
17051 if Use_Original_Node
then
17052 Orig_Node
:= Original_Node
(N
);
17057 -- Definitely OK if Assignment_OK is set. Since this is something that
17058 -- only gets set for expanded nodes, the test is on N, not Orig_Node.
17060 if Nkind
(N
) in N_Subexpr
and then Assignment_OK
(N
) then
17063 -- Normally we go to the original node, but there is one exception where
17064 -- we use the rewritten node, namely when it is an explicit dereference.
17065 -- The generated code may rewrite a prefix which is an access type with
17066 -- an explicit dereference. The dereference is a variable, even though
17067 -- the original node may not be (since it could be a constant of the
17070 -- In Ada 2005 we have a further case to consider: the prefix may be a
17071 -- function call given in prefix notation. The original node appears to
17072 -- be a selected component, but we need to examine the call.
17074 elsif Nkind
(N
) = N_Explicit_Dereference
17075 and then Nkind
(Orig_Node
) /= N_Explicit_Dereference
17076 and then Present
(Etype
(Orig_Node
))
17077 and then Is_Access_Type
(Etype
(Orig_Node
))
17079 -- Note that if the prefix is an explicit dereference that does not
17080 -- come from source, we must check for a rewritten function call in
17081 -- prefixed notation before other forms of rewriting, to prevent a
17085 (Nkind
(Orig_Node
) = N_Function_Call
17086 and then not Is_Access_Constant
(Etype
(Prefix
(N
))))
17088 Is_Variable_Prefix
(Original_Node
(Prefix
(N
)));
17090 -- in Ada 2012, the dereference may have been added for a type with
17091 -- a declared implicit dereference aspect. Check that it is not an
17092 -- access to constant.
17094 elsif Nkind
(N
) = N_Explicit_Dereference
17095 and then Present
(Etype
(Orig_Node
))
17096 and then Ada_Version
>= Ada_2012
17097 and then Has_Implicit_Dereference
(Etype
(Orig_Node
))
17099 return not Is_Access_Constant
(Etype
(Prefix
(N
)));
17101 -- A function call is never a variable
17103 elsif Nkind
(N
) = N_Function_Call
then
17106 -- All remaining checks use the original node
17108 elsif Is_Entity_Name
(Orig_Node
)
17109 and then Present
(Entity
(Orig_Node
))
17112 E
: constant Entity_Id
:= Entity
(Orig_Node
);
17113 K
: constant Entity_Kind
:= Ekind
(E
);
17116 return (K
= E_Variable
17117 and then Nkind
(Parent
(E
)) /= N_Exception_Handler
)
17118 or else (K
= E_Component
17119 and then not In_Protected_Function
(E
))
17120 or else K
= E_Out_Parameter
17121 or else K
= E_In_Out_Parameter
17122 or else K
= E_Generic_In_Out_Parameter
17124 -- Current instance of type. If this is a protected type, check
17125 -- we are not within the body of one of its protected functions.
17127 or else (Is_Type
(E
)
17128 and then In_Open_Scopes
(E
)
17129 and then not In_Protected_Function
(E
))
17131 or else (Is_Incomplete_Or_Private_Type
(E
)
17132 and then In_Open_Scopes
(Full_View
(E
)));
17136 case Nkind
(Orig_Node
) is
17137 when N_Indexed_Component
17140 return Is_Variable_Prefix
(Prefix
(Orig_Node
));
17142 when N_Selected_Component
=>
17143 return (Is_Variable
(Selector_Name
(Orig_Node
))
17144 and then Is_Variable_Prefix
(Prefix
(Orig_Node
)))
17146 (Nkind
(N
) = N_Expanded_Name
17147 and then Scope
(Entity
(N
)) = Entity
(Prefix
(N
)));
17149 -- For an explicit dereference, the type of the prefix cannot
17150 -- be an access to constant or an access to subprogram.
17152 when N_Explicit_Dereference
=>
17154 Typ
: constant Entity_Id
:= Etype
(Prefix
(Orig_Node
));
17156 return Is_Access_Type
(Typ
)
17157 and then not Is_Access_Constant
(Root_Type
(Typ
))
17158 and then Ekind
(Typ
) /= E_Access_Subprogram_Type
;
17161 -- The type conversion is the case where we do not deal with the
17162 -- context dependent special case of an actual parameter. Thus
17163 -- the type conversion is only considered a variable for the
17164 -- purposes of this routine if the target type is tagged. However,
17165 -- a type conversion is considered to be a variable if it does not
17166 -- come from source (this deals for example with the conversions
17167 -- of expressions to their actual subtypes).
17169 when N_Type_Conversion
=>
17170 return Is_Variable
(Expression
(Orig_Node
))
17172 (not Comes_From_Source
(Orig_Node
)
17174 (Is_Tagged_Type
(Etype
(Subtype_Mark
(Orig_Node
)))
17176 Is_Tagged_Type
(Etype
(Expression
(Orig_Node
)))));
17178 -- GNAT allows an unchecked type conversion as a variable. This
17179 -- only affects the generation of internal expanded code, since
17180 -- calls to instantiations of Unchecked_Conversion are never
17181 -- considered variables (since they are function calls).
17183 when N_Unchecked_Type_Conversion
=>
17184 return Is_Variable
(Expression
(Orig_Node
));
17192 ------------------------------
17193 -- Is_Verifiable_DIC_Pragma --
17194 ------------------------------
17196 function Is_Verifiable_DIC_Pragma
(Prag
: Node_Id
) return Boolean is
17197 Args
: constant List_Id
:= Pragma_Argument_Associations
(Prag
);
17200 -- To qualify as verifiable, a DIC pragma must have a non-null argument
17204 and then Nkind
(Get_Pragma_Arg
(First
(Args
))) /= N_Null
;
17205 end Is_Verifiable_DIC_Pragma
;
17207 ---------------------------
17208 -- Is_Visibly_Controlled --
17209 ---------------------------
17211 function Is_Visibly_Controlled
(T
: Entity_Id
) return Boolean is
17212 Root
: constant Entity_Id
:= Root_Type
(T
);
17214 return Chars
(Scope
(Root
)) = Name_Finalization
17215 and then Chars
(Scope
(Scope
(Root
))) = Name_Ada
17216 and then Scope
(Scope
(Scope
(Root
))) = Standard_Standard
;
17217 end Is_Visibly_Controlled
;
17219 --------------------------
17220 -- Is_Volatile_Function --
17221 --------------------------
17223 function Is_Volatile_Function
(Func_Id
: Entity_Id
) return Boolean is
17225 pragma Assert
(Ekind_In
(Func_Id
, E_Function
, E_Generic_Function
));
17227 -- A function declared within a protected type is volatile
17229 if Is_Protected_Type
(Scope
(Func_Id
)) then
17232 -- An instance of Ada.Unchecked_Conversion is a volatile function if
17233 -- either the source or the target are effectively volatile.
17235 elsif Is_Unchecked_Conversion_Instance
(Func_Id
)
17236 and then Has_Effectively_Volatile_Profile
(Func_Id
)
17240 -- Otherwise the function is treated as volatile if it is subject to
17241 -- enabled pragma Volatile_Function.
17245 Is_Enabled_Pragma
(Get_Pragma
(Func_Id
, Pragma_Volatile_Function
));
17247 end Is_Volatile_Function
;
17249 ------------------------
17250 -- Is_Volatile_Object --
17251 ------------------------
17253 function Is_Volatile_Object
(N
: Node_Id
) return Boolean is
17254 function Is_Volatile_Prefix
(N
: Node_Id
) return Boolean;
17255 -- If prefix is an implicit dereference, examine designated type
17257 function Object_Has_Volatile_Components
(N
: Node_Id
) return Boolean;
17258 -- Determines if given object has volatile components
17260 ------------------------
17261 -- Is_Volatile_Prefix --
17262 ------------------------
17264 function Is_Volatile_Prefix
(N
: Node_Id
) return Boolean is
17265 Typ
: constant Entity_Id
:= Etype
(N
);
17268 if Is_Access_Type
(Typ
) then
17270 Dtyp
: constant Entity_Id
:= Designated_Type
(Typ
);
17273 return Is_Volatile
(Dtyp
)
17274 or else Has_Volatile_Components
(Dtyp
);
17278 return Object_Has_Volatile_Components
(N
);
17280 end Is_Volatile_Prefix
;
17282 ------------------------------------
17283 -- Object_Has_Volatile_Components --
17284 ------------------------------------
17286 function Object_Has_Volatile_Components
(N
: Node_Id
) return Boolean is
17287 Typ
: constant Entity_Id
:= Etype
(N
);
17290 if Is_Volatile
(Typ
)
17291 or else Has_Volatile_Components
(Typ
)
17295 elsif Is_Entity_Name
(N
)
17296 and then (Has_Volatile_Components
(Entity
(N
))
17297 or else Is_Volatile
(Entity
(N
)))
17301 elsif Nkind
(N
) = N_Indexed_Component
17302 or else Nkind
(N
) = N_Selected_Component
17304 return Is_Volatile_Prefix
(Prefix
(N
));
17309 end Object_Has_Volatile_Components
;
17311 -- Start of processing for Is_Volatile_Object
17314 if Nkind
(N
) = N_Defining_Identifier
then
17315 return Is_Volatile
(N
) or else Is_Volatile
(Etype
(N
));
17317 elsif Nkind
(N
) = N_Expanded_Name
then
17318 return Is_Volatile_Object
(Entity
(N
));
17320 elsif Is_Volatile
(Etype
(N
))
17321 or else (Is_Entity_Name
(N
) and then Is_Volatile
(Entity
(N
)))
17325 elsif Nkind_In
(N
, N_Indexed_Component
, N_Selected_Component
)
17326 and then Is_Volatile_Prefix
(Prefix
(N
))
17330 elsif Nkind
(N
) = N_Selected_Component
17331 and then Is_Volatile
(Entity
(Selector_Name
(N
)))
17338 end Is_Volatile_Object
;
17340 -----------------------------
17341 -- Iterate_Call_Parameters --
17342 -----------------------------
17344 procedure Iterate_Call_Parameters
(Call
: Node_Id
) is
17345 Formal
: Entity_Id
:= First_Formal
(Get_Called_Entity
(Call
));
17346 Actual
: Node_Id
:= First_Actual
(Call
);
17349 while Present
(Formal
) and then Present
(Actual
) loop
17350 Handle_Parameter
(Formal
, Actual
);
17351 Formal
:= Next_Formal
(Formal
);
17352 Actual
:= Next_Actual
(Actual
);
17354 end Iterate_Call_Parameters
;
17356 ---------------------------
17357 -- Itype_Has_Declaration --
17358 ---------------------------
17360 function Itype_Has_Declaration
(Id
: Entity_Id
) return Boolean is
17362 pragma Assert
(Is_Itype
(Id
));
17363 return Present
(Parent
(Id
))
17364 and then Nkind_In
(Parent
(Id
), N_Full_Type_Declaration
,
17365 N_Subtype_Declaration
)
17366 and then Defining_Entity
(Parent
(Id
)) = Id
;
17367 end Itype_Has_Declaration
;
17369 -------------------------
17370 -- Kill_Current_Values --
17371 -------------------------
17373 procedure Kill_Current_Values
17375 Last_Assignment_Only
: Boolean := False)
17378 if Is_Assignable
(Ent
) then
17379 Set_Last_Assignment
(Ent
, Empty
);
17382 if Is_Object
(Ent
) then
17383 if not Last_Assignment_Only
then
17385 Set_Current_Value
(Ent
, Empty
);
17387 -- Do not reset the Is_Known_[Non_]Null and Is_Known_Valid flags
17388 -- for a constant. Once the constant is elaborated, its value is
17389 -- not changed, therefore the associated flags that describe the
17390 -- value should not be modified either.
17392 if Ekind
(Ent
) = E_Constant
then
17395 -- Non-constant entities
17398 if not Can_Never_Be_Null
(Ent
) then
17399 Set_Is_Known_Non_Null
(Ent
, False);
17402 Set_Is_Known_Null
(Ent
, False);
17404 -- Reset the Is_Known_Valid flag unless the type is always
17405 -- valid. This does not apply to a loop parameter because its
17406 -- bounds are defined by the loop header and therefore always
17409 if not Is_Known_Valid
(Etype
(Ent
))
17410 and then Ekind
(Ent
) /= E_Loop_Parameter
17412 Set_Is_Known_Valid
(Ent
, False);
17417 end Kill_Current_Values
;
17419 procedure Kill_Current_Values
(Last_Assignment_Only
: Boolean := False) is
17422 procedure Kill_Current_Values_For_Entity_Chain
(E
: Entity_Id
);
17423 -- Clear current value for entity E and all entities chained to E
17425 ------------------------------------------
17426 -- Kill_Current_Values_For_Entity_Chain --
17427 ------------------------------------------
17429 procedure Kill_Current_Values_For_Entity_Chain
(E
: Entity_Id
) is
17433 while Present
(Ent
) loop
17434 Kill_Current_Values
(Ent
, Last_Assignment_Only
);
17437 end Kill_Current_Values_For_Entity_Chain
;
17439 -- Start of processing for Kill_Current_Values
17442 -- Kill all saved checks, a special case of killing saved values
17444 if not Last_Assignment_Only
then
17448 -- Loop through relevant scopes, which includes the current scope and
17449 -- any parent scopes if the current scope is a block or a package.
17451 S
:= Current_Scope
;
17454 -- Clear current values of all entities in current scope
17456 Kill_Current_Values_For_Entity_Chain
(First_Entity
(S
));
17458 -- If scope is a package, also clear current values of all private
17459 -- entities in the scope.
17461 if Is_Package_Or_Generic_Package
(S
)
17462 or else Is_Concurrent_Type
(S
)
17464 Kill_Current_Values_For_Entity_Chain
(First_Private_Entity
(S
));
17467 -- If this is a not a subprogram, deal with parents
17469 if not Is_Subprogram
(S
) then
17471 exit Scope_Loop
when S
= Standard_Standard
;
17475 end loop Scope_Loop
;
17476 end Kill_Current_Values
;
17478 --------------------------
17479 -- Kill_Size_Check_Code --
17480 --------------------------
17482 procedure Kill_Size_Check_Code
(E
: Entity_Id
) is
17484 if (Ekind
(E
) = E_Constant
or else Ekind
(E
) = E_Variable
)
17485 and then Present
(Size_Check_Code
(E
))
17487 Remove
(Size_Check_Code
(E
));
17488 Set_Size_Check_Code
(E
, Empty
);
17490 end Kill_Size_Check_Code
;
17492 --------------------
17493 -- Known_Non_Null --
17494 --------------------
17496 function Known_Non_Null
(N
: Node_Id
) return Boolean is
17497 Status
: constant Null_Status_Kind
:= Null_Status
(N
);
17504 -- The expression yields a non-null value ignoring simple flow analysis
17506 if Status
= Is_Non_Null
then
17509 -- Otherwise check whether N is a reference to an entity that appears
17510 -- within a conditional construct.
17512 elsif Is_Entity_Name
(N
) and then Present
(Entity
(N
)) then
17514 -- First check if we are in decisive conditional
17516 Get_Current_Value_Condition
(N
, Op
, Val
);
17518 if Known_Null
(Val
) then
17519 if Op
= N_Op_Eq
then
17521 elsif Op
= N_Op_Ne
then
17526 -- If OK to do replacement, test Is_Known_Non_Null flag
17530 if OK_To_Do_Constant_Replacement
(Id
) then
17531 return Is_Known_Non_Null
(Id
);
17535 -- Otherwise it is not possible to determine whether N yields a non-null
17539 end Known_Non_Null
;
17545 function Known_Null
(N
: Node_Id
) return Boolean is
17546 Status
: constant Null_Status_Kind
:= Null_Status
(N
);
17553 -- The expression yields a null value ignoring simple flow analysis
17555 if Status
= Is_Null
then
17558 -- Otherwise check whether N is a reference to an entity that appears
17559 -- within a conditional construct.
17561 elsif Is_Entity_Name
(N
) and then Present
(Entity
(N
)) then
17563 -- First check if we are in decisive conditional
17565 Get_Current_Value_Condition
(N
, Op
, Val
);
17567 if Known_Null
(Val
) then
17568 if Op
= N_Op_Eq
then
17570 elsif Op
= N_Op_Ne
then
17575 -- If OK to do replacement, test Is_Known_Null flag
17579 if OK_To_Do_Constant_Replacement
(Id
) then
17580 return Is_Known_Null
(Id
);
17584 -- Otherwise it is not possible to determine whether N yields a null
17590 --------------------------
17591 -- Known_To_Be_Assigned --
17592 --------------------------
17594 function Known_To_Be_Assigned
(N
: Node_Id
) return Boolean is
17595 P
: constant Node_Id
:= Parent
(N
);
17600 -- Test left side of assignment
17602 when N_Assignment_Statement
=>
17603 return N
= Name
(P
);
17605 -- Function call arguments are never lvalues
17607 when N_Function_Call
=>
17610 -- Positional parameter for procedure or accept call
17612 when N_Accept_Statement
17613 | N_Procedure_Call_Statement
17621 Proc
:= Get_Subprogram_Entity
(P
);
17627 -- If we are not a list member, something is strange, so
17628 -- be conservative and return False.
17630 if not Is_List_Member
(N
) then
17634 -- We are going to find the right formal by stepping forward
17635 -- through the formals, as we step backwards in the actuals.
17637 Form
:= First_Formal
(Proc
);
17640 -- If no formal, something is weird, so be conservative
17641 -- and return False.
17648 exit when No
(Act
);
17649 Next_Formal
(Form
);
17652 return Ekind
(Form
) /= E_In_Parameter
;
17655 -- Named parameter for procedure or accept call
17657 when N_Parameter_Association
=>
17663 Proc
:= Get_Subprogram_Entity
(Parent
(P
));
17669 -- Loop through formals to find the one that matches
17671 Form
:= First_Formal
(Proc
);
17673 -- If no matching formal, that's peculiar, some kind of
17674 -- previous error, so return False to be conservative.
17675 -- Actually this also happens in legal code in the case
17676 -- where P is a parameter association for an Extra_Formal???
17682 -- Else test for match
17684 if Chars
(Form
) = Chars
(Selector_Name
(P
)) then
17685 return Ekind
(Form
) /= E_In_Parameter
;
17688 Next_Formal
(Form
);
17692 -- Test for appearing in a conversion that itself appears
17693 -- in an lvalue context, since this should be an lvalue.
17695 when N_Type_Conversion
=>
17696 return Known_To_Be_Assigned
(P
);
17698 -- All other references are definitely not known to be modifications
17703 end Known_To_Be_Assigned
;
17705 ---------------------------
17706 -- Last_Source_Statement --
17707 ---------------------------
17709 function Last_Source_Statement
(HSS
: Node_Id
) return Node_Id
is
17713 N
:= Last
(Statements
(HSS
));
17714 while Present
(N
) loop
17715 exit when Comes_From_Source
(N
);
17720 end Last_Source_Statement
;
17722 -----------------------
17723 -- Mark_Coextensions --
17724 -----------------------
17726 procedure Mark_Coextensions
(Context_Nod
: Node_Id
; Root_Nod
: Node_Id
) is
17727 Is_Dynamic
: Boolean;
17728 -- Indicates whether the context causes nested coextensions to be
17729 -- dynamic or static
17731 function Mark_Allocator
(N
: Node_Id
) return Traverse_Result
;
17732 -- Recognize an allocator node and label it as a dynamic coextension
17734 --------------------
17735 -- Mark_Allocator --
17736 --------------------
17738 function Mark_Allocator
(N
: Node_Id
) return Traverse_Result
is
17740 if Nkind
(N
) = N_Allocator
then
17742 Set_Is_Dynamic_Coextension
(N
);
17744 -- If the allocator expression is potentially dynamic, it may
17745 -- be expanded out of order and require dynamic allocation
17746 -- anyway, so we treat the coextension itself as dynamic.
17747 -- Potential optimization ???
17749 elsif Nkind
(Expression
(N
)) = N_Qualified_Expression
17750 and then Nkind
(Expression
(Expression
(N
))) = N_Op_Concat
17752 Set_Is_Dynamic_Coextension
(N
);
17754 Set_Is_Static_Coextension
(N
);
17759 end Mark_Allocator
;
17761 procedure Mark_Allocators
is new Traverse_Proc
(Mark_Allocator
);
17763 -- Start of processing for Mark_Coextensions
17766 -- An allocator that appears on the right-hand side of an assignment is
17767 -- treated as a potentially dynamic coextension when the right-hand side
17768 -- is an allocator or a qualified expression.
17770 -- Obj := new ...'(new Coextension ...);
17772 if Nkind
(Context_Nod
) = N_Assignment_Statement
then
17774 Nkind_In
(Expression
(Context_Nod
), N_Allocator
,
17775 N_Qualified_Expression
);
17777 -- An allocator that appears within the expression of a simple return
17778 -- statement is treated as a potentially dynamic coextension when the
17779 -- expression is either aggregate, allocator, or qualified expression.
17781 -- return (new Coextension ...);
17782 -- return new ...'(new Coextension ...);
17784 elsif Nkind
(Context_Nod
) = N_Simple_Return_Statement
then
17786 Nkind_In
(Expression
(Context_Nod
), N_Aggregate
,
17788 N_Qualified_Expression
);
17790 -- An alloctor that appears within the initialization expression of an
17791 -- object declaration is considered a potentially dynamic coextension
17792 -- when the initialization expression is an allocator or a qualified
17795 -- Obj : ... := new ...'(new Coextension ...);
17797 -- A similar case arises when the object declaration is part of an
17798 -- extended return statement.
17800 -- return Obj : ... := new ...'(new Coextension ...);
17801 -- return Obj : ... := (new Coextension ...);
17803 elsif Nkind
(Context_Nod
) = N_Object_Declaration
then
17805 Nkind_In
(Root_Nod
, N_Allocator
, N_Qualified_Expression
)
17807 Nkind
(Parent
(Context_Nod
)) = N_Extended_Return_Statement
;
17809 -- This routine should not be called with constructs that cannot contain
17813 raise Program_Error
;
17816 Mark_Allocators
(Root_Nod
);
17817 end Mark_Coextensions
;
17819 ---------------------------------
17820 -- Mark_Elaboration_Attributes --
17821 ---------------------------------
17823 procedure Mark_Elaboration_Attributes
17824 (N_Id
: Node_Or_Entity_Id
;
17825 Checks
: Boolean := False;
17826 Level
: Boolean := False;
17827 Modes
: Boolean := False)
17829 function Elaboration_Checks_OK
17830 (Target_Id
: Entity_Id
;
17831 Context_Id
: Entity_Id
) return Boolean;
17832 -- Determine whether elaboration checks are enabled for target Target_Id
17833 -- which resides within context Context_Id.
17835 procedure Mark_Elaboration_Attributes_Id
(Id
: Entity_Id
);
17836 -- Preserve relevant attributes of the context in arbitrary entity Id
17838 procedure Mark_Elaboration_Attributes_Node
(N
: Node_Id
);
17839 -- Preserve relevant attributes of the context in arbitrary node N
17841 ---------------------------
17842 -- Elaboration_Checks_OK --
17843 ---------------------------
17845 function Elaboration_Checks_OK
17846 (Target_Id
: Entity_Id
;
17847 Context_Id
: Entity_Id
) return Boolean
17849 Encl_Scop
: Entity_Id
;
17852 -- Elaboration checks are suppressed for the target
17854 if Elaboration_Checks_Suppressed
(Target_Id
) then
17858 -- Otherwise elaboration checks are OK for the target, but may be
17859 -- suppressed for the context where the target is declared.
17861 Encl_Scop
:= Context_Id
;
17862 while Present
(Encl_Scop
) and then Encl_Scop
/= Standard_Standard
loop
17863 if Elaboration_Checks_Suppressed
(Encl_Scop
) then
17867 Encl_Scop
:= Scope
(Encl_Scop
);
17870 -- Neither the target nor its declarative context have elaboration
17871 -- checks suppressed.
17874 end Elaboration_Checks_OK
;
17876 ------------------------------------
17877 -- Mark_Elaboration_Attributes_Id --
17878 ------------------------------------
17880 procedure Mark_Elaboration_Attributes_Id
(Id
: Entity_Id
) is
17882 -- Mark the status of elaboration checks in effect. Do not reset the
17883 -- status in case the entity is reanalyzed with checks suppressed.
17885 if Checks
and then not Is_Elaboration_Checks_OK_Id
(Id
) then
17886 Set_Is_Elaboration_Checks_OK_Id
(Id
,
17887 Elaboration_Checks_OK
17889 Context_Id
=> Scope
(Id
)));
17891 -- Entities do not need to capture their enclosing level. The Ghost
17892 -- and SPARK modes in effect are already marked during analysis.
17897 end Mark_Elaboration_Attributes_Id
;
17899 --------------------------------------
17900 -- Mark_Elaboration_Attributes_Node --
17901 --------------------------------------
17903 procedure Mark_Elaboration_Attributes_Node
(N
: Node_Id
) is
17904 function Extract_Name
(N
: Node_Id
) return Node_Id
;
17905 -- Obtain the Name attribute of call or instantiation N
17911 function Extract_Name
(N
: Node_Id
) return Node_Id
is
17917 -- A call to an entry family appears in indexed form
17919 if Nkind
(Nam
) = N_Indexed_Component
then
17920 Nam
:= Prefix
(Nam
);
17923 -- The name may also appear in qualified form
17925 if Nkind
(Nam
) = N_Selected_Component
then
17926 Nam
:= Selector_Name
(Nam
);
17934 Context_Id
: Entity_Id
;
17937 -- Start of processing for Mark_Elaboration_Attributes_Node
17940 -- Mark the status of elaboration checks in effect. Do not reset the
17941 -- status in case the node is reanalyzed with checks suppressed.
17943 if Checks
and then not Is_Elaboration_Checks_OK_Node
(N
) then
17945 -- Assignments, attribute references, and variable references do
17946 -- not have a "declarative" context.
17948 Context_Id
:= Empty
;
17950 -- The status of elaboration checks for calls and instantiations
17951 -- depends on the most recent pragma Suppress/Unsuppress, as well
17952 -- as the suppression status of the context where the target is
17956 -- function Func ...;
17960 -- procedure Main is
17961 -- pragma Suppress (Elaboration_Checks, Pack);
17962 -- X : ... := Pack.Func;
17965 -- In the example above, the call to Func has elaboration checks
17966 -- enabled because there is no active general purpose suppression
17967 -- pragma, however the elaboration checks of Pack are explicitly
17968 -- suppressed. As a result the elaboration checks of the call must
17969 -- be disabled in order to preserve this dependency.
17971 if Nkind_In
(N
, N_Entry_Call_Statement
,
17973 N_Function_Instantiation
,
17974 N_Package_Instantiation
,
17975 N_Procedure_Call_Statement
,
17976 N_Procedure_Instantiation
)
17978 Nam
:= Extract_Name
(N
);
17980 if Is_Entity_Name
(Nam
) and then Present
(Entity
(Nam
)) then
17981 Context_Id
:= Scope
(Entity
(Nam
));
17985 Set_Is_Elaboration_Checks_OK_Node
(N
,
17986 Elaboration_Checks_OK
17987 (Target_Id
=> Empty
,
17988 Context_Id
=> Context_Id
));
17991 -- Mark the enclosing level of the node. Do not reset the status in
17992 -- case the node is relocated and reanalyzed.
17994 if Level
and then not Is_Declaration_Level_Node
(N
) then
17995 Set_Is_Declaration_Level_Node
(N
,
17996 Find_Enclosing_Level
(N
) = Declaration_Level
);
17999 -- Mark the Ghost and SPARK mode in effect
18002 if Ghost_Mode
= Ignore
then
18003 Set_Is_Ignored_Ghost_Node
(N
);
18006 if SPARK_Mode
= On
then
18007 Set_Is_SPARK_Mode_On_Node
(N
);
18010 end Mark_Elaboration_Attributes_Node
;
18012 -- Start of processing for Mark_Elaboration_Attributes
18015 if Nkind
(N_Id
) in N_Entity
then
18016 Mark_Elaboration_Attributes_Id
(N_Id
);
18018 Mark_Elaboration_Attributes_Node
(N_Id
);
18020 end Mark_Elaboration_Attributes
;
18022 ----------------------------------
18023 -- Matching_Static_Array_Bounds --
18024 ----------------------------------
18026 function Matching_Static_Array_Bounds
18028 R_Typ
: Node_Id
) return Boolean
18030 L_Ndims
: constant Nat
:= Number_Dimensions
(L_Typ
);
18031 R_Ndims
: constant Nat
:= Number_Dimensions
(R_Typ
);
18033 L_Index
: Node_Id
:= Empty
; -- init to ...
18034 R_Index
: Node_Id
:= Empty
; -- ...avoid warnings
18043 if L_Ndims
/= R_Ndims
then
18047 -- Unconstrained types do not have static bounds
18049 if not Is_Constrained
(L_Typ
) or else not Is_Constrained
(R_Typ
) then
18053 -- First treat specially the first dimension, as the lower bound and
18054 -- length of string literals are not stored like those of arrays.
18056 if Ekind
(L_Typ
) = E_String_Literal_Subtype
then
18057 L_Low
:= String_Literal_Low_Bound
(L_Typ
);
18058 L_Len
:= String_Literal_Length
(L_Typ
);
18060 L_Index
:= First_Index
(L_Typ
);
18061 Get_Index_Bounds
(L_Index
, L_Low
, L_High
);
18063 if Is_OK_Static_Expression
(L_Low
)
18065 Is_OK_Static_Expression
(L_High
)
18067 if Expr_Value
(L_High
) < Expr_Value
(L_Low
) then
18070 L_Len
:= (Expr_Value
(L_High
) - Expr_Value
(L_Low
)) + 1;
18077 if Ekind
(R_Typ
) = E_String_Literal_Subtype
then
18078 R_Low
:= String_Literal_Low_Bound
(R_Typ
);
18079 R_Len
:= String_Literal_Length
(R_Typ
);
18081 R_Index
:= First_Index
(R_Typ
);
18082 Get_Index_Bounds
(R_Index
, R_Low
, R_High
);
18084 if Is_OK_Static_Expression
(R_Low
)
18086 Is_OK_Static_Expression
(R_High
)
18088 if Expr_Value
(R_High
) < Expr_Value
(R_Low
) then
18091 R_Len
:= (Expr_Value
(R_High
) - Expr_Value
(R_Low
)) + 1;
18098 if (Is_OK_Static_Expression
(L_Low
)
18100 Is_OK_Static_Expression
(R_Low
))
18101 and then Expr_Value
(L_Low
) = Expr_Value
(R_Low
)
18102 and then L_Len
= R_Len
18109 -- Then treat all other dimensions
18111 for Indx
in 2 .. L_Ndims
loop
18115 Get_Index_Bounds
(L_Index
, L_Low
, L_High
);
18116 Get_Index_Bounds
(R_Index
, R_Low
, R_High
);
18118 if (Is_OK_Static_Expression
(L_Low
) and then
18119 Is_OK_Static_Expression
(L_High
) and then
18120 Is_OK_Static_Expression
(R_Low
) and then
18121 Is_OK_Static_Expression
(R_High
))
18122 and then (Expr_Value
(L_Low
) = Expr_Value
(R_Low
)
18124 Expr_Value
(L_High
) = Expr_Value
(R_High
))
18132 -- If we fall through the loop, all indexes matched
18135 end Matching_Static_Array_Bounds
;
18137 -------------------
18138 -- May_Be_Lvalue --
18139 -------------------
18141 function May_Be_Lvalue
(N
: Node_Id
) return Boolean is
18142 P
: constant Node_Id
:= Parent
(N
);
18147 -- Test left side of assignment
18149 when N_Assignment_Statement
=>
18150 return N
= Name
(P
);
18152 -- Test prefix of component or attribute. Note that the prefix of an
18153 -- explicit or implicit dereference cannot be an l-value. In the case
18154 -- of a 'Read attribute, the reference can be an actual in the
18155 -- argument list of the attribute.
18157 when N_Attribute_Reference
=>
18158 return (N
= Prefix
(P
)
18159 and then Name_Implies_Lvalue_Prefix
(Attribute_Name
(P
)))
18161 Attribute_Name
(P
) = Name_Read
;
18163 -- For an expanded name, the name is an lvalue if the expanded name
18164 -- is an lvalue, but the prefix is never an lvalue, since it is just
18165 -- the scope where the name is found.
18167 when N_Expanded_Name
=>
18168 if N
= Prefix
(P
) then
18169 return May_Be_Lvalue
(P
);
18174 -- For a selected component A.B, A is certainly an lvalue if A.B is.
18175 -- B is a little interesting, if we have A.B := 3, there is some
18176 -- discussion as to whether B is an lvalue or not, we choose to say
18177 -- it is. Note however that A is not an lvalue if it is of an access
18178 -- type since this is an implicit dereference.
18180 when N_Selected_Component
=>
18182 and then Present
(Etype
(N
))
18183 and then Is_Access_Type
(Etype
(N
))
18187 return May_Be_Lvalue
(P
);
18190 -- For an indexed component or slice, the index or slice bounds is
18191 -- never an lvalue. The prefix is an lvalue if the indexed component
18192 -- or slice is an lvalue, except if it is an access type, where we
18193 -- have an implicit dereference.
18195 when N_Indexed_Component
18199 or else (Present
(Etype
(N
)) and then Is_Access_Type
(Etype
(N
)))
18203 return May_Be_Lvalue
(P
);
18206 -- Prefix of a reference is an lvalue if the reference is an lvalue
18208 when N_Reference
=>
18209 return May_Be_Lvalue
(P
);
18211 -- Prefix of explicit dereference is never an lvalue
18213 when N_Explicit_Dereference
=>
18216 -- Positional parameter for subprogram, entry, or accept call.
18217 -- In older versions of Ada function call arguments are never
18218 -- lvalues. In Ada 2012 functions can have in-out parameters.
18220 when N_Accept_Statement
18221 | N_Entry_Call_Statement
18222 | N_Subprogram_Call
18224 if Nkind
(P
) = N_Function_Call
and then Ada_Version
< Ada_2012
then
18228 -- The following mechanism is clumsy and fragile. A single flag
18229 -- set in Resolve_Actuals would be preferable ???
18237 Proc
:= Get_Subprogram_Entity
(P
);
18243 -- If we are not a list member, something is strange, so be
18244 -- conservative and return True.
18246 if not Is_List_Member
(N
) then
18250 -- We are going to find the right formal by stepping forward
18251 -- through the formals, as we step backwards in the actuals.
18253 Form
:= First_Formal
(Proc
);
18256 -- If no formal, something is weird, so be conservative and
18264 exit when No
(Act
);
18265 Next_Formal
(Form
);
18268 return Ekind
(Form
) /= E_In_Parameter
;
18271 -- Named parameter for procedure or accept call
18273 when N_Parameter_Association
=>
18279 Proc
:= Get_Subprogram_Entity
(Parent
(P
));
18285 -- Loop through formals to find the one that matches
18287 Form
:= First_Formal
(Proc
);
18289 -- If no matching formal, that's peculiar, some kind of
18290 -- previous error, so return True to be conservative.
18291 -- Actually happens with legal code for an unresolved call
18292 -- where we may get the wrong homonym???
18298 -- Else test for match
18300 if Chars
(Form
) = Chars
(Selector_Name
(P
)) then
18301 return Ekind
(Form
) /= E_In_Parameter
;
18304 Next_Formal
(Form
);
18308 -- Test for appearing in a conversion that itself appears in an
18309 -- lvalue context, since this should be an lvalue.
18311 when N_Type_Conversion
=>
18312 return May_Be_Lvalue
(P
);
18314 -- Test for appearance in object renaming declaration
18316 when N_Object_Renaming_Declaration
=>
18319 -- All other references are definitely not lvalues
18330 function Might_Raise
(N
: Node_Id
) return Boolean is
18331 Result
: Boolean := False;
18333 function Process
(N
: Node_Id
) return Traverse_Result
;
18334 -- Set Result to True if we find something that could raise an exception
18340 function Process
(N
: Node_Id
) return Traverse_Result
is
18342 if Nkind_In
(N
, N_Procedure_Call_Statement
,
18345 N_Raise_Constraint_Error
,
18346 N_Raise_Program_Error
,
18347 N_Raise_Storage_Error
)
18356 procedure Set_Result
is new Traverse_Proc
(Process
);
18358 -- Start of processing for Might_Raise
18361 -- False if exceptions can't be propagated
18363 if No_Exception_Handlers_Set
then
18367 -- If the checks handled by the back end are not disabled, we cannot
18368 -- ensure that no exception will be raised.
18370 if not Access_Checks_Suppressed
(Empty
)
18371 or else not Discriminant_Checks_Suppressed
(Empty
)
18372 or else not Range_Checks_Suppressed
(Empty
)
18373 or else not Index_Checks_Suppressed
(Empty
)
18374 or else Opt
.Stack_Checking_Enabled
18383 --------------------------------
18384 -- Nearest_Enclosing_Instance --
18385 --------------------------------
18387 function Nearest_Enclosing_Instance
(E
: Entity_Id
) return Entity_Id
is
18392 while Present
(Inst
) and then Inst
/= Standard_Standard
loop
18393 if Is_Generic_Instance
(Inst
) then
18397 Inst
:= Scope
(Inst
);
18401 end Nearest_Enclosing_Instance
;
18403 ----------------------
18404 -- Needs_One_Actual --
18405 ----------------------
18407 function Needs_One_Actual
(E
: Entity_Id
) return Boolean is
18408 Formal
: Entity_Id
;
18411 -- Ada 2005 or later, and formals present. The first formal must be
18412 -- of a type that supports prefix notation: a controlling argument,
18413 -- a class-wide type, or an access to such.
18415 if Ada_Version
>= Ada_2005
18416 and then Present
(First_Formal
(E
))
18417 and then No
(Default_Value
(First_Formal
(E
)))
18419 (Is_Controlling_Formal
(First_Formal
(E
))
18420 or else Is_Class_Wide_Type
(Etype
(First_Formal
(E
)))
18421 or else Is_Anonymous_Access_Type
(Etype
(First_Formal
(E
))))
18423 Formal
:= Next_Formal
(First_Formal
(E
));
18424 while Present
(Formal
) loop
18425 if No
(Default_Value
(Formal
)) then
18429 Next_Formal
(Formal
);
18434 -- Ada 83/95 or no formals
18439 end Needs_One_Actual
;
18441 ------------------------
18442 -- New_Copy_List_Tree --
18443 ------------------------
18445 function New_Copy_List_Tree
(List
: List_Id
) return List_Id
is
18450 if List
= No_List
then
18457 while Present
(E
) loop
18458 Append
(New_Copy_Tree
(E
), NL
);
18464 end New_Copy_List_Tree
;
18466 -------------------
18467 -- New_Copy_Tree --
18468 -------------------
18470 -- The following tables play a key role in replicating entities and Itypes.
18471 -- They are intentionally declared at the library level rather than within
18472 -- New_Copy_Tree to avoid elaborating them on each call. This performance
18473 -- optimization saves up to 2% of the entire compilation time spent in the
18474 -- front end. Care should be taken to reset the tables on each new call to
18477 NCT_Table_Max
: constant := 511;
18479 subtype NCT_Table_Index
is Nat
range 0 .. NCT_Table_Max
- 1;
18481 function NCT_Table_Hash
(Key
: Node_Or_Entity_Id
) return NCT_Table_Index
;
18482 -- Obtain the hash value of node or entity Key
18484 --------------------
18485 -- NCT_Table_Hash --
18486 --------------------
18488 function NCT_Table_Hash
(Key
: Node_Or_Entity_Id
) return NCT_Table_Index
is
18490 return NCT_Table_Index
(Key
mod NCT_Table_Max
);
18491 end NCT_Table_Hash
;
18493 ----------------------
18494 -- NCT_New_Entities --
18495 ----------------------
18497 -- The following table maps old entities and Itypes to their corresponding
18498 -- new entities and Itypes.
18502 package NCT_New_Entities
is new Simple_HTable
(
18503 Header_Num
=> NCT_Table_Index
,
18504 Element
=> Entity_Id
,
18505 No_Element
=> Empty
,
18507 Hash
=> NCT_Table_Hash
,
18510 ------------------------
18511 -- NCT_Pending_Itypes --
18512 ------------------------
18514 -- The following table maps old Associated_Node_For_Itype nodes to a set of
18515 -- new itypes. Given a set of old Itypes Aaa, Bbb, and Ccc, where all three
18516 -- have the same Associated_Node_For_Itype Ppp, and their corresponding new
18517 -- Itypes Xxx, Yyy, Zzz, the table contains the following mapping:
18519 -- Ppp -> (Xxx, Yyy, Zzz)
18521 -- The set is expressed as an Elist
18523 package NCT_Pending_Itypes
is new Simple_HTable
(
18524 Header_Num
=> NCT_Table_Index
,
18525 Element
=> Elist_Id
,
18526 No_Element
=> No_Elist
,
18528 Hash
=> NCT_Table_Hash
,
18531 NCT_Tables_In_Use
: Boolean := False;
18532 -- This flag keeps track of whether the two tables NCT_New_Entities and
18533 -- NCT_Pending_Itypes are in use. The flag is part of an optimization
18534 -- where certain operations are not performed if the tables are not in
18535 -- use. This saves up to 8% of the entire compilation time spent in the
18538 -------------------
18539 -- New_Copy_Tree --
18540 -------------------
18542 function New_Copy_Tree
18544 Map
: Elist_Id
:= No_Elist
;
18545 New_Sloc
: Source_Ptr
:= No_Location
;
18546 New_Scope
: Entity_Id
:= Empty
) return Node_Id
18548 -- This routine performs low-level tree manipulations and needs access
18549 -- to the internals of the tree.
18551 use Atree
.Unchecked_Access
;
18552 use Atree_Private_Part
;
18554 EWA_Level
: Nat
:= 0;
18555 -- This counter keeps track of how many N_Expression_With_Actions nodes
18556 -- are encountered during a depth-first traversal of the subtree. These
18557 -- nodes may define new entities in their Actions lists and thus require
18558 -- special processing.
18560 EWA_Inner_Scope_Level
: Nat
:= 0;
18561 -- This counter keeps track of how many scoping constructs appear within
18562 -- an N_Expression_With_Actions node.
18564 procedure Add_New_Entity
(Old_Id
: Entity_Id
; New_Id
: Entity_Id
);
18565 pragma Inline
(Add_New_Entity
);
18566 -- Add an entry in the NCT_New_Entities table which maps key Old_Id to
18567 -- value New_Id. Old_Id is an entity which appears within the Actions
18568 -- list of an N_Expression_With_Actions node, or within an entity map.
18569 -- New_Id is the corresponding new entity generated during Phase 1.
18571 procedure Add_Pending_Itype
(Assoc_Nod
: Node_Id
; Itype
: Entity_Id
);
18572 pragma Inline
(Add_New_Entity
);
18573 -- Add an entry in the NCT_Pending_Itypes which maps key Assoc_Nod to
18574 -- value Itype. Assoc_Nod is the associated node of an itype. Itype is
18577 procedure Build_NCT_Tables
(Entity_Map
: Elist_Id
);
18578 pragma Inline
(Build_NCT_Tables
);
18579 -- Populate tables NCT_New_Entities and NCT_Pending_Itypes with the
18580 -- information supplied in entity map Entity_Map. The format of the
18581 -- entity map must be as follows:
18583 -- Old_Id1, New_Id1, Old_Id2, New_Id2, .., Old_IdN, New_IdN
18585 function Copy_Any_Node_With_Replacement
18586 (N
: Node_Or_Entity_Id
) return Node_Or_Entity_Id
;
18587 pragma Inline
(Copy_Any_Node_With_Replacement
);
18588 -- Replicate entity or node N by invoking one of the following routines:
18590 -- Copy_Node_With_Replacement
18591 -- Corresponding_Entity
18593 function Copy_Elist_With_Replacement
(List
: Elist_Id
) return Elist_Id
;
18594 -- Replicate the elements of entity list List
18596 function Copy_Field_With_Replacement
18598 Old_Par
: Node_Id
:= Empty
;
18599 New_Par
: Node_Id
:= Empty
;
18600 Semantic
: Boolean := False) return Union_Id
;
18601 -- Replicate field Field by invoking one of the following routines:
18603 -- Copy_Elist_With_Replacement
18604 -- Copy_List_With_Replacement
18605 -- Copy_Node_With_Replacement
18606 -- Corresponding_Entity
18608 -- If the field is not an entity list, entity, itype, syntactic list,
18609 -- or node, then the field is returned unchanged. The routine always
18610 -- replicates entities, itypes, and valid syntactic fields. Old_Par is
18611 -- the expected parent of a syntactic field. New_Par is the new parent
18612 -- associated with a replicated syntactic field. Flag Semantic should
18613 -- be set when the input is a semantic field.
18615 function Copy_List_With_Replacement
(List
: List_Id
) return List_Id
;
18616 -- Replicate the elements of syntactic list List
18618 function Copy_Node_With_Replacement
(N
: Node_Id
) return Node_Id
;
18619 -- Replicate node N
18621 function Corresponding_Entity
(Id
: Entity_Id
) return Entity_Id
;
18622 pragma Inline
(Corresponding_Entity
);
18623 -- Return the corresponding new entity of Id generated during Phase 1.
18624 -- If there is no such entity, return Id.
18626 function In_Entity_Map
18628 Entity_Map
: Elist_Id
) return Boolean;
18629 pragma Inline
(In_Entity_Map
);
18630 -- Determine whether entity Id is one of the old ids specified in entity
18631 -- map Entity_Map. The format of the entity map must be as follows:
18633 -- Old_Id1, New_Id1, Old_Id2, New_Id2, .., Old_IdN, New_IdN
18635 procedure Update_CFS_Sloc
(N
: Node_Or_Entity_Id
);
18636 pragma Inline
(Update_CFS_Sloc
);
18637 -- Update the Comes_From_Source and Sloc attributes of node or entity N
18639 procedure Update_First_Real_Statement
18640 (Old_HSS
: Node_Id
;
18641 New_HSS
: Node_Id
);
18642 pragma Inline
(Update_First_Real_Statement
);
18643 -- Update semantic attribute First_Real_Statement of handled sequence of
18644 -- statements New_HSS based on handled sequence of statements Old_HSS.
18646 procedure Update_Named_Associations
18647 (Old_Call
: Node_Id
;
18648 New_Call
: Node_Id
);
18649 pragma Inline
(Update_Named_Associations
);
18650 -- Update semantic chain First/Next_Named_Association of call New_call
18651 -- based on call Old_Call.
18653 procedure Update_New_Entities
(Entity_Map
: Elist_Id
);
18654 pragma Inline
(Update_New_Entities
);
18655 -- Update the semantic attributes of all new entities generated during
18656 -- Phase 1 that do not appear in entity map Entity_Map. The format of
18657 -- the entity map must be as follows:
18659 -- Old_Id1, New_Id1, Old_Id2, New_Id2, .., Old_IdN, New_IdN
18661 procedure Update_Pending_Itypes
18662 (Old_Assoc
: Node_Id
;
18663 New_Assoc
: Node_Id
);
18664 pragma Inline
(Update_Pending_Itypes
);
18665 -- Update semantic attribute Associated_Node_For_Itype to refer to node
18666 -- New_Assoc for all itypes whose associated node is Old_Assoc.
18668 procedure Update_Semantic_Fields
(Id
: Entity_Id
);
18669 pragma Inline
(Update_Semantic_Fields
);
18670 -- Subsidiary to Update_New_Entities. Update semantic fields of entity
18673 procedure Visit_Any_Node
(N
: Node_Or_Entity_Id
);
18674 pragma Inline
(Visit_Any_Node
);
18675 -- Visit entity of node N by invoking one of the following routines:
18681 procedure Visit_Elist
(List
: Elist_Id
);
18682 -- Visit the elements of entity list List
18684 procedure Visit_Entity
(Id
: Entity_Id
);
18685 -- Visit entity Id. This action may create a new entity of Id and save
18686 -- it in table NCT_New_Entities.
18688 procedure Visit_Field
18690 Par_Nod
: Node_Id
:= Empty
;
18691 Semantic
: Boolean := False);
18692 -- Visit field Field by invoking one of the following routines:
18700 -- If the field is not an entity list, entity, itype, syntactic list,
18701 -- or node, then the field is not visited. The routine always visits
18702 -- valid syntactic fields. Par_Nod is the expected parent of the
18703 -- syntactic field. Flag Semantic should be set when the input is a
18706 procedure Visit_Itype
(Itype
: Entity_Id
);
18707 -- Visit itype Itype. This action may create a new entity for Itype and
18708 -- save it in table NCT_New_Entities. In addition, the routine may map
18709 -- the associated node of Itype to the new itype in NCT_Pending_Itypes.
18711 procedure Visit_List
(List
: List_Id
);
18712 -- Visit the elements of syntactic list List
18714 procedure Visit_Node
(N
: Node_Id
);
18717 procedure Visit_Semantic_Fields
(Id
: Entity_Id
);
18718 pragma Inline
(Visit_Semantic_Fields
);
18719 -- Subsidiary to Visit_Entity and Visit_Itype. Visit common semantic
18720 -- fields of entity or itype Id.
18722 --------------------
18723 -- Add_New_Entity --
18724 --------------------
18726 procedure Add_New_Entity
(Old_Id
: Entity_Id
; New_Id
: Entity_Id
) is
18728 pragma Assert
(Present
(Old_Id
));
18729 pragma Assert
(Present
(New_Id
));
18730 pragma Assert
(Nkind
(Old_Id
) in N_Entity
);
18731 pragma Assert
(Nkind
(New_Id
) in N_Entity
);
18733 NCT_Tables_In_Use
:= True;
18735 -- Sanity check the NCT_New_Entities table. No previous mapping with
18736 -- key Old_Id should exist.
18738 pragma Assert
(No
(NCT_New_Entities
.Get
(Old_Id
)));
18740 -- Establish the mapping
18742 -- Old_Id -> New_Id
18744 NCT_New_Entities
.Set
(Old_Id
, New_Id
);
18745 end Add_New_Entity
;
18747 -----------------------
18748 -- Add_Pending_Itype --
18749 -----------------------
18751 procedure Add_Pending_Itype
(Assoc_Nod
: Node_Id
; Itype
: Entity_Id
) is
18755 pragma Assert
(Present
(Assoc_Nod
));
18756 pragma Assert
(Present
(Itype
));
18757 pragma Assert
(Nkind
(Itype
) in N_Entity
);
18758 pragma Assert
(Is_Itype
(Itype
));
18760 NCT_Tables_In_Use
:= True;
18762 -- It is not possible to sanity check the NCT_Pendint_Itypes table
18763 -- directly because a single node may act as the associated node for
18764 -- multiple itypes.
18766 Itypes
:= NCT_Pending_Itypes
.Get
(Assoc_Nod
);
18768 if No
(Itypes
) then
18769 Itypes
:= New_Elmt_List
;
18770 NCT_Pending_Itypes
.Set
(Assoc_Nod
, Itypes
);
18773 -- Establish the mapping
18775 -- Assoc_Nod -> (Itype, ...)
18777 -- Avoid inserting the same itype multiple times. This involves a
18778 -- linear search, however the set of itypes with the same associated
18779 -- node is very small.
18781 Append_Unique_Elmt
(Itype
, Itypes
);
18782 end Add_Pending_Itype
;
18784 ----------------------
18785 -- Build_NCT_Tables --
18786 ----------------------
18788 procedure Build_NCT_Tables
(Entity_Map
: Elist_Id
) is
18790 Old_Id
: Entity_Id
;
18791 New_Id
: Entity_Id
;
18794 -- Nothing to do when there is no entity map
18796 if No
(Entity_Map
) then
18800 Elmt
:= First_Elmt
(Entity_Map
);
18801 while Present
(Elmt
) loop
18803 -- Extract the (Old_Id, New_Id) pair from the entity map
18805 Old_Id
:= Node
(Elmt
);
18808 New_Id
:= Node
(Elmt
);
18811 -- Establish the following mapping within table NCT_New_Entities
18813 -- Old_Id -> New_Id
18815 Add_New_Entity
(Old_Id
, New_Id
);
18817 -- Establish the following mapping within table NCT_Pending_Itypes
18818 -- when the new entity is an itype.
18820 -- Assoc_Nod -> (New_Id, ...)
18822 -- IMPORTANT: the associated node is that of the old itype because
18823 -- the node will be replicated in Phase 2.
18825 if Is_Itype
(Old_Id
) then
18827 (Assoc_Nod
=> Associated_Node_For_Itype
(Old_Id
),
18831 end Build_NCT_Tables
;
18833 ------------------------------------
18834 -- Copy_Any_Node_With_Replacement --
18835 ------------------------------------
18837 function Copy_Any_Node_With_Replacement
18838 (N
: Node_Or_Entity_Id
) return Node_Or_Entity_Id
18841 if Nkind
(N
) in N_Entity
then
18842 return Corresponding_Entity
(N
);
18844 return Copy_Node_With_Replacement
(N
);
18846 end Copy_Any_Node_With_Replacement
;
18848 ---------------------------------
18849 -- Copy_Elist_With_Replacement --
18850 ---------------------------------
18852 function Copy_Elist_With_Replacement
(List
: Elist_Id
) return Elist_Id
is
18857 -- Copy the contents of the old list. Note that the list itself may
18858 -- be empty, in which case the routine returns a new empty list. This
18859 -- avoids sharing lists between subtrees. The element of an entity
18860 -- list could be an entity or a node, hence the invocation of routine
18861 -- Copy_Any_Node_With_Replacement.
18863 if Present
(List
) then
18864 Result
:= New_Elmt_List
;
18866 Elmt
:= First_Elmt
(List
);
18867 while Present
(Elmt
) loop
18869 (Copy_Any_Node_With_Replacement
(Node
(Elmt
)), Result
);
18874 -- Otherwise the list does not exist
18877 Result
:= No_Elist
;
18881 end Copy_Elist_With_Replacement
;
18883 ---------------------------------
18884 -- Copy_Field_With_Replacement --
18885 ---------------------------------
18887 function Copy_Field_With_Replacement
18889 Old_Par
: Node_Id
:= Empty
;
18890 New_Par
: Node_Id
:= Empty
;
18891 Semantic
: Boolean := False) return Union_Id
18894 -- The field is empty
18896 if Field
= Union_Id
(Empty
) then
18899 -- The field is an entity/itype/node
18901 elsif Field
in Node_Range
then
18903 Old_N
: constant Node_Id
:= Node_Id
(Field
);
18904 Syntactic
: constant Boolean := Parent
(Old_N
) = Old_Par
;
18909 -- The field is an entity/itype
18911 if Nkind
(Old_N
) in N_Entity
then
18913 -- An entity/itype is always replicated
18915 New_N
:= Corresponding_Entity
(Old_N
);
18917 -- Update the parent pointer when the entity is a syntactic
18918 -- field. Note that itypes do not have parent pointers.
18920 if Syntactic
and then New_N
/= Old_N
then
18921 Set_Parent
(New_N
, New_Par
);
18924 -- The field is a node
18927 -- A node is replicated when it is either a syntactic field
18928 -- or when the caller treats it as a semantic attribute.
18930 if Syntactic
or else Semantic
then
18931 New_N
:= Copy_Node_With_Replacement
(Old_N
);
18933 -- Update the parent pointer when the node is a syntactic
18936 if Syntactic
and then New_N
/= Old_N
then
18937 Set_Parent
(New_N
, New_Par
);
18940 -- Otherwise the node is returned unchanged
18947 return Union_Id
(New_N
);
18950 -- The field is an entity list
18952 elsif Field
in Elist_Range
then
18953 return Union_Id
(Copy_Elist_With_Replacement
(Elist_Id
(Field
)));
18955 -- The field is a syntactic list
18957 elsif Field
in List_Range
then
18959 Old_List
: constant List_Id
:= List_Id
(Field
);
18960 Syntactic
: constant Boolean := Parent
(Old_List
) = Old_Par
;
18962 New_List
: List_Id
;
18965 -- A list is replicated when it is either a syntactic field or
18966 -- when the caller treats it as a semantic attribute.
18968 if Syntactic
or else Semantic
then
18969 New_List
:= Copy_List_With_Replacement
(Old_List
);
18971 -- Update the parent pointer when the list is a syntactic
18974 if Syntactic
and then New_List
/= Old_List
then
18975 Set_Parent
(New_List
, New_Par
);
18978 -- Otherwise the list is returned unchanged
18981 New_List
:= Old_List
;
18984 return Union_Id
(New_List
);
18987 -- Otherwise the field denotes an attribute that does not need to be
18988 -- replicated (Chars, literals, etc).
18993 end Copy_Field_With_Replacement
;
18995 --------------------------------
18996 -- Copy_List_With_Replacement --
18997 --------------------------------
18999 function Copy_List_With_Replacement
(List
: List_Id
) return List_Id
is
19004 -- Copy the contents of the old list. Note that the list itself may
19005 -- be empty, in which case the routine returns a new empty list. This
19006 -- avoids sharing lists between subtrees. The element of a syntactic
19007 -- list is always a node, never an entity or itype, hence the call to
19008 -- routine Copy_Node_With_Replacement.
19010 if Present
(List
) then
19011 Result
:= New_List
;
19013 Elmt
:= First
(List
);
19014 while Present
(Elmt
) loop
19015 Append
(Copy_Node_With_Replacement
(Elmt
), Result
);
19020 -- Otherwise the list does not exist
19027 end Copy_List_With_Replacement
;
19029 --------------------------------
19030 -- Copy_Node_With_Replacement --
19031 --------------------------------
19033 function Copy_Node_With_Replacement
(N
: Node_Id
) return Node_Id
is
19037 -- Assume that the node must be returned unchanged
19041 if N
> Empty_Or_Error
then
19042 pragma Assert
(Nkind
(N
) not in N_Entity
);
19044 Result
:= New_Copy
(N
);
19046 Set_Field1
(Result
,
19047 Copy_Field_With_Replacement
19048 (Field
=> Field1
(Result
),
19050 New_Par
=> Result
));
19052 Set_Field2
(Result
,
19053 Copy_Field_With_Replacement
19054 (Field
=> Field2
(Result
),
19056 New_Par
=> Result
));
19058 Set_Field3
(Result
,
19059 Copy_Field_With_Replacement
19060 (Field
=> Field3
(Result
),
19062 New_Par
=> Result
));
19064 Set_Field4
(Result
,
19065 Copy_Field_With_Replacement
19066 (Field
=> Field4
(Result
),
19068 New_Par
=> Result
));
19070 Set_Field5
(Result
,
19071 Copy_Field_With_Replacement
19072 (Field
=> Field5
(Result
),
19074 New_Par
=> Result
));
19076 -- Update the Comes_From_Source and Sloc attributes of the node
19077 -- in case the caller has supplied new values.
19079 Update_CFS_Sloc
(Result
);
19081 -- Update the Associated_Node_For_Itype attribute of all itypes
19082 -- created during Phase 1 whose associated node is N. As a result
19083 -- the Associated_Node_For_Itype refers to the replicated node.
19084 -- No action needs to be taken when the Associated_Node_For_Itype
19085 -- refers to an entity because this was already handled during
19086 -- Phase 1, in Visit_Itype.
19088 Update_Pending_Itypes
19090 New_Assoc
=> Result
);
19092 -- Update the First/Next_Named_Association chain for a replicated
19095 if Nkind_In
(N
, N_Entry_Call_Statement
,
19097 N_Procedure_Call_Statement
)
19099 Update_Named_Associations
19101 New_Call
=> Result
);
19103 -- Update the Renamed_Object attribute of a replicated object
19106 elsif Nkind
(N
) = N_Object_Renaming_Declaration
then
19107 Set_Renamed_Object
(Defining_Entity
(Result
), Name
(Result
));
19109 -- Update the First_Real_Statement attribute of a replicated
19110 -- handled sequence of statements.
19112 elsif Nkind
(N
) = N_Handled_Sequence_Of_Statements
then
19113 Update_First_Real_Statement
19115 New_HSS
=> Result
);
19120 end Copy_Node_With_Replacement
;
19122 --------------------------
19123 -- Corresponding_Entity --
19124 --------------------------
19126 function Corresponding_Entity
(Id
: Entity_Id
) return Entity_Id
is
19127 New_Id
: Entity_Id
;
19128 Result
: Entity_Id
;
19131 -- Assume that the entity must be returned unchanged
19135 if Id
> Empty_Or_Error
then
19136 pragma Assert
(Nkind
(Id
) in N_Entity
);
19138 -- Determine whether the entity has a corresponding new entity
19139 -- generated during Phase 1 and if it does, use it.
19141 if NCT_Tables_In_Use
then
19142 New_Id
:= NCT_New_Entities
.Get
(Id
);
19144 if Present
(New_Id
) then
19151 end Corresponding_Entity
;
19153 -------------------
19154 -- In_Entity_Map --
19155 -------------------
19157 function In_Entity_Map
19159 Entity_Map
: Elist_Id
) return Boolean
19162 Old_Id
: Entity_Id
;
19165 -- The entity map contains pairs (Old_Id, New_Id). The advancement
19166 -- step always skips the New_Id portion of the pair.
19168 if Present
(Entity_Map
) then
19169 Elmt
:= First_Elmt
(Entity_Map
);
19170 while Present
(Elmt
) loop
19171 Old_Id
:= Node
(Elmt
);
19173 if Old_Id
= Id
then
19185 ---------------------
19186 -- Update_CFS_Sloc --
19187 ---------------------
19189 procedure Update_CFS_Sloc
(N
: Node_Or_Entity_Id
) is
19191 -- A new source location defaults the Comes_From_Source attribute
19193 if New_Sloc
/= No_Location
then
19194 Set_Comes_From_Source
(N
, Default_Node
.Comes_From_Source
);
19195 Set_Sloc
(N
, New_Sloc
);
19197 end Update_CFS_Sloc
;
19199 ---------------------------------
19200 -- Update_First_Real_Statement --
19201 ---------------------------------
19203 procedure Update_First_Real_Statement
19204 (Old_HSS
: Node_Id
;
19207 Old_First_Stmt
: constant Node_Id
:= First_Real_Statement
(Old_HSS
);
19209 New_Stmt
: Node_Id
;
19210 Old_Stmt
: Node_Id
;
19213 -- Recreate the First_Real_Statement attribute of a handled sequence
19214 -- of statements by traversing the statement lists of both sequences
19217 if Present
(Old_First_Stmt
) then
19218 New_Stmt
:= First
(Statements
(New_HSS
));
19219 Old_Stmt
:= First
(Statements
(Old_HSS
));
19220 while Present
(Old_Stmt
) and then Old_Stmt
/= Old_First_Stmt
loop
19225 pragma Assert
(Present
(New_Stmt
));
19226 pragma Assert
(Present
(Old_Stmt
));
19228 Set_First_Real_Statement
(New_HSS
, New_Stmt
);
19230 end Update_First_Real_Statement
;
19232 -------------------------------
19233 -- Update_Named_Associations --
19234 -------------------------------
19236 procedure Update_Named_Associations
19237 (Old_Call
: Node_Id
;
19238 New_Call
: Node_Id
)
19241 New_Next
: Node_Id
;
19243 Old_Next
: Node_Id
;
19246 -- Recreate the First/Next_Named_Actual chain of a call by traversing
19247 -- the chains of both the old and new calls in parallel.
19249 New_Act
:= First
(Parameter_Associations
(New_Call
));
19250 Old_Act
:= First
(Parameter_Associations
(Old_Call
));
19251 while Present
(Old_Act
) loop
19252 if Nkind
(Old_Act
) = N_Parameter_Association
19253 and then Present
(Next_Named_Actual
(Old_Act
))
19255 if First_Named_Actual
(Old_Call
) =
19256 Explicit_Actual_Parameter
(Old_Act
)
19258 Set_First_Named_Actual
(New_Call
,
19259 Explicit_Actual_Parameter
(New_Act
));
19262 -- Scan the actual parameter list to find the next suitable
19263 -- named actual. Note that the list may be out of order.
19265 New_Next
:= First
(Parameter_Associations
(New_Call
));
19266 Old_Next
:= First
(Parameter_Associations
(Old_Call
));
19267 while Nkind
(Old_Next
) /= N_Parameter_Association
19268 or else Explicit_Actual_Parameter
(Old_Next
) /=
19269 Next_Named_Actual
(Old_Act
)
19275 Set_Next_Named_Actual
(New_Act
,
19276 Explicit_Actual_Parameter
(New_Next
));
19282 end Update_Named_Associations
;
19284 -------------------------
19285 -- Update_New_Entities --
19286 -------------------------
19288 procedure Update_New_Entities
(Entity_Map
: Elist_Id
) is
19289 New_Id
: Entity_Id
:= Empty
;
19290 Old_Id
: Entity_Id
:= Empty
;
19293 if NCT_Tables_In_Use
then
19294 NCT_New_Entities
.Get_First
(Old_Id
, New_Id
);
19296 -- Update the semantic fields of all new entities created during
19297 -- Phase 1 which were not supplied via an entity map.
19298 -- ??? Is there a better way of distinguishing those?
19300 while Present
(Old_Id
) and then Present
(New_Id
) loop
19301 if not (Present
(Entity_Map
)
19302 and then In_Entity_Map
(Old_Id
, Entity_Map
))
19304 Update_Semantic_Fields
(New_Id
);
19307 NCT_New_Entities
.Get_Next
(Old_Id
, New_Id
);
19310 end Update_New_Entities
;
19312 ---------------------------
19313 -- Update_Pending_Itypes --
19314 ---------------------------
19316 procedure Update_Pending_Itypes
19317 (Old_Assoc
: Node_Id
;
19318 New_Assoc
: Node_Id
)
19324 if NCT_Tables_In_Use
then
19325 Itypes
:= NCT_Pending_Itypes
.Get
(Old_Assoc
);
19327 -- Update the Associated_Node_For_Itype attribute for all itypes
19328 -- which originally refer to Old_Assoc to designate New_Assoc.
19330 if Present
(Itypes
) then
19331 Item
:= First_Elmt
(Itypes
);
19332 while Present
(Item
) loop
19333 Set_Associated_Node_For_Itype
(Node
(Item
), New_Assoc
);
19339 end Update_Pending_Itypes
;
19341 ----------------------------
19342 -- Update_Semantic_Fields --
19343 ----------------------------
19345 procedure Update_Semantic_Fields
(Id
: Entity_Id
) is
19347 -- Discriminant_Constraint
19349 if Has_Discriminants
(Base_Type
(Id
)) then
19350 Set_Discriminant_Constraint
(Id
, Elist_Id
(
19351 Copy_Field_With_Replacement
19352 (Field
=> Union_Id
(Discriminant_Constraint
(Id
)),
19353 Semantic
=> True)));
19358 Set_Etype
(Id
, Node_Id
(
19359 Copy_Field_With_Replacement
19360 (Field
=> Union_Id
(Etype
(Id
)),
19361 Semantic
=> True)));
19364 -- Packed_Array_Impl_Type
19366 if Is_Array_Type
(Id
) then
19367 if Present
(First_Index
(Id
)) then
19368 Set_First_Index
(Id
, First
(List_Id
(
19369 Copy_Field_With_Replacement
19370 (Field
=> Union_Id
(List_Containing
(First_Index
(Id
))),
19371 Semantic
=> True))));
19374 if Is_Packed
(Id
) then
19375 Set_Packed_Array_Impl_Type
(Id
, Node_Id
(
19376 Copy_Field_With_Replacement
19377 (Field
=> Union_Id
(Packed_Array_Impl_Type
(Id
)),
19378 Semantic
=> True)));
19384 Set_Next_Entity
(Id
, Node_Id
(
19385 Copy_Field_With_Replacement
19386 (Field
=> Union_Id
(Next_Entity
(Id
)),
19387 Semantic
=> True)));
19391 if Is_Discrete_Type
(Id
) then
19392 Set_Scalar_Range
(Id
, Node_Id
(
19393 Copy_Field_With_Replacement
19394 (Field
=> Union_Id
(Scalar_Range
(Id
)),
19395 Semantic
=> True)));
19400 -- Update the scope when the caller specified an explicit one
19402 if Present
(New_Scope
) then
19403 Set_Scope
(Id
, New_Scope
);
19405 Set_Scope
(Id
, Node_Id
(
19406 Copy_Field_With_Replacement
19407 (Field
=> Union_Id
(Scope
(Id
)),
19408 Semantic
=> True)));
19410 end Update_Semantic_Fields
;
19412 --------------------
19413 -- Visit_Any_Node --
19414 --------------------
19416 procedure Visit_Any_Node
(N
: Node_Or_Entity_Id
) is
19418 if Nkind
(N
) in N_Entity
then
19419 if Is_Itype
(N
) then
19427 end Visit_Any_Node
;
19433 procedure Visit_Elist
(List
: Elist_Id
) is
19437 -- The element of an entity list could be an entity, itype, or a
19438 -- node, hence the call to Visit_Any_Node.
19440 if Present
(List
) then
19441 Elmt
:= First_Elmt
(List
);
19442 while Present
(Elmt
) loop
19443 Visit_Any_Node
(Node
(Elmt
));
19454 procedure Visit_Entity
(Id
: Entity_Id
) is
19455 New_Id
: Entity_Id
;
19458 pragma Assert
(Nkind
(Id
) in N_Entity
);
19459 pragma Assert
(not Is_Itype
(Id
));
19461 -- Nothing to do if the entity is not defined in the Actions list of
19462 -- an N_Expression_With_Actions node.
19464 if EWA_Level
= 0 then
19467 -- Nothing to do if the entity is defined within a scoping construct
19468 -- of an N_Expression_With_Actions node.
19470 elsif EWA_Inner_Scope_Level
> 0 then
19473 -- Nothing to do if the entity is not an object or a type. Relaxing
19474 -- this restriction leads to a performance penalty.
19476 elsif not Ekind_In
(Id
, E_Constant
, E_Variable
)
19477 and then not Is_Type
(Id
)
19481 -- Nothing to do if the entity was already visited
19483 elsif NCT_Tables_In_Use
19484 and then Present
(NCT_New_Entities
.Get
(Id
))
19488 -- Nothing to do if the declaration node of the entity is not within
19489 -- the subtree being replicated.
19491 elsif not In_Subtree
19492 (N
=> Declaration_Node
(Id
),
19498 -- Create a new entity by directly copying the old entity. This
19499 -- action causes all attributes of the old entity to be inherited.
19501 New_Id
:= New_Copy
(Id
);
19503 -- Create a new name for the new entity because the back end needs
19504 -- distinct names for debugging purposes.
19506 Set_Chars
(New_Id
, New_Internal_Name
('T'));
19508 -- Update the Comes_From_Source and Sloc attributes of the entity in
19509 -- case the caller has supplied new values.
19511 Update_CFS_Sloc
(New_Id
);
19513 -- Establish the following mapping within table NCT_New_Entities:
19517 Add_New_Entity
(Id
, New_Id
);
19519 -- Deal with the semantic fields of entities. The fields are visited
19520 -- because they may mention entities which reside within the subtree
19523 Visit_Semantic_Fields
(Id
);
19530 procedure Visit_Field
19532 Par_Nod
: Node_Id
:= Empty
;
19533 Semantic
: Boolean := False)
19536 -- The field is empty
19538 if Field
= Union_Id
(Empty
) then
19541 -- The field is an entity/itype/node
19543 elsif Field
in Node_Range
then
19545 N
: constant Node_Id
:= Node_Id
(Field
);
19548 -- The field is an entity/itype
19550 if Nkind
(N
) in N_Entity
then
19552 -- Itypes are always visited
19554 if Is_Itype
(N
) then
19557 -- An entity is visited when it is either a syntactic field
19558 -- or when the caller treats it as a semantic attribute.
19560 elsif Parent
(N
) = Par_Nod
or else Semantic
then
19564 -- The field is a node
19567 -- A node is visited when it is either a syntactic field or
19568 -- when the caller treats it as a semantic attribute.
19570 if Parent
(N
) = Par_Nod
or else Semantic
then
19576 -- The field is an entity list
19578 elsif Field
in Elist_Range
then
19579 Visit_Elist
(Elist_Id
(Field
));
19581 -- The field is a syntax list
19583 elsif Field
in List_Range
then
19585 List
: constant List_Id
:= List_Id
(Field
);
19588 -- A syntax list is visited when it is either a syntactic field
19589 -- or when the caller treats it as a semantic attribute.
19591 if Parent
(List
) = Par_Nod
or else Semantic
then
19596 -- Otherwise the field denotes information which does not need to be
19597 -- visited (chars, literals, etc.).
19608 procedure Visit_Itype
(Itype
: Entity_Id
) is
19609 New_Assoc
: Node_Id
;
19610 New_Itype
: Entity_Id
;
19611 Old_Assoc
: Node_Id
;
19614 pragma Assert
(Nkind
(Itype
) in N_Entity
);
19615 pragma Assert
(Is_Itype
(Itype
));
19617 -- Itypes that describe the designated type of access to subprograms
19618 -- have the structure of subprogram declarations, with signatures,
19619 -- etc. Either we duplicate the signatures completely, or choose to
19620 -- share such itypes, which is fine because their elaboration will
19621 -- have no side effects.
19623 if Ekind
(Itype
) = E_Subprogram_Type
then
19626 -- Nothing to do if the itype was already visited
19628 elsif NCT_Tables_In_Use
19629 and then Present
(NCT_New_Entities
.Get
(Itype
))
19633 -- Nothing to do if the associated node of the itype is not within
19634 -- the subtree being replicated.
19636 elsif not In_Subtree
19637 (N
=> Associated_Node_For_Itype
(Itype
),
19643 -- Create a new itype by directly copying the old itype. This action
19644 -- causes all attributes of the old itype to be inherited.
19646 New_Itype
:= New_Copy
(Itype
);
19648 -- Create a new name for the new itype because the back end requires
19649 -- distinct names for debugging purposes.
19651 Set_Chars
(New_Itype
, New_Internal_Name
('T'));
19653 -- Update the Comes_From_Source and Sloc attributes of the itype in
19654 -- case the caller has supplied new values.
19656 Update_CFS_Sloc
(New_Itype
);
19658 -- Establish the following mapping within table NCT_New_Entities:
19660 -- Itype -> New_Itype
19662 Add_New_Entity
(Itype
, New_Itype
);
19664 -- The new itype must be unfrozen because the resulting subtree may
19665 -- be inserted anywhere and cause an earlier or later freezing.
19667 if Present
(Freeze_Node
(New_Itype
)) then
19668 Set_Freeze_Node
(New_Itype
, Empty
);
19669 Set_Is_Frozen
(New_Itype
, False);
19672 -- If a record subtype is simply copied, the entity list will be
19673 -- shared. Thus cloned_Subtype must be set to indicate the sharing.
19674 -- ??? What does this do?
19676 if Ekind_In
(Itype
, E_Class_Wide_Subtype
, E_Record_Subtype
) then
19677 Set_Cloned_Subtype
(New_Itype
, Itype
);
19680 -- The associated node may denote an entity, in which case it may
19681 -- already have a new corresponding entity created during a prior
19682 -- call to Visit_Entity or Visit_Itype for the same subtree.
19685 -- Old_Assoc ---------> New_Assoc
19687 -- Created by Visit_Itype
19688 -- Itype -------------> New_Itype
19689 -- ANFI = Old_Assoc ANFI = Old_Assoc < must be updated
19691 -- In the example above, Old_Assoc is an arbitrary entity that was
19692 -- already visited for the same subtree and has a corresponding new
19693 -- entity New_Assoc. Old_Assoc was inherited by New_Itype by virtue
19694 -- of copying entities, however it must be updated to New_Assoc.
19696 Old_Assoc
:= Associated_Node_For_Itype
(Itype
);
19698 if Nkind
(Old_Assoc
) in N_Entity
then
19699 if NCT_Tables_In_Use
then
19700 New_Assoc
:= NCT_New_Entities
.Get
(Old_Assoc
);
19702 if Present
(New_Assoc
) then
19703 Set_Associated_Node_For_Itype
(New_Itype
, New_Assoc
);
19707 -- Otherwise the associated node denotes a node. Postpone the update
19708 -- until Phase 2 when the node is replicated. Establish the following
19709 -- mapping within table NCT_Pending_Itypes:
19711 -- Old_Assoc -> (New_Type, ...)
19714 Add_Pending_Itype
(Old_Assoc
, New_Itype
);
19717 -- Deal with the semantic fields of itypes. The fields are visited
19718 -- because they may mention entities that reside within the subtree
19721 Visit_Semantic_Fields
(Itype
);
19728 procedure Visit_List
(List
: List_Id
) is
19732 -- Note that the element of a syntactic list is always a node, never
19733 -- an entity or itype, hence the call to Visit_Node.
19735 if Present
(List
) then
19736 Elmt
:= First
(List
);
19737 while Present
(Elmt
) loop
19749 procedure Visit_Node
(N
: Node_Or_Entity_Id
) is
19751 pragma Assert
(Nkind
(N
) not in N_Entity
);
19753 if Nkind
(N
) = N_Expression_With_Actions
then
19754 EWA_Level
:= EWA_Level
+ 1;
19756 elsif EWA_Level
> 0
19757 and then Nkind_In
(N
, N_Block_Statement
,
19759 N_Subprogram_Declaration
)
19761 EWA_Inner_Scope_Level
:= EWA_Inner_Scope_Level
+ 1;
19765 (Field
=> Field1
(N
),
19769 (Field
=> Field2
(N
),
19773 (Field
=> Field3
(N
),
19777 (Field
=> Field4
(N
),
19781 (Field
=> Field5
(N
),
19785 and then Nkind_In
(N
, N_Block_Statement
,
19787 N_Subprogram_Declaration
)
19789 EWA_Inner_Scope_Level
:= EWA_Inner_Scope_Level
- 1;
19791 elsif Nkind
(N
) = N_Expression_With_Actions
then
19792 EWA_Level
:= EWA_Level
- 1;
19796 ---------------------------
19797 -- Visit_Semantic_Fields --
19798 ---------------------------
19800 procedure Visit_Semantic_Fields
(Id
: Entity_Id
) is
19802 pragma Assert
(Nkind
(Id
) in N_Entity
);
19804 -- Discriminant_Constraint
19806 if Has_Discriminants
(Base_Type
(Id
)) then
19808 (Field
=> Union_Id
(Discriminant_Constraint
(Id
)),
19815 (Field
=> Union_Id
(Etype
(Id
)),
19819 -- Packed_Array_Impl_Type
19821 if Is_Array_Type
(Id
) then
19822 if Present
(First_Index
(Id
)) then
19824 (Field
=> Union_Id
(List_Containing
(First_Index
(Id
))),
19828 if Is_Packed
(Id
) then
19830 (Field
=> Union_Id
(Packed_Array_Impl_Type
(Id
)),
19837 if Is_Discrete_Type
(Id
) then
19839 (Field
=> Union_Id
(Scalar_Range
(Id
)),
19842 end Visit_Semantic_Fields
;
19844 -- Start of processing for New_Copy_Tree
19847 -- Routine New_Copy_Tree performs a deep copy of a subtree by creating
19848 -- shallow copies for each node within, and then updating the child and
19849 -- parent pointers accordingly. This process is straightforward, however
19850 -- the routine must deal with the following complications:
19852 -- * Entities defined within N_Expression_With_Actions nodes must be
19853 -- replicated rather than shared to avoid introducing two identical
19854 -- symbols within the same scope. Note that no other expression can
19855 -- currently define entities.
19858 -- Source_Low : ...;
19859 -- Source_High : ...;
19861 -- <reference to Source_Low>
19862 -- <reference to Source_High>
19865 -- New_Copy_Tree handles this case by first creating new entities
19866 -- and then updating all existing references to point to these new
19873 -- <reference to New_Low>
19874 -- <reference to New_High>
19877 -- * Itypes defined within the subtree must be replicated to avoid any
19878 -- dependencies on invalid or inaccessible data.
19880 -- subtype Source_Itype is ... range Source_Low .. Source_High;
19882 -- New_Copy_Tree handles this case by first creating a new itype in
19883 -- the same fashion as entities, and then updating various relevant
19886 -- subtype New_Itype is ... range New_Low .. New_High;
19888 -- * The Associated_Node_For_Itype field of itypes must be updated to
19889 -- reference the proper replicated entity or node.
19891 -- * Semantic fields of entities such as Etype and Scope must be
19892 -- updated to reference the proper replicated entities.
19894 -- * Semantic fields of nodes such as First_Real_Statement must be
19895 -- updated to reference the proper replicated nodes.
19897 -- To meet all these demands, routine New_Copy_Tree is split into two
19900 -- Phase 1 traverses the tree in order to locate entities and itypes
19901 -- defined within the subtree. New entities are generated and saved in
19902 -- table NCT_New_Entities. The semantic fields of all new entities and
19903 -- itypes are then updated accordingly.
19905 -- Phase 2 traverses the tree in order to replicate each node. Various
19906 -- semantic fields of nodes and entities are updated accordingly.
19908 -- Preparatory phase. Clear the contents of tables NCT_New_Entities and
19909 -- NCT_Pending_Itypes in case a previous call to New_Copy_Tree left some
19912 if NCT_Tables_In_Use
then
19913 NCT_Tables_In_Use
:= False;
19915 NCT_New_Entities
.Reset
;
19916 NCT_Pending_Itypes
.Reset
;
19919 -- Populate tables NCT_New_Entities and NCT_Pending_Itypes with data
19920 -- supplied by a linear entity map. The tables offer faster access to
19923 Build_NCT_Tables
(Map
);
19925 -- Execute Phase 1. Traverse the subtree and generate new entities for
19926 -- the following cases:
19928 -- * An entity defined within an N_Expression_With_Actions node
19930 -- * An itype referenced within the subtree where the associated node
19931 -- is also in the subtree.
19933 -- All new entities are accessible via table NCT_New_Entities, which
19934 -- contains mappings of the form:
19936 -- Old_Entity -> New_Entity
19937 -- Old_Itype -> New_Itype
19939 -- In addition, the associated nodes of all new itypes are mapped in
19940 -- table NCT_Pending_Itypes:
19942 -- Assoc_Nod -> (New_Itype1, New_Itype2, .., New_ItypeN)
19944 Visit_Any_Node
(Source
);
19946 -- Update the semantic attributes of all new entities generated during
19947 -- Phase 1 before starting Phase 2. The updates could be performed in
19948 -- routine Corresponding_Entity, however this may cause the same entity
19949 -- to be updated multiple times, effectively generating useless nodes.
19950 -- Keeping the updates separates from Phase 2 ensures that only one set
19951 -- of attributes is generated for an entity at any one time.
19953 Update_New_Entities
(Map
);
19955 -- Execute Phase 2. Replicate the source subtree one node at a time.
19956 -- The following transformations take place:
19958 -- * References to entities and itypes are updated to refer to the
19959 -- new entities and itypes generated during Phase 1.
19961 -- * All Associated_Node_For_Itype attributes of itypes are updated
19962 -- to refer to the new replicated Associated_Node_For_Itype.
19964 return Copy_Node_With_Replacement
(Source
);
19967 -------------------------
19968 -- New_External_Entity --
19969 -------------------------
19971 function New_External_Entity
19972 (Kind
: Entity_Kind
;
19973 Scope_Id
: Entity_Id
;
19974 Sloc_Value
: Source_Ptr
;
19975 Related_Id
: Entity_Id
;
19976 Suffix
: Character;
19977 Suffix_Index
: Nat
:= 0;
19978 Prefix
: Character := ' ') return Entity_Id
19980 N
: constant Entity_Id
:=
19981 Make_Defining_Identifier
(Sloc_Value
,
19983 (Chars
(Related_Id
), Suffix
, Suffix_Index
, Prefix
));
19986 Set_Ekind
(N
, Kind
);
19987 Set_Is_Internal
(N
, True);
19988 Append_Entity
(N
, Scope_Id
);
19989 Set_Public_Status
(N
);
19991 if Kind
in Type_Kind
then
19992 Init_Size_Align
(N
);
19996 end New_External_Entity
;
19998 -------------------------
19999 -- New_Internal_Entity --
20000 -------------------------
20002 function New_Internal_Entity
20003 (Kind
: Entity_Kind
;
20004 Scope_Id
: Entity_Id
;
20005 Sloc_Value
: Source_Ptr
;
20006 Id_Char
: Character) return Entity_Id
20008 N
: constant Entity_Id
:= Make_Temporary
(Sloc_Value
, Id_Char
);
20011 Set_Ekind
(N
, Kind
);
20012 Set_Is_Internal
(N
, True);
20013 Append_Entity
(N
, Scope_Id
);
20015 if Kind
in Type_Kind
then
20016 Init_Size_Align
(N
);
20020 end New_Internal_Entity
;
20026 function Next_Actual
(Actual_Id
: Node_Id
) return Node_Id
is
20030 -- If we are pointing at a positional parameter, it is a member of a
20031 -- node list (the list of parameters), and the next parameter is the
20032 -- next node on the list, unless we hit a parameter association, then
20033 -- we shift to using the chain whose head is the First_Named_Actual in
20034 -- the parent, and then is threaded using the Next_Named_Actual of the
20035 -- Parameter_Association. All this fiddling is because the original node
20036 -- list is in the textual call order, and what we need is the
20037 -- declaration order.
20039 if Is_List_Member
(Actual_Id
) then
20040 N
:= Next
(Actual_Id
);
20042 if Nkind
(N
) = N_Parameter_Association
then
20044 -- In case of a build-in-place call, the call will no longer be a
20045 -- call; it will have been rewritten.
20047 if Nkind_In
(Parent
(Actual_Id
), N_Entry_Call_Statement
,
20049 N_Procedure_Call_Statement
)
20051 return First_Named_Actual
(Parent
(Actual_Id
));
20060 return Next_Named_Actual
(Parent
(Actual_Id
));
20064 procedure Next_Actual
(Actual_Id
: in out Node_Id
) is
20066 Actual_Id
:= Next_Actual
(Actual_Id
);
20073 function Next_Global
(Node
: Node_Id
) return Node_Id
is
20075 -- The global item may either be in a list, or by itself, in which case
20076 -- there is no next global item with the same mode.
20078 if Is_List_Member
(Node
) then
20079 return Next
(Node
);
20085 procedure Next_Global
(Node
: in out Node_Id
) is
20087 Node
:= Next_Global
(Node
);
20090 ----------------------------------
20091 -- New_Requires_Transient_Scope --
20092 ----------------------------------
20094 function New_Requires_Transient_Scope
(Id
: Entity_Id
) return Boolean is
20095 function Caller_Known_Size_Record
(Typ
: Entity_Id
) return Boolean;
20096 -- This is called for untagged records and protected types, with
20097 -- nondefaulted discriminants. Returns True if the size of function
20098 -- results is known at the call site, False otherwise. Returns False
20099 -- if there is a variant part that depends on the discriminants of
20100 -- this type, or if there is an array constrained by the discriminants
20101 -- of this type. ???Currently, this is overly conservative (the array
20102 -- could be nested inside some other record that is constrained by
20103 -- nondiscriminants). That is, the recursive calls are too conservative.
20105 function Large_Max_Size_Mutable
(Typ
: Entity_Id
) return Boolean;
20106 -- Returns True if Typ is a nonlimited record with defaulted
20107 -- discriminants whose max size makes it unsuitable for allocating on
20108 -- the primary stack.
20110 ------------------------------
20111 -- Caller_Known_Size_Record --
20112 ------------------------------
20114 function Caller_Known_Size_Record
(Typ
: Entity_Id
) return Boolean is
20115 pragma Assert
(Typ
= Underlying_Type
(Typ
));
20118 if Has_Variant_Part
(Typ
) and then not Is_Definite_Subtype
(Typ
) then
20126 Comp
:= First_Entity
(Typ
);
20127 while Present
(Comp
) loop
20129 -- Only look at E_Component entities. No need to look at
20130 -- E_Discriminant entities, and we must ignore internal
20131 -- subtypes generated for constrained components.
20133 if Ekind
(Comp
) = E_Component
then
20135 Comp_Type
: constant Entity_Id
:=
20136 Underlying_Type
(Etype
(Comp
));
20139 if Is_Record_Type
(Comp_Type
)
20141 Is_Protected_Type
(Comp_Type
)
20143 if not Caller_Known_Size_Record
(Comp_Type
) then
20147 elsif Is_Array_Type
(Comp_Type
) then
20148 if Size_Depends_On_Discriminant
(Comp_Type
) then
20155 Next_Entity
(Comp
);
20160 end Caller_Known_Size_Record
;
20162 ------------------------------
20163 -- Large_Max_Size_Mutable --
20164 ------------------------------
20166 function Large_Max_Size_Mutable
(Typ
: Entity_Id
) return Boolean is
20167 pragma Assert
(Typ
= Underlying_Type
(Typ
));
20169 function Is_Large_Discrete_Type
(T
: Entity_Id
) return Boolean;
20170 -- Returns true if the discrete type T has a large range
20172 ----------------------------
20173 -- Is_Large_Discrete_Type --
20174 ----------------------------
20176 function Is_Large_Discrete_Type
(T
: Entity_Id
) return Boolean is
20177 Threshold
: constant Int
:= 16;
20178 -- Arbitrary threshold above which we consider it "large". We want
20179 -- a fairly large threshold, because these large types really
20180 -- shouldn't have default discriminants in the first place, in
20184 return UI_To_Int
(RM_Size
(T
)) > Threshold
;
20185 end Is_Large_Discrete_Type
;
20187 -- Start of processing for Large_Max_Size_Mutable
20190 if Is_Record_Type
(Typ
)
20191 and then not Is_Limited_View
(Typ
)
20192 and then Has_Defaulted_Discriminants
(Typ
)
20194 -- Loop through the components, looking for an array whose upper
20195 -- bound(s) depends on discriminants, where both the subtype of
20196 -- the discriminant and the index subtype are too large.
20202 Comp
:= First_Entity
(Typ
);
20203 while Present
(Comp
) loop
20204 if Ekind
(Comp
) = E_Component
then
20206 Comp_Type
: constant Entity_Id
:=
20207 Underlying_Type
(Etype
(Comp
));
20214 if Is_Array_Type
(Comp_Type
) then
20215 Indx
:= First_Index
(Comp_Type
);
20217 while Present
(Indx
) loop
20218 Ityp
:= Etype
(Indx
);
20219 Hi
:= Type_High_Bound
(Ityp
);
20221 if Nkind
(Hi
) = N_Identifier
20222 and then Ekind
(Entity
(Hi
)) = E_Discriminant
20223 and then Is_Large_Discrete_Type
(Ityp
)
20224 and then Is_Large_Discrete_Type
20225 (Etype
(Entity
(Hi
)))
20236 Next_Entity
(Comp
);
20242 end Large_Max_Size_Mutable
;
20244 -- Local declarations
20246 Typ
: constant Entity_Id
:= Underlying_Type
(Id
);
20248 -- Start of processing for New_Requires_Transient_Scope
20251 -- This is a private type which is not completed yet. This can only
20252 -- happen in a default expression (of a formal parameter or of a
20253 -- record component). Do not expand transient scope in this case.
20258 -- Do not expand transient scope for non-existent procedure return or
20259 -- string literal types.
20261 elsif Typ
= Standard_Void_Type
20262 or else Ekind
(Typ
) = E_String_Literal_Subtype
20266 -- If Typ is a generic formal incomplete type, then we want to look at
20267 -- the actual type.
20269 elsif Ekind
(Typ
) = E_Record_Subtype
20270 and then Present
(Cloned_Subtype
(Typ
))
20272 return New_Requires_Transient_Scope
(Cloned_Subtype
(Typ
));
20274 -- Functions returning specific tagged types may dispatch on result, so
20275 -- their returned value is allocated on the secondary stack, even in the
20276 -- definite case. We must treat nondispatching functions the same way,
20277 -- because access-to-function types can point at both, so the calling
20278 -- conventions must be compatible. Is_Tagged_Type includes controlled
20279 -- types and class-wide types. Controlled type temporaries need
20282 -- ???It's not clear why we need to return noncontrolled types with
20283 -- controlled components on the secondary stack.
20285 elsif Is_Tagged_Type
(Typ
) or else Has_Controlled_Component
(Typ
) then
20288 -- Untagged definite subtypes are known size. This includes all
20289 -- elementary [sub]types. Tasks are known size even if they have
20290 -- discriminants. So we return False here, with one exception:
20291 -- For a type like:
20292 -- type T (Last : Natural := 0) is
20293 -- X : String (1 .. Last);
20295 -- we return True. That's because for "P(F(...));", where F returns T,
20296 -- we don't know the size of the result at the call site, so if we
20297 -- allocated it on the primary stack, we would have to allocate the
20298 -- maximum size, which is way too big.
20300 elsif Is_Definite_Subtype
(Typ
) or else Is_Task_Type
(Typ
) then
20301 return Large_Max_Size_Mutable
(Typ
);
20303 -- Indefinite (discriminated) untagged record or protected type
20305 elsif Is_Record_Type
(Typ
) or else Is_Protected_Type
(Typ
) then
20306 return not Caller_Known_Size_Record
(Typ
);
20308 -- Unconstrained array
20311 pragma Assert
(Is_Array_Type
(Typ
) and not Is_Definite_Subtype
(Typ
));
20314 end New_Requires_Transient_Scope
;
20316 --------------------------
20317 -- No_Heap_Finalization --
20318 --------------------------
20320 function No_Heap_Finalization
(Typ
: Entity_Id
) return Boolean is
20322 if Ekind_In
(Typ
, E_Access_Type
, E_General_Access_Type
)
20323 and then Is_Library_Level_Entity
(Typ
)
20325 -- A global No_Heap_Finalization pragma applies to all library-level
20326 -- named access-to-object types.
20328 if Present
(No_Heap_Finalization_Pragma
) then
20331 -- The library-level named access-to-object type itself is subject to
20332 -- pragma No_Heap_Finalization.
20334 elsif Present
(Get_Pragma
(Typ
, Pragma_No_Heap_Finalization
)) then
20340 end No_Heap_Finalization
;
20342 -----------------------
20343 -- Normalize_Actuals --
20344 -----------------------
20346 -- Chain actuals according to formals of subprogram. If there are no named
20347 -- associations, the chain is simply the list of Parameter Associations,
20348 -- since the order is the same as the declaration order. If there are named
20349 -- associations, then the First_Named_Actual field in the N_Function_Call
20350 -- or N_Procedure_Call_Statement node points to the Parameter_Association
20351 -- node for the parameter that comes first in declaration order. The
20352 -- remaining named parameters are then chained in declaration order using
20353 -- Next_Named_Actual.
20355 -- This routine also verifies that the number of actuals is compatible with
20356 -- the number and default values of formals, but performs no type checking
20357 -- (type checking is done by the caller).
20359 -- If the matching succeeds, Success is set to True and the caller proceeds
20360 -- with type-checking. If the match is unsuccessful, then Success is set to
20361 -- False, and the caller attempts a different interpretation, if there is
20364 -- If the flag Report is on, the call is not overloaded, and a failure to
20365 -- match can be reported here, rather than in the caller.
20367 procedure Normalize_Actuals
20371 Success
: out Boolean)
20373 Actuals
: constant List_Id
:= Parameter_Associations
(N
);
20374 Actual
: Node_Id
:= Empty
;
20375 Formal
: Entity_Id
;
20376 Last
: Node_Id
:= Empty
;
20377 First_Named
: Node_Id
:= Empty
;
20380 Formals_To_Match
: Integer := 0;
20381 Actuals_To_Match
: Integer := 0;
20383 procedure Chain
(A
: Node_Id
);
20384 -- Add named actual at the proper place in the list, using the
20385 -- Next_Named_Actual link.
20387 function Reporting
return Boolean;
20388 -- Determines if an error is to be reported. To report an error, we
20389 -- need Report to be True, and also we do not report errors caused
20390 -- by calls to init procs that occur within other init procs. Such
20391 -- errors must always be cascaded errors, since if all the types are
20392 -- declared correctly, the compiler will certainly build decent calls.
20398 procedure Chain
(A
: Node_Id
) is
20402 -- Call node points to first actual in list
20404 Set_First_Named_Actual
(N
, Explicit_Actual_Parameter
(A
));
20407 Set_Next_Named_Actual
(Last
, Explicit_Actual_Parameter
(A
));
20411 Set_Next_Named_Actual
(Last
, Empty
);
20418 function Reporting
return Boolean is
20423 elsif not Within_Init_Proc
then
20426 elsif Is_Init_Proc
(Entity
(Name
(N
))) then
20434 -- Start of processing for Normalize_Actuals
20437 if Is_Access_Type
(S
) then
20439 -- The name in the call is a function call that returns an access
20440 -- to subprogram. The designated type has the list of formals.
20442 Formal
:= First_Formal
(Designated_Type
(S
));
20444 Formal
:= First_Formal
(S
);
20447 while Present
(Formal
) loop
20448 Formals_To_Match
:= Formals_To_Match
+ 1;
20449 Next_Formal
(Formal
);
20452 -- Find if there is a named association, and verify that no positional
20453 -- associations appear after named ones.
20455 if Present
(Actuals
) then
20456 Actual
:= First
(Actuals
);
20459 while Present
(Actual
)
20460 and then Nkind
(Actual
) /= N_Parameter_Association
20462 Actuals_To_Match
:= Actuals_To_Match
+ 1;
20466 if No
(Actual
) and Actuals_To_Match
= Formals_To_Match
then
20468 -- Most common case: positional notation, no defaults
20473 elsif Actuals_To_Match
> Formals_To_Match
then
20475 -- Too many actuals: will not work
20478 if Is_Entity_Name
(Name
(N
)) then
20479 Error_Msg_N
("too many arguments in call to&", Name
(N
));
20481 Error_Msg_N
("too many arguments in call", N
);
20489 First_Named
:= Actual
;
20491 while Present
(Actual
) loop
20492 if Nkind
(Actual
) /= N_Parameter_Association
then
20494 ("positional parameters not allowed after named ones", Actual
);
20499 Actuals_To_Match
:= Actuals_To_Match
+ 1;
20505 if Present
(Actuals
) then
20506 Actual
:= First
(Actuals
);
20509 Formal
:= First_Formal
(S
);
20510 while Present
(Formal
) loop
20512 -- Match the formals in order. If the corresponding actual is
20513 -- positional, nothing to do. Else scan the list of named actuals
20514 -- to find the one with the right name.
20516 if Present
(Actual
)
20517 and then Nkind
(Actual
) /= N_Parameter_Association
20520 Actuals_To_Match
:= Actuals_To_Match
- 1;
20521 Formals_To_Match
:= Formals_To_Match
- 1;
20524 -- For named parameters, search the list of actuals to find
20525 -- one that matches the next formal name.
20527 Actual
:= First_Named
;
20529 while Present
(Actual
) loop
20530 if Chars
(Selector_Name
(Actual
)) = Chars
(Formal
) then
20533 Actuals_To_Match
:= Actuals_To_Match
- 1;
20534 Formals_To_Match
:= Formals_To_Match
- 1;
20542 if Ekind
(Formal
) /= E_In_Parameter
20543 or else No
(Default_Value
(Formal
))
20546 if (Comes_From_Source
(S
)
20547 or else Sloc
(S
) = Standard_Location
)
20548 and then Is_Overloadable
(S
)
20552 Nkind_In
(Parent
(N
), N_Procedure_Call_Statement
,
20554 N_Parameter_Association
)
20555 and then Ekind
(S
) /= E_Function
20557 Set_Etype
(N
, Etype
(S
));
20560 Error_Msg_Name_1
:= Chars
(S
);
20561 Error_Msg_Sloc
:= Sloc
(S
);
20563 ("missing argument for parameter & "
20564 & "in call to % declared #", N
, Formal
);
20567 elsif Is_Overloadable
(S
) then
20568 Error_Msg_Name_1
:= Chars
(S
);
20570 -- Point to type derivation that generated the
20573 Error_Msg_Sloc
:= Sloc
(Parent
(S
));
20576 ("missing argument for parameter & "
20577 & "in call to % (inherited) #", N
, Formal
);
20581 ("missing argument for parameter &", N
, Formal
);
20589 Formals_To_Match
:= Formals_To_Match
- 1;
20594 Next_Formal
(Formal
);
20597 if Formals_To_Match
= 0 and then Actuals_To_Match
= 0 then
20604 -- Find some superfluous named actual that did not get
20605 -- attached to the list of associations.
20607 Actual
:= First
(Actuals
);
20608 while Present
(Actual
) loop
20609 if Nkind
(Actual
) = N_Parameter_Association
20610 and then Actual
/= Last
20611 and then No
(Next_Named_Actual
(Actual
))
20613 -- A validity check may introduce a copy of a call that
20614 -- includes an extra actual (for example for an unrelated
20615 -- accessibility check). Check that the extra actual matches
20616 -- some extra formal, which must exist already because
20617 -- subprogram must be frozen at this point.
20619 if Present
(Extra_Formals
(S
))
20620 and then not Comes_From_Source
(Actual
)
20621 and then Nkind
(Actual
) = N_Parameter_Association
20622 and then Chars
(Extra_Formals
(S
)) =
20623 Chars
(Selector_Name
(Actual
))
20628 ("unmatched actual & in call", Selector_Name
(Actual
));
20640 end Normalize_Actuals
;
20642 --------------------------------
20643 -- Note_Possible_Modification --
20644 --------------------------------
20646 procedure Note_Possible_Modification
(N
: Node_Id
; Sure
: Boolean) is
20647 Modification_Comes_From_Source
: constant Boolean :=
20648 Comes_From_Source
(Parent
(N
));
20654 -- Loop to find referenced entity, if there is one
20660 if Is_Entity_Name
(Exp
) then
20661 Ent
:= Entity
(Exp
);
20663 -- If the entity is missing, it is an undeclared identifier,
20664 -- and there is nothing to annotate.
20670 elsif Nkind
(Exp
) = N_Explicit_Dereference
then
20672 P
: constant Node_Id
:= Prefix
(Exp
);
20675 -- In formal verification mode, keep track of all reads and
20676 -- writes through explicit dereferences.
20678 if GNATprove_Mode
then
20679 SPARK_Specific
.Generate_Dereference
(N
, 'm');
20682 if Nkind
(P
) = N_Selected_Component
20683 and then Present
(Entry_Formal
(Entity
(Selector_Name
(P
))))
20685 -- Case of a reference to an entry formal
20687 Ent
:= Entry_Formal
(Entity
(Selector_Name
(P
)));
20689 elsif Nkind
(P
) = N_Identifier
20690 and then Nkind
(Parent
(Entity
(P
))) = N_Object_Declaration
20691 and then Present
(Expression
(Parent
(Entity
(P
))))
20692 and then Nkind
(Expression
(Parent
(Entity
(P
)))) =
20695 -- Case of a reference to a value on which side effects have
20698 Exp
:= Prefix
(Expression
(Parent
(Entity
(P
))));
20706 elsif Nkind_In
(Exp
, N_Type_Conversion
,
20707 N_Unchecked_Type_Conversion
)
20709 Exp
:= Expression
(Exp
);
20712 elsif Nkind_In
(Exp
, N_Slice
,
20713 N_Indexed_Component
,
20714 N_Selected_Component
)
20716 -- Special check, if the prefix is an access type, then return
20717 -- since we are modifying the thing pointed to, not the prefix.
20718 -- When we are expanding, most usually the prefix is replaced
20719 -- by an explicit dereference, and this test is not needed, but
20720 -- in some cases (notably -gnatc mode and generics) when we do
20721 -- not do full expansion, we need this special test.
20723 if Is_Access_Type
(Etype
(Prefix
(Exp
))) then
20726 -- Otherwise go to prefix and keep going
20729 Exp
:= Prefix
(Exp
);
20733 -- All other cases, not a modification
20739 -- Now look for entity being referenced
20741 if Present
(Ent
) then
20742 if Is_Object
(Ent
) then
20743 if Comes_From_Source
(Exp
)
20744 or else Modification_Comes_From_Source
20746 -- Give warning if pragma unmodified is given and we are
20747 -- sure this is a modification.
20749 if Has_Pragma_Unmodified
(Ent
) and then Sure
then
20751 -- Note that the entity may be present only as a result
20752 -- of pragma Unused.
20754 if Has_Pragma_Unused
(Ent
) then
20755 Error_Msg_NE
("??pragma Unused given for &!", N
, Ent
);
20758 ("??pragma Unmodified given for &!", N
, Ent
);
20762 Set_Never_Set_In_Source
(Ent
, False);
20765 Set_Is_True_Constant
(Ent
, False);
20766 Set_Current_Value
(Ent
, Empty
);
20767 Set_Is_Known_Null
(Ent
, False);
20769 if not Can_Never_Be_Null
(Ent
) then
20770 Set_Is_Known_Non_Null
(Ent
, False);
20773 -- Follow renaming chain
20775 if (Ekind
(Ent
) = E_Variable
or else Ekind
(Ent
) = E_Constant
)
20776 and then Present
(Renamed_Object
(Ent
))
20778 Exp
:= Renamed_Object
(Ent
);
20780 -- If the entity is the loop variable in an iteration over
20781 -- a container, retrieve container expression to indicate
20782 -- possible modification.
20784 if Present
(Related_Expression
(Ent
))
20785 and then Nkind
(Parent
(Related_Expression
(Ent
))) =
20786 N_Iterator_Specification
20788 Exp
:= Original_Node
(Related_Expression
(Ent
));
20793 -- The expression may be the renaming of a subcomponent of an
20794 -- array or container. The assignment to the subcomponent is
20795 -- a modification of the container.
20797 elsif Comes_From_Source
(Original_Node
(Exp
))
20798 and then Nkind_In
(Original_Node
(Exp
), N_Selected_Component
,
20799 N_Indexed_Component
)
20801 Exp
:= Prefix
(Original_Node
(Exp
));
20805 -- Generate a reference only if the assignment comes from
20806 -- source. This excludes, for example, calls to a dispatching
20807 -- assignment operation when the left-hand side is tagged. In
20808 -- GNATprove mode, we need those references also on generated
20809 -- code, as these are used to compute the local effects of
20812 if Modification_Comes_From_Source
or GNATprove_Mode
then
20813 Generate_Reference
(Ent
, Exp
, 'm');
20815 -- If the target of the assignment is the bound variable
20816 -- in an iterator, indicate that the corresponding array
20817 -- or container is also modified.
20819 if Ada_Version
>= Ada_2012
20820 and then Nkind
(Parent
(Ent
)) = N_Iterator_Specification
20823 Domain
: constant Node_Id
:= Name
(Parent
(Ent
));
20826 -- TBD : in the full version of the construct, the
20827 -- domain of iteration can be given by an expression.
20829 if Is_Entity_Name
(Domain
) then
20830 Generate_Reference
(Entity
(Domain
), Exp
, 'm');
20831 Set_Is_True_Constant
(Entity
(Domain
), False);
20832 Set_Never_Set_In_Source
(Entity
(Domain
), False);
20841 -- If we are sure this is a modification from source, and we know
20842 -- this modifies a constant, then give an appropriate warning.
20845 and then Modification_Comes_From_Source
20846 and then Overlays_Constant
(Ent
)
20847 and then Address_Clause_Overlay_Warnings
20850 Addr
: constant Node_Id
:= Address_Clause
(Ent
);
20855 Find_Overlaid_Entity
(Addr
, O_Ent
, Off
);
20857 Error_Msg_Sloc
:= Sloc
(Addr
);
20859 ("??constant& may be modified via address clause#",
20870 end Note_Possible_Modification
;
20876 function Null_Status
(N
: Node_Id
) return Null_Status_Kind
is
20877 function Is_Null_Excluding_Def
(Def
: Node_Id
) return Boolean;
20878 -- Determine whether definition Def carries a null exclusion
20880 function Null_Status_Of_Entity
(Id
: Entity_Id
) return Null_Status_Kind
;
20881 -- Determine the null status of arbitrary entity Id
20883 function Null_Status_Of_Type
(Typ
: Entity_Id
) return Null_Status_Kind
;
20884 -- Determine the null status of type Typ
20886 ---------------------------
20887 -- Is_Null_Excluding_Def --
20888 ---------------------------
20890 function Is_Null_Excluding_Def
(Def
: Node_Id
) return Boolean is
20893 Nkind_In
(Def
, N_Access_Definition
,
20894 N_Access_Function_Definition
,
20895 N_Access_Procedure_Definition
,
20896 N_Access_To_Object_Definition
,
20897 N_Component_Definition
,
20898 N_Derived_Type_Definition
)
20899 and then Null_Exclusion_Present
(Def
);
20900 end Is_Null_Excluding_Def
;
20902 ---------------------------
20903 -- Null_Status_Of_Entity --
20904 ---------------------------
20906 function Null_Status_Of_Entity
20907 (Id
: Entity_Id
) return Null_Status_Kind
20909 Decl
: constant Node_Id
:= Declaration_Node
(Id
);
20913 -- The value of an imported or exported entity may be set externally
20914 -- regardless of a null exclusion. As a result, the value cannot be
20915 -- determined statically.
20917 if Is_Imported
(Id
) or else Is_Exported
(Id
) then
20920 elsif Nkind_In
(Decl
, N_Component_Declaration
,
20921 N_Discriminant_Specification
,
20922 N_Formal_Object_Declaration
,
20923 N_Object_Declaration
,
20924 N_Object_Renaming_Declaration
,
20925 N_Parameter_Specification
)
20927 -- A component declaration yields a non-null value when either
20928 -- its component definition or access definition carries a null
20931 if Nkind
(Decl
) = N_Component_Declaration
then
20932 Def
:= Component_Definition
(Decl
);
20934 if Is_Null_Excluding_Def
(Def
) then
20935 return Is_Non_Null
;
20938 Def
:= Access_Definition
(Def
);
20940 if Present
(Def
) and then Is_Null_Excluding_Def
(Def
) then
20941 return Is_Non_Null
;
20944 -- A formal object declaration yields a non-null value if its
20945 -- access definition carries a null exclusion. If the object is
20946 -- default initialized, then the value depends on the expression.
20948 elsif Nkind
(Decl
) = N_Formal_Object_Declaration
then
20949 Def
:= Access_Definition
(Decl
);
20951 if Present
(Def
) and then Is_Null_Excluding_Def
(Def
) then
20952 return Is_Non_Null
;
20955 -- A constant may yield a null or non-null value depending on its
20956 -- initialization expression.
20958 elsif Ekind
(Id
) = E_Constant
then
20959 return Null_Status
(Constant_Value
(Id
));
20961 -- The construct yields a non-null value when it has a null
20964 elsif Null_Exclusion_Present
(Decl
) then
20965 return Is_Non_Null
;
20967 -- An object renaming declaration yields a non-null value if its
20968 -- access definition carries a null exclusion. Otherwise the value
20969 -- depends on the renamed name.
20971 elsif Nkind
(Decl
) = N_Object_Renaming_Declaration
then
20972 Def
:= Access_Definition
(Decl
);
20974 if Present
(Def
) and then Is_Null_Excluding_Def
(Def
) then
20975 return Is_Non_Null
;
20978 return Null_Status
(Name
(Decl
));
20983 -- At this point the declaration of the entity does not carry a null
20984 -- exclusion and lacks an initialization expression. Check the status
20987 return Null_Status_Of_Type
(Etype
(Id
));
20988 end Null_Status_Of_Entity
;
20990 -------------------------
20991 -- Null_Status_Of_Type --
20992 -------------------------
20994 function Null_Status_Of_Type
(Typ
: Entity_Id
) return Null_Status_Kind
is
20999 -- Traverse the type chain looking for types with null exclusion
21002 while Present
(Curr
) and then Etype
(Curr
) /= Curr
loop
21003 Decl
:= Parent
(Curr
);
21005 -- Guard against itypes which do not always have declarations. A
21006 -- type yields a non-null value if it carries a null exclusion.
21008 if Present
(Decl
) then
21009 if Nkind
(Decl
) = N_Full_Type_Declaration
21010 and then Is_Null_Excluding_Def
(Type_Definition
(Decl
))
21012 return Is_Non_Null
;
21014 elsif Nkind
(Decl
) = N_Subtype_Declaration
21015 and then Null_Exclusion_Present
(Decl
)
21017 return Is_Non_Null
;
21021 Curr
:= Etype
(Curr
);
21024 -- The type chain does not contain any null excluding types
21027 end Null_Status_Of_Type
;
21029 -- Start of processing for Null_Status
21032 -- An allocator always creates a non-null value
21034 if Nkind
(N
) = N_Allocator
then
21035 return Is_Non_Null
;
21037 -- Taking the 'Access of something yields a non-null value
21039 elsif Nkind
(N
) = N_Attribute_Reference
21040 and then Nam_In
(Attribute_Name
(N
), Name_Access
,
21041 Name_Unchecked_Access
,
21042 Name_Unrestricted_Access
)
21044 return Is_Non_Null
;
21046 -- "null" yields null
21048 elsif Nkind
(N
) = N_Null
then
21051 -- Check the status of the operand of a type conversion
21053 elsif Nkind
(N
) = N_Type_Conversion
then
21054 return Null_Status
(Expression
(N
));
21056 -- The input denotes a reference to an entity. Determine whether the
21057 -- entity or its type yields a null or non-null value.
21059 elsif Is_Entity_Name
(N
) and then Present
(Entity
(N
)) then
21060 return Null_Status_Of_Entity
(Entity
(N
));
21063 -- Otherwise it is not possible to determine the null status of the
21064 -- subexpression at compile time without resorting to simple flow
21070 --------------------------------------
21071 -- Null_To_Null_Address_Convert_OK --
21072 --------------------------------------
21074 function Null_To_Null_Address_Convert_OK
21076 Typ
: Entity_Id
:= Empty
) return Boolean
21079 if not Relaxed_RM_Semantics
then
21083 if Nkind
(N
) = N_Null
then
21084 return Present
(Typ
) and then Is_Descendant_Of_Address
(Typ
);
21086 elsif Nkind_In
(N
, N_Op_Eq
, N_Op_Ge
, N_Op_Gt
, N_Op_Le
, N_Op_Lt
, N_Op_Ne
)
21089 L
: constant Node_Id
:= Left_Opnd
(N
);
21090 R
: constant Node_Id
:= Right_Opnd
(N
);
21093 -- We check the Etype of the complementary operand since the
21094 -- N_Null node is not decorated at this stage.
21097 ((Nkind
(L
) = N_Null
21098 and then Is_Descendant_Of_Address
(Etype
(R
)))
21100 (Nkind
(R
) = N_Null
21101 and then Is_Descendant_Of_Address
(Etype
(L
))));
21106 end Null_To_Null_Address_Convert_OK
;
21108 ---------------------------------
21109 -- Number_Of_Elements_In_Array --
21110 ---------------------------------
21112 function Number_Of_Elements_In_Array
(T
: Entity_Id
) return Int
is
21120 pragma Assert
(Is_Array_Type
(T
));
21122 Indx
:= First_Index
(T
);
21123 while Present
(Indx
) loop
21124 Typ
:= Underlying_Type
(Etype
(Indx
));
21126 -- Never look at junk bounds of a generic type
21128 if Is_Generic_Type
(Typ
) then
21132 -- Check the array bounds are known at compile time and return zero
21133 -- if they are not.
21135 Low
:= Type_Low_Bound
(Typ
);
21136 High
:= Type_High_Bound
(Typ
);
21138 if not Compile_Time_Known_Value
(Low
) then
21140 elsif not Compile_Time_Known_Value
(High
) then
21144 Num
* UI_To_Int
((Expr_Value
(High
) - Expr_Value
(Low
) + 1));
21151 end Number_Of_Elements_In_Array
;
21153 -------------------------
21154 -- Object_Access_Level --
21155 -------------------------
21157 -- Returns the static accessibility level of the view denoted by Obj. Note
21158 -- that the value returned is the result of a call to Scope_Depth. Only
21159 -- scope depths associated with dynamic scopes can actually be returned.
21160 -- Since only relative levels matter for accessibility checking, the fact
21161 -- that the distance between successive levels of accessibility is not
21162 -- always one is immaterial (invariant: if level(E2) is deeper than
21163 -- level(E1), then Scope_Depth(E1) < Scope_Depth(E2)).
21165 function Object_Access_Level
(Obj
: Node_Id
) return Uint
is
21166 function Is_Interface_Conversion
(N
: Node_Id
) return Boolean;
21167 -- Determine whether N is a construct of the form
21168 -- Some_Type (Operand._tag'Address)
21169 -- This construct appears in the context of dispatching calls.
21171 function Reference_To
(Obj
: Node_Id
) return Node_Id
;
21172 -- An explicit dereference is created when removing side effects from
21173 -- expressions for constraint checking purposes. In this case a local
21174 -- access type is created for it. The correct access level is that of
21175 -- the original source node. We detect this case by noting that the
21176 -- prefix of the dereference is created by an object declaration whose
21177 -- initial expression is a reference.
21179 -----------------------------
21180 -- Is_Interface_Conversion --
21181 -----------------------------
21183 function Is_Interface_Conversion
(N
: Node_Id
) return Boolean is
21185 return Nkind
(N
) = N_Unchecked_Type_Conversion
21186 and then Nkind
(Expression
(N
)) = N_Attribute_Reference
21187 and then Attribute_Name
(Expression
(N
)) = Name_Address
;
21188 end Is_Interface_Conversion
;
21194 function Reference_To
(Obj
: Node_Id
) return Node_Id
is
21195 Pref
: constant Node_Id
:= Prefix
(Obj
);
21197 if Is_Entity_Name
(Pref
)
21198 and then Nkind
(Parent
(Entity
(Pref
))) = N_Object_Declaration
21199 and then Present
(Expression
(Parent
(Entity
(Pref
))))
21200 and then Nkind
(Expression
(Parent
(Entity
(Pref
)))) = N_Reference
21202 return (Prefix
(Expression
(Parent
(Entity
(Pref
)))));
21212 -- Start of processing for Object_Access_Level
21215 if Nkind
(Obj
) = N_Defining_Identifier
21216 or else Is_Entity_Name
(Obj
)
21218 if Nkind
(Obj
) = N_Defining_Identifier
then
21224 if Is_Prival
(E
) then
21225 E
:= Prival_Link
(E
);
21228 -- If E is a type then it denotes a current instance. For this case
21229 -- we add one to the normal accessibility level of the type to ensure
21230 -- that current instances are treated as always being deeper than
21231 -- than the level of any visible named access type (see 3.10.2(21)).
21233 if Is_Type
(E
) then
21234 return Type_Access_Level
(E
) + 1;
21236 elsif Present
(Renamed_Object
(E
)) then
21237 return Object_Access_Level
(Renamed_Object
(E
));
21239 -- Similarly, if E is a component of the current instance of a
21240 -- protected type, any instance of it is assumed to be at a deeper
21241 -- level than the type. For a protected object (whose type is an
21242 -- anonymous protected type) its components are at the same level
21243 -- as the type itself.
21245 elsif not Is_Overloadable
(E
)
21246 and then Ekind
(Scope
(E
)) = E_Protected_Type
21247 and then Comes_From_Source
(Scope
(E
))
21249 return Type_Access_Level
(Scope
(E
)) + 1;
21252 -- Aliased formals of functions take their access level from the
21253 -- point of call, i.e. require a dynamic check. For static check
21254 -- purposes, this is smaller than the level of the subprogram
21255 -- itself. For procedures the aliased makes no difference.
21258 and then Is_Aliased
(E
)
21259 and then Ekind
(Scope
(E
)) = E_Function
21261 return Type_Access_Level
(Etype
(E
));
21264 return Scope_Depth
(Enclosing_Dynamic_Scope
(E
));
21268 elsif Nkind_In
(Obj
, N_Indexed_Component
, N_Selected_Component
) then
21269 if Is_Access_Type
(Etype
(Prefix
(Obj
))) then
21270 return Type_Access_Level
(Etype
(Prefix
(Obj
)));
21272 return Object_Access_Level
(Prefix
(Obj
));
21275 elsif Nkind
(Obj
) = N_Explicit_Dereference
then
21277 -- If the prefix is a selected access discriminant then we make a
21278 -- recursive call on the prefix, which will in turn check the level
21279 -- of the prefix object of the selected discriminant.
21281 -- In Ada 2012, if the discriminant has implicit dereference and
21282 -- the context is a selected component, treat this as an object of
21283 -- unknown scope (see below). This is necessary in compile-only mode;
21284 -- otherwise expansion will already have transformed the prefix into
21287 if Nkind
(Prefix
(Obj
)) = N_Selected_Component
21288 and then Ekind
(Etype
(Prefix
(Obj
))) = E_Anonymous_Access_Type
21290 Ekind
(Entity
(Selector_Name
(Prefix
(Obj
)))) = E_Discriminant
21292 (not Has_Implicit_Dereference
21293 (Entity
(Selector_Name
(Prefix
(Obj
))))
21294 or else Nkind
(Parent
(Obj
)) /= N_Selected_Component
)
21296 return Object_Access_Level
(Prefix
(Obj
));
21298 -- Detect an interface conversion in the context of a dispatching
21299 -- call. Use the original form of the conversion to find the access
21300 -- level of the operand.
21302 elsif Is_Interface
(Etype
(Obj
))
21303 and then Is_Interface_Conversion
(Prefix
(Obj
))
21304 and then Nkind
(Original_Node
(Obj
)) = N_Type_Conversion
21306 return Object_Access_Level
(Original_Node
(Obj
));
21308 elsif not Comes_From_Source
(Obj
) then
21310 Ref
: constant Node_Id
:= Reference_To
(Obj
);
21312 if Present
(Ref
) then
21313 return Object_Access_Level
(Ref
);
21315 return Type_Access_Level
(Etype
(Prefix
(Obj
)));
21320 return Type_Access_Level
(Etype
(Prefix
(Obj
)));
21323 elsif Nkind_In
(Obj
, N_Type_Conversion
, N_Unchecked_Type_Conversion
) then
21324 return Object_Access_Level
(Expression
(Obj
));
21326 elsif Nkind
(Obj
) = N_Function_Call
then
21328 -- Function results are objects, so we get either the access level of
21329 -- the function or, in the case of an indirect call, the level of the
21330 -- access-to-subprogram type. (This code is used for Ada 95, but it
21331 -- looks wrong, because it seems that we should be checking the level
21332 -- of the call itself, even for Ada 95. However, using the Ada 2005
21333 -- version of the code causes regressions in several tests that are
21334 -- compiled with -gnat95. ???)
21336 if Ada_Version
< Ada_2005
then
21337 if Is_Entity_Name
(Name
(Obj
)) then
21338 return Subprogram_Access_Level
(Entity
(Name
(Obj
)));
21340 return Type_Access_Level
(Etype
(Prefix
(Name
(Obj
))));
21343 -- For Ada 2005, the level of the result object of a function call is
21344 -- defined to be the level of the call's innermost enclosing master.
21345 -- We determine that by querying the depth of the innermost enclosing
21349 Return_Master_Scope_Depth_Of_Call
: declare
21350 function Innermost_Master_Scope_Depth
21351 (N
: Node_Id
) return Uint
;
21352 -- Returns the scope depth of the given node's innermost
21353 -- enclosing dynamic scope (effectively the accessibility
21354 -- level of the innermost enclosing master).
21356 ----------------------------------
21357 -- Innermost_Master_Scope_Depth --
21358 ----------------------------------
21360 function Innermost_Master_Scope_Depth
21361 (N
: Node_Id
) return Uint
21363 Node_Par
: Node_Id
:= Parent
(N
);
21366 -- Locate the nearest enclosing node (by traversing Parents)
21367 -- that Defining_Entity can be applied to, and return the
21368 -- depth of that entity's nearest enclosing dynamic scope.
21370 while Present
(Node_Par
) loop
21371 case Nkind
(Node_Par
) is
21372 when N_Abstract_Subprogram_Declaration
21373 | N_Block_Statement
21375 | N_Component_Declaration
21377 | N_Entry_Declaration
21378 | N_Exception_Declaration
21379 | N_Formal_Object_Declaration
21380 | N_Formal_Package_Declaration
21381 | N_Formal_Subprogram_Declaration
21382 | N_Formal_Type_Declaration
21383 | N_Full_Type_Declaration
21384 | N_Function_Specification
21385 | N_Generic_Declaration
21386 | N_Generic_Instantiation
21387 | N_Implicit_Label_Declaration
21388 | N_Incomplete_Type_Declaration
21389 | N_Loop_Parameter_Specification
21390 | N_Number_Declaration
21391 | N_Object_Declaration
21392 | N_Package_Declaration
21393 | N_Package_Specification
21394 | N_Parameter_Specification
21395 | N_Private_Extension_Declaration
21396 | N_Private_Type_Declaration
21397 | N_Procedure_Specification
21399 | N_Protected_Type_Declaration
21400 | N_Renaming_Declaration
21401 | N_Single_Protected_Declaration
21402 | N_Single_Task_Declaration
21403 | N_Subprogram_Declaration
21404 | N_Subtype_Declaration
21406 | N_Task_Type_Declaration
21409 (Nearest_Dynamic_Scope
21410 (Defining_Entity
(Node_Par
)));
21412 -- For a return statement within a function, return
21413 -- the depth of the function itself. This is not just
21414 -- a small optimization, but matters when analyzing
21415 -- the expression in an expression function before
21416 -- the body is created.
21418 when N_Simple_Return_Statement
=>
21419 if Ekind
(Current_Scope
) = E_Function
then
21420 return Scope_Depth
(Current_Scope
);
21427 Node_Par
:= Parent
(Node_Par
);
21430 pragma Assert
(False);
21432 -- Should never reach the following return
21434 return Scope_Depth
(Current_Scope
) + 1;
21435 end Innermost_Master_Scope_Depth
;
21437 -- Start of processing for Return_Master_Scope_Depth_Of_Call
21440 return Innermost_Master_Scope_Depth
(Obj
);
21441 end Return_Master_Scope_Depth_Of_Call
;
21444 -- For convenience we handle qualified expressions, even though they
21445 -- aren't technically object names.
21447 elsif Nkind
(Obj
) = N_Qualified_Expression
then
21448 return Object_Access_Level
(Expression
(Obj
));
21450 -- Ditto for aggregates. They have the level of the temporary that
21451 -- will hold their value.
21453 elsif Nkind
(Obj
) = N_Aggregate
then
21454 return Object_Access_Level
(Current_Scope
);
21456 -- Otherwise return the scope level of Standard. (If there are cases
21457 -- that fall through to this point they will be treated as having
21458 -- global accessibility for now. ???)
21461 return Scope_Depth
(Standard_Standard
);
21463 end Object_Access_Level
;
21465 ----------------------------------
21466 -- Old_Requires_Transient_Scope --
21467 ----------------------------------
21469 function Old_Requires_Transient_Scope
(Id
: Entity_Id
) return Boolean is
21470 Typ
: constant Entity_Id
:= Underlying_Type
(Id
);
21473 -- This is a private type which is not completed yet. This can only
21474 -- happen in a default expression (of a formal parameter or of a
21475 -- record component). Do not expand transient scope in this case.
21480 -- Do not expand transient scope for non-existent procedure return
21482 elsif Typ
= Standard_Void_Type
then
21485 -- Elementary types do not require a transient scope
21487 elsif Is_Elementary_Type
(Typ
) then
21490 -- Generally, indefinite subtypes require a transient scope, since the
21491 -- back end cannot generate temporaries, since this is not a valid type
21492 -- for declaring an object. It might be possible to relax this in the
21493 -- future, e.g. by declaring the maximum possible space for the type.
21495 elsif not Is_Definite_Subtype
(Typ
) then
21498 -- Functions returning tagged types may dispatch on result so their
21499 -- returned value is allocated on the secondary stack. Controlled
21500 -- type temporaries need finalization.
21502 elsif Is_Tagged_Type
(Typ
) or else Has_Controlled_Component
(Typ
) then
21507 elsif Is_Record_Type
(Typ
) then
21512 Comp
:= First_Entity
(Typ
);
21513 while Present
(Comp
) loop
21514 if Ekind
(Comp
) = E_Component
then
21516 -- ???It's not clear we need a full recursive call to
21517 -- Old_Requires_Transient_Scope here. Note that the
21518 -- following can't happen.
21520 pragma Assert
(Is_Definite_Subtype
(Etype
(Comp
)));
21521 pragma Assert
(not Has_Controlled_Component
(Etype
(Comp
)));
21523 if Old_Requires_Transient_Scope
(Etype
(Comp
)) then
21528 Next_Entity
(Comp
);
21534 -- String literal types never require transient scope
21536 elsif Ekind
(Typ
) = E_String_Literal_Subtype
then
21539 -- Array type. Note that we already know that this is a constrained
21540 -- array, since unconstrained arrays will fail the indefinite test.
21542 elsif Is_Array_Type
(Typ
) then
21544 -- If component type requires a transient scope, the array does too
21546 if Old_Requires_Transient_Scope
(Component_Type
(Typ
)) then
21549 -- Otherwise, we only need a transient scope if the size depends on
21550 -- the value of one or more discriminants.
21553 return Size_Depends_On_Discriminant
(Typ
);
21556 -- All other cases do not require a transient scope
21559 pragma Assert
(Is_Protected_Type
(Typ
) or else Is_Task_Type
(Typ
));
21562 end Old_Requires_Transient_Scope
;
21564 ---------------------------------
21565 -- Original_Aspect_Pragma_Name --
21566 ---------------------------------
21568 function Original_Aspect_Pragma_Name
(N
: Node_Id
) return Name_Id
is
21570 Item_Nam
: Name_Id
;
21573 pragma Assert
(Nkind_In
(N
, N_Aspect_Specification
, N_Pragma
));
21577 -- The pragma was generated to emulate an aspect, use the original
21578 -- aspect specification.
21580 if Nkind
(Item
) = N_Pragma
and then From_Aspect_Specification
(Item
) then
21581 Item
:= Corresponding_Aspect
(Item
);
21584 -- Retrieve the name of the aspect/pragma. Note that Pre, Pre_Class,
21585 -- Post and Post_Class rewrite their pragma identifier to preserve the
21587 -- ??? this is kludgey
21589 if Nkind
(Item
) = N_Pragma
then
21590 Item_Nam
:= Chars
(Original_Node
(Pragma_Identifier
(Item
)));
21593 pragma Assert
(Nkind
(Item
) = N_Aspect_Specification
);
21594 Item_Nam
:= Chars
(Identifier
(Item
));
21597 -- Deal with 'Class by converting the name to its _XXX form
21599 if Class_Present
(Item
) then
21600 if Item_Nam
= Name_Invariant
then
21601 Item_Nam
:= Name_uInvariant
;
21603 elsif Item_Nam
= Name_Post
then
21604 Item_Nam
:= Name_uPost
;
21606 elsif Item_Nam
= Name_Pre
then
21607 Item_Nam
:= Name_uPre
;
21609 elsif Nam_In
(Item_Nam
, Name_Type_Invariant
,
21610 Name_Type_Invariant_Class
)
21612 Item_Nam
:= Name_uType_Invariant
;
21614 -- Nothing to do for other cases (e.g. a Check that derived from
21615 -- Pre_Class and has the flag set). Also we do nothing if the name
21616 -- is already in special _xxx form.
21622 end Original_Aspect_Pragma_Name
;
21624 --------------------------------------
21625 -- Original_Corresponding_Operation --
21626 --------------------------------------
21628 function Original_Corresponding_Operation
(S
: Entity_Id
) return Entity_Id
21630 Typ
: constant Entity_Id
:= Find_Dispatching_Type
(S
);
21633 -- If S is an inherited primitive S2 the original corresponding
21634 -- operation of S is the original corresponding operation of S2
21636 if Present
(Alias
(S
))
21637 and then Find_Dispatching_Type
(Alias
(S
)) /= Typ
21639 return Original_Corresponding_Operation
(Alias
(S
));
21641 -- If S overrides an inherited subprogram S2 the original corresponding
21642 -- operation of S is the original corresponding operation of S2
21644 elsif Present
(Overridden_Operation
(S
)) then
21645 return Original_Corresponding_Operation
(Overridden_Operation
(S
));
21647 -- otherwise it is S itself
21652 end Original_Corresponding_Operation
;
21654 -------------------
21655 -- Output_Entity --
21656 -------------------
21658 procedure Output_Entity
(Id
: Entity_Id
) is
21662 Scop
:= Scope
(Id
);
21664 -- The entity may lack a scope when it is in the process of being
21665 -- analyzed. Use the current scope as an approximation.
21668 Scop
:= Current_Scope
;
21671 Output_Name
(Chars
(Id
), Scop
);
21678 procedure Output_Name
(Nam
: Name_Id
; Scop
: Entity_Id
:= Current_Scope
) is
21682 (Get_Qualified_Name
21689 ----------------------
21690 -- Policy_In_Effect --
21691 ----------------------
21693 function Policy_In_Effect
(Policy
: Name_Id
) return Name_Id
is
21694 function Policy_In_List
(List
: Node_Id
) return Name_Id
;
21695 -- Determine the mode of a policy in a N_Pragma list
21697 --------------------
21698 -- Policy_In_List --
21699 --------------------
21701 function Policy_In_List
(List
: Node_Id
) return Name_Id
is
21708 while Present
(Prag
) loop
21709 Arg1
:= First
(Pragma_Argument_Associations
(Prag
));
21710 Arg2
:= Next
(Arg1
);
21712 Arg1
:= Get_Pragma_Arg
(Arg1
);
21713 Arg2
:= Get_Pragma_Arg
(Arg2
);
21715 -- The current Check_Policy pragma matches the requested policy or
21716 -- appears in the single argument form (Assertion, policy_id).
21718 if Nam_In
(Chars
(Arg1
), Name_Assertion
, Policy
) then
21719 return Chars
(Arg2
);
21722 Prag
:= Next_Pragma
(Prag
);
21726 end Policy_In_List
;
21732 -- Start of processing for Policy_In_Effect
21735 if not Is_Valid_Assertion_Kind
(Policy
) then
21736 raise Program_Error
;
21739 -- Inspect all policy pragmas that appear within scopes (if any)
21741 Kind
:= Policy_In_List
(Check_Policy_List
);
21743 -- Inspect all configuration policy pragmas (if any)
21745 if Kind
= No_Name
then
21746 Kind
:= Policy_In_List
(Check_Policy_List_Config
);
21749 -- The context lacks policy pragmas, determine the mode based on whether
21750 -- assertions are enabled at the configuration level. This ensures that
21751 -- the policy is preserved when analyzing generics.
21753 if Kind
= No_Name
then
21754 if Assertions_Enabled_Config
then
21755 Kind
:= Name_Check
;
21757 Kind
:= Name_Ignore
;
21762 end Policy_In_Effect
;
21764 ----------------------------------
21765 -- Predicate_Tests_On_Arguments --
21766 ----------------------------------
21768 function Predicate_Tests_On_Arguments
(Subp
: Entity_Id
) return Boolean is
21770 -- Always test predicates on indirect call
21772 if Ekind
(Subp
) = E_Subprogram_Type
then
21775 -- Do not test predicates on call to generated default Finalize, since
21776 -- we are not interested in whether something we are finalizing (and
21777 -- typically destroying) satisfies its predicates.
21779 elsif Chars
(Subp
) = Name_Finalize
21780 and then not Comes_From_Source
(Subp
)
21784 -- Do not test predicates on any internally generated routines
21786 elsif Is_Internal_Name
(Chars
(Subp
)) then
21789 -- Do not test predicates on call to Init_Proc, since if needed the
21790 -- predicate test will occur at some other point.
21792 elsif Is_Init_Proc
(Subp
) then
21795 -- Do not test predicates on call to predicate function, since this
21796 -- would cause infinite recursion.
21798 elsif Ekind
(Subp
) = E_Function
21799 and then (Is_Predicate_Function
(Subp
)
21801 Is_Predicate_Function_M
(Subp
))
21805 -- For now, no other exceptions
21810 end Predicate_Tests_On_Arguments
;
21812 -----------------------
21813 -- Private_Component --
21814 -----------------------
21816 function Private_Component
(Type_Id
: Entity_Id
) return Entity_Id
is
21817 Ancestor
: constant Entity_Id
:= Base_Type
(Type_Id
);
21819 function Trace_Components
21821 Check
: Boolean) return Entity_Id
;
21822 -- Recursive function that does the work, and checks against circular
21823 -- definition for each subcomponent type.
21825 ----------------------
21826 -- Trace_Components --
21827 ----------------------
21829 function Trace_Components
21831 Check
: Boolean) return Entity_Id
21833 Btype
: constant Entity_Id
:= Base_Type
(T
);
21834 Component
: Entity_Id
;
21836 Candidate
: Entity_Id
:= Empty
;
21839 if Check
and then Btype
= Ancestor
then
21840 Error_Msg_N
("circular type definition", Type_Id
);
21844 if Is_Private_Type
(Btype
) and then not Is_Generic_Type
(Btype
) then
21845 if Present
(Full_View
(Btype
))
21846 and then Is_Record_Type
(Full_View
(Btype
))
21847 and then not Is_Frozen
(Btype
)
21849 -- To indicate that the ancestor depends on a private type, the
21850 -- current Btype is sufficient. However, to check for circular
21851 -- definition we must recurse on the full view.
21853 Candidate
:= Trace_Components
(Full_View
(Btype
), True);
21855 if Candidate
= Any_Type
then
21865 elsif Is_Array_Type
(Btype
) then
21866 return Trace_Components
(Component_Type
(Btype
), True);
21868 elsif Is_Record_Type
(Btype
) then
21869 Component
:= First_Entity
(Btype
);
21870 while Present
(Component
)
21871 and then Comes_From_Source
(Component
)
21873 -- Skip anonymous types generated by constrained components
21875 if not Is_Type
(Component
) then
21876 P
:= Trace_Components
(Etype
(Component
), True);
21878 if Present
(P
) then
21879 if P
= Any_Type
then
21887 Next_Entity
(Component
);
21895 end Trace_Components
;
21897 -- Start of processing for Private_Component
21900 return Trace_Components
(Type_Id
, False);
21901 end Private_Component
;
21903 ---------------------------
21904 -- Primitive_Names_Match --
21905 ---------------------------
21907 function Primitive_Names_Match
(E1
, E2
: Entity_Id
) return Boolean is
21908 function Non_Internal_Name
(E
: Entity_Id
) return Name_Id
;
21909 -- Given an internal name, returns the corresponding non-internal name
21911 ------------------------
21912 -- Non_Internal_Name --
21913 ------------------------
21915 function Non_Internal_Name
(E
: Entity_Id
) return Name_Id
is
21917 Get_Name_String
(Chars
(E
));
21918 Name_Len
:= Name_Len
- 1;
21920 end Non_Internal_Name
;
21922 -- Start of processing for Primitive_Names_Match
21925 pragma Assert
(Present
(E1
) and then Present
(E2
));
21927 return Chars
(E1
) = Chars
(E2
)
21929 (not Is_Internal_Name
(Chars
(E1
))
21930 and then Is_Internal_Name
(Chars
(E2
))
21931 and then Non_Internal_Name
(E2
) = Chars
(E1
))
21933 (not Is_Internal_Name
(Chars
(E2
))
21934 and then Is_Internal_Name
(Chars
(E1
))
21935 and then Non_Internal_Name
(E1
) = Chars
(E2
))
21937 (Is_Predefined_Dispatching_Operation
(E1
)
21938 and then Is_Predefined_Dispatching_Operation
(E2
)
21939 and then Same_TSS
(E1
, E2
))
21941 (Is_Init_Proc
(E1
) and then Is_Init_Proc
(E2
));
21942 end Primitive_Names_Match
;
21944 -----------------------
21945 -- Process_End_Label --
21946 -----------------------
21948 procedure Process_End_Label
21957 Label_Ref
: Boolean;
21958 -- Set True if reference to end label itself is required
21961 -- Gets set to the operator symbol or identifier that references the
21962 -- entity Ent. For the child unit case, this is the identifier from the
21963 -- designator. For other cases, this is simply Endl.
21965 procedure Generate_Parent_Ref
(N
: Node_Id
; E
: Entity_Id
);
21966 -- N is an identifier node that appears as a parent unit reference in
21967 -- the case where Ent is a child unit. This procedure generates an
21968 -- appropriate cross-reference entry. E is the corresponding entity.
21970 -------------------------
21971 -- Generate_Parent_Ref --
21972 -------------------------
21974 procedure Generate_Parent_Ref
(N
: Node_Id
; E
: Entity_Id
) is
21976 -- If names do not match, something weird, skip reference
21978 if Chars
(E
) = Chars
(N
) then
21980 -- Generate the reference. We do NOT consider this as a reference
21981 -- for unreferenced symbol purposes.
21983 Generate_Reference
(E
, N
, 'r', Set_Ref
=> False, Force
=> True);
21985 if Style_Check
then
21986 Style
.Check_Identifier
(N
, E
);
21989 end Generate_Parent_Ref
;
21991 -- Start of processing for Process_End_Label
21994 -- If no node, ignore. This happens in some error situations, and
21995 -- also for some internally generated structures where no end label
21996 -- references are required in any case.
22002 -- Nothing to do if no End_Label, happens for internally generated
22003 -- constructs where we don't want an end label reference anyway. Also
22004 -- nothing to do if Endl is a string literal, which means there was
22005 -- some prior error (bad operator symbol)
22007 Endl
:= End_Label
(N
);
22009 if No
(Endl
) or else Nkind
(Endl
) = N_String_Literal
then
22013 -- Reference node is not in extended main source unit
22015 if not In_Extended_Main_Source_Unit
(N
) then
22017 -- Generally we do not collect references except for the extended
22018 -- main source unit. The one exception is the 'e' entry for a
22019 -- package spec, where it is useful for a client to have the
22020 -- ending information to define scopes.
22026 Label_Ref
:= False;
22028 -- For this case, we can ignore any parent references, but we
22029 -- need the package name itself for the 'e' entry.
22031 if Nkind
(Endl
) = N_Designator
then
22032 Endl
:= Identifier
(Endl
);
22036 -- Reference is in extended main source unit
22041 -- For designator, generate references for the parent entries
22043 if Nkind
(Endl
) = N_Designator
then
22045 -- Generate references for the prefix if the END line comes from
22046 -- source (otherwise we do not need these references) We climb the
22047 -- scope stack to find the expected entities.
22049 if Comes_From_Source
(Endl
) then
22050 Nam
:= Name
(Endl
);
22051 Scop
:= Current_Scope
;
22052 while Nkind
(Nam
) = N_Selected_Component
loop
22053 Scop
:= Scope
(Scop
);
22054 exit when No
(Scop
);
22055 Generate_Parent_Ref
(Selector_Name
(Nam
), Scop
);
22056 Nam
:= Prefix
(Nam
);
22059 if Present
(Scop
) then
22060 Generate_Parent_Ref
(Nam
, Scope
(Scop
));
22064 Endl
:= Identifier
(Endl
);
22068 -- If the end label is not for the given entity, then either we have
22069 -- some previous error, or this is a generic instantiation for which
22070 -- we do not need to make a cross-reference in this case anyway. In
22071 -- either case we simply ignore the call.
22073 if Chars
(Ent
) /= Chars
(Endl
) then
22077 -- If label was really there, then generate a normal reference and then
22078 -- adjust the location in the end label to point past the name (which
22079 -- should almost always be the semicolon).
22081 Loc
:= Sloc
(Endl
);
22083 if Comes_From_Source
(Endl
) then
22085 -- If a label reference is required, then do the style check and
22086 -- generate an l-type cross-reference entry for the label
22089 if Style_Check
then
22090 Style
.Check_Identifier
(Endl
, Ent
);
22093 Generate_Reference
(Ent
, Endl
, 'l', Set_Ref
=> False);
22096 -- Set the location to point past the label (normally this will
22097 -- mean the semicolon immediately following the label). This is
22098 -- done for the sake of the 'e' or 't' entry generated below.
22100 Get_Decoded_Name_String
(Chars
(Endl
));
22101 Set_Sloc
(Endl
, Sloc
(Endl
) + Source_Ptr
(Name_Len
));
22104 -- In SPARK mode, no missing label is allowed for packages and
22105 -- subprogram bodies. Detect those cases by testing whether
22106 -- Process_End_Label was called for a body (Typ = 't') or a package.
22108 if Restriction_Check_Required
(SPARK_05
)
22109 and then (Typ
= 't' or else Ekind
(Ent
) = E_Package
)
22111 Error_Msg_Node_1
:= Endl
;
22112 Check_SPARK_05_Restriction
22113 ("`END &` required", Endl
, Force
=> True);
22117 -- Now generate the e/t reference
22119 Generate_Reference
(Ent
, Endl
, Typ
, Set_Ref
=> False, Force
=> True);
22121 -- Restore Sloc, in case modified above, since we have an identifier
22122 -- and the normal Sloc should be left set in the tree.
22124 Set_Sloc
(Endl
, Loc
);
22125 end Process_End_Label
;
22127 --------------------------------
22128 -- Propagate_Concurrent_Flags --
22129 --------------------------------
22131 procedure Propagate_Concurrent_Flags
22133 Comp_Typ
: Entity_Id
)
22136 if Has_Task
(Comp_Typ
) then
22137 Set_Has_Task
(Typ
);
22140 if Has_Protected
(Comp_Typ
) then
22141 Set_Has_Protected
(Typ
);
22144 if Has_Timing_Event
(Comp_Typ
) then
22145 Set_Has_Timing_Event
(Typ
);
22147 end Propagate_Concurrent_Flags
;
22149 ------------------------------
22150 -- Propagate_DIC_Attributes --
22151 ------------------------------
22153 procedure Propagate_DIC_Attributes
22155 From_Typ
: Entity_Id
)
22157 DIC_Proc
: Entity_Id
;
22160 if Present
(Typ
) and then Present
(From_Typ
) then
22161 pragma Assert
(Is_Type
(Typ
) and then Is_Type
(From_Typ
));
22163 -- Nothing to do if both the source and the destination denote the
22166 if From_Typ
= Typ
then
22170 DIC_Proc
:= DIC_Procedure
(From_Typ
);
22172 -- The setting of the attributes is intentionally conservative. This
22173 -- prevents accidental clobbering of enabled attributes.
22175 if Has_Inherited_DIC
(From_Typ
)
22176 and then not Has_Inherited_DIC
(Typ
)
22178 Set_Has_Inherited_DIC
(Typ
);
22181 if Has_Own_DIC
(From_Typ
) and then not Has_Own_DIC
(Typ
) then
22182 Set_Has_Own_DIC
(Typ
);
22185 if Present
(DIC_Proc
) and then No
(DIC_Procedure
(Typ
)) then
22186 Set_DIC_Procedure
(Typ
, DIC_Proc
);
22189 end Propagate_DIC_Attributes
;
22191 ------------------------------------
22192 -- Propagate_Invariant_Attributes --
22193 ------------------------------------
22195 procedure Propagate_Invariant_Attributes
22197 From_Typ
: Entity_Id
)
22199 Full_IP
: Entity_Id
;
22200 Part_IP
: Entity_Id
;
22203 if Present
(Typ
) and then Present
(From_Typ
) then
22204 pragma Assert
(Is_Type
(Typ
) and then Is_Type
(From_Typ
));
22206 -- Nothing to do if both the source and the destination denote the
22209 if From_Typ
= Typ
then
22213 Full_IP
:= Invariant_Procedure
(From_Typ
);
22214 Part_IP
:= Partial_Invariant_Procedure
(From_Typ
);
22216 -- The setting of the attributes is intentionally conservative. This
22217 -- prevents accidental clobbering of enabled attributes.
22219 if Has_Inheritable_Invariants
(From_Typ
)
22220 and then not Has_Inheritable_Invariants
(Typ
)
22222 Set_Has_Inheritable_Invariants
(Typ
, True);
22225 if Has_Inherited_Invariants
(From_Typ
)
22226 and then not Has_Inherited_Invariants
(Typ
)
22228 Set_Has_Inherited_Invariants
(Typ
, True);
22231 if Has_Own_Invariants
(From_Typ
)
22232 and then not Has_Own_Invariants
(Typ
)
22234 Set_Has_Own_Invariants
(Typ
, True);
22237 if Present
(Full_IP
) and then No
(Invariant_Procedure
(Typ
)) then
22238 Set_Invariant_Procedure
(Typ
, Full_IP
);
22241 if Present
(Part_IP
) and then No
(Partial_Invariant_Procedure
(Typ
))
22243 Set_Partial_Invariant_Procedure
(Typ
, Part_IP
);
22246 end Propagate_Invariant_Attributes
;
22248 ---------------------------------------
22249 -- Record_Possible_Part_Of_Reference --
22250 ---------------------------------------
22252 procedure Record_Possible_Part_Of_Reference
22253 (Var_Id
: Entity_Id
;
22256 Encap
: constant Entity_Id
:= Encapsulating_State
(Var_Id
);
22260 -- The variable is a constituent of a single protected/task type. Such
22261 -- a variable acts as a component of the type and must appear within a
22262 -- specific region (SPARK RM 9.3). Instead of recording the reference,
22263 -- verify its legality now.
22265 if Present
(Encap
) and then Is_Single_Concurrent_Object
(Encap
) then
22266 Check_Part_Of_Reference
(Var_Id
, Ref
);
22268 -- The variable is subject to pragma Part_Of and may eventually become a
22269 -- constituent of a single protected/task type. Record the reference to
22270 -- verify its placement when the contract of the variable is analyzed.
22272 elsif Present
(Get_Pragma
(Var_Id
, Pragma_Part_Of
)) then
22273 Refs
:= Part_Of_References
(Var_Id
);
22276 Refs
:= New_Elmt_List
;
22277 Set_Part_Of_References
(Var_Id
, Refs
);
22280 Append_Elmt
(Ref
, Refs
);
22282 end Record_Possible_Part_Of_Reference
;
22288 function Referenced
(Id
: Entity_Id
; Expr
: Node_Id
) return Boolean is
22289 Seen
: Boolean := False;
22291 function Is_Reference
(N
: Node_Id
) return Traverse_Result
;
22292 -- Determine whether node N denotes a reference to Id. If this is the
22293 -- case, set global flag Seen to True and stop the traversal.
22299 function Is_Reference
(N
: Node_Id
) return Traverse_Result
is
22301 if Is_Entity_Name
(N
)
22302 and then Present
(Entity
(N
))
22303 and then Entity
(N
) = Id
22312 procedure Inspect_Expression
is new Traverse_Proc
(Is_Reference
);
22314 -- Start of processing for Referenced
22317 Inspect_Expression
(Expr
);
22321 ------------------------------------
22322 -- References_Generic_Formal_Type --
22323 ------------------------------------
22325 function References_Generic_Formal_Type
(N
: Node_Id
) return Boolean is
22327 function Process
(N
: Node_Id
) return Traverse_Result
;
22328 -- Process one node in search for generic formal type
22334 function Process
(N
: Node_Id
) return Traverse_Result
is
22336 if Nkind
(N
) in N_Has_Entity
then
22338 E
: constant Entity_Id
:= Entity
(N
);
22340 if Present
(E
) then
22341 if Is_Generic_Type
(E
) then
22343 elsif Present
(Etype
(E
))
22344 and then Is_Generic_Type
(Etype
(E
))
22355 function Traverse
is new Traverse_Func
(Process
);
22356 -- Traverse tree to look for generic type
22359 if Inside_A_Generic
then
22360 return Traverse
(N
) = Abandon
;
22364 end References_Generic_Formal_Type
;
22366 -------------------
22367 -- Remove_Entity --
22368 -------------------
22370 procedure Remove_Entity
(Id
: Entity_Id
) is
22371 Scop
: constant Entity_Id
:= Scope
(Id
);
22372 Prev_Id
: Entity_Id
;
22375 -- Remove the entity from the homonym chain. When the entity is the
22376 -- head of the chain, associate the entry in the name table with its
22377 -- homonym effectively making it the new head of the chain.
22379 if Current_Entity
(Id
) = Id
then
22380 Set_Name_Entity_Id
(Chars
(Id
), Homonym
(Id
));
22382 -- Otherwise link the previous and next homonyms
22385 Prev_Id
:= Current_Entity
(Id
);
22386 while Present
(Prev_Id
) and then Homonym
(Prev_Id
) /= Id
loop
22387 Prev_Id
:= Homonym
(Prev_Id
);
22390 Set_Homonym
(Prev_Id
, Homonym
(Id
));
22393 -- Remove the entity from the scope entity chain. When the entity is
22394 -- the head of the chain, set the next entity as the new head of the
22397 if First_Entity
(Scop
) = Id
then
22399 Set_First_Entity
(Scop
, Next_Entity
(Id
));
22401 -- Otherwise the entity is either in the middle of the chain or it acts
22402 -- as its tail. Traverse and link the previous and next entities.
22405 Prev_Id
:= First_Entity
(Scop
);
22406 while Present
(Prev_Id
) and then Next_Entity
(Prev_Id
) /= Id
loop
22407 Next_Entity
(Prev_Id
);
22410 Set_Next_Entity
(Prev_Id
, Next_Entity
(Id
));
22413 -- Handle the case where the entity acts as the tail of the scope entity
22416 if Last_Entity
(Scop
) = Id
then
22417 Set_Last_Entity
(Scop
, Prev_Id
);
22421 --------------------
22422 -- Remove_Homonym --
22423 --------------------
22425 procedure Remove_Homonym
(E
: Entity_Id
) is
22426 Prev
: Entity_Id
:= Empty
;
22430 if E
= Current_Entity
(E
) then
22431 if Present
(Homonym
(E
)) then
22432 Set_Current_Entity
(Homonym
(E
));
22434 Set_Name_Entity_Id
(Chars
(E
), Empty
);
22438 H
:= Current_Entity
(E
);
22439 while Present
(H
) and then H
/= E
loop
22444 -- If E is not on the homonym chain, nothing to do
22446 if Present
(H
) then
22447 Set_Homonym
(Prev
, Homonym
(E
));
22450 end Remove_Homonym
;
22452 ------------------------------
22453 -- Remove_Overloaded_Entity --
22454 ------------------------------
22456 procedure Remove_Overloaded_Entity
(Id
: Entity_Id
) is
22457 procedure Remove_Primitive_Of
(Typ
: Entity_Id
);
22458 -- Remove primitive subprogram Id from the list of primitives that
22459 -- belong to type Typ.
22461 -------------------------
22462 -- Remove_Primitive_Of --
22463 -------------------------
22465 procedure Remove_Primitive_Of
(Typ
: Entity_Id
) is
22469 if Is_Tagged_Type
(Typ
) then
22470 Prims
:= Direct_Primitive_Operations
(Typ
);
22472 if Present
(Prims
) then
22473 Remove
(Prims
, Id
);
22476 end Remove_Primitive_Of
;
22480 Formal
: Entity_Id
;
22482 -- Start of processing for Remove_Overloaded_Entity
22485 -- Remove the entity from both the homonym and scope chains
22487 Remove_Entity
(Id
);
22489 -- The entity denotes a primitive subprogram. Remove it from the list of
22490 -- primitives of the associated controlling type.
22492 if Ekind_In
(Id
, E_Function
, E_Procedure
) and then Is_Primitive
(Id
) then
22493 Formal
:= First_Formal
(Id
);
22494 while Present
(Formal
) loop
22495 if Is_Controlling_Formal
(Formal
) then
22496 Remove_Primitive_Of
(Etype
(Formal
));
22500 Next_Formal
(Formal
);
22503 if Ekind
(Id
) = E_Function
and then Has_Controlling_Result
(Id
) then
22504 Remove_Primitive_Of
(Etype
(Id
));
22507 end Remove_Overloaded_Entity
;
22509 ---------------------
22510 -- Rep_To_Pos_Flag --
22511 ---------------------
22513 function Rep_To_Pos_Flag
(E
: Entity_Id
; Loc
: Source_Ptr
) return Node_Id
is
22515 return New_Occurrence_Of
22516 (Boolean_Literals
(not Range_Checks_Suppressed
(E
)), Loc
);
22517 end Rep_To_Pos_Flag
;
22519 --------------------
22520 -- Require_Entity --
22521 --------------------
22523 procedure Require_Entity
(N
: Node_Id
) is
22525 if Is_Entity_Name
(N
) and then No
(Entity
(N
)) then
22526 if Total_Errors_Detected
/= 0 then
22527 Set_Entity
(N
, Any_Id
);
22529 raise Program_Error
;
22532 end Require_Entity
;
22534 ------------------------------
22535 -- Requires_Transient_Scope --
22536 ------------------------------
22538 -- A transient scope is required when variable-sized temporaries are
22539 -- allocated on the secondary stack, or when finalization actions must be
22540 -- generated before the next instruction.
22542 function Requires_Transient_Scope
(Id
: Entity_Id
) return Boolean is
22543 Old_Result
: constant Boolean := Old_Requires_Transient_Scope
(Id
);
22546 if Debug_Flag_QQ
then
22551 New_Result
: constant Boolean := New_Requires_Transient_Scope
(Id
);
22554 -- Assert that we're not putting things on the secondary stack if we
22555 -- didn't before; we are trying to AVOID secondary stack when
22558 if not Old_Result
then
22559 pragma Assert
(not New_Result
);
22563 if New_Result
/= Old_Result
then
22564 Results_Differ
(Id
, Old_Result
, New_Result
);
22569 end Requires_Transient_Scope
;
22571 --------------------
22572 -- Results_Differ --
22573 --------------------
22575 procedure Results_Differ
22581 if False then -- False to disable; True for debugging
22582 Treepr
.Print_Tree_Node
(Id
);
22584 if Old_Val
= New_Val
then
22585 raise Program_Error
;
22588 end Results_Differ
;
22590 --------------------------
22591 -- Reset_Analyzed_Flags --
22592 --------------------------
22594 procedure Reset_Analyzed_Flags
(N
: Node_Id
) is
22595 function Clear_Analyzed
(N
: Node_Id
) return Traverse_Result
;
22596 -- Function used to reset Analyzed flags in tree. Note that we do
22597 -- not reset Analyzed flags in entities, since there is no need to
22598 -- reanalyze entities, and indeed, it is wrong to do so, since it
22599 -- can result in generating auxiliary stuff more than once.
22601 --------------------
22602 -- Clear_Analyzed --
22603 --------------------
22605 function Clear_Analyzed
(N
: Node_Id
) return Traverse_Result
is
22607 if Nkind
(N
) not in N_Entity
then
22608 Set_Analyzed
(N
, False);
22612 end Clear_Analyzed
;
22614 procedure Reset_Analyzed
is new Traverse_Proc
(Clear_Analyzed
);
22616 -- Start of processing for Reset_Analyzed_Flags
22619 Reset_Analyzed
(N
);
22620 end Reset_Analyzed_Flags
;
22622 ------------------------
22623 -- Restore_SPARK_Mode --
22624 ------------------------
22626 procedure Restore_SPARK_Mode
22627 (Mode
: SPARK_Mode_Type
;
22631 SPARK_Mode
:= Mode
;
22632 SPARK_Mode_Pragma
:= Prag
;
22633 end Restore_SPARK_Mode
;
22635 --------------------------------
22636 -- Returns_Unconstrained_Type --
22637 --------------------------------
22639 function Returns_Unconstrained_Type
(Subp
: Entity_Id
) return Boolean is
22641 return Ekind
(Subp
) = E_Function
22642 and then not Is_Scalar_Type
(Etype
(Subp
))
22643 and then not Is_Access_Type
(Etype
(Subp
))
22644 and then not Is_Constrained
(Etype
(Subp
));
22645 end Returns_Unconstrained_Type
;
22647 ----------------------------
22648 -- Root_Type_Of_Full_View --
22649 ----------------------------
22651 function Root_Type_Of_Full_View
(T
: Entity_Id
) return Entity_Id
is
22652 Rtyp
: constant Entity_Id
:= Root_Type
(T
);
22655 -- The root type of the full view may itself be a private type. Keep
22656 -- looking for the ultimate derivation parent.
22658 if Is_Private_Type
(Rtyp
) and then Present
(Full_View
(Rtyp
)) then
22659 return Root_Type_Of_Full_View
(Full_View
(Rtyp
));
22663 end Root_Type_Of_Full_View
;
22665 ---------------------------
22666 -- Safe_To_Capture_Value --
22667 ---------------------------
22669 function Safe_To_Capture_Value
22672 Cond
: Boolean := False) return Boolean
22675 -- The only entities for which we track constant values are variables
22676 -- which are not renamings, constants, out parameters, and in out
22677 -- parameters, so check if we have this case.
22679 -- Note: it may seem odd to track constant values for constants, but in
22680 -- fact this routine is used for other purposes than simply capturing
22681 -- the value. In particular, the setting of Known[_Non]_Null.
22683 if (Ekind
(Ent
) = E_Variable
and then No
(Renamed_Object
(Ent
)))
22685 Ekind_In
(Ent
, E_Constant
, E_Out_Parameter
, E_In_Out_Parameter
)
22689 -- For conditionals, we also allow loop parameters and all formals,
22690 -- including in parameters.
22692 elsif Cond
and then Ekind_In
(Ent
, E_Loop_Parameter
, E_In_Parameter
) then
22695 -- For all other cases, not just unsafe, but impossible to capture
22696 -- Current_Value, since the above are the only entities which have
22697 -- Current_Value fields.
22703 -- Skip if volatile or aliased, since funny things might be going on in
22704 -- these cases which we cannot necessarily track. Also skip any variable
22705 -- for which an address clause is given, or whose address is taken. Also
22706 -- never capture value of library level variables (an attempt to do so
22707 -- can occur in the case of package elaboration code).
22709 if Treat_As_Volatile
(Ent
)
22710 or else Is_Aliased
(Ent
)
22711 or else Present
(Address_Clause
(Ent
))
22712 or else Address_Taken
(Ent
)
22713 or else (Is_Library_Level_Entity
(Ent
)
22714 and then Ekind
(Ent
) = E_Variable
)
22719 -- OK, all above conditions are met. We also require that the scope of
22720 -- the reference be the same as the scope of the entity, not counting
22721 -- packages and blocks and loops.
22724 E_Scope
: constant Entity_Id
:= Scope
(Ent
);
22725 R_Scope
: Entity_Id
;
22728 R_Scope
:= Current_Scope
;
22729 while R_Scope
/= Standard_Standard
loop
22730 exit when R_Scope
= E_Scope
;
22732 if not Ekind_In
(R_Scope
, E_Package
, E_Block
, E_Loop
) then
22735 R_Scope
:= Scope
(R_Scope
);
22740 -- We also require that the reference does not appear in a context
22741 -- where it is not sure to be executed (i.e. a conditional context
22742 -- or an exception handler). We skip this if Cond is True, since the
22743 -- capturing of values from conditional tests handles this ok.
22756 -- Seems dubious that case expressions are not handled here ???
22759 while Present
(P
) loop
22760 if Nkind
(P
) = N_If_Statement
22761 or else Nkind
(P
) = N_Case_Statement
22762 or else (Nkind
(P
) in N_Short_Circuit
22763 and then Desc
= Right_Opnd
(P
))
22764 or else (Nkind
(P
) = N_If_Expression
22765 and then Desc
/= First
(Expressions
(P
)))
22766 or else Nkind
(P
) = N_Exception_Handler
22767 or else Nkind
(P
) = N_Selective_Accept
22768 or else Nkind
(P
) = N_Conditional_Entry_Call
22769 or else Nkind
(P
) = N_Timed_Entry_Call
22770 or else Nkind
(P
) = N_Asynchronous_Select
22778 -- A special Ada 2012 case: the original node may be part
22779 -- of the else_actions of a conditional expression, in which
22780 -- case it might not have been expanded yet, and appears in
22781 -- a non-syntactic list of actions. In that case it is clearly
22782 -- not safe to save a value.
22785 and then Is_List_Member
(Desc
)
22786 and then No
(Parent
(List_Containing
(Desc
)))
22794 -- OK, looks safe to set value
22797 end Safe_To_Capture_Value
;
22803 function Same_Name
(N1
, N2
: Node_Id
) return Boolean is
22804 K1
: constant Node_Kind
:= Nkind
(N1
);
22805 K2
: constant Node_Kind
:= Nkind
(N2
);
22808 if (K1
= N_Identifier
or else K1
= N_Defining_Identifier
)
22809 and then (K2
= N_Identifier
or else K2
= N_Defining_Identifier
)
22811 return Chars
(N1
) = Chars
(N2
);
22813 elsif (K1
= N_Selected_Component
or else K1
= N_Expanded_Name
)
22814 and then (K2
= N_Selected_Component
or else K2
= N_Expanded_Name
)
22816 return Same_Name
(Selector_Name
(N1
), Selector_Name
(N2
))
22817 and then Same_Name
(Prefix
(N1
), Prefix
(N2
));
22828 function Same_Object
(Node1
, Node2
: Node_Id
) return Boolean is
22829 N1
: constant Node_Id
:= Original_Node
(Node1
);
22830 N2
: constant Node_Id
:= Original_Node
(Node2
);
22831 -- We do the tests on original nodes, since we are most interested
22832 -- in the original source, not any expansion that got in the way.
22834 K1
: constant Node_Kind
:= Nkind
(N1
);
22835 K2
: constant Node_Kind
:= Nkind
(N2
);
22838 -- First case, both are entities with same entity
22840 if K1
in N_Has_Entity
and then K2
in N_Has_Entity
then
22842 EN1
: constant Entity_Id
:= Entity
(N1
);
22843 EN2
: constant Entity_Id
:= Entity
(N2
);
22845 if Present
(EN1
) and then Present
(EN2
)
22846 and then (Ekind_In
(EN1
, E_Variable
, E_Constant
)
22847 or else Is_Formal
(EN1
))
22855 -- Second case, selected component with same selector, same record
22857 if K1
= N_Selected_Component
22858 and then K2
= N_Selected_Component
22859 and then Chars
(Selector_Name
(N1
)) = Chars
(Selector_Name
(N2
))
22861 return Same_Object
(Prefix
(N1
), Prefix
(N2
));
22863 -- Third case, indexed component with same subscripts, same array
22865 elsif K1
= N_Indexed_Component
22866 and then K2
= N_Indexed_Component
22867 and then Same_Object
(Prefix
(N1
), Prefix
(N2
))
22872 E1
:= First
(Expressions
(N1
));
22873 E2
:= First
(Expressions
(N2
));
22874 while Present
(E1
) loop
22875 if not Same_Value
(E1
, E2
) then
22886 -- Fourth case, slice of same array with same bounds
22889 and then K2
= N_Slice
22890 and then Nkind
(Discrete_Range
(N1
)) = N_Range
22891 and then Nkind
(Discrete_Range
(N2
)) = N_Range
22892 and then Same_Value
(Low_Bound
(Discrete_Range
(N1
)),
22893 Low_Bound
(Discrete_Range
(N2
)))
22894 and then Same_Value
(High_Bound
(Discrete_Range
(N1
)),
22895 High_Bound
(Discrete_Range
(N2
)))
22897 return Same_Name
(Prefix
(N1
), Prefix
(N2
));
22899 -- All other cases, not clearly the same object
22910 function Same_Type
(T1
, T2
: Entity_Id
) return Boolean is
22915 elsif not Is_Constrained
(T1
)
22916 and then not Is_Constrained
(T2
)
22917 and then Base_Type
(T1
) = Base_Type
(T2
)
22921 -- For now don't bother with case of identical constraints, to be
22922 -- fiddled with later on perhaps (this is only used for optimization
22923 -- purposes, so it is not critical to do a best possible job)
22934 function Same_Value
(Node1
, Node2
: Node_Id
) return Boolean is
22936 if Compile_Time_Known_Value
(Node1
)
22937 and then Compile_Time_Known_Value
(Node2
)
22939 -- Handle properly compile-time expressions that are not
22942 if Is_String_Type
(Etype
(Node1
)) then
22943 return Expr_Value_S
(Node1
) = Expr_Value_S
(Node2
);
22946 return Expr_Value
(Node1
) = Expr_Value
(Node2
);
22949 elsif Same_Object
(Node1
, Node2
) then
22956 --------------------
22957 -- Set_SPARK_Mode --
22958 --------------------
22960 procedure Set_SPARK_Mode
(Context
: Entity_Id
) is
22962 -- Do not consider illegal or partially decorated constructs
22964 if Ekind
(Context
) = E_Void
or else Error_Posted
(Context
) then
22967 elsif Present
(SPARK_Pragma
(Context
)) then
22969 (Mode
=> Get_SPARK_Mode_From_Annotation
(SPARK_Pragma
(Context
)),
22970 Prag
=> SPARK_Pragma
(Context
));
22972 end Set_SPARK_Mode
;
22974 -------------------------
22975 -- Scalar_Part_Present --
22976 -------------------------
22978 function Scalar_Part_Present
(T
: Entity_Id
) return Boolean is
22982 if Is_Scalar_Type
(T
) then
22985 elsif Is_Array_Type
(T
) then
22986 return Scalar_Part_Present
(Component_Type
(T
));
22988 elsif Is_Record_Type
(T
) or else Has_Discriminants
(T
) then
22989 C
:= First_Component_Or_Discriminant
(T
);
22990 while Present
(C
) loop
22991 if Scalar_Part_Present
(Etype
(C
)) then
22994 Next_Component_Or_Discriminant
(C
);
23000 end Scalar_Part_Present
;
23002 ------------------------
23003 -- Scope_Is_Transient --
23004 ------------------------
23006 function Scope_Is_Transient
return Boolean is
23008 return Scope_Stack
.Table
(Scope_Stack
.Last
).Is_Transient
;
23009 end Scope_Is_Transient
;
23015 function Scope_Within
23016 (Inner
: Entity_Id
;
23017 Outer
: Entity_Id
) return Boolean
23023 while Present
(Curr
) and then Curr
/= Standard_Standard
loop
23024 Curr
:= Scope
(Curr
);
23026 if Curr
= Outer
then
23034 --------------------------
23035 -- Scope_Within_Or_Same --
23036 --------------------------
23038 function Scope_Within_Or_Same
23039 (Inner
: Entity_Id
;
23040 Outer
: Entity_Id
) return Boolean
23046 while Present
(Curr
) and then Curr
/= Standard_Standard
loop
23047 if Curr
= Outer
then
23051 Curr
:= Scope
(Curr
);
23055 end Scope_Within_Or_Same
;
23057 --------------------
23058 -- Set_Convention --
23059 --------------------
23061 procedure Set_Convention
(E
: Entity_Id
; Val
: Snames
.Convention_Id
) is
23063 Basic_Set_Convention
(E
, Val
);
23066 and then Is_Access_Subprogram_Type
(Base_Type
(E
))
23067 and then Has_Foreign_Convention
(E
)
23070 -- A pragma Convention in an instance may apply to the subtype
23071 -- created for a formal, in which case we have already verified
23072 -- that conventions of actual and formal match and there is nothing
23073 -- to flag on the subtype.
23075 if In_Instance
then
23078 Set_Can_Use_Internal_Rep
(E
, False);
23082 -- If E is an object, including a component, and the type of E is an
23083 -- anonymous access type with no convention set, then also set the
23084 -- convention of the anonymous access type. We do not do this for
23085 -- anonymous protected types, since protected types always have the
23086 -- default convention.
23088 if Present
(Etype
(E
))
23089 and then (Is_Object
(E
)
23091 -- Allow E_Void (happens for pragma Convention appearing
23092 -- in the middle of a record applying to a component)
23094 or else Ekind
(E
) = E_Void
)
23097 Typ
: constant Entity_Id
:= Etype
(E
);
23100 if Ekind_In
(Typ
, E_Anonymous_Access_Type
,
23101 E_Anonymous_Access_Subprogram_Type
)
23102 and then not Has_Convention_Pragma
(Typ
)
23104 Basic_Set_Convention
(Typ
, Val
);
23105 Set_Has_Convention_Pragma
(Typ
);
23107 -- And for the access subprogram type, deal similarly with the
23108 -- designated E_Subprogram_Type, which is always internal.
23110 if Ekind
(Typ
) = E_Anonymous_Access_Subprogram_Type
then
23112 Dtype
: constant Entity_Id
:= Designated_Type
(Typ
);
23114 if Ekind
(Dtype
) = E_Subprogram_Type
23115 and then not Has_Convention_Pragma
(Dtype
)
23117 Basic_Set_Convention
(Dtype
, Val
);
23118 Set_Has_Convention_Pragma
(Dtype
);
23125 end Set_Convention
;
23127 ------------------------
23128 -- Set_Current_Entity --
23129 ------------------------
23131 -- The given entity is to be set as the currently visible definition of its
23132 -- associated name (i.e. the Node_Id associated with its name). All we have
23133 -- to do is to get the name from the identifier, and then set the
23134 -- associated Node_Id to point to the given entity.
23136 procedure Set_Current_Entity
(E
: Entity_Id
) is
23138 Set_Name_Entity_Id
(Chars
(E
), E
);
23139 end Set_Current_Entity
;
23141 ---------------------------
23142 -- Set_Debug_Info_Needed --
23143 ---------------------------
23145 procedure Set_Debug_Info_Needed
(T
: Entity_Id
) is
23147 procedure Set_Debug_Info_Needed_If_Not_Set
(E
: Entity_Id
);
23148 pragma Inline
(Set_Debug_Info_Needed_If_Not_Set
);
23149 -- Used to set debug info in a related node if not set already
23151 --------------------------------------
23152 -- Set_Debug_Info_Needed_If_Not_Set --
23153 --------------------------------------
23155 procedure Set_Debug_Info_Needed_If_Not_Set
(E
: Entity_Id
) is
23157 if Present
(E
) and then not Needs_Debug_Info
(E
) then
23158 Set_Debug_Info_Needed
(E
);
23160 -- For a private type, indicate that the full view also needs
23161 -- debug information.
23164 and then Is_Private_Type
(E
)
23165 and then Present
(Full_View
(E
))
23167 Set_Debug_Info_Needed
(Full_View
(E
));
23170 end Set_Debug_Info_Needed_If_Not_Set
;
23172 -- Start of processing for Set_Debug_Info_Needed
23175 -- Nothing to do if argument is Empty or has Debug_Info_Off set, which
23176 -- indicates that Debug_Info_Needed is never required for the entity.
23177 -- Nothing to do if entity comes from a predefined file. Library files
23178 -- are compiled without debug information, but inlined bodies of these
23179 -- routines may appear in user code, and debug information on them ends
23180 -- up complicating debugging the user code.
23183 or else Debug_Info_Off
(T
)
23187 elsif In_Inlined_Body
and then In_Predefined_Unit
(T
) then
23188 Set_Needs_Debug_Info
(T
, False);
23191 -- Set flag in entity itself. Note that we will go through the following
23192 -- circuitry even if the flag is already set on T. That's intentional,
23193 -- it makes sure that the flag will be set in subsidiary entities.
23195 Set_Needs_Debug_Info
(T
);
23197 -- Set flag on subsidiary entities if not set already
23199 if Is_Object
(T
) then
23200 Set_Debug_Info_Needed_If_Not_Set
(Etype
(T
));
23202 elsif Is_Type
(T
) then
23203 Set_Debug_Info_Needed_If_Not_Set
(Etype
(T
));
23205 if Is_Record_Type
(T
) then
23207 Ent
: Entity_Id
:= First_Entity
(T
);
23209 while Present
(Ent
) loop
23210 Set_Debug_Info_Needed_If_Not_Set
(Ent
);
23215 -- For a class wide subtype, we also need debug information
23216 -- for the equivalent type.
23218 if Ekind
(T
) = E_Class_Wide_Subtype
then
23219 Set_Debug_Info_Needed_If_Not_Set
(Equivalent_Type
(T
));
23222 elsif Is_Array_Type
(T
) then
23223 Set_Debug_Info_Needed_If_Not_Set
(Component_Type
(T
));
23226 Indx
: Node_Id
:= First_Index
(T
);
23228 while Present
(Indx
) loop
23229 Set_Debug_Info_Needed_If_Not_Set
(Etype
(Indx
));
23230 Indx
:= Next_Index
(Indx
);
23234 -- For a packed array type, we also need debug information for
23235 -- the type used to represent the packed array. Conversely, we
23236 -- also need it for the former if we need it for the latter.
23238 if Is_Packed
(T
) then
23239 Set_Debug_Info_Needed_If_Not_Set
(Packed_Array_Impl_Type
(T
));
23242 if Is_Packed_Array_Impl_Type
(T
) then
23243 Set_Debug_Info_Needed_If_Not_Set
(Original_Array_Type
(T
));
23246 elsif Is_Access_Type
(T
) then
23247 Set_Debug_Info_Needed_If_Not_Set
(Directly_Designated_Type
(T
));
23249 elsif Is_Private_Type
(T
) then
23251 FV
: constant Entity_Id
:= Full_View
(T
);
23254 Set_Debug_Info_Needed_If_Not_Set
(FV
);
23256 -- If the full view is itself a derived private type, we need
23257 -- debug information on its underlying type.
23260 and then Is_Private_Type
(FV
)
23261 and then Present
(Underlying_Full_View
(FV
))
23263 Set_Needs_Debug_Info
(Underlying_Full_View
(FV
));
23267 elsif Is_Protected_Type
(T
) then
23268 Set_Debug_Info_Needed_If_Not_Set
(Corresponding_Record_Type
(T
));
23270 elsif Is_Scalar_Type
(T
) then
23272 -- If the subrange bounds are materialized by dedicated constant
23273 -- objects, also include them in the debug info to make sure the
23274 -- debugger can properly use them.
23276 if Present
(Scalar_Range
(T
))
23277 and then Nkind
(Scalar_Range
(T
)) = N_Range
23280 Low_Bnd
: constant Node_Id
:= Type_Low_Bound
(T
);
23281 High_Bnd
: constant Node_Id
:= Type_High_Bound
(T
);
23284 if Is_Entity_Name
(Low_Bnd
) then
23285 Set_Debug_Info_Needed_If_Not_Set
(Entity
(Low_Bnd
));
23288 if Is_Entity_Name
(High_Bnd
) then
23289 Set_Debug_Info_Needed_If_Not_Set
(Entity
(High_Bnd
));
23295 end Set_Debug_Info_Needed
;
23297 ----------------------------
23298 -- Set_Entity_With_Checks --
23299 ----------------------------
23301 procedure Set_Entity_With_Checks
(N
: Node_Id
; Val
: Entity_Id
) is
23302 Val_Actual
: Entity_Id
;
23304 Post_Node
: Node_Id
;
23307 -- Unconditionally set the entity
23309 Set_Entity
(N
, Val
);
23311 -- The node to post on is the selector in the case of an expanded name,
23312 -- and otherwise the node itself.
23314 if Nkind
(N
) = N_Expanded_Name
then
23315 Post_Node
:= Selector_Name
(N
);
23320 -- Check for violation of No_Fixed_IO
23322 if Restriction_Check_Required
(No_Fixed_IO
)
23324 ((RTU_Loaded
(Ada_Text_IO
)
23325 and then (Is_RTE
(Val
, RE_Decimal_IO
)
23327 Is_RTE
(Val
, RE_Fixed_IO
)))
23330 (RTU_Loaded
(Ada_Wide_Text_IO
)
23331 and then (Is_RTE
(Val
, RO_WT_Decimal_IO
)
23333 Is_RTE
(Val
, RO_WT_Fixed_IO
)))
23336 (RTU_Loaded
(Ada_Wide_Wide_Text_IO
)
23337 and then (Is_RTE
(Val
, RO_WW_Decimal_IO
)
23339 Is_RTE
(Val
, RO_WW_Fixed_IO
))))
23341 -- A special extra check, don't complain about a reference from within
23342 -- the Ada.Interrupts package itself!
23344 and then not In_Same_Extended_Unit
(N
, Val
)
23346 Check_Restriction
(No_Fixed_IO
, Post_Node
);
23349 -- Remaining checks are only done on source nodes. Note that we test
23350 -- for violation of No_Fixed_IO even on non-source nodes, because the
23351 -- cases for checking violations of this restriction are instantiations
23352 -- where the reference in the instance has Comes_From_Source False.
23354 if not Comes_From_Source
(N
) then
23358 -- Check for violation of No_Abort_Statements, which is triggered by
23359 -- call to Ada.Task_Identification.Abort_Task.
23361 if Restriction_Check_Required
(No_Abort_Statements
)
23362 and then (Is_RTE
(Val
, RE_Abort_Task
))
23364 -- A special extra check, don't complain about a reference from within
23365 -- the Ada.Task_Identification package itself!
23367 and then not In_Same_Extended_Unit
(N
, Val
)
23369 Check_Restriction
(No_Abort_Statements
, Post_Node
);
23372 if Val
= Standard_Long_Long_Integer
then
23373 Check_Restriction
(No_Long_Long_Integers
, Post_Node
);
23376 -- Check for violation of No_Dynamic_Attachment
23378 if Restriction_Check_Required
(No_Dynamic_Attachment
)
23379 and then RTU_Loaded
(Ada_Interrupts
)
23380 and then (Is_RTE
(Val
, RE_Is_Reserved
) or else
23381 Is_RTE
(Val
, RE_Is_Attached
) or else
23382 Is_RTE
(Val
, RE_Current_Handler
) or else
23383 Is_RTE
(Val
, RE_Attach_Handler
) or else
23384 Is_RTE
(Val
, RE_Exchange_Handler
) or else
23385 Is_RTE
(Val
, RE_Detach_Handler
) or else
23386 Is_RTE
(Val
, RE_Reference
))
23388 -- A special extra check, don't complain about a reference from within
23389 -- the Ada.Interrupts package itself!
23391 and then not In_Same_Extended_Unit
(N
, Val
)
23393 Check_Restriction
(No_Dynamic_Attachment
, Post_Node
);
23396 -- Check for No_Implementation_Identifiers
23398 if Restriction_Check_Required
(No_Implementation_Identifiers
) then
23400 -- We have an implementation defined entity if it is marked as
23401 -- implementation defined, or is defined in a package marked as
23402 -- implementation defined. However, library packages themselves
23403 -- are excluded (we don't want to flag Interfaces itself, just
23404 -- the entities within it).
23406 if (Is_Implementation_Defined
(Val
)
23408 (Present
(Scope
(Val
))
23409 and then Is_Implementation_Defined
(Scope
(Val
))))
23410 and then not (Ekind_In
(Val
, E_Package
, E_Generic_Package
)
23411 and then Is_Library_Level_Entity
(Val
))
23413 Check_Restriction
(No_Implementation_Identifiers
, Post_Node
);
23417 -- Do the style check
23420 and then not Suppress_Style_Checks
(Val
)
23421 and then not In_Instance
23423 if Nkind
(N
) = N_Identifier
then
23425 elsif Nkind
(N
) = N_Expanded_Name
then
23426 Nod
:= Selector_Name
(N
);
23431 -- A special situation arises for derived operations, where we want
23432 -- to do the check against the parent (since the Sloc of the derived
23433 -- operation points to the derived type declaration itself).
23436 while not Comes_From_Source
(Val_Actual
)
23437 and then Nkind
(Val_Actual
) in N_Entity
23438 and then (Ekind
(Val_Actual
) = E_Enumeration_Literal
23439 or else Is_Subprogram_Or_Generic_Subprogram
(Val_Actual
))
23440 and then Present
(Alias
(Val_Actual
))
23442 Val_Actual
:= Alias
(Val_Actual
);
23445 -- Renaming declarations for generic actuals do not come from source,
23446 -- and have a different name from that of the entity they rename, so
23447 -- there is no style check to perform here.
23449 if Chars
(Nod
) = Chars
(Val_Actual
) then
23450 Style
.Check_Identifier
(Nod
, Val_Actual
);
23454 Set_Entity
(N
, Val
);
23455 end Set_Entity_With_Checks
;
23457 ------------------------
23458 -- Set_Name_Entity_Id --
23459 ------------------------
23461 procedure Set_Name_Entity_Id
(Id
: Name_Id
; Val
: Entity_Id
) is
23463 Set_Name_Table_Int
(Id
, Int
(Val
));
23464 end Set_Name_Entity_Id
;
23466 ---------------------
23467 -- Set_Next_Actual --
23468 ---------------------
23470 procedure Set_Next_Actual
(Ass1_Id
: Node_Id
; Ass2_Id
: Node_Id
) is
23472 if Nkind
(Parent
(Ass1_Id
)) = N_Parameter_Association
then
23473 Set_First_Named_Actual
(Parent
(Ass1_Id
), Ass2_Id
);
23475 end Set_Next_Actual
;
23477 ----------------------------------
23478 -- Set_Optimize_Alignment_Flags --
23479 ----------------------------------
23481 procedure Set_Optimize_Alignment_Flags
(E
: Entity_Id
) is
23483 if Optimize_Alignment
= 'S' then
23484 Set_Optimize_Alignment_Space
(E
);
23485 elsif Optimize_Alignment
= 'T' then
23486 Set_Optimize_Alignment_Time
(E
);
23488 end Set_Optimize_Alignment_Flags
;
23490 -----------------------
23491 -- Set_Public_Status --
23492 -----------------------
23494 procedure Set_Public_Status
(Id
: Entity_Id
) is
23495 S
: constant Entity_Id
:= Current_Scope
;
23497 function Within_HSS_Or_If
(E
: Entity_Id
) return Boolean;
23498 -- Determines if E is defined within handled statement sequence or
23499 -- an if statement, returns True if so, False otherwise.
23501 ----------------------
23502 -- Within_HSS_Or_If --
23503 ----------------------
23505 function Within_HSS_Or_If
(E
: Entity_Id
) return Boolean is
23508 N
:= Declaration_Node
(E
);
23515 elsif Nkind_In
(N
, N_Handled_Sequence_Of_Statements
,
23521 end Within_HSS_Or_If
;
23523 -- Start of processing for Set_Public_Status
23526 -- Everything in the scope of Standard is public
23528 if S
= Standard_Standard
then
23529 Set_Is_Public
(Id
);
23531 -- Entity is definitely not public if enclosing scope is not public
23533 elsif not Is_Public
(S
) then
23536 -- An object or function declaration that occurs in a handled sequence
23537 -- of statements or within an if statement is the declaration for a
23538 -- temporary object or local subprogram generated by the expander. It
23539 -- never needs to be made public and furthermore, making it public can
23540 -- cause back end problems.
23542 elsif Nkind_In
(Parent
(Id
), N_Object_Declaration
,
23543 N_Function_Specification
)
23544 and then Within_HSS_Or_If
(Id
)
23548 -- Entities in public packages or records are public
23550 elsif Ekind
(S
) = E_Package
or Is_Record_Type
(S
) then
23551 Set_Is_Public
(Id
);
23553 -- The bounds of an entry family declaration can generate object
23554 -- declarations that are visible to the back-end, e.g. in the
23555 -- the declaration of a composite type that contains tasks.
23557 elsif Is_Concurrent_Type
(S
)
23558 and then not Has_Completion
(S
)
23559 and then Nkind
(Parent
(Id
)) = N_Object_Declaration
23561 Set_Is_Public
(Id
);
23563 end Set_Public_Status
;
23565 -----------------------------
23566 -- Set_Referenced_Modified --
23567 -----------------------------
23569 procedure Set_Referenced_Modified
(N
: Node_Id
; Out_Param
: Boolean) is
23573 -- Deal with indexed or selected component where prefix is modified
23575 if Nkind_In
(N
, N_Indexed_Component
, N_Selected_Component
) then
23576 Pref
:= Prefix
(N
);
23578 -- If prefix is access type, then it is the designated object that is
23579 -- being modified, which means we have no entity to set the flag on.
23581 if No
(Etype
(Pref
)) or else Is_Access_Type
(Etype
(Pref
)) then
23584 -- Otherwise chase the prefix
23587 Set_Referenced_Modified
(Pref
, Out_Param
);
23590 -- Otherwise see if we have an entity name (only other case to process)
23592 elsif Is_Entity_Name
(N
) and then Present
(Entity
(N
)) then
23593 Set_Referenced_As_LHS
(Entity
(N
), not Out_Param
);
23594 Set_Referenced_As_Out_Parameter
(Entity
(N
), Out_Param
);
23596 end Set_Referenced_Modified
;
23602 procedure Set_Rep_Info
(T1
: Entity_Id
; T2
: Entity_Id
) is
23604 Set_Is_Atomic
(T1
, Is_Atomic
(T2
));
23605 Set_Is_Independent
(T1
, Is_Independent
(T2
));
23606 Set_Is_Volatile_Full_Access
(T1
, Is_Volatile_Full_Access
(T2
));
23608 if Is_Base_Type
(T1
) then
23609 Set_Is_Volatile
(T1
, Is_Volatile
(T2
));
23613 ----------------------------
23614 -- Set_Scope_Is_Transient --
23615 ----------------------------
23617 procedure Set_Scope_Is_Transient
(V
: Boolean := True) is
23619 Scope_Stack
.Table
(Scope_Stack
.Last
).Is_Transient
:= V
;
23620 end Set_Scope_Is_Transient
;
23622 -------------------
23623 -- Set_Size_Info --
23624 -------------------
23626 procedure Set_Size_Info
(T1
, T2
: Entity_Id
) is
23628 -- We copy Esize, but not RM_Size, since in general RM_Size is
23629 -- subtype specific and does not get inherited by all subtypes.
23631 Set_Esize
(T1
, Esize
(T2
));
23632 Set_Has_Biased_Representation
(T1
, Has_Biased_Representation
(T2
));
23634 if Is_Discrete_Or_Fixed_Point_Type
(T1
)
23636 Is_Discrete_Or_Fixed_Point_Type
(T2
)
23638 Set_Is_Unsigned_Type
(T1
, Is_Unsigned_Type
(T2
));
23641 Set_Alignment
(T1
, Alignment
(T2
));
23644 ------------------------------
23645 -- Should_Ignore_Pragma_Par --
23646 ------------------------------
23648 function Should_Ignore_Pragma_Par
(Prag_Name
: Name_Id
) return Boolean is
23649 pragma Assert
(Compiler_State
= Parsing
);
23650 -- This one can't work during semantic analysis, because we don't have a
23651 -- correct Current_Source_File.
23653 Result
: constant Boolean :=
23654 Get_Name_Table_Boolean3
(Prag_Name
)
23655 and then not Is_Internal_File_Name
23656 (File_Name
(Current_Source_File
));
23659 end Should_Ignore_Pragma_Par
;
23661 ------------------------------
23662 -- Should_Ignore_Pragma_Sem --
23663 ------------------------------
23665 function Should_Ignore_Pragma_Sem
(N
: Node_Id
) return Boolean is
23666 pragma Assert
(Compiler_State
= Analyzing
);
23667 Prag_Name
: constant Name_Id
:= Pragma_Name
(N
);
23668 Result
: constant Boolean :=
23669 Get_Name_Table_Boolean3
(Prag_Name
)
23670 and then not In_Internal_Unit
(N
);
23674 end Should_Ignore_Pragma_Sem
;
23676 --------------------
23677 -- Static_Boolean --
23678 --------------------
23680 function Static_Boolean
(N
: Node_Id
) return Uint
is
23682 Analyze_And_Resolve
(N
, Standard_Boolean
);
23685 or else Error_Posted
(N
)
23686 or else Etype
(N
) = Any_Type
23691 if Is_OK_Static_Expression
(N
) then
23692 if not Raises_Constraint_Error
(N
) then
23693 return Expr_Value
(N
);
23698 elsif Etype
(N
) = Any_Type
then
23702 Flag_Non_Static_Expr
23703 ("static boolean expression required here", N
);
23706 end Static_Boolean
;
23708 --------------------
23709 -- Static_Integer --
23710 --------------------
23712 function Static_Integer
(N
: Node_Id
) return Uint
is
23714 Analyze_And_Resolve
(N
, Any_Integer
);
23717 or else Error_Posted
(N
)
23718 or else Etype
(N
) = Any_Type
23723 if Is_OK_Static_Expression
(N
) then
23724 if not Raises_Constraint_Error
(N
) then
23725 return Expr_Value
(N
);
23730 elsif Etype
(N
) = Any_Type
then
23734 Flag_Non_Static_Expr
23735 ("static integer expression required here", N
);
23738 end Static_Integer
;
23740 --------------------------
23741 -- Statically_Different --
23742 --------------------------
23744 function Statically_Different
(E1
, E2
: Node_Id
) return Boolean is
23745 R1
: constant Node_Id
:= Get_Referenced_Object
(E1
);
23746 R2
: constant Node_Id
:= Get_Referenced_Object
(E2
);
23748 return Is_Entity_Name
(R1
)
23749 and then Is_Entity_Name
(R2
)
23750 and then Entity
(R1
) /= Entity
(R2
)
23751 and then not Is_Formal
(Entity
(R1
))
23752 and then not Is_Formal
(Entity
(R2
));
23753 end Statically_Different
;
23755 --------------------------------------
23756 -- Subject_To_Loop_Entry_Attributes --
23757 --------------------------------------
23759 function Subject_To_Loop_Entry_Attributes
(N
: Node_Id
) return Boolean is
23765 -- The expansion mechanism transform a loop subject to at least one
23766 -- 'Loop_Entry attribute into a conditional block. Infinite loops lack
23767 -- the conditional part.
23769 if Nkind_In
(Stmt
, N_Block_Statement
, N_If_Statement
)
23770 and then Nkind
(Original_Node
(N
)) = N_Loop_Statement
23772 Stmt
:= Original_Node
(N
);
23776 Nkind
(Stmt
) = N_Loop_Statement
23777 and then Present
(Identifier
(Stmt
))
23778 and then Present
(Entity
(Identifier
(Stmt
)))
23779 and then Has_Loop_Entry_Attributes
(Entity
(Identifier
(Stmt
)));
23780 end Subject_To_Loop_Entry_Attributes
;
23782 -----------------------------
23783 -- Subprogram_Access_Level --
23784 -----------------------------
23786 function Subprogram_Access_Level
(Subp
: Entity_Id
) return Uint
is
23788 if Present
(Alias
(Subp
)) then
23789 return Subprogram_Access_Level
(Alias
(Subp
));
23791 return Scope_Depth
(Enclosing_Dynamic_Scope
(Subp
));
23793 end Subprogram_Access_Level
;
23795 ---------------------
23796 -- Subprogram_Name --
23797 ---------------------
23799 function Subprogram_Name
(N
: Node_Id
) return String is
23800 Buf
: Bounded_String
;
23801 Ent
: Node_Id
:= N
;
23805 while Present
(Ent
) loop
23806 case Nkind
(Ent
) is
23807 when N_Subprogram_Body
=>
23808 Ent
:= Defining_Unit_Name
(Specification
(Ent
));
23811 when N_Subprogram_Declaration
=>
23812 Nod
:= Corresponding_Body
(Ent
);
23814 if Present
(Nod
) then
23817 Ent
:= Defining_Unit_Name
(Specification
(Ent
));
23822 when N_Subprogram_Instantiation
23824 | N_Package_Specification
23826 Ent
:= Defining_Unit_Name
(Ent
);
23829 when N_Protected_Type_Declaration
=>
23830 Ent
:= Corresponding_Body
(Ent
);
23833 when N_Protected_Body
23836 Ent
:= Defining_Identifier
(Ent
);
23843 Ent
:= Parent
(Ent
);
23847 return "unknown subprogram:unknown file:0:0";
23850 -- If the subprogram is a child unit, use its simple name to start the
23851 -- construction of the fully qualified name.
23853 if Nkind
(Ent
) = N_Defining_Program_Unit_Name
then
23854 Ent
:= Defining_Identifier
(Ent
);
23857 Append_Entity_Name
(Buf
, Ent
);
23859 -- Append homonym number if needed
23861 if Nkind
(N
) in N_Entity
and then Has_Homonym
(N
) then
23863 H
: Entity_Id
:= Homonym
(N
);
23867 while Present
(H
) loop
23868 if Scope
(H
) = Scope
(N
) then
23882 -- Append source location of Ent to Buf so that the string will
23883 -- look like "subp:file:line:col".
23886 Loc
: constant Source_Ptr
:= Sloc
(Ent
);
23889 Append
(Buf
, Reference_Name
(Get_Source_File_Index
(Loc
)));
23891 Append
(Buf
, Nat
(Get_Logical_Line_Number
(Loc
)));
23893 Append
(Buf
, Nat
(Get_Column_Number
(Loc
)));
23897 end Subprogram_Name
;
23899 -------------------------------
23900 -- Support_Atomic_Primitives --
23901 -------------------------------
23903 function Support_Atomic_Primitives
(Typ
: Entity_Id
) return Boolean is
23907 -- Verify the alignment of Typ is known
23909 if not Known_Alignment
(Typ
) then
23913 if Known_Static_Esize
(Typ
) then
23914 Size
:= UI_To_Int
(Esize
(Typ
));
23916 -- If the Esize (Object_Size) is unknown at compile time, look at the
23917 -- RM_Size (Value_Size) which may have been set by an explicit rep item.
23919 elsif Known_Static_RM_Size
(Typ
) then
23920 Size
:= UI_To_Int
(RM_Size
(Typ
));
23922 -- Otherwise, the size is considered to be unknown.
23928 -- Check that the size of the component is 8, 16, 32, or 64 bits and
23929 -- that Typ is properly aligned.
23932 when 8 |
16 |
32 |
64 =>
23933 return Size
= UI_To_Int
(Alignment
(Typ
)) * 8;
23938 end Support_Atomic_Primitives
;
23944 procedure Trace_Scope
(N
: Node_Id
; E
: Entity_Id
; Msg
: String) is
23946 if Debug_Flag_W
then
23947 for J
in 0 .. Scope_Stack
.Last
loop
23952 Write_Name
(Chars
(E
));
23953 Write_Str
(" from ");
23954 Write_Location
(Sloc
(N
));
23959 -----------------------
23960 -- Transfer_Entities --
23961 -----------------------
23963 procedure Transfer_Entities
(From
: Entity_Id
; To
: Entity_Id
) is
23964 procedure Set_Public_Status_Of
(Id
: Entity_Id
);
23965 -- Set the Is_Public attribute of arbitrary entity Id by calling routine
23966 -- Set_Public_Status. If successful and Id denotes a record type, set
23967 -- the Is_Public attribute of its fields.
23969 --------------------------
23970 -- Set_Public_Status_Of --
23971 --------------------------
23973 procedure Set_Public_Status_Of
(Id
: Entity_Id
) is
23977 if not Is_Public
(Id
) then
23978 Set_Public_Status
(Id
);
23980 -- When the input entity is a public record type, ensure that all
23981 -- its internal fields are also exposed to the linker. The fields
23982 -- of a class-wide type are never made public.
23985 and then Is_Record_Type
(Id
)
23986 and then not Is_Class_Wide_Type
(Id
)
23988 Field
:= First_Entity
(Id
);
23989 while Present
(Field
) loop
23990 Set_Is_Public
(Field
);
23991 Next_Entity
(Field
);
23995 end Set_Public_Status_Of
;
23999 Full_Id
: Entity_Id
;
24002 -- Start of processing for Transfer_Entities
24005 Id
:= First_Entity
(From
);
24007 if Present
(Id
) then
24009 -- Merge the entity chain of the source scope with that of the
24010 -- destination scope.
24012 if Present
(Last_Entity
(To
)) then
24013 Set_Next_Entity
(Last_Entity
(To
), Id
);
24015 Set_First_Entity
(To
, Id
);
24018 Set_Last_Entity
(To
, Last_Entity
(From
));
24020 -- Inspect the entities of the source scope and update their Scope
24023 while Present
(Id
) loop
24024 Set_Scope
(Id
, To
);
24025 Set_Public_Status_Of
(Id
);
24027 -- Handle an internally generated full view for a private type
24029 if Is_Private_Type
(Id
)
24030 and then Present
(Full_View
(Id
))
24031 and then Is_Itype
(Full_View
(Id
))
24033 Full_Id
:= Full_View
(Id
);
24035 Set_Scope
(Full_Id
, To
);
24036 Set_Public_Status_Of
(Full_Id
);
24042 Set_First_Entity
(From
, Empty
);
24043 Set_Last_Entity
(From
, Empty
);
24045 end Transfer_Entities
;
24047 -----------------------
24048 -- Type_Access_Level --
24049 -----------------------
24051 function Type_Access_Level
(Typ
: Entity_Id
) return Uint
is
24055 Btyp
:= Base_Type
(Typ
);
24057 -- Ada 2005 (AI-230): For most cases of anonymous access types, we
24058 -- simply use the level where the type is declared. This is true for
24059 -- stand-alone object declarations, and for anonymous access types
24060 -- associated with components the level is the same as that of the
24061 -- enclosing composite type. However, special treatment is needed for
24062 -- the cases of access parameters, return objects of an anonymous access
24063 -- type, and, in Ada 95, access discriminants of limited types.
24065 if Is_Access_Type
(Btyp
) then
24066 if Ekind
(Btyp
) = E_Anonymous_Access_Type
then
24068 -- If the type is a nonlocal anonymous access type (such as for
24069 -- an access parameter) we treat it as being declared at the
24070 -- library level to ensure that names such as X.all'access don't
24071 -- fail static accessibility checks.
24073 if not Is_Local_Anonymous_Access
(Typ
) then
24074 return Scope_Depth
(Standard_Standard
);
24076 -- If this is a return object, the accessibility level is that of
24077 -- the result subtype of the enclosing function. The test here is
24078 -- little complicated, because we have to account for extended
24079 -- return statements that have been rewritten as blocks, in which
24080 -- case we have to find and the Is_Return_Object attribute of the
24081 -- itype's associated object. It would be nice to find a way to
24082 -- simplify this test, but it doesn't seem worthwhile to add a new
24083 -- flag just for purposes of this test. ???
24085 elsif Ekind
(Scope
(Btyp
)) = E_Return_Statement
24088 and then Nkind
(Associated_Node_For_Itype
(Btyp
)) =
24089 N_Object_Declaration
24090 and then Is_Return_Object
24091 (Defining_Identifier
24092 (Associated_Node_For_Itype
(Btyp
))))
24098 Scop
:= Scope
(Scope
(Btyp
));
24099 while Present
(Scop
) loop
24100 exit when Ekind
(Scop
) = E_Function
;
24101 Scop
:= Scope
(Scop
);
24104 -- Treat the return object's type as having the level of the
24105 -- function's result subtype (as per RM05-6.5(5.3/2)).
24107 return Type_Access_Level
(Etype
(Scop
));
24112 Btyp
:= Root_Type
(Btyp
);
24114 -- The accessibility level of anonymous access types associated with
24115 -- discriminants is that of the current instance of the type, and
24116 -- that's deeper than the type itself (AARM 3.10.2 (12.3.21)).
24118 -- AI-402: access discriminants have accessibility based on the
24119 -- object rather than the type in Ada 2005, so the above paragraph
24122 -- ??? Needs completion with rules from AI-416
24124 if Ada_Version
<= Ada_95
24125 and then Ekind
(Typ
) = E_Anonymous_Access_Type
24126 and then Present
(Associated_Node_For_Itype
(Typ
))
24127 and then Nkind
(Associated_Node_For_Itype
(Typ
)) =
24128 N_Discriminant_Specification
24130 return Scope_Depth
(Enclosing_Dynamic_Scope
(Btyp
)) + 1;
24134 -- Return library level for a generic formal type. This is done because
24135 -- RM(10.3.2) says that "The statically deeper relationship does not
24136 -- apply to ... a descendant of a generic formal type". Rather than
24137 -- checking at each point where a static accessibility check is
24138 -- performed to see if we are dealing with a formal type, this rule is
24139 -- implemented by having Type_Access_Level and Deepest_Type_Access_Level
24140 -- return extreme values for a formal type; Deepest_Type_Access_Level
24141 -- returns Int'Last. By calling the appropriate function from among the
24142 -- two, we ensure that the static accessibility check will pass if we
24143 -- happen to run into a formal type. More specifically, we should call
24144 -- Deepest_Type_Access_Level instead of Type_Access_Level whenever the
24145 -- call occurs as part of a static accessibility check and the error
24146 -- case is the case where the type's level is too shallow (as opposed
24149 if Is_Generic_Type
(Root_Type
(Btyp
)) then
24150 return Scope_Depth
(Standard_Standard
);
24153 return Scope_Depth
(Enclosing_Dynamic_Scope
(Btyp
));
24154 end Type_Access_Level
;
24156 ------------------------------------
24157 -- Type_Without_Stream_Operation --
24158 ------------------------------------
24160 function Type_Without_Stream_Operation
24162 Op
: TSS_Name_Type
:= TSS_Null
) return Entity_Id
24164 BT
: constant Entity_Id
:= Base_Type
(T
);
24165 Op_Missing
: Boolean;
24168 if not Restriction_Active
(No_Default_Stream_Attributes
) then
24172 if Is_Elementary_Type
(T
) then
24173 if Op
= TSS_Null
then
24175 No
(TSS
(BT
, TSS_Stream_Read
))
24176 or else No
(TSS
(BT
, TSS_Stream_Write
));
24179 Op_Missing
:= No
(TSS
(BT
, Op
));
24188 elsif Is_Array_Type
(T
) then
24189 return Type_Without_Stream_Operation
(Component_Type
(T
), Op
);
24191 elsif Is_Record_Type
(T
) then
24197 Comp
:= First_Component
(T
);
24198 while Present
(Comp
) loop
24199 C_Typ
:= Type_Without_Stream_Operation
(Etype
(Comp
), Op
);
24201 if Present
(C_Typ
) then
24205 Next_Component
(Comp
);
24211 elsif Is_Private_Type
(T
) and then Present
(Full_View
(T
)) then
24212 return Type_Without_Stream_Operation
(Full_View
(T
), Op
);
24216 end Type_Without_Stream_Operation
;
24218 ----------------------------
24219 -- Unique_Defining_Entity --
24220 ----------------------------
24222 function Unique_Defining_Entity
(N
: Node_Id
) return Entity_Id
is
24224 return Unique_Entity
(Defining_Entity
(N
));
24225 end Unique_Defining_Entity
;
24227 -------------------
24228 -- Unique_Entity --
24229 -------------------
24231 function Unique_Entity
(E
: Entity_Id
) return Entity_Id
is
24232 U
: Entity_Id
:= E
;
24238 if Present
(Full_View
(E
)) then
24239 U
:= Full_View
(E
);
24243 if Nkind
(Parent
(E
)) = N_Entry_Body
then
24245 Prot_Item
: Entity_Id
;
24246 Prot_Type
: Entity_Id
;
24249 if Ekind
(E
) = E_Entry
then
24250 Prot_Type
:= Scope
(E
);
24252 -- Bodies of entry families are nested within an extra scope
24253 -- that contains an entry index declaration.
24256 Prot_Type
:= Scope
(Scope
(E
));
24259 -- A protected type may be declared as a private type, in
24260 -- which case we need to get its full view.
24262 if Is_Private_Type
(Prot_Type
) then
24263 Prot_Type
:= Full_View
(Prot_Type
);
24266 -- Full view may not be present on error, in which case
24267 -- return E by default.
24269 if Present
(Prot_Type
) then
24270 pragma Assert
(Ekind
(Prot_Type
) = E_Protected_Type
);
24272 -- Traverse the entity list of the protected type and
24273 -- locate an entry declaration which matches the entry
24276 Prot_Item
:= First_Entity
(Prot_Type
);
24277 while Present
(Prot_Item
) loop
24278 if Ekind
(Prot_Item
) in Entry_Kind
24279 and then Corresponding_Body
(Parent
(Prot_Item
)) = E
24285 Next_Entity
(Prot_Item
);
24291 when Formal_Kind
=>
24292 if Present
(Spec_Entity
(E
)) then
24293 U
:= Spec_Entity
(E
);
24296 when E_Package_Body
=>
24299 if Nkind
(P
) = N_Defining_Program_Unit_Name
then
24303 if Nkind
(P
) = N_Package_Body
24304 and then Present
(Corresponding_Spec
(P
))
24306 U
:= Corresponding_Spec
(P
);
24308 elsif Nkind
(P
) = N_Package_Body_Stub
24309 and then Present
(Corresponding_Spec_Of_Stub
(P
))
24311 U
:= Corresponding_Spec_Of_Stub
(P
);
24314 when E_Protected_Body
=>
24317 if Nkind
(P
) = N_Protected_Body
24318 and then Present
(Corresponding_Spec
(P
))
24320 U
:= Corresponding_Spec
(P
);
24322 elsif Nkind
(P
) = N_Protected_Body_Stub
24323 and then Present
(Corresponding_Spec_Of_Stub
(P
))
24325 U
:= Corresponding_Spec_Of_Stub
(P
);
24327 if Is_Single_Protected_Object
(U
) then
24332 if Is_Private_Type
(U
) then
24333 U
:= Full_View
(U
);
24336 when E_Subprogram_Body
=>
24339 if Nkind
(P
) = N_Defining_Program_Unit_Name
then
24345 if Nkind
(P
) = N_Subprogram_Body
24346 and then Present
(Corresponding_Spec
(P
))
24348 U
:= Corresponding_Spec
(P
);
24350 elsif Nkind
(P
) = N_Subprogram_Body_Stub
24351 and then Present
(Corresponding_Spec_Of_Stub
(P
))
24353 U
:= Corresponding_Spec_Of_Stub
(P
);
24355 elsif Nkind
(P
) = N_Subprogram_Renaming_Declaration
then
24356 U
:= Corresponding_Spec
(P
);
24359 when E_Task_Body
=>
24362 if Nkind
(P
) = N_Task_Body
24363 and then Present
(Corresponding_Spec
(P
))
24365 U
:= Corresponding_Spec
(P
);
24367 elsif Nkind
(P
) = N_Task_Body_Stub
24368 and then Present
(Corresponding_Spec_Of_Stub
(P
))
24370 U
:= Corresponding_Spec_Of_Stub
(P
);
24372 if Is_Single_Task_Object
(U
) then
24377 if Is_Private_Type
(U
) then
24378 U
:= Full_View
(U
);
24382 if Present
(Full_View
(E
)) then
24383 U
:= Full_View
(E
);
24397 function Unique_Name
(E
: Entity_Id
) return String is
24399 -- Names in E_Subprogram_Body or E_Package_Body entities are not
24400 -- reliable, as they may not include the overloading suffix. Instead,
24401 -- when looking for the name of E or one of its enclosing scope, we get
24402 -- the name of the corresponding Unique_Entity.
24404 U
: constant Entity_Id
:= Unique_Entity
(E
);
24406 function This_Name
return String;
24412 function This_Name
return String is
24414 return Get_Name_String
(Chars
(U
));
24417 -- Start of processing for Unique_Name
24420 if E
= Standard_Standard
24421 or else Has_Fully_Qualified_Name
(E
)
24425 elsif Ekind
(E
) = E_Enumeration_Literal
then
24426 return Unique_Name
(Etype
(E
)) & "__" & This_Name
;
24430 S
: constant Entity_Id
:= Scope
(U
);
24431 pragma Assert
(Present
(S
));
24434 -- Prefix names of predefined types with standard__, but leave
24435 -- names of user-defined packages and subprograms without prefix
24436 -- (even if technically they are nested in the Standard package).
24438 if S
= Standard_Standard
then
24439 if Ekind
(U
) = E_Package
or else Is_Subprogram
(U
) then
24442 return Unique_Name
(S
) & "__" & This_Name
;
24445 -- For intances of generic subprograms use the name of the related
24446 -- instace and skip the scope of its wrapper package.
24448 elsif Is_Wrapper_Package
(S
) then
24449 pragma Assert
(Scope
(S
) = Scope
(Related_Instance
(S
)));
24450 -- Wrapper package and the instantiation are in the same scope
24453 Enclosing_Name
: constant String :=
24454 Unique_Name
(Scope
(S
)) & "__" &
24455 Get_Name_String
(Chars
(Related_Instance
(S
)));
24458 if Is_Subprogram
(U
)
24459 and then not Is_Generic_Actual_Subprogram
(U
)
24461 return Enclosing_Name
;
24463 return Enclosing_Name
& "__" & This_Name
;
24468 return Unique_Name
(S
) & "__" & This_Name
;
24474 ---------------------
24475 -- Unit_Is_Visible --
24476 ---------------------
24478 function Unit_Is_Visible
(U
: Entity_Id
) return Boolean is
24479 Curr
: constant Node_Id
:= Cunit
(Current_Sem_Unit
);
24480 Curr_Entity
: constant Entity_Id
:= Cunit_Entity
(Current_Sem_Unit
);
24482 function Unit_In_Parent_Context
(Par_Unit
: Node_Id
) return Boolean;
24483 -- For a child unit, check whether unit appears in a with_clause
24486 function Unit_In_Context
(Comp_Unit
: Node_Id
) return Boolean;
24487 -- Scan the context clause of one compilation unit looking for a
24488 -- with_clause for the unit in question.
24490 ----------------------------
24491 -- Unit_In_Parent_Context --
24492 ----------------------------
24494 function Unit_In_Parent_Context
(Par_Unit
: Node_Id
) return Boolean is
24496 if Unit_In_Context
(Par_Unit
) then
24499 elsif Is_Child_Unit
(Defining_Entity
(Unit
(Par_Unit
))) then
24500 return Unit_In_Parent_Context
(Parent_Spec
(Unit
(Par_Unit
)));
24505 end Unit_In_Parent_Context
;
24507 ---------------------
24508 -- Unit_In_Context --
24509 ---------------------
24511 function Unit_In_Context
(Comp_Unit
: Node_Id
) return Boolean is
24515 Clause
:= First
(Context_Items
(Comp_Unit
));
24516 while Present
(Clause
) loop
24517 if Nkind
(Clause
) = N_With_Clause
then
24518 if Library_Unit
(Clause
) = U
then
24521 -- The with_clause may denote a renaming of the unit we are
24522 -- looking for, eg. Text_IO which renames Ada.Text_IO.
24525 Renamed_Entity
(Entity
(Name
(Clause
))) =
24526 Defining_Entity
(Unit
(U
))
24536 end Unit_In_Context
;
24538 -- Start of processing for Unit_Is_Visible
24541 -- The currrent unit is directly visible
24546 elsif Unit_In_Context
(Curr
) then
24549 -- If the current unit is a body, check the context of the spec
24551 elsif Nkind
(Unit
(Curr
)) = N_Package_Body
24553 (Nkind
(Unit
(Curr
)) = N_Subprogram_Body
24554 and then not Acts_As_Spec
(Unit
(Curr
)))
24556 if Unit_In_Context
(Library_Unit
(Curr
)) then
24561 -- If the spec is a child unit, examine the parents
24563 if Is_Child_Unit
(Curr_Entity
) then
24564 if Nkind
(Unit
(Curr
)) in N_Unit_Body
then
24566 Unit_In_Parent_Context
24567 (Parent_Spec
(Unit
(Library_Unit
(Curr
))));
24569 return Unit_In_Parent_Context
(Parent_Spec
(Unit
(Curr
)));
24575 end Unit_Is_Visible
;
24577 ------------------------------
24578 -- Universal_Interpretation --
24579 ------------------------------
24581 function Universal_Interpretation
(Opnd
: Node_Id
) return Entity_Id
is
24582 Index
: Interp_Index
;
24586 -- The argument may be a formal parameter of an operator or subprogram
24587 -- with multiple interpretations, or else an expression for an actual.
24589 if Nkind
(Opnd
) = N_Defining_Identifier
24590 or else not Is_Overloaded
(Opnd
)
24592 if Etype
(Opnd
) = Universal_Integer
24593 or else Etype
(Opnd
) = Universal_Real
24595 return Etype
(Opnd
);
24601 Get_First_Interp
(Opnd
, Index
, It
);
24602 while Present
(It
.Typ
) loop
24603 if It
.Typ
= Universal_Integer
24604 or else It
.Typ
= Universal_Real
24609 Get_Next_Interp
(Index
, It
);
24614 end Universal_Interpretation
;
24620 function Unqualify
(Expr
: Node_Id
) return Node_Id
is
24622 -- Recurse to handle unlikely case of multiple levels of qualification
24624 if Nkind
(Expr
) = N_Qualified_Expression
then
24625 return Unqualify
(Expression
(Expr
));
24627 -- Normal case, not a qualified expression
24638 function Unqual_Conv
(Expr
: Node_Id
) return Node_Id
is
24640 -- Recurse to handle unlikely case of multiple levels of qualification
24641 -- and/or conversion.
24643 if Nkind_In
(Expr
, N_Qualified_Expression
,
24645 N_Unchecked_Type_Conversion
)
24647 return Unqual_Conv
(Expression
(Expr
));
24649 -- Normal case, not a qualified expression
24656 -----------------------
24657 -- Visible_Ancestors --
24658 -----------------------
24660 function Visible_Ancestors
(Typ
: Entity_Id
) return Elist_Id
is
24666 pragma Assert
(Is_Record_Type
(Typ
) and then Is_Tagged_Type
(Typ
));
24668 -- Collect all the parents and progenitors of Typ. If the full-view of
24669 -- private parents and progenitors is available then it is used to
24670 -- generate the list of visible ancestors; otherwise their partial
24671 -- view is added to the resulting list.
24676 Use_Full_View
=> True);
24680 Ifaces_List
=> List_2
,
24681 Exclude_Parents
=> True,
24682 Use_Full_View
=> True);
24684 -- Join the two lists. Avoid duplications because an interface may
24685 -- simultaneously be parent and progenitor of a type.
24687 Elmt
:= First_Elmt
(List_2
);
24688 while Present
(Elmt
) loop
24689 Append_Unique_Elmt
(Node
(Elmt
), List_1
);
24694 end Visible_Ancestors
;
24696 ----------------------
24697 -- Within_Init_Proc --
24698 ----------------------
24700 function Within_Init_Proc
return Boolean is
24704 S
:= Current_Scope
;
24705 while not Is_Overloadable
(S
) loop
24706 if S
= Standard_Standard
then
24713 return Is_Init_Proc
(S
);
24714 end Within_Init_Proc
;
24716 ---------------------------
24717 -- Within_Protected_Type --
24718 ---------------------------
24720 function Within_Protected_Type
(E
: Entity_Id
) return Boolean is
24721 Scop
: Entity_Id
:= Scope
(E
);
24724 while Present
(Scop
) loop
24725 if Ekind
(Scop
) = E_Protected_Type
then
24729 Scop
:= Scope
(Scop
);
24733 end Within_Protected_Type
;
24739 function Within_Scope
(E
: Entity_Id
; S
: Entity_Id
) return Boolean is
24741 return Scope_Within_Or_Same
(Scope
(E
), S
);
24744 ----------------------------
24745 -- Within_Subprogram_Call --
24746 ----------------------------
24748 function Within_Subprogram_Call
(N
: Node_Id
) return Boolean is
24752 -- Climb the parent chain looking for a function or procedure call
24755 while Present
(Par
) loop
24756 if Nkind_In
(Par
, N_Entry_Call_Statement
,
24758 N_Procedure_Call_Statement
)
24762 -- Prevent the search from going too far
24764 elsif Is_Body_Or_Package_Declaration
(Par
) then
24768 Par
:= Parent
(Par
);
24772 end Within_Subprogram_Call
;
24778 procedure Wrong_Type
(Expr
: Node_Id
; Expected_Type
: Entity_Id
) is
24779 Found_Type
: constant Entity_Id
:= First_Subtype
(Etype
(Expr
));
24780 Expec_Type
: constant Entity_Id
:= First_Subtype
(Expected_Type
);
24782 Matching_Field
: Entity_Id
;
24783 -- Entity to give a more precise suggestion on how to write a one-
24784 -- element positional aggregate.
24786 function Has_One_Matching_Field
return Boolean;
24787 -- Determines if Expec_Type is a record type with a single component or
24788 -- discriminant whose type matches the found type or is one dimensional
24789 -- array whose component type matches the found type. In the case of
24790 -- one discriminant, we ignore the variant parts. That's not accurate,
24791 -- but good enough for the warning.
24793 ----------------------------
24794 -- Has_One_Matching_Field --
24795 ----------------------------
24797 function Has_One_Matching_Field
return Boolean is
24801 Matching_Field
:= Empty
;
24803 if Is_Array_Type
(Expec_Type
)
24804 and then Number_Dimensions
(Expec_Type
) = 1
24805 and then Covers
(Etype
(Component_Type
(Expec_Type
)), Found_Type
)
24807 -- Use type name if available. This excludes multidimensional
24808 -- arrays and anonymous arrays.
24810 if Comes_From_Source
(Expec_Type
) then
24811 Matching_Field
:= Expec_Type
;
24813 -- For an assignment, use name of target
24815 elsif Nkind
(Parent
(Expr
)) = N_Assignment_Statement
24816 and then Is_Entity_Name
(Name
(Parent
(Expr
)))
24818 Matching_Field
:= Entity
(Name
(Parent
(Expr
)));
24823 elsif not Is_Record_Type
(Expec_Type
) then
24827 E
:= First_Entity
(Expec_Type
);
24832 elsif not Ekind_In
(E
, E_Discriminant
, E_Component
)
24833 or else Nam_In
(Chars
(E
), Name_uTag
, Name_uParent
)
24842 if not Covers
(Etype
(E
), Found_Type
) then
24845 elsif Present
(Next_Entity
(E
))
24846 and then (Ekind
(E
) = E_Component
24847 or else Ekind
(Next_Entity
(E
)) = E_Discriminant
)
24852 Matching_Field
:= E
;
24856 end Has_One_Matching_Field
;
24858 -- Start of processing for Wrong_Type
24861 -- Don't output message if either type is Any_Type, or if a message
24862 -- has already been posted for this node. We need to do the latter
24863 -- check explicitly (it is ordinarily done in Errout), because we
24864 -- are using ! to force the output of the error messages.
24866 if Expec_Type
= Any_Type
24867 or else Found_Type
= Any_Type
24868 or else Error_Posted
(Expr
)
24872 -- If one of the types is a Taft-Amendment type and the other it its
24873 -- completion, it must be an illegal use of a TAT in the spec, for
24874 -- which an error was already emitted. Avoid cascaded errors.
24876 elsif Is_Incomplete_Type
(Expec_Type
)
24877 and then Has_Completion_In_Body
(Expec_Type
)
24878 and then Full_View
(Expec_Type
) = Etype
(Expr
)
24882 elsif Is_Incomplete_Type
(Etype
(Expr
))
24883 and then Has_Completion_In_Body
(Etype
(Expr
))
24884 and then Full_View
(Etype
(Expr
)) = Expec_Type
24888 -- In an instance, there is an ongoing problem with completion of
24889 -- type derived from private types. Their structure is what Gigi
24890 -- expects, but the Etype is the parent type rather than the
24891 -- derived private type itself. Do not flag error in this case. The
24892 -- private completion is an entity without a parent, like an Itype.
24893 -- Similarly, full and partial views may be incorrect in the instance.
24894 -- There is no simple way to insure that it is consistent ???
24896 -- A similar view discrepancy can happen in an inlined body, for the
24897 -- same reason: inserted body may be outside of the original package
24898 -- and only partial views are visible at the point of insertion.
24900 elsif In_Instance
or else In_Inlined_Body
then
24901 if Etype
(Etype
(Expr
)) = Etype
(Expected_Type
)
24903 (Has_Private_Declaration
(Expected_Type
)
24904 or else Has_Private_Declaration
(Etype
(Expr
)))
24905 and then No
(Parent
(Expected_Type
))
24909 elsif Nkind
(Parent
(Expr
)) = N_Qualified_Expression
24910 and then Entity
(Subtype_Mark
(Parent
(Expr
))) = Expected_Type
24914 elsif Is_Private_Type
(Expected_Type
)
24915 and then Present
(Full_View
(Expected_Type
))
24916 and then Covers
(Full_View
(Expected_Type
), Etype
(Expr
))
24920 -- Conversely, type of expression may be the private one
24922 elsif Is_Private_Type
(Base_Type
(Etype
(Expr
)))
24923 and then Full_View
(Base_Type
(Etype
(Expr
))) = Expected_Type
24929 -- An interesting special check. If the expression is parenthesized
24930 -- and its type corresponds to the type of the sole component of the
24931 -- expected record type, or to the component type of the expected one
24932 -- dimensional array type, then assume we have a bad aggregate attempt.
24934 if Nkind
(Expr
) in N_Subexpr
24935 and then Paren_Count
(Expr
) /= 0
24936 and then Has_One_Matching_Field
24938 Error_Msg_N
("positional aggregate cannot have one component", Expr
);
24940 if Present
(Matching_Field
) then
24941 if Is_Array_Type
(Expec_Type
) then
24943 ("\write instead `&''First ='> ...`", Expr
, Matching_Field
);
24946 ("\write instead `& ='> ...`", Expr
, Matching_Field
);
24950 -- Another special check, if we are looking for a pool-specific access
24951 -- type and we found an E_Access_Attribute_Type, then we have the case
24952 -- of an Access attribute being used in a context which needs a pool-
24953 -- specific type, which is never allowed. The one extra check we make
24954 -- is that the expected designated type covers the Found_Type.
24956 elsif Is_Access_Type
(Expec_Type
)
24957 and then Ekind
(Found_Type
) = E_Access_Attribute_Type
24958 and then Ekind
(Base_Type
(Expec_Type
)) /= E_General_Access_Type
24959 and then Ekind
(Base_Type
(Expec_Type
)) /= E_Anonymous_Access_Type
24961 (Designated_Type
(Expec_Type
), Designated_Type
(Found_Type
))
24963 Error_Msg_N
-- CODEFIX
24964 ("result must be general access type!", Expr
);
24965 Error_Msg_NE
-- CODEFIX
24966 ("add ALL to }!", Expr
, Expec_Type
);
24968 -- Another special check, if the expected type is an integer type,
24969 -- but the expression is of type System.Address, and the parent is
24970 -- an addition or subtraction operation whose left operand is the
24971 -- expression in question and whose right operand is of an integral
24972 -- type, then this is an attempt at address arithmetic, so give
24973 -- appropriate message.
24975 elsif Is_Integer_Type
(Expec_Type
)
24976 and then Is_RTE
(Found_Type
, RE_Address
)
24977 and then Nkind_In
(Parent
(Expr
), N_Op_Add
, N_Op_Subtract
)
24978 and then Expr
= Left_Opnd
(Parent
(Expr
))
24979 and then Is_Integer_Type
(Etype
(Right_Opnd
(Parent
(Expr
))))
24982 ("address arithmetic not predefined in package System",
24985 ("\possible missing with/use of System.Storage_Elements",
24989 -- If the expected type is an anonymous access type, as for access
24990 -- parameters and discriminants, the error is on the designated types.
24992 elsif Ekind
(Expec_Type
) = E_Anonymous_Access_Type
then
24993 if Comes_From_Source
(Expec_Type
) then
24994 Error_Msg_NE
("expected}!", Expr
, Expec_Type
);
24997 ("expected an access type with designated}",
24998 Expr
, Designated_Type
(Expec_Type
));
25001 if Is_Access_Type
(Found_Type
)
25002 and then not Comes_From_Source
(Found_Type
)
25005 ("\\found an access type with designated}!",
25006 Expr
, Designated_Type
(Found_Type
));
25008 if From_Limited_With
(Found_Type
) then
25009 Error_Msg_NE
("\\found incomplete}!", Expr
, Found_Type
);
25010 Error_Msg_Qual_Level
:= 99;
25011 Error_Msg_NE
-- CODEFIX
25012 ("\\missing `WITH &;", Expr
, Scope
(Found_Type
));
25013 Error_Msg_Qual_Level
:= 0;
25015 Error_Msg_NE
("found}!", Expr
, Found_Type
);
25019 -- Normal case of one type found, some other type expected
25022 -- If the names of the two types are the same, see if some number
25023 -- of levels of qualification will help. Don't try more than three
25024 -- levels, and if we get to standard, it's no use (and probably
25025 -- represents an error in the compiler) Also do not bother with
25026 -- internal scope names.
25029 Expec_Scope
: Entity_Id
;
25030 Found_Scope
: Entity_Id
;
25033 Expec_Scope
:= Expec_Type
;
25034 Found_Scope
:= Found_Type
;
25036 for Levels
in Nat
range 0 .. 3 loop
25037 if Chars
(Expec_Scope
) /= Chars
(Found_Scope
) then
25038 Error_Msg_Qual_Level
:= Levels
;
25042 Expec_Scope
:= Scope
(Expec_Scope
);
25043 Found_Scope
:= Scope
(Found_Scope
);
25045 exit when Expec_Scope
= Standard_Standard
25046 or else Found_Scope
= Standard_Standard
25047 or else not Comes_From_Source
(Expec_Scope
)
25048 or else not Comes_From_Source
(Found_Scope
);
25052 if Is_Record_Type
(Expec_Type
)
25053 and then Present
(Corresponding_Remote_Type
(Expec_Type
))
25055 Error_Msg_NE
("expected}!", Expr
,
25056 Corresponding_Remote_Type
(Expec_Type
));
25058 Error_Msg_NE
("expected}!", Expr
, Expec_Type
);
25061 if Is_Entity_Name
(Expr
)
25062 and then Is_Package_Or_Generic_Package
(Entity
(Expr
))
25064 Error_Msg_N
("\\found package name!", Expr
);
25066 elsif Is_Entity_Name
(Expr
)
25067 and then Ekind_In
(Entity
(Expr
), E_Procedure
, E_Generic_Procedure
)
25069 if Ekind
(Expec_Type
) = E_Access_Subprogram_Type
then
25071 ("found procedure name, possibly missing Access attribute!",
25075 ("\\found procedure name instead of function!", Expr
);
25078 elsif Nkind
(Expr
) = N_Function_Call
25079 and then Ekind
(Expec_Type
) = E_Access_Subprogram_Type
25080 and then Etype
(Designated_Type
(Expec_Type
)) = Etype
(Expr
)
25081 and then No
(Parameter_Associations
(Expr
))
25084 ("found function name, possibly missing Access attribute!",
25087 -- Catch common error: a prefix or infix operator which is not
25088 -- directly visible because the type isn't.
25090 elsif Nkind
(Expr
) in N_Op
25091 and then Is_Overloaded
(Expr
)
25092 and then not Is_Immediately_Visible
(Expec_Type
)
25093 and then not Is_Potentially_Use_Visible
(Expec_Type
)
25094 and then not In_Use
(Expec_Type
)
25095 and then Has_Compatible_Type
(Right_Opnd
(Expr
), Expec_Type
)
25098 ("operator of the type is not directly visible!", Expr
);
25100 elsif Ekind
(Found_Type
) = E_Void
25101 and then Present
(Parent
(Found_Type
))
25102 and then Nkind
(Parent
(Found_Type
)) = N_Full_Type_Declaration
25104 Error_Msg_NE
("\\found premature usage of}!", Expr
, Found_Type
);
25107 Error_Msg_NE
("\\found}!", Expr
, Found_Type
);
25110 -- A special check for cases like M1 and M2 = 0 where M1 and M2 are
25111 -- of the same modular type, and (M1 and M2) = 0 was intended.
25113 if Expec_Type
= Standard_Boolean
25114 and then Is_Modular_Integer_Type
(Found_Type
)
25115 and then Nkind_In
(Parent
(Expr
), N_Op_And
, N_Op_Or
, N_Op_Xor
)
25116 and then Nkind
(Right_Opnd
(Parent
(Expr
))) in N_Op_Compare
25119 Op
: constant Node_Id
:= Right_Opnd
(Parent
(Expr
));
25120 L
: constant Node_Id
:= Left_Opnd
(Op
);
25121 R
: constant Node_Id
:= Right_Opnd
(Op
);
25124 -- The case for the message is when the left operand of the
25125 -- comparison is the same modular type, or when it is an
25126 -- integer literal (or other universal integer expression),
25127 -- which would have been typed as the modular type if the
25128 -- parens had been there.
25130 if (Etype
(L
) = Found_Type
25132 Etype
(L
) = Universal_Integer
)
25133 and then Is_Integer_Type
(Etype
(R
))
25136 ("\\possible missing parens for modular operation", Expr
);
25141 -- Reset error message qualification indication
25143 Error_Msg_Qual_Level
:= 0;
25147 --------------------------------
25148 -- Yields_Synchronized_Object --
25149 --------------------------------
25151 function Yields_Synchronized_Object
(Typ
: Entity_Id
) return Boolean is
25152 Has_Sync_Comp
: Boolean := False;
25156 -- An array type yields a synchronized object if its component type
25157 -- yields a synchronized object.
25159 if Is_Array_Type
(Typ
) then
25160 return Yields_Synchronized_Object
(Component_Type
(Typ
));
25162 -- A descendant of type Ada.Synchronous_Task_Control.Suspension_Object
25163 -- yields a synchronized object by default.
25165 elsif Is_Descendant_Of_Suspension_Object
(Typ
) then
25168 -- A protected type yields a synchronized object by default
25170 elsif Is_Protected_Type
(Typ
) then
25173 -- A record type or type extension yields a synchronized object when its
25174 -- discriminants (if any) lack default values and all components are of
25175 -- a type that yelds a synchronized object.
25177 elsif Is_Record_Type
(Typ
) then
25179 -- Inspect all entities defined in the scope of the type, looking for
25180 -- components of a type that does not yeld a synchronized object or
25181 -- for discriminants with default values.
25183 Id
:= First_Entity
(Typ
);
25184 while Present
(Id
) loop
25185 if Comes_From_Source
(Id
) then
25186 if Ekind
(Id
) = E_Component
then
25187 if Yields_Synchronized_Object
(Etype
(Id
)) then
25188 Has_Sync_Comp
:= True;
25190 -- The component does not yield a synchronized object
25196 elsif Ekind
(Id
) = E_Discriminant
25197 and then Present
(Expression
(Parent
(Id
)))
25206 -- Ensure that the parent type of a type extension yields a
25207 -- synchronized object.
25209 if Etype
(Typ
) /= Typ
25210 and then not Yields_Synchronized_Object
(Etype
(Typ
))
25215 -- If we get here, then all discriminants lack default values and all
25216 -- components are of a type that yields a synchronized object.
25218 return Has_Sync_Comp
;
25220 -- A synchronized interface type yields a synchronized object by default
25222 elsif Is_Synchronized_Interface
(Typ
) then
25225 -- A task type yelds a synchronized object by default
25227 elsif Is_Task_Type
(Typ
) then
25230 -- Otherwise the type does not yield a synchronized object
25235 end Yields_Synchronized_Object
;
25237 ---------------------------
25238 -- Yields_Universal_Type --
25239 ---------------------------
25241 function Yields_Universal_Type
(N
: Node_Id
) return Boolean is
25243 -- Integer and real literals are of a universal type
25245 if Nkind_In
(N
, N_Integer_Literal
, N_Real_Literal
) then
25248 -- The values of certain attributes are of a universal type
25250 elsif Nkind
(N
) = N_Attribute_Reference
then
25252 Universal_Type_Attribute
(Get_Attribute_Id
(Attribute_Name
(N
)));
25254 -- ??? There are possibly other cases to consider
25259 end Yields_Universal_Type
;
25262 Erroutc
.Subprogram_Name_Ptr
:= Subprogram_Name
'Access;