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
);
9089 -- Position in the enumeration type starts at 0.
9090 if UI_To_Int
(Pos
) < 0 then
9091 raise Constraint_Error
;
9094 for J
in 1 .. UI_To_Int
(Pos
) loop
9097 -- If Lit is Empty, Pos is not in range, so raise Constraint_Error
9098 -- inside the loop to avoid calling Next_Literal on Empty.
9101 raise Constraint_Error
;
9105 -- Create a new node from Lit, with source location provided by Loc
9106 -- if not equal to No_Location, or by copying the source location of
9111 if LLoc
= No_Location
then
9115 return New_Occurrence_Of
(Lit
, LLoc
);
9117 end Get_Enum_Lit_From_Pos
;
9119 ------------------------
9120 -- Get_Generic_Entity --
9121 ------------------------
9123 function Get_Generic_Entity
(N
: Node_Id
) return Entity_Id
is
9124 Ent
: constant Entity_Id
:= Entity
(Name
(N
));
9126 if Present
(Renamed_Object
(Ent
)) then
9127 return Renamed_Object
(Ent
);
9131 end Get_Generic_Entity
;
9133 -------------------------------------
9134 -- Get_Incomplete_View_Of_Ancestor --
9135 -------------------------------------
9137 function Get_Incomplete_View_Of_Ancestor
(E
: Entity_Id
) return Entity_Id
is
9138 Cur_Unit
: constant Entity_Id
:= Cunit_Entity
(Current_Sem_Unit
);
9139 Par_Scope
: Entity_Id
;
9140 Par_Type
: Entity_Id
;
9143 -- The incomplete view of an ancestor is only relevant for private
9144 -- derived types in child units.
9146 if not Is_Derived_Type
(E
)
9147 or else not Is_Child_Unit
(Cur_Unit
)
9152 Par_Scope
:= Scope
(Cur_Unit
);
9153 if No
(Par_Scope
) then
9157 Par_Type
:= Etype
(Base_Type
(E
));
9159 -- Traverse list of ancestor types until we find one declared in
9160 -- a parent or grandparent unit (two levels seem sufficient).
9162 while Present
(Par_Type
) loop
9163 if Scope
(Par_Type
) = Par_Scope
9164 or else Scope
(Par_Type
) = Scope
(Par_Scope
)
9168 elsif not Is_Derived_Type
(Par_Type
) then
9172 Par_Type
:= Etype
(Base_Type
(Par_Type
));
9176 -- If none found, there is no relevant ancestor type.
9180 end Get_Incomplete_View_Of_Ancestor
;
9182 ----------------------
9183 -- Get_Index_Bounds --
9184 ----------------------
9186 procedure Get_Index_Bounds
9190 Use_Full_View
: Boolean := False)
9192 function Scalar_Range_Of_Type
(Typ
: Entity_Id
) return Node_Id
;
9193 -- Obtain the scalar range of type Typ. If flag Use_Full_View is set and
9194 -- Typ qualifies, the scalar range is obtained from the full view of the
9197 --------------------------
9198 -- Scalar_Range_Of_Type --
9199 --------------------------
9201 function Scalar_Range_Of_Type
(Typ
: Entity_Id
) return Node_Id
is
9202 T
: Entity_Id
:= Typ
;
9205 if Use_Full_View
and then Present
(Full_View
(T
)) then
9209 return Scalar_Range
(T
);
9210 end Scalar_Range_Of_Type
;
9214 Kind
: constant Node_Kind
:= Nkind
(N
);
9217 -- Start of processing for Get_Index_Bounds
9220 if Kind
= N_Range
then
9222 H
:= High_Bound
(N
);
9224 elsif Kind
= N_Subtype_Indication
then
9225 Rng
:= Range_Expression
(Constraint
(N
));
9233 L
:= Low_Bound
(Range_Expression
(Constraint
(N
)));
9234 H
:= High_Bound
(Range_Expression
(Constraint
(N
)));
9237 elsif Is_Entity_Name
(N
) and then Is_Type
(Entity
(N
)) then
9238 Rng
:= Scalar_Range_Of_Type
(Entity
(N
));
9240 if Error_Posted
(Rng
) then
9244 elsif Nkind
(Rng
) = N_Subtype_Indication
then
9245 Get_Index_Bounds
(Rng
, L
, H
);
9248 L
:= Low_Bound
(Rng
);
9249 H
:= High_Bound
(Rng
);
9253 -- N is an expression, indicating a range with one value
9258 end Get_Index_Bounds
;
9260 -----------------------------
9261 -- Get_Interfacing_Aspects --
9262 -----------------------------
9264 procedure Get_Interfacing_Aspects
9265 (Iface_Asp
: Node_Id
;
9266 Conv_Asp
: out Node_Id
;
9267 EN_Asp
: out Node_Id
;
9268 Expo_Asp
: out Node_Id
;
9269 Imp_Asp
: out Node_Id
;
9270 LN_Asp
: out Node_Id
;
9271 Do_Checks
: Boolean := False)
9273 procedure Save_Or_Duplication_Error
9275 To
: in out Node_Id
);
9276 -- Save the value of aspect Asp in node To. If To already has a value,
9277 -- then this is considered a duplicate use of aspect. Emit an error if
9278 -- flag Do_Checks is set.
9280 -------------------------------
9281 -- Save_Or_Duplication_Error --
9282 -------------------------------
9284 procedure Save_Or_Duplication_Error
9286 To
: in out Node_Id
)
9289 -- Detect an extra aspect and issue an error
9291 if Present
(To
) then
9293 Error_Msg_Name_1
:= Chars
(Identifier
(Asp
));
9294 Error_Msg_Sloc
:= Sloc
(To
);
9295 Error_Msg_N
("aspect % previously given #", Asp
);
9298 -- Otherwise capture the aspect
9303 end Save_Or_Duplication_Error
;
9310 -- The following variables capture each individual aspect
9312 Conv
: Node_Id
:= Empty
;
9313 EN
: Node_Id
:= Empty
;
9314 Expo
: Node_Id
:= Empty
;
9315 Imp
: Node_Id
:= Empty
;
9316 LN
: Node_Id
:= Empty
;
9318 -- Start of processing for Get_Interfacing_Aspects
9321 -- The input interfacing aspect should reside in an aspect specification
9324 pragma Assert
(Is_List_Member
(Iface_Asp
));
9326 -- Examine the aspect specifications of the related entity. Find and
9327 -- capture all interfacing aspects. Detect duplicates and emit errors
9330 Asp
:= First
(List_Containing
(Iface_Asp
));
9331 while Present
(Asp
) loop
9332 Asp_Id
:= Get_Aspect_Id
(Asp
);
9334 if Asp_Id
= Aspect_Convention
then
9335 Save_Or_Duplication_Error
(Asp
, Conv
);
9337 elsif Asp_Id
= Aspect_External_Name
then
9338 Save_Or_Duplication_Error
(Asp
, EN
);
9340 elsif Asp_Id
= Aspect_Export
then
9341 Save_Or_Duplication_Error
(Asp
, Expo
);
9343 elsif Asp_Id
= Aspect_Import
then
9344 Save_Or_Duplication_Error
(Asp
, Imp
);
9346 elsif Asp_Id
= Aspect_Link_Name
then
9347 Save_Or_Duplication_Error
(Asp
, LN
);
9358 end Get_Interfacing_Aspects
;
9360 ---------------------------------
9361 -- Get_Iterable_Type_Primitive --
9362 ---------------------------------
9364 function Get_Iterable_Type_Primitive
9366 Nam
: Name_Id
) return Entity_Id
9368 Funcs
: constant Node_Id
:= Find_Value_Of_Aspect
(Typ
, Aspect_Iterable
);
9376 Assoc
:= First
(Component_Associations
(Funcs
));
9377 while Present
(Assoc
) loop
9378 if Chars
(First
(Choices
(Assoc
))) = Nam
then
9379 return Entity
(Expression
(Assoc
));
9382 Assoc
:= Next
(Assoc
);
9387 end Get_Iterable_Type_Primitive
;
9389 ----------------------------------
9390 -- Get_Library_Unit_Name_string --
9391 ----------------------------------
9393 procedure Get_Library_Unit_Name_String
(Decl_Node
: Node_Id
) is
9394 Unit_Name_Id
: constant Unit_Name_Type
:= Get_Unit_Name
(Decl_Node
);
9397 Get_Unit_Name_String
(Unit_Name_Id
);
9399 -- Remove seven last character (" (spec)" or " (body)")
9401 Name_Len
:= Name_Len
- 7;
9402 pragma Assert
(Name_Buffer
(Name_Len
+ 1) = ' ');
9403 end Get_Library_Unit_Name_String
;
9405 --------------------------
9406 -- Get_Max_Queue_Length --
9407 --------------------------
9409 function Get_Max_Queue_Length
(Id
: Entity_Id
) return Uint
is
9410 pragma Assert
(Is_Entry
(Id
));
9411 Prag
: constant Entity_Id
:= Get_Pragma
(Id
, Pragma_Max_Queue_Length
);
9414 -- A value of 0 represents no maximum specified, and entries and entry
9415 -- families with no Max_Queue_Length aspect or pragma default to it.
9417 if not Present
(Prag
) then
9421 return Intval
(Expression
(First
(Pragma_Argument_Associations
(Prag
))));
9422 end Get_Max_Queue_Length
;
9424 ------------------------
9425 -- Get_Name_Entity_Id --
9426 ------------------------
9428 function Get_Name_Entity_Id
(Id
: Name_Id
) return Entity_Id
is
9430 return Entity_Id
(Get_Name_Table_Int
(Id
));
9431 end Get_Name_Entity_Id
;
9433 ------------------------------
9434 -- Get_Name_From_CTC_Pragma --
9435 ------------------------------
9437 function Get_Name_From_CTC_Pragma
(N
: Node_Id
) return String_Id
is
9438 Arg
: constant Node_Id
:=
9439 Get_Pragma_Arg
(First
(Pragma_Argument_Associations
(N
)));
9441 return Strval
(Expr_Value_S
(Arg
));
9442 end Get_Name_From_CTC_Pragma
;
9444 -----------------------
9445 -- Get_Parent_Entity --
9446 -----------------------
9448 function Get_Parent_Entity
(Unit
: Node_Id
) return Entity_Id
is
9450 if Nkind
(Unit
) = N_Package_Body
9451 and then Nkind
(Original_Node
(Unit
)) = N_Package_Instantiation
9453 return Defining_Entity
9454 (Specification
(Instance_Spec
(Original_Node
(Unit
))));
9455 elsif Nkind
(Unit
) = N_Package_Instantiation
then
9456 return Defining_Entity
(Specification
(Instance_Spec
(Unit
)));
9458 return Defining_Entity
(Unit
);
9460 end Get_Parent_Entity
;
9466 function Get_Pragma_Id
(N
: Node_Id
) return Pragma_Id
is
9468 return Get_Pragma_Id
(Pragma_Name_Unmapped
(N
));
9471 ------------------------
9472 -- Get_Qualified_Name --
9473 ------------------------
9475 function Get_Qualified_Name
9477 Suffix
: Entity_Id
:= Empty
) return Name_Id
9479 Suffix_Nam
: Name_Id
:= No_Name
;
9482 if Present
(Suffix
) then
9483 Suffix_Nam
:= Chars
(Suffix
);
9486 return Get_Qualified_Name
(Chars
(Id
), Suffix_Nam
, Scope
(Id
));
9487 end Get_Qualified_Name
;
9489 function Get_Qualified_Name
9491 Suffix
: Name_Id
:= No_Name
;
9492 Scop
: Entity_Id
:= Current_Scope
) return Name_Id
9494 procedure Add_Scope
(S
: Entity_Id
);
9495 -- Add the fully qualified form of scope S to the name buffer. The
9503 procedure Add_Scope
(S
: Entity_Id
) is
9508 elsif S
= Standard_Standard
then
9512 Add_Scope
(Scope
(S
));
9513 Get_Name_String_And_Append
(Chars
(S
));
9514 Add_Str_To_Name_Buffer
("__");
9518 -- Start of processing for Get_Qualified_Name
9524 -- Append the base name after all scopes have been chained
9526 Get_Name_String_And_Append
(Nam
);
9528 -- Append the suffix (if present)
9530 if Suffix
/= No_Name
then
9531 Add_Str_To_Name_Buffer
("__");
9532 Get_Name_String_And_Append
(Suffix
);
9536 end Get_Qualified_Name
;
9538 -----------------------
9539 -- Get_Reason_String --
9540 -----------------------
9542 procedure Get_Reason_String
(N
: Node_Id
) is
9544 if Nkind
(N
) = N_String_Literal
then
9545 Store_String_Chars
(Strval
(N
));
9547 elsif Nkind
(N
) = N_Op_Concat
then
9548 Get_Reason_String
(Left_Opnd
(N
));
9549 Get_Reason_String
(Right_Opnd
(N
));
9551 -- If not of required form, error
9555 ("Reason for pragma Warnings has wrong form", N
);
9557 ("\must be string literal or concatenation of string literals", N
);
9560 end Get_Reason_String
;
9562 --------------------------------
9563 -- Get_Reference_Discriminant --
9564 --------------------------------
9566 function Get_Reference_Discriminant
(Typ
: Entity_Id
) return Entity_Id
is
9570 D
:= First_Discriminant
(Typ
);
9571 while Present
(D
) loop
9572 if Has_Implicit_Dereference
(D
) then
9575 Next_Discriminant
(D
);
9579 end Get_Reference_Discriminant
;
9581 ---------------------------
9582 -- Get_Referenced_Object --
9583 ---------------------------
9585 function Get_Referenced_Object
(N
: Node_Id
) return Node_Id
is
9590 while Is_Entity_Name
(R
)
9591 and then Present
(Renamed_Object
(Entity
(R
)))
9593 R
:= Renamed_Object
(Entity
(R
));
9597 end Get_Referenced_Object
;
9599 ------------------------
9600 -- Get_Renamed_Entity --
9601 ------------------------
9603 function Get_Renamed_Entity
(E
: Entity_Id
) return Entity_Id
is
9608 while Present
(Renamed_Entity
(R
)) loop
9609 R
:= Renamed_Entity
(R
);
9613 end Get_Renamed_Entity
;
9615 -----------------------
9616 -- Get_Return_Object --
9617 -----------------------
9619 function Get_Return_Object
(N
: Node_Id
) return Entity_Id
is
9623 Decl
:= First
(Return_Object_Declarations
(N
));
9624 while Present
(Decl
) loop
9625 exit when Nkind
(Decl
) = N_Object_Declaration
9626 and then Is_Return_Object
(Defining_Identifier
(Decl
));
9630 pragma Assert
(Present
(Decl
));
9631 return Defining_Identifier
(Decl
);
9632 end Get_Return_Object
;
9634 ---------------------------
9635 -- Get_Subprogram_Entity --
9636 ---------------------------
9638 function Get_Subprogram_Entity
(Nod
: Node_Id
) return Entity_Id
is
9640 Subp_Id
: Entity_Id
;
9643 if Nkind
(Nod
) = N_Accept_Statement
then
9644 Subp
:= Entry_Direct_Name
(Nod
);
9646 elsif Nkind
(Nod
) = N_Slice
then
9647 Subp
:= Prefix
(Nod
);
9653 -- Strip the subprogram call
9656 if Nkind_In
(Subp
, N_Explicit_Dereference
,
9657 N_Indexed_Component
,
9658 N_Selected_Component
)
9660 Subp
:= Prefix
(Subp
);
9662 elsif Nkind_In
(Subp
, N_Type_Conversion
,
9663 N_Unchecked_Type_Conversion
)
9665 Subp
:= Expression
(Subp
);
9672 -- Extract the entity of the subprogram call
9674 if Is_Entity_Name
(Subp
) then
9675 Subp_Id
:= Entity
(Subp
);
9677 if Ekind
(Subp_Id
) = E_Access_Subprogram_Type
then
9678 Subp_Id
:= Directly_Designated_Type
(Subp_Id
);
9681 if Is_Subprogram
(Subp_Id
) then
9687 -- The search did not find a construct that denotes a subprogram
9692 end Get_Subprogram_Entity
;
9694 -----------------------------
9695 -- Get_Task_Body_Procedure --
9696 -----------------------------
9698 function Get_Task_Body_Procedure
(E
: Entity_Id
) return Entity_Id
is
9700 -- Note: A task type may be the completion of a private type with
9701 -- discriminants. When performing elaboration checks on a task
9702 -- declaration, the current view of the type may be the private one,
9703 -- and the procedure that holds the body of the task is held in its
9706 -- This is an odd function, why not have Task_Body_Procedure do
9707 -- the following digging???
9709 return Task_Body_Procedure
(Underlying_Type
(Root_Type
(E
)));
9710 end Get_Task_Body_Procedure
;
9712 -------------------------
9713 -- Get_User_Defined_Eq --
9714 -------------------------
9716 function Get_User_Defined_Eq
(E
: Entity_Id
) return Entity_Id
is
9721 Prim
:= First_Elmt
(Collect_Primitive_Operations
(E
));
9722 while Present
(Prim
) loop
9725 if Chars
(Op
) = Name_Op_Eq
9726 and then Etype
(Op
) = Standard_Boolean
9727 and then Etype
(First_Formal
(Op
)) = E
9728 and then Etype
(Next_Formal
(First_Formal
(Op
))) = E
9737 end Get_User_Defined_Eq
;
9745 Priv_Typ
: out Entity_Id
;
9746 Full_Typ
: out Entity_Id
;
9747 Full_Base
: out Entity_Id
;
9748 CRec_Typ
: out Entity_Id
)
9750 IP_View
: Entity_Id
;
9753 -- Assume that none of the views can be recovered
9760 -- The input type is the corresponding record type of a protected or a
9763 if Ekind
(Typ
) = E_Record_Type
9764 and then Is_Concurrent_Record_Type
(Typ
)
9767 Full_Typ
:= Corresponding_Concurrent_Type
(CRec_Typ
);
9768 Full_Base
:= Base_Type
(Full_Typ
);
9769 Priv_Typ
:= Incomplete_Or_Partial_View
(Full_Typ
);
9771 -- Otherwise the input type denotes an arbitrary type
9774 IP_View
:= Incomplete_Or_Partial_View
(Typ
);
9776 -- The input type denotes the full view of a private type
9778 if Present
(IP_View
) then
9779 Priv_Typ
:= IP_View
;
9782 -- The input type is a private type
9784 elsif Is_Private_Type
(Typ
) then
9786 Full_Typ
:= Full_View
(Priv_Typ
);
9788 -- Otherwise the input type does not have any views
9794 if Present
(Full_Typ
) then
9795 Full_Base
:= Base_Type
(Full_Typ
);
9797 if Ekind_In
(Full_Typ
, E_Protected_Type
, E_Task_Type
) then
9798 CRec_Typ
:= Corresponding_Record_Type
(Full_Typ
);
9804 -----------------------
9805 -- Has_Access_Values --
9806 -----------------------
9808 function Has_Access_Values
(T
: Entity_Id
) return Boolean is
9809 Typ
: constant Entity_Id
:= Underlying_Type
(T
);
9812 -- Case of a private type which is not completed yet. This can only
9813 -- happen in the case of a generic format type appearing directly, or
9814 -- as a component of the type to which this function is being applied
9815 -- at the top level. Return False in this case, since we certainly do
9816 -- not know that the type contains access types.
9821 elsif Is_Access_Type
(Typ
) then
9824 elsif Is_Array_Type
(Typ
) then
9825 return Has_Access_Values
(Component_Type
(Typ
));
9827 elsif Is_Record_Type
(Typ
) then
9832 -- Loop to Check components
9834 Comp
:= First_Component_Or_Discriminant
(Typ
);
9835 while Present
(Comp
) loop
9837 -- Check for access component, tag field does not count, even
9838 -- though it is implemented internally using an access type.
9840 if Has_Access_Values
(Etype
(Comp
))
9841 and then Chars
(Comp
) /= Name_uTag
9846 Next_Component_Or_Discriminant
(Comp
);
9855 end Has_Access_Values
;
9857 ------------------------------
9858 -- Has_Compatible_Alignment --
9859 ------------------------------
9861 function Has_Compatible_Alignment
9864 Layout_Done
: Boolean) return Alignment_Result
9866 function Has_Compatible_Alignment_Internal
9869 Layout_Done
: Boolean;
9870 Default
: Alignment_Result
) return Alignment_Result
;
9871 -- This is the internal recursive function that actually does the work.
9872 -- There is one additional parameter, which says what the result should
9873 -- be if no alignment information is found, and there is no definite
9874 -- indication of compatible alignments. At the outer level, this is set
9875 -- to Unknown, but for internal recursive calls in the case where types
9876 -- are known to be correct, it is set to Known_Compatible.
9878 ---------------------------------------
9879 -- Has_Compatible_Alignment_Internal --
9880 ---------------------------------------
9882 function Has_Compatible_Alignment_Internal
9885 Layout_Done
: Boolean;
9886 Default
: Alignment_Result
) return Alignment_Result
9888 Result
: Alignment_Result
:= Known_Compatible
;
9889 -- Holds the current status of the result. Note that once a value of
9890 -- Known_Incompatible is set, it is sticky and does not get changed
9891 -- to Unknown (the value in Result only gets worse as we go along,
9894 Offs
: Uint
:= No_Uint
;
9895 -- Set to a factor of the offset from the base object when Expr is a
9896 -- selected or indexed component, based on Component_Bit_Offset and
9897 -- Component_Size respectively. A negative value is used to represent
9898 -- a value which is not known at compile time.
9900 procedure Check_Prefix
;
9901 -- Checks the prefix recursively in the case where the expression
9902 -- is an indexed or selected component.
9904 procedure Set_Result
(R
: Alignment_Result
);
9905 -- If R represents a worse outcome (unknown instead of known
9906 -- compatible, or known incompatible), then set Result to R.
9912 procedure Check_Prefix
is
9914 -- The subtlety here is that in doing a recursive call to check
9915 -- the prefix, we have to decide what to do in the case where we
9916 -- don't find any specific indication of an alignment problem.
9918 -- At the outer level, we normally set Unknown as the result in
9919 -- this case, since we can only set Known_Compatible if we really
9920 -- know that the alignment value is OK, but for the recursive
9921 -- call, in the case where the types match, and we have not
9922 -- specified a peculiar alignment for the object, we are only
9923 -- concerned about suspicious rep clauses, the default case does
9924 -- not affect us, since the compiler will, in the absence of such
9925 -- rep clauses, ensure that the alignment is correct.
9927 if Default
= Known_Compatible
9929 (Etype
(Obj
) = Etype
(Expr
)
9930 and then (Unknown_Alignment
(Obj
)
9932 Alignment
(Obj
) = Alignment
(Etype
(Obj
))))
9935 (Has_Compatible_Alignment_Internal
9936 (Obj
, Prefix
(Expr
), Layout_Done
, Known_Compatible
));
9938 -- In all other cases, we need a full check on the prefix
9942 (Has_Compatible_Alignment_Internal
9943 (Obj
, Prefix
(Expr
), Layout_Done
, Unknown
));
9951 procedure Set_Result
(R
: Alignment_Result
) is
9958 -- Start of processing for Has_Compatible_Alignment_Internal
9961 -- If Expr is a selected component, we must make sure there is no
9962 -- potentially troublesome component clause and that the record is
9963 -- not packed if the layout is not done.
9965 if Nkind
(Expr
) = N_Selected_Component
then
9967 -- Packing generates unknown alignment if layout is not done
9969 if Is_Packed
(Etype
(Prefix
(Expr
))) and then not Layout_Done
then
9970 Set_Result
(Unknown
);
9973 -- Check prefix and component offset
9976 Offs
:= Component_Bit_Offset
(Entity
(Selector_Name
(Expr
)));
9978 -- If Expr is an indexed component, we must make sure there is no
9979 -- potentially troublesome Component_Size clause and that the array
9980 -- is not bit-packed if the layout is not done.
9982 elsif Nkind
(Expr
) = N_Indexed_Component
then
9984 Typ
: constant Entity_Id
:= Etype
(Prefix
(Expr
));
9987 -- Packing generates unknown alignment if layout is not done
9989 if Is_Bit_Packed_Array
(Typ
) and then not Layout_Done
then
9990 Set_Result
(Unknown
);
9993 -- Check prefix and component offset (or at least size)
9996 Offs
:= Indexed_Component_Bit_Offset
(Expr
);
9997 if Offs
= No_Uint
then
9998 Offs
:= Component_Size
(Typ
);
10003 -- If we have a null offset, the result is entirely determined by
10004 -- the base object and has already been computed recursively.
10006 if Offs
= Uint_0
then
10009 -- Case where we know the alignment of the object
10011 elsif Known_Alignment
(Obj
) then
10013 ObjA
: constant Uint
:= Alignment
(Obj
);
10014 ExpA
: Uint
:= No_Uint
;
10015 SizA
: Uint
:= No_Uint
;
10018 -- If alignment of Obj is 1, then we are always OK
10021 Set_Result
(Known_Compatible
);
10023 -- Alignment of Obj is greater than 1, so we need to check
10026 -- If we have an offset, see if it is compatible
10028 if Offs
/= No_Uint
and Offs
> Uint_0
then
10029 if Offs
mod (System_Storage_Unit
* ObjA
) /= 0 then
10030 Set_Result
(Known_Incompatible
);
10033 -- See if Expr is an object with known alignment
10035 elsif Is_Entity_Name
(Expr
)
10036 and then Known_Alignment
(Entity
(Expr
))
10038 ExpA
:= Alignment
(Entity
(Expr
));
10040 -- Otherwise, we can use the alignment of the type of
10041 -- Expr given that we already checked for
10042 -- discombobulating rep clauses for the cases of indexed
10043 -- and selected components above.
10045 elsif Known_Alignment
(Etype
(Expr
)) then
10046 ExpA
:= Alignment
(Etype
(Expr
));
10048 -- Otherwise the alignment is unknown
10051 Set_Result
(Default
);
10054 -- If we got an alignment, see if it is acceptable
10056 if ExpA
/= No_Uint
and then ExpA
< ObjA
then
10057 Set_Result
(Known_Incompatible
);
10060 -- If Expr is not a piece of a larger object, see if size
10061 -- is given. If so, check that it is not too small for the
10062 -- required alignment.
10064 if Offs
/= No_Uint
then
10067 -- See if Expr is an object with known size
10069 elsif Is_Entity_Name
(Expr
)
10070 and then Known_Static_Esize
(Entity
(Expr
))
10072 SizA
:= Esize
(Entity
(Expr
));
10074 -- Otherwise, we check the object size of the Expr type
10076 elsif Known_Static_Esize
(Etype
(Expr
)) then
10077 SizA
:= Esize
(Etype
(Expr
));
10080 -- If we got a size, see if it is a multiple of the Obj
10081 -- alignment, if not, then the alignment cannot be
10082 -- acceptable, since the size is always a multiple of the
10085 if SizA
/= No_Uint
then
10086 if SizA
mod (ObjA
* Ttypes
.System_Storage_Unit
) /= 0 then
10087 Set_Result
(Known_Incompatible
);
10093 -- If we do not know required alignment, any non-zero offset is a
10094 -- potential problem (but certainly may be OK, so result is unknown).
10096 elsif Offs
/= No_Uint
then
10097 Set_Result
(Unknown
);
10099 -- If we can't find the result by direct comparison of alignment
10100 -- values, then there is still one case that we can determine known
10101 -- result, and that is when we can determine that the types are the
10102 -- same, and no alignments are specified. Then we known that the
10103 -- alignments are compatible, even if we don't know the alignment
10104 -- value in the front end.
10106 elsif Etype
(Obj
) = Etype
(Expr
) then
10108 -- Types are the same, but we have to check for possible size
10109 -- and alignments on the Expr object that may make the alignment
10110 -- different, even though the types are the same.
10112 if Is_Entity_Name
(Expr
) then
10114 -- First check alignment of the Expr object. Any alignment less
10115 -- than Maximum_Alignment is worrisome since this is the case
10116 -- where we do not know the alignment of Obj.
10118 if Known_Alignment
(Entity
(Expr
))
10119 and then UI_To_Int
(Alignment
(Entity
(Expr
))) <
10120 Ttypes
.Maximum_Alignment
10122 Set_Result
(Unknown
);
10124 -- Now check size of Expr object. Any size that is not an
10125 -- even multiple of Maximum_Alignment is also worrisome
10126 -- since it may cause the alignment of the object to be less
10127 -- than the alignment of the type.
10129 elsif Known_Static_Esize
(Entity
(Expr
))
10131 (UI_To_Int
(Esize
(Entity
(Expr
))) mod
10132 (Ttypes
.Maximum_Alignment
* Ttypes
.System_Storage_Unit
))
10135 Set_Result
(Unknown
);
10137 -- Otherwise same type is decisive
10140 Set_Result
(Known_Compatible
);
10144 -- Another case to deal with is when there is an explicit size or
10145 -- alignment clause when the types are not the same. If so, then the
10146 -- result is Unknown. We don't need to do this test if the Default is
10147 -- Unknown, since that result will be set in any case.
10149 elsif Default
/= Unknown
10150 and then (Has_Size_Clause
(Etype
(Expr
))
10152 Has_Alignment_Clause
(Etype
(Expr
)))
10154 Set_Result
(Unknown
);
10156 -- If no indication found, set default
10159 Set_Result
(Default
);
10162 -- Return worst result found
10165 end Has_Compatible_Alignment_Internal
;
10167 -- Start of processing for Has_Compatible_Alignment
10170 -- If Obj has no specified alignment, then set alignment from the type
10171 -- alignment. Perhaps we should always do this, but for sure we should
10172 -- do it when there is an address clause since we can do more if the
10173 -- alignment is known.
10175 if Unknown_Alignment
(Obj
) then
10176 Set_Alignment
(Obj
, Alignment
(Etype
(Obj
)));
10179 -- Now do the internal call that does all the work
10182 Has_Compatible_Alignment_Internal
(Obj
, Expr
, Layout_Done
, Unknown
);
10183 end Has_Compatible_Alignment
;
10185 ----------------------
10186 -- Has_Declarations --
10187 ----------------------
10189 function Has_Declarations
(N
: Node_Id
) return Boolean is
10191 return Nkind_In
(Nkind
(N
), N_Accept_Statement
,
10193 N_Compilation_Unit_Aux
,
10199 N_Package_Specification
);
10200 end Has_Declarations
;
10202 ---------------------------------
10203 -- Has_Defaulted_Discriminants --
10204 ---------------------------------
10206 function Has_Defaulted_Discriminants
(Typ
: Entity_Id
) return Boolean is
10208 return Has_Discriminants
(Typ
)
10209 and then Present
(First_Discriminant
(Typ
))
10210 and then Present
(Discriminant_Default_Value
10211 (First_Discriminant
(Typ
)));
10212 end Has_Defaulted_Discriminants
;
10214 -------------------
10215 -- Has_Denormals --
10216 -------------------
10218 function Has_Denormals
(E
: Entity_Id
) return Boolean is
10220 return Is_Floating_Point_Type
(E
) and then Denorm_On_Target
;
10223 -------------------------------------------
10224 -- Has_Discriminant_Dependent_Constraint --
10225 -------------------------------------------
10227 function Has_Discriminant_Dependent_Constraint
10228 (Comp
: Entity_Id
) return Boolean
10230 Comp_Decl
: constant Node_Id
:= Parent
(Comp
);
10231 Subt_Indic
: Node_Id
;
10236 -- Discriminants can't depend on discriminants
10238 if Ekind
(Comp
) = E_Discriminant
then
10242 Subt_Indic
:= Subtype_Indication
(Component_Definition
(Comp_Decl
));
10244 if Nkind
(Subt_Indic
) = N_Subtype_Indication
then
10245 Constr
:= Constraint
(Subt_Indic
);
10247 if Nkind
(Constr
) = N_Index_Or_Discriminant_Constraint
then
10248 Assn
:= First
(Constraints
(Constr
));
10249 while Present
(Assn
) loop
10250 case Nkind
(Assn
) is
10253 | N_Subtype_Indication
10255 if Depends_On_Discriminant
(Assn
) then
10259 when N_Discriminant_Association
=>
10260 if Depends_On_Discriminant
(Expression
(Assn
)) then
10275 end Has_Discriminant_Dependent_Constraint
;
10277 --------------------------------------
10278 -- Has_Effectively_Volatile_Profile --
10279 --------------------------------------
10281 function Has_Effectively_Volatile_Profile
10282 (Subp_Id
: Entity_Id
) return Boolean
10284 Formal
: Entity_Id
;
10287 -- Inspect the formal parameters looking for an effectively volatile
10290 Formal
:= First_Formal
(Subp_Id
);
10291 while Present
(Formal
) loop
10292 if Is_Effectively_Volatile
(Etype
(Formal
)) then
10296 Next_Formal
(Formal
);
10299 -- Inspect the return type of functions
10301 if Ekind_In
(Subp_Id
, E_Function
, E_Generic_Function
)
10302 and then Is_Effectively_Volatile
(Etype
(Subp_Id
))
10308 end Has_Effectively_Volatile_Profile
;
10310 --------------------------
10311 -- Has_Enabled_Property --
10312 --------------------------
10314 function Has_Enabled_Property
10315 (Item_Id
: Entity_Id
;
10316 Property
: Name_Id
) return Boolean
10318 function Protected_Object_Has_Enabled_Property
return Boolean;
10319 -- Determine whether a protected object denoted by Item_Id has the
10320 -- property enabled.
10322 function State_Has_Enabled_Property
return Boolean;
10323 -- Determine whether a state denoted by Item_Id has the property enabled
10325 function Variable_Has_Enabled_Property
return Boolean;
10326 -- Determine whether a variable denoted by Item_Id has the property
10329 -------------------------------------------
10330 -- Protected_Object_Has_Enabled_Property --
10331 -------------------------------------------
10333 function Protected_Object_Has_Enabled_Property
return Boolean is
10334 Constits
: constant Elist_Id
:= Part_Of_Constituents
(Item_Id
);
10335 Constit_Elmt
: Elmt_Id
;
10336 Constit_Id
: Entity_Id
;
10339 -- Protected objects always have the properties Async_Readers and
10340 -- Async_Writers (SPARK RM 7.1.2(16)).
10342 if Property
= Name_Async_Readers
10343 or else Property
= Name_Async_Writers
10347 -- Protected objects that have Part_Of components also inherit their
10348 -- properties Effective_Reads and Effective_Writes
10349 -- (SPARK RM 7.1.2(16)).
10351 elsif Present
(Constits
) then
10352 Constit_Elmt
:= First_Elmt
(Constits
);
10353 while Present
(Constit_Elmt
) loop
10354 Constit_Id
:= Node
(Constit_Elmt
);
10356 if Has_Enabled_Property
(Constit_Id
, Property
) then
10360 Next_Elmt
(Constit_Elmt
);
10365 end Protected_Object_Has_Enabled_Property
;
10367 --------------------------------
10368 -- State_Has_Enabled_Property --
10369 --------------------------------
10371 function State_Has_Enabled_Property
return Boolean is
10372 Decl
: constant Node_Id
:= Parent
(Item_Id
);
10376 Prop_Nam
: Node_Id
;
10380 -- The declaration of an external abstract state appears as an
10381 -- extension aggregate. If this is not the case, properties can never
10384 if Nkind
(Decl
) /= N_Extension_Aggregate
then
10388 -- When External appears as a simple option, it automatically enables
10391 Opt
:= First
(Expressions
(Decl
));
10392 while Present
(Opt
) loop
10393 if Nkind
(Opt
) = N_Identifier
10394 and then Chars
(Opt
) = Name_External
10402 -- When External specifies particular properties, inspect those and
10403 -- find the desired one (if any).
10405 Opt
:= First
(Component_Associations
(Decl
));
10406 while Present
(Opt
) loop
10407 Opt_Nam
:= First
(Choices
(Opt
));
10409 if Nkind
(Opt_Nam
) = N_Identifier
10410 and then Chars
(Opt_Nam
) = Name_External
10412 Props
:= Expression
(Opt
);
10414 -- Multiple properties appear as an aggregate
10416 if Nkind
(Props
) = N_Aggregate
then
10418 -- Simple property form
10420 Prop
:= First
(Expressions
(Props
));
10421 while Present
(Prop
) loop
10422 if Chars
(Prop
) = Property
then
10429 -- Property with expression form
10431 Prop
:= First
(Component_Associations
(Props
));
10432 while Present
(Prop
) loop
10433 Prop_Nam
:= First
(Choices
(Prop
));
10435 -- The property can be represented in two ways:
10436 -- others => <value>
10437 -- <property> => <value>
10439 if Nkind
(Prop_Nam
) = N_Others_Choice
10440 or else (Nkind
(Prop_Nam
) = N_Identifier
10441 and then Chars
(Prop_Nam
) = Property
)
10443 return Is_True
(Expr_Value
(Expression
(Prop
)));
10452 return Chars
(Props
) = Property
;
10460 end State_Has_Enabled_Property
;
10462 -----------------------------------
10463 -- Variable_Has_Enabled_Property --
10464 -----------------------------------
10466 function Variable_Has_Enabled_Property
return Boolean is
10467 function Is_Enabled
(Prag
: Node_Id
) return Boolean;
10468 -- Determine whether property pragma Prag (if present) denotes an
10469 -- enabled property.
10475 function Is_Enabled
(Prag
: Node_Id
) return Boolean is
10479 if Present
(Prag
) then
10480 Arg1
:= First
(Pragma_Argument_Associations
(Prag
));
10482 -- The pragma has an optional Boolean expression, the related
10483 -- property is enabled only when the expression evaluates to
10486 if Present
(Arg1
) then
10487 return Is_True
(Expr_Value
(Get_Pragma_Arg
(Arg1
)));
10489 -- Otherwise the lack of expression enables the property by
10496 -- The property was never set in the first place
10505 AR
: constant Node_Id
:=
10506 Get_Pragma
(Item_Id
, Pragma_Async_Readers
);
10507 AW
: constant Node_Id
:=
10508 Get_Pragma
(Item_Id
, Pragma_Async_Writers
);
10509 ER
: constant Node_Id
:=
10510 Get_Pragma
(Item_Id
, Pragma_Effective_Reads
);
10511 EW
: constant Node_Id
:=
10512 Get_Pragma
(Item_Id
, Pragma_Effective_Writes
);
10514 -- Start of processing for Variable_Has_Enabled_Property
10517 -- A non-effectively volatile object can never possess external
10520 if not Is_Effectively_Volatile
(Item_Id
) then
10523 -- External properties related to variables come in two flavors -
10524 -- explicit and implicit. The explicit case is characterized by the
10525 -- presence of a property pragma with an optional Boolean flag. The
10526 -- property is enabled when the flag evaluates to True or the flag is
10527 -- missing altogether.
10529 elsif Property
= Name_Async_Readers
and then Is_Enabled
(AR
) then
10532 elsif Property
= Name_Async_Writers
and then Is_Enabled
(AW
) then
10535 elsif Property
= Name_Effective_Reads
and then Is_Enabled
(ER
) then
10538 elsif Property
= Name_Effective_Writes
and then Is_Enabled
(EW
) then
10541 -- The implicit case lacks all property pragmas
10543 elsif No
(AR
) and then No
(AW
) and then No
(ER
) and then No
(EW
) then
10544 if Is_Protected_Type
(Etype
(Item_Id
)) then
10545 return Protected_Object_Has_Enabled_Property
;
10553 end Variable_Has_Enabled_Property
;
10555 -- Start of processing for Has_Enabled_Property
10558 -- Abstract states and variables have a flexible scheme of specifying
10559 -- external properties.
10561 if Ekind
(Item_Id
) = E_Abstract_State
then
10562 return State_Has_Enabled_Property
;
10564 elsif Ekind
(Item_Id
) = E_Variable
then
10565 return Variable_Has_Enabled_Property
;
10567 -- By default, protected objects only have the properties Async_Readers
10568 -- and Async_Writers. If they have Part_Of components, they also inherit
10569 -- their properties Effective_Reads and Effective_Writes
10570 -- (SPARK RM 7.1.2(16)).
10572 elsif Ekind
(Item_Id
) = E_Protected_Object
then
10573 return Protected_Object_Has_Enabled_Property
;
10575 -- Otherwise a property is enabled when the related item is effectively
10579 return Is_Effectively_Volatile
(Item_Id
);
10581 end Has_Enabled_Property
;
10583 -------------------------------------
10584 -- Has_Full_Default_Initialization --
10585 -------------------------------------
10587 function Has_Full_Default_Initialization
(Typ
: Entity_Id
) return Boolean is
10592 -- A type subject to pragma Default_Initial_Condition is fully default
10593 -- initialized when the pragma appears with a non-null argument. Since
10594 -- any type may act as the full view of a private type, this check must
10595 -- be performed prior to the specialized tests below.
10597 if Has_DIC
(Typ
) then
10598 Prag
:= Get_Pragma
(Typ
, Pragma_Default_Initial_Condition
);
10599 pragma Assert
(Present
(Prag
));
10601 return Is_Verifiable_DIC_Pragma
(Prag
);
10604 -- A scalar type is fully default initialized if it is subject to aspect
10607 if Is_Scalar_Type
(Typ
) then
10608 return Has_Default_Aspect
(Typ
);
10610 -- An array type is fully default initialized if its element type is
10611 -- scalar and the array type carries aspect Default_Component_Value or
10612 -- the element type is fully default initialized.
10614 elsif Is_Array_Type
(Typ
) then
10616 Has_Default_Aspect
(Typ
)
10617 or else Has_Full_Default_Initialization
(Component_Type
(Typ
));
10619 -- A protected type, record type, or type extension is fully default
10620 -- initialized if all its components either carry an initialization
10621 -- expression or have a type that is fully default initialized. The
10622 -- parent type of a type extension must be fully default initialized.
10624 elsif Is_Record_Type
(Typ
) or else Is_Protected_Type
(Typ
) then
10626 -- Inspect all entities defined in the scope of the type, looking for
10627 -- uninitialized components.
10629 Comp
:= First_Entity
(Typ
);
10630 while Present
(Comp
) loop
10631 if Ekind
(Comp
) = E_Component
10632 and then Comes_From_Source
(Comp
)
10633 and then No
(Expression
(Parent
(Comp
)))
10634 and then not Has_Full_Default_Initialization
(Etype
(Comp
))
10639 Next_Entity
(Comp
);
10642 -- Ensure that the parent type of a type extension is fully default
10645 if Etype
(Typ
) /= Typ
10646 and then not Has_Full_Default_Initialization
(Etype
(Typ
))
10651 -- If we get here, then all components and parent portion are fully
10652 -- default initialized.
10656 -- A task type is fully default initialized by default
10658 elsif Is_Task_Type
(Typ
) then
10661 -- Otherwise the type is not fully default initialized
10666 end Has_Full_Default_Initialization
;
10668 --------------------
10669 -- Has_Infinities --
10670 --------------------
10672 function Has_Infinities
(E
: Entity_Id
) return Boolean is
10675 Is_Floating_Point_Type
(E
)
10676 and then Nkind
(Scalar_Range
(E
)) = N_Range
10677 and then Includes_Infinities
(Scalar_Range
(E
));
10678 end Has_Infinities
;
10680 --------------------
10681 -- Has_Interfaces --
10682 --------------------
10684 function Has_Interfaces
10686 Use_Full_View
: Boolean := True) return Boolean
10688 Typ
: Entity_Id
:= Base_Type
(T
);
10691 -- Handle concurrent types
10693 if Is_Concurrent_Type
(Typ
) then
10694 Typ
:= Corresponding_Record_Type
(Typ
);
10697 if not Present
(Typ
)
10698 or else not Is_Record_Type
(Typ
)
10699 or else not Is_Tagged_Type
(Typ
)
10704 -- Handle private types
10706 if Use_Full_View
and then Present
(Full_View
(Typ
)) then
10707 Typ
:= Full_View
(Typ
);
10710 -- Handle concurrent record types
10712 if Is_Concurrent_Record_Type
(Typ
)
10713 and then Is_Non_Empty_List
(Abstract_Interface_List
(Typ
))
10719 if Is_Interface
(Typ
)
10721 (Is_Record_Type
(Typ
)
10722 and then Present
(Interfaces
(Typ
))
10723 and then not Is_Empty_Elmt_List
(Interfaces
(Typ
)))
10728 exit when Etype
(Typ
) = Typ
10730 -- Handle private types
10732 or else (Present
(Full_View
(Etype
(Typ
)))
10733 and then Full_View
(Etype
(Typ
)) = Typ
)
10735 -- Protect frontend against wrong sources with cyclic derivations
10737 or else Etype
(Typ
) = T
;
10739 -- Climb to the ancestor type handling private types
10741 if Present
(Full_View
(Etype
(Typ
))) then
10742 Typ
:= Full_View
(Etype
(Typ
));
10744 Typ
:= Etype
(Typ
);
10749 end Has_Interfaces
;
10751 --------------------------
10752 -- Has_Max_Queue_Length --
10753 --------------------------
10755 function Has_Max_Queue_Length
(Id
: Entity_Id
) return Boolean is
10758 Ekind
(Id
) = E_Entry
10759 and then Present
(Get_Pragma
(Id
, Pragma_Max_Queue_Length
));
10760 end Has_Max_Queue_Length
;
10762 ---------------------------------
10763 -- Has_No_Obvious_Side_Effects --
10764 ---------------------------------
10766 function Has_No_Obvious_Side_Effects
(N
: Node_Id
) return Boolean is
10768 -- For now handle literals, constants, and non-volatile variables and
10769 -- expressions combining these with operators or short circuit forms.
10771 if Nkind
(N
) in N_Numeric_Or_String_Literal
then
10774 elsif Nkind
(N
) = N_Character_Literal
then
10777 elsif Nkind
(N
) in N_Unary_Op
then
10778 return Has_No_Obvious_Side_Effects
(Right_Opnd
(N
));
10780 elsif Nkind
(N
) in N_Binary_Op
or else Nkind
(N
) in N_Short_Circuit
then
10781 return Has_No_Obvious_Side_Effects
(Left_Opnd
(N
))
10783 Has_No_Obvious_Side_Effects
(Right_Opnd
(N
));
10785 elsif Nkind
(N
) = N_Expression_With_Actions
10786 and then Is_Empty_List
(Actions
(N
))
10788 return Has_No_Obvious_Side_Effects
(Expression
(N
));
10790 elsif Nkind
(N
) in N_Has_Entity
then
10791 return Present
(Entity
(N
))
10792 and then Ekind_In
(Entity
(N
), E_Variable
,
10794 E_Enumeration_Literal
,
10797 E_In_Out_Parameter
)
10798 and then not Is_Volatile
(Entity
(N
));
10803 end Has_No_Obvious_Side_Effects
;
10805 -----------------------------
10806 -- Has_Non_Null_Refinement --
10807 -----------------------------
10809 function Has_Non_Null_Refinement
(Id
: Entity_Id
) return Boolean is
10810 Constits
: Elist_Id
;
10813 pragma Assert
(Ekind
(Id
) = E_Abstract_State
);
10814 Constits
:= Refinement_Constituents
(Id
);
10816 -- For a refinement to be non-null, the first constituent must be
10817 -- anything other than null.
10821 and then Nkind
(Node
(First_Elmt
(Constits
))) /= N_Null
;
10822 end Has_Non_Null_Refinement
;
10824 ----------------------------------
10825 -- Has_Non_Trivial_Precondition --
10826 ----------------------------------
10828 function Has_Non_Trivial_Precondition
(Subp
: Entity_Id
) return Boolean is
10829 Pre
: constant Node_Id
:= Find_Aspect
(Subp
, Aspect_Pre
);
10834 and then Class_Present
(Pre
)
10835 and then not Is_Entity_Name
(Expression
(Pre
));
10836 end Has_Non_Trivial_Precondition
;
10838 -------------------
10839 -- Has_Null_Body --
10840 -------------------
10842 function Has_Null_Body
(Proc_Id
: Entity_Id
) return Boolean is
10843 Body_Id
: Entity_Id
;
10850 Spec
:= Parent
(Proc_Id
);
10851 Decl
:= Parent
(Spec
);
10853 -- Retrieve the entity of the procedure body (e.g. invariant proc).
10855 if Nkind
(Spec
) = N_Procedure_Specification
10856 and then Nkind
(Decl
) = N_Subprogram_Declaration
10858 Body_Id
:= Corresponding_Body
(Decl
);
10860 -- The body acts as a spec
10863 Body_Id
:= Proc_Id
;
10866 -- The body will be generated later
10868 if No
(Body_Id
) then
10872 Spec
:= Parent
(Body_Id
);
10873 Decl
:= Parent
(Spec
);
10876 (Nkind
(Spec
) = N_Procedure_Specification
10877 and then Nkind
(Decl
) = N_Subprogram_Body
);
10879 Stmt1
:= First
(Statements
(Handled_Statement_Sequence
(Decl
)));
10881 -- Look for a null statement followed by an optional return
10884 if Nkind
(Stmt1
) = N_Null_Statement
then
10885 Stmt2
:= Next
(Stmt1
);
10887 if Present
(Stmt2
) then
10888 return Nkind
(Stmt2
) = N_Simple_Return_Statement
;
10897 ------------------------
10898 -- Has_Null_Exclusion --
10899 ------------------------
10901 function Has_Null_Exclusion
(N
: Node_Id
) return Boolean is
10904 when N_Access_Definition
10905 | N_Access_Function_Definition
10906 | N_Access_Procedure_Definition
10907 | N_Access_To_Object_Definition
10909 | N_Derived_Type_Definition
10910 | N_Function_Specification
10911 | N_Subtype_Declaration
10913 return Null_Exclusion_Present
(N
);
10915 when N_Component_Definition
10916 | N_Formal_Object_Declaration
10917 | N_Object_Renaming_Declaration
10919 if Present
(Subtype_Mark
(N
)) then
10920 return Null_Exclusion_Present
(N
);
10921 else pragma Assert
(Present
(Access_Definition
(N
)));
10922 return Null_Exclusion_Present
(Access_Definition
(N
));
10925 when N_Discriminant_Specification
=>
10926 if Nkind
(Discriminant_Type
(N
)) = N_Access_Definition
then
10927 return Null_Exclusion_Present
(Discriminant_Type
(N
));
10929 return Null_Exclusion_Present
(N
);
10932 when N_Object_Declaration
=>
10933 if Nkind
(Object_Definition
(N
)) = N_Access_Definition
then
10934 return Null_Exclusion_Present
(Object_Definition
(N
));
10936 return Null_Exclusion_Present
(N
);
10939 when N_Parameter_Specification
=>
10940 if Nkind
(Parameter_Type
(N
)) = N_Access_Definition
then
10941 return Null_Exclusion_Present
(Parameter_Type
(N
));
10943 return Null_Exclusion_Present
(N
);
10949 end Has_Null_Exclusion
;
10951 ------------------------
10952 -- Has_Null_Extension --
10953 ------------------------
10955 function Has_Null_Extension
(T
: Entity_Id
) return Boolean is
10956 B
: constant Entity_Id
:= Base_Type
(T
);
10961 if Nkind
(Parent
(B
)) = N_Full_Type_Declaration
10962 and then Present
(Record_Extension_Part
(Type_Definition
(Parent
(B
))))
10964 Ext
:= Record_Extension_Part
(Type_Definition
(Parent
(B
)));
10966 if Present
(Ext
) then
10967 if Null_Present
(Ext
) then
10970 Comps
:= Component_List
(Ext
);
10972 -- The null component list is rewritten during analysis to
10973 -- include the parent component. Any other component indicates
10974 -- that the extension was not originally null.
10976 return Null_Present
(Comps
)
10977 or else No
(Next
(First
(Component_Items
(Comps
))));
10986 end Has_Null_Extension
;
10988 -------------------------
10989 -- Has_Null_Refinement --
10990 -------------------------
10992 function Has_Null_Refinement
(Id
: Entity_Id
) return Boolean is
10993 Constits
: Elist_Id
;
10996 pragma Assert
(Ekind
(Id
) = E_Abstract_State
);
10997 Constits
:= Refinement_Constituents
(Id
);
10999 -- For a refinement to be null, the state's sole constituent must be a
11004 and then Nkind
(Node
(First_Elmt
(Constits
))) = N_Null
;
11005 end Has_Null_Refinement
;
11007 -------------------------------
11008 -- Has_Overriding_Initialize --
11009 -------------------------------
11011 function Has_Overriding_Initialize
(T
: Entity_Id
) return Boolean is
11012 BT
: constant Entity_Id
:= Base_Type
(T
);
11016 if Is_Controlled
(BT
) then
11017 if Is_RTU
(Scope
(BT
), Ada_Finalization
) then
11020 elsif Present
(Primitive_Operations
(BT
)) then
11021 P
:= First_Elmt
(Primitive_Operations
(BT
));
11022 while Present
(P
) loop
11024 Init
: constant Entity_Id
:= Node
(P
);
11025 Formal
: constant Entity_Id
:= First_Formal
(Init
);
11027 if Ekind
(Init
) = E_Procedure
11028 and then Chars
(Init
) = Name_Initialize
11029 and then Comes_From_Source
(Init
)
11030 and then Present
(Formal
)
11031 and then Etype
(Formal
) = BT
11032 and then No
(Next_Formal
(Formal
))
11033 and then (Ada_Version
< Ada_2012
11034 or else not Null_Present
(Parent
(Init
)))
11044 -- Here if type itself does not have a non-null Initialize operation:
11045 -- check immediate ancestor.
11047 if Is_Derived_Type
(BT
)
11048 and then Has_Overriding_Initialize
(Etype
(BT
))
11055 end Has_Overriding_Initialize
;
11057 --------------------------------------
11058 -- Has_Preelaborable_Initialization --
11059 --------------------------------------
11061 function Has_Preelaborable_Initialization
(E
: Entity_Id
) return Boolean is
11064 procedure Check_Components
(E
: Entity_Id
);
11065 -- Check component/discriminant chain, sets Has_PE False if a component
11066 -- or discriminant does not meet the preelaborable initialization rules.
11068 ----------------------
11069 -- Check_Components --
11070 ----------------------
11072 procedure Check_Components
(E
: Entity_Id
) is
11077 -- Loop through entities of record or protected type
11080 while Present
(Ent
) loop
11082 -- We are interested only in components and discriminants
11086 case Ekind
(Ent
) is
11087 when E_Component
=>
11089 -- Get default expression if any. If there is no declaration
11090 -- node, it means we have an internal entity. The parent and
11091 -- tag fields are examples of such entities. For such cases,
11092 -- we just test the type of the entity.
11094 if Present
(Declaration_Node
(Ent
)) then
11095 Exp
:= Expression
(Declaration_Node
(Ent
));
11098 when E_Discriminant
=>
11100 -- Note: for a renamed discriminant, the Declaration_Node
11101 -- may point to the one from the ancestor, and have a
11102 -- different expression, so use the proper attribute to
11103 -- retrieve the expression from the derived constraint.
11105 Exp
:= Discriminant_Default_Value
(Ent
);
11108 goto Check_Next_Entity
;
11111 -- A component has PI if it has no default expression and the
11112 -- component type has PI.
11115 if not Has_Preelaborable_Initialization
(Etype
(Ent
)) then
11120 -- Require the default expression to be preelaborable
11122 elsif not Is_Preelaborable_Construct
(Exp
) then
11127 <<Check_Next_Entity
>>
11130 end Check_Components
;
11132 -- Start of processing for Has_Preelaborable_Initialization
11135 -- Immediate return if already marked as known preelaborable init. This
11136 -- covers types for which this function has already been called once
11137 -- and returned True (in which case the result is cached), and also
11138 -- types to which a pragma Preelaborable_Initialization applies.
11140 if Known_To_Have_Preelab_Init
(E
) then
11144 -- If the type is a subtype representing a generic actual type, then
11145 -- test whether its base type has preelaborable initialization since
11146 -- the subtype representing the actual does not inherit this attribute
11147 -- from the actual or formal. (but maybe it should???)
11149 if Is_Generic_Actual_Type
(E
) then
11150 return Has_Preelaborable_Initialization
(Base_Type
(E
));
11153 -- All elementary types have preelaborable initialization
11155 if Is_Elementary_Type
(E
) then
11158 -- Array types have PI if the component type has PI
11160 elsif Is_Array_Type
(E
) then
11161 Has_PE
:= Has_Preelaborable_Initialization
(Component_Type
(E
));
11163 -- A derived type has preelaborable initialization if its parent type
11164 -- has preelaborable initialization and (in the case of a derived record
11165 -- extension) if the non-inherited components all have preelaborable
11166 -- initialization. However, a user-defined controlled type with an
11167 -- overriding Initialize procedure does not have preelaborable
11170 elsif Is_Derived_Type
(E
) then
11172 -- If the derived type is a private extension then it doesn't have
11173 -- preelaborable initialization.
11175 if Ekind
(Base_Type
(E
)) = E_Record_Type_With_Private
then
11179 -- First check whether ancestor type has preelaborable initialization
11181 Has_PE
:= Has_Preelaborable_Initialization
(Etype
(Base_Type
(E
)));
11183 -- If OK, check extension components (if any)
11185 if Has_PE
and then Is_Record_Type
(E
) then
11186 Check_Components
(First_Entity
(E
));
11189 -- Check specifically for 10.2.1(11.4/2) exception: a controlled type
11190 -- with a user defined Initialize procedure does not have PI. If
11191 -- the type is untagged, the control primitives come from a component
11192 -- that has already been checked.
11195 and then Is_Controlled
(E
)
11196 and then Is_Tagged_Type
(E
)
11197 and then Has_Overriding_Initialize
(E
)
11202 -- Private types not derived from a type having preelaborable init and
11203 -- that are not marked with pragma Preelaborable_Initialization do not
11204 -- have preelaborable initialization.
11206 elsif Is_Private_Type
(E
) then
11209 -- Record type has PI if it is non private and all components have PI
11211 elsif Is_Record_Type
(E
) then
11213 Check_Components
(First_Entity
(E
));
11215 -- Protected types must not have entries, and components must meet
11216 -- same set of rules as for record components.
11218 elsif Is_Protected_Type
(E
) then
11219 if Has_Entries
(E
) then
11223 Check_Components
(First_Entity
(E
));
11224 Check_Components
(First_Private_Entity
(E
));
11227 -- Type System.Address always has preelaborable initialization
11229 elsif Is_RTE
(E
, RE_Address
) then
11232 -- In all other cases, type does not have preelaborable initialization
11238 -- If type has preelaborable initialization, cache result
11241 Set_Known_To_Have_Preelab_Init
(E
);
11245 end Has_Preelaborable_Initialization
;
11247 ---------------------------
11248 -- Has_Private_Component --
11249 ---------------------------
11251 function Has_Private_Component
(Type_Id
: Entity_Id
) return Boolean is
11252 Btype
: Entity_Id
:= Base_Type
(Type_Id
);
11253 Component
: Entity_Id
;
11256 if Error_Posted
(Type_Id
)
11257 or else Error_Posted
(Btype
)
11262 if Is_Class_Wide_Type
(Btype
) then
11263 Btype
:= Root_Type
(Btype
);
11266 if Is_Private_Type
(Btype
) then
11268 UT
: constant Entity_Id
:= Underlying_Type
(Btype
);
11271 if No
(Full_View
(Btype
)) then
11272 return not Is_Generic_Type
(Btype
)
11274 not Is_Generic_Type
(Root_Type
(Btype
));
11276 return not Is_Generic_Type
(Root_Type
(Full_View
(Btype
)));
11279 return not Is_Frozen
(UT
) and then Has_Private_Component
(UT
);
11283 elsif Is_Array_Type
(Btype
) then
11284 return Has_Private_Component
(Component_Type
(Btype
));
11286 elsif Is_Record_Type
(Btype
) then
11287 Component
:= First_Component
(Btype
);
11288 while Present
(Component
) loop
11289 if Has_Private_Component
(Etype
(Component
)) then
11293 Next_Component
(Component
);
11298 elsif Is_Protected_Type
(Btype
)
11299 and then Present
(Corresponding_Record_Type
(Btype
))
11301 return Has_Private_Component
(Corresponding_Record_Type
(Btype
));
11306 end Has_Private_Component
;
11308 ----------------------
11309 -- Has_Signed_Zeros --
11310 ----------------------
11312 function Has_Signed_Zeros
(E
: Entity_Id
) return Boolean is
11314 return Is_Floating_Point_Type
(E
) and then Signed_Zeros_On_Target
;
11315 end Has_Signed_Zeros
;
11317 ------------------------------
11318 -- Has_Significant_Contract --
11319 ------------------------------
11321 function Has_Significant_Contract
(Subp_Id
: Entity_Id
) return Boolean is
11322 Subp_Nam
: constant Name_Id
:= Chars
(Subp_Id
);
11325 -- _Finalizer procedure
11327 if Subp_Nam
= Name_uFinalizer
then
11330 -- _Postconditions procedure
11332 elsif Subp_Nam
= Name_uPostconditions
then
11335 -- Predicate function
11337 elsif Ekind
(Subp_Id
) = E_Function
11338 and then Is_Predicate_Function
(Subp_Id
)
11344 elsif Get_TSS_Name
(Subp_Id
) /= TSS_Null
then
11350 end Has_Significant_Contract
;
11352 -----------------------------
11353 -- Has_Static_Array_Bounds --
11354 -----------------------------
11356 function Has_Static_Array_Bounds
(Typ
: Node_Id
) return Boolean is
11357 Ndims
: constant Nat
:= Number_Dimensions
(Typ
);
11364 -- Unconstrained types do not have static bounds
11366 if not Is_Constrained
(Typ
) then
11370 -- First treat string literals specially, as the lower bound and length
11371 -- of string literals are not stored like those of arrays.
11373 -- A string literal always has static bounds
11375 if Ekind
(Typ
) = E_String_Literal_Subtype
then
11379 -- Treat all dimensions in turn
11381 Index
:= First_Index
(Typ
);
11382 for Indx
in 1 .. Ndims
loop
11384 -- In case of an illegal index which is not a discrete type, return
11385 -- that the type is not static.
11387 if not Is_Discrete_Type
(Etype
(Index
))
11388 or else Etype
(Index
) = Any_Type
11393 Get_Index_Bounds
(Index
, Low
, High
);
11395 if Error_Posted
(Low
) or else Error_Posted
(High
) then
11399 if Is_OK_Static_Expression
(Low
)
11401 Is_OK_Static_Expression
(High
)
11411 -- If we fall through the loop, all indexes matched
11414 end Has_Static_Array_Bounds
;
11420 function Has_Stream
(T
: Entity_Id
) return Boolean is
11427 elsif Is_RTE
(Root_Type
(T
), RE_Root_Stream_Type
) then
11430 elsif Is_Array_Type
(T
) then
11431 return Has_Stream
(Component_Type
(T
));
11433 elsif Is_Record_Type
(T
) then
11434 E
:= First_Component
(T
);
11435 while Present
(E
) loop
11436 if Has_Stream
(Etype
(E
)) then
11439 Next_Component
(E
);
11445 elsif Is_Private_Type
(T
) then
11446 return Has_Stream
(Underlying_Type
(T
));
11457 function Has_Suffix
(E
: Entity_Id
; Suffix
: Character) return Boolean is
11459 Get_Name_String
(Chars
(E
));
11460 return Name_Buffer
(Name_Len
) = Suffix
;
11467 function Add_Suffix
(E
: Entity_Id
; Suffix
: Character) return Name_Id
is
11469 Get_Name_String
(Chars
(E
));
11470 Add_Char_To_Name_Buffer
(Suffix
);
11474 -------------------
11475 -- Remove_Suffix --
11476 -------------------
11478 function Remove_Suffix
(E
: Entity_Id
; Suffix
: Character) return Name_Id
is
11480 pragma Assert
(Has_Suffix
(E
, Suffix
));
11481 Get_Name_String
(Chars
(E
));
11482 Name_Len
:= Name_Len
- 1;
11486 ----------------------------------
11487 -- Replace_Null_By_Null_Address --
11488 ----------------------------------
11490 procedure Replace_Null_By_Null_Address
(N
: Node_Id
) is
11491 procedure Replace_Null_Operand
(Op
: Node_Id
; Other_Op
: Node_Id
);
11492 -- Replace operand Op with a reference to Null_Address when the operand
11493 -- denotes a null Address. Other_Op denotes the other operand.
11495 --------------------------
11496 -- Replace_Null_Operand --
11497 --------------------------
11499 procedure Replace_Null_Operand
(Op
: Node_Id
; Other_Op
: Node_Id
) is
11501 -- Check the type of the complementary operand since the N_Null node
11502 -- has not been decorated yet.
11504 if Nkind
(Op
) = N_Null
11505 and then Is_Descendant_Of_Address
(Etype
(Other_Op
))
11507 Rewrite
(Op
, New_Occurrence_Of
(RTE
(RE_Null_Address
), Sloc
(Op
)));
11509 end Replace_Null_Operand
;
11511 -- Start of processing for Replace_Null_By_Null_Address
11514 pragma Assert
(Relaxed_RM_Semantics
);
11515 pragma Assert
(Nkind_In
(N
, N_Null
,
11523 if Nkind
(N
) = N_Null
then
11524 Rewrite
(N
, New_Occurrence_Of
(RTE
(RE_Null_Address
), Sloc
(N
)));
11528 L
: constant Node_Id
:= Left_Opnd
(N
);
11529 R
: constant Node_Id
:= Right_Opnd
(N
);
11532 Replace_Null_Operand
(L
, Other_Op
=> R
);
11533 Replace_Null_Operand
(R
, Other_Op
=> L
);
11536 end Replace_Null_By_Null_Address
;
11538 --------------------------
11539 -- Has_Tagged_Component --
11540 --------------------------
11542 function Has_Tagged_Component
(Typ
: Entity_Id
) return Boolean is
11546 if Is_Private_Type
(Typ
) and then Present
(Underlying_Type
(Typ
)) then
11547 return Has_Tagged_Component
(Underlying_Type
(Typ
));
11549 elsif Is_Array_Type
(Typ
) then
11550 return Has_Tagged_Component
(Component_Type
(Typ
));
11552 elsif Is_Tagged_Type
(Typ
) then
11555 elsif Is_Record_Type
(Typ
) then
11556 Comp
:= First_Component
(Typ
);
11557 while Present
(Comp
) loop
11558 if Has_Tagged_Component
(Etype
(Comp
)) then
11562 Next_Component
(Comp
);
11570 end Has_Tagged_Component
;
11572 -----------------------------
11573 -- Has_Undefined_Reference --
11574 -----------------------------
11576 function Has_Undefined_Reference
(Expr
: Node_Id
) return Boolean is
11577 Has_Undef_Ref
: Boolean := False;
11578 -- Flag set when expression Expr contains at least one undefined
11581 function Is_Undefined_Reference
(N
: Node_Id
) return Traverse_Result
;
11582 -- Determine whether N denotes a reference and if it does, whether it is
11585 ----------------------------
11586 -- Is_Undefined_Reference --
11587 ----------------------------
11589 function Is_Undefined_Reference
(N
: Node_Id
) return Traverse_Result
is
11591 if Is_Entity_Name
(N
)
11592 and then Present
(Entity
(N
))
11593 and then Entity
(N
) = Any_Id
11595 Has_Undef_Ref
:= True;
11600 end Is_Undefined_Reference
;
11602 procedure Find_Undefined_References
is
11603 new Traverse_Proc
(Is_Undefined_Reference
);
11605 -- Start of processing for Has_Undefined_Reference
11608 Find_Undefined_References
(Expr
);
11610 return Has_Undef_Ref
;
11611 end Has_Undefined_Reference
;
11613 ----------------------------
11614 -- Has_Volatile_Component --
11615 ----------------------------
11617 function Has_Volatile_Component
(Typ
: Entity_Id
) return Boolean is
11621 if Has_Volatile_Components
(Typ
) then
11624 elsif Is_Array_Type
(Typ
) then
11625 return Is_Volatile
(Component_Type
(Typ
));
11627 elsif Is_Record_Type
(Typ
) then
11628 Comp
:= First_Component
(Typ
);
11629 while Present
(Comp
) loop
11630 if Is_Volatile_Object
(Comp
) then
11634 Comp
:= Next_Component
(Comp
);
11639 end Has_Volatile_Component
;
11641 -------------------------
11642 -- Implementation_Kind --
11643 -------------------------
11645 function Implementation_Kind
(Subp
: Entity_Id
) return Name_Id
is
11646 Impl_Prag
: constant Node_Id
:= Get_Rep_Pragma
(Subp
, Name_Implemented
);
11649 pragma Assert
(Present
(Impl_Prag
));
11650 Arg
:= Last
(Pragma_Argument_Associations
(Impl_Prag
));
11651 return Chars
(Get_Pragma_Arg
(Arg
));
11652 end Implementation_Kind
;
11654 --------------------------
11655 -- Implements_Interface --
11656 --------------------------
11658 function Implements_Interface
11659 (Typ_Ent
: Entity_Id
;
11660 Iface_Ent
: Entity_Id
;
11661 Exclude_Parents
: Boolean := False) return Boolean
11663 Ifaces_List
: Elist_Id
;
11665 Iface
: Entity_Id
:= Base_Type
(Iface_Ent
);
11666 Typ
: Entity_Id
:= Base_Type
(Typ_Ent
);
11669 if Is_Class_Wide_Type
(Typ
) then
11670 Typ
:= Root_Type
(Typ
);
11673 if not Has_Interfaces
(Typ
) then
11677 if Is_Class_Wide_Type
(Iface
) then
11678 Iface
:= Root_Type
(Iface
);
11681 Collect_Interfaces
(Typ
, Ifaces_List
);
11683 Elmt
:= First_Elmt
(Ifaces_List
);
11684 while Present
(Elmt
) loop
11685 if Is_Ancestor
(Node
(Elmt
), Typ
, Use_Full_View
=> True)
11686 and then Exclude_Parents
11690 elsif Node
(Elmt
) = Iface
then
11698 end Implements_Interface
;
11700 ------------------------------------
11701 -- In_Assertion_Expression_Pragma --
11702 ------------------------------------
11704 function In_Assertion_Expression_Pragma
(N
: Node_Id
) return Boolean is
11706 Prag
: Node_Id
:= Empty
;
11709 -- Climb the parent chain looking for an enclosing pragma
11712 while Present
(Par
) loop
11713 if Nkind
(Par
) = N_Pragma
then
11717 -- Precondition-like pragmas are expanded into if statements, check
11718 -- the original node instead.
11720 elsif Nkind
(Original_Node
(Par
)) = N_Pragma
then
11721 Prag
:= Original_Node
(Par
);
11724 -- The expansion of attribute 'Old generates a constant to capture
11725 -- the result of the prefix. If the parent traversal reaches
11726 -- one of these constants, then the node technically came from a
11727 -- postcondition-like pragma. Note that the Ekind is not tested here
11728 -- because N may be the expression of an object declaration which is
11729 -- currently being analyzed. Such objects carry Ekind of E_Void.
11731 elsif Nkind
(Par
) = N_Object_Declaration
11732 and then Constant_Present
(Par
)
11733 and then Stores_Attribute_Old_Prefix
(Defining_Entity
(Par
))
11737 -- Prevent the search from going too far
11739 elsif Is_Body_Or_Package_Declaration
(Par
) then
11743 Par
:= Parent
(Par
);
11748 and then Assertion_Expression_Pragma
(Get_Pragma_Id
(Prag
));
11749 end In_Assertion_Expression_Pragma
;
11751 ----------------------
11752 -- In_Generic_Scope --
11753 ----------------------
11755 function In_Generic_Scope
(E
: Entity_Id
) return Boolean is
11760 while Present
(S
) and then S
/= Standard_Standard
loop
11761 if Is_Generic_Unit
(S
) then
11769 end In_Generic_Scope
;
11775 function In_Instance
return Boolean is
11776 Curr_Unit
: constant Entity_Id
:= Cunit_Entity
(Current_Sem_Unit
);
11780 S
:= Current_Scope
;
11781 while Present
(S
) and then S
/= Standard_Standard
loop
11782 if Is_Generic_Instance
(S
) then
11784 -- A child instance is always compiled in the context of a parent
11785 -- instance. Nevertheless, the actuals are not analyzed in an
11786 -- instance context. We detect this case by examining the current
11787 -- compilation unit, which must be a child instance, and checking
11788 -- that it is not currently on the scope stack.
11790 if Is_Child_Unit
(Curr_Unit
)
11791 and then Nkind
(Unit
(Cunit
(Current_Sem_Unit
))) =
11792 N_Package_Instantiation
11793 and then not In_Open_Scopes
(Curr_Unit
)
11807 ----------------------
11808 -- In_Instance_Body --
11809 ----------------------
11811 function In_Instance_Body
return Boolean is
11815 S
:= Current_Scope
;
11816 while Present
(S
) and then S
/= Standard_Standard
loop
11817 if Ekind_In
(S
, E_Function
, E_Procedure
)
11818 and then Is_Generic_Instance
(S
)
11822 elsif Ekind
(S
) = E_Package
11823 and then In_Package_Body
(S
)
11824 and then Is_Generic_Instance
(S
)
11833 end In_Instance_Body
;
11835 -----------------------------
11836 -- In_Instance_Not_Visible --
11837 -----------------------------
11839 function In_Instance_Not_Visible
return Boolean is
11843 S
:= Current_Scope
;
11844 while Present
(S
) and then S
/= Standard_Standard
loop
11845 if Ekind_In
(S
, E_Function
, E_Procedure
)
11846 and then Is_Generic_Instance
(S
)
11850 elsif Ekind
(S
) = E_Package
11851 and then (In_Package_Body
(S
) or else In_Private_Part
(S
))
11852 and then Is_Generic_Instance
(S
)
11861 end In_Instance_Not_Visible
;
11863 ------------------------------
11864 -- In_Instance_Visible_Part --
11865 ------------------------------
11867 function In_Instance_Visible_Part
11868 (Id
: Entity_Id
:= Current_Scope
) return Boolean
11874 while Present
(Inst
) and then Inst
/= Standard_Standard
loop
11875 if Ekind
(Inst
) = E_Package
11876 and then Is_Generic_Instance
(Inst
)
11877 and then not In_Package_Body
(Inst
)
11878 and then not In_Private_Part
(Inst
)
11883 Inst
:= Scope
(Inst
);
11887 end In_Instance_Visible_Part
;
11889 ---------------------
11890 -- In_Package_Body --
11891 ---------------------
11893 function In_Package_Body
return Boolean is
11897 S
:= Current_Scope
;
11898 while Present
(S
) and then S
/= Standard_Standard
loop
11899 if Ekind
(S
) = E_Package
and then In_Package_Body
(S
) then
11907 end In_Package_Body
;
11909 --------------------------
11910 -- In_Pragma_Expression --
11911 --------------------------
11913 function In_Pragma_Expression
(N
: Node_Id
; Nam
: Name_Id
) return Boolean is
11920 elsif Nkind
(P
) = N_Pragma
and then Pragma_Name
(P
) = Nam
then
11926 end In_Pragma_Expression
;
11928 ---------------------------
11929 -- In_Pre_Post_Condition --
11930 ---------------------------
11932 function In_Pre_Post_Condition
(N
: Node_Id
) return Boolean is
11934 Prag
: Node_Id
:= Empty
;
11935 Prag_Id
: Pragma_Id
;
11938 -- Climb the parent chain looking for an enclosing pragma
11941 while Present
(Par
) loop
11942 if Nkind
(Par
) = N_Pragma
then
11946 -- Prevent the search from going too far
11948 elsif Is_Body_Or_Package_Declaration
(Par
) then
11952 Par
:= Parent
(Par
);
11955 if Present
(Prag
) then
11956 Prag_Id
:= Get_Pragma_Id
(Prag
);
11959 Prag_Id
= Pragma_Post
11960 or else Prag_Id
= Pragma_Post_Class
11961 or else Prag_Id
= Pragma_Postcondition
11962 or else Prag_Id
= Pragma_Pre
11963 or else Prag_Id
= Pragma_Pre_Class
11964 or else Prag_Id
= Pragma_Precondition
;
11966 -- Otherwise the node is not enclosed by a pre/postcondition pragma
11971 end In_Pre_Post_Condition
;
11973 -------------------------------------
11974 -- In_Reverse_Storage_Order_Object --
11975 -------------------------------------
11977 function In_Reverse_Storage_Order_Object
(N
: Node_Id
) return Boolean is
11979 Btyp
: Entity_Id
:= Empty
;
11982 -- Climb up indexed components
11986 case Nkind
(Pref
) is
11987 when N_Selected_Component
=>
11988 Pref
:= Prefix
(Pref
);
11991 when N_Indexed_Component
=>
11992 Pref
:= Prefix
(Pref
);
12000 if Present
(Pref
) then
12001 Btyp
:= Base_Type
(Etype
(Pref
));
12004 return Present
(Btyp
)
12005 and then (Is_Record_Type
(Btyp
) or else Is_Array_Type
(Btyp
))
12006 and then Reverse_Storage_Order
(Btyp
);
12007 end In_Reverse_Storage_Order_Object
;
12009 --------------------------------------
12010 -- In_Subprogram_Or_Concurrent_Unit --
12011 --------------------------------------
12013 function In_Subprogram_Or_Concurrent_Unit
return Boolean is
12018 -- Use scope chain to check successively outer scopes
12020 E
:= Current_Scope
;
12024 if K
in Subprogram_Kind
12025 or else K
in Concurrent_Kind
12026 or else K
in Generic_Subprogram_Kind
12030 elsif E
= Standard_Standard
then
12036 end In_Subprogram_Or_Concurrent_Unit
;
12042 function In_Subtree
(N
: Node_Id
; Root
: Node_Id
) return Boolean is
12047 while Present
(Curr
) loop
12048 if Curr
= Root
then
12052 Curr
:= Parent
(Curr
);
12062 function In_Subtree
12065 Root2
: Node_Id
) return Boolean
12071 while Present
(Curr
) loop
12072 if Curr
= Root1
or else Curr
= Root2
then
12076 Curr
:= Parent
(Curr
);
12082 ---------------------
12083 -- In_Visible_Part --
12084 ---------------------
12086 function In_Visible_Part
(Scope_Id
: Entity_Id
) return Boolean is
12088 return Is_Package_Or_Generic_Package
(Scope_Id
)
12089 and then In_Open_Scopes
(Scope_Id
)
12090 and then not In_Package_Body
(Scope_Id
)
12091 and then not In_Private_Part
(Scope_Id
);
12092 end In_Visible_Part
;
12094 --------------------------------
12095 -- Incomplete_Or_Partial_View --
12096 --------------------------------
12098 function Incomplete_Or_Partial_View
(Id
: Entity_Id
) return Entity_Id
is
12099 function Inspect_Decls
12101 Taft
: Boolean := False) return Entity_Id
;
12102 -- Check whether a declarative region contains the incomplete or partial
12105 -------------------
12106 -- Inspect_Decls --
12107 -------------------
12109 function Inspect_Decls
12111 Taft
: Boolean := False) return Entity_Id
12117 Decl
:= First
(Decls
);
12118 while Present
(Decl
) loop
12121 -- The partial view of a Taft-amendment type is an incomplete
12125 if Nkind
(Decl
) = N_Incomplete_Type_Declaration
then
12126 Match
:= Defining_Identifier
(Decl
);
12129 -- Otherwise look for a private type whose full view matches the
12130 -- input type. Note that this checks full_type_declaration nodes
12131 -- to account for derivations from a private type where the type
12132 -- declaration hold the partial view and the full view is an
12135 elsif Nkind_In
(Decl
, N_Full_Type_Declaration
,
12136 N_Private_Extension_Declaration
,
12137 N_Private_Type_Declaration
)
12139 Match
:= Defining_Identifier
(Decl
);
12142 -- Guard against unanalyzed entities
12145 and then Is_Type
(Match
)
12146 and then Present
(Full_View
(Match
))
12147 and then Full_View
(Match
) = Id
12162 -- Start of processing for Incomplete_Or_Partial_View
12165 -- Deferred constant or incomplete type case
12167 Prev
:= Current_Entity_In_Scope
(Id
);
12170 and then (Is_Incomplete_Type
(Prev
) or else Ekind
(Prev
) = E_Constant
)
12171 and then Present
(Full_View
(Prev
))
12172 and then Full_View
(Prev
) = Id
12177 -- Private or Taft amendment type case
12180 Pkg
: constant Entity_Id
:= Scope
(Id
);
12181 Pkg_Decl
: Node_Id
:= Pkg
;
12185 and then Ekind_In
(Pkg
, E_Generic_Package
, E_Package
)
12187 while Nkind
(Pkg_Decl
) /= N_Package_Specification
loop
12188 Pkg_Decl
:= Parent
(Pkg_Decl
);
12191 -- It is knows that Typ has a private view, look for it in the
12192 -- visible declarations of the enclosing scope. A special case
12193 -- of this is when the two views have been exchanged - the full
12194 -- appears earlier than the private.
12196 if Has_Private_Declaration
(Id
) then
12197 Prev
:= Inspect_Decls
(Visible_Declarations
(Pkg_Decl
));
12199 -- Exchanged view case, look in the private declarations
12202 Prev
:= Inspect_Decls
(Private_Declarations
(Pkg_Decl
));
12207 -- Otherwise if this is the package body, then Typ is a potential
12208 -- Taft amendment type. The incomplete view should be located in
12209 -- the private declarations of the enclosing scope.
12211 elsif In_Package_Body
(Pkg
) then
12212 return Inspect_Decls
(Private_Declarations
(Pkg_Decl
), True);
12217 -- The type has no incomplete or private view
12220 end Incomplete_Or_Partial_View
;
12222 ---------------------------------------
12223 -- Incomplete_View_From_Limited_With --
12224 ---------------------------------------
12226 function Incomplete_View_From_Limited_With
12227 (Typ
: Entity_Id
) return Entity_Id
is
12229 -- It might make sense to make this an attribute in Einfo, and set it
12230 -- in Sem_Ch10 in Build_Shadow_Entity. However, we're running short on
12231 -- slots for new attributes, and it seems a bit simpler to just search
12232 -- the Limited_View (if it exists) for an incomplete type whose
12233 -- Non_Limited_View is Typ.
12235 if Ekind
(Scope
(Typ
)) = E_Package
12236 and then Present
(Limited_View
(Scope
(Typ
)))
12239 Ent
: Entity_Id
:= First_Entity
(Limited_View
(Scope
(Typ
)));
12241 while Present
(Ent
) loop
12242 if Ekind
(Ent
) in Incomplete_Kind
12243 and then Non_Limited_View
(Ent
) = Typ
12248 Ent
:= Next_Entity
(Ent
);
12254 end Incomplete_View_From_Limited_With
;
12256 ----------------------------------
12257 -- Indexed_Component_Bit_Offset --
12258 ----------------------------------
12260 function Indexed_Component_Bit_Offset
(N
: Node_Id
) return Uint
is
12261 Exp
: constant Node_Id
:= First
(Expressions
(N
));
12262 Typ
: constant Entity_Id
:= Etype
(Prefix
(N
));
12263 Off
: constant Uint
:= Component_Size
(Typ
);
12267 -- Return early if the component size is not known or variable
12269 if Off
= No_Uint
or else Off
< Uint_0
then
12273 -- Deal with the degenerate case of an empty component
12275 if Off
= Uint_0
then
12279 -- Check that both the index value and the low bound are known
12281 if not Compile_Time_Known_Value
(Exp
) then
12285 Ind
:= First_Index
(Typ
);
12290 if Nkind
(Ind
) = N_Subtype_Indication
then
12291 Ind
:= Constraint
(Ind
);
12293 if Nkind
(Ind
) = N_Range_Constraint
then
12294 Ind
:= Range_Expression
(Ind
);
12298 if Nkind
(Ind
) /= N_Range
12299 or else not Compile_Time_Known_Value
(Low_Bound
(Ind
))
12304 -- Return the scaled offset
12306 return Off
* (Expr_Value
(Exp
) - Expr_Value
(Low_Bound
((Ind
))));
12307 end Indexed_Component_Bit_Offset
;
12309 ----------------------------
12310 -- Inherit_Rep_Item_Chain --
12311 ----------------------------
12313 procedure Inherit_Rep_Item_Chain
(Typ
: Entity_Id
; From_Typ
: Entity_Id
) is
12315 Next_Item
: Node_Id
;
12318 -- There are several inheritance scenarios to consider depending on
12319 -- whether both types have rep item chains and whether the destination
12320 -- type already inherits part of the source type's rep item chain.
12322 -- 1) The source type lacks a rep item chain
12323 -- From_Typ ---> Empty
12325 -- Typ --------> Item (or Empty)
12327 -- In this case inheritance cannot take place because there are no items
12330 -- 2) The destination type lacks a rep item chain
12331 -- From_Typ ---> Item ---> ...
12333 -- Typ --------> Empty
12335 -- Inheritance takes place by setting the First_Rep_Item of the
12336 -- destination type to the First_Rep_Item of the source type.
12337 -- From_Typ ---> Item ---> ...
12339 -- Typ -----------+
12341 -- 3.1) Both source and destination types have at least one rep item.
12342 -- The destination type does NOT inherit a rep item from the source
12344 -- From_Typ ---> Item ---> Item
12346 -- Typ --------> Item ---> Item
12348 -- Inheritance takes place by setting the Next_Rep_Item of the last item
12349 -- of the destination type to the First_Rep_Item of the source type.
12350 -- From_Typ -------------------> Item ---> Item
12352 -- Typ --------> Item ---> Item --+
12354 -- 3.2) Both source and destination types have at least one rep item.
12355 -- The destination type DOES inherit part of the rep item chain of the
12357 -- From_Typ ---> Item ---> Item ---> Item
12359 -- Typ --------> Item ------+
12361 -- This rare case arises when the full view of a private extension must
12362 -- inherit the rep item chain from the full view of its parent type and
12363 -- the full view of the parent type contains extra rep items. Currently
12364 -- only invariants may lead to such form of inheritance.
12366 -- type From_Typ is tagged private
12367 -- with Type_Invariant'Class => Item_2;
12369 -- type Typ is new From_Typ with private
12370 -- with Type_Invariant => Item_4;
12372 -- At this point the rep item chains contain the following items
12374 -- From_Typ -----------> Item_2 ---> Item_3
12376 -- Typ --------> Item_4 --+
12378 -- The full views of both types may introduce extra invariants
12380 -- type From_Typ is tagged null record
12381 -- with Type_Invariant => Item_1;
12383 -- type Typ is new From_Typ with null record;
12385 -- The full view of Typ would have to inherit any new rep items added to
12386 -- the full view of From_Typ.
12388 -- From_Typ -----------> Item_1 ---> Item_2 ---> Item_3
12390 -- Typ --------> Item_4 --+
12392 -- To achieve this form of inheritance, the destination type must first
12393 -- sever the link between its own rep chain and that of the source type,
12394 -- then inheritance 3.1 takes place.
12396 -- Case 1: The source type lacks a rep item chain
12398 if No
(First_Rep_Item
(From_Typ
)) then
12401 -- Case 2: The destination type lacks a rep item chain
12403 elsif No
(First_Rep_Item
(Typ
)) then
12404 Set_First_Rep_Item
(Typ
, First_Rep_Item
(From_Typ
));
12406 -- Case 3: Both the source and destination types have at least one rep
12407 -- item. Traverse the rep item chain of the destination type to find the
12412 Next_Item
:= First_Rep_Item
(Typ
);
12413 while Present
(Next_Item
) loop
12415 -- Detect a link between the destination type's rep chain and that
12416 -- of the source type. There are two possibilities:
12421 -- From_Typ ---> Item_1 --->
12423 -- Typ -----------+
12430 -- From_Typ ---> Item_1 ---> Item_2 --->
12432 -- Typ --------> Item_3 ------+
12436 if Has_Rep_Item
(From_Typ
, Next_Item
) then
12441 Next_Item
:= Next_Rep_Item
(Next_Item
);
12444 -- Inherit the source type's rep item chain
12446 if Present
(Item
) then
12447 Set_Next_Rep_Item
(Item
, First_Rep_Item
(From_Typ
));
12449 Set_First_Rep_Item
(Typ
, First_Rep_Item
(From_Typ
));
12452 end Inherit_Rep_Item_Chain
;
12454 ---------------------------------
12455 -- Insert_Explicit_Dereference --
12456 ---------------------------------
12458 procedure Insert_Explicit_Dereference
(N
: Node_Id
) is
12459 New_Prefix
: constant Node_Id
:= Relocate_Node
(N
);
12460 Ent
: Entity_Id
:= Empty
;
12467 Save_Interps
(N
, New_Prefix
);
12470 Make_Explicit_Dereference
(Sloc
(Parent
(N
)),
12471 Prefix
=> New_Prefix
));
12473 Set_Etype
(N
, Designated_Type
(Etype
(New_Prefix
)));
12475 if Is_Overloaded
(New_Prefix
) then
12477 -- The dereference is also overloaded, and its interpretations are
12478 -- the designated types of the interpretations of the original node.
12480 Set_Etype
(N
, Any_Type
);
12482 Get_First_Interp
(New_Prefix
, I
, It
);
12483 while Present
(It
.Nam
) loop
12486 if Is_Access_Type
(T
) then
12487 Add_One_Interp
(N
, Designated_Type
(T
), Designated_Type
(T
));
12490 Get_Next_Interp
(I
, It
);
12496 -- Prefix is unambiguous: mark the original prefix (which might
12497 -- Come_From_Source) as a reference, since the new (relocated) one
12498 -- won't be taken into account.
12500 if Is_Entity_Name
(New_Prefix
) then
12501 Ent
:= Entity
(New_Prefix
);
12502 Pref
:= New_Prefix
;
12504 -- For a retrieval of a subcomponent of some composite object,
12505 -- retrieve the ultimate entity if there is one.
12507 elsif Nkind_In
(New_Prefix
, N_Selected_Component
,
12508 N_Indexed_Component
)
12510 Pref
:= Prefix
(New_Prefix
);
12511 while Present
(Pref
)
12512 and then Nkind_In
(Pref
, N_Selected_Component
,
12513 N_Indexed_Component
)
12515 Pref
:= Prefix
(Pref
);
12518 if Present
(Pref
) and then Is_Entity_Name
(Pref
) then
12519 Ent
:= Entity
(Pref
);
12523 -- Place the reference on the entity node
12525 if Present
(Ent
) then
12526 Generate_Reference
(Ent
, Pref
);
12529 end Insert_Explicit_Dereference
;
12531 ------------------------------------------
12532 -- Inspect_Deferred_Constant_Completion --
12533 ------------------------------------------
12535 procedure Inspect_Deferred_Constant_Completion
(Decls
: List_Id
) is
12539 Decl
:= First
(Decls
);
12540 while Present
(Decl
) loop
12542 -- Deferred constant signature
12544 if Nkind
(Decl
) = N_Object_Declaration
12545 and then Constant_Present
(Decl
)
12546 and then No
(Expression
(Decl
))
12548 -- No need to check internally generated constants
12550 and then Comes_From_Source
(Decl
)
12552 -- The constant is not completed. A full object declaration or a
12553 -- pragma Import complete a deferred constant.
12555 and then not Has_Completion
(Defining_Identifier
(Decl
))
12558 ("constant declaration requires initialization expression",
12559 Defining_Identifier
(Decl
));
12562 Decl
:= Next
(Decl
);
12564 end Inspect_Deferred_Constant_Completion
;
12566 -----------------------------
12567 -- Install_Generic_Formals --
12568 -----------------------------
12570 procedure Install_Generic_Formals
(Subp_Id
: Entity_Id
) is
12574 pragma Assert
(Is_Generic_Subprogram
(Subp_Id
));
12576 E
:= First_Entity
(Subp_Id
);
12577 while Present
(E
) loop
12578 Install_Entity
(E
);
12581 end Install_Generic_Formals
;
12583 ------------------------
12584 -- Install_SPARK_Mode --
12585 ------------------------
12587 procedure Install_SPARK_Mode
(Mode
: SPARK_Mode_Type
; Prag
: Node_Id
) is
12589 SPARK_Mode
:= Mode
;
12590 SPARK_Mode_Pragma
:= Prag
;
12591 end Install_SPARK_Mode
;
12593 -----------------------------
12594 -- Is_Actual_Out_Parameter --
12595 -----------------------------
12597 function Is_Actual_Out_Parameter
(N
: Node_Id
) return Boolean is
12598 Formal
: Entity_Id
;
12601 Find_Actual
(N
, Formal
, Call
);
12602 return Present
(Formal
) and then Ekind
(Formal
) = E_Out_Parameter
;
12603 end Is_Actual_Out_Parameter
;
12605 -------------------------
12606 -- Is_Actual_Parameter --
12607 -------------------------
12609 function Is_Actual_Parameter
(N
: Node_Id
) return Boolean is
12610 PK
: constant Node_Kind
:= Nkind
(Parent
(N
));
12614 when N_Parameter_Association
=>
12615 return N
= Explicit_Actual_Parameter
(Parent
(N
));
12617 when N_Subprogram_Call
=>
12618 return Is_List_Member
(N
)
12620 List_Containing
(N
) = Parameter_Associations
(Parent
(N
));
12625 end Is_Actual_Parameter
;
12627 --------------------------------
12628 -- Is_Actual_Tagged_Parameter --
12629 --------------------------------
12631 function Is_Actual_Tagged_Parameter
(N
: Node_Id
) return Boolean is
12632 Formal
: Entity_Id
;
12635 Find_Actual
(N
, Formal
, Call
);
12636 return Present
(Formal
) and then Is_Tagged_Type
(Etype
(Formal
));
12637 end Is_Actual_Tagged_Parameter
;
12639 ---------------------
12640 -- Is_Aliased_View --
12641 ---------------------
12643 function Is_Aliased_View
(Obj
: Node_Id
) return Boolean is
12647 if Is_Entity_Name
(Obj
) then
12654 or else (Present
(Renamed_Object
(E
))
12655 and then Is_Aliased_View
(Renamed_Object
(E
)))))
12657 or else ((Is_Formal
(E
) or else Is_Formal_Object
(E
))
12658 and then Is_Tagged_Type
(Etype
(E
)))
12660 or else (Is_Concurrent_Type
(E
) and then In_Open_Scopes
(E
))
12662 -- Current instance of type, either directly or as rewritten
12663 -- reference to the current object.
12665 or else (Is_Entity_Name
(Original_Node
(Obj
))
12666 and then Present
(Entity
(Original_Node
(Obj
)))
12667 and then Is_Type
(Entity
(Original_Node
(Obj
))))
12669 or else (Is_Type
(E
) and then E
= Current_Scope
)
12671 or else (Is_Incomplete_Or_Private_Type
(E
)
12672 and then Full_View
(E
) = Current_Scope
)
12674 -- Ada 2012 AI05-0053: the return object of an extended return
12675 -- statement is aliased if its type is immutably limited.
12677 or else (Is_Return_Object
(E
)
12678 and then Is_Limited_View
(Etype
(E
)));
12680 elsif Nkind
(Obj
) = N_Selected_Component
then
12681 return Is_Aliased
(Entity
(Selector_Name
(Obj
)));
12683 elsif Nkind
(Obj
) = N_Indexed_Component
then
12684 return Has_Aliased_Components
(Etype
(Prefix
(Obj
)))
12686 (Is_Access_Type
(Etype
(Prefix
(Obj
)))
12687 and then Has_Aliased_Components
12688 (Designated_Type
(Etype
(Prefix
(Obj
)))));
12690 elsif Nkind_In
(Obj
, N_Unchecked_Type_Conversion
, N_Type_Conversion
) then
12691 return Is_Tagged_Type
(Etype
(Obj
))
12692 and then Is_Aliased_View
(Expression
(Obj
));
12694 elsif Nkind
(Obj
) = N_Explicit_Dereference
then
12695 return Nkind
(Original_Node
(Obj
)) /= N_Function_Call
;
12700 end Is_Aliased_View
;
12702 -------------------------
12703 -- Is_Ancestor_Package --
12704 -------------------------
12706 function Is_Ancestor_Package
12708 E2
: Entity_Id
) return Boolean
12714 while Present
(Par
) and then Par
/= Standard_Standard
loop
12719 Par
:= Scope
(Par
);
12723 end Is_Ancestor_Package
;
12725 ----------------------
12726 -- Is_Atomic_Object --
12727 ----------------------
12729 function Is_Atomic_Object
(N
: Node_Id
) return Boolean is
12731 function Object_Has_Atomic_Components
(N
: Node_Id
) return Boolean;
12732 -- Determines if given object has atomic components
12734 function Is_Atomic_Prefix
(N
: Node_Id
) return Boolean;
12735 -- If prefix is an implicit dereference, examine designated type
12737 ----------------------
12738 -- Is_Atomic_Prefix --
12739 ----------------------
12741 function Is_Atomic_Prefix
(N
: Node_Id
) return Boolean is
12743 if Is_Access_Type
(Etype
(N
)) then
12745 Has_Atomic_Components
(Designated_Type
(Etype
(N
)));
12747 return Object_Has_Atomic_Components
(N
);
12749 end Is_Atomic_Prefix
;
12751 ----------------------------------
12752 -- Object_Has_Atomic_Components --
12753 ----------------------------------
12755 function Object_Has_Atomic_Components
(N
: Node_Id
) return Boolean is
12757 if Has_Atomic_Components
(Etype
(N
))
12758 or else Is_Atomic
(Etype
(N
))
12762 elsif Is_Entity_Name
(N
)
12763 and then (Has_Atomic_Components
(Entity
(N
))
12764 or else Is_Atomic
(Entity
(N
)))
12768 elsif Nkind
(N
) = N_Selected_Component
12769 and then Is_Atomic
(Entity
(Selector_Name
(N
)))
12773 elsif Nkind
(N
) = N_Indexed_Component
12774 or else Nkind
(N
) = N_Selected_Component
12776 return Is_Atomic_Prefix
(Prefix
(N
));
12781 end Object_Has_Atomic_Components
;
12783 -- Start of processing for Is_Atomic_Object
12786 -- Predicate is not relevant to subprograms
12788 if Is_Entity_Name
(N
) and then Is_Overloadable
(Entity
(N
)) then
12791 elsif Is_Atomic
(Etype
(N
))
12792 or else (Is_Entity_Name
(N
) and then Is_Atomic
(Entity
(N
)))
12796 elsif Nkind
(N
) = N_Selected_Component
12797 and then Is_Atomic
(Entity
(Selector_Name
(N
)))
12801 elsif Nkind
(N
) = N_Indexed_Component
12802 or else Nkind
(N
) = N_Selected_Component
12804 return Is_Atomic_Prefix
(Prefix
(N
));
12809 end Is_Atomic_Object
;
12811 -----------------------------
12812 -- Is_Atomic_Or_VFA_Object --
12813 -----------------------------
12815 function Is_Atomic_Or_VFA_Object
(N
: Node_Id
) return Boolean is
12817 return Is_Atomic_Object
(N
)
12818 or else (Is_Object_Reference
(N
)
12819 and then Is_Entity_Name
(N
)
12820 and then (Is_Volatile_Full_Access
(Entity
(N
))
12822 Is_Volatile_Full_Access
(Etype
(Entity
(N
)))));
12823 end Is_Atomic_Or_VFA_Object
;
12825 -------------------------
12826 -- Is_Attribute_Result --
12827 -------------------------
12829 function Is_Attribute_Result
(N
: Node_Id
) return Boolean is
12831 return Nkind
(N
) = N_Attribute_Reference
12832 and then Attribute_Name
(N
) = Name_Result
;
12833 end Is_Attribute_Result
;
12835 -------------------------
12836 -- Is_Attribute_Update --
12837 -------------------------
12839 function Is_Attribute_Update
(N
: Node_Id
) return Boolean is
12841 return Nkind
(N
) = N_Attribute_Reference
12842 and then Attribute_Name
(N
) = Name_Update
;
12843 end Is_Attribute_Update
;
12845 ------------------------------------
12846 -- Is_Body_Or_Package_Declaration --
12847 ------------------------------------
12849 function Is_Body_Or_Package_Declaration
(N
: Node_Id
) return Boolean is
12851 return Nkind_In
(N
, N_Entry_Body
,
12853 N_Package_Declaration
,
12857 end Is_Body_Or_Package_Declaration
;
12859 -----------------------
12860 -- Is_Bounded_String --
12861 -----------------------
12863 function Is_Bounded_String
(T
: Entity_Id
) return Boolean is
12864 Under
: constant Entity_Id
:= Underlying_Type
(Root_Type
(T
));
12867 -- Check whether T is ultimately derived from Ada.Strings.Superbounded.
12868 -- Super_String, or one of the [Wide_]Wide_ versions. This will
12869 -- be True for all the Bounded_String types in instances of the
12870 -- Generic_Bounded_Length generics, and for types derived from those.
12872 return Present
(Under
)
12873 and then (Is_RTE
(Root_Type
(Under
), RO_SU_Super_String
) or else
12874 Is_RTE
(Root_Type
(Under
), RO_WI_Super_String
) or else
12875 Is_RTE
(Root_Type
(Under
), RO_WW_Super_String
));
12876 end Is_Bounded_String
;
12878 ---------------------
12879 -- Is_CCT_Instance --
12880 ---------------------
12882 function Is_CCT_Instance
12883 (Ref_Id
: Entity_Id
;
12884 Context_Id
: Entity_Id
) return Boolean
12887 pragma Assert
(Ekind_In
(Ref_Id
, E_Protected_Type
, E_Task_Type
));
12889 if Is_Single_Task_Object
(Context_Id
) then
12890 return Scope_Within_Or_Same
(Etype
(Context_Id
), Ref_Id
);
12893 pragma Assert
(Ekind_In
(Context_Id
, E_Entry
,
12901 Is_Record_Type
(Context_Id
));
12902 return Scope_Within_Or_Same
(Context_Id
, Ref_Id
);
12904 end Is_CCT_Instance
;
12906 -------------------------
12907 -- Is_Child_Or_Sibling --
12908 -------------------------
12910 function Is_Child_Or_Sibling
12911 (Pack_1
: Entity_Id
;
12912 Pack_2
: Entity_Id
) return Boolean
12914 function Distance_From_Standard
(Pack
: Entity_Id
) return Nat
;
12915 -- Given an arbitrary package, return the number of "climbs" necessary
12916 -- to reach scope Standard_Standard.
12918 procedure Equalize_Depths
12919 (Pack
: in out Entity_Id
;
12920 Depth
: in out Nat
;
12921 Depth_To_Reach
: Nat
);
12922 -- Given an arbitrary package, its depth and a target depth to reach,
12923 -- climb the scope chain until the said depth is reached. The pointer
12924 -- to the package and its depth a modified during the climb.
12926 ----------------------------
12927 -- Distance_From_Standard --
12928 ----------------------------
12930 function Distance_From_Standard
(Pack
: Entity_Id
) return Nat
is
12937 while Present
(Scop
) and then Scop
/= Standard_Standard
loop
12939 Scop
:= Scope
(Scop
);
12943 end Distance_From_Standard
;
12945 ---------------------
12946 -- Equalize_Depths --
12947 ---------------------
12949 procedure Equalize_Depths
12950 (Pack
: in out Entity_Id
;
12951 Depth
: in out Nat
;
12952 Depth_To_Reach
: Nat
)
12955 -- The package must be at a greater or equal depth
12957 if Depth
< Depth_To_Reach
then
12958 raise Program_Error
;
12961 -- Climb the scope chain until the desired depth is reached
12963 while Present
(Pack
) and then Depth
/= Depth_To_Reach
loop
12964 Pack
:= Scope
(Pack
);
12965 Depth
:= Depth
- 1;
12967 end Equalize_Depths
;
12971 P_1
: Entity_Id
:= Pack_1
;
12972 P_1_Child
: Boolean := False;
12973 P_1_Depth
: Nat
:= Distance_From_Standard
(P_1
);
12974 P_2
: Entity_Id
:= Pack_2
;
12975 P_2_Child
: Boolean := False;
12976 P_2_Depth
: Nat
:= Distance_From_Standard
(P_2
);
12978 -- Start of processing for Is_Child_Or_Sibling
12982 (Ekind
(Pack_1
) = E_Package
and then Ekind
(Pack_2
) = E_Package
);
12984 -- Both packages denote the same entity, therefore they cannot be
12985 -- children or siblings.
12990 -- One of the packages is at a deeper level than the other. Note that
12991 -- both may still come from different hierarchies.
12999 elsif P_1_Depth
> P_2_Depth
then
13002 Depth
=> P_1_Depth
,
13003 Depth_To_Reach
=> P_2_Depth
);
13012 elsif P_2_Depth
> P_1_Depth
then
13015 Depth
=> P_2_Depth
,
13016 Depth_To_Reach
=> P_1_Depth
);
13020 -- At this stage the package pointers have been elevated to the same
13021 -- depth. If the related entities are the same, then one package is a
13022 -- potential child of the other:
13026 -- X became P_1 P_2 or vice versa
13032 return Is_Child_Unit
(Pack_1
);
13034 else pragma Assert
(P_2_Child
);
13035 return Is_Child_Unit
(Pack_2
);
13038 -- The packages may come from the same package chain or from entirely
13039 -- different hierarcies. To determine this, climb the scope stack until
13040 -- a common root is found.
13042 -- (root) (root 1) (root 2)
13047 while Present
(P_1
) and then Present
(P_2
) loop
13049 -- The two packages may be siblings
13052 return Is_Child_Unit
(Pack_1
) and then Is_Child_Unit
(Pack_2
);
13055 P_1
:= Scope
(P_1
);
13056 P_2
:= Scope
(P_2
);
13061 end Is_Child_Or_Sibling
;
13063 -----------------------------
13064 -- Is_Concurrent_Interface --
13065 -----------------------------
13067 function Is_Concurrent_Interface
(T
: Entity_Id
) return Boolean is
13069 return Is_Interface
(T
)
13071 (Is_Protected_Interface
(T
)
13072 or else Is_Synchronized_Interface
(T
)
13073 or else Is_Task_Interface
(T
));
13074 end Is_Concurrent_Interface
;
13076 -----------------------
13077 -- Is_Constant_Bound --
13078 -----------------------
13080 function Is_Constant_Bound
(Exp
: Node_Id
) return Boolean is
13082 if Compile_Time_Known_Value
(Exp
) then
13085 elsif Is_Entity_Name
(Exp
) and then Present
(Entity
(Exp
)) then
13086 return Is_Constant_Object
(Entity
(Exp
))
13087 or else Ekind
(Entity
(Exp
)) = E_Enumeration_Literal
;
13089 elsif Nkind
(Exp
) in N_Binary_Op
then
13090 return Is_Constant_Bound
(Left_Opnd
(Exp
))
13091 and then Is_Constant_Bound
(Right_Opnd
(Exp
))
13092 and then Scope
(Entity
(Exp
)) = Standard_Standard
;
13097 end Is_Constant_Bound
;
13099 ---------------------------
13100 -- Is_Container_Element --
13101 ---------------------------
13103 function Is_Container_Element
(Exp
: Node_Id
) return Boolean is
13104 Loc
: constant Source_Ptr
:= Sloc
(Exp
);
13105 Pref
: constant Node_Id
:= Prefix
(Exp
);
13108 -- Call to an indexing aspect
13110 Cont_Typ
: Entity_Id
;
13111 -- The type of the container being accessed
13113 Elem_Typ
: Entity_Id
;
13114 -- Its element type
13116 Indexing
: Entity_Id
;
13117 Is_Const
: Boolean;
13118 -- Indicates that constant indexing is used, and the element is thus
13121 Ref_Typ
: Entity_Id
;
13122 -- The reference type returned by the indexing operation
13125 -- If C is a container, in a context that imposes the element type of
13126 -- that container, the indexing notation C (X) is rewritten as:
13128 -- Indexing (C, X).Discr.all
13130 -- where Indexing is one of the indexing aspects of the container.
13131 -- If the context does not require a reference, the construct can be
13136 -- First, verify that the construct has the proper form
13138 if not Expander_Active
then
13141 elsif Nkind
(Pref
) /= N_Selected_Component
then
13144 elsif Nkind
(Prefix
(Pref
)) /= N_Function_Call
then
13148 Call
:= Prefix
(Pref
);
13149 Ref_Typ
:= Etype
(Call
);
13152 if not Has_Implicit_Dereference
(Ref_Typ
)
13153 or else No
(First
(Parameter_Associations
(Call
)))
13154 or else not Is_Entity_Name
(Name
(Call
))
13159 -- Retrieve type of container object, and its iterator aspects
13161 Cont_Typ
:= Etype
(First
(Parameter_Associations
(Call
)));
13162 Indexing
:= Find_Value_Of_Aspect
(Cont_Typ
, Aspect_Constant_Indexing
);
13165 if No
(Indexing
) then
13167 -- Container should have at least one indexing operation
13171 elsif Entity
(Name
(Call
)) /= Entity
(Indexing
) then
13173 -- This may be a variable indexing operation
13175 Indexing
:= Find_Value_Of_Aspect
(Cont_Typ
, Aspect_Variable_Indexing
);
13178 or else Entity
(Name
(Call
)) /= Entity
(Indexing
)
13187 Elem_Typ
:= Find_Value_Of_Aspect
(Cont_Typ
, Aspect_Iterator_Element
);
13189 if No
(Elem_Typ
) or else Entity
(Elem_Typ
) /= Etype
(Exp
) then
13193 -- Check that the expression is not the target of an assignment, in
13194 -- which case the rewriting is not possible.
13196 if not Is_Const
then
13202 while Present
(Par
)
13204 if Nkind
(Parent
(Par
)) = N_Assignment_Statement
13205 and then Par
= Name
(Parent
(Par
))
13209 -- A renaming produces a reference, and the transformation
13212 elsif Nkind
(Parent
(Par
)) = N_Object_Renaming_Declaration
then
13216 (Nkind
(Parent
(Par
)), N_Function_Call
,
13217 N_Procedure_Call_Statement
,
13218 N_Entry_Call_Statement
)
13220 -- Check that the element is not part of an actual for an
13221 -- in-out parameter.
13228 F
:= First_Formal
(Entity
(Name
(Parent
(Par
))));
13229 A
:= First
(Parameter_Associations
(Parent
(Par
)));
13230 while Present
(F
) loop
13231 if A
= Par
and then Ekind
(F
) /= E_In_Parameter
then
13240 -- E_In_Parameter in a call: element is not modified.
13245 Par
:= Parent
(Par
);
13250 -- The expression has the proper form and the context requires the
13251 -- element type. Retrieve the Element function of the container and
13252 -- rewrite the construct as a call to it.
13258 Op
:= First_Elmt
(Primitive_Operations
(Cont_Typ
));
13259 while Present
(Op
) loop
13260 exit when Chars
(Node
(Op
)) = Name_Element
;
13269 Make_Function_Call
(Loc
,
13270 Name
=> New_Occurrence_Of
(Node
(Op
), Loc
),
13271 Parameter_Associations
=> Parameter_Associations
(Call
)));
13272 Analyze_And_Resolve
(Exp
, Entity
(Elem_Typ
));
13276 end Is_Container_Element
;
13278 ----------------------------
13279 -- Is_Contract_Annotation --
13280 ----------------------------
13282 function Is_Contract_Annotation
(Item
: Node_Id
) return Boolean is
13284 return Is_Package_Contract_Annotation
(Item
)
13286 Is_Subprogram_Contract_Annotation
(Item
);
13287 end Is_Contract_Annotation
;
13289 --------------------------------------
13290 -- Is_Controlling_Limited_Procedure --
13291 --------------------------------------
13293 function Is_Controlling_Limited_Procedure
13294 (Proc_Nam
: Entity_Id
) return Boolean
13297 Param_Typ
: Entity_Id
:= Empty
;
13300 if Ekind
(Proc_Nam
) = E_Procedure
13301 and then Present
(Parameter_Specifications
(Parent
(Proc_Nam
)))
13305 (First
(Parameter_Specifications
(Parent
(Proc_Nam
))));
13307 -- The formal may be an anonymous access type
13309 if Nkind
(Param
) = N_Access_Definition
then
13310 Param_Typ
:= Entity
(Subtype_Mark
(Param
));
13312 Param_Typ
:= Etype
(Param
);
13315 -- In the case where an Itype was created for a dispatchin call, the
13316 -- procedure call has been rewritten. The actual may be an access to
13317 -- interface type in which case it is the designated type that is the
13318 -- controlling type.
13320 elsif Present
(Associated_Node_For_Itype
(Proc_Nam
))
13321 and then Present
(Original_Node
(Associated_Node_For_Itype
(Proc_Nam
)))
13323 Present
(Parameter_Associations
13324 (Associated_Node_For_Itype
(Proc_Nam
)))
13327 Etype
(First
(Parameter_Associations
13328 (Associated_Node_For_Itype
(Proc_Nam
))));
13330 if Ekind
(Param_Typ
) = E_Anonymous_Access_Type
then
13331 Param_Typ
:= Directly_Designated_Type
(Param_Typ
);
13335 if Present
(Param_Typ
) then
13337 Is_Interface
(Param_Typ
)
13338 and then Is_Limited_Record
(Param_Typ
);
13342 end Is_Controlling_Limited_Procedure
;
13344 -----------------------------
13345 -- Is_CPP_Constructor_Call --
13346 -----------------------------
13348 function Is_CPP_Constructor_Call
(N
: Node_Id
) return Boolean is
13350 return Nkind
(N
) = N_Function_Call
13351 and then Is_CPP_Class
(Etype
(Etype
(N
)))
13352 and then Is_Constructor
(Entity
(Name
(N
)))
13353 and then Is_Imported
(Entity
(Name
(N
)));
13354 end Is_CPP_Constructor_Call
;
13356 -------------------------
13357 -- Is_Current_Instance --
13358 -------------------------
13360 function Is_Current_Instance
(N
: Node_Id
) return Boolean is
13361 Typ
: constant Entity_Id
:= Entity
(N
);
13365 -- Simplest case: entity is a concurrent type and we are currently
13366 -- inside the body. This will eventually be expanded into a
13367 -- call to Self (for tasks) or _object (for protected objects).
13369 if Is_Concurrent_Type
(Typ
) and then In_Open_Scopes
(Typ
) then
13373 -- Check whether the context is a (sub)type declaration for the
13377 while Present
(P
) loop
13378 if Nkind_In
(P
, N_Full_Type_Declaration
,
13379 N_Private_Type_Declaration
,
13380 N_Subtype_Declaration
)
13381 and then Comes_From_Source
(P
)
13382 and then Defining_Entity
(P
) = Typ
13386 -- A subtype name may appear in an aspect specification for a
13387 -- Predicate_Failure aspect, for which we do not construct a
13388 -- wrapper procedure. The subtype will be replaced by the
13389 -- expression being tested when the corresponding predicate
13390 -- check is expanded.
13392 elsif Nkind
(P
) = N_Aspect_Specification
13393 and then Nkind
(Parent
(P
)) = N_Subtype_Declaration
13397 elsif Nkind
(P
) = N_Pragma
13399 Get_Pragma_Id
(P
) = Pragma_Predicate_Failure
13408 -- In any other context this is not a current occurrence
13411 end Is_Current_Instance
;
13413 --------------------
13414 -- Is_Declaration --
13415 --------------------
13417 function Is_Declaration
(N
: Node_Id
) return Boolean is
13420 Is_Declaration_Other_Than_Renaming
(N
)
13421 or else Is_Renaming_Declaration
(N
);
13422 end Is_Declaration
;
13424 ----------------------------------------
13425 -- Is_Declaration_Other_Than_Renaming --
13426 ----------------------------------------
13428 function Is_Declaration_Other_Than_Renaming
(N
: Node_Id
) return Boolean is
13431 when N_Abstract_Subprogram_Declaration
13432 | N_Exception_Declaration
13433 | N_Expression_Function
13434 | N_Full_Type_Declaration
13435 | N_Generic_Package_Declaration
13436 | N_Generic_Subprogram_Declaration
13437 | N_Number_Declaration
13438 | N_Object_Declaration
13439 | N_Package_Declaration
13440 | N_Private_Extension_Declaration
13441 | N_Private_Type_Declaration
13442 | N_Subprogram_Declaration
13443 | N_Subtype_Declaration
13450 end Is_Declaration_Other_Than_Renaming
;
13452 --------------------------------
13453 -- Is_Declared_Within_Variant --
13454 --------------------------------
13456 function Is_Declared_Within_Variant
(Comp
: Entity_Id
) return Boolean is
13457 Comp_Decl
: constant Node_Id
:= Parent
(Comp
);
13458 Comp_List
: constant Node_Id
:= Parent
(Comp_Decl
);
13460 return Nkind
(Parent
(Comp_List
)) = N_Variant
;
13461 end Is_Declared_Within_Variant
;
13463 ----------------------------------------------
13464 -- Is_Dependent_Component_Of_Mutable_Object --
13465 ----------------------------------------------
13467 function Is_Dependent_Component_Of_Mutable_Object
13468 (Object
: Node_Id
) return Boolean
13471 Prefix_Type
: Entity_Id
;
13472 P_Aliased
: Boolean := False;
13475 Deref
: Node_Id
:= Object
;
13476 -- Dereference node, in something like X.all.Y(2)
13478 -- Start of processing for Is_Dependent_Component_Of_Mutable_Object
13481 -- Find the dereference node if any
13483 while Nkind_In
(Deref
, N_Indexed_Component
,
13484 N_Selected_Component
,
13487 Deref
:= Prefix
(Deref
);
13490 -- Ada 2005: If we have a component or slice of a dereference,
13491 -- something like X.all.Y (2), and the type of X is access-to-constant,
13492 -- Is_Variable will return False, because it is indeed a constant
13493 -- view. But it might be a view of a variable object, so we want the
13494 -- following condition to be True in that case.
13496 if Is_Variable
(Object
)
13497 or else (Ada_Version
>= Ada_2005
13498 and then Nkind
(Deref
) = N_Explicit_Dereference
)
13500 if Nkind
(Object
) = N_Selected_Component
then
13501 P
:= Prefix
(Object
);
13502 Prefix_Type
:= Etype
(P
);
13504 if Is_Entity_Name
(P
) then
13505 if Ekind
(Entity
(P
)) = E_Generic_In_Out_Parameter
then
13506 Prefix_Type
:= Base_Type
(Prefix_Type
);
13509 if Is_Aliased
(Entity
(P
)) then
13513 -- A discriminant check on a selected component may be expanded
13514 -- into a dereference when removing side effects. Recover the
13515 -- original node and its type, which may be unconstrained.
13517 elsif Nkind
(P
) = N_Explicit_Dereference
13518 and then not (Comes_From_Source
(P
))
13520 P
:= Original_Node
(P
);
13521 Prefix_Type
:= Etype
(P
);
13524 -- Check for prefix being an aliased component???
13530 -- A heap object is constrained by its initial value
13532 -- Ada 2005 (AI-363): Always assume the object could be mutable in
13533 -- the dereferenced case, since the access value might denote an
13534 -- unconstrained aliased object, whereas in Ada 95 the designated
13535 -- object is guaranteed to be constrained. A worst-case assumption
13536 -- has to apply in Ada 2005 because we can't tell at compile
13537 -- time whether the object is "constrained by its initial value",
13538 -- despite the fact that 3.10.2(26/2) and 8.5.1(5/2) are semantic
13539 -- rules (these rules are acknowledged to need fixing). We don't
13540 -- impose this more stringent checking for earlier Ada versions or
13541 -- when Relaxed_RM_Semantics applies (the latter for CodePeer's
13542 -- benefit, though it's unclear on why using -gnat95 would not be
13545 if Ada_Version
< Ada_2005
or else Relaxed_RM_Semantics
then
13546 if Is_Access_Type
(Prefix_Type
)
13547 or else Nkind
(P
) = N_Explicit_Dereference
13552 else pragma Assert
(Ada_Version
>= Ada_2005
);
13553 if Is_Access_Type
(Prefix_Type
) then
13555 -- If the access type is pool-specific, and there is no
13556 -- constrained partial view of the designated type, then the
13557 -- designated object is known to be constrained.
13559 if Ekind
(Prefix_Type
) = E_Access_Type
13560 and then not Object_Type_Has_Constrained_Partial_View
13561 (Typ
=> Designated_Type
(Prefix_Type
),
13562 Scop
=> Current_Scope
)
13566 -- Otherwise (general access type, or there is a constrained
13567 -- partial view of the designated type), we need to check
13568 -- based on the designated type.
13571 Prefix_Type
:= Designated_Type
(Prefix_Type
);
13577 Original_Record_Component
(Entity
(Selector_Name
(Object
)));
13579 -- As per AI-0017, the renaming is illegal in a generic body, even
13580 -- if the subtype is indefinite.
13582 -- Ada 2005 (AI-363): In Ada 2005 an aliased object can be mutable
13584 if not Is_Constrained
(Prefix_Type
)
13585 and then (Is_Definite_Subtype
(Prefix_Type
)
13587 (Is_Generic_Type
(Prefix_Type
)
13588 and then Ekind
(Current_Scope
) = E_Generic_Package
13589 and then In_Package_Body
(Current_Scope
)))
13591 and then (Is_Declared_Within_Variant
(Comp
)
13592 or else Has_Discriminant_Dependent_Constraint
(Comp
))
13593 and then (not P_Aliased
or else Ada_Version
>= Ada_2005
)
13597 -- If the prefix is of an access type at this point, then we want
13598 -- to return False, rather than calling this function recursively
13599 -- on the access object (which itself might be a discriminant-
13600 -- dependent component of some other object, but that isn't
13601 -- relevant to checking the object passed to us). This avoids
13602 -- issuing wrong errors when compiling with -gnatc, where there
13603 -- can be implicit dereferences that have not been expanded.
13605 elsif Is_Access_Type
(Etype
(Prefix
(Object
))) then
13610 Is_Dependent_Component_Of_Mutable_Object
(Prefix
(Object
));
13613 elsif Nkind
(Object
) = N_Indexed_Component
13614 or else Nkind
(Object
) = N_Slice
13616 return Is_Dependent_Component_Of_Mutable_Object
(Prefix
(Object
));
13618 -- A type conversion that Is_Variable is a view conversion:
13619 -- go back to the denoted object.
13621 elsif Nkind
(Object
) = N_Type_Conversion
then
13623 Is_Dependent_Component_Of_Mutable_Object
(Expression
(Object
));
13628 end Is_Dependent_Component_Of_Mutable_Object
;
13630 ---------------------
13631 -- Is_Dereferenced --
13632 ---------------------
13634 function Is_Dereferenced
(N
: Node_Id
) return Boolean is
13635 P
: constant Node_Id
:= Parent
(N
);
13637 return Nkind_In
(P
, N_Selected_Component
,
13638 N_Explicit_Dereference
,
13639 N_Indexed_Component
,
13641 and then Prefix
(P
) = N
;
13642 end Is_Dereferenced
;
13644 ----------------------
13645 -- Is_Descendant_Of --
13646 ----------------------
13648 function Is_Descendant_Of
(T1
: Entity_Id
; T2
: Entity_Id
) return Boolean is
13653 pragma Assert
(Nkind
(T1
) in N_Entity
);
13654 pragma Assert
(Nkind
(T2
) in N_Entity
);
13656 T
:= Base_Type
(T1
);
13658 -- Immediate return if the types match
13663 -- Comment needed here ???
13665 elsif Ekind
(T
) = E_Class_Wide_Type
then
13666 return Etype
(T
) = T2
;
13674 -- Done if we found the type we are looking for
13679 -- Done if no more derivations to check
13686 -- Following test catches error cases resulting from prev errors
13688 elsif No
(Etyp
) then
13691 elsif Is_Private_Type
(T
) and then Etyp
= Full_View
(T
) then
13694 elsif Is_Private_Type
(Etyp
) and then Full_View
(Etyp
) = T
then
13698 T
:= Base_Type
(Etyp
);
13701 end Is_Descendant_Of
;
13703 ----------------------------------------
13704 -- Is_Descendant_Of_Suspension_Object --
13705 ----------------------------------------
13707 function Is_Descendant_Of_Suspension_Object
13708 (Typ
: Entity_Id
) return Boolean
13710 Cur_Typ
: Entity_Id
;
13711 Par_Typ
: Entity_Id
;
13714 -- Climb the type derivation chain checking each parent type against
13715 -- Suspension_Object.
13717 Cur_Typ
:= Base_Type
(Typ
);
13718 while Present
(Cur_Typ
) loop
13719 Par_Typ
:= Etype
(Cur_Typ
);
13721 -- The current type is a match
13723 if Is_Suspension_Object
(Cur_Typ
) then
13726 -- Stop the traversal once the root of the derivation chain has been
13727 -- reached. In that case the current type is its own base type.
13729 elsif Cur_Typ
= Par_Typ
then
13733 Cur_Typ
:= Base_Type
(Par_Typ
);
13737 end Is_Descendant_Of_Suspension_Object
;
13739 ---------------------------------------------
13740 -- Is_Double_Precision_Floating_Point_Type --
13741 ---------------------------------------------
13743 function Is_Double_Precision_Floating_Point_Type
13744 (E
: Entity_Id
) return Boolean is
13746 return Is_Floating_Point_Type
(E
)
13747 and then Machine_Radix_Value
(E
) = Uint_2
13748 and then Machine_Mantissa_Value
(E
) = UI_From_Int
(53)
13749 and then Machine_Emax_Value
(E
) = Uint_2
** Uint_10
13750 and then Machine_Emin_Value
(E
) = Uint_3
- (Uint_2
** Uint_10
);
13751 end Is_Double_Precision_Floating_Point_Type
;
13753 -----------------------------
13754 -- Is_Effectively_Volatile --
13755 -----------------------------
13757 function Is_Effectively_Volatile
(Id
: Entity_Id
) return Boolean is
13759 if Is_Type
(Id
) then
13761 -- An arbitrary type is effectively volatile when it is subject to
13762 -- pragma Atomic or Volatile.
13764 if Is_Volatile
(Id
) then
13767 -- An array type is effectively volatile when it is subject to pragma
13768 -- Atomic_Components or Volatile_Components or its component type is
13769 -- effectively volatile.
13771 elsif Is_Array_Type
(Id
) then
13773 Anc
: Entity_Id
:= Base_Type
(Id
);
13775 if Is_Private_Type
(Anc
) then
13776 Anc
:= Full_View
(Anc
);
13779 -- Test for presence of ancestor, as the full view of a private
13780 -- type may be missing in case of error.
13783 Has_Volatile_Components
(Id
)
13786 and then Is_Effectively_Volatile
(Component_Type
(Anc
)));
13789 -- A protected type is always volatile
13791 elsif Is_Protected_Type
(Id
) then
13794 -- A descendant of Ada.Synchronous_Task_Control.Suspension_Object is
13795 -- automatically volatile.
13797 elsif Is_Descendant_Of_Suspension_Object
(Id
) then
13800 -- Otherwise the type is not effectively volatile
13806 -- Otherwise Id denotes an object
13811 or else Has_Volatile_Components
(Id
)
13812 or else Is_Effectively_Volatile
(Etype
(Id
));
13814 end Is_Effectively_Volatile
;
13816 ------------------------------------
13817 -- Is_Effectively_Volatile_Object --
13818 ------------------------------------
13820 function Is_Effectively_Volatile_Object
(N
: Node_Id
) return Boolean is
13822 if Is_Entity_Name
(N
) then
13823 return Is_Effectively_Volatile
(Entity
(N
));
13825 elsif Nkind
(N
) = N_Indexed_Component
then
13826 return Is_Effectively_Volatile_Object
(Prefix
(N
));
13828 elsif Nkind
(N
) = N_Selected_Component
then
13830 Is_Effectively_Volatile_Object
(Prefix
(N
))
13832 Is_Effectively_Volatile_Object
(Selector_Name
(N
));
13837 end Is_Effectively_Volatile_Object
;
13839 -------------------
13840 -- Is_Entry_Body --
13841 -------------------
13843 function Is_Entry_Body
(Id
: Entity_Id
) return Boolean is
13846 Ekind_In
(Id
, E_Entry
, E_Entry_Family
)
13847 and then Nkind
(Unit_Declaration_Node
(Id
)) = N_Entry_Body
;
13850 --------------------------
13851 -- Is_Entry_Declaration --
13852 --------------------------
13854 function Is_Entry_Declaration
(Id
: Entity_Id
) return Boolean is
13857 Ekind_In
(Id
, E_Entry
, E_Entry_Family
)
13858 and then Nkind
(Unit_Declaration_Node
(Id
)) = N_Entry_Declaration
;
13859 end Is_Entry_Declaration
;
13861 ------------------------------------
13862 -- Is_Expanded_Priority_Attribute --
13863 ------------------------------------
13865 function Is_Expanded_Priority_Attribute
(E
: Entity_Id
) return Boolean is
13868 Nkind
(E
) = N_Function_Call
13869 and then not Configurable_Run_Time_Mode
13870 and then (Entity
(Name
(E
)) = RTE
(RE_Get_Ceiling
)
13871 or else Entity
(Name
(E
)) = RTE
(RO_PE_Get_Ceiling
));
13872 end Is_Expanded_Priority_Attribute
;
13874 ----------------------------
13875 -- Is_Expression_Function --
13876 ----------------------------
13878 function Is_Expression_Function
(Subp
: Entity_Id
) return Boolean is
13880 if Ekind_In
(Subp
, E_Function
, E_Subprogram_Body
) then
13882 Nkind
(Original_Node
(Unit_Declaration_Node
(Subp
))) =
13883 N_Expression_Function
;
13887 end Is_Expression_Function
;
13889 ------------------------------------------
13890 -- Is_Expression_Function_Or_Completion --
13891 ------------------------------------------
13893 function Is_Expression_Function_Or_Completion
13894 (Subp
: Entity_Id
) return Boolean
13896 Subp_Decl
: Node_Id
;
13899 if Ekind
(Subp
) = E_Function
then
13900 Subp_Decl
:= Unit_Declaration_Node
(Subp
);
13902 -- The function declaration is either an expression function or is
13903 -- completed by an expression function body.
13906 Is_Expression_Function
(Subp
)
13907 or else (Nkind
(Subp_Decl
) = N_Subprogram_Declaration
13908 and then Present
(Corresponding_Body
(Subp_Decl
))
13909 and then Is_Expression_Function
13910 (Corresponding_Body
(Subp_Decl
)));
13912 elsif Ekind
(Subp
) = E_Subprogram_Body
then
13913 return Is_Expression_Function
(Subp
);
13918 end Is_Expression_Function_Or_Completion
;
13920 -----------------------
13921 -- Is_EVF_Expression --
13922 -----------------------
13924 function Is_EVF_Expression
(N
: Node_Id
) return Boolean is
13925 Orig_N
: constant Node_Id
:= Original_Node
(N
);
13931 -- Detect a reference to a formal parameter of a specific tagged type
13932 -- whose related subprogram is subject to pragma Expresions_Visible with
13935 if Is_Entity_Name
(N
) and then Present
(Entity
(N
)) then
13940 and then Is_Specific_Tagged_Type
(Etype
(Id
))
13941 and then Extensions_Visible_Status
(Id
) =
13942 Extensions_Visible_False
;
13944 -- A case expression is an EVF expression when it contains at least one
13945 -- EVF dependent_expression. Note that a case expression may have been
13946 -- expanded, hence the use of Original_Node.
13948 elsif Nkind
(Orig_N
) = N_Case_Expression
then
13949 Alt
:= First
(Alternatives
(Orig_N
));
13950 while Present
(Alt
) loop
13951 if Is_EVF_Expression
(Expression
(Alt
)) then
13958 -- An if expression is an EVF expression when it contains at least one
13959 -- EVF dependent_expression. Note that an if expression may have been
13960 -- expanded, hence the use of Original_Node.
13962 elsif Nkind
(Orig_N
) = N_If_Expression
then
13963 Expr
:= Next
(First
(Expressions
(Orig_N
)));
13964 while Present
(Expr
) loop
13965 if Is_EVF_Expression
(Expr
) then
13972 -- A qualified expression or a type conversion is an EVF expression when
13973 -- its operand is an EVF expression.
13975 elsif Nkind_In
(N
, N_Qualified_Expression
,
13976 N_Unchecked_Type_Conversion
,
13979 return Is_EVF_Expression
(Expression
(N
));
13981 -- Attributes 'Loop_Entry, 'Old, and 'Update are EVF expressions when
13982 -- their prefix denotes an EVF expression.
13984 elsif Nkind
(N
) = N_Attribute_Reference
13985 and then Nam_In
(Attribute_Name
(N
), Name_Loop_Entry
,
13989 return Is_EVF_Expression
(Prefix
(N
));
13993 end Is_EVF_Expression
;
13999 function Is_False
(U
: Uint
) return Boolean is
14004 ---------------------------
14005 -- Is_Fixed_Model_Number --
14006 ---------------------------
14008 function Is_Fixed_Model_Number
(U
: Ureal
; T
: Entity_Id
) return Boolean is
14009 S
: constant Ureal
:= Small_Value
(T
);
14010 M
: Urealp
.Save_Mark
;
14015 R
:= (U
= UR_Trunc
(U
/ S
) * S
);
14016 Urealp
.Release
(M
);
14018 end Is_Fixed_Model_Number
;
14020 -------------------------------
14021 -- Is_Fully_Initialized_Type --
14022 -------------------------------
14024 function Is_Fully_Initialized_Type
(Typ
: Entity_Id
) return Boolean is
14028 if Is_Scalar_Type
(Typ
) then
14030 -- A scalar type with an aspect Default_Value is fully initialized
14032 -- Note: Iniitalize/Normalize_Scalars also ensure full initialization
14033 -- of a scalar type, but we don't take that into account here, since
14034 -- we don't want these to affect warnings.
14036 return Has_Default_Aspect
(Typ
);
14038 elsif Is_Access_Type
(Typ
) then
14041 elsif Is_Array_Type
(Typ
) then
14042 if Is_Fully_Initialized_Type
(Component_Type
(Typ
))
14043 or else (Ada_Version
>= Ada_2012
and then Has_Default_Aspect
(Typ
))
14048 -- An interesting case, if we have a constrained type one of whose
14049 -- bounds is known to be null, then there are no elements to be
14050 -- initialized, so all the elements are initialized.
14052 if Is_Constrained
(Typ
) then
14055 Indx_Typ
: Entity_Id
;
14056 Lbd
, Hbd
: Node_Id
;
14059 Indx
:= First_Index
(Typ
);
14060 while Present
(Indx
) loop
14061 if Etype
(Indx
) = Any_Type
then
14064 -- If index is a range, use directly
14066 elsif Nkind
(Indx
) = N_Range
then
14067 Lbd
:= Low_Bound
(Indx
);
14068 Hbd
:= High_Bound
(Indx
);
14071 Indx_Typ
:= Etype
(Indx
);
14073 if Is_Private_Type
(Indx_Typ
) then
14074 Indx_Typ
:= Full_View
(Indx_Typ
);
14077 if No
(Indx_Typ
) or else Etype
(Indx_Typ
) = Any_Type
then
14080 Lbd
:= Type_Low_Bound
(Indx_Typ
);
14081 Hbd
:= Type_High_Bound
(Indx_Typ
);
14085 if Compile_Time_Known_Value
(Lbd
)
14087 Compile_Time_Known_Value
(Hbd
)
14089 if Expr_Value
(Hbd
) < Expr_Value
(Lbd
) then
14099 -- If no null indexes, then type is not fully initialized
14105 elsif Is_Record_Type
(Typ
) then
14106 if Has_Discriminants
(Typ
)
14108 Present
(Discriminant_Default_Value
(First_Discriminant
(Typ
)))
14109 and then Is_Fully_Initialized_Variant
(Typ
)
14114 -- We consider bounded string types to be fully initialized, because
14115 -- otherwise we get false alarms when the Data component is not
14116 -- default-initialized.
14118 if Is_Bounded_String
(Typ
) then
14122 -- Controlled records are considered to be fully initialized if
14123 -- there is a user defined Initialize routine. This may not be
14124 -- entirely correct, but as the spec notes, we are guessing here
14125 -- what is best from the point of view of issuing warnings.
14127 if Is_Controlled
(Typ
) then
14129 Utyp
: constant Entity_Id
:= Underlying_Type
(Typ
);
14132 if Present
(Utyp
) then
14134 Init
: constant Entity_Id
:=
14135 (Find_Optional_Prim_Op
14136 (Underlying_Type
(Typ
), Name_Initialize
));
14140 and then Comes_From_Source
(Init
)
14141 and then not In_Predefined_Unit
(Init
)
14145 elsif Has_Null_Extension
(Typ
)
14147 Is_Fully_Initialized_Type
14148 (Etype
(Base_Type
(Typ
)))
14157 -- Otherwise see if all record components are initialized
14163 Ent
:= First_Entity
(Typ
);
14164 while Present
(Ent
) loop
14165 if Ekind
(Ent
) = E_Component
14166 and then (No
(Parent
(Ent
))
14167 or else No
(Expression
(Parent
(Ent
))))
14168 and then not Is_Fully_Initialized_Type
(Etype
(Ent
))
14170 -- Special VM case for tag components, which need to be
14171 -- defined in this case, but are never initialized as VMs
14172 -- are using other dispatching mechanisms. Ignore this
14173 -- uninitialized case. Note that this applies both to the
14174 -- uTag entry and the main vtable pointer (CPP_Class case).
14176 and then (Tagged_Type_Expansion
or else not Is_Tag
(Ent
))
14185 -- No uninitialized components, so type is fully initialized.
14186 -- Note that this catches the case of no components as well.
14190 elsif Is_Concurrent_Type
(Typ
) then
14193 elsif Is_Private_Type
(Typ
) then
14195 U
: constant Entity_Id
:= Underlying_Type
(Typ
);
14201 return Is_Fully_Initialized_Type
(U
);
14208 end Is_Fully_Initialized_Type
;
14210 ----------------------------------
14211 -- Is_Fully_Initialized_Variant --
14212 ----------------------------------
14214 function Is_Fully_Initialized_Variant
(Typ
: Entity_Id
) return Boolean is
14215 Loc
: constant Source_Ptr
:= Sloc
(Typ
);
14216 Constraints
: constant List_Id
:= New_List
;
14217 Components
: constant Elist_Id
:= New_Elmt_List
;
14218 Comp_Elmt
: Elmt_Id
;
14220 Comp_List
: Node_Id
;
14222 Discr_Val
: Node_Id
;
14224 Report_Errors
: Boolean;
14225 pragma Warnings
(Off
, Report_Errors
);
14228 if Serious_Errors_Detected
> 0 then
14232 if Is_Record_Type
(Typ
)
14233 and then Nkind
(Parent
(Typ
)) = N_Full_Type_Declaration
14234 and then Nkind
(Type_Definition
(Parent
(Typ
))) = N_Record_Definition
14236 Comp_List
:= Component_List
(Type_Definition
(Parent
(Typ
)));
14238 Discr
:= First_Discriminant
(Typ
);
14239 while Present
(Discr
) loop
14240 if Nkind
(Parent
(Discr
)) = N_Discriminant_Specification
then
14241 Discr_Val
:= Expression
(Parent
(Discr
));
14243 if Present
(Discr_Val
)
14244 and then Is_OK_Static_Expression
(Discr_Val
)
14246 Append_To
(Constraints
,
14247 Make_Component_Association
(Loc
,
14248 Choices
=> New_List
(New_Occurrence_Of
(Discr
, Loc
)),
14249 Expression
=> New_Copy
(Discr_Val
)));
14257 Next_Discriminant
(Discr
);
14262 Comp_List
=> Comp_List
,
14263 Governed_By
=> Constraints
,
14264 Into
=> Components
,
14265 Report_Errors
=> Report_Errors
);
14267 -- Check that each component present is fully initialized
14269 Comp_Elmt
:= First_Elmt
(Components
);
14270 while Present
(Comp_Elmt
) loop
14271 Comp_Id
:= Node
(Comp_Elmt
);
14273 if Ekind
(Comp_Id
) = E_Component
14274 and then (No
(Parent
(Comp_Id
))
14275 or else No
(Expression
(Parent
(Comp_Id
))))
14276 and then not Is_Fully_Initialized_Type
(Etype
(Comp_Id
))
14281 Next_Elmt
(Comp_Elmt
);
14286 elsif Is_Private_Type
(Typ
) then
14288 U
: constant Entity_Id
:= Underlying_Type
(Typ
);
14294 return Is_Fully_Initialized_Variant
(U
);
14301 end Is_Fully_Initialized_Variant
;
14303 ------------------------------------
14304 -- Is_Generic_Declaration_Or_Body --
14305 ------------------------------------
14307 function Is_Generic_Declaration_Or_Body
(Decl
: Node_Id
) return Boolean is
14308 Spec_Decl
: Node_Id
;
14311 -- Package/subprogram body
14313 if Nkind_In
(Decl
, N_Package_Body
, N_Subprogram_Body
)
14314 and then Present
(Corresponding_Spec
(Decl
))
14316 Spec_Decl
:= Unit_Declaration_Node
(Corresponding_Spec
(Decl
));
14318 -- Package/subprogram body stub
14320 elsif Nkind_In
(Decl
, N_Package_Body_Stub
, N_Subprogram_Body_Stub
)
14321 and then Present
(Corresponding_Spec_Of_Stub
(Decl
))
14324 Unit_Declaration_Node
(Corresponding_Spec_Of_Stub
(Decl
));
14332 -- Rather than inspecting the defining entity of the spec declaration,
14333 -- look at its Nkind. This takes care of the case where the analysis of
14334 -- a generic body modifies the Ekind of its spec to allow for recursive
14338 Nkind_In
(Spec_Decl
, N_Generic_Package_Declaration
,
14339 N_Generic_Subprogram_Declaration
);
14340 end Is_Generic_Declaration_Or_Body
;
14342 ----------------------------
14343 -- Is_Inherited_Operation --
14344 ----------------------------
14346 function Is_Inherited_Operation
(E
: Entity_Id
) return Boolean is
14347 pragma Assert
(Is_Overloadable
(E
));
14348 Kind
: constant Node_Kind
:= Nkind
(Parent
(E
));
14350 return Kind
= N_Full_Type_Declaration
14351 or else Kind
= N_Private_Extension_Declaration
14352 or else Kind
= N_Subtype_Declaration
14353 or else (Ekind
(E
) = E_Enumeration_Literal
14354 and then Is_Derived_Type
(Etype
(E
)));
14355 end Is_Inherited_Operation
;
14357 -------------------------------------
14358 -- Is_Inherited_Operation_For_Type --
14359 -------------------------------------
14361 function Is_Inherited_Operation_For_Type
14363 Typ
: Entity_Id
) return Boolean
14366 -- Check that the operation has been created by the type declaration
14368 return Is_Inherited_Operation
(E
)
14369 and then Defining_Identifier
(Parent
(E
)) = Typ
;
14370 end Is_Inherited_Operation_For_Type
;
14372 --------------------------------------
14373 -- Is_Inlinable_Expression_Function --
14374 --------------------------------------
14376 function Is_Inlinable_Expression_Function
14377 (Subp
: Entity_Id
) return Boolean
14379 Return_Expr
: Node_Id
;
14382 if Is_Expression_Function_Or_Completion
(Subp
)
14383 and then Has_Pragma_Inline_Always
(Subp
)
14384 and then Needs_No_Actuals
(Subp
)
14385 and then No
(Contract
(Subp
))
14386 and then not Is_Dispatching_Operation
(Subp
)
14387 and then Needs_Finalization
(Etype
(Subp
))
14388 and then not Is_Class_Wide_Type
(Etype
(Subp
))
14389 and then not (Has_Invariants
(Etype
(Subp
)))
14390 and then Present
(Subprogram_Body
(Subp
))
14391 and then Was_Expression_Function
(Subprogram_Body
(Subp
))
14393 Return_Expr
:= Expression_Of_Expression_Function
(Subp
);
14395 -- The returned object must not have a qualified expression and its
14396 -- nominal subtype must be statically compatible with the result
14397 -- subtype of the expression function.
14400 Nkind
(Return_Expr
) = N_Identifier
14401 and then Etype
(Return_Expr
) = Etype
(Subp
);
14405 end Is_Inlinable_Expression_Function
;
14411 function Is_Iterator
(Typ
: Entity_Id
) return Boolean is
14412 function Denotes_Iterator
(Iter_Typ
: Entity_Id
) return Boolean;
14413 -- Determine whether type Iter_Typ is a predefined forward or reversible
14416 ----------------------
14417 -- Denotes_Iterator --
14418 ----------------------
14420 function Denotes_Iterator
(Iter_Typ
: Entity_Id
) return Boolean is
14422 -- Check that the name matches, and that the ultimate ancestor is in
14423 -- a predefined unit, i.e the one that declares iterator interfaces.
14426 Nam_In
(Chars
(Iter_Typ
), Name_Forward_Iterator
,
14427 Name_Reversible_Iterator
)
14428 and then In_Predefined_Unit
(Root_Type
(Iter_Typ
));
14429 end Denotes_Iterator
;
14433 Iface_Elmt
: Elmt_Id
;
14436 -- Start of processing for Is_Iterator
14439 -- The type may be a subtype of a descendant of the proper instance of
14440 -- the predefined interface type, so we must use the root type of the
14441 -- given type. The same is done for Is_Reversible_Iterator.
14443 if Is_Class_Wide_Type
(Typ
)
14444 and then Denotes_Iterator
(Root_Type
(Typ
))
14448 elsif not Is_Tagged_Type
(Typ
) or else not Is_Derived_Type
(Typ
) then
14451 elsif Present
(Find_Value_Of_Aspect
(Typ
, Aspect_Iterable
)) then
14455 Collect_Interfaces
(Typ
, Ifaces
);
14457 Iface_Elmt
:= First_Elmt
(Ifaces
);
14458 while Present
(Iface_Elmt
) loop
14459 if Denotes_Iterator
(Node
(Iface_Elmt
)) then
14463 Next_Elmt
(Iface_Elmt
);
14470 ----------------------------
14471 -- Is_Iterator_Over_Array --
14472 ----------------------------
14474 function Is_Iterator_Over_Array
(N
: Node_Id
) return Boolean is
14475 Container
: constant Node_Id
:= Name
(N
);
14476 Container_Typ
: constant Entity_Id
:= Base_Type
(Etype
(Container
));
14478 return Is_Array_Type
(Container_Typ
);
14479 end Is_Iterator_Over_Array
;
14485 -- We seem to have a lot of overlapping functions that do similar things
14486 -- (testing for left hand sides or lvalues???).
14488 function Is_LHS
(N
: Node_Id
) return Is_LHS_Result
is
14489 P
: constant Node_Id
:= Parent
(N
);
14492 -- Return True if we are the left hand side of an assignment statement
14494 if Nkind
(P
) = N_Assignment_Statement
then
14495 if Name
(P
) = N
then
14501 -- Case of prefix of indexed or selected component or slice
14503 elsif Nkind_In
(P
, N_Indexed_Component
, N_Selected_Component
, N_Slice
)
14504 and then N
= Prefix
(P
)
14506 -- Here we have the case where the parent P is N.Q or N(Q .. R).
14507 -- If P is an LHS, then N is also effectively an LHS, but there
14508 -- is an important exception. If N is of an access type, then
14509 -- what we really have is N.all.Q (or N.all(Q .. R)). In either
14510 -- case this makes N.all a left hand side but not N itself.
14512 -- If we don't know the type yet, this is the case where we return
14513 -- Unknown, since the answer depends on the type which is unknown.
14515 if No
(Etype
(N
)) then
14518 -- We have an Etype set, so we can check it
14520 elsif Is_Access_Type
(Etype
(N
)) then
14523 -- OK, not access type case, so just test whole expression
14529 -- All other cases are not left hand sides
14536 -----------------------------
14537 -- Is_Library_Level_Entity --
14538 -----------------------------
14540 function Is_Library_Level_Entity
(E
: Entity_Id
) return Boolean is
14542 -- The following is a small optimization, and it also properly handles
14543 -- discriminals, which in task bodies might appear in expressions before
14544 -- the corresponding procedure has been created, and which therefore do
14545 -- not have an assigned scope.
14547 if Is_Formal
(E
) then
14551 -- Normal test is simply that the enclosing dynamic scope is Standard
14553 return Enclosing_Dynamic_Scope
(E
) = Standard_Standard
;
14554 end Is_Library_Level_Entity
;
14556 --------------------------------
14557 -- Is_Limited_Class_Wide_Type --
14558 --------------------------------
14560 function Is_Limited_Class_Wide_Type
(Typ
: Entity_Id
) return Boolean is
14563 Is_Class_Wide_Type
(Typ
)
14564 and then (Is_Limited_Type
(Typ
) or else From_Limited_With
(Typ
));
14565 end Is_Limited_Class_Wide_Type
;
14567 ---------------------------------
14568 -- Is_Local_Variable_Reference --
14569 ---------------------------------
14571 function Is_Local_Variable_Reference
(Expr
: Node_Id
) return Boolean is
14573 if not Is_Entity_Name
(Expr
) then
14578 Ent
: constant Entity_Id
:= Entity
(Expr
);
14579 Sub
: constant Entity_Id
:= Enclosing_Subprogram
(Ent
);
14581 if not Ekind_In
(Ent
, E_Variable
, E_In_Out_Parameter
) then
14584 return Present
(Sub
) and then Sub
= Current_Subprogram
;
14588 end Is_Local_Variable_Reference
;
14590 -----------------------
14591 -- Is_Name_Reference --
14592 -----------------------
14594 function Is_Name_Reference
(N
: Node_Id
) return Boolean is
14596 if Is_Entity_Name
(N
) then
14597 return Present
(Entity
(N
)) and then Is_Object
(Entity
(N
));
14601 when N_Indexed_Component
14605 Is_Name_Reference
(Prefix
(N
))
14606 or else Is_Access_Type
(Etype
(Prefix
(N
)));
14608 -- Attributes 'Input, 'Old and 'Result produce objects
14610 when N_Attribute_Reference
=>
14612 Nam_In
(Attribute_Name
(N
), Name_Input
, Name_Old
, Name_Result
);
14614 when N_Selected_Component
=>
14616 Is_Name_Reference
(Selector_Name
(N
))
14618 (Is_Name_Reference
(Prefix
(N
))
14619 or else Is_Access_Type
(Etype
(Prefix
(N
))));
14621 when N_Explicit_Dereference
=>
14624 -- A view conversion of a tagged name is a name reference
14626 when N_Type_Conversion
=>
14628 Is_Tagged_Type
(Etype
(Subtype_Mark
(N
)))
14629 and then Is_Tagged_Type
(Etype
(Expression
(N
)))
14630 and then Is_Name_Reference
(Expression
(N
));
14632 -- An unchecked type conversion is considered to be a name if the
14633 -- operand is a name (this construction arises only as a result of
14634 -- expansion activities).
14636 when N_Unchecked_Type_Conversion
=>
14637 return Is_Name_Reference
(Expression
(N
));
14642 end Is_Name_Reference
;
14644 ------------------------------------
14645 -- Is_Non_Preelaborable_Construct --
14646 ------------------------------------
14648 function Is_Non_Preelaborable_Construct
(N
: Node_Id
) return Boolean is
14650 -- NOTE: the routines within Is_Non_Preelaborable_Construct are
14651 -- intentionally unnested to avoid deep indentation of code.
14653 Non_Preelaborable
: exception;
14654 -- This exception is raised when the construct violates preelaborability
14655 -- to terminate the recursion.
14657 procedure Visit
(Nod
: Node_Id
);
14658 -- Semantically inspect construct Nod to determine whether it violates
14659 -- preelaborability. This routine raises Non_Preelaborable.
14661 procedure Visit_List
(List
: List_Id
);
14662 pragma Inline
(Visit_List
);
14663 -- Invoke Visit on each element of list List. This routine raises
14664 -- Non_Preelaborable.
14666 procedure Visit_Pragma
(Prag
: Node_Id
);
14667 pragma Inline
(Visit_Pragma
);
14668 -- Semantically inspect pragma Prag to determine whether it violates
14669 -- preelaborability. This routine raises Non_Preelaborable.
14671 procedure Visit_Subexpression
(Expr
: Node_Id
);
14672 pragma Inline
(Visit_Subexpression
);
14673 -- Semantically inspect expression Expr to determine whether it violates
14674 -- preelaborability. This routine raises Non_Preelaborable.
14680 procedure Visit
(Nod
: Node_Id
) is
14682 case Nkind
(Nod
) is
14686 when N_Component_Declaration
=>
14688 -- Defining_Identifier is left out because it is not relevant
14689 -- for preelaborability.
14691 Visit
(Component_Definition
(Nod
));
14692 Visit
(Expression
(Nod
));
14694 when N_Derived_Type_Definition
=>
14696 -- Interface_List is left out because it is not relevant for
14697 -- preelaborability.
14699 Visit
(Record_Extension_Part
(Nod
));
14700 Visit
(Subtype_Indication
(Nod
));
14702 when N_Entry_Declaration
=>
14704 -- A protected type with at leat one entry is not preelaborable
14705 -- while task types are never preelaborable. This renders entry
14706 -- declarations non-preelaborable.
14708 raise Non_Preelaborable
;
14710 when N_Full_Type_Declaration
=>
14712 -- Defining_Identifier and Discriminant_Specifications are left
14713 -- out because they are not relevant for preelaborability.
14715 Visit
(Type_Definition
(Nod
));
14717 when N_Function_Instantiation
14718 | N_Package_Instantiation
14719 | N_Procedure_Instantiation
14721 -- Defining_Unit_Name and Name are left out because they are
14722 -- not relevant for preelaborability.
14724 Visit_List
(Generic_Associations
(Nod
));
14726 when N_Object_Declaration
=>
14728 -- Defining_Identifier is left out because it is not relevant
14729 -- for preelaborability.
14731 Visit
(Object_Definition
(Nod
));
14733 if Has_Init_Expression
(Nod
) then
14734 Visit
(Expression
(Nod
));
14736 elsif not Has_Preelaborable_Initialization
14737 (Etype
(Defining_Entity
(Nod
)))
14739 raise Non_Preelaborable
;
14742 when N_Private_Extension_Declaration
14743 | N_Subtype_Declaration
14745 -- Defining_Identifier, Discriminant_Specifications, and
14746 -- Interface_List are left out because they are not relevant
14747 -- for preelaborability.
14749 Visit
(Subtype_Indication
(Nod
));
14751 when N_Protected_Type_Declaration
14752 | N_Single_Protected_Declaration
14754 -- Defining_Identifier, Discriminant_Specifications, and
14755 -- Interface_List are left out because they are not relevant
14756 -- for preelaborability.
14758 Visit
(Protected_Definition
(Nod
));
14760 -- A [single] task type is never preelaborable
14762 when N_Single_Task_Declaration
14763 | N_Task_Type_Declaration
14765 raise Non_Preelaborable
;
14770 Visit_Pragma
(Nod
);
14774 when N_Statement_Other_Than_Procedure_Call
=>
14775 if Nkind
(Nod
) /= N_Null_Statement
then
14776 raise Non_Preelaborable
;
14782 Visit_Subexpression
(Nod
);
14786 when N_Access_To_Object_Definition
=>
14787 Visit
(Subtype_Indication
(Nod
));
14789 when N_Case_Expression_Alternative
=>
14790 Visit
(Expression
(Nod
));
14791 Visit_List
(Discrete_Choices
(Nod
));
14793 when N_Component_Definition
=>
14794 Visit
(Access_Definition
(Nod
));
14795 Visit
(Subtype_Indication
(Nod
));
14797 when N_Component_List
=>
14798 Visit_List
(Component_Items
(Nod
));
14799 Visit
(Variant_Part
(Nod
));
14801 when N_Constrained_Array_Definition
=>
14802 Visit_List
(Discrete_Subtype_Definitions
(Nod
));
14803 Visit
(Component_Definition
(Nod
));
14805 when N_Delta_Constraint
14806 | N_Digits_Constraint
14808 -- Delta_Expression and Digits_Expression are left out because
14809 -- they are not relevant for preelaborability.
14811 Visit
(Range_Constraint
(Nod
));
14813 when N_Discriminant_Specification
=>
14815 -- Defining_Identifier and Expression are left out because they
14816 -- are not relevant for preelaborability.
14818 Visit
(Discriminant_Type
(Nod
));
14820 when N_Generic_Association
=>
14822 -- Selector_Name is left out because it is not relevant for
14823 -- preelaborability.
14825 Visit
(Explicit_Generic_Actual_Parameter
(Nod
));
14827 when N_Index_Or_Discriminant_Constraint
=>
14828 Visit_List
(Constraints
(Nod
));
14830 when N_Iterator_Specification
=>
14832 -- Defining_Identifier is left out because it is not relevant
14833 -- for preelaborability.
14835 Visit
(Name
(Nod
));
14836 Visit
(Subtype_Indication
(Nod
));
14838 when N_Loop_Parameter_Specification
=>
14840 -- Defining_Identifier is left out because it is not relevant
14841 -- for preelaborability.
14843 Visit
(Discrete_Subtype_Definition
(Nod
));
14845 when N_Protected_Definition
=>
14847 -- End_Label is left out because it is not relevant for
14848 -- preelaborability.
14850 Visit_List
(Private_Declarations
(Nod
));
14851 Visit_List
(Visible_Declarations
(Nod
));
14853 when N_Range_Constraint
=>
14854 Visit
(Range_Expression
(Nod
));
14856 when N_Record_Definition
14859 -- End_Label, Discrete_Choices, and Interface_List are left out
14860 -- because they are not relevant for preelaborability.
14862 Visit
(Component_List
(Nod
));
14864 when N_Subtype_Indication
=>
14866 -- Subtype_Mark is left out because it is not relevant for
14867 -- preelaborability.
14869 Visit
(Constraint
(Nod
));
14871 when N_Unconstrained_Array_Definition
=>
14873 -- Subtype_Marks is left out because it is not relevant for
14874 -- preelaborability.
14876 Visit
(Component_Definition
(Nod
));
14878 when N_Variant_Part
=>
14880 -- Name is left out because it is not relevant for
14881 -- preelaborability.
14883 Visit_List
(Variants
(Nod
));
14896 procedure Visit_List
(List
: List_Id
) is
14900 if Present
(List
) then
14901 Nod
:= First
(List
);
14902 while Present
(Nod
) loop
14913 procedure Visit_Pragma
(Prag
: Node_Id
) is
14915 case Get_Pragma_Id
(Prag
) is
14917 | Pragma_Assert_And_Cut
14919 | Pragma_Async_Readers
14920 | Pragma_Async_Writers
14921 | Pragma_Attribute_Definition
14923 | Pragma_Constant_After_Elaboration
14925 | Pragma_Deadline_Floor
14926 | Pragma_Dispatching_Domain
14927 | Pragma_Effective_Reads
14928 | Pragma_Effective_Writes
14929 | Pragma_Extensions_Visible
14931 | Pragma_Secondary_Stack_Size
14933 | Pragma_Volatile_Function
14935 Visit_List
(Pragma_Argument_Associations
(Prag
));
14944 -------------------------
14945 -- Visit_Subexpression --
14946 -------------------------
14948 procedure Visit_Subexpression
(Expr
: Node_Id
) is
14949 procedure Visit_Aggregate
(Aggr
: Node_Id
);
14950 pragma Inline
(Visit_Aggregate
);
14951 -- Semantically inspect aggregate Aggr to determine whether it
14952 -- violates preelaborability.
14954 ---------------------
14955 -- Visit_Aggregate --
14956 ---------------------
14958 procedure Visit_Aggregate
(Aggr
: Node_Id
) is
14960 if not Is_Preelaborable_Aggregate
(Aggr
) then
14961 raise Non_Preelaborable
;
14963 end Visit_Aggregate
;
14965 -- Start of processing for Visit_Subexpression
14968 case Nkind
(Expr
) is
14970 | N_Qualified_Expression
14971 | N_Type_Conversion
14972 | N_Unchecked_Expression
14973 | N_Unchecked_Type_Conversion
14975 -- Subpool_Handle_Name and Subtype_Mark are left out because
14976 -- they are not relevant for preelaborability.
14978 Visit
(Expression
(Expr
));
14981 | N_Extension_Aggregate
14983 Visit_Aggregate
(Expr
);
14985 when N_Attribute_Reference
14986 | N_Explicit_Dereference
14989 -- Attribute_Name and Expressions are left out because they are
14990 -- not relevant for preelaborability.
14992 Visit
(Prefix
(Expr
));
14994 when N_Case_Expression
=>
14996 -- End_Span is left out because it is not relevant for
14997 -- preelaborability.
14999 Visit_List
(Alternatives
(Expr
));
15000 Visit
(Expression
(Expr
));
15002 when N_Delta_Aggregate
=>
15003 Visit_Aggregate
(Expr
);
15004 Visit
(Expression
(Expr
));
15006 when N_Expression_With_Actions
=>
15007 Visit_List
(Actions
(Expr
));
15008 Visit
(Expression
(Expr
));
15010 when N_If_Expression
=>
15011 Visit_List
(Expressions
(Expr
));
15013 when N_Quantified_Expression
=>
15014 Visit
(Condition
(Expr
));
15015 Visit
(Iterator_Specification
(Expr
));
15016 Visit
(Loop_Parameter_Specification
(Expr
));
15019 Visit
(High_Bound
(Expr
));
15020 Visit
(Low_Bound
(Expr
));
15023 Visit
(Discrete_Range
(Expr
));
15024 Visit
(Prefix
(Expr
));
15030 -- The evaluation of an object name is not preelaborable,
15031 -- unless the name is a static expression (checked further
15032 -- below), or statically denotes a discriminant.
15034 if Is_Entity_Name
(Expr
) then
15035 Object_Name
: declare
15036 Id
: constant Entity_Id
:= Entity
(Expr
);
15039 if Is_Object
(Id
) then
15040 if Ekind
(Id
) = E_Discriminant
then
15043 elsif Ekind_In
(Id
, E_Constant
, E_In_Parameter
)
15044 and then Present
(Discriminal_Link
(Id
))
15049 raise Non_Preelaborable
;
15054 -- A non-static expression is not preelaborable
15056 elsif not Is_OK_Static_Expression
(Expr
) then
15057 raise Non_Preelaborable
;
15060 end Visit_Subexpression
;
15062 -- Start of processing for Is_Non_Preelaborable_Construct
15067 -- At this point it is known that the construct is preelaborable
15073 -- The elaboration of the construct performs an action which violates
15074 -- preelaborability.
15076 when Non_Preelaborable
=>
15078 end Is_Non_Preelaborable_Construct
;
15080 ---------------------------------
15081 -- Is_Nontrivial_DIC_Procedure --
15082 ---------------------------------
15084 function Is_Nontrivial_DIC_Procedure
(Id
: Entity_Id
) return Boolean is
15085 Body_Decl
: Node_Id
;
15089 if Ekind
(Id
) = E_Procedure
and then Is_DIC_Procedure
(Id
) then
15091 Unit_Declaration_Node
15092 (Corresponding_Body
(Unit_Declaration_Node
(Id
)));
15094 -- The body of the Default_Initial_Condition procedure must contain
15095 -- at least one statement, otherwise the generation of the subprogram
15098 pragma Assert
(Present
(Handled_Statement_Sequence
(Body_Decl
)));
15100 -- To qualify as nontrivial, the first statement of the procedure
15101 -- must be a check in the form of an if statement. If the original
15102 -- Default_Initial_Condition expression was folded, then the first
15103 -- statement is not a check.
15105 Stmt
:= First
(Statements
(Handled_Statement_Sequence
(Body_Decl
)));
15108 Nkind
(Stmt
) = N_If_Statement
15109 and then Nkind
(Original_Node
(Stmt
)) = N_Pragma
;
15113 end Is_Nontrivial_DIC_Procedure
;
15115 -------------------------
15116 -- Is_Null_Record_Type --
15117 -------------------------
15119 function Is_Null_Record_Type
(T
: Entity_Id
) return Boolean is
15120 Decl
: constant Node_Id
:= Parent
(T
);
15122 return Nkind
(Decl
) = N_Full_Type_Declaration
15123 and then Nkind
(Type_Definition
(Decl
)) = N_Record_Definition
15125 (No
(Component_List
(Type_Definition
(Decl
)))
15126 or else Null_Present
(Component_List
(Type_Definition
(Decl
))));
15127 end Is_Null_Record_Type
;
15129 ---------------------
15130 -- Is_Object_Image --
15131 ---------------------
15133 function Is_Object_Image
(Prefix
: Node_Id
) return Boolean is
15135 -- When the type of the prefix is not scalar, then the prefix is not
15136 -- valid in any scenario.
15138 if not Is_Scalar_Type
(Etype
(Prefix
)) then
15142 -- Here we test for the case that the prefix is not a type and assume
15143 -- if it is not then it must be a named value or an object reference.
15144 -- This is because the parser always checks that prefixes of attributes
15147 return not (Is_Entity_Name
(Prefix
) and then Is_Type
(Entity
(Prefix
)));
15148 end Is_Object_Image
;
15150 -------------------------
15151 -- Is_Object_Reference --
15152 -------------------------
15154 function Is_Object_Reference
(N
: Node_Id
) return Boolean is
15155 function Is_Internally_Generated_Renaming
(N
: Node_Id
) return Boolean;
15156 -- Determine whether N is the name of an internally-generated renaming
15158 --------------------------------------
15159 -- Is_Internally_Generated_Renaming --
15160 --------------------------------------
15162 function Is_Internally_Generated_Renaming
(N
: Node_Id
) return Boolean is
15167 while Present
(P
) loop
15168 if Nkind
(P
) = N_Object_Renaming_Declaration
then
15169 return not Comes_From_Source
(P
);
15170 elsif Is_List_Member
(P
) then
15178 end Is_Internally_Generated_Renaming
;
15180 -- Start of processing for Is_Object_Reference
15183 if Is_Entity_Name
(N
) then
15184 return Present
(Entity
(N
)) and then Is_Object
(Entity
(N
));
15188 when N_Indexed_Component
15192 Is_Object_Reference
(Prefix
(N
))
15193 or else Is_Access_Type
(Etype
(Prefix
(N
)));
15195 -- In Ada 95, a function call is a constant object; a procedure
15198 -- Note that predefined operators are functions as well, and so
15199 -- are attributes that are (can be renamed as) functions.
15205 return Etype
(N
) /= Standard_Void_Type
;
15207 -- Attributes references 'Loop_Entry, 'Old, and 'Result yield
15208 -- objects, even though they are not functions.
15210 when N_Attribute_Reference
=>
15212 Nam_In
(Attribute_Name
(N
), Name_Loop_Entry
,
15215 or else Is_Function_Attribute_Name
(Attribute_Name
(N
));
15217 when N_Selected_Component
=>
15219 Is_Object_Reference
(Selector_Name
(N
))
15221 (Is_Object_Reference
(Prefix
(N
))
15222 or else Is_Access_Type
(Etype
(Prefix
(N
))));
15224 -- An explicit dereference denotes an object, except that a
15225 -- conditional expression gets turned into an explicit dereference
15226 -- in some cases, and conditional expressions are not object
15229 when N_Explicit_Dereference
=>
15230 return not Nkind_In
(Original_Node
(N
), N_Case_Expression
,
15233 -- A view conversion of a tagged object is an object reference
15235 when N_Type_Conversion
=>
15236 return Is_Tagged_Type
(Etype
(Subtype_Mark
(N
)))
15237 and then Is_Tagged_Type
(Etype
(Expression
(N
)))
15238 and then Is_Object_Reference
(Expression
(N
));
15240 -- An unchecked type conversion is considered to be an object if
15241 -- the operand is an object (this construction arises only as a
15242 -- result of expansion activities).
15244 when N_Unchecked_Type_Conversion
=>
15247 -- Allow string literals to act as objects as long as they appear
15248 -- in internally-generated renamings. The expansion of iterators
15249 -- may generate such renamings when the range involves a string
15252 when N_String_Literal
=>
15253 return Is_Internally_Generated_Renaming
(Parent
(N
));
15255 -- AI05-0003: In Ada 2012 a qualified expression is a name.
15256 -- This allows disambiguation of function calls and the use
15257 -- of aggregates in more contexts.
15259 when N_Qualified_Expression
=>
15260 if Ada_Version
< Ada_2012
then
15263 return Is_Object_Reference
(Expression
(N
))
15264 or else Nkind
(Expression
(N
)) = N_Aggregate
;
15271 end Is_Object_Reference
;
15273 -----------------------------------
15274 -- Is_OK_Variable_For_Out_Formal --
15275 -----------------------------------
15277 function Is_OK_Variable_For_Out_Formal
(AV
: Node_Id
) return Boolean is
15279 Note_Possible_Modification
(AV
, Sure
=> True);
15281 -- We must reject parenthesized variable names. Comes_From_Source is
15282 -- checked because there are currently cases where the compiler violates
15283 -- this rule (e.g. passing a task object to its controlled Initialize
15284 -- routine). This should be properly documented in sinfo???
15286 if Paren_Count
(AV
) > 0 and then Comes_From_Source
(AV
) then
15289 -- A variable is always allowed
15291 elsif Is_Variable
(AV
) then
15294 -- Generalized indexing operations are rewritten as explicit
15295 -- dereferences, and it is only during resolution that we can
15296 -- check whether the context requires an access_to_variable type.
15298 elsif Nkind
(AV
) = N_Explicit_Dereference
15299 and then Ada_Version
>= Ada_2012
15300 and then Nkind
(Original_Node
(AV
)) = N_Indexed_Component
15301 and then Present
(Etype
(Original_Node
(AV
)))
15302 and then Has_Implicit_Dereference
(Etype
(Original_Node
(AV
)))
15304 return not Is_Access_Constant
(Etype
(Prefix
(AV
)));
15306 -- Unchecked conversions are allowed only if they come from the
15307 -- generated code, which sometimes uses unchecked conversions for out
15308 -- parameters in cases where code generation is unaffected. We tell
15309 -- source unchecked conversions by seeing if they are rewrites of
15310 -- an original Unchecked_Conversion function call, or of an explicit
15311 -- conversion of a function call or an aggregate (as may happen in the
15312 -- expansion of a packed array aggregate).
15314 elsif Nkind
(AV
) = N_Unchecked_Type_Conversion
then
15315 if Nkind_In
(Original_Node
(AV
), N_Function_Call
, N_Aggregate
) then
15318 elsif Comes_From_Source
(AV
)
15319 and then Nkind
(Original_Node
(Expression
(AV
))) = N_Function_Call
15323 elsif Nkind
(Original_Node
(AV
)) = N_Type_Conversion
then
15324 return Is_OK_Variable_For_Out_Formal
(Expression
(AV
));
15330 -- Normal type conversions are allowed if argument is a variable
15332 elsif Nkind
(AV
) = N_Type_Conversion
then
15333 if Is_Variable
(Expression
(AV
))
15334 and then Paren_Count
(Expression
(AV
)) = 0
15336 Note_Possible_Modification
(Expression
(AV
), Sure
=> True);
15339 -- We also allow a non-parenthesized expression that raises
15340 -- constraint error if it rewrites what used to be a variable
15342 elsif Raises_Constraint_Error
(Expression
(AV
))
15343 and then Paren_Count
(Expression
(AV
)) = 0
15344 and then Is_Variable
(Original_Node
(Expression
(AV
)))
15348 -- Type conversion of something other than a variable
15354 -- If this node is rewritten, then test the original form, if that is
15355 -- OK, then we consider the rewritten node OK (for example, if the
15356 -- original node is a conversion, then Is_Variable will not be true
15357 -- but we still want to allow the conversion if it converts a variable).
15359 elsif Original_Node
(AV
) /= AV
then
15361 -- In Ada 2012, the explicit dereference may be a rewritten call to a
15362 -- Reference function.
15364 if Ada_Version
>= Ada_2012
15365 and then Nkind
(Original_Node
(AV
)) = N_Function_Call
15367 Has_Implicit_Dereference
(Etype
(Name
(Original_Node
(AV
))))
15370 -- Check that this is not a constant reference.
15372 return not Is_Access_Constant
(Etype
(Prefix
(AV
)));
15374 elsif Has_Implicit_Dereference
(Etype
(Original_Node
(AV
))) then
15376 not Is_Access_Constant
(Etype
15377 (Get_Reference_Discriminant
(Etype
(Original_Node
(AV
)))));
15380 return Is_OK_Variable_For_Out_Formal
(Original_Node
(AV
));
15383 -- All other non-variables are rejected
15388 end Is_OK_Variable_For_Out_Formal
;
15390 ----------------------------
15391 -- Is_OK_Volatile_Context --
15392 ----------------------------
15394 function Is_OK_Volatile_Context
15395 (Context
: Node_Id
;
15396 Obj_Ref
: Node_Id
) return Boolean
15398 function Is_Protected_Operation_Call
(Nod
: Node_Id
) return Boolean;
15399 -- Determine whether an arbitrary node denotes a call to a protected
15400 -- entry, function, or procedure in prefixed form where the prefix is
15403 function Within_Check
(Nod
: Node_Id
) return Boolean;
15404 -- Determine whether an arbitrary node appears in a check node
15406 function Within_Volatile_Function
(Id
: Entity_Id
) return Boolean;
15407 -- Determine whether an arbitrary entity appears in a volatile function
15409 ---------------------------------
15410 -- Is_Protected_Operation_Call --
15411 ---------------------------------
15413 function Is_Protected_Operation_Call
(Nod
: Node_Id
) return Boolean is
15418 -- A call to a protected operations retains its selected component
15419 -- form as opposed to other prefixed calls that are transformed in
15422 if Nkind
(Nod
) = N_Selected_Component
then
15423 Pref
:= Prefix
(Nod
);
15424 Subp
:= Selector_Name
(Nod
);
15428 and then Present
(Etype
(Pref
))
15429 and then Is_Protected_Type
(Etype
(Pref
))
15430 and then Is_Entity_Name
(Subp
)
15431 and then Present
(Entity
(Subp
))
15432 and then Ekind_In
(Entity
(Subp
), E_Entry
,
15439 end Is_Protected_Operation_Call
;
15445 function Within_Check
(Nod
: Node_Id
) return Boolean is
15449 -- Climb the parent chain looking for a check node
15452 while Present
(Par
) loop
15453 if Nkind
(Par
) in N_Raise_xxx_Error
then
15456 -- Prevent the search from going too far
15458 elsif Is_Body_Or_Package_Declaration
(Par
) then
15462 Par
:= Parent
(Par
);
15468 ------------------------------
15469 -- Within_Volatile_Function --
15470 ------------------------------
15472 function Within_Volatile_Function
(Id
: Entity_Id
) return Boolean is
15473 Func_Id
: Entity_Id
;
15476 -- Traverse the scope stack looking for a [generic] function
15479 while Present
(Func_Id
) and then Func_Id
/= Standard_Standard
loop
15480 if Ekind_In
(Func_Id
, E_Function
, E_Generic_Function
) then
15481 return Is_Volatile_Function
(Func_Id
);
15484 Func_Id
:= Scope
(Func_Id
);
15488 end Within_Volatile_Function
;
15492 Obj_Id
: Entity_Id
;
15494 -- Start of processing for Is_OK_Volatile_Context
15497 -- The volatile object appears on either side of an assignment
15499 if Nkind
(Context
) = N_Assignment_Statement
then
15502 -- The volatile object is part of the initialization expression of
15505 elsif Nkind
(Context
) = N_Object_Declaration
15506 and then Present
(Expression
(Context
))
15507 and then Expression
(Context
) = Obj_Ref
15509 Obj_Id
:= Defining_Entity
(Context
);
15511 -- The volatile object acts as the initialization expression of an
15512 -- extended return statement. This is valid context as long as the
15513 -- function is volatile.
15515 if Is_Return_Object
(Obj_Id
) then
15516 return Within_Volatile_Function
(Obj_Id
);
15518 -- Otherwise this is a normal object initialization
15524 -- The volatile object acts as the name of a renaming declaration
15526 elsif Nkind
(Context
) = N_Object_Renaming_Declaration
15527 and then Name
(Context
) = Obj_Ref
15531 -- The volatile object appears as an actual parameter in a call to an
15532 -- instance of Unchecked_Conversion whose result is renamed.
15534 elsif Nkind
(Context
) = N_Function_Call
15535 and then Is_Entity_Name
(Name
(Context
))
15536 and then Is_Unchecked_Conversion_Instance
(Entity
(Name
(Context
)))
15537 and then Nkind
(Parent
(Context
)) = N_Object_Renaming_Declaration
15541 -- The volatile object is actually the prefix in a protected entry,
15542 -- function, or procedure call.
15544 elsif Is_Protected_Operation_Call
(Context
) then
15547 -- The volatile object appears as the expression of a simple return
15548 -- statement that applies to a volatile function.
15550 elsif Nkind
(Context
) = N_Simple_Return_Statement
15551 and then Expression
(Context
) = Obj_Ref
15554 Within_Volatile_Function
(Return_Statement_Entity
(Context
));
15556 -- The volatile object appears as the prefix of a name occurring in a
15557 -- non-interfering context.
15559 elsif Nkind_In
(Context
, N_Attribute_Reference
,
15560 N_Explicit_Dereference
,
15561 N_Indexed_Component
,
15562 N_Selected_Component
,
15564 and then Prefix
(Context
) = Obj_Ref
15565 and then Is_OK_Volatile_Context
15566 (Context
=> Parent
(Context
),
15567 Obj_Ref
=> Context
)
15571 -- The volatile object appears as the prefix of attributes Address,
15572 -- Alignment, Component_Size, First_Bit, Last_Bit, Position, Size,
15575 elsif Nkind
(Context
) = N_Attribute_Reference
15576 and then Prefix
(Context
) = Obj_Ref
15577 and then Nam_In
(Attribute_Name
(Context
), Name_Address
,
15579 Name_Component_Size
,
15588 -- The volatile object appears as the expression of a type conversion
15589 -- occurring in a non-interfering context.
15591 elsif Nkind_In
(Context
, N_Type_Conversion
,
15592 N_Unchecked_Type_Conversion
)
15593 and then Expression
(Context
) = Obj_Ref
15594 and then Is_OK_Volatile_Context
15595 (Context
=> Parent
(Context
),
15596 Obj_Ref
=> Context
)
15600 -- The volatile object appears as the expression in a delay statement
15602 elsif Nkind
(Context
) in N_Delay_Statement
then
15605 -- Allow references to volatile objects in various checks. This is not a
15606 -- direct SPARK 2014 requirement.
15608 elsif Within_Check
(Context
) then
15611 -- Assume that references to effectively volatile objects that appear
15612 -- as actual parameters in a subprogram call are always legal. A full
15613 -- legality check is done when the actuals are resolved (see routine
15614 -- Resolve_Actuals).
15616 elsif Within_Subprogram_Call
(Context
) then
15619 -- Otherwise the context is not suitable for an effectively volatile
15625 end Is_OK_Volatile_Context
;
15627 ------------------------------------
15628 -- Is_Package_Contract_Annotation --
15629 ------------------------------------
15631 function Is_Package_Contract_Annotation
(Item
: Node_Id
) return Boolean is
15635 if Nkind
(Item
) = N_Aspect_Specification
then
15636 Nam
:= Chars
(Identifier
(Item
));
15638 else pragma Assert
(Nkind
(Item
) = N_Pragma
);
15639 Nam
:= Pragma_Name
(Item
);
15642 return Nam
= Name_Abstract_State
15643 or else Nam
= Name_Initial_Condition
15644 or else Nam
= Name_Initializes
15645 or else Nam
= Name_Refined_State
;
15646 end Is_Package_Contract_Annotation
;
15648 -----------------------------------
15649 -- Is_Partially_Initialized_Type --
15650 -----------------------------------
15652 function Is_Partially_Initialized_Type
15654 Include_Implicit
: Boolean := True) return Boolean
15657 if Is_Scalar_Type
(Typ
) then
15660 elsif Is_Access_Type
(Typ
) then
15661 return Include_Implicit
;
15663 elsif Is_Array_Type
(Typ
) then
15665 -- If component type is partially initialized, so is array type
15667 if Is_Partially_Initialized_Type
15668 (Component_Type
(Typ
), Include_Implicit
)
15672 -- Otherwise we are only partially initialized if we are fully
15673 -- initialized (this is the empty array case, no point in us
15674 -- duplicating that code here).
15677 return Is_Fully_Initialized_Type
(Typ
);
15680 elsif Is_Record_Type
(Typ
) then
15682 -- A discriminated type is always partially initialized if in
15685 if Has_Discriminants
(Typ
) and then Include_Implicit
then
15688 -- A tagged type is always partially initialized
15690 elsif Is_Tagged_Type
(Typ
) then
15693 -- Case of non-discriminated record
15699 Component_Present
: Boolean := False;
15700 -- Set True if at least one component is present. If no
15701 -- components are present, then record type is fully
15702 -- initialized (another odd case, like the null array).
15705 -- Loop through components
15707 Ent
:= First_Entity
(Typ
);
15708 while Present
(Ent
) loop
15709 if Ekind
(Ent
) = E_Component
then
15710 Component_Present
:= True;
15712 -- If a component has an initialization expression then
15713 -- the enclosing record type is partially initialized
15715 if Present
(Parent
(Ent
))
15716 and then Present
(Expression
(Parent
(Ent
)))
15720 -- If a component is of a type which is itself partially
15721 -- initialized, then the enclosing record type is also.
15723 elsif Is_Partially_Initialized_Type
15724 (Etype
(Ent
), Include_Implicit
)
15733 -- No initialized components found. If we found any components
15734 -- they were all uninitialized so the result is false.
15736 if Component_Present
then
15739 -- But if we found no components, then all the components are
15740 -- initialized so we consider the type to be initialized.
15748 -- Concurrent types are always fully initialized
15750 elsif Is_Concurrent_Type
(Typ
) then
15753 -- For a private type, go to underlying type. If there is no underlying
15754 -- type then just assume this partially initialized. Not clear if this
15755 -- can happen in a non-error case, but no harm in testing for this.
15757 elsif Is_Private_Type
(Typ
) then
15759 U
: constant Entity_Id
:= Underlying_Type
(Typ
);
15764 return Is_Partially_Initialized_Type
(U
, Include_Implicit
);
15768 -- For any other type (are there any?) assume partially initialized
15773 end Is_Partially_Initialized_Type
;
15775 ------------------------------------
15776 -- Is_Potentially_Persistent_Type --
15777 ------------------------------------
15779 function Is_Potentially_Persistent_Type
(T
: Entity_Id
) return Boolean is
15784 -- For private type, test corresponding full type
15786 if Is_Private_Type
(T
) then
15787 return Is_Potentially_Persistent_Type
(Full_View
(T
));
15789 -- Scalar types are potentially persistent
15791 elsif Is_Scalar_Type
(T
) then
15794 -- Record type is potentially persistent if not tagged and the types of
15795 -- all it components are potentially persistent, and no component has
15796 -- an initialization expression.
15798 elsif Is_Record_Type
(T
)
15799 and then not Is_Tagged_Type
(T
)
15800 and then not Is_Partially_Initialized_Type
(T
)
15802 Comp
:= First_Component
(T
);
15803 while Present
(Comp
) loop
15804 if not Is_Potentially_Persistent_Type
(Etype
(Comp
)) then
15807 Next_Entity
(Comp
);
15813 -- Array type is potentially persistent if its component type is
15814 -- potentially persistent and if all its constraints are static.
15816 elsif Is_Array_Type
(T
) then
15817 if not Is_Potentially_Persistent_Type
(Component_Type
(T
)) then
15821 Indx
:= First_Index
(T
);
15822 while Present
(Indx
) loop
15823 if not Is_OK_Static_Subtype
(Etype
(Indx
)) then
15832 -- All other types are not potentially persistent
15837 end Is_Potentially_Persistent_Type
;
15839 --------------------------------
15840 -- Is_Potentially_Unevaluated --
15841 --------------------------------
15843 function Is_Potentially_Unevaluated
(N
: Node_Id
) return Boolean is
15851 -- A postcondition whose expression is a short-circuit is broken down
15852 -- into individual aspects for better exception reporting. The original
15853 -- short-circuit expression is rewritten as the second operand, and an
15854 -- occurrence of 'Old in that operand is potentially unevaluated.
15855 -- See Sem_ch13.adb for details of this transformation.
15857 if Nkind
(Original_Node
(Par
)) = N_And_Then
then
15861 while not Nkind_In
(Par
, N_If_Expression
,
15867 N_Quantified_Expression
)
15870 Par
:= Parent
(Par
);
15872 -- If the context is not an expression, or if is the result of
15873 -- expansion of an enclosing construct (such as another attribute)
15874 -- the predicate does not apply.
15876 if Nkind
(Par
) = N_Case_Expression_Alternative
then
15879 elsif Nkind
(Par
) not in N_Subexpr
15880 or else not Comes_From_Source
(Par
)
15886 if Nkind
(Par
) = N_If_Expression
then
15887 return Is_Elsif
(Par
) or else Expr
/= First
(Expressions
(Par
));
15889 elsif Nkind
(Par
) = N_Case_Expression
then
15890 return Expr
/= Expression
(Par
);
15892 elsif Nkind_In
(Par
, N_And_Then
, N_Or_Else
) then
15893 return Expr
= Right_Opnd
(Par
);
15895 elsif Nkind_In
(Par
, N_In
, N_Not_In
) then
15897 -- If the membership includes several alternatives, only the first is
15898 -- definitely evaluated.
15900 if Present
(Alternatives
(Par
)) then
15901 return Expr
/= First
(Alternatives
(Par
));
15903 -- If this is a range membership both bounds are evaluated
15909 elsif Nkind
(Par
) = N_Quantified_Expression
then
15910 return Expr
= Condition
(Par
);
15915 end Is_Potentially_Unevaluated
;
15917 --------------------------------
15918 -- Is_Preelaborable_Aggregate --
15919 --------------------------------
15921 function Is_Preelaborable_Aggregate
(Aggr
: Node_Id
) return Boolean is
15922 Aggr_Typ
: constant Entity_Id
:= Etype
(Aggr
);
15923 Array_Aggr
: constant Boolean := Is_Array_Type
(Aggr_Typ
);
15925 Anc_Part
: Node_Id
;
15928 Comp_Typ
: Entity_Id
:= Empty
; -- init to avoid warning
15933 Comp_Typ
:= Component_Type
(Aggr_Typ
);
15936 -- Inspect the ancestor part
15938 if Nkind
(Aggr
) = N_Extension_Aggregate
then
15939 Anc_Part
:= Ancestor_Part
(Aggr
);
15941 -- The ancestor denotes a subtype mark
15943 if Is_Entity_Name
(Anc_Part
)
15944 and then Is_Type
(Entity
(Anc_Part
))
15946 if not Has_Preelaborable_Initialization
(Entity
(Anc_Part
)) then
15950 -- Otherwise the ancestor denotes an expression
15952 elsif not Is_Preelaborable_Construct
(Anc_Part
) then
15957 -- Inspect the positional associations
15959 Expr
:= First
(Expressions
(Aggr
));
15960 while Present
(Expr
) loop
15961 if not Is_Preelaborable_Construct
(Expr
) then
15968 -- Inspect the named associations
15970 Assoc
:= First
(Component_Associations
(Aggr
));
15971 while Present
(Assoc
) loop
15973 -- Inspect the choices of the current named association
15975 Choice
:= First
(Choices
(Assoc
));
15976 while Present
(Choice
) loop
15979 -- For a choice to be preelaborable, it must denote either a
15980 -- static range or a static expression.
15982 if Nkind
(Choice
) = N_Others_Choice
then
15985 elsif Nkind
(Choice
) = N_Range
then
15986 if not Is_OK_Static_Range
(Choice
) then
15990 elsif not Is_OK_Static_Expression
(Choice
) then
15995 Comp_Typ
:= Etype
(Choice
);
16001 -- The type of the choice must have preelaborable initialization if
16002 -- the association carries a <>.
16004 pragma Assert
(Present
(Comp_Typ
));
16005 if Box_Present
(Assoc
) then
16006 if not Has_Preelaborable_Initialization
(Comp_Typ
) then
16010 -- The type of the expression must have preelaborable initialization
16012 elsif not Is_Preelaborable_Construct
(Expression
(Assoc
)) then
16019 -- At this point the aggregate is preelaborable
16022 end Is_Preelaborable_Aggregate
;
16024 --------------------------------
16025 -- Is_Preelaborable_Construct --
16026 --------------------------------
16028 function Is_Preelaborable_Construct
(N
: Node_Id
) return Boolean is
16032 if Nkind_In
(N
, N_Aggregate
, N_Extension_Aggregate
) then
16033 return Is_Preelaborable_Aggregate
(N
);
16035 -- Attributes are allowed in general, even if their prefix is a formal
16036 -- type. It seems that certain attributes known not to be static might
16037 -- not be allowed, but there are no rules to prevent them.
16039 elsif Nkind
(N
) = N_Attribute_Reference
then
16044 elsif Nkind
(N
) in N_Subexpr
and then Is_OK_Static_Expression
(N
) then
16047 elsif Nkind
(N
) = N_Qualified_Expression
then
16048 return Is_Preelaborable_Construct
(Expression
(N
));
16050 -- Names are preelaborable when they denote a discriminant of an
16051 -- enclosing type. Discriminals are also considered for this check.
16053 elsif Is_Entity_Name
(N
)
16054 and then Present
(Entity
(N
))
16056 (Ekind
(Entity
(N
)) = E_Discriminant
16057 or else (Ekind_In
(Entity
(N
), E_Constant
, E_In_Parameter
)
16058 and then Present
(Discriminal_Link
(Entity
(N
)))))
16064 elsif Nkind
(N
) = N_Null
then
16067 -- Otherwise the construct is not preelaborable
16072 end Is_Preelaborable_Construct
;
16074 ---------------------------------
16075 -- Is_Protected_Self_Reference --
16076 ---------------------------------
16078 function Is_Protected_Self_Reference
(N
: Node_Id
) return Boolean is
16080 function In_Access_Definition
(N
: Node_Id
) return Boolean;
16081 -- Returns true if N belongs to an access definition
16083 --------------------------
16084 -- In_Access_Definition --
16085 --------------------------
16087 function In_Access_Definition
(N
: Node_Id
) return Boolean is
16092 while Present
(P
) loop
16093 if Nkind
(P
) = N_Access_Definition
then
16101 end In_Access_Definition
;
16103 -- Start of processing for Is_Protected_Self_Reference
16106 -- Verify that prefix is analyzed and has the proper form. Note that
16107 -- the attributes Elab_Spec, Elab_Body, and Elab_Subp_Body, which also
16108 -- produce the address of an entity, do not analyze their prefix
16109 -- because they denote entities that are not necessarily visible.
16110 -- Neither of them can apply to a protected type.
16112 return Ada_Version
>= Ada_2005
16113 and then Is_Entity_Name
(N
)
16114 and then Present
(Entity
(N
))
16115 and then Is_Protected_Type
(Entity
(N
))
16116 and then In_Open_Scopes
(Entity
(N
))
16117 and then not In_Access_Definition
(N
);
16118 end Is_Protected_Self_Reference
;
16120 -----------------------------
16121 -- Is_RCI_Pkg_Spec_Or_Body --
16122 -----------------------------
16124 function Is_RCI_Pkg_Spec_Or_Body
(Cunit
: Node_Id
) return Boolean is
16126 function Is_RCI_Pkg_Decl_Cunit
(Cunit
: Node_Id
) return Boolean;
16127 -- Return True if the unit of Cunit is an RCI package declaration
16129 ---------------------------
16130 -- Is_RCI_Pkg_Decl_Cunit --
16131 ---------------------------
16133 function Is_RCI_Pkg_Decl_Cunit
(Cunit
: Node_Id
) return Boolean is
16134 The_Unit
: constant Node_Id
:= Unit
(Cunit
);
16137 if Nkind
(The_Unit
) /= N_Package_Declaration
then
16141 return Is_Remote_Call_Interface
(Defining_Entity
(The_Unit
));
16142 end Is_RCI_Pkg_Decl_Cunit
;
16144 -- Start of processing for Is_RCI_Pkg_Spec_Or_Body
16147 return Is_RCI_Pkg_Decl_Cunit
(Cunit
)
16149 (Nkind
(Unit
(Cunit
)) = N_Package_Body
16150 and then Is_RCI_Pkg_Decl_Cunit
(Library_Unit
(Cunit
)));
16151 end Is_RCI_Pkg_Spec_Or_Body
;
16153 -----------------------------------------
16154 -- Is_Remote_Access_To_Class_Wide_Type --
16155 -----------------------------------------
16157 function Is_Remote_Access_To_Class_Wide_Type
16158 (E
: Entity_Id
) return Boolean
16161 -- A remote access to class-wide type is a general access to object type
16162 -- declared in the visible part of a Remote_Types or Remote_Call_
16165 return Ekind
(E
) = E_General_Access_Type
16166 and then (Is_Remote_Call_Interface
(E
) or else Is_Remote_Types
(E
));
16167 end Is_Remote_Access_To_Class_Wide_Type
;
16169 -----------------------------------------
16170 -- Is_Remote_Access_To_Subprogram_Type --
16171 -----------------------------------------
16173 function Is_Remote_Access_To_Subprogram_Type
16174 (E
: Entity_Id
) return Boolean
16177 return (Ekind
(E
) = E_Access_Subprogram_Type
16178 or else (Ekind
(E
) = E_Record_Type
16179 and then Present
(Corresponding_Remote_Type
(E
))))
16180 and then (Is_Remote_Call_Interface
(E
) or else Is_Remote_Types
(E
));
16181 end Is_Remote_Access_To_Subprogram_Type
;
16183 --------------------
16184 -- Is_Remote_Call --
16185 --------------------
16187 function Is_Remote_Call
(N
: Node_Id
) return Boolean is
16189 if Nkind
(N
) not in N_Subprogram_Call
then
16191 -- An entry call cannot be remote
16195 elsif Nkind
(Name
(N
)) in N_Has_Entity
16196 and then Is_Remote_Call_Interface
(Entity
(Name
(N
)))
16198 -- A subprogram declared in the spec of a RCI package is remote
16202 elsif Nkind
(Name
(N
)) = N_Explicit_Dereference
16203 and then Is_Remote_Access_To_Subprogram_Type
16204 (Etype
(Prefix
(Name
(N
))))
16206 -- The dereference of a RAS is a remote call
16210 elsif Present
(Controlling_Argument
(N
))
16211 and then Is_Remote_Access_To_Class_Wide_Type
16212 (Etype
(Controlling_Argument
(N
)))
16214 -- Any primitive operation call with a controlling argument of
16215 -- a RACW type is a remote call.
16220 -- All other calls are local calls
16223 end Is_Remote_Call
;
16225 ----------------------
16226 -- Is_Renamed_Entry --
16227 ----------------------
16229 function Is_Renamed_Entry
(Proc_Nam
: Entity_Id
) return Boolean is
16230 Orig_Node
: Node_Id
:= Empty
;
16231 Subp_Decl
: Node_Id
:= Parent
(Parent
(Proc_Nam
));
16233 function Is_Entry
(Nam
: Node_Id
) return Boolean;
16234 -- Determine whether Nam is an entry. Traverse selectors if there are
16235 -- nested selected components.
16241 function Is_Entry
(Nam
: Node_Id
) return Boolean is
16243 if Nkind
(Nam
) = N_Selected_Component
then
16244 return Is_Entry
(Selector_Name
(Nam
));
16247 return Ekind
(Entity
(Nam
)) = E_Entry
;
16250 -- Start of processing for Is_Renamed_Entry
16253 if Present
(Alias
(Proc_Nam
)) then
16254 Subp_Decl
:= Parent
(Parent
(Alias
(Proc_Nam
)));
16257 -- Look for a rewritten subprogram renaming declaration
16259 if Nkind
(Subp_Decl
) = N_Subprogram_Declaration
16260 and then Present
(Original_Node
(Subp_Decl
))
16262 Orig_Node
:= Original_Node
(Subp_Decl
);
16265 -- The rewritten subprogram is actually an entry
16267 if Present
(Orig_Node
)
16268 and then Nkind
(Orig_Node
) = N_Subprogram_Renaming_Declaration
16269 and then Is_Entry
(Name
(Orig_Node
))
16275 end Is_Renamed_Entry
;
16277 -----------------------------
16278 -- Is_Renaming_Declaration --
16279 -----------------------------
16281 function Is_Renaming_Declaration
(N
: Node_Id
) return Boolean is
16284 when N_Exception_Renaming_Declaration
16285 | N_Generic_Function_Renaming_Declaration
16286 | N_Generic_Package_Renaming_Declaration
16287 | N_Generic_Procedure_Renaming_Declaration
16288 | N_Object_Renaming_Declaration
16289 | N_Package_Renaming_Declaration
16290 | N_Subprogram_Renaming_Declaration
16297 end Is_Renaming_Declaration
;
16299 ----------------------------
16300 -- Is_Reversible_Iterator --
16301 ----------------------------
16303 function Is_Reversible_Iterator
(Typ
: Entity_Id
) return Boolean is
16304 Ifaces_List
: Elist_Id
;
16305 Iface_Elmt
: Elmt_Id
;
16309 if Is_Class_Wide_Type
(Typ
)
16310 and then Chars
(Root_Type
(Typ
)) = Name_Reversible_Iterator
16311 and then In_Predefined_Unit
(Root_Type
(Typ
))
16315 elsif not Is_Tagged_Type
(Typ
) or else not Is_Derived_Type
(Typ
) then
16319 Collect_Interfaces
(Typ
, Ifaces_List
);
16321 Iface_Elmt
:= First_Elmt
(Ifaces_List
);
16322 while Present
(Iface_Elmt
) loop
16323 Iface
:= Node
(Iface_Elmt
);
16324 if Chars
(Iface
) = Name_Reversible_Iterator
16325 and then In_Predefined_Unit
(Iface
)
16330 Next_Elmt
(Iface_Elmt
);
16335 end Is_Reversible_Iterator
;
16337 ----------------------
16338 -- Is_Selector_Name --
16339 ----------------------
16341 function Is_Selector_Name
(N
: Node_Id
) return Boolean is
16343 if not Is_List_Member
(N
) then
16345 P
: constant Node_Id
:= Parent
(N
);
16347 return Nkind_In
(P
, N_Expanded_Name
,
16348 N_Generic_Association
,
16349 N_Parameter_Association
,
16350 N_Selected_Component
)
16351 and then Selector_Name
(P
) = N
;
16356 L
: constant List_Id
:= List_Containing
(N
);
16357 P
: constant Node_Id
:= Parent
(L
);
16359 return (Nkind
(P
) = N_Discriminant_Association
16360 and then Selector_Names
(P
) = L
)
16362 (Nkind
(P
) = N_Component_Association
16363 and then Choices
(P
) = L
);
16366 end Is_Selector_Name
;
16368 ---------------------------------
16369 -- Is_Single_Concurrent_Object --
16370 ---------------------------------
16372 function Is_Single_Concurrent_Object
(Id
: Entity_Id
) return Boolean is
16375 Is_Single_Protected_Object
(Id
) or else Is_Single_Task_Object
(Id
);
16376 end Is_Single_Concurrent_Object
;
16378 -------------------------------
16379 -- Is_Single_Concurrent_Type --
16380 -------------------------------
16382 function Is_Single_Concurrent_Type
(Id
: Entity_Id
) return Boolean is
16385 Ekind_In
(Id
, E_Protected_Type
, E_Task_Type
)
16386 and then Is_Single_Concurrent_Type_Declaration
16387 (Declaration_Node
(Id
));
16388 end Is_Single_Concurrent_Type
;
16390 -------------------------------------------
16391 -- Is_Single_Concurrent_Type_Declaration --
16392 -------------------------------------------
16394 function Is_Single_Concurrent_Type_Declaration
16395 (N
: Node_Id
) return Boolean
16398 return Nkind_In
(Original_Node
(N
), N_Single_Protected_Declaration
,
16399 N_Single_Task_Declaration
);
16400 end Is_Single_Concurrent_Type_Declaration
;
16402 ---------------------------------------------
16403 -- Is_Single_Precision_Floating_Point_Type --
16404 ---------------------------------------------
16406 function Is_Single_Precision_Floating_Point_Type
16407 (E
: Entity_Id
) return Boolean is
16409 return Is_Floating_Point_Type
(E
)
16410 and then Machine_Radix_Value
(E
) = Uint_2
16411 and then Machine_Mantissa_Value
(E
) = Uint_24
16412 and then Machine_Emax_Value
(E
) = Uint_2
** Uint_7
16413 and then Machine_Emin_Value
(E
) = Uint_3
- (Uint_2
** Uint_7
);
16414 end Is_Single_Precision_Floating_Point_Type
;
16416 --------------------------------
16417 -- Is_Single_Protected_Object --
16418 --------------------------------
16420 function Is_Single_Protected_Object
(Id
: Entity_Id
) return Boolean is
16423 Ekind
(Id
) = E_Variable
16424 and then Ekind
(Etype
(Id
)) = E_Protected_Type
16425 and then Is_Single_Concurrent_Type
(Etype
(Id
));
16426 end Is_Single_Protected_Object
;
16428 ---------------------------
16429 -- Is_Single_Task_Object --
16430 ---------------------------
16432 function Is_Single_Task_Object
(Id
: Entity_Id
) return Boolean is
16435 Ekind
(Id
) = E_Variable
16436 and then Ekind
(Etype
(Id
)) = E_Task_Type
16437 and then Is_Single_Concurrent_Type
(Etype
(Id
));
16438 end Is_Single_Task_Object
;
16440 -------------------------------------
16441 -- Is_SPARK_05_Initialization_Expr --
16442 -------------------------------------
16444 function Is_SPARK_05_Initialization_Expr
(N
: Node_Id
) return Boolean is
16447 Comp_Assn
: Node_Id
;
16448 Orig_N
: constant Node_Id
:= Original_Node
(N
);
16453 if not Comes_From_Source
(Orig_N
) then
16457 pragma Assert
(Nkind
(Orig_N
) in N_Subexpr
);
16459 case Nkind
(Orig_N
) is
16460 when N_Character_Literal
16461 | N_Integer_Literal
16467 when N_Expanded_Name
16470 if Is_Entity_Name
(Orig_N
)
16471 and then Present
(Entity
(Orig_N
)) -- needed in some cases
16473 case Ekind
(Entity
(Orig_N
)) is
16475 | E_Enumeration_Literal
16482 if Is_Type
(Entity
(Orig_N
)) then
16490 when N_Qualified_Expression
16491 | N_Type_Conversion
16493 Is_Ok
:= Is_SPARK_05_Initialization_Expr
(Expression
(Orig_N
));
16496 Is_Ok
:= Is_SPARK_05_Initialization_Expr
(Right_Opnd
(Orig_N
));
16499 | N_Membership_Test
16502 Is_Ok
:= Is_SPARK_05_Initialization_Expr
(Left_Opnd
(Orig_N
))
16504 Is_SPARK_05_Initialization_Expr
(Right_Opnd
(Orig_N
));
16507 | N_Extension_Aggregate
16509 if Nkind
(Orig_N
) = N_Extension_Aggregate
then
16511 Is_SPARK_05_Initialization_Expr
(Ancestor_Part
(Orig_N
));
16514 Expr
:= First
(Expressions
(Orig_N
));
16515 while Present
(Expr
) loop
16516 if not Is_SPARK_05_Initialization_Expr
(Expr
) then
16524 Comp_Assn
:= First
(Component_Associations
(Orig_N
));
16525 while Present
(Comp_Assn
) loop
16526 Expr
:= Expression
(Comp_Assn
);
16528 -- Note: test for Present here needed for box assocation
16531 and then not Is_SPARK_05_Initialization_Expr
(Expr
)
16540 when N_Attribute_Reference
=>
16541 if Nkind
(Prefix
(Orig_N
)) in N_Subexpr
then
16542 Is_Ok
:= Is_SPARK_05_Initialization_Expr
(Prefix
(Orig_N
));
16545 Expr
:= First
(Expressions
(Orig_N
));
16546 while Present
(Expr
) loop
16547 if not Is_SPARK_05_Initialization_Expr
(Expr
) then
16555 -- Selected components might be expanded named not yet resolved, so
16556 -- default on the safe side. (Eg on sparklex.ads)
16558 when N_Selected_Component
=>
16567 end Is_SPARK_05_Initialization_Expr
;
16569 ----------------------------------
16570 -- Is_SPARK_05_Object_Reference --
16571 ----------------------------------
16573 function Is_SPARK_05_Object_Reference
(N
: Node_Id
) return Boolean is
16575 if Is_Entity_Name
(N
) then
16576 return Present
(Entity
(N
))
16578 (Ekind_In
(Entity
(N
), E_Constant
, E_Variable
)
16579 or else Ekind
(Entity
(N
)) in Formal_Kind
);
16583 when N_Selected_Component
=>
16584 return Is_SPARK_05_Object_Reference
(Prefix
(N
));
16590 end Is_SPARK_05_Object_Reference
;
16592 -----------------------------
16593 -- Is_Specific_Tagged_Type --
16594 -----------------------------
16596 function Is_Specific_Tagged_Type
(Typ
: Entity_Id
) return Boolean is
16597 Full_Typ
: Entity_Id
;
16600 -- Handle private types
16602 if Is_Private_Type
(Typ
) and then Present
(Full_View
(Typ
)) then
16603 Full_Typ
:= Full_View
(Typ
);
16608 -- A specific tagged type is a non-class-wide tagged type
16610 return Is_Tagged_Type
(Full_Typ
) and not Is_Class_Wide_Type
(Full_Typ
);
16611 end Is_Specific_Tagged_Type
;
16617 function Is_Statement
(N
: Node_Id
) return Boolean is
16620 Nkind
(N
) in N_Statement_Other_Than_Procedure_Call
16621 or else Nkind
(N
) = N_Procedure_Call_Statement
;
16624 ---------------------------------------
16625 -- Is_Subprogram_Contract_Annotation --
16626 ---------------------------------------
16628 function Is_Subprogram_Contract_Annotation
16629 (Item
: Node_Id
) return Boolean
16634 if Nkind
(Item
) = N_Aspect_Specification
then
16635 Nam
:= Chars
(Identifier
(Item
));
16637 else pragma Assert
(Nkind
(Item
) = N_Pragma
);
16638 Nam
:= Pragma_Name
(Item
);
16641 return Nam
= Name_Contract_Cases
16642 or else Nam
= Name_Depends
16643 or else Nam
= Name_Extensions_Visible
16644 or else Nam
= Name_Global
16645 or else Nam
= Name_Post
16646 or else Nam
= Name_Post_Class
16647 or else Nam
= Name_Postcondition
16648 or else Nam
= Name_Pre
16649 or else Nam
= Name_Pre_Class
16650 or else Nam
= Name_Precondition
16651 or else Nam
= Name_Refined_Depends
16652 or else Nam
= Name_Refined_Global
16653 or else Nam
= Name_Refined_Post
16654 or else Nam
= Name_Test_Case
;
16655 end Is_Subprogram_Contract_Annotation
;
16657 --------------------------------------------------
16658 -- Is_Subprogram_Stub_Without_Prior_Declaration --
16659 --------------------------------------------------
16661 function Is_Subprogram_Stub_Without_Prior_Declaration
16662 (N
: Node_Id
) return Boolean
16665 -- A subprogram stub without prior declaration serves as declaration for
16666 -- the actual subprogram body. As such, it has an attached defining
16667 -- entity of E_[Generic_]Function or E_[Generic_]Procedure.
16669 return Nkind
(N
) = N_Subprogram_Body_Stub
16670 and then Ekind
(Defining_Entity
(N
)) /= E_Subprogram_Body
;
16671 end Is_Subprogram_Stub_Without_Prior_Declaration
;
16673 --------------------------
16674 -- Is_Suspension_Object --
16675 --------------------------
16677 function Is_Suspension_Object
(Id
: Entity_Id
) return Boolean is
16679 -- This approach does an exact name match rather than to rely on
16680 -- RTSfind. Routine Is_Effectively_Volatile is used by clients of the
16681 -- front end at point where all auxiliary tables are locked and any
16682 -- modifications to them are treated as violations. Do not tamper with
16683 -- the tables, instead examine the Chars fields of all the scopes of Id.
16686 Chars
(Id
) = Name_Suspension_Object
16687 and then Present
(Scope
(Id
))
16688 and then Chars
(Scope
(Id
)) = Name_Synchronous_Task_Control
16689 and then Present
(Scope
(Scope
(Id
)))
16690 and then Chars
(Scope
(Scope
(Id
))) = Name_Ada
16691 and then Present
(Scope
(Scope
(Scope
(Id
))))
16692 and then Scope
(Scope
(Scope
(Id
))) = Standard_Standard
;
16693 end Is_Suspension_Object
;
16695 ----------------------------
16696 -- Is_Synchronized_Object --
16697 ----------------------------
16699 function Is_Synchronized_Object
(Id
: Entity_Id
) return Boolean is
16703 if Is_Object
(Id
) then
16705 -- The object is synchronized if it is of a type that yields a
16706 -- synchronized object.
16708 if Yields_Synchronized_Object
(Etype
(Id
)) then
16711 -- The object is synchronized if it is atomic and Async_Writers is
16714 elsif Is_Atomic
(Id
) and then Async_Writers_Enabled
(Id
) then
16717 -- A constant is a synchronized object by default
16719 elsif Ekind
(Id
) = E_Constant
then
16722 -- A variable is a synchronized object if it is subject to pragma
16723 -- Constant_After_Elaboration.
16725 elsif Ekind
(Id
) = E_Variable
then
16726 Prag
:= Get_Pragma
(Id
, Pragma_Constant_After_Elaboration
);
16728 return Present
(Prag
) and then Is_Enabled_Pragma
(Prag
);
16732 -- Otherwise the input is not an object or it does not qualify as a
16733 -- synchronized object.
16736 end Is_Synchronized_Object
;
16738 ---------------------------------
16739 -- Is_Synchronized_Tagged_Type --
16740 ---------------------------------
16742 function Is_Synchronized_Tagged_Type
(E
: Entity_Id
) return Boolean is
16743 Kind
: constant Entity_Kind
:= Ekind
(Base_Type
(E
));
16746 -- A task or protected type derived from an interface is a tagged type.
16747 -- Such a tagged type is called a synchronized tagged type, as are
16748 -- synchronized interfaces and private extensions whose declaration
16749 -- includes the reserved word synchronized.
16751 return (Is_Tagged_Type
(E
)
16752 and then (Kind
= E_Task_Type
16754 Kind
= E_Protected_Type
))
16757 and then Is_Synchronized_Interface
(E
))
16759 (Ekind
(E
) = E_Record_Type_With_Private
16760 and then Nkind
(Parent
(E
)) = N_Private_Extension_Declaration
16761 and then (Synchronized_Present
(Parent
(E
))
16762 or else Is_Synchronized_Interface
(Etype
(E
))));
16763 end Is_Synchronized_Tagged_Type
;
16769 function Is_Transfer
(N
: Node_Id
) return Boolean is
16770 Kind
: constant Node_Kind
:= Nkind
(N
);
16773 if Kind
= N_Simple_Return_Statement
16775 Kind
= N_Extended_Return_Statement
16777 Kind
= N_Goto_Statement
16779 Kind
= N_Raise_Statement
16781 Kind
= N_Requeue_Statement
16785 elsif (Kind
= N_Exit_Statement
or else Kind
in N_Raise_xxx_Error
)
16786 and then No
(Condition
(N
))
16790 elsif Kind
= N_Procedure_Call_Statement
16791 and then Is_Entity_Name
(Name
(N
))
16792 and then Present
(Entity
(Name
(N
)))
16793 and then No_Return
(Entity
(Name
(N
)))
16797 elsif Nkind
(Original_Node
(N
)) = N_Raise_Statement
then
16809 function Is_True
(U
: Uint
) return Boolean is
16814 --------------------------------------
16815 -- Is_Unchecked_Conversion_Instance --
16816 --------------------------------------
16818 function Is_Unchecked_Conversion_Instance
(Id
: Entity_Id
) return Boolean is
16822 -- Look for a function whose generic parent is the predefined intrinsic
16823 -- function Unchecked_Conversion, or for one that renames such an
16826 if Ekind
(Id
) = E_Function
then
16827 Par
:= Parent
(Id
);
16829 if Nkind
(Par
) = N_Function_Specification
then
16830 Par
:= Generic_Parent
(Par
);
16832 if Present
(Par
) then
16834 Chars
(Par
) = Name_Unchecked_Conversion
16835 and then Is_Intrinsic_Subprogram
(Par
)
16836 and then In_Predefined_Unit
(Par
);
16839 Present
(Alias
(Id
))
16840 and then Is_Unchecked_Conversion_Instance
(Alias
(Id
));
16846 end Is_Unchecked_Conversion_Instance
;
16848 -------------------------------
16849 -- Is_Universal_Numeric_Type --
16850 -------------------------------
16852 function Is_Universal_Numeric_Type
(T
: Entity_Id
) return Boolean is
16854 return T
= Universal_Integer
or else T
= Universal_Real
;
16855 end Is_Universal_Numeric_Type
;
16857 ------------------------------
16858 -- Is_User_Defined_Equality --
16859 ------------------------------
16861 function Is_User_Defined_Equality
(Id
: Entity_Id
) return Boolean is
16863 return Ekind
(Id
) = E_Function
16864 and then Chars
(Id
) = Name_Op_Eq
16865 and then Comes_From_Source
(Id
)
16867 -- Internally generated equalities have a full type declaration
16868 -- as their parent.
16870 and then Nkind
(Parent
(Id
)) = N_Function_Specification
;
16871 end Is_User_Defined_Equality
;
16873 --------------------------------------
16874 -- Is_Validation_Variable_Reference --
16875 --------------------------------------
16877 function Is_Validation_Variable_Reference
(N
: Node_Id
) return Boolean is
16878 Var
: constant Node_Id
:= Unqual_Conv
(N
);
16879 Var_Id
: Entity_Id
;
16884 if Is_Entity_Name
(Var
) then
16885 Var_Id
:= Entity
(Var
);
16890 and then Ekind
(Var_Id
) = E_Variable
16891 and then Present
(Validated_Object
(Var_Id
));
16892 end Is_Validation_Variable_Reference
;
16894 ----------------------------
16895 -- Is_Variable_Size_Array --
16896 ----------------------------
16898 function Is_Variable_Size_Array
(E
: Entity_Id
) return Boolean is
16902 pragma Assert
(Is_Array_Type
(E
));
16904 -- Check if some index is initialized with a non-constant value
16906 Idx
:= First_Index
(E
);
16907 while Present
(Idx
) loop
16908 if Nkind
(Idx
) = N_Range
then
16909 if not Is_Constant_Bound
(Low_Bound
(Idx
))
16910 or else not Is_Constant_Bound
(High_Bound
(Idx
))
16916 Idx
:= Next_Index
(Idx
);
16920 end Is_Variable_Size_Array
;
16922 -----------------------------
16923 -- Is_Variable_Size_Record --
16924 -----------------------------
16926 function Is_Variable_Size_Record
(E
: Entity_Id
) return Boolean is
16928 Comp_Typ
: Entity_Id
;
16931 pragma Assert
(Is_Record_Type
(E
));
16933 Comp
:= First_Entity
(E
);
16934 while Present
(Comp
) loop
16935 Comp_Typ
:= Etype
(Comp
);
16937 -- Recursive call if the record type has discriminants
16939 if Is_Record_Type
(Comp_Typ
)
16940 and then Has_Discriminants
(Comp_Typ
)
16941 and then Is_Variable_Size_Record
(Comp_Typ
)
16945 elsif Is_Array_Type
(Comp_Typ
)
16946 and then Is_Variable_Size_Array
(Comp_Typ
)
16951 Next_Entity
(Comp
);
16955 end Is_Variable_Size_Record
;
16961 function Is_Variable
16963 Use_Original_Node
: Boolean := True) return Boolean
16965 Orig_Node
: Node_Id
;
16967 function In_Protected_Function
(E
: Entity_Id
) return Boolean;
16968 -- Within a protected function, the private components of the enclosing
16969 -- protected type are constants. A function nested within a (protected)
16970 -- procedure is not itself protected. Within the body of a protected
16971 -- function the current instance of the protected type is a constant.
16973 function Is_Variable_Prefix
(P
: Node_Id
) return Boolean;
16974 -- Prefixes can involve implicit dereferences, in which case we must
16975 -- test for the case of a reference of a constant access type, which can
16976 -- can never be a variable.
16978 ---------------------------
16979 -- In_Protected_Function --
16980 ---------------------------
16982 function In_Protected_Function
(E
: Entity_Id
) return Boolean is
16987 -- E is the current instance of a type
16989 if Is_Type
(E
) then
16998 if not Is_Protected_Type
(Prot
) then
17002 S
:= Current_Scope
;
17003 while Present
(S
) and then S
/= Prot
loop
17004 if Ekind
(S
) = E_Function
and then Scope
(S
) = Prot
then
17013 end In_Protected_Function
;
17015 ------------------------
17016 -- Is_Variable_Prefix --
17017 ------------------------
17019 function Is_Variable_Prefix
(P
: Node_Id
) return Boolean is
17021 if Is_Access_Type
(Etype
(P
)) then
17022 return not Is_Access_Constant
(Root_Type
(Etype
(P
)));
17024 -- For the case of an indexed component whose prefix has a packed
17025 -- array type, the prefix has been rewritten into a type conversion.
17026 -- Determine variable-ness from the converted expression.
17028 elsif Nkind
(P
) = N_Type_Conversion
17029 and then not Comes_From_Source
(P
)
17030 and then Is_Array_Type
(Etype
(P
))
17031 and then Is_Packed
(Etype
(P
))
17033 return Is_Variable
(Expression
(P
));
17036 return Is_Variable
(P
);
17038 end Is_Variable_Prefix
;
17040 -- Start of processing for Is_Variable
17043 -- Special check, allow x'Deref(expr) as a variable
17045 if Nkind
(N
) = N_Attribute_Reference
17046 and then Attribute_Name
(N
) = Name_Deref
17051 -- Check if we perform the test on the original node since this may be a
17052 -- test of syntactic categories which must not be disturbed by whatever
17053 -- rewriting might have occurred. For example, an aggregate, which is
17054 -- certainly NOT a variable, could be turned into a variable by
17057 if Use_Original_Node
then
17058 Orig_Node
:= Original_Node
(N
);
17063 -- Definitely OK if Assignment_OK is set. Since this is something that
17064 -- only gets set for expanded nodes, the test is on N, not Orig_Node.
17066 if Nkind
(N
) in N_Subexpr
and then Assignment_OK
(N
) then
17069 -- Normally we go to the original node, but there is one exception where
17070 -- we use the rewritten node, namely when it is an explicit dereference.
17071 -- The generated code may rewrite a prefix which is an access type with
17072 -- an explicit dereference. The dereference is a variable, even though
17073 -- the original node may not be (since it could be a constant of the
17076 -- In Ada 2005 we have a further case to consider: the prefix may be a
17077 -- function call given in prefix notation. The original node appears to
17078 -- be a selected component, but we need to examine the call.
17080 elsif Nkind
(N
) = N_Explicit_Dereference
17081 and then Nkind
(Orig_Node
) /= N_Explicit_Dereference
17082 and then Present
(Etype
(Orig_Node
))
17083 and then Is_Access_Type
(Etype
(Orig_Node
))
17085 -- Note that if the prefix is an explicit dereference that does not
17086 -- come from source, we must check for a rewritten function call in
17087 -- prefixed notation before other forms of rewriting, to prevent a
17091 (Nkind
(Orig_Node
) = N_Function_Call
17092 and then not Is_Access_Constant
(Etype
(Prefix
(N
))))
17094 Is_Variable_Prefix
(Original_Node
(Prefix
(N
)));
17096 -- in Ada 2012, the dereference may have been added for a type with
17097 -- a declared implicit dereference aspect. Check that it is not an
17098 -- access to constant.
17100 elsif Nkind
(N
) = N_Explicit_Dereference
17101 and then Present
(Etype
(Orig_Node
))
17102 and then Ada_Version
>= Ada_2012
17103 and then Has_Implicit_Dereference
(Etype
(Orig_Node
))
17105 return not Is_Access_Constant
(Etype
(Prefix
(N
)));
17107 -- A function call is never a variable
17109 elsif Nkind
(N
) = N_Function_Call
then
17112 -- All remaining checks use the original node
17114 elsif Is_Entity_Name
(Orig_Node
)
17115 and then Present
(Entity
(Orig_Node
))
17118 E
: constant Entity_Id
:= Entity
(Orig_Node
);
17119 K
: constant Entity_Kind
:= Ekind
(E
);
17122 return (K
= E_Variable
17123 and then Nkind
(Parent
(E
)) /= N_Exception_Handler
)
17124 or else (K
= E_Component
17125 and then not In_Protected_Function
(E
))
17126 or else K
= E_Out_Parameter
17127 or else K
= E_In_Out_Parameter
17128 or else K
= E_Generic_In_Out_Parameter
17130 -- Current instance of type. If this is a protected type, check
17131 -- we are not within the body of one of its protected functions.
17133 or else (Is_Type
(E
)
17134 and then In_Open_Scopes
(E
)
17135 and then not In_Protected_Function
(E
))
17137 or else (Is_Incomplete_Or_Private_Type
(E
)
17138 and then In_Open_Scopes
(Full_View
(E
)));
17142 case Nkind
(Orig_Node
) is
17143 when N_Indexed_Component
17146 return Is_Variable_Prefix
(Prefix
(Orig_Node
));
17148 when N_Selected_Component
=>
17149 return (Is_Variable
(Selector_Name
(Orig_Node
))
17150 and then Is_Variable_Prefix
(Prefix
(Orig_Node
)))
17152 (Nkind
(N
) = N_Expanded_Name
17153 and then Scope
(Entity
(N
)) = Entity
(Prefix
(N
)));
17155 -- For an explicit dereference, the type of the prefix cannot
17156 -- be an access to constant or an access to subprogram.
17158 when N_Explicit_Dereference
=>
17160 Typ
: constant Entity_Id
:= Etype
(Prefix
(Orig_Node
));
17162 return Is_Access_Type
(Typ
)
17163 and then not Is_Access_Constant
(Root_Type
(Typ
))
17164 and then Ekind
(Typ
) /= E_Access_Subprogram_Type
;
17167 -- The type conversion is the case where we do not deal with the
17168 -- context dependent special case of an actual parameter. Thus
17169 -- the type conversion is only considered a variable for the
17170 -- purposes of this routine if the target type is tagged. However,
17171 -- a type conversion is considered to be a variable if it does not
17172 -- come from source (this deals for example with the conversions
17173 -- of expressions to their actual subtypes).
17175 when N_Type_Conversion
=>
17176 return Is_Variable
(Expression
(Orig_Node
))
17178 (not Comes_From_Source
(Orig_Node
)
17180 (Is_Tagged_Type
(Etype
(Subtype_Mark
(Orig_Node
)))
17182 Is_Tagged_Type
(Etype
(Expression
(Orig_Node
)))));
17184 -- GNAT allows an unchecked type conversion as a variable. This
17185 -- only affects the generation of internal expanded code, since
17186 -- calls to instantiations of Unchecked_Conversion are never
17187 -- considered variables (since they are function calls).
17189 when N_Unchecked_Type_Conversion
=>
17190 return Is_Variable
(Expression
(Orig_Node
));
17198 ------------------------------
17199 -- Is_Verifiable_DIC_Pragma --
17200 ------------------------------
17202 function Is_Verifiable_DIC_Pragma
(Prag
: Node_Id
) return Boolean is
17203 Args
: constant List_Id
:= Pragma_Argument_Associations
(Prag
);
17206 -- To qualify as verifiable, a DIC pragma must have a non-null argument
17210 and then Nkind
(Get_Pragma_Arg
(First
(Args
))) /= N_Null
;
17211 end Is_Verifiable_DIC_Pragma
;
17213 ---------------------------
17214 -- Is_Visibly_Controlled --
17215 ---------------------------
17217 function Is_Visibly_Controlled
(T
: Entity_Id
) return Boolean is
17218 Root
: constant Entity_Id
:= Root_Type
(T
);
17220 return Chars
(Scope
(Root
)) = Name_Finalization
17221 and then Chars
(Scope
(Scope
(Root
))) = Name_Ada
17222 and then Scope
(Scope
(Scope
(Root
))) = Standard_Standard
;
17223 end Is_Visibly_Controlled
;
17225 --------------------------
17226 -- Is_Volatile_Function --
17227 --------------------------
17229 function Is_Volatile_Function
(Func_Id
: Entity_Id
) return Boolean is
17231 pragma Assert
(Ekind_In
(Func_Id
, E_Function
, E_Generic_Function
));
17233 -- A function declared within a protected type is volatile
17235 if Is_Protected_Type
(Scope
(Func_Id
)) then
17238 -- An instance of Ada.Unchecked_Conversion is a volatile function if
17239 -- either the source or the target are effectively volatile.
17241 elsif Is_Unchecked_Conversion_Instance
(Func_Id
)
17242 and then Has_Effectively_Volatile_Profile
(Func_Id
)
17246 -- Otherwise the function is treated as volatile if it is subject to
17247 -- enabled pragma Volatile_Function.
17251 Is_Enabled_Pragma
(Get_Pragma
(Func_Id
, Pragma_Volatile_Function
));
17253 end Is_Volatile_Function
;
17255 ------------------------
17256 -- Is_Volatile_Object --
17257 ------------------------
17259 function Is_Volatile_Object
(N
: Node_Id
) return Boolean is
17260 function Is_Volatile_Prefix
(N
: Node_Id
) return Boolean;
17261 -- If prefix is an implicit dereference, examine designated type
17263 function Object_Has_Volatile_Components
(N
: Node_Id
) return Boolean;
17264 -- Determines if given object has volatile components
17266 ------------------------
17267 -- Is_Volatile_Prefix --
17268 ------------------------
17270 function Is_Volatile_Prefix
(N
: Node_Id
) return Boolean is
17271 Typ
: constant Entity_Id
:= Etype
(N
);
17274 if Is_Access_Type
(Typ
) then
17276 Dtyp
: constant Entity_Id
:= Designated_Type
(Typ
);
17279 return Is_Volatile
(Dtyp
)
17280 or else Has_Volatile_Components
(Dtyp
);
17284 return Object_Has_Volatile_Components
(N
);
17286 end Is_Volatile_Prefix
;
17288 ------------------------------------
17289 -- Object_Has_Volatile_Components --
17290 ------------------------------------
17292 function Object_Has_Volatile_Components
(N
: Node_Id
) return Boolean is
17293 Typ
: constant Entity_Id
:= Etype
(N
);
17296 if Is_Volatile
(Typ
)
17297 or else Has_Volatile_Components
(Typ
)
17301 elsif Is_Entity_Name
(N
)
17302 and then (Has_Volatile_Components
(Entity
(N
))
17303 or else Is_Volatile
(Entity
(N
)))
17307 elsif Nkind
(N
) = N_Indexed_Component
17308 or else Nkind
(N
) = N_Selected_Component
17310 return Is_Volatile_Prefix
(Prefix
(N
));
17315 end Object_Has_Volatile_Components
;
17317 -- Start of processing for Is_Volatile_Object
17320 if Nkind
(N
) = N_Defining_Identifier
then
17321 return Is_Volatile
(N
) or else Is_Volatile
(Etype
(N
));
17323 elsif Nkind
(N
) = N_Expanded_Name
then
17324 return Is_Volatile_Object
(Entity
(N
));
17326 elsif Is_Volatile
(Etype
(N
))
17327 or else (Is_Entity_Name
(N
) and then Is_Volatile
(Entity
(N
)))
17331 elsif Nkind_In
(N
, N_Indexed_Component
, N_Selected_Component
)
17332 and then Is_Volatile_Prefix
(Prefix
(N
))
17336 elsif Nkind
(N
) = N_Selected_Component
17337 and then Is_Volatile
(Entity
(Selector_Name
(N
)))
17344 end Is_Volatile_Object
;
17346 -----------------------------
17347 -- Iterate_Call_Parameters --
17348 -----------------------------
17350 procedure Iterate_Call_Parameters
(Call
: Node_Id
) is
17351 Formal
: Entity_Id
:= First_Formal
(Get_Called_Entity
(Call
));
17352 Actual
: Node_Id
:= First_Actual
(Call
);
17355 while Present
(Formal
) and then Present
(Actual
) loop
17356 Handle_Parameter
(Formal
, Actual
);
17357 Formal
:= Next_Formal
(Formal
);
17358 Actual
:= Next_Actual
(Actual
);
17360 end Iterate_Call_Parameters
;
17362 ---------------------------
17363 -- Itype_Has_Declaration --
17364 ---------------------------
17366 function Itype_Has_Declaration
(Id
: Entity_Id
) return Boolean is
17368 pragma Assert
(Is_Itype
(Id
));
17369 return Present
(Parent
(Id
))
17370 and then Nkind_In
(Parent
(Id
), N_Full_Type_Declaration
,
17371 N_Subtype_Declaration
)
17372 and then Defining_Entity
(Parent
(Id
)) = Id
;
17373 end Itype_Has_Declaration
;
17375 -------------------------
17376 -- Kill_Current_Values --
17377 -------------------------
17379 procedure Kill_Current_Values
17381 Last_Assignment_Only
: Boolean := False)
17384 if Is_Assignable
(Ent
) then
17385 Set_Last_Assignment
(Ent
, Empty
);
17388 if Is_Object
(Ent
) then
17389 if not Last_Assignment_Only
then
17391 Set_Current_Value
(Ent
, Empty
);
17393 -- Do not reset the Is_Known_[Non_]Null and Is_Known_Valid flags
17394 -- for a constant. Once the constant is elaborated, its value is
17395 -- not changed, therefore the associated flags that describe the
17396 -- value should not be modified either.
17398 if Ekind
(Ent
) = E_Constant
then
17401 -- Non-constant entities
17404 if not Can_Never_Be_Null
(Ent
) then
17405 Set_Is_Known_Non_Null
(Ent
, False);
17408 Set_Is_Known_Null
(Ent
, False);
17410 -- Reset the Is_Known_Valid flag unless the type is always
17411 -- valid. This does not apply to a loop parameter because its
17412 -- bounds are defined by the loop header and therefore always
17415 if not Is_Known_Valid
(Etype
(Ent
))
17416 and then Ekind
(Ent
) /= E_Loop_Parameter
17418 Set_Is_Known_Valid
(Ent
, False);
17423 end Kill_Current_Values
;
17425 procedure Kill_Current_Values
(Last_Assignment_Only
: Boolean := False) is
17428 procedure Kill_Current_Values_For_Entity_Chain
(E
: Entity_Id
);
17429 -- Clear current value for entity E and all entities chained to E
17431 ------------------------------------------
17432 -- Kill_Current_Values_For_Entity_Chain --
17433 ------------------------------------------
17435 procedure Kill_Current_Values_For_Entity_Chain
(E
: Entity_Id
) is
17439 while Present
(Ent
) loop
17440 Kill_Current_Values
(Ent
, Last_Assignment_Only
);
17443 end Kill_Current_Values_For_Entity_Chain
;
17445 -- Start of processing for Kill_Current_Values
17448 -- Kill all saved checks, a special case of killing saved values
17450 if not Last_Assignment_Only
then
17454 -- Loop through relevant scopes, which includes the current scope and
17455 -- any parent scopes if the current scope is a block or a package.
17457 S
:= Current_Scope
;
17460 -- Clear current values of all entities in current scope
17462 Kill_Current_Values_For_Entity_Chain
(First_Entity
(S
));
17464 -- If scope is a package, also clear current values of all private
17465 -- entities in the scope.
17467 if Is_Package_Or_Generic_Package
(S
)
17468 or else Is_Concurrent_Type
(S
)
17470 Kill_Current_Values_For_Entity_Chain
(First_Private_Entity
(S
));
17473 -- If this is a not a subprogram, deal with parents
17475 if not Is_Subprogram
(S
) then
17477 exit Scope_Loop
when S
= Standard_Standard
;
17481 end loop Scope_Loop
;
17482 end Kill_Current_Values
;
17484 --------------------------
17485 -- Kill_Size_Check_Code --
17486 --------------------------
17488 procedure Kill_Size_Check_Code
(E
: Entity_Id
) is
17490 if (Ekind
(E
) = E_Constant
or else Ekind
(E
) = E_Variable
)
17491 and then Present
(Size_Check_Code
(E
))
17493 Remove
(Size_Check_Code
(E
));
17494 Set_Size_Check_Code
(E
, Empty
);
17496 end Kill_Size_Check_Code
;
17498 --------------------
17499 -- Known_Non_Null --
17500 --------------------
17502 function Known_Non_Null
(N
: Node_Id
) return Boolean is
17503 Status
: constant Null_Status_Kind
:= Null_Status
(N
);
17510 -- The expression yields a non-null value ignoring simple flow analysis
17512 if Status
= Is_Non_Null
then
17515 -- Otherwise check whether N is a reference to an entity that appears
17516 -- within a conditional construct.
17518 elsif Is_Entity_Name
(N
) and then Present
(Entity
(N
)) then
17520 -- First check if we are in decisive conditional
17522 Get_Current_Value_Condition
(N
, Op
, Val
);
17524 if Known_Null
(Val
) then
17525 if Op
= N_Op_Eq
then
17527 elsif Op
= N_Op_Ne
then
17532 -- If OK to do replacement, test Is_Known_Non_Null flag
17536 if OK_To_Do_Constant_Replacement
(Id
) then
17537 return Is_Known_Non_Null
(Id
);
17541 -- Otherwise it is not possible to determine whether N yields a non-null
17545 end Known_Non_Null
;
17551 function Known_Null
(N
: Node_Id
) return Boolean is
17552 Status
: constant Null_Status_Kind
:= Null_Status
(N
);
17559 -- The expression yields a null value ignoring simple flow analysis
17561 if Status
= Is_Null
then
17564 -- Otherwise check whether N is a reference to an entity that appears
17565 -- within a conditional construct.
17567 elsif Is_Entity_Name
(N
) and then Present
(Entity
(N
)) then
17569 -- First check if we are in decisive conditional
17571 Get_Current_Value_Condition
(N
, Op
, Val
);
17573 if Known_Null
(Val
) then
17574 if Op
= N_Op_Eq
then
17576 elsif Op
= N_Op_Ne
then
17581 -- If OK to do replacement, test Is_Known_Null flag
17585 if OK_To_Do_Constant_Replacement
(Id
) then
17586 return Is_Known_Null
(Id
);
17590 -- Otherwise it is not possible to determine whether N yields a null
17596 --------------------------
17597 -- Known_To_Be_Assigned --
17598 --------------------------
17600 function Known_To_Be_Assigned
(N
: Node_Id
) return Boolean is
17601 P
: constant Node_Id
:= Parent
(N
);
17606 -- Test left side of assignment
17608 when N_Assignment_Statement
=>
17609 return N
= Name
(P
);
17611 -- Function call arguments are never lvalues
17613 when N_Function_Call
=>
17616 -- Positional parameter for procedure or accept call
17618 when N_Accept_Statement
17619 | N_Procedure_Call_Statement
17627 Proc
:= Get_Subprogram_Entity
(P
);
17633 -- If we are not a list member, something is strange, so
17634 -- be conservative and return False.
17636 if not Is_List_Member
(N
) then
17640 -- We are going to find the right formal by stepping forward
17641 -- through the formals, as we step backwards in the actuals.
17643 Form
:= First_Formal
(Proc
);
17646 -- If no formal, something is weird, so be conservative
17647 -- and return False.
17654 exit when No
(Act
);
17655 Next_Formal
(Form
);
17658 return Ekind
(Form
) /= E_In_Parameter
;
17661 -- Named parameter for procedure or accept call
17663 when N_Parameter_Association
=>
17669 Proc
:= Get_Subprogram_Entity
(Parent
(P
));
17675 -- Loop through formals to find the one that matches
17677 Form
:= First_Formal
(Proc
);
17679 -- If no matching formal, that's peculiar, some kind of
17680 -- previous error, so return False to be conservative.
17681 -- Actually this also happens in legal code in the case
17682 -- where P is a parameter association for an Extra_Formal???
17688 -- Else test for match
17690 if Chars
(Form
) = Chars
(Selector_Name
(P
)) then
17691 return Ekind
(Form
) /= E_In_Parameter
;
17694 Next_Formal
(Form
);
17698 -- Test for appearing in a conversion that itself appears
17699 -- in an lvalue context, since this should be an lvalue.
17701 when N_Type_Conversion
=>
17702 return Known_To_Be_Assigned
(P
);
17704 -- All other references are definitely not known to be modifications
17709 end Known_To_Be_Assigned
;
17711 ---------------------------
17712 -- Last_Source_Statement --
17713 ---------------------------
17715 function Last_Source_Statement
(HSS
: Node_Id
) return Node_Id
is
17719 N
:= Last
(Statements
(HSS
));
17720 while Present
(N
) loop
17721 exit when Comes_From_Source
(N
);
17726 end Last_Source_Statement
;
17728 -----------------------
17729 -- Mark_Coextensions --
17730 -----------------------
17732 procedure Mark_Coextensions
(Context_Nod
: Node_Id
; Root_Nod
: Node_Id
) is
17733 Is_Dynamic
: Boolean;
17734 -- Indicates whether the context causes nested coextensions to be
17735 -- dynamic or static
17737 function Mark_Allocator
(N
: Node_Id
) return Traverse_Result
;
17738 -- Recognize an allocator node and label it as a dynamic coextension
17740 --------------------
17741 -- Mark_Allocator --
17742 --------------------
17744 function Mark_Allocator
(N
: Node_Id
) return Traverse_Result
is
17746 if Nkind
(N
) = N_Allocator
then
17748 Set_Is_Dynamic_Coextension
(N
);
17750 -- If the allocator expression is potentially dynamic, it may
17751 -- be expanded out of order and require dynamic allocation
17752 -- anyway, so we treat the coextension itself as dynamic.
17753 -- Potential optimization ???
17755 elsif Nkind
(Expression
(N
)) = N_Qualified_Expression
17756 and then Nkind
(Expression
(Expression
(N
))) = N_Op_Concat
17758 Set_Is_Dynamic_Coextension
(N
);
17760 Set_Is_Static_Coextension
(N
);
17765 end Mark_Allocator
;
17767 procedure Mark_Allocators
is new Traverse_Proc
(Mark_Allocator
);
17769 -- Start of processing for Mark_Coextensions
17772 -- An allocator that appears on the right-hand side of an assignment is
17773 -- treated as a potentially dynamic coextension when the right-hand side
17774 -- is an allocator or a qualified expression.
17776 -- Obj := new ...'(new Coextension ...);
17778 if Nkind
(Context_Nod
) = N_Assignment_Statement
then
17780 Nkind_In
(Expression
(Context_Nod
), N_Allocator
,
17781 N_Qualified_Expression
);
17783 -- An allocator that appears within the expression of a simple return
17784 -- statement is treated as a potentially dynamic coextension when the
17785 -- expression is either aggregate, allocator, or qualified expression.
17787 -- return (new Coextension ...);
17788 -- return new ...'(new Coextension ...);
17790 elsif Nkind
(Context_Nod
) = N_Simple_Return_Statement
then
17792 Nkind_In
(Expression
(Context_Nod
), N_Aggregate
,
17794 N_Qualified_Expression
);
17796 -- An alloctor that appears within the initialization expression of an
17797 -- object declaration is considered a potentially dynamic coextension
17798 -- when the initialization expression is an allocator or a qualified
17801 -- Obj : ... := new ...'(new Coextension ...);
17803 -- A similar case arises when the object declaration is part of an
17804 -- extended return statement.
17806 -- return Obj : ... := new ...'(new Coextension ...);
17807 -- return Obj : ... := (new Coextension ...);
17809 elsif Nkind
(Context_Nod
) = N_Object_Declaration
then
17811 Nkind_In
(Root_Nod
, N_Allocator
, N_Qualified_Expression
)
17813 Nkind
(Parent
(Context_Nod
)) = N_Extended_Return_Statement
;
17815 -- This routine should not be called with constructs that cannot contain
17819 raise Program_Error
;
17822 Mark_Allocators
(Root_Nod
);
17823 end Mark_Coextensions
;
17825 ---------------------------------
17826 -- Mark_Elaboration_Attributes --
17827 ---------------------------------
17829 procedure Mark_Elaboration_Attributes
17830 (N_Id
: Node_Or_Entity_Id
;
17831 Checks
: Boolean := False;
17832 Level
: Boolean := False;
17833 Modes
: Boolean := False;
17834 Warnings
: Boolean := False)
17836 function Elaboration_Checks_OK
17837 (Target_Id
: Entity_Id
;
17838 Context_Id
: Entity_Id
) return Boolean;
17839 -- Determine whether elaboration checks are enabled for target Target_Id
17840 -- which resides within context Context_Id.
17842 procedure Mark_Elaboration_Attributes_Id
(Id
: Entity_Id
);
17843 -- Preserve relevant attributes of the context in arbitrary entity Id
17845 procedure Mark_Elaboration_Attributes_Node
(N
: Node_Id
);
17846 -- Preserve relevant attributes of the context in arbitrary node N
17848 ---------------------------
17849 -- Elaboration_Checks_OK --
17850 ---------------------------
17852 function Elaboration_Checks_OK
17853 (Target_Id
: Entity_Id
;
17854 Context_Id
: Entity_Id
) return Boolean
17856 Encl_Scop
: Entity_Id
;
17859 -- Elaboration checks are suppressed for the target
17861 if Elaboration_Checks_Suppressed
(Target_Id
) then
17865 -- Otherwise elaboration checks are OK for the target, but may be
17866 -- suppressed for the context where the target is declared.
17868 Encl_Scop
:= Context_Id
;
17869 while Present
(Encl_Scop
) and then Encl_Scop
/= Standard_Standard
loop
17870 if Elaboration_Checks_Suppressed
(Encl_Scop
) then
17874 Encl_Scop
:= Scope
(Encl_Scop
);
17877 -- Neither the target nor its declarative context have elaboration
17878 -- checks suppressed.
17881 end Elaboration_Checks_OK
;
17883 ------------------------------------
17884 -- Mark_Elaboration_Attributes_Id --
17885 ------------------------------------
17887 procedure Mark_Elaboration_Attributes_Id
(Id
: Entity_Id
) is
17889 -- Mark the status of elaboration checks in effect. Do not reset the
17890 -- status in case the entity is reanalyzed with checks suppressed.
17892 if Checks
and then not Is_Elaboration_Checks_OK_Id
(Id
) then
17893 Set_Is_Elaboration_Checks_OK_Id
(Id
,
17894 Elaboration_Checks_OK
17896 Context_Id
=> Scope
(Id
)));
17898 -- Entities do not need to capture their enclosing level. The Ghost
17899 -- and SPARK modes in effect are already marked during analysis.
17904 end Mark_Elaboration_Attributes_Id
;
17906 --------------------------------------
17907 -- Mark_Elaboration_Attributes_Node --
17908 --------------------------------------
17910 procedure Mark_Elaboration_Attributes_Node
(N
: Node_Id
) is
17911 function Extract_Name
(N
: Node_Id
) return Node_Id
;
17912 -- Obtain the Name attribute of call or instantiation N
17918 function Extract_Name
(N
: Node_Id
) return Node_Id
is
17924 -- A call to an entry family appears in indexed form
17926 if Nkind
(Nam
) = N_Indexed_Component
then
17927 Nam
:= Prefix
(Nam
);
17930 -- The name may also appear in qualified form
17932 if Nkind
(Nam
) = N_Selected_Component
then
17933 Nam
:= Selector_Name
(Nam
);
17941 Context_Id
: Entity_Id
;
17944 -- Start of processing for Mark_Elaboration_Attributes_Node
17947 -- Mark the status of elaboration checks in effect. Do not reset the
17948 -- status in case the node is reanalyzed with checks suppressed.
17950 if Checks
and then not Is_Elaboration_Checks_OK_Node
(N
) then
17952 -- Assignments, attribute references, and variable references do
17953 -- not have a "declarative" context.
17955 Context_Id
:= Empty
;
17957 -- The status of elaboration checks for calls and instantiations
17958 -- depends on the most recent pragma Suppress/Unsuppress, as well
17959 -- as the suppression status of the context where the target is
17963 -- function Func ...;
17967 -- procedure Main is
17968 -- pragma Suppress (Elaboration_Checks, Pack);
17969 -- X : ... := Pack.Func;
17972 -- In the example above, the call to Func has elaboration checks
17973 -- enabled because there is no active general purpose suppression
17974 -- pragma, however the elaboration checks of Pack are explicitly
17975 -- suppressed. As a result the elaboration checks of the call must
17976 -- be disabled in order to preserve this dependency.
17978 if Nkind_In
(N
, N_Entry_Call_Statement
,
17980 N_Function_Instantiation
,
17981 N_Package_Instantiation
,
17982 N_Procedure_Call_Statement
,
17983 N_Procedure_Instantiation
)
17985 Nam
:= Extract_Name
(N
);
17987 if Is_Entity_Name
(Nam
) and then Present
(Entity
(Nam
)) then
17988 Context_Id
:= Scope
(Entity
(Nam
));
17992 Set_Is_Elaboration_Checks_OK_Node
(N
,
17993 Elaboration_Checks_OK
17994 (Target_Id
=> Empty
,
17995 Context_Id
=> Context_Id
));
17998 -- Mark the enclosing level of the node. Do not reset the status in
17999 -- case the node is relocated and reanalyzed.
18001 if Level
and then not Is_Declaration_Level_Node
(N
) then
18002 Set_Is_Declaration_Level_Node
(N
,
18003 Find_Enclosing_Level
(N
) = Declaration_Level
);
18006 -- Mark the Ghost and SPARK mode in effect
18009 if Ghost_Mode
= Ignore
then
18010 Set_Is_Ignored_Ghost_Node
(N
);
18013 if SPARK_Mode
= On
then
18014 Set_Is_SPARK_Mode_On_Node
(N
);
18018 -- Mark the status of elaboration warnings in effect. Do not reset
18019 -- the status in case the node is reanalyzed with warnings off.
18021 if Warnings
and then not Is_Elaboration_Warnings_OK_Node
(N
) then
18022 Set_Is_Elaboration_Warnings_OK_Node
(N
, Elab_Warnings
);
18024 end Mark_Elaboration_Attributes_Node
;
18026 -- Start of processing for Mark_Elaboration_Attributes
18029 if Nkind
(N_Id
) in N_Entity
then
18030 Mark_Elaboration_Attributes_Id
(N_Id
);
18032 Mark_Elaboration_Attributes_Node
(N_Id
);
18034 end Mark_Elaboration_Attributes
;
18036 ----------------------------------
18037 -- Matching_Static_Array_Bounds --
18038 ----------------------------------
18040 function Matching_Static_Array_Bounds
18042 R_Typ
: Node_Id
) return Boolean
18044 L_Ndims
: constant Nat
:= Number_Dimensions
(L_Typ
);
18045 R_Ndims
: constant Nat
:= Number_Dimensions
(R_Typ
);
18047 L_Index
: Node_Id
:= Empty
; -- init to ...
18048 R_Index
: Node_Id
:= Empty
; -- ...avoid warnings
18057 if L_Ndims
/= R_Ndims
then
18061 -- Unconstrained types do not have static bounds
18063 if not Is_Constrained
(L_Typ
) or else not Is_Constrained
(R_Typ
) then
18067 -- First treat specially the first dimension, as the lower bound and
18068 -- length of string literals are not stored like those of arrays.
18070 if Ekind
(L_Typ
) = E_String_Literal_Subtype
then
18071 L_Low
:= String_Literal_Low_Bound
(L_Typ
);
18072 L_Len
:= String_Literal_Length
(L_Typ
);
18074 L_Index
:= First_Index
(L_Typ
);
18075 Get_Index_Bounds
(L_Index
, L_Low
, L_High
);
18077 if Is_OK_Static_Expression
(L_Low
)
18079 Is_OK_Static_Expression
(L_High
)
18081 if Expr_Value
(L_High
) < Expr_Value
(L_Low
) then
18084 L_Len
:= (Expr_Value
(L_High
) - Expr_Value
(L_Low
)) + 1;
18091 if Ekind
(R_Typ
) = E_String_Literal_Subtype
then
18092 R_Low
:= String_Literal_Low_Bound
(R_Typ
);
18093 R_Len
:= String_Literal_Length
(R_Typ
);
18095 R_Index
:= First_Index
(R_Typ
);
18096 Get_Index_Bounds
(R_Index
, R_Low
, R_High
);
18098 if Is_OK_Static_Expression
(R_Low
)
18100 Is_OK_Static_Expression
(R_High
)
18102 if Expr_Value
(R_High
) < Expr_Value
(R_Low
) then
18105 R_Len
:= (Expr_Value
(R_High
) - Expr_Value
(R_Low
)) + 1;
18112 if (Is_OK_Static_Expression
(L_Low
)
18114 Is_OK_Static_Expression
(R_Low
))
18115 and then Expr_Value
(L_Low
) = Expr_Value
(R_Low
)
18116 and then L_Len
= R_Len
18123 -- Then treat all other dimensions
18125 for Indx
in 2 .. L_Ndims
loop
18129 Get_Index_Bounds
(L_Index
, L_Low
, L_High
);
18130 Get_Index_Bounds
(R_Index
, R_Low
, R_High
);
18132 if (Is_OK_Static_Expression
(L_Low
) and then
18133 Is_OK_Static_Expression
(L_High
) and then
18134 Is_OK_Static_Expression
(R_Low
) and then
18135 Is_OK_Static_Expression
(R_High
))
18136 and then (Expr_Value
(L_Low
) = Expr_Value
(R_Low
)
18138 Expr_Value
(L_High
) = Expr_Value
(R_High
))
18146 -- If we fall through the loop, all indexes matched
18149 end Matching_Static_Array_Bounds
;
18151 -------------------
18152 -- May_Be_Lvalue --
18153 -------------------
18155 function May_Be_Lvalue
(N
: Node_Id
) return Boolean is
18156 P
: constant Node_Id
:= Parent
(N
);
18161 -- Test left side of assignment
18163 when N_Assignment_Statement
=>
18164 return N
= Name
(P
);
18166 -- Test prefix of component or attribute. Note that the prefix of an
18167 -- explicit or implicit dereference cannot be an l-value. In the case
18168 -- of a 'Read attribute, the reference can be an actual in the
18169 -- argument list of the attribute.
18171 when N_Attribute_Reference
=>
18172 return (N
= Prefix
(P
)
18173 and then Name_Implies_Lvalue_Prefix
(Attribute_Name
(P
)))
18175 Attribute_Name
(P
) = Name_Read
;
18177 -- For an expanded name, the name is an lvalue if the expanded name
18178 -- is an lvalue, but the prefix is never an lvalue, since it is just
18179 -- the scope where the name is found.
18181 when N_Expanded_Name
=>
18182 if N
= Prefix
(P
) then
18183 return May_Be_Lvalue
(P
);
18188 -- For a selected component A.B, A is certainly an lvalue if A.B is.
18189 -- B is a little interesting, if we have A.B := 3, there is some
18190 -- discussion as to whether B is an lvalue or not, we choose to say
18191 -- it is. Note however that A is not an lvalue if it is of an access
18192 -- type since this is an implicit dereference.
18194 when N_Selected_Component
=>
18196 and then Present
(Etype
(N
))
18197 and then Is_Access_Type
(Etype
(N
))
18201 return May_Be_Lvalue
(P
);
18204 -- For an indexed component or slice, the index or slice bounds is
18205 -- never an lvalue. The prefix is an lvalue if the indexed component
18206 -- or slice is an lvalue, except if it is an access type, where we
18207 -- have an implicit dereference.
18209 when N_Indexed_Component
18213 or else (Present
(Etype
(N
)) and then Is_Access_Type
(Etype
(N
)))
18217 return May_Be_Lvalue
(P
);
18220 -- Prefix of a reference is an lvalue if the reference is an lvalue
18222 when N_Reference
=>
18223 return May_Be_Lvalue
(P
);
18225 -- Prefix of explicit dereference is never an lvalue
18227 when N_Explicit_Dereference
=>
18230 -- Positional parameter for subprogram, entry, or accept call.
18231 -- In older versions of Ada function call arguments are never
18232 -- lvalues. In Ada 2012 functions can have in-out parameters.
18234 when N_Accept_Statement
18235 | N_Entry_Call_Statement
18236 | N_Subprogram_Call
18238 if Nkind
(P
) = N_Function_Call
and then Ada_Version
< Ada_2012
then
18242 -- The following mechanism is clumsy and fragile. A single flag
18243 -- set in Resolve_Actuals would be preferable ???
18251 Proc
:= Get_Subprogram_Entity
(P
);
18257 -- If we are not a list member, something is strange, so be
18258 -- conservative and return True.
18260 if not Is_List_Member
(N
) then
18264 -- We are going to find the right formal by stepping forward
18265 -- through the formals, as we step backwards in the actuals.
18267 Form
:= First_Formal
(Proc
);
18270 -- If no formal, something is weird, so be conservative and
18278 exit when No
(Act
);
18279 Next_Formal
(Form
);
18282 return Ekind
(Form
) /= E_In_Parameter
;
18285 -- Named parameter for procedure or accept call
18287 when N_Parameter_Association
=>
18293 Proc
:= Get_Subprogram_Entity
(Parent
(P
));
18299 -- Loop through formals to find the one that matches
18301 Form
:= First_Formal
(Proc
);
18303 -- If no matching formal, that's peculiar, some kind of
18304 -- previous error, so return True to be conservative.
18305 -- Actually happens with legal code for an unresolved call
18306 -- where we may get the wrong homonym???
18312 -- Else test for match
18314 if Chars
(Form
) = Chars
(Selector_Name
(P
)) then
18315 return Ekind
(Form
) /= E_In_Parameter
;
18318 Next_Formal
(Form
);
18322 -- Test for appearing in a conversion that itself appears in an
18323 -- lvalue context, since this should be an lvalue.
18325 when N_Type_Conversion
=>
18326 return May_Be_Lvalue
(P
);
18328 -- Test for appearance in object renaming declaration
18330 when N_Object_Renaming_Declaration
=>
18333 -- All other references are definitely not lvalues
18344 function Might_Raise
(N
: Node_Id
) return Boolean is
18345 Result
: Boolean := False;
18347 function Process
(N
: Node_Id
) return Traverse_Result
;
18348 -- Set Result to True if we find something that could raise an exception
18354 function Process
(N
: Node_Id
) return Traverse_Result
is
18356 if Nkind_In
(N
, N_Procedure_Call_Statement
,
18359 N_Raise_Constraint_Error
,
18360 N_Raise_Program_Error
,
18361 N_Raise_Storage_Error
)
18370 procedure Set_Result
is new Traverse_Proc
(Process
);
18372 -- Start of processing for Might_Raise
18375 -- False if exceptions can't be propagated
18377 if No_Exception_Handlers_Set
then
18381 -- If the checks handled by the back end are not disabled, we cannot
18382 -- ensure that no exception will be raised.
18384 if not Access_Checks_Suppressed
(Empty
)
18385 or else not Discriminant_Checks_Suppressed
(Empty
)
18386 or else not Range_Checks_Suppressed
(Empty
)
18387 or else not Index_Checks_Suppressed
(Empty
)
18388 or else Opt
.Stack_Checking_Enabled
18397 --------------------------------
18398 -- Nearest_Enclosing_Instance --
18399 --------------------------------
18401 function Nearest_Enclosing_Instance
(E
: Entity_Id
) return Entity_Id
is
18406 while Present
(Inst
) and then Inst
/= Standard_Standard
loop
18407 if Is_Generic_Instance
(Inst
) then
18411 Inst
:= Scope
(Inst
);
18415 end Nearest_Enclosing_Instance
;
18417 ----------------------
18418 -- Needs_One_Actual --
18419 ----------------------
18421 function Needs_One_Actual
(E
: Entity_Id
) return Boolean is
18422 Formal
: Entity_Id
;
18425 -- Ada 2005 or later, and formals present. The first formal must be
18426 -- of a type that supports prefix notation: a controlling argument,
18427 -- a class-wide type, or an access to such.
18429 if Ada_Version
>= Ada_2005
18430 and then Present
(First_Formal
(E
))
18431 and then No
(Default_Value
(First_Formal
(E
)))
18433 (Is_Controlling_Formal
(First_Formal
(E
))
18434 or else Is_Class_Wide_Type
(Etype
(First_Formal
(E
)))
18435 or else Is_Anonymous_Access_Type
(Etype
(First_Formal
(E
))))
18437 Formal
:= Next_Formal
(First_Formal
(E
));
18438 while Present
(Formal
) loop
18439 if No
(Default_Value
(Formal
)) then
18443 Next_Formal
(Formal
);
18448 -- Ada 83/95 or no formals
18453 end Needs_One_Actual
;
18455 ------------------------
18456 -- New_Copy_List_Tree --
18457 ------------------------
18459 function New_Copy_List_Tree
(List
: List_Id
) return List_Id
is
18464 if List
= No_List
then
18471 while Present
(E
) loop
18472 Append
(New_Copy_Tree
(E
), NL
);
18478 end New_Copy_List_Tree
;
18480 -------------------
18481 -- New_Copy_Tree --
18482 -------------------
18484 -- The following tables play a key role in replicating entities and Itypes.
18485 -- They are intentionally declared at the library level rather than within
18486 -- New_Copy_Tree to avoid elaborating them on each call. This performance
18487 -- optimization saves up to 2% of the entire compilation time spent in the
18488 -- front end. Care should be taken to reset the tables on each new call to
18491 NCT_Table_Max
: constant := 511;
18493 subtype NCT_Table_Index
is Nat
range 0 .. NCT_Table_Max
- 1;
18495 function NCT_Table_Hash
(Key
: Node_Or_Entity_Id
) return NCT_Table_Index
;
18496 -- Obtain the hash value of node or entity Key
18498 --------------------
18499 -- NCT_Table_Hash --
18500 --------------------
18502 function NCT_Table_Hash
(Key
: Node_Or_Entity_Id
) return NCT_Table_Index
is
18504 return NCT_Table_Index
(Key
mod NCT_Table_Max
);
18505 end NCT_Table_Hash
;
18507 ----------------------
18508 -- NCT_New_Entities --
18509 ----------------------
18511 -- The following table maps old entities and Itypes to their corresponding
18512 -- new entities and Itypes.
18516 package NCT_New_Entities
is new Simple_HTable
(
18517 Header_Num
=> NCT_Table_Index
,
18518 Element
=> Entity_Id
,
18519 No_Element
=> Empty
,
18521 Hash
=> NCT_Table_Hash
,
18524 ------------------------
18525 -- NCT_Pending_Itypes --
18526 ------------------------
18528 -- The following table maps old Associated_Node_For_Itype nodes to a set of
18529 -- new itypes. Given a set of old Itypes Aaa, Bbb, and Ccc, where all three
18530 -- have the same Associated_Node_For_Itype Ppp, and their corresponding new
18531 -- Itypes Xxx, Yyy, Zzz, the table contains the following mapping:
18533 -- Ppp -> (Xxx, Yyy, Zzz)
18535 -- The set is expressed as an Elist
18537 package NCT_Pending_Itypes
is new Simple_HTable
(
18538 Header_Num
=> NCT_Table_Index
,
18539 Element
=> Elist_Id
,
18540 No_Element
=> No_Elist
,
18542 Hash
=> NCT_Table_Hash
,
18545 NCT_Tables_In_Use
: Boolean := False;
18546 -- This flag keeps track of whether the two tables NCT_New_Entities and
18547 -- NCT_Pending_Itypes are in use. The flag is part of an optimization
18548 -- where certain operations are not performed if the tables are not in
18549 -- use. This saves up to 8% of the entire compilation time spent in the
18552 -------------------
18553 -- New_Copy_Tree --
18554 -------------------
18556 function New_Copy_Tree
18558 Map
: Elist_Id
:= No_Elist
;
18559 New_Sloc
: Source_Ptr
:= No_Location
;
18560 New_Scope
: Entity_Id
:= Empty
) return Node_Id
18562 -- This routine performs low-level tree manipulations and needs access
18563 -- to the internals of the tree.
18565 use Atree
.Unchecked_Access
;
18566 use Atree_Private_Part
;
18568 EWA_Level
: Nat
:= 0;
18569 -- This counter keeps track of how many N_Expression_With_Actions nodes
18570 -- are encountered during a depth-first traversal of the subtree. These
18571 -- nodes may define new entities in their Actions lists and thus require
18572 -- special processing.
18574 EWA_Inner_Scope_Level
: Nat
:= 0;
18575 -- This counter keeps track of how many scoping constructs appear within
18576 -- an N_Expression_With_Actions node.
18578 procedure Add_New_Entity
(Old_Id
: Entity_Id
; New_Id
: Entity_Id
);
18579 pragma Inline
(Add_New_Entity
);
18580 -- Add an entry in the NCT_New_Entities table which maps key Old_Id to
18581 -- value New_Id. Old_Id is an entity which appears within the Actions
18582 -- list of an N_Expression_With_Actions node, or within an entity map.
18583 -- New_Id is the corresponding new entity generated during Phase 1.
18585 procedure Add_Pending_Itype
(Assoc_Nod
: Node_Id
; Itype
: Entity_Id
);
18586 pragma Inline
(Add_New_Entity
);
18587 -- Add an entry in the NCT_Pending_Itypes which maps key Assoc_Nod to
18588 -- value Itype. Assoc_Nod is the associated node of an itype. Itype is
18591 procedure Build_NCT_Tables
(Entity_Map
: Elist_Id
);
18592 pragma Inline
(Build_NCT_Tables
);
18593 -- Populate tables NCT_New_Entities and NCT_Pending_Itypes with the
18594 -- information supplied in entity map Entity_Map. The format of the
18595 -- entity map must be as follows:
18597 -- Old_Id1, New_Id1, Old_Id2, New_Id2, .., Old_IdN, New_IdN
18599 function Copy_Any_Node_With_Replacement
18600 (N
: Node_Or_Entity_Id
) return Node_Or_Entity_Id
;
18601 pragma Inline
(Copy_Any_Node_With_Replacement
);
18602 -- Replicate entity or node N by invoking one of the following routines:
18604 -- Copy_Node_With_Replacement
18605 -- Corresponding_Entity
18607 function Copy_Elist_With_Replacement
(List
: Elist_Id
) return Elist_Id
;
18608 -- Replicate the elements of entity list List
18610 function Copy_Field_With_Replacement
18612 Old_Par
: Node_Id
:= Empty
;
18613 New_Par
: Node_Id
:= Empty
;
18614 Semantic
: Boolean := False) return Union_Id
;
18615 -- Replicate field Field by invoking one of the following routines:
18617 -- Copy_Elist_With_Replacement
18618 -- Copy_List_With_Replacement
18619 -- Copy_Node_With_Replacement
18620 -- Corresponding_Entity
18622 -- If the field is not an entity list, entity, itype, syntactic list,
18623 -- or node, then the field is returned unchanged. The routine always
18624 -- replicates entities, itypes, and valid syntactic fields. Old_Par is
18625 -- the expected parent of a syntactic field. New_Par is the new parent
18626 -- associated with a replicated syntactic field. Flag Semantic should
18627 -- be set when the input is a semantic field.
18629 function Copy_List_With_Replacement
(List
: List_Id
) return List_Id
;
18630 -- Replicate the elements of syntactic list List
18632 function Copy_Node_With_Replacement
(N
: Node_Id
) return Node_Id
;
18633 -- Replicate node N
18635 function Corresponding_Entity
(Id
: Entity_Id
) return Entity_Id
;
18636 pragma Inline
(Corresponding_Entity
);
18637 -- Return the corresponding new entity of Id generated during Phase 1.
18638 -- If there is no such entity, return Id.
18640 function In_Entity_Map
18642 Entity_Map
: Elist_Id
) return Boolean;
18643 pragma Inline
(In_Entity_Map
);
18644 -- Determine whether entity Id is one of the old ids specified in entity
18645 -- map Entity_Map. The format of the entity map must be as follows:
18647 -- Old_Id1, New_Id1, Old_Id2, New_Id2, .., Old_IdN, New_IdN
18649 procedure Update_CFS_Sloc
(N
: Node_Or_Entity_Id
);
18650 pragma Inline
(Update_CFS_Sloc
);
18651 -- Update the Comes_From_Source and Sloc attributes of node or entity N
18653 procedure Update_First_Real_Statement
18654 (Old_HSS
: Node_Id
;
18655 New_HSS
: Node_Id
);
18656 pragma Inline
(Update_First_Real_Statement
);
18657 -- Update semantic attribute First_Real_Statement of handled sequence of
18658 -- statements New_HSS based on handled sequence of statements Old_HSS.
18660 procedure Update_Named_Associations
18661 (Old_Call
: Node_Id
;
18662 New_Call
: Node_Id
);
18663 pragma Inline
(Update_Named_Associations
);
18664 -- Update semantic chain First/Next_Named_Association of call New_call
18665 -- based on call Old_Call.
18667 procedure Update_New_Entities
(Entity_Map
: Elist_Id
);
18668 pragma Inline
(Update_New_Entities
);
18669 -- Update the semantic attributes of all new entities generated during
18670 -- Phase 1 that do not appear in entity map Entity_Map. The format of
18671 -- the entity map must be as follows:
18673 -- Old_Id1, New_Id1, Old_Id2, New_Id2, .., Old_IdN, New_IdN
18675 procedure Update_Pending_Itypes
18676 (Old_Assoc
: Node_Id
;
18677 New_Assoc
: Node_Id
);
18678 pragma Inline
(Update_Pending_Itypes
);
18679 -- Update semantic attribute Associated_Node_For_Itype to refer to node
18680 -- New_Assoc for all itypes whose associated node is Old_Assoc.
18682 procedure Update_Semantic_Fields
(Id
: Entity_Id
);
18683 pragma Inline
(Update_Semantic_Fields
);
18684 -- Subsidiary to Update_New_Entities. Update semantic fields of entity
18687 procedure Visit_Any_Node
(N
: Node_Or_Entity_Id
);
18688 pragma Inline
(Visit_Any_Node
);
18689 -- Visit entity of node N by invoking one of the following routines:
18695 procedure Visit_Elist
(List
: Elist_Id
);
18696 -- Visit the elements of entity list List
18698 procedure Visit_Entity
(Id
: Entity_Id
);
18699 -- Visit entity Id. This action may create a new entity of Id and save
18700 -- it in table NCT_New_Entities.
18702 procedure Visit_Field
18704 Par_Nod
: Node_Id
:= Empty
;
18705 Semantic
: Boolean := False);
18706 -- Visit field Field by invoking one of the following routines:
18714 -- If the field is not an entity list, entity, itype, syntactic list,
18715 -- or node, then the field is not visited. The routine always visits
18716 -- valid syntactic fields. Par_Nod is the expected parent of the
18717 -- syntactic field. Flag Semantic should be set when the input is a
18720 procedure Visit_Itype
(Itype
: Entity_Id
);
18721 -- Visit itype Itype. This action may create a new entity for Itype and
18722 -- save it in table NCT_New_Entities. In addition, the routine may map
18723 -- the associated node of Itype to the new itype in NCT_Pending_Itypes.
18725 procedure Visit_List
(List
: List_Id
);
18726 -- Visit the elements of syntactic list List
18728 procedure Visit_Node
(N
: Node_Id
);
18731 procedure Visit_Semantic_Fields
(Id
: Entity_Id
);
18732 pragma Inline
(Visit_Semantic_Fields
);
18733 -- Subsidiary to Visit_Entity and Visit_Itype. Visit common semantic
18734 -- fields of entity or itype Id.
18736 --------------------
18737 -- Add_New_Entity --
18738 --------------------
18740 procedure Add_New_Entity
(Old_Id
: Entity_Id
; New_Id
: Entity_Id
) is
18742 pragma Assert
(Present
(Old_Id
));
18743 pragma Assert
(Present
(New_Id
));
18744 pragma Assert
(Nkind
(Old_Id
) in N_Entity
);
18745 pragma Assert
(Nkind
(New_Id
) in N_Entity
);
18747 NCT_Tables_In_Use
:= True;
18749 -- Sanity check the NCT_New_Entities table. No previous mapping with
18750 -- key Old_Id should exist.
18752 pragma Assert
(No
(NCT_New_Entities
.Get
(Old_Id
)));
18754 -- Establish the mapping
18756 -- Old_Id -> New_Id
18758 NCT_New_Entities
.Set
(Old_Id
, New_Id
);
18759 end Add_New_Entity
;
18761 -----------------------
18762 -- Add_Pending_Itype --
18763 -----------------------
18765 procedure Add_Pending_Itype
(Assoc_Nod
: Node_Id
; Itype
: Entity_Id
) is
18769 pragma Assert
(Present
(Assoc_Nod
));
18770 pragma Assert
(Present
(Itype
));
18771 pragma Assert
(Nkind
(Itype
) in N_Entity
);
18772 pragma Assert
(Is_Itype
(Itype
));
18774 NCT_Tables_In_Use
:= True;
18776 -- It is not possible to sanity check the NCT_Pendint_Itypes table
18777 -- directly because a single node may act as the associated node for
18778 -- multiple itypes.
18780 Itypes
:= NCT_Pending_Itypes
.Get
(Assoc_Nod
);
18782 if No
(Itypes
) then
18783 Itypes
:= New_Elmt_List
;
18784 NCT_Pending_Itypes
.Set
(Assoc_Nod
, Itypes
);
18787 -- Establish the mapping
18789 -- Assoc_Nod -> (Itype, ...)
18791 -- Avoid inserting the same itype multiple times. This involves a
18792 -- linear search, however the set of itypes with the same associated
18793 -- node is very small.
18795 Append_Unique_Elmt
(Itype
, Itypes
);
18796 end Add_Pending_Itype
;
18798 ----------------------
18799 -- Build_NCT_Tables --
18800 ----------------------
18802 procedure Build_NCT_Tables
(Entity_Map
: Elist_Id
) is
18804 Old_Id
: Entity_Id
;
18805 New_Id
: Entity_Id
;
18808 -- Nothing to do when there is no entity map
18810 if No
(Entity_Map
) then
18814 Elmt
:= First_Elmt
(Entity_Map
);
18815 while Present
(Elmt
) loop
18817 -- Extract the (Old_Id, New_Id) pair from the entity map
18819 Old_Id
:= Node
(Elmt
);
18822 New_Id
:= Node
(Elmt
);
18825 -- Establish the following mapping within table NCT_New_Entities
18827 -- Old_Id -> New_Id
18829 Add_New_Entity
(Old_Id
, New_Id
);
18831 -- Establish the following mapping within table NCT_Pending_Itypes
18832 -- when the new entity is an itype.
18834 -- Assoc_Nod -> (New_Id, ...)
18836 -- IMPORTANT: the associated node is that of the old itype because
18837 -- the node will be replicated in Phase 2.
18839 if Is_Itype
(Old_Id
) then
18841 (Assoc_Nod
=> Associated_Node_For_Itype
(Old_Id
),
18845 end Build_NCT_Tables
;
18847 ------------------------------------
18848 -- Copy_Any_Node_With_Replacement --
18849 ------------------------------------
18851 function Copy_Any_Node_With_Replacement
18852 (N
: Node_Or_Entity_Id
) return Node_Or_Entity_Id
18855 if Nkind
(N
) in N_Entity
then
18856 return Corresponding_Entity
(N
);
18858 return Copy_Node_With_Replacement
(N
);
18860 end Copy_Any_Node_With_Replacement
;
18862 ---------------------------------
18863 -- Copy_Elist_With_Replacement --
18864 ---------------------------------
18866 function Copy_Elist_With_Replacement
(List
: Elist_Id
) return Elist_Id
is
18871 -- Copy the contents of the old list. Note that the list itself may
18872 -- be empty, in which case the routine returns a new empty list. This
18873 -- avoids sharing lists between subtrees. The element of an entity
18874 -- list could be an entity or a node, hence the invocation of routine
18875 -- Copy_Any_Node_With_Replacement.
18877 if Present
(List
) then
18878 Result
:= New_Elmt_List
;
18880 Elmt
:= First_Elmt
(List
);
18881 while Present
(Elmt
) loop
18883 (Copy_Any_Node_With_Replacement
(Node
(Elmt
)), Result
);
18888 -- Otherwise the list does not exist
18891 Result
:= No_Elist
;
18895 end Copy_Elist_With_Replacement
;
18897 ---------------------------------
18898 -- Copy_Field_With_Replacement --
18899 ---------------------------------
18901 function Copy_Field_With_Replacement
18903 Old_Par
: Node_Id
:= Empty
;
18904 New_Par
: Node_Id
:= Empty
;
18905 Semantic
: Boolean := False) return Union_Id
18908 -- The field is empty
18910 if Field
= Union_Id
(Empty
) then
18913 -- The field is an entity/itype/node
18915 elsif Field
in Node_Range
then
18917 Old_N
: constant Node_Id
:= Node_Id
(Field
);
18918 Syntactic
: constant Boolean := Parent
(Old_N
) = Old_Par
;
18923 -- The field is an entity/itype
18925 if Nkind
(Old_N
) in N_Entity
then
18927 -- An entity/itype is always replicated
18929 New_N
:= Corresponding_Entity
(Old_N
);
18931 -- Update the parent pointer when the entity is a syntactic
18932 -- field. Note that itypes do not have parent pointers.
18934 if Syntactic
and then New_N
/= Old_N
then
18935 Set_Parent
(New_N
, New_Par
);
18938 -- The field is a node
18941 -- A node is replicated when it is either a syntactic field
18942 -- or when the caller treats it as a semantic attribute.
18944 if Syntactic
or else Semantic
then
18945 New_N
:= Copy_Node_With_Replacement
(Old_N
);
18947 -- Update the parent pointer when the node is a syntactic
18950 if Syntactic
and then New_N
/= Old_N
then
18951 Set_Parent
(New_N
, New_Par
);
18954 -- Otherwise the node is returned unchanged
18961 return Union_Id
(New_N
);
18964 -- The field is an entity list
18966 elsif Field
in Elist_Range
then
18967 return Union_Id
(Copy_Elist_With_Replacement
(Elist_Id
(Field
)));
18969 -- The field is a syntactic list
18971 elsif Field
in List_Range
then
18973 Old_List
: constant List_Id
:= List_Id
(Field
);
18974 Syntactic
: constant Boolean := Parent
(Old_List
) = Old_Par
;
18976 New_List
: List_Id
;
18979 -- A list is replicated when it is either a syntactic field or
18980 -- when the caller treats it as a semantic attribute.
18982 if Syntactic
or else Semantic
then
18983 New_List
:= Copy_List_With_Replacement
(Old_List
);
18985 -- Update the parent pointer when the list is a syntactic
18988 if Syntactic
and then New_List
/= Old_List
then
18989 Set_Parent
(New_List
, New_Par
);
18992 -- Otherwise the list is returned unchanged
18995 New_List
:= Old_List
;
18998 return Union_Id
(New_List
);
19001 -- Otherwise the field denotes an attribute that does not need to be
19002 -- replicated (Chars, literals, etc).
19007 end Copy_Field_With_Replacement
;
19009 --------------------------------
19010 -- Copy_List_With_Replacement --
19011 --------------------------------
19013 function Copy_List_With_Replacement
(List
: List_Id
) return List_Id
is
19018 -- Copy the contents of the old list. Note that the list itself may
19019 -- be empty, in which case the routine returns a new empty list. This
19020 -- avoids sharing lists between subtrees. The element of a syntactic
19021 -- list is always a node, never an entity or itype, hence the call to
19022 -- routine Copy_Node_With_Replacement.
19024 if Present
(List
) then
19025 Result
:= New_List
;
19027 Elmt
:= First
(List
);
19028 while Present
(Elmt
) loop
19029 Append
(Copy_Node_With_Replacement
(Elmt
), Result
);
19034 -- Otherwise the list does not exist
19041 end Copy_List_With_Replacement
;
19043 --------------------------------
19044 -- Copy_Node_With_Replacement --
19045 --------------------------------
19047 function Copy_Node_With_Replacement
(N
: Node_Id
) return Node_Id
is
19051 -- Assume that the node must be returned unchanged
19055 if N
> Empty_Or_Error
then
19056 pragma Assert
(Nkind
(N
) not in N_Entity
);
19058 Result
:= New_Copy
(N
);
19060 Set_Field1
(Result
,
19061 Copy_Field_With_Replacement
19062 (Field
=> Field1
(Result
),
19064 New_Par
=> Result
));
19066 Set_Field2
(Result
,
19067 Copy_Field_With_Replacement
19068 (Field
=> Field2
(Result
),
19070 New_Par
=> Result
));
19072 Set_Field3
(Result
,
19073 Copy_Field_With_Replacement
19074 (Field
=> Field3
(Result
),
19076 New_Par
=> Result
));
19078 Set_Field4
(Result
,
19079 Copy_Field_With_Replacement
19080 (Field
=> Field4
(Result
),
19082 New_Par
=> Result
));
19084 Set_Field5
(Result
,
19085 Copy_Field_With_Replacement
19086 (Field
=> Field5
(Result
),
19088 New_Par
=> Result
));
19090 -- Update the Comes_From_Source and Sloc attributes of the node
19091 -- in case the caller has supplied new values.
19093 Update_CFS_Sloc
(Result
);
19095 -- Update the Associated_Node_For_Itype attribute of all itypes
19096 -- created during Phase 1 whose associated node is N. As a result
19097 -- the Associated_Node_For_Itype refers to the replicated node.
19098 -- No action needs to be taken when the Associated_Node_For_Itype
19099 -- refers to an entity because this was already handled during
19100 -- Phase 1, in Visit_Itype.
19102 Update_Pending_Itypes
19104 New_Assoc
=> Result
);
19106 -- Update the First/Next_Named_Association chain for a replicated
19109 if Nkind_In
(N
, N_Entry_Call_Statement
,
19111 N_Procedure_Call_Statement
)
19113 Update_Named_Associations
19115 New_Call
=> Result
);
19117 -- Update the Renamed_Object attribute of a replicated object
19120 elsif Nkind
(N
) = N_Object_Renaming_Declaration
then
19121 Set_Renamed_Object
(Defining_Entity
(Result
), Name
(Result
));
19123 -- Update the First_Real_Statement attribute of a replicated
19124 -- handled sequence of statements.
19126 elsif Nkind
(N
) = N_Handled_Sequence_Of_Statements
then
19127 Update_First_Real_Statement
19129 New_HSS
=> Result
);
19134 end Copy_Node_With_Replacement
;
19136 --------------------------
19137 -- Corresponding_Entity --
19138 --------------------------
19140 function Corresponding_Entity
(Id
: Entity_Id
) return Entity_Id
is
19141 New_Id
: Entity_Id
;
19142 Result
: Entity_Id
;
19145 -- Assume that the entity must be returned unchanged
19149 if Id
> Empty_Or_Error
then
19150 pragma Assert
(Nkind
(Id
) in N_Entity
);
19152 -- Determine whether the entity has a corresponding new entity
19153 -- generated during Phase 1 and if it does, use it.
19155 if NCT_Tables_In_Use
then
19156 New_Id
:= NCT_New_Entities
.Get
(Id
);
19158 if Present
(New_Id
) then
19165 end Corresponding_Entity
;
19167 -------------------
19168 -- In_Entity_Map --
19169 -------------------
19171 function In_Entity_Map
19173 Entity_Map
: Elist_Id
) return Boolean
19176 Old_Id
: Entity_Id
;
19179 -- The entity map contains pairs (Old_Id, New_Id). The advancement
19180 -- step always skips the New_Id portion of the pair.
19182 if Present
(Entity_Map
) then
19183 Elmt
:= First_Elmt
(Entity_Map
);
19184 while Present
(Elmt
) loop
19185 Old_Id
:= Node
(Elmt
);
19187 if Old_Id
= Id
then
19199 ---------------------
19200 -- Update_CFS_Sloc --
19201 ---------------------
19203 procedure Update_CFS_Sloc
(N
: Node_Or_Entity_Id
) is
19205 -- A new source location defaults the Comes_From_Source attribute
19207 if New_Sloc
/= No_Location
then
19208 Set_Comes_From_Source
(N
, Default_Node
.Comes_From_Source
);
19209 Set_Sloc
(N
, New_Sloc
);
19211 end Update_CFS_Sloc
;
19213 ---------------------------------
19214 -- Update_First_Real_Statement --
19215 ---------------------------------
19217 procedure Update_First_Real_Statement
19218 (Old_HSS
: Node_Id
;
19221 Old_First_Stmt
: constant Node_Id
:= First_Real_Statement
(Old_HSS
);
19223 New_Stmt
: Node_Id
;
19224 Old_Stmt
: Node_Id
;
19227 -- Recreate the First_Real_Statement attribute of a handled sequence
19228 -- of statements by traversing the statement lists of both sequences
19231 if Present
(Old_First_Stmt
) then
19232 New_Stmt
:= First
(Statements
(New_HSS
));
19233 Old_Stmt
:= First
(Statements
(Old_HSS
));
19234 while Present
(Old_Stmt
) and then Old_Stmt
/= Old_First_Stmt
loop
19239 pragma Assert
(Present
(New_Stmt
));
19240 pragma Assert
(Present
(Old_Stmt
));
19242 Set_First_Real_Statement
(New_HSS
, New_Stmt
);
19244 end Update_First_Real_Statement
;
19246 -------------------------------
19247 -- Update_Named_Associations --
19248 -------------------------------
19250 procedure Update_Named_Associations
19251 (Old_Call
: Node_Id
;
19252 New_Call
: Node_Id
)
19255 New_Next
: Node_Id
;
19257 Old_Next
: Node_Id
;
19260 -- Recreate the First/Next_Named_Actual chain of a call by traversing
19261 -- the chains of both the old and new calls in parallel.
19263 New_Act
:= First
(Parameter_Associations
(New_Call
));
19264 Old_Act
:= First
(Parameter_Associations
(Old_Call
));
19265 while Present
(Old_Act
) loop
19266 if Nkind
(Old_Act
) = N_Parameter_Association
19267 and then Present
(Next_Named_Actual
(Old_Act
))
19269 if First_Named_Actual
(Old_Call
) =
19270 Explicit_Actual_Parameter
(Old_Act
)
19272 Set_First_Named_Actual
(New_Call
,
19273 Explicit_Actual_Parameter
(New_Act
));
19276 -- Scan the actual parameter list to find the next suitable
19277 -- named actual. Note that the list may be out of order.
19279 New_Next
:= First
(Parameter_Associations
(New_Call
));
19280 Old_Next
:= First
(Parameter_Associations
(Old_Call
));
19281 while Nkind
(Old_Next
) /= N_Parameter_Association
19282 or else Explicit_Actual_Parameter
(Old_Next
) /=
19283 Next_Named_Actual
(Old_Act
)
19289 Set_Next_Named_Actual
(New_Act
,
19290 Explicit_Actual_Parameter
(New_Next
));
19296 end Update_Named_Associations
;
19298 -------------------------
19299 -- Update_New_Entities --
19300 -------------------------
19302 procedure Update_New_Entities
(Entity_Map
: Elist_Id
) is
19303 New_Id
: Entity_Id
:= Empty
;
19304 Old_Id
: Entity_Id
:= Empty
;
19307 if NCT_Tables_In_Use
then
19308 NCT_New_Entities
.Get_First
(Old_Id
, New_Id
);
19310 -- Update the semantic fields of all new entities created during
19311 -- Phase 1 which were not supplied via an entity map.
19312 -- ??? Is there a better way of distinguishing those?
19314 while Present
(Old_Id
) and then Present
(New_Id
) loop
19315 if not (Present
(Entity_Map
)
19316 and then In_Entity_Map
(Old_Id
, Entity_Map
))
19318 Update_Semantic_Fields
(New_Id
);
19321 NCT_New_Entities
.Get_Next
(Old_Id
, New_Id
);
19324 end Update_New_Entities
;
19326 ---------------------------
19327 -- Update_Pending_Itypes --
19328 ---------------------------
19330 procedure Update_Pending_Itypes
19331 (Old_Assoc
: Node_Id
;
19332 New_Assoc
: Node_Id
)
19338 if NCT_Tables_In_Use
then
19339 Itypes
:= NCT_Pending_Itypes
.Get
(Old_Assoc
);
19341 -- Update the Associated_Node_For_Itype attribute for all itypes
19342 -- which originally refer to Old_Assoc to designate New_Assoc.
19344 if Present
(Itypes
) then
19345 Item
:= First_Elmt
(Itypes
);
19346 while Present
(Item
) loop
19347 Set_Associated_Node_For_Itype
(Node
(Item
), New_Assoc
);
19353 end Update_Pending_Itypes
;
19355 ----------------------------
19356 -- Update_Semantic_Fields --
19357 ----------------------------
19359 procedure Update_Semantic_Fields
(Id
: Entity_Id
) is
19361 -- Discriminant_Constraint
19363 if Has_Discriminants
(Base_Type
(Id
)) then
19364 Set_Discriminant_Constraint
(Id
, Elist_Id
(
19365 Copy_Field_With_Replacement
19366 (Field
=> Union_Id
(Discriminant_Constraint
(Id
)),
19367 Semantic
=> True)));
19372 Set_Etype
(Id
, Node_Id
(
19373 Copy_Field_With_Replacement
19374 (Field
=> Union_Id
(Etype
(Id
)),
19375 Semantic
=> True)));
19378 -- Packed_Array_Impl_Type
19380 if Is_Array_Type
(Id
) then
19381 if Present
(First_Index
(Id
)) then
19382 Set_First_Index
(Id
, First
(List_Id
(
19383 Copy_Field_With_Replacement
19384 (Field
=> Union_Id
(List_Containing
(First_Index
(Id
))),
19385 Semantic
=> True))));
19388 if Is_Packed
(Id
) then
19389 Set_Packed_Array_Impl_Type
(Id
, Node_Id
(
19390 Copy_Field_With_Replacement
19391 (Field
=> Union_Id
(Packed_Array_Impl_Type
(Id
)),
19392 Semantic
=> True)));
19398 Set_Next_Entity
(Id
, Node_Id
(
19399 Copy_Field_With_Replacement
19400 (Field
=> Union_Id
(Next_Entity
(Id
)),
19401 Semantic
=> True)));
19405 if Is_Discrete_Type
(Id
) then
19406 Set_Scalar_Range
(Id
, Node_Id
(
19407 Copy_Field_With_Replacement
19408 (Field
=> Union_Id
(Scalar_Range
(Id
)),
19409 Semantic
=> True)));
19414 -- Update the scope when the caller specified an explicit one
19416 if Present
(New_Scope
) then
19417 Set_Scope
(Id
, New_Scope
);
19419 Set_Scope
(Id
, Node_Id
(
19420 Copy_Field_With_Replacement
19421 (Field
=> Union_Id
(Scope
(Id
)),
19422 Semantic
=> True)));
19424 end Update_Semantic_Fields
;
19426 --------------------
19427 -- Visit_Any_Node --
19428 --------------------
19430 procedure Visit_Any_Node
(N
: Node_Or_Entity_Id
) is
19432 if Nkind
(N
) in N_Entity
then
19433 if Is_Itype
(N
) then
19441 end Visit_Any_Node
;
19447 procedure Visit_Elist
(List
: Elist_Id
) is
19451 -- The element of an entity list could be an entity, itype, or a
19452 -- node, hence the call to Visit_Any_Node.
19454 if Present
(List
) then
19455 Elmt
:= First_Elmt
(List
);
19456 while Present
(Elmt
) loop
19457 Visit_Any_Node
(Node
(Elmt
));
19468 procedure Visit_Entity
(Id
: Entity_Id
) is
19469 New_Id
: Entity_Id
;
19472 pragma Assert
(Nkind
(Id
) in N_Entity
);
19473 pragma Assert
(not Is_Itype
(Id
));
19475 -- Nothing to do if the entity is not defined in the Actions list of
19476 -- an N_Expression_With_Actions node.
19478 if EWA_Level
= 0 then
19481 -- Nothing to do if the entity is defined within a scoping construct
19482 -- of an N_Expression_With_Actions node.
19484 elsif EWA_Inner_Scope_Level
> 0 then
19487 -- Nothing to do if the entity is not an object or a type. Relaxing
19488 -- this restriction leads to a performance penalty.
19490 elsif not Ekind_In
(Id
, E_Constant
, E_Variable
)
19491 and then not Is_Type
(Id
)
19495 -- Nothing to do if the entity was already visited
19497 elsif NCT_Tables_In_Use
19498 and then Present
(NCT_New_Entities
.Get
(Id
))
19502 -- Nothing to do if the declaration node of the entity is not within
19503 -- the subtree being replicated.
19505 elsif not In_Subtree
19506 (N
=> Declaration_Node
(Id
),
19512 -- Create a new entity by directly copying the old entity. This
19513 -- action causes all attributes of the old entity to be inherited.
19515 New_Id
:= New_Copy
(Id
);
19517 -- Create a new name for the new entity because the back end needs
19518 -- distinct names for debugging purposes.
19520 Set_Chars
(New_Id
, New_Internal_Name
('T'));
19522 -- Update the Comes_From_Source and Sloc attributes of the entity in
19523 -- case the caller has supplied new values.
19525 Update_CFS_Sloc
(New_Id
);
19527 -- Establish the following mapping within table NCT_New_Entities:
19531 Add_New_Entity
(Id
, New_Id
);
19533 -- Deal with the semantic fields of entities. The fields are visited
19534 -- because they may mention entities which reside within the subtree
19537 Visit_Semantic_Fields
(Id
);
19544 procedure Visit_Field
19546 Par_Nod
: Node_Id
:= Empty
;
19547 Semantic
: Boolean := False)
19550 -- The field is empty
19552 if Field
= Union_Id
(Empty
) then
19555 -- The field is an entity/itype/node
19557 elsif Field
in Node_Range
then
19559 N
: constant Node_Id
:= Node_Id
(Field
);
19562 -- The field is an entity/itype
19564 if Nkind
(N
) in N_Entity
then
19566 -- Itypes are always visited
19568 if Is_Itype
(N
) then
19571 -- An entity is visited when it is either a syntactic field
19572 -- or when the caller treats it as a semantic attribute.
19574 elsif Parent
(N
) = Par_Nod
or else Semantic
then
19578 -- The field is a node
19581 -- A node is visited when it is either a syntactic field or
19582 -- when the caller treats it as a semantic attribute.
19584 if Parent
(N
) = Par_Nod
or else Semantic
then
19590 -- The field is an entity list
19592 elsif Field
in Elist_Range
then
19593 Visit_Elist
(Elist_Id
(Field
));
19595 -- The field is a syntax list
19597 elsif Field
in List_Range
then
19599 List
: constant List_Id
:= List_Id
(Field
);
19602 -- A syntax list is visited when it is either a syntactic field
19603 -- or when the caller treats it as a semantic attribute.
19605 if Parent
(List
) = Par_Nod
or else Semantic
then
19610 -- Otherwise the field denotes information which does not need to be
19611 -- visited (chars, literals, etc.).
19622 procedure Visit_Itype
(Itype
: Entity_Id
) is
19623 New_Assoc
: Node_Id
;
19624 New_Itype
: Entity_Id
;
19625 Old_Assoc
: Node_Id
;
19628 pragma Assert
(Nkind
(Itype
) in N_Entity
);
19629 pragma Assert
(Is_Itype
(Itype
));
19631 -- Itypes that describe the designated type of access to subprograms
19632 -- have the structure of subprogram declarations, with signatures,
19633 -- etc. Either we duplicate the signatures completely, or choose to
19634 -- share such itypes, which is fine because their elaboration will
19635 -- have no side effects.
19637 if Ekind
(Itype
) = E_Subprogram_Type
then
19640 -- Nothing to do if the itype was already visited
19642 elsif NCT_Tables_In_Use
19643 and then Present
(NCT_New_Entities
.Get
(Itype
))
19647 -- Nothing to do if the associated node of the itype is not within
19648 -- the subtree being replicated.
19650 elsif not In_Subtree
19651 (N
=> Associated_Node_For_Itype
(Itype
),
19657 -- Create a new itype by directly copying the old itype. This action
19658 -- causes all attributes of the old itype to be inherited.
19660 New_Itype
:= New_Copy
(Itype
);
19662 -- Create a new name for the new itype because the back end requires
19663 -- distinct names for debugging purposes.
19665 Set_Chars
(New_Itype
, New_Internal_Name
('T'));
19667 -- Update the Comes_From_Source and Sloc attributes of the itype in
19668 -- case the caller has supplied new values.
19670 Update_CFS_Sloc
(New_Itype
);
19672 -- Establish the following mapping within table NCT_New_Entities:
19674 -- Itype -> New_Itype
19676 Add_New_Entity
(Itype
, New_Itype
);
19678 -- The new itype must be unfrozen because the resulting subtree may
19679 -- be inserted anywhere and cause an earlier or later freezing.
19681 if Present
(Freeze_Node
(New_Itype
)) then
19682 Set_Freeze_Node
(New_Itype
, Empty
);
19683 Set_Is_Frozen
(New_Itype
, False);
19686 -- If a record subtype is simply copied, the entity list will be
19687 -- shared. Thus cloned_Subtype must be set to indicate the sharing.
19688 -- ??? What does this do?
19690 if Ekind_In
(Itype
, E_Class_Wide_Subtype
, E_Record_Subtype
) then
19691 Set_Cloned_Subtype
(New_Itype
, Itype
);
19694 -- The associated node may denote an entity, in which case it may
19695 -- already have a new corresponding entity created during a prior
19696 -- call to Visit_Entity or Visit_Itype for the same subtree.
19699 -- Old_Assoc ---------> New_Assoc
19701 -- Created by Visit_Itype
19702 -- Itype -------------> New_Itype
19703 -- ANFI = Old_Assoc ANFI = Old_Assoc < must be updated
19705 -- In the example above, Old_Assoc is an arbitrary entity that was
19706 -- already visited for the same subtree and has a corresponding new
19707 -- entity New_Assoc. Old_Assoc was inherited by New_Itype by virtue
19708 -- of copying entities, however it must be updated to New_Assoc.
19710 Old_Assoc
:= Associated_Node_For_Itype
(Itype
);
19712 if Nkind
(Old_Assoc
) in N_Entity
then
19713 if NCT_Tables_In_Use
then
19714 New_Assoc
:= NCT_New_Entities
.Get
(Old_Assoc
);
19716 if Present
(New_Assoc
) then
19717 Set_Associated_Node_For_Itype
(New_Itype
, New_Assoc
);
19721 -- Otherwise the associated node denotes a node. Postpone the update
19722 -- until Phase 2 when the node is replicated. Establish the following
19723 -- mapping within table NCT_Pending_Itypes:
19725 -- Old_Assoc -> (New_Type, ...)
19728 Add_Pending_Itype
(Old_Assoc
, New_Itype
);
19731 -- Deal with the semantic fields of itypes. The fields are visited
19732 -- because they may mention entities that reside within the subtree
19735 Visit_Semantic_Fields
(Itype
);
19742 procedure Visit_List
(List
: List_Id
) is
19746 -- Note that the element of a syntactic list is always a node, never
19747 -- an entity or itype, hence the call to Visit_Node.
19749 if Present
(List
) then
19750 Elmt
:= First
(List
);
19751 while Present
(Elmt
) loop
19763 procedure Visit_Node
(N
: Node_Or_Entity_Id
) is
19765 pragma Assert
(Nkind
(N
) not in N_Entity
);
19767 if Nkind
(N
) = N_Expression_With_Actions
then
19768 EWA_Level
:= EWA_Level
+ 1;
19770 elsif EWA_Level
> 0
19771 and then Nkind_In
(N
, N_Block_Statement
,
19773 N_Subprogram_Declaration
)
19775 EWA_Inner_Scope_Level
:= EWA_Inner_Scope_Level
+ 1;
19779 (Field
=> Field1
(N
),
19783 (Field
=> Field2
(N
),
19787 (Field
=> Field3
(N
),
19791 (Field
=> Field4
(N
),
19795 (Field
=> Field5
(N
),
19799 and then Nkind_In
(N
, N_Block_Statement
,
19801 N_Subprogram_Declaration
)
19803 EWA_Inner_Scope_Level
:= EWA_Inner_Scope_Level
- 1;
19805 elsif Nkind
(N
) = N_Expression_With_Actions
then
19806 EWA_Level
:= EWA_Level
- 1;
19810 ---------------------------
19811 -- Visit_Semantic_Fields --
19812 ---------------------------
19814 procedure Visit_Semantic_Fields
(Id
: Entity_Id
) is
19816 pragma Assert
(Nkind
(Id
) in N_Entity
);
19818 -- Discriminant_Constraint
19820 if Has_Discriminants
(Base_Type
(Id
)) then
19822 (Field
=> Union_Id
(Discriminant_Constraint
(Id
)),
19829 (Field
=> Union_Id
(Etype
(Id
)),
19833 -- Packed_Array_Impl_Type
19835 if Is_Array_Type
(Id
) then
19836 if Present
(First_Index
(Id
)) then
19838 (Field
=> Union_Id
(List_Containing
(First_Index
(Id
))),
19842 if Is_Packed
(Id
) then
19844 (Field
=> Union_Id
(Packed_Array_Impl_Type
(Id
)),
19851 if Is_Discrete_Type
(Id
) then
19853 (Field
=> Union_Id
(Scalar_Range
(Id
)),
19856 end Visit_Semantic_Fields
;
19858 -- Start of processing for New_Copy_Tree
19861 -- Routine New_Copy_Tree performs a deep copy of a subtree by creating
19862 -- shallow copies for each node within, and then updating the child and
19863 -- parent pointers accordingly. This process is straightforward, however
19864 -- the routine must deal with the following complications:
19866 -- * Entities defined within N_Expression_With_Actions nodes must be
19867 -- replicated rather than shared to avoid introducing two identical
19868 -- symbols within the same scope. Note that no other expression can
19869 -- currently define entities.
19872 -- Source_Low : ...;
19873 -- Source_High : ...;
19875 -- <reference to Source_Low>
19876 -- <reference to Source_High>
19879 -- New_Copy_Tree handles this case by first creating new entities
19880 -- and then updating all existing references to point to these new
19887 -- <reference to New_Low>
19888 -- <reference to New_High>
19891 -- * Itypes defined within the subtree must be replicated to avoid any
19892 -- dependencies on invalid or inaccessible data.
19894 -- subtype Source_Itype is ... range Source_Low .. Source_High;
19896 -- New_Copy_Tree handles this case by first creating a new itype in
19897 -- the same fashion as entities, and then updating various relevant
19900 -- subtype New_Itype is ... range New_Low .. New_High;
19902 -- * The Associated_Node_For_Itype field of itypes must be updated to
19903 -- reference the proper replicated entity or node.
19905 -- * Semantic fields of entities such as Etype and Scope must be
19906 -- updated to reference the proper replicated entities.
19908 -- * Semantic fields of nodes such as First_Real_Statement must be
19909 -- updated to reference the proper replicated nodes.
19911 -- To meet all these demands, routine New_Copy_Tree is split into two
19914 -- Phase 1 traverses the tree in order to locate entities and itypes
19915 -- defined within the subtree. New entities are generated and saved in
19916 -- table NCT_New_Entities. The semantic fields of all new entities and
19917 -- itypes are then updated accordingly.
19919 -- Phase 2 traverses the tree in order to replicate each node. Various
19920 -- semantic fields of nodes and entities are updated accordingly.
19922 -- Preparatory phase. Clear the contents of tables NCT_New_Entities and
19923 -- NCT_Pending_Itypes in case a previous call to New_Copy_Tree left some
19926 if NCT_Tables_In_Use
then
19927 NCT_Tables_In_Use
:= False;
19929 NCT_New_Entities
.Reset
;
19930 NCT_Pending_Itypes
.Reset
;
19933 -- Populate tables NCT_New_Entities and NCT_Pending_Itypes with data
19934 -- supplied by a linear entity map. The tables offer faster access to
19937 Build_NCT_Tables
(Map
);
19939 -- Execute Phase 1. Traverse the subtree and generate new entities for
19940 -- the following cases:
19942 -- * An entity defined within an N_Expression_With_Actions node
19944 -- * An itype referenced within the subtree where the associated node
19945 -- is also in the subtree.
19947 -- All new entities are accessible via table NCT_New_Entities, which
19948 -- contains mappings of the form:
19950 -- Old_Entity -> New_Entity
19951 -- Old_Itype -> New_Itype
19953 -- In addition, the associated nodes of all new itypes are mapped in
19954 -- table NCT_Pending_Itypes:
19956 -- Assoc_Nod -> (New_Itype1, New_Itype2, .., New_ItypeN)
19958 Visit_Any_Node
(Source
);
19960 -- Update the semantic attributes of all new entities generated during
19961 -- Phase 1 before starting Phase 2. The updates could be performed in
19962 -- routine Corresponding_Entity, however this may cause the same entity
19963 -- to be updated multiple times, effectively generating useless nodes.
19964 -- Keeping the updates separates from Phase 2 ensures that only one set
19965 -- of attributes is generated for an entity at any one time.
19967 Update_New_Entities
(Map
);
19969 -- Execute Phase 2. Replicate the source subtree one node at a time.
19970 -- The following transformations take place:
19972 -- * References to entities and itypes are updated to refer to the
19973 -- new entities and itypes generated during Phase 1.
19975 -- * All Associated_Node_For_Itype attributes of itypes are updated
19976 -- to refer to the new replicated Associated_Node_For_Itype.
19978 return Copy_Node_With_Replacement
(Source
);
19981 -------------------------
19982 -- New_External_Entity --
19983 -------------------------
19985 function New_External_Entity
19986 (Kind
: Entity_Kind
;
19987 Scope_Id
: Entity_Id
;
19988 Sloc_Value
: Source_Ptr
;
19989 Related_Id
: Entity_Id
;
19990 Suffix
: Character;
19991 Suffix_Index
: Nat
:= 0;
19992 Prefix
: Character := ' ') return Entity_Id
19994 N
: constant Entity_Id
:=
19995 Make_Defining_Identifier
(Sloc_Value
,
19997 (Chars
(Related_Id
), Suffix
, Suffix_Index
, Prefix
));
20000 Set_Ekind
(N
, Kind
);
20001 Set_Is_Internal
(N
, True);
20002 Append_Entity
(N
, Scope_Id
);
20003 Set_Public_Status
(N
);
20005 if Kind
in Type_Kind
then
20006 Init_Size_Align
(N
);
20010 end New_External_Entity
;
20012 -------------------------
20013 -- New_Internal_Entity --
20014 -------------------------
20016 function New_Internal_Entity
20017 (Kind
: Entity_Kind
;
20018 Scope_Id
: Entity_Id
;
20019 Sloc_Value
: Source_Ptr
;
20020 Id_Char
: Character) return Entity_Id
20022 N
: constant Entity_Id
:= Make_Temporary
(Sloc_Value
, Id_Char
);
20025 Set_Ekind
(N
, Kind
);
20026 Set_Is_Internal
(N
, True);
20027 Append_Entity
(N
, Scope_Id
);
20029 if Kind
in Type_Kind
then
20030 Init_Size_Align
(N
);
20034 end New_Internal_Entity
;
20040 function Next_Actual
(Actual_Id
: Node_Id
) return Node_Id
is
20044 -- If we are pointing at a positional parameter, it is a member of a
20045 -- node list (the list of parameters), and the next parameter is the
20046 -- next node on the list, unless we hit a parameter association, then
20047 -- we shift to using the chain whose head is the First_Named_Actual in
20048 -- the parent, and then is threaded using the Next_Named_Actual of the
20049 -- Parameter_Association. All this fiddling is because the original node
20050 -- list is in the textual call order, and what we need is the
20051 -- declaration order.
20053 if Is_List_Member
(Actual_Id
) then
20054 N
:= Next
(Actual_Id
);
20056 if Nkind
(N
) = N_Parameter_Association
then
20058 -- In case of a build-in-place call, the call will no longer be a
20059 -- call; it will have been rewritten.
20061 if Nkind_In
(Parent
(Actual_Id
), N_Entry_Call_Statement
,
20063 N_Procedure_Call_Statement
)
20065 return First_Named_Actual
(Parent
(Actual_Id
));
20074 return Next_Named_Actual
(Parent
(Actual_Id
));
20078 procedure Next_Actual
(Actual_Id
: in out Node_Id
) is
20080 Actual_Id
:= Next_Actual
(Actual_Id
);
20087 function Next_Global
(Node
: Node_Id
) return Node_Id
is
20089 -- The global item may either be in a list, or by itself, in which case
20090 -- there is no next global item with the same mode.
20092 if Is_List_Member
(Node
) then
20093 return Next
(Node
);
20099 procedure Next_Global
(Node
: in out Node_Id
) is
20101 Node
:= Next_Global
(Node
);
20104 ----------------------------------
20105 -- New_Requires_Transient_Scope --
20106 ----------------------------------
20108 function New_Requires_Transient_Scope
(Id
: Entity_Id
) return Boolean is
20109 function Caller_Known_Size_Record
(Typ
: Entity_Id
) return Boolean;
20110 -- This is called for untagged records and protected types, with
20111 -- nondefaulted discriminants. Returns True if the size of function
20112 -- results is known at the call site, False otherwise. Returns False
20113 -- if there is a variant part that depends on the discriminants of
20114 -- this type, or if there is an array constrained by the discriminants
20115 -- of this type. ???Currently, this is overly conservative (the array
20116 -- could be nested inside some other record that is constrained by
20117 -- nondiscriminants). That is, the recursive calls are too conservative.
20119 function Large_Max_Size_Mutable
(Typ
: Entity_Id
) return Boolean;
20120 -- Returns True if Typ is a nonlimited record with defaulted
20121 -- discriminants whose max size makes it unsuitable for allocating on
20122 -- the primary stack.
20124 ------------------------------
20125 -- Caller_Known_Size_Record --
20126 ------------------------------
20128 function Caller_Known_Size_Record
(Typ
: Entity_Id
) return Boolean is
20129 pragma Assert
(Typ
= Underlying_Type
(Typ
));
20132 if Has_Variant_Part
(Typ
) and then not Is_Definite_Subtype
(Typ
) then
20140 Comp
:= First_Entity
(Typ
);
20141 while Present
(Comp
) loop
20143 -- Only look at E_Component entities. No need to look at
20144 -- E_Discriminant entities, and we must ignore internal
20145 -- subtypes generated for constrained components.
20147 if Ekind
(Comp
) = E_Component
then
20149 Comp_Type
: constant Entity_Id
:=
20150 Underlying_Type
(Etype
(Comp
));
20153 if Is_Record_Type
(Comp_Type
)
20155 Is_Protected_Type
(Comp_Type
)
20157 if not Caller_Known_Size_Record
(Comp_Type
) then
20161 elsif Is_Array_Type
(Comp_Type
) then
20162 if Size_Depends_On_Discriminant
(Comp_Type
) then
20169 Next_Entity
(Comp
);
20174 end Caller_Known_Size_Record
;
20176 ------------------------------
20177 -- Large_Max_Size_Mutable --
20178 ------------------------------
20180 function Large_Max_Size_Mutable
(Typ
: Entity_Id
) return Boolean is
20181 pragma Assert
(Typ
= Underlying_Type
(Typ
));
20183 function Is_Large_Discrete_Type
(T
: Entity_Id
) return Boolean;
20184 -- Returns true if the discrete type T has a large range
20186 ----------------------------
20187 -- Is_Large_Discrete_Type --
20188 ----------------------------
20190 function Is_Large_Discrete_Type
(T
: Entity_Id
) return Boolean is
20191 Threshold
: constant Int
:= 16;
20192 -- Arbitrary threshold above which we consider it "large". We want
20193 -- a fairly large threshold, because these large types really
20194 -- shouldn't have default discriminants in the first place, in
20198 return UI_To_Int
(RM_Size
(T
)) > Threshold
;
20199 end Is_Large_Discrete_Type
;
20201 -- Start of processing for Large_Max_Size_Mutable
20204 if Is_Record_Type
(Typ
)
20205 and then not Is_Limited_View
(Typ
)
20206 and then Has_Defaulted_Discriminants
(Typ
)
20208 -- Loop through the components, looking for an array whose upper
20209 -- bound(s) depends on discriminants, where both the subtype of
20210 -- the discriminant and the index subtype are too large.
20216 Comp
:= First_Entity
(Typ
);
20217 while Present
(Comp
) loop
20218 if Ekind
(Comp
) = E_Component
then
20220 Comp_Type
: constant Entity_Id
:=
20221 Underlying_Type
(Etype
(Comp
));
20228 if Is_Array_Type
(Comp_Type
) then
20229 Indx
:= First_Index
(Comp_Type
);
20231 while Present
(Indx
) loop
20232 Ityp
:= Etype
(Indx
);
20233 Hi
:= Type_High_Bound
(Ityp
);
20235 if Nkind
(Hi
) = N_Identifier
20236 and then Ekind
(Entity
(Hi
)) = E_Discriminant
20237 and then Is_Large_Discrete_Type
(Ityp
)
20238 and then Is_Large_Discrete_Type
20239 (Etype
(Entity
(Hi
)))
20250 Next_Entity
(Comp
);
20256 end Large_Max_Size_Mutable
;
20258 -- Local declarations
20260 Typ
: constant Entity_Id
:= Underlying_Type
(Id
);
20262 -- Start of processing for New_Requires_Transient_Scope
20265 -- This is a private type which is not completed yet. This can only
20266 -- happen in a default expression (of a formal parameter or of a
20267 -- record component). Do not expand transient scope in this case.
20272 -- Do not expand transient scope for non-existent procedure return or
20273 -- string literal types.
20275 elsif Typ
= Standard_Void_Type
20276 or else Ekind
(Typ
) = E_String_Literal_Subtype
20280 -- If Typ is a generic formal incomplete type, then we want to look at
20281 -- the actual type.
20283 elsif Ekind
(Typ
) = E_Record_Subtype
20284 and then Present
(Cloned_Subtype
(Typ
))
20286 return New_Requires_Transient_Scope
(Cloned_Subtype
(Typ
));
20288 -- Functions returning specific tagged types may dispatch on result, so
20289 -- their returned value is allocated on the secondary stack, even in the
20290 -- definite case. We must treat nondispatching functions the same way,
20291 -- because access-to-function types can point at both, so the calling
20292 -- conventions must be compatible. Is_Tagged_Type includes controlled
20293 -- types and class-wide types. Controlled type temporaries need
20296 -- ???It's not clear why we need to return noncontrolled types with
20297 -- controlled components on the secondary stack.
20299 elsif Is_Tagged_Type
(Typ
) or else Has_Controlled_Component
(Typ
) then
20302 -- Untagged definite subtypes are known size. This includes all
20303 -- elementary [sub]types. Tasks are known size even if they have
20304 -- discriminants. So we return False here, with one exception:
20305 -- For a type like:
20306 -- type T (Last : Natural := 0) is
20307 -- X : String (1 .. Last);
20309 -- we return True. That's because for "P(F(...));", where F returns T,
20310 -- we don't know the size of the result at the call site, so if we
20311 -- allocated it on the primary stack, we would have to allocate the
20312 -- maximum size, which is way too big.
20314 elsif Is_Definite_Subtype
(Typ
) or else Is_Task_Type
(Typ
) then
20315 return Large_Max_Size_Mutable
(Typ
);
20317 -- Indefinite (discriminated) untagged record or protected type
20319 elsif Is_Record_Type
(Typ
) or else Is_Protected_Type
(Typ
) then
20320 return not Caller_Known_Size_Record
(Typ
);
20322 -- Unconstrained array
20325 pragma Assert
(Is_Array_Type
(Typ
) and not Is_Definite_Subtype
(Typ
));
20328 end New_Requires_Transient_Scope
;
20330 --------------------------
20331 -- No_Heap_Finalization --
20332 --------------------------
20334 function No_Heap_Finalization
(Typ
: Entity_Id
) return Boolean is
20336 if Ekind_In
(Typ
, E_Access_Type
, E_General_Access_Type
)
20337 and then Is_Library_Level_Entity
(Typ
)
20339 -- A global No_Heap_Finalization pragma applies to all library-level
20340 -- named access-to-object types.
20342 if Present
(No_Heap_Finalization_Pragma
) then
20345 -- The library-level named access-to-object type itself is subject to
20346 -- pragma No_Heap_Finalization.
20348 elsif Present
(Get_Pragma
(Typ
, Pragma_No_Heap_Finalization
)) then
20354 end No_Heap_Finalization
;
20356 -----------------------
20357 -- Normalize_Actuals --
20358 -----------------------
20360 -- Chain actuals according to formals of subprogram. If there are no named
20361 -- associations, the chain is simply the list of Parameter Associations,
20362 -- since the order is the same as the declaration order. If there are named
20363 -- associations, then the First_Named_Actual field in the N_Function_Call
20364 -- or N_Procedure_Call_Statement node points to the Parameter_Association
20365 -- node for the parameter that comes first in declaration order. The
20366 -- remaining named parameters are then chained in declaration order using
20367 -- Next_Named_Actual.
20369 -- This routine also verifies that the number of actuals is compatible with
20370 -- the number and default values of formals, but performs no type checking
20371 -- (type checking is done by the caller).
20373 -- If the matching succeeds, Success is set to True and the caller proceeds
20374 -- with type-checking. If the match is unsuccessful, then Success is set to
20375 -- False, and the caller attempts a different interpretation, if there is
20378 -- If the flag Report is on, the call is not overloaded, and a failure to
20379 -- match can be reported here, rather than in the caller.
20381 procedure Normalize_Actuals
20385 Success
: out Boolean)
20387 Actuals
: constant List_Id
:= Parameter_Associations
(N
);
20388 Actual
: Node_Id
:= Empty
;
20389 Formal
: Entity_Id
;
20390 Last
: Node_Id
:= Empty
;
20391 First_Named
: Node_Id
:= Empty
;
20394 Formals_To_Match
: Integer := 0;
20395 Actuals_To_Match
: Integer := 0;
20397 procedure Chain
(A
: Node_Id
);
20398 -- Add named actual at the proper place in the list, using the
20399 -- Next_Named_Actual link.
20401 function Reporting
return Boolean;
20402 -- Determines if an error is to be reported. To report an error, we
20403 -- need Report to be True, and also we do not report errors caused
20404 -- by calls to init procs that occur within other init procs. Such
20405 -- errors must always be cascaded errors, since if all the types are
20406 -- declared correctly, the compiler will certainly build decent calls.
20412 procedure Chain
(A
: Node_Id
) is
20416 -- Call node points to first actual in list
20418 Set_First_Named_Actual
(N
, Explicit_Actual_Parameter
(A
));
20421 Set_Next_Named_Actual
(Last
, Explicit_Actual_Parameter
(A
));
20425 Set_Next_Named_Actual
(Last
, Empty
);
20432 function Reporting
return Boolean is
20437 elsif not Within_Init_Proc
then
20440 elsif Is_Init_Proc
(Entity
(Name
(N
))) then
20448 -- Start of processing for Normalize_Actuals
20451 if Is_Access_Type
(S
) then
20453 -- The name in the call is a function call that returns an access
20454 -- to subprogram. The designated type has the list of formals.
20456 Formal
:= First_Formal
(Designated_Type
(S
));
20458 Formal
:= First_Formal
(S
);
20461 while Present
(Formal
) loop
20462 Formals_To_Match
:= Formals_To_Match
+ 1;
20463 Next_Formal
(Formal
);
20466 -- Find if there is a named association, and verify that no positional
20467 -- associations appear after named ones.
20469 if Present
(Actuals
) then
20470 Actual
:= First
(Actuals
);
20473 while Present
(Actual
)
20474 and then Nkind
(Actual
) /= N_Parameter_Association
20476 Actuals_To_Match
:= Actuals_To_Match
+ 1;
20480 if No
(Actual
) and Actuals_To_Match
= Formals_To_Match
then
20482 -- Most common case: positional notation, no defaults
20487 elsif Actuals_To_Match
> Formals_To_Match
then
20489 -- Too many actuals: will not work
20492 if Is_Entity_Name
(Name
(N
)) then
20493 Error_Msg_N
("too many arguments in call to&", Name
(N
));
20495 Error_Msg_N
("too many arguments in call", N
);
20503 First_Named
:= Actual
;
20505 while Present
(Actual
) loop
20506 if Nkind
(Actual
) /= N_Parameter_Association
then
20508 ("positional parameters not allowed after named ones", Actual
);
20513 Actuals_To_Match
:= Actuals_To_Match
+ 1;
20519 if Present
(Actuals
) then
20520 Actual
:= First
(Actuals
);
20523 Formal
:= First_Formal
(S
);
20524 while Present
(Formal
) loop
20526 -- Match the formals in order. If the corresponding actual is
20527 -- positional, nothing to do. Else scan the list of named actuals
20528 -- to find the one with the right name.
20530 if Present
(Actual
)
20531 and then Nkind
(Actual
) /= N_Parameter_Association
20534 Actuals_To_Match
:= Actuals_To_Match
- 1;
20535 Formals_To_Match
:= Formals_To_Match
- 1;
20538 -- For named parameters, search the list of actuals to find
20539 -- one that matches the next formal name.
20541 Actual
:= First_Named
;
20543 while Present
(Actual
) loop
20544 if Chars
(Selector_Name
(Actual
)) = Chars
(Formal
) then
20547 Actuals_To_Match
:= Actuals_To_Match
- 1;
20548 Formals_To_Match
:= Formals_To_Match
- 1;
20556 if Ekind
(Formal
) /= E_In_Parameter
20557 or else No
(Default_Value
(Formal
))
20560 if (Comes_From_Source
(S
)
20561 or else Sloc
(S
) = Standard_Location
)
20562 and then Is_Overloadable
(S
)
20566 Nkind_In
(Parent
(N
), N_Procedure_Call_Statement
,
20568 N_Parameter_Association
)
20569 and then Ekind
(S
) /= E_Function
20571 Set_Etype
(N
, Etype
(S
));
20574 Error_Msg_Name_1
:= Chars
(S
);
20575 Error_Msg_Sloc
:= Sloc
(S
);
20577 ("missing argument for parameter & "
20578 & "in call to % declared #", N
, Formal
);
20581 elsif Is_Overloadable
(S
) then
20582 Error_Msg_Name_1
:= Chars
(S
);
20584 -- Point to type derivation that generated the
20587 Error_Msg_Sloc
:= Sloc
(Parent
(S
));
20590 ("missing argument for parameter & "
20591 & "in call to % (inherited) #", N
, Formal
);
20595 ("missing argument for parameter &", N
, Formal
);
20603 Formals_To_Match
:= Formals_To_Match
- 1;
20608 Next_Formal
(Formal
);
20611 if Formals_To_Match
= 0 and then Actuals_To_Match
= 0 then
20618 -- Find some superfluous named actual that did not get
20619 -- attached to the list of associations.
20621 Actual
:= First
(Actuals
);
20622 while Present
(Actual
) loop
20623 if Nkind
(Actual
) = N_Parameter_Association
20624 and then Actual
/= Last
20625 and then No
(Next_Named_Actual
(Actual
))
20627 -- A validity check may introduce a copy of a call that
20628 -- includes an extra actual (for example for an unrelated
20629 -- accessibility check). Check that the extra actual matches
20630 -- some extra formal, which must exist already because
20631 -- subprogram must be frozen at this point.
20633 if Present
(Extra_Formals
(S
))
20634 and then not Comes_From_Source
(Actual
)
20635 and then Nkind
(Actual
) = N_Parameter_Association
20636 and then Chars
(Extra_Formals
(S
)) =
20637 Chars
(Selector_Name
(Actual
))
20642 ("unmatched actual & in call", Selector_Name
(Actual
));
20654 end Normalize_Actuals
;
20656 --------------------------------
20657 -- Note_Possible_Modification --
20658 --------------------------------
20660 procedure Note_Possible_Modification
(N
: Node_Id
; Sure
: Boolean) is
20661 Modification_Comes_From_Source
: constant Boolean :=
20662 Comes_From_Source
(Parent
(N
));
20668 -- Loop to find referenced entity, if there is one
20674 if Is_Entity_Name
(Exp
) then
20675 Ent
:= Entity
(Exp
);
20677 -- If the entity is missing, it is an undeclared identifier,
20678 -- and there is nothing to annotate.
20684 elsif Nkind
(Exp
) = N_Explicit_Dereference
then
20686 P
: constant Node_Id
:= Prefix
(Exp
);
20689 -- In formal verification mode, keep track of all reads and
20690 -- writes through explicit dereferences.
20692 if GNATprove_Mode
then
20693 SPARK_Specific
.Generate_Dereference
(N
, 'm');
20696 if Nkind
(P
) = N_Selected_Component
20697 and then Present
(Entry_Formal
(Entity
(Selector_Name
(P
))))
20699 -- Case of a reference to an entry formal
20701 Ent
:= Entry_Formal
(Entity
(Selector_Name
(P
)));
20703 elsif Nkind
(P
) = N_Identifier
20704 and then Nkind
(Parent
(Entity
(P
))) = N_Object_Declaration
20705 and then Present
(Expression
(Parent
(Entity
(P
))))
20706 and then Nkind
(Expression
(Parent
(Entity
(P
)))) =
20709 -- Case of a reference to a value on which side effects have
20712 Exp
:= Prefix
(Expression
(Parent
(Entity
(P
))));
20720 elsif Nkind_In
(Exp
, N_Type_Conversion
,
20721 N_Unchecked_Type_Conversion
)
20723 Exp
:= Expression
(Exp
);
20726 elsif Nkind_In
(Exp
, N_Slice
,
20727 N_Indexed_Component
,
20728 N_Selected_Component
)
20730 -- Special check, if the prefix is an access type, then return
20731 -- since we are modifying the thing pointed to, not the prefix.
20732 -- When we are expanding, most usually the prefix is replaced
20733 -- by an explicit dereference, and this test is not needed, but
20734 -- in some cases (notably -gnatc mode and generics) when we do
20735 -- not do full expansion, we need this special test.
20737 if Is_Access_Type
(Etype
(Prefix
(Exp
))) then
20740 -- Otherwise go to prefix and keep going
20743 Exp
:= Prefix
(Exp
);
20747 -- All other cases, not a modification
20753 -- Now look for entity being referenced
20755 if Present
(Ent
) then
20756 if Is_Object
(Ent
) then
20757 if Comes_From_Source
(Exp
)
20758 or else Modification_Comes_From_Source
20760 -- Give warning if pragma unmodified is given and we are
20761 -- sure this is a modification.
20763 if Has_Pragma_Unmodified
(Ent
) and then Sure
then
20765 -- Note that the entity may be present only as a result
20766 -- of pragma Unused.
20768 if Has_Pragma_Unused
(Ent
) then
20769 Error_Msg_NE
("??pragma Unused given for &!", N
, Ent
);
20772 ("??pragma Unmodified given for &!", N
, Ent
);
20776 Set_Never_Set_In_Source
(Ent
, False);
20779 Set_Is_True_Constant
(Ent
, False);
20780 Set_Current_Value
(Ent
, Empty
);
20781 Set_Is_Known_Null
(Ent
, False);
20783 if not Can_Never_Be_Null
(Ent
) then
20784 Set_Is_Known_Non_Null
(Ent
, False);
20787 -- Follow renaming chain
20789 if (Ekind
(Ent
) = E_Variable
or else Ekind
(Ent
) = E_Constant
)
20790 and then Present
(Renamed_Object
(Ent
))
20792 Exp
:= Renamed_Object
(Ent
);
20794 -- If the entity is the loop variable in an iteration over
20795 -- a container, retrieve container expression to indicate
20796 -- possible modification.
20798 if Present
(Related_Expression
(Ent
))
20799 and then Nkind
(Parent
(Related_Expression
(Ent
))) =
20800 N_Iterator_Specification
20802 Exp
:= Original_Node
(Related_Expression
(Ent
));
20807 -- The expression may be the renaming of a subcomponent of an
20808 -- array or container. The assignment to the subcomponent is
20809 -- a modification of the container.
20811 elsif Comes_From_Source
(Original_Node
(Exp
))
20812 and then Nkind_In
(Original_Node
(Exp
), N_Selected_Component
,
20813 N_Indexed_Component
)
20815 Exp
:= Prefix
(Original_Node
(Exp
));
20819 -- Generate a reference only if the assignment comes from
20820 -- source. This excludes, for example, calls to a dispatching
20821 -- assignment operation when the left-hand side is tagged. In
20822 -- GNATprove mode, we need those references also on generated
20823 -- code, as these are used to compute the local effects of
20826 if Modification_Comes_From_Source
or GNATprove_Mode
then
20827 Generate_Reference
(Ent
, Exp
, 'm');
20829 -- If the target of the assignment is the bound variable
20830 -- in an iterator, indicate that the corresponding array
20831 -- or container is also modified.
20833 if Ada_Version
>= Ada_2012
20834 and then Nkind
(Parent
(Ent
)) = N_Iterator_Specification
20837 Domain
: constant Node_Id
:= Name
(Parent
(Ent
));
20840 -- TBD : in the full version of the construct, the
20841 -- domain of iteration can be given by an expression.
20843 if Is_Entity_Name
(Domain
) then
20844 Generate_Reference
(Entity
(Domain
), Exp
, 'm');
20845 Set_Is_True_Constant
(Entity
(Domain
), False);
20846 Set_Never_Set_In_Source
(Entity
(Domain
), False);
20855 -- If we are sure this is a modification from source, and we know
20856 -- this modifies a constant, then give an appropriate warning.
20859 and then Modification_Comes_From_Source
20860 and then Overlays_Constant
(Ent
)
20861 and then Address_Clause_Overlay_Warnings
20864 Addr
: constant Node_Id
:= Address_Clause
(Ent
);
20869 Find_Overlaid_Entity
(Addr
, O_Ent
, Off
);
20871 Error_Msg_Sloc
:= Sloc
(Addr
);
20873 ("??constant& may be modified via address clause#",
20884 end Note_Possible_Modification
;
20890 function Null_Status
(N
: Node_Id
) return Null_Status_Kind
is
20891 function Is_Null_Excluding_Def
(Def
: Node_Id
) return Boolean;
20892 -- Determine whether definition Def carries a null exclusion
20894 function Null_Status_Of_Entity
(Id
: Entity_Id
) return Null_Status_Kind
;
20895 -- Determine the null status of arbitrary entity Id
20897 function Null_Status_Of_Type
(Typ
: Entity_Id
) return Null_Status_Kind
;
20898 -- Determine the null status of type Typ
20900 ---------------------------
20901 -- Is_Null_Excluding_Def --
20902 ---------------------------
20904 function Is_Null_Excluding_Def
(Def
: Node_Id
) return Boolean is
20907 Nkind_In
(Def
, N_Access_Definition
,
20908 N_Access_Function_Definition
,
20909 N_Access_Procedure_Definition
,
20910 N_Access_To_Object_Definition
,
20911 N_Component_Definition
,
20912 N_Derived_Type_Definition
)
20913 and then Null_Exclusion_Present
(Def
);
20914 end Is_Null_Excluding_Def
;
20916 ---------------------------
20917 -- Null_Status_Of_Entity --
20918 ---------------------------
20920 function Null_Status_Of_Entity
20921 (Id
: Entity_Id
) return Null_Status_Kind
20923 Decl
: constant Node_Id
:= Declaration_Node
(Id
);
20927 -- The value of an imported or exported entity may be set externally
20928 -- regardless of a null exclusion. As a result, the value cannot be
20929 -- determined statically.
20931 if Is_Imported
(Id
) or else Is_Exported
(Id
) then
20934 elsif Nkind_In
(Decl
, N_Component_Declaration
,
20935 N_Discriminant_Specification
,
20936 N_Formal_Object_Declaration
,
20937 N_Object_Declaration
,
20938 N_Object_Renaming_Declaration
,
20939 N_Parameter_Specification
)
20941 -- A component declaration yields a non-null value when either
20942 -- its component definition or access definition carries a null
20945 if Nkind
(Decl
) = N_Component_Declaration
then
20946 Def
:= Component_Definition
(Decl
);
20948 if Is_Null_Excluding_Def
(Def
) then
20949 return Is_Non_Null
;
20952 Def
:= Access_Definition
(Def
);
20954 if Present
(Def
) and then Is_Null_Excluding_Def
(Def
) then
20955 return Is_Non_Null
;
20958 -- A formal object declaration yields a non-null value if its
20959 -- access definition carries a null exclusion. If the object is
20960 -- default initialized, then the value depends on the expression.
20962 elsif Nkind
(Decl
) = N_Formal_Object_Declaration
then
20963 Def
:= Access_Definition
(Decl
);
20965 if Present
(Def
) and then Is_Null_Excluding_Def
(Def
) then
20966 return Is_Non_Null
;
20969 -- A constant may yield a null or non-null value depending on its
20970 -- initialization expression.
20972 elsif Ekind
(Id
) = E_Constant
then
20973 return Null_Status
(Constant_Value
(Id
));
20975 -- The construct yields a non-null value when it has a null
20978 elsif Null_Exclusion_Present
(Decl
) then
20979 return Is_Non_Null
;
20981 -- An object renaming declaration yields a non-null value if its
20982 -- access definition carries a null exclusion. Otherwise the value
20983 -- depends on the renamed name.
20985 elsif Nkind
(Decl
) = N_Object_Renaming_Declaration
then
20986 Def
:= Access_Definition
(Decl
);
20988 if Present
(Def
) and then Is_Null_Excluding_Def
(Def
) then
20989 return Is_Non_Null
;
20992 return Null_Status
(Name
(Decl
));
20997 -- At this point the declaration of the entity does not carry a null
20998 -- exclusion and lacks an initialization expression. Check the status
21001 return Null_Status_Of_Type
(Etype
(Id
));
21002 end Null_Status_Of_Entity
;
21004 -------------------------
21005 -- Null_Status_Of_Type --
21006 -------------------------
21008 function Null_Status_Of_Type
(Typ
: Entity_Id
) return Null_Status_Kind
is
21013 -- Traverse the type chain looking for types with null exclusion
21016 while Present
(Curr
) and then Etype
(Curr
) /= Curr
loop
21017 Decl
:= Parent
(Curr
);
21019 -- Guard against itypes which do not always have declarations. A
21020 -- type yields a non-null value if it carries a null exclusion.
21022 if Present
(Decl
) then
21023 if Nkind
(Decl
) = N_Full_Type_Declaration
21024 and then Is_Null_Excluding_Def
(Type_Definition
(Decl
))
21026 return Is_Non_Null
;
21028 elsif Nkind
(Decl
) = N_Subtype_Declaration
21029 and then Null_Exclusion_Present
(Decl
)
21031 return Is_Non_Null
;
21035 Curr
:= Etype
(Curr
);
21038 -- The type chain does not contain any null excluding types
21041 end Null_Status_Of_Type
;
21043 -- Start of processing for Null_Status
21046 -- An allocator always creates a non-null value
21048 if Nkind
(N
) = N_Allocator
then
21049 return Is_Non_Null
;
21051 -- Taking the 'Access of something yields a non-null value
21053 elsif Nkind
(N
) = N_Attribute_Reference
21054 and then Nam_In
(Attribute_Name
(N
), Name_Access
,
21055 Name_Unchecked_Access
,
21056 Name_Unrestricted_Access
)
21058 return Is_Non_Null
;
21060 -- "null" yields null
21062 elsif Nkind
(N
) = N_Null
then
21065 -- Check the status of the operand of a type conversion
21067 elsif Nkind
(N
) = N_Type_Conversion
then
21068 return Null_Status
(Expression
(N
));
21070 -- The input denotes a reference to an entity. Determine whether the
21071 -- entity or its type yields a null or non-null value.
21073 elsif Is_Entity_Name
(N
) and then Present
(Entity
(N
)) then
21074 return Null_Status_Of_Entity
(Entity
(N
));
21077 -- Otherwise it is not possible to determine the null status of the
21078 -- subexpression at compile time without resorting to simple flow
21084 --------------------------------------
21085 -- Null_To_Null_Address_Convert_OK --
21086 --------------------------------------
21088 function Null_To_Null_Address_Convert_OK
21090 Typ
: Entity_Id
:= Empty
) return Boolean
21093 if not Relaxed_RM_Semantics
then
21097 if Nkind
(N
) = N_Null
then
21098 return Present
(Typ
) and then Is_Descendant_Of_Address
(Typ
);
21100 elsif Nkind_In
(N
, N_Op_Eq
, N_Op_Ge
, N_Op_Gt
, N_Op_Le
, N_Op_Lt
, N_Op_Ne
)
21103 L
: constant Node_Id
:= Left_Opnd
(N
);
21104 R
: constant Node_Id
:= Right_Opnd
(N
);
21107 -- We check the Etype of the complementary operand since the
21108 -- N_Null node is not decorated at this stage.
21111 ((Nkind
(L
) = N_Null
21112 and then Is_Descendant_Of_Address
(Etype
(R
)))
21114 (Nkind
(R
) = N_Null
21115 and then Is_Descendant_Of_Address
(Etype
(L
))));
21120 end Null_To_Null_Address_Convert_OK
;
21122 ---------------------------------
21123 -- Number_Of_Elements_In_Array --
21124 ---------------------------------
21126 function Number_Of_Elements_In_Array
(T
: Entity_Id
) return Int
is
21134 pragma Assert
(Is_Array_Type
(T
));
21136 Indx
:= First_Index
(T
);
21137 while Present
(Indx
) loop
21138 Typ
:= Underlying_Type
(Etype
(Indx
));
21140 -- Never look at junk bounds of a generic type
21142 if Is_Generic_Type
(Typ
) then
21146 -- Check the array bounds are known at compile time and return zero
21147 -- if they are not.
21149 Low
:= Type_Low_Bound
(Typ
);
21150 High
:= Type_High_Bound
(Typ
);
21152 if not Compile_Time_Known_Value
(Low
) then
21154 elsif not Compile_Time_Known_Value
(High
) then
21158 Num
* UI_To_Int
((Expr_Value
(High
) - Expr_Value
(Low
) + 1));
21165 end Number_Of_Elements_In_Array
;
21167 -------------------------
21168 -- Object_Access_Level --
21169 -------------------------
21171 -- Returns the static accessibility level of the view denoted by Obj. Note
21172 -- that the value returned is the result of a call to Scope_Depth. Only
21173 -- scope depths associated with dynamic scopes can actually be returned.
21174 -- Since only relative levels matter for accessibility checking, the fact
21175 -- that the distance between successive levels of accessibility is not
21176 -- always one is immaterial (invariant: if level(E2) is deeper than
21177 -- level(E1), then Scope_Depth(E1) < Scope_Depth(E2)).
21179 function Object_Access_Level
(Obj
: Node_Id
) return Uint
is
21180 function Is_Interface_Conversion
(N
: Node_Id
) return Boolean;
21181 -- Determine whether N is a construct of the form
21182 -- Some_Type (Operand._tag'Address)
21183 -- This construct appears in the context of dispatching calls.
21185 function Reference_To
(Obj
: Node_Id
) return Node_Id
;
21186 -- An explicit dereference is created when removing side effects from
21187 -- expressions for constraint checking purposes. In this case a local
21188 -- access type is created for it. The correct access level is that of
21189 -- the original source node. We detect this case by noting that the
21190 -- prefix of the dereference is created by an object declaration whose
21191 -- initial expression is a reference.
21193 -----------------------------
21194 -- Is_Interface_Conversion --
21195 -----------------------------
21197 function Is_Interface_Conversion
(N
: Node_Id
) return Boolean is
21199 return Nkind
(N
) = N_Unchecked_Type_Conversion
21200 and then Nkind
(Expression
(N
)) = N_Attribute_Reference
21201 and then Attribute_Name
(Expression
(N
)) = Name_Address
;
21202 end Is_Interface_Conversion
;
21208 function Reference_To
(Obj
: Node_Id
) return Node_Id
is
21209 Pref
: constant Node_Id
:= Prefix
(Obj
);
21211 if Is_Entity_Name
(Pref
)
21212 and then Nkind
(Parent
(Entity
(Pref
))) = N_Object_Declaration
21213 and then Present
(Expression
(Parent
(Entity
(Pref
))))
21214 and then Nkind
(Expression
(Parent
(Entity
(Pref
)))) = N_Reference
21216 return (Prefix
(Expression
(Parent
(Entity
(Pref
)))));
21226 -- Start of processing for Object_Access_Level
21229 if Nkind
(Obj
) = N_Defining_Identifier
21230 or else Is_Entity_Name
(Obj
)
21232 if Nkind
(Obj
) = N_Defining_Identifier
then
21238 if Is_Prival
(E
) then
21239 E
:= Prival_Link
(E
);
21242 -- If E is a type then it denotes a current instance. For this case
21243 -- we add one to the normal accessibility level of the type to ensure
21244 -- that current instances are treated as always being deeper than
21245 -- than the level of any visible named access type (see 3.10.2(21)).
21247 if Is_Type
(E
) then
21248 return Type_Access_Level
(E
) + 1;
21250 elsif Present
(Renamed_Object
(E
)) then
21251 return Object_Access_Level
(Renamed_Object
(E
));
21253 -- Similarly, if E is a component of the current instance of a
21254 -- protected type, any instance of it is assumed to be at a deeper
21255 -- level than the type. For a protected object (whose type is an
21256 -- anonymous protected type) its components are at the same level
21257 -- as the type itself.
21259 elsif not Is_Overloadable
(E
)
21260 and then Ekind
(Scope
(E
)) = E_Protected_Type
21261 and then Comes_From_Source
(Scope
(E
))
21263 return Type_Access_Level
(Scope
(E
)) + 1;
21266 -- Aliased formals of functions take their access level from the
21267 -- point of call, i.e. require a dynamic check. For static check
21268 -- purposes, this is smaller than the level of the subprogram
21269 -- itself. For procedures the aliased makes no difference.
21272 and then Is_Aliased
(E
)
21273 and then Ekind
(Scope
(E
)) = E_Function
21275 return Type_Access_Level
(Etype
(E
));
21278 return Scope_Depth
(Enclosing_Dynamic_Scope
(E
));
21282 elsif Nkind_In
(Obj
, N_Indexed_Component
, N_Selected_Component
) then
21283 if Is_Access_Type
(Etype
(Prefix
(Obj
))) then
21284 return Type_Access_Level
(Etype
(Prefix
(Obj
)));
21286 return Object_Access_Level
(Prefix
(Obj
));
21289 elsif Nkind
(Obj
) = N_Explicit_Dereference
then
21291 -- If the prefix is a selected access discriminant then we make a
21292 -- recursive call on the prefix, which will in turn check the level
21293 -- of the prefix object of the selected discriminant.
21295 -- In Ada 2012, if the discriminant has implicit dereference and
21296 -- the context is a selected component, treat this as an object of
21297 -- unknown scope (see below). This is necessary in compile-only mode;
21298 -- otherwise expansion will already have transformed the prefix into
21301 if Nkind
(Prefix
(Obj
)) = N_Selected_Component
21302 and then Ekind
(Etype
(Prefix
(Obj
))) = E_Anonymous_Access_Type
21304 Ekind
(Entity
(Selector_Name
(Prefix
(Obj
)))) = E_Discriminant
21306 (not Has_Implicit_Dereference
21307 (Entity
(Selector_Name
(Prefix
(Obj
))))
21308 or else Nkind
(Parent
(Obj
)) /= N_Selected_Component
)
21310 return Object_Access_Level
(Prefix
(Obj
));
21312 -- Detect an interface conversion in the context of a dispatching
21313 -- call. Use the original form of the conversion to find the access
21314 -- level of the operand.
21316 elsif Is_Interface
(Etype
(Obj
))
21317 and then Is_Interface_Conversion
(Prefix
(Obj
))
21318 and then Nkind
(Original_Node
(Obj
)) = N_Type_Conversion
21320 return Object_Access_Level
(Original_Node
(Obj
));
21322 elsif not Comes_From_Source
(Obj
) then
21324 Ref
: constant Node_Id
:= Reference_To
(Obj
);
21326 if Present
(Ref
) then
21327 return Object_Access_Level
(Ref
);
21329 return Type_Access_Level
(Etype
(Prefix
(Obj
)));
21334 return Type_Access_Level
(Etype
(Prefix
(Obj
)));
21337 elsif Nkind_In
(Obj
, N_Type_Conversion
, N_Unchecked_Type_Conversion
) then
21338 return Object_Access_Level
(Expression
(Obj
));
21340 elsif Nkind
(Obj
) = N_Function_Call
then
21342 -- Function results are objects, so we get either the access level of
21343 -- the function or, in the case of an indirect call, the level of the
21344 -- access-to-subprogram type. (This code is used for Ada 95, but it
21345 -- looks wrong, because it seems that we should be checking the level
21346 -- of the call itself, even for Ada 95. However, using the Ada 2005
21347 -- version of the code causes regressions in several tests that are
21348 -- compiled with -gnat95. ???)
21350 if Ada_Version
< Ada_2005
then
21351 if Is_Entity_Name
(Name
(Obj
)) then
21352 return Subprogram_Access_Level
(Entity
(Name
(Obj
)));
21354 return Type_Access_Level
(Etype
(Prefix
(Name
(Obj
))));
21357 -- For Ada 2005, the level of the result object of a function call is
21358 -- defined to be the level of the call's innermost enclosing master.
21359 -- We determine that by querying the depth of the innermost enclosing
21363 Return_Master_Scope_Depth_Of_Call
: declare
21364 function Innermost_Master_Scope_Depth
21365 (N
: Node_Id
) return Uint
;
21366 -- Returns the scope depth of the given node's innermost
21367 -- enclosing dynamic scope (effectively the accessibility
21368 -- level of the innermost enclosing master).
21370 ----------------------------------
21371 -- Innermost_Master_Scope_Depth --
21372 ----------------------------------
21374 function Innermost_Master_Scope_Depth
21375 (N
: Node_Id
) return Uint
21377 Node_Par
: Node_Id
:= Parent
(N
);
21380 -- Locate the nearest enclosing node (by traversing Parents)
21381 -- that Defining_Entity can be applied to, and return the
21382 -- depth of that entity's nearest enclosing dynamic scope.
21384 while Present
(Node_Par
) loop
21385 case Nkind
(Node_Par
) is
21386 when N_Abstract_Subprogram_Declaration
21387 | N_Block_Statement
21389 | N_Component_Declaration
21391 | N_Entry_Declaration
21392 | N_Exception_Declaration
21393 | N_Formal_Object_Declaration
21394 | N_Formal_Package_Declaration
21395 | N_Formal_Subprogram_Declaration
21396 | N_Formal_Type_Declaration
21397 | N_Full_Type_Declaration
21398 | N_Function_Specification
21399 | N_Generic_Declaration
21400 | N_Generic_Instantiation
21401 | N_Implicit_Label_Declaration
21402 | N_Incomplete_Type_Declaration
21403 | N_Loop_Parameter_Specification
21404 | N_Number_Declaration
21405 | N_Object_Declaration
21406 | N_Package_Declaration
21407 | N_Package_Specification
21408 | N_Parameter_Specification
21409 | N_Private_Extension_Declaration
21410 | N_Private_Type_Declaration
21411 | N_Procedure_Specification
21413 | N_Protected_Type_Declaration
21414 | N_Renaming_Declaration
21415 | N_Single_Protected_Declaration
21416 | N_Single_Task_Declaration
21417 | N_Subprogram_Declaration
21418 | N_Subtype_Declaration
21420 | N_Task_Type_Declaration
21423 (Nearest_Dynamic_Scope
21424 (Defining_Entity
(Node_Par
)));
21426 -- For a return statement within a function, return
21427 -- the depth of the function itself. This is not just
21428 -- a small optimization, but matters when analyzing
21429 -- the expression in an expression function before
21430 -- the body is created.
21432 when N_Simple_Return_Statement
=>
21433 if Ekind
(Current_Scope
) = E_Function
then
21434 return Scope_Depth
(Current_Scope
);
21441 Node_Par
:= Parent
(Node_Par
);
21444 pragma Assert
(False);
21446 -- Should never reach the following return
21448 return Scope_Depth
(Current_Scope
) + 1;
21449 end Innermost_Master_Scope_Depth
;
21451 -- Start of processing for Return_Master_Scope_Depth_Of_Call
21454 return Innermost_Master_Scope_Depth
(Obj
);
21455 end Return_Master_Scope_Depth_Of_Call
;
21458 -- For convenience we handle qualified expressions, even though they
21459 -- aren't technically object names.
21461 elsif Nkind
(Obj
) = N_Qualified_Expression
then
21462 return Object_Access_Level
(Expression
(Obj
));
21464 -- Ditto for aggregates. They have the level of the temporary that
21465 -- will hold their value.
21467 elsif Nkind
(Obj
) = N_Aggregate
then
21468 return Object_Access_Level
(Current_Scope
);
21470 -- Otherwise return the scope level of Standard. (If there are cases
21471 -- that fall through to this point they will be treated as having
21472 -- global accessibility for now. ???)
21475 return Scope_Depth
(Standard_Standard
);
21477 end Object_Access_Level
;
21479 ----------------------------------
21480 -- Old_Requires_Transient_Scope --
21481 ----------------------------------
21483 function Old_Requires_Transient_Scope
(Id
: Entity_Id
) return Boolean is
21484 Typ
: constant Entity_Id
:= Underlying_Type
(Id
);
21487 -- This is a private type which is not completed yet. This can only
21488 -- happen in a default expression (of a formal parameter or of a
21489 -- record component). Do not expand transient scope in this case.
21494 -- Do not expand transient scope for non-existent procedure return
21496 elsif Typ
= Standard_Void_Type
then
21499 -- Elementary types do not require a transient scope
21501 elsif Is_Elementary_Type
(Typ
) then
21504 -- Generally, indefinite subtypes require a transient scope, since the
21505 -- back end cannot generate temporaries, since this is not a valid type
21506 -- for declaring an object. It might be possible to relax this in the
21507 -- future, e.g. by declaring the maximum possible space for the type.
21509 elsif not Is_Definite_Subtype
(Typ
) then
21512 -- Functions returning tagged types may dispatch on result so their
21513 -- returned value is allocated on the secondary stack. Controlled
21514 -- type temporaries need finalization.
21516 elsif Is_Tagged_Type
(Typ
) or else Has_Controlled_Component
(Typ
) then
21521 elsif Is_Record_Type
(Typ
) then
21526 Comp
:= First_Entity
(Typ
);
21527 while Present
(Comp
) loop
21528 if Ekind
(Comp
) = E_Component
then
21530 -- ???It's not clear we need a full recursive call to
21531 -- Old_Requires_Transient_Scope here. Note that the
21532 -- following can't happen.
21534 pragma Assert
(Is_Definite_Subtype
(Etype
(Comp
)));
21535 pragma Assert
(not Has_Controlled_Component
(Etype
(Comp
)));
21537 if Old_Requires_Transient_Scope
(Etype
(Comp
)) then
21542 Next_Entity
(Comp
);
21548 -- String literal types never require transient scope
21550 elsif Ekind
(Typ
) = E_String_Literal_Subtype
then
21553 -- Array type. Note that we already know that this is a constrained
21554 -- array, since unconstrained arrays will fail the indefinite test.
21556 elsif Is_Array_Type
(Typ
) then
21558 -- If component type requires a transient scope, the array does too
21560 if Old_Requires_Transient_Scope
(Component_Type
(Typ
)) then
21563 -- Otherwise, we only need a transient scope if the size depends on
21564 -- the value of one or more discriminants.
21567 return Size_Depends_On_Discriminant
(Typ
);
21570 -- All other cases do not require a transient scope
21573 pragma Assert
(Is_Protected_Type
(Typ
) or else Is_Task_Type
(Typ
));
21576 end Old_Requires_Transient_Scope
;
21578 ---------------------------------
21579 -- Original_Aspect_Pragma_Name --
21580 ---------------------------------
21582 function Original_Aspect_Pragma_Name
(N
: Node_Id
) return Name_Id
is
21584 Item_Nam
: Name_Id
;
21587 pragma Assert
(Nkind_In
(N
, N_Aspect_Specification
, N_Pragma
));
21591 -- The pragma was generated to emulate an aspect, use the original
21592 -- aspect specification.
21594 if Nkind
(Item
) = N_Pragma
and then From_Aspect_Specification
(Item
) then
21595 Item
:= Corresponding_Aspect
(Item
);
21598 -- Retrieve the name of the aspect/pragma. Note that Pre, Pre_Class,
21599 -- Post and Post_Class rewrite their pragma identifier to preserve the
21601 -- ??? this is kludgey
21603 if Nkind
(Item
) = N_Pragma
then
21604 Item_Nam
:= Chars
(Original_Node
(Pragma_Identifier
(Item
)));
21607 pragma Assert
(Nkind
(Item
) = N_Aspect_Specification
);
21608 Item_Nam
:= Chars
(Identifier
(Item
));
21611 -- Deal with 'Class by converting the name to its _XXX form
21613 if Class_Present
(Item
) then
21614 if Item_Nam
= Name_Invariant
then
21615 Item_Nam
:= Name_uInvariant
;
21617 elsif Item_Nam
= Name_Post
then
21618 Item_Nam
:= Name_uPost
;
21620 elsif Item_Nam
= Name_Pre
then
21621 Item_Nam
:= Name_uPre
;
21623 elsif Nam_In
(Item_Nam
, Name_Type_Invariant
,
21624 Name_Type_Invariant_Class
)
21626 Item_Nam
:= Name_uType_Invariant
;
21628 -- Nothing to do for other cases (e.g. a Check that derived from
21629 -- Pre_Class and has the flag set). Also we do nothing if the name
21630 -- is already in special _xxx form.
21636 end Original_Aspect_Pragma_Name
;
21638 --------------------------------------
21639 -- Original_Corresponding_Operation --
21640 --------------------------------------
21642 function Original_Corresponding_Operation
(S
: Entity_Id
) return Entity_Id
21644 Typ
: constant Entity_Id
:= Find_Dispatching_Type
(S
);
21647 -- If S is an inherited primitive S2 the original corresponding
21648 -- operation of S is the original corresponding operation of S2
21650 if Present
(Alias
(S
))
21651 and then Find_Dispatching_Type
(Alias
(S
)) /= Typ
21653 return Original_Corresponding_Operation
(Alias
(S
));
21655 -- If S overrides an inherited subprogram S2 the original corresponding
21656 -- operation of S is the original corresponding operation of S2
21658 elsif Present
(Overridden_Operation
(S
)) then
21659 return Original_Corresponding_Operation
(Overridden_Operation
(S
));
21661 -- otherwise it is S itself
21666 end Original_Corresponding_Operation
;
21668 -------------------
21669 -- Output_Entity --
21670 -------------------
21672 procedure Output_Entity
(Id
: Entity_Id
) is
21676 Scop
:= Scope
(Id
);
21678 -- The entity may lack a scope when it is in the process of being
21679 -- analyzed. Use the current scope as an approximation.
21682 Scop
:= Current_Scope
;
21685 Output_Name
(Chars
(Id
), Scop
);
21692 procedure Output_Name
(Nam
: Name_Id
; Scop
: Entity_Id
:= Current_Scope
) is
21696 (Get_Qualified_Name
21703 ----------------------
21704 -- Policy_In_Effect --
21705 ----------------------
21707 function Policy_In_Effect
(Policy
: Name_Id
) return Name_Id
is
21708 function Policy_In_List
(List
: Node_Id
) return Name_Id
;
21709 -- Determine the mode of a policy in a N_Pragma list
21711 --------------------
21712 -- Policy_In_List --
21713 --------------------
21715 function Policy_In_List
(List
: Node_Id
) return Name_Id
is
21722 while Present
(Prag
) loop
21723 Arg1
:= First
(Pragma_Argument_Associations
(Prag
));
21724 Arg2
:= Next
(Arg1
);
21726 Arg1
:= Get_Pragma_Arg
(Arg1
);
21727 Arg2
:= Get_Pragma_Arg
(Arg2
);
21729 -- The current Check_Policy pragma matches the requested policy or
21730 -- appears in the single argument form (Assertion, policy_id).
21732 if Nam_In
(Chars
(Arg1
), Name_Assertion
, Policy
) then
21733 return Chars
(Arg2
);
21736 Prag
:= Next_Pragma
(Prag
);
21740 end Policy_In_List
;
21746 -- Start of processing for Policy_In_Effect
21749 if not Is_Valid_Assertion_Kind
(Policy
) then
21750 raise Program_Error
;
21753 -- Inspect all policy pragmas that appear within scopes (if any)
21755 Kind
:= Policy_In_List
(Check_Policy_List
);
21757 -- Inspect all configuration policy pragmas (if any)
21759 if Kind
= No_Name
then
21760 Kind
:= Policy_In_List
(Check_Policy_List_Config
);
21763 -- The context lacks policy pragmas, determine the mode based on whether
21764 -- assertions are enabled at the configuration level. This ensures that
21765 -- the policy is preserved when analyzing generics.
21767 if Kind
= No_Name
then
21768 if Assertions_Enabled_Config
then
21769 Kind
:= Name_Check
;
21771 Kind
:= Name_Ignore
;
21776 end Policy_In_Effect
;
21778 ----------------------------------
21779 -- Predicate_Tests_On_Arguments --
21780 ----------------------------------
21782 function Predicate_Tests_On_Arguments
(Subp
: Entity_Id
) return Boolean is
21784 -- Always test predicates on indirect call
21786 if Ekind
(Subp
) = E_Subprogram_Type
then
21789 -- Do not test predicates on call to generated default Finalize, since
21790 -- we are not interested in whether something we are finalizing (and
21791 -- typically destroying) satisfies its predicates.
21793 elsif Chars
(Subp
) = Name_Finalize
21794 and then not Comes_From_Source
(Subp
)
21798 -- Do not test predicates on any internally generated routines
21800 elsif Is_Internal_Name
(Chars
(Subp
)) then
21803 -- Do not test predicates on call to Init_Proc, since if needed the
21804 -- predicate test will occur at some other point.
21806 elsif Is_Init_Proc
(Subp
) then
21809 -- Do not test predicates on call to predicate function, since this
21810 -- would cause infinite recursion.
21812 elsif Ekind
(Subp
) = E_Function
21813 and then (Is_Predicate_Function
(Subp
)
21815 Is_Predicate_Function_M
(Subp
))
21819 -- For now, no other exceptions
21824 end Predicate_Tests_On_Arguments
;
21826 -----------------------
21827 -- Private_Component --
21828 -----------------------
21830 function Private_Component
(Type_Id
: Entity_Id
) return Entity_Id
is
21831 Ancestor
: constant Entity_Id
:= Base_Type
(Type_Id
);
21833 function Trace_Components
21835 Check
: Boolean) return Entity_Id
;
21836 -- Recursive function that does the work, and checks against circular
21837 -- definition for each subcomponent type.
21839 ----------------------
21840 -- Trace_Components --
21841 ----------------------
21843 function Trace_Components
21845 Check
: Boolean) return Entity_Id
21847 Btype
: constant Entity_Id
:= Base_Type
(T
);
21848 Component
: Entity_Id
;
21850 Candidate
: Entity_Id
:= Empty
;
21853 if Check
and then Btype
= Ancestor
then
21854 Error_Msg_N
("circular type definition", Type_Id
);
21858 if Is_Private_Type
(Btype
) and then not Is_Generic_Type
(Btype
) then
21859 if Present
(Full_View
(Btype
))
21860 and then Is_Record_Type
(Full_View
(Btype
))
21861 and then not Is_Frozen
(Btype
)
21863 -- To indicate that the ancestor depends on a private type, the
21864 -- current Btype is sufficient. However, to check for circular
21865 -- definition we must recurse on the full view.
21867 Candidate
:= Trace_Components
(Full_View
(Btype
), True);
21869 if Candidate
= Any_Type
then
21879 elsif Is_Array_Type
(Btype
) then
21880 return Trace_Components
(Component_Type
(Btype
), True);
21882 elsif Is_Record_Type
(Btype
) then
21883 Component
:= First_Entity
(Btype
);
21884 while Present
(Component
)
21885 and then Comes_From_Source
(Component
)
21887 -- Skip anonymous types generated by constrained components
21889 if not Is_Type
(Component
) then
21890 P
:= Trace_Components
(Etype
(Component
), True);
21892 if Present
(P
) then
21893 if P
= Any_Type
then
21901 Next_Entity
(Component
);
21909 end Trace_Components
;
21911 -- Start of processing for Private_Component
21914 return Trace_Components
(Type_Id
, False);
21915 end Private_Component
;
21917 ---------------------------
21918 -- Primitive_Names_Match --
21919 ---------------------------
21921 function Primitive_Names_Match
(E1
, E2
: Entity_Id
) return Boolean is
21922 function Non_Internal_Name
(E
: Entity_Id
) return Name_Id
;
21923 -- Given an internal name, returns the corresponding non-internal name
21925 ------------------------
21926 -- Non_Internal_Name --
21927 ------------------------
21929 function Non_Internal_Name
(E
: Entity_Id
) return Name_Id
is
21931 Get_Name_String
(Chars
(E
));
21932 Name_Len
:= Name_Len
- 1;
21934 end Non_Internal_Name
;
21936 -- Start of processing for Primitive_Names_Match
21939 pragma Assert
(Present
(E1
) and then Present
(E2
));
21941 return Chars
(E1
) = Chars
(E2
)
21943 (not Is_Internal_Name
(Chars
(E1
))
21944 and then Is_Internal_Name
(Chars
(E2
))
21945 and then Non_Internal_Name
(E2
) = Chars
(E1
))
21947 (not Is_Internal_Name
(Chars
(E2
))
21948 and then Is_Internal_Name
(Chars
(E1
))
21949 and then Non_Internal_Name
(E1
) = Chars
(E2
))
21951 (Is_Predefined_Dispatching_Operation
(E1
)
21952 and then Is_Predefined_Dispatching_Operation
(E2
)
21953 and then Same_TSS
(E1
, E2
))
21955 (Is_Init_Proc
(E1
) and then Is_Init_Proc
(E2
));
21956 end Primitive_Names_Match
;
21958 -----------------------
21959 -- Process_End_Label --
21960 -----------------------
21962 procedure Process_End_Label
21971 Label_Ref
: Boolean;
21972 -- Set True if reference to end label itself is required
21975 -- Gets set to the operator symbol or identifier that references the
21976 -- entity Ent. For the child unit case, this is the identifier from the
21977 -- designator. For other cases, this is simply Endl.
21979 procedure Generate_Parent_Ref
(N
: Node_Id
; E
: Entity_Id
);
21980 -- N is an identifier node that appears as a parent unit reference in
21981 -- the case where Ent is a child unit. This procedure generates an
21982 -- appropriate cross-reference entry. E is the corresponding entity.
21984 -------------------------
21985 -- Generate_Parent_Ref --
21986 -------------------------
21988 procedure Generate_Parent_Ref
(N
: Node_Id
; E
: Entity_Id
) is
21990 -- If names do not match, something weird, skip reference
21992 if Chars
(E
) = Chars
(N
) then
21994 -- Generate the reference. We do NOT consider this as a reference
21995 -- for unreferenced symbol purposes.
21997 Generate_Reference
(E
, N
, 'r', Set_Ref
=> False, Force
=> True);
21999 if Style_Check
then
22000 Style
.Check_Identifier
(N
, E
);
22003 end Generate_Parent_Ref
;
22005 -- Start of processing for Process_End_Label
22008 -- If no node, ignore. This happens in some error situations, and
22009 -- also for some internally generated structures where no end label
22010 -- references are required in any case.
22016 -- Nothing to do if no End_Label, happens for internally generated
22017 -- constructs where we don't want an end label reference anyway. Also
22018 -- nothing to do if Endl is a string literal, which means there was
22019 -- some prior error (bad operator symbol)
22021 Endl
:= End_Label
(N
);
22023 if No
(Endl
) or else Nkind
(Endl
) = N_String_Literal
then
22027 -- Reference node is not in extended main source unit
22029 if not In_Extended_Main_Source_Unit
(N
) then
22031 -- Generally we do not collect references except for the extended
22032 -- main source unit. The one exception is the 'e' entry for a
22033 -- package spec, where it is useful for a client to have the
22034 -- ending information to define scopes.
22040 Label_Ref
:= False;
22042 -- For this case, we can ignore any parent references, but we
22043 -- need the package name itself for the 'e' entry.
22045 if Nkind
(Endl
) = N_Designator
then
22046 Endl
:= Identifier
(Endl
);
22050 -- Reference is in extended main source unit
22055 -- For designator, generate references for the parent entries
22057 if Nkind
(Endl
) = N_Designator
then
22059 -- Generate references for the prefix if the END line comes from
22060 -- source (otherwise we do not need these references) We climb the
22061 -- scope stack to find the expected entities.
22063 if Comes_From_Source
(Endl
) then
22064 Nam
:= Name
(Endl
);
22065 Scop
:= Current_Scope
;
22066 while Nkind
(Nam
) = N_Selected_Component
loop
22067 Scop
:= Scope
(Scop
);
22068 exit when No
(Scop
);
22069 Generate_Parent_Ref
(Selector_Name
(Nam
), Scop
);
22070 Nam
:= Prefix
(Nam
);
22073 if Present
(Scop
) then
22074 Generate_Parent_Ref
(Nam
, Scope
(Scop
));
22078 Endl
:= Identifier
(Endl
);
22082 -- If the end label is not for the given entity, then either we have
22083 -- some previous error, or this is a generic instantiation for which
22084 -- we do not need to make a cross-reference in this case anyway. In
22085 -- either case we simply ignore the call.
22087 if Chars
(Ent
) /= Chars
(Endl
) then
22091 -- If label was really there, then generate a normal reference and then
22092 -- adjust the location in the end label to point past the name (which
22093 -- should almost always be the semicolon).
22095 Loc
:= Sloc
(Endl
);
22097 if Comes_From_Source
(Endl
) then
22099 -- If a label reference is required, then do the style check and
22100 -- generate an l-type cross-reference entry for the label
22103 if Style_Check
then
22104 Style
.Check_Identifier
(Endl
, Ent
);
22107 Generate_Reference
(Ent
, Endl
, 'l', Set_Ref
=> False);
22110 -- Set the location to point past the label (normally this will
22111 -- mean the semicolon immediately following the label). This is
22112 -- done for the sake of the 'e' or 't' entry generated below.
22114 Get_Decoded_Name_String
(Chars
(Endl
));
22115 Set_Sloc
(Endl
, Sloc
(Endl
) + Source_Ptr
(Name_Len
));
22118 -- In SPARK mode, no missing label is allowed for packages and
22119 -- subprogram bodies. Detect those cases by testing whether
22120 -- Process_End_Label was called for a body (Typ = 't') or a package.
22122 if Restriction_Check_Required
(SPARK_05
)
22123 and then (Typ
= 't' or else Ekind
(Ent
) = E_Package
)
22125 Error_Msg_Node_1
:= Endl
;
22126 Check_SPARK_05_Restriction
22127 ("`END &` required", Endl
, Force
=> True);
22131 -- Now generate the e/t reference
22133 Generate_Reference
(Ent
, Endl
, Typ
, Set_Ref
=> False, Force
=> True);
22135 -- Restore Sloc, in case modified above, since we have an identifier
22136 -- and the normal Sloc should be left set in the tree.
22138 Set_Sloc
(Endl
, Loc
);
22139 end Process_End_Label
;
22141 --------------------------------
22142 -- Propagate_Concurrent_Flags --
22143 --------------------------------
22145 procedure Propagate_Concurrent_Flags
22147 Comp_Typ
: Entity_Id
)
22150 if Has_Task
(Comp_Typ
) then
22151 Set_Has_Task
(Typ
);
22154 if Has_Protected
(Comp_Typ
) then
22155 Set_Has_Protected
(Typ
);
22158 if Has_Timing_Event
(Comp_Typ
) then
22159 Set_Has_Timing_Event
(Typ
);
22161 end Propagate_Concurrent_Flags
;
22163 ------------------------------
22164 -- Propagate_DIC_Attributes --
22165 ------------------------------
22167 procedure Propagate_DIC_Attributes
22169 From_Typ
: Entity_Id
)
22171 DIC_Proc
: Entity_Id
;
22174 if Present
(Typ
) and then Present
(From_Typ
) then
22175 pragma Assert
(Is_Type
(Typ
) and then Is_Type
(From_Typ
));
22177 -- Nothing to do if both the source and the destination denote the
22180 if From_Typ
= Typ
then
22184 DIC_Proc
:= DIC_Procedure
(From_Typ
);
22186 -- The setting of the attributes is intentionally conservative. This
22187 -- prevents accidental clobbering of enabled attributes.
22189 if Has_Inherited_DIC
(From_Typ
)
22190 and then not Has_Inherited_DIC
(Typ
)
22192 Set_Has_Inherited_DIC
(Typ
);
22195 if Has_Own_DIC
(From_Typ
) and then not Has_Own_DIC
(Typ
) then
22196 Set_Has_Own_DIC
(Typ
);
22199 if Present
(DIC_Proc
) and then No
(DIC_Procedure
(Typ
)) then
22200 Set_DIC_Procedure
(Typ
, DIC_Proc
);
22203 end Propagate_DIC_Attributes
;
22205 ------------------------------------
22206 -- Propagate_Invariant_Attributes --
22207 ------------------------------------
22209 procedure Propagate_Invariant_Attributes
22211 From_Typ
: Entity_Id
)
22213 Full_IP
: Entity_Id
;
22214 Part_IP
: Entity_Id
;
22217 if Present
(Typ
) and then Present
(From_Typ
) then
22218 pragma Assert
(Is_Type
(Typ
) and then Is_Type
(From_Typ
));
22220 -- Nothing to do if both the source and the destination denote the
22223 if From_Typ
= Typ
then
22227 Full_IP
:= Invariant_Procedure
(From_Typ
);
22228 Part_IP
:= Partial_Invariant_Procedure
(From_Typ
);
22230 -- The setting of the attributes is intentionally conservative. This
22231 -- prevents accidental clobbering of enabled attributes.
22233 if Has_Inheritable_Invariants
(From_Typ
)
22234 and then not Has_Inheritable_Invariants
(Typ
)
22236 Set_Has_Inheritable_Invariants
(Typ
, True);
22239 if Has_Inherited_Invariants
(From_Typ
)
22240 and then not Has_Inherited_Invariants
(Typ
)
22242 Set_Has_Inherited_Invariants
(Typ
, True);
22245 if Has_Own_Invariants
(From_Typ
)
22246 and then not Has_Own_Invariants
(Typ
)
22248 Set_Has_Own_Invariants
(Typ
, True);
22251 if Present
(Full_IP
) and then No
(Invariant_Procedure
(Typ
)) then
22252 Set_Invariant_Procedure
(Typ
, Full_IP
);
22255 if Present
(Part_IP
) and then No
(Partial_Invariant_Procedure
(Typ
))
22257 Set_Partial_Invariant_Procedure
(Typ
, Part_IP
);
22260 end Propagate_Invariant_Attributes
;
22262 ---------------------------------------
22263 -- Record_Possible_Part_Of_Reference --
22264 ---------------------------------------
22266 procedure Record_Possible_Part_Of_Reference
22267 (Var_Id
: Entity_Id
;
22270 Encap
: constant Entity_Id
:= Encapsulating_State
(Var_Id
);
22274 -- The variable is a constituent of a single protected/task type. Such
22275 -- a variable acts as a component of the type and must appear within a
22276 -- specific region (SPARK RM 9.3). Instead of recording the reference,
22277 -- verify its legality now.
22279 if Present
(Encap
) and then Is_Single_Concurrent_Object
(Encap
) then
22280 Check_Part_Of_Reference
(Var_Id
, Ref
);
22282 -- The variable is subject to pragma Part_Of and may eventually become a
22283 -- constituent of a single protected/task type. Record the reference to
22284 -- verify its placement when the contract of the variable is analyzed.
22286 elsif Present
(Get_Pragma
(Var_Id
, Pragma_Part_Of
)) then
22287 Refs
:= Part_Of_References
(Var_Id
);
22290 Refs
:= New_Elmt_List
;
22291 Set_Part_Of_References
(Var_Id
, Refs
);
22294 Append_Elmt
(Ref
, Refs
);
22296 end Record_Possible_Part_Of_Reference
;
22302 function Referenced
(Id
: Entity_Id
; Expr
: Node_Id
) return Boolean is
22303 Seen
: Boolean := False;
22305 function Is_Reference
(N
: Node_Id
) return Traverse_Result
;
22306 -- Determine whether node N denotes a reference to Id. If this is the
22307 -- case, set global flag Seen to True and stop the traversal.
22313 function Is_Reference
(N
: Node_Id
) return Traverse_Result
is
22315 if Is_Entity_Name
(N
)
22316 and then Present
(Entity
(N
))
22317 and then Entity
(N
) = Id
22326 procedure Inspect_Expression
is new Traverse_Proc
(Is_Reference
);
22328 -- Start of processing for Referenced
22331 Inspect_Expression
(Expr
);
22335 ------------------------------------
22336 -- References_Generic_Formal_Type --
22337 ------------------------------------
22339 function References_Generic_Formal_Type
(N
: Node_Id
) return Boolean is
22341 function Process
(N
: Node_Id
) return Traverse_Result
;
22342 -- Process one node in search for generic formal type
22348 function Process
(N
: Node_Id
) return Traverse_Result
is
22350 if Nkind
(N
) in N_Has_Entity
then
22352 E
: constant Entity_Id
:= Entity
(N
);
22354 if Present
(E
) then
22355 if Is_Generic_Type
(E
) then
22357 elsif Present
(Etype
(E
))
22358 and then Is_Generic_Type
(Etype
(E
))
22369 function Traverse
is new Traverse_Func
(Process
);
22370 -- Traverse tree to look for generic type
22373 if Inside_A_Generic
then
22374 return Traverse
(N
) = Abandon
;
22378 end References_Generic_Formal_Type
;
22380 -------------------
22381 -- Remove_Entity --
22382 -------------------
22384 procedure Remove_Entity
(Id
: Entity_Id
) is
22385 Scop
: constant Entity_Id
:= Scope
(Id
);
22386 Prev_Id
: Entity_Id
;
22389 -- Remove the entity from the homonym chain. When the entity is the
22390 -- head of the chain, associate the entry in the name table with its
22391 -- homonym effectively making it the new head of the chain.
22393 if Current_Entity
(Id
) = Id
then
22394 Set_Name_Entity_Id
(Chars
(Id
), Homonym
(Id
));
22396 -- Otherwise link the previous and next homonyms
22399 Prev_Id
:= Current_Entity
(Id
);
22400 while Present
(Prev_Id
) and then Homonym
(Prev_Id
) /= Id
loop
22401 Prev_Id
:= Homonym
(Prev_Id
);
22404 Set_Homonym
(Prev_Id
, Homonym
(Id
));
22407 -- Remove the entity from the scope entity chain. When the entity is
22408 -- the head of the chain, set the next entity as the new head of the
22411 if First_Entity
(Scop
) = Id
then
22413 Set_First_Entity
(Scop
, Next_Entity
(Id
));
22415 -- Otherwise the entity is either in the middle of the chain or it acts
22416 -- as its tail. Traverse and link the previous and next entities.
22419 Prev_Id
:= First_Entity
(Scop
);
22420 while Present
(Prev_Id
) and then Next_Entity
(Prev_Id
) /= Id
loop
22421 Next_Entity
(Prev_Id
);
22424 Set_Next_Entity
(Prev_Id
, Next_Entity
(Id
));
22427 -- Handle the case where the entity acts as the tail of the scope entity
22430 if Last_Entity
(Scop
) = Id
then
22431 Set_Last_Entity
(Scop
, Prev_Id
);
22435 --------------------
22436 -- Remove_Homonym --
22437 --------------------
22439 procedure Remove_Homonym
(E
: Entity_Id
) is
22440 Prev
: Entity_Id
:= Empty
;
22444 if E
= Current_Entity
(E
) then
22445 if Present
(Homonym
(E
)) then
22446 Set_Current_Entity
(Homonym
(E
));
22448 Set_Name_Entity_Id
(Chars
(E
), Empty
);
22452 H
:= Current_Entity
(E
);
22453 while Present
(H
) and then H
/= E
loop
22458 -- If E is not on the homonym chain, nothing to do
22460 if Present
(H
) then
22461 Set_Homonym
(Prev
, Homonym
(E
));
22464 end Remove_Homonym
;
22466 ------------------------------
22467 -- Remove_Overloaded_Entity --
22468 ------------------------------
22470 procedure Remove_Overloaded_Entity
(Id
: Entity_Id
) is
22471 procedure Remove_Primitive_Of
(Typ
: Entity_Id
);
22472 -- Remove primitive subprogram Id from the list of primitives that
22473 -- belong to type Typ.
22475 -------------------------
22476 -- Remove_Primitive_Of --
22477 -------------------------
22479 procedure Remove_Primitive_Of
(Typ
: Entity_Id
) is
22483 if Is_Tagged_Type
(Typ
) then
22484 Prims
:= Direct_Primitive_Operations
(Typ
);
22486 if Present
(Prims
) then
22487 Remove
(Prims
, Id
);
22490 end Remove_Primitive_Of
;
22494 Formal
: Entity_Id
;
22496 -- Start of processing for Remove_Overloaded_Entity
22499 -- Remove the entity from both the homonym and scope chains
22501 Remove_Entity
(Id
);
22503 -- The entity denotes a primitive subprogram. Remove it from the list of
22504 -- primitives of the associated controlling type.
22506 if Ekind_In
(Id
, E_Function
, E_Procedure
) and then Is_Primitive
(Id
) then
22507 Formal
:= First_Formal
(Id
);
22508 while Present
(Formal
) loop
22509 if Is_Controlling_Formal
(Formal
) then
22510 Remove_Primitive_Of
(Etype
(Formal
));
22514 Next_Formal
(Formal
);
22517 if Ekind
(Id
) = E_Function
and then Has_Controlling_Result
(Id
) then
22518 Remove_Primitive_Of
(Etype
(Id
));
22521 end Remove_Overloaded_Entity
;
22523 ---------------------
22524 -- Rep_To_Pos_Flag --
22525 ---------------------
22527 function Rep_To_Pos_Flag
(E
: Entity_Id
; Loc
: Source_Ptr
) return Node_Id
is
22529 return New_Occurrence_Of
22530 (Boolean_Literals
(not Range_Checks_Suppressed
(E
)), Loc
);
22531 end Rep_To_Pos_Flag
;
22533 --------------------
22534 -- Require_Entity --
22535 --------------------
22537 procedure Require_Entity
(N
: Node_Id
) is
22539 if Is_Entity_Name
(N
) and then No
(Entity
(N
)) then
22540 if Total_Errors_Detected
/= 0 then
22541 Set_Entity
(N
, Any_Id
);
22543 raise Program_Error
;
22546 end Require_Entity
;
22548 ------------------------------
22549 -- Requires_Transient_Scope --
22550 ------------------------------
22552 -- A transient scope is required when variable-sized temporaries are
22553 -- allocated on the secondary stack, or when finalization actions must be
22554 -- generated before the next instruction.
22556 function Requires_Transient_Scope
(Id
: Entity_Id
) return Boolean is
22557 Old_Result
: constant Boolean := Old_Requires_Transient_Scope
(Id
);
22560 if Debug_Flag_QQ
then
22565 New_Result
: constant Boolean := New_Requires_Transient_Scope
(Id
);
22568 -- Assert that we're not putting things on the secondary stack if we
22569 -- didn't before; we are trying to AVOID secondary stack when
22572 if not Old_Result
then
22573 pragma Assert
(not New_Result
);
22577 if New_Result
/= Old_Result
then
22578 Results_Differ
(Id
, Old_Result
, New_Result
);
22583 end Requires_Transient_Scope
;
22585 --------------------
22586 -- Results_Differ --
22587 --------------------
22589 procedure Results_Differ
22595 if False then -- False to disable; True for debugging
22596 Treepr
.Print_Tree_Node
(Id
);
22598 if Old_Val
= New_Val
then
22599 raise Program_Error
;
22602 end Results_Differ
;
22604 --------------------------
22605 -- Reset_Analyzed_Flags --
22606 --------------------------
22608 procedure Reset_Analyzed_Flags
(N
: Node_Id
) is
22609 function Clear_Analyzed
(N
: Node_Id
) return Traverse_Result
;
22610 -- Function used to reset Analyzed flags in tree. Note that we do
22611 -- not reset Analyzed flags in entities, since there is no need to
22612 -- reanalyze entities, and indeed, it is wrong to do so, since it
22613 -- can result in generating auxiliary stuff more than once.
22615 --------------------
22616 -- Clear_Analyzed --
22617 --------------------
22619 function Clear_Analyzed
(N
: Node_Id
) return Traverse_Result
is
22621 if Nkind
(N
) not in N_Entity
then
22622 Set_Analyzed
(N
, False);
22626 end Clear_Analyzed
;
22628 procedure Reset_Analyzed
is new Traverse_Proc
(Clear_Analyzed
);
22630 -- Start of processing for Reset_Analyzed_Flags
22633 Reset_Analyzed
(N
);
22634 end Reset_Analyzed_Flags
;
22636 ------------------------
22637 -- Restore_SPARK_Mode --
22638 ------------------------
22640 procedure Restore_SPARK_Mode
22641 (Mode
: SPARK_Mode_Type
;
22645 SPARK_Mode
:= Mode
;
22646 SPARK_Mode_Pragma
:= Prag
;
22647 end Restore_SPARK_Mode
;
22649 --------------------------------
22650 -- Returns_Unconstrained_Type --
22651 --------------------------------
22653 function Returns_Unconstrained_Type
(Subp
: Entity_Id
) return Boolean is
22655 return Ekind
(Subp
) = E_Function
22656 and then not Is_Scalar_Type
(Etype
(Subp
))
22657 and then not Is_Access_Type
(Etype
(Subp
))
22658 and then not Is_Constrained
(Etype
(Subp
));
22659 end Returns_Unconstrained_Type
;
22661 ----------------------------
22662 -- Root_Type_Of_Full_View --
22663 ----------------------------
22665 function Root_Type_Of_Full_View
(T
: Entity_Id
) return Entity_Id
is
22666 Rtyp
: constant Entity_Id
:= Root_Type
(T
);
22669 -- The root type of the full view may itself be a private type. Keep
22670 -- looking for the ultimate derivation parent.
22672 if Is_Private_Type
(Rtyp
) and then Present
(Full_View
(Rtyp
)) then
22673 return Root_Type_Of_Full_View
(Full_View
(Rtyp
));
22677 end Root_Type_Of_Full_View
;
22679 ---------------------------
22680 -- Safe_To_Capture_Value --
22681 ---------------------------
22683 function Safe_To_Capture_Value
22686 Cond
: Boolean := False) return Boolean
22689 -- The only entities for which we track constant values are variables
22690 -- which are not renamings, constants, out parameters, and in out
22691 -- parameters, so check if we have this case.
22693 -- Note: it may seem odd to track constant values for constants, but in
22694 -- fact this routine is used for other purposes than simply capturing
22695 -- the value. In particular, the setting of Known[_Non]_Null.
22697 if (Ekind
(Ent
) = E_Variable
and then No
(Renamed_Object
(Ent
)))
22699 Ekind_In
(Ent
, E_Constant
, E_Out_Parameter
, E_In_Out_Parameter
)
22703 -- For conditionals, we also allow loop parameters and all formals,
22704 -- including in parameters.
22706 elsif Cond
and then Ekind_In
(Ent
, E_Loop_Parameter
, E_In_Parameter
) then
22709 -- For all other cases, not just unsafe, but impossible to capture
22710 -- Current_Value, since the above are the only entities which have
22711 -- Current_Value fields.
22717 -- Skip if volatile or aliased, since funny things might be going on in
22718 -- these cases which we cannot necessarily track. Also skip any variable
22719 -- for which an address clause is given, or whose address is taken. Also
22720 -- never capture value of library level variables (an attempt to do so
22721 -- can occur in the case of package elaboration code).
22723 if Treat_As_Volatile
(Ent
)
22724 or else Is_Aliased
(Ent
)
22725 or else Present
(Address_Clause
(Ent
))
22726 or else Address_Taken
(Ent
)
22727 or else (Is_Library_Level_Entity
(Ent
)
22728 and then Ekind
(Ent
) = E_Variable
)
22733 -- OK, all above conditions are met. We also require that the scope of
22734 -- the reference be the same as the scope of the entity, not counting
22735 -- packages and blocks and loops.
22738 E_Scope
: constant Entity_Id
:= Scope
(Ent
);
22739 R_Scope
: Entity_Id
;
22742 R_Scope
:= Current_Scope
;
22743 while R_Scope
/= Standard_Standard
loop
22744 exit when R_Scope
= E_Scope
;
22746 if not Ekind_In
(R_Scope
, E_Package
, E_Block
, E_Loop
) then
22749 R_Scope
:= Scope
(R_Scope
);
22754 -- We also require that the reference does not appear in a context
22755 -- where it is not sure to be executed (i.e. a conditional context
22756 -- or an exception handler). We skip this if Cond is True, since the
22757 -- capturing of values from conditional tests handles this ok.
22770 -- Seems dubious that case expressions are not handled here ???
22773 while Present
(P
) loop
22774 if Nkind
(P
) = N_If_Statement
22775 or else Nkind
(P
) = N_Case_Statement
22776 or else (Nkind
(P
) in N_Short_Circuit
22777 and then Desc
= Right_Opnd
(P
))
22778 or else (Nkind
(P
) = N_If_Expression
22779 and then Desc
/= First
(Expressions
(P
)))
22780 or else Nkind
(P
) = N_Exception_Handler
22781 or else Nkind
(P
) = N_Selective_Accept
22782 or else Nkind
(P
) = N_Conditional_Entry_Call
22783 or else Nkind
(P
) = N_Timed_Entry_Call
22784 or else Nkind
(P
) = N_Asynchronous_Select
22792 -- A special Ada 2012 case: the original node may be part
22793 -- of the else_actions of a conditional expression, in which
22794 -- case it might not have been expanded yet, and appears in
22795 -- a non-syntactic list of actions. In that case it is clearly
22796 -- not safe to save a value.
22799 and then Is_List_Member
(Desc
)
22800 and then No
(Parent
(List_Containing
(Desc
)))
22808 -- OK, looks safe to set value
22811 end Safe_To_Capture_Value
;
22817 function Same_Name
(N1
, N2
: Node_Id
) return Boolean is
22818 K1
: constant Node_Kind
:= Nkind
(N1
);
22819 K2
: constant Node_Kind
:= Nkind
(N2
);
22822 if (K1
= N_Identifier
or else K1
= N_Defining_Identifier
)
22823 and then (K2
= N_Identifier
or else K2
= N_Defining_Identifier
)
22825 return Chars
(N1
) = Chars
(N2
);
22827 elsif (K1
= N_Selected_Component
or else K1
= N_Expanded_Name
)
22828 and then (K2
= N_Selected_Component
or else K2
= N_Expanded_Name
)
22830 return Same_Name
(Selector_Name
(N1
), Selector_Name
(N2
))
22831 and then Same_Name
(Prefix
(N1
), Prefix
(N2
));
22842 function Same_Object
(Node1
, Node2
: Node_Id
) return Boolean is
22843 N1
: constant Node_Id
:= Original_Node
(Node1
);
22844 N2
: constant Node_Id
:= Original_Node
(Node2
);
22845 -- We do the tests on original nodes, since we are most interested
22846 -- in the original source, not any expansion that got in the way.
22848 K1
: constant Node_Kind
:= Nkind
(N1
);
22849 K2
: constant Node_Kind
:= Nkind
(N2
);
22852 -- First case, both are entities with same entity
22854 if K1
in N_Has_Entity
and then K2
in N_Has_Entity
then
22856 EN1
: constant Entity_Id
:= Entity
(N1
);
22857 EN2
: constant Entity_Id
:= Entity
(N2
);
22859 if Present
(EN1
) and then Present
(EN2
)
22860 and then (Ekind_In
(EN1
, E_Variable
, E_Constant
)
22861 or else Is_Formal
(EN1
))
22869 -- Second case, selected component with same selector, same record
22871 if K1
= N_Selected_Component
22872 and then K2
= N_Selected_Component
22873 and then Chars
(Selector_Name
(N1
)) = Chars
(Selector_Name
(N2
))
22875 return Same_Object
(Prefix
(N1
), Prefix
(N2
));
22877 -- Third case, indexed component with same subscripts, same array
22879 elsif K1
= N_Indexed_Component
22880 and then K2
= N_Indexed_Component
22881 and then Same_Object
(Prefix
(N1
), Prefix
(N2
))
22886 E1
:= First
(Expressions
(N1
));
22887 E2
:= First
(Expressions
(N2
));
22888 while Present
(E1
) loop
22889 if not Same_Value
(E1
, E2
) then
22900 -- Fourth case, slice of same array with same bounds
22903 and then K2
= N_Slice
22904 and then Nkind
(Discrete_Range
(N1
)) = N_Range
22905 and then Nkind
(Discrete_Range
(N2
)) = N_Range
22906 and then Same_Value
(Low_Bound
(Discrete_Range
(N1
)),
22907 Low_Bound
(Discrete_Range
(N2
)))
22908 and then Same_Value
(High_Bound
(Discrete_Range
(N1
)),
22909 High_Bound
(Discrete_Range
(N2
)))
22911 return Same_Name
(Prefix
(N1
), Prefix
(N2
));
22913 -- All other cases, not clearly the same object
22924 function Same_Type
(T1
, T2
: Entity_Id
) return Boolean is
22929 elsif not Is_Constrained
(T1
)
22930 and then not Is_Constrained
(T2
)
22931 and then Base_Type
(T1
) = Base_Type
(T2
)
22935 -- For now don't bother with case of identical constraints, to be
22936 -- fiddled with later on perhaps (this is only used for optimization
22937 -- purposes, so it is not critical to do a best possible job)
22948 function Same_Value
(Node1
, Node2
: Node_Id
) return Boolean is
22950 if Compile_Time_Known_Value
(Node1
)
22951 and then Compile_Time_Known_Value
(Node2
)
22953 -- Handle properly compile-time expressions that are not
22956 if Is_String_Type
(Etype
(Node1
)) then
22957 return Expr_Value_S
(Node1
) = Expr_Value_S
(Node2
);
22960 return Expr_Value
(Node1
) = Expr_Value
(Node2
);
22963 elsif Same_Object
(Node1
, Node2
) then
22970 --------------------
22971 -- Set_SPARK_Mode --
22972 --------------------
22974 procedure Set_SPARK_Mode
(Context
: Entity_Id
) is
22976 -- Do not consider illegal or partially decorated constructs
22978 if Ekind
(Context
) = E_Void
or else Error_Posted
(Context
) then
22981 elsif Present
(SPARK_Pragma
(Context
)) then
22983 (Mode
=> Get_SPARK_Mode_From_Annotation
(SPARK_Pragma
(Context
)),
22984 Prag
=> SPARK_Pragma
(Context
));
22986 end Set_SPARK_Mode
;
22988 -------------------------
22989 -- Scalar_Part_Present --
22990 -------------------------
22992 function Scalar_Part_Present
(T
: Entity_Id
) return Boolean is
22996 if Is_Scalar_Type
(T
) then
22999 elsif Is_Array_Type
(T
) then
23000 return Scalar_Part_Present
(Component_Type
(T
));
23002 elsif Is_Record_Type
(T
) or else Has_Discriminants
(T
) then
23003 C
:= First_Component_Or_Discriminant
(T
);
23004 while Present
(C
) loop
23005 if Scalar_Part_Present
(Etype
(C
)) then
23008 Next_Component_Or_Discriminant
(C
);
23014 end Scalar_Part_Present
;
23016 ------------------------
23017 -- Scope_Is_Transient --
23018 ------------------------
23020 function Scope_Is_Transient
return Boolean is
23022 return Scope_Stack
.Table
(Scope_Stack
.Last
).Is_Transient
;
23023 end Scope_Is_Transient
;
23029 function Scope_Within
23030 (Inner
: Entity_Id
;
23031 Outer
: Entity_Id
) return Boolean
23037 while Present
(Curr
) and then Curr
/= Standard_Standard
loop
23038 Curr
:= Scope
(Curr
);
23040 if Curr
= Outer
then
23048 --------------------------
23049 -- Scope_Within_Or_Same --
23050 --------------------------
23052 function Scope_Within_Or_Same
23053 (Inner
: Entity_Id
;
23054 Outer
: Entity_Id
) return Boolean
23060 while Present
(Curr
) and then Curr
/= Standard_Standard
loop
23061 if Curr
= Outer
then
23065 Curr
:= Scope
(Curr
);
23069 end Scope_Within_Or_Same
;
23071 --------------------
23072 -- Set_Convention --
23073 --------------------
23075 procedure Set_Convention
(E
: Entity_Id
; Val
: Snames
.Convention_Id
) is
23077 Basic_Set_Convention
(E
, Val
);
23080 and then Is_Access_Subprogram_Type
(Base_Type
(E
))
23081 and then Has_Foreign_Convention
(E
)
23084 -- A pragma Convention in an instance may apply to the subtype
23085 -- created for a formal, in which case we have already verified
23086 -- that conventions of actual and formal match and there is nothing
23087 -- to flag on the subtype.
23089 if In_Instance
then
23092 Set_Can_Use_Internal_Rep
(E
, False);
23096 -- If E is an object, including a component, and the type of E is an
23097 -- anonymous access type with no convention set, then also set the
23098 -- convention of the anonymous access type. We do not do this for
23099 -- anonymous protected types, since protected types always have the
23100 -- default convention.
23102 if Present
(Etype
(E
))
23103 and then (Is_Object
(E
)
23105 -- Allow E_Void (happens for pragma Convention appearing
23106 -- in the middle of a record applying to a component)
23108 or else Ekind
(E
) = E_Void
)
23111 Typ
: constant Entity_Id
:= Etype
(E
);
23114 if Ekind_In
(Typ
, E_Anonymous_Access_Type
,
23115 E_Anonymous_Access_Subprogram_Type
)
23116 and then not Has_Convention_Pragma
(Typ
)
23118 Basic_Set_Convention
(Typ
, Val
);
23119 Set_Has_Convention_Pragma
(Typ
);
23121 -- And for the access subprogram type, deal similarly with the
23122 -- designated E_Subprogram_Type, which is always internal.
23124 if Ekind
(Typ
) = E_Anonymous_Access_Subprogram_Type
then
23126 Dtype
: constant Entity_Id
:= Designated_Type
(Typ
);
23128 if Ekind
(Dtype
) = E_Subprogram_Type
23129 and then not Has_Convention_Pragma
(Dtype
)
23131 Basic_Set_Convention
(Dtype
, Val
);
23132 Set_Has_Convention_Pragma
(Dtype
);
23139 end Set_Convention
;
23141 ------------------------
23142 -- Set_Current_Entity --
23143 ------------------------
23145 -- The given entity is to be set as the currently visible definition of its
23146 -- associated name (i.e. the Node_Id associated with its name). All we have
23147 -- to do is to get the name from the identifier, and then set the
23148 -- associated Node_Id to point to the given entity.
23150 procedure Set_Current_Entity
(E
: Entity_Id
) is
23152 Set_Name_Entity_Id
(Chars
(E
), E
);
23153 end Set_Current_Entity
;
23155 ---------------------------
23156 -- Set_Debug_Info_Needed --
23157 ---------------------------
23159 procedure Set_Debug_Info_Needed
(T
: Entity_Id
) is
23161 procedure Set_Debug_Info_Needed_If_Not_Set
(E
: Entity_Id
);
23162 pragma Inline
(Set_Debug_Info_Needed_If_Not_Set
);
23163 -- Used to set debug info in a related node if not set already
23165 --------------------------------------
23166 -- Set_Debug_Info_Needed_If_Not_Set --
23167 --------------------------------------
23169 procedure Set_Debug_Info_Needed_If_Not_Set
(E
: Entity_Id
) is
23171 if Present
(E
) and then not Needs_Debug_Info
(E
) then
23172 Set_Debug_Info_Needed
(E
);
23174 -- For a private type, indicate that the full view also needs
23175 -- debug information.
23178 and then Is_Private_Type
(E
)
23179 and then Present
(Full_View
(E
))
23181 Set_Debug_Info_Needed
(Full_View
(E
));
23184 end Set_Debug_Info_Needed_If_Not_Set
;
23186 -- Start of processing for Set_Debug_Info_Needed
23189 -- Nothing to do if argument is Empty or has Debug_Info_Off set, which
23190 -- indicates that Debug_Info_Needed is never required for the entity.
23191 -- Nothing to do if entity comes from a predefined file. Library files
23192 -- are compiled without debug information, but inlined bodies of these
23193 -- routines may appear in user code, and debug information on them ends
23194 -- up complicating debugging the user code.
23197 or else Debug_Info_Off
(T
)
23201 elsif In_Inlined_Body
and then In_Predefined_Unit
(T
) then
23202 Set_Needs_Debug_Info
(T
, False);
23205 -- Set flag in entity itself. Note that we will go through the following
23206 -- circuitry even if the flag is already set on T. That's intentional,
23207 -- it makes sure that the flag will be set in subsidiary entities.
23209 Set_Needs_Debug_Info
(T
);
23211 -- Set flag on subsidiary entities if not set already
23213 if Is_Object
(T
) then
23214 Set_Debug_Info_Needed_If_Not_Set
(Etype
(T
));
23216 elsif Is_Type
(T
) then
23217 Set_Debug_Info_Needed_If_Not_Set
(Etype
(T
));
23219 if Is_Record_Type
(T
) then
23221 Ent
: Entity_Id
:= First_Entity
(T
);
23223 while Present
(Ent
) loop
23224 Set_Debug_Info_Needed_If_Not_Set
(Ent
);
23229 -- For a class wide subtype, we also need debug information
23230 -- for the equivalent type.
23232 if Ekind
(T
) = E_Class_Wide_Subtype
then
23233 Set_Debug_Info_Needed_If_Not_Set
(Equivalent_Type
(T
));
23236 elsif Is_Array_Type
(T
) then
23237 Set_Debug_Info_Needed_If_Not_Set
(Component_Type
(T
));
23240 Indx
: Node_Id
:= First_Index
(T
);
23242 while Present
(Indx
) loop
23243 Set_Debug_Info_Needed_If_Not_Set
(Etype
(Indx
));
23244 Indx
:= Next_Index
(Indx
);
23248 -- For a packed array type, we also need debug information for
23249 -- the type used to represent the packed array. Conversely, we
23250 -- also need it for the former if we need it for the latter.
23252 if Is_Packed
(T
) then
23253 Set_Debug_Info_Needed_If_Not_Set
(Packed_Array_Impl_Type
(T
));
23256 if Is_Packed_Array_Impl_Type
(T
) then
23257 Set_Debug_Info_Needed_If_Not_Set
(Original_Array_Type
(T
));
23260 elsif Is_Access_Type
(T
) then
23261 Set_Debug_Info_Needed_If_Not_Set
(Directly_Designated_Type
(T
));
23263 elsif Is_Private_Type
(T
) then
23265 FV
: constant Entity_Id
:= Full_View
(T
);
23268 Set_Debug_Info_Needed_If_Not_Set
(FV
);
23270 -- If the full view is itself a derived private type, we need
23271 -- debug information on its underlying type.
23274 and then Is_Private_Type
(FV
)
23275 and then Present
(Underlying_Full_View
(FV
))
23277 Set_Needs_Debug_Info
(Underlying_Full_View
(FV
));
23281 elsif Is_Protected_Type
(T
) then
23282 Set_Debug_Info_Needed_If_Not_Set
(Corresponding_Record_Type
(T
));
23284 elsif Is_Scalar_Type
(T
) then
23286 -- If the subrange bounds are materialized by dedicated constant
23287 -- objects, also include them in the debug info to make sure the
23288 -- debugger can properly use them.
23290 if Present
(Scalar_Range
(T
))
23291 and then Nkind
(Scalar_Range
(T
)) = N_Range
23294 Low_Bnd
: constant Node_Id
:= Type_Low_Bound
(T
);
23295 High_Bnd
: constant Node_Id
:= Type_High_Bound
(T
);
23298 if Is_Entity_Name
(Low_Bnd
) then
23299 Set_Debug_Info_Needed_If_Not_Set
(Entity
(Low_Bnd
));
23302 if Is_Entity_Name
(High_Bnd
) then
23303 Set_Debug_Info_Needed_If_Not_Set
(Entity
(High_Bnd
));
23309 end Set_Debug_Info_Needed
;
23311 ----------------------------
23312 -- Set_Entity_With_Checks --
23313 ----------------------------
23315 procedure Set_Entity_With_Checks
(N
: Node_Id
; Val
: Entity_Id
) is
23316 Val_Actual
: Entity_Id
;
23318 Post_Node
: Node_Id
;
23321 -- Unconditionally set the entity
23323 Set_Entity
(N
, Val
);
23325 -- The node to post on is the selector in the case of an expanded name,
23326 -- and otherwise the node itself.
23328 if Nkind
(N
) = N_Expanded_Name
then
23329 Post_Node
:= Selector_Name
(N
);
23334 -- Check for violation of No_Fixed_IO
23336 if Restriction_Check_Required
(No_Fixed_IO
)
23338 ((RTU_Loaded
(Ada_Text_IO
)
23339 and then (Is_RTE
(Val
, RE_Decimal_IO
)
23341 Is_RTE
(Val
, RE_Fixed_IO
)))
23344 (RTU_Loaded
(Ada_Wide_Text_IO
)
23345 and then (Is_RTE
(Val
, RO_WT_Decimal_IO
)
23347 Is_RTE
(Val
, RO_WT_Fixed_IO
)))
23350 (RTU_Loaded
(Ada_Wide_Wide_Text_IO
)
23351 and then (Is_RTE
(Val
, RO_WW_Decimal_IO
)
23353 Is_RTE
(Val
, RO_WW_Fixed_IO
))))
23355 -- A special extra check, don't complain about a reference from within
23356 -- the Ada.Interrupts package itself!
23358 and then not In_Same_Extended_Unit
(N
, Val
)
23360 Check_Restriction
(No_Fixed_IO
, Post_Node
);
23363 -- Remaining checks are only done on source nodes. Note that we test
23364 -- for violation of No_Fixed_IO even on non-source nodes, because the
23365 -- cases for checking violations of this restriction are instantiations
23366 -- where the reference in the instance has Comes_From_Source False.
23368 if not Comes_From_Source
(N
) then
23372 -- Check for violation of No_Abort_Statements, which is triggered by
23373 -- call to Ada.Task_Identification.Abort_Task.
23375 if Restriction_Check_Required
(No_Abort_Statements
)
23376 and then (Is_RTE
(Val
, RE_Abort_Task
))
23378 -- A special extra check, don't complain about a reference from within
23379 -- the Ada.Task_Identification package itself!
23381 and then not In_Same_Extended_Unit
(N
, Val
)
23383 Check_Restriction
(No_Abort_Statements
, Post_Node
);
23386 if Val
= Standard_Long_Long_Integer
then
23387 Check_Restriction
(No_Long_Long_Integers
, Post_Node
);
23390 -- Check for violation of No_Dynamic_Attachment
23392 if Restriction_Check_Required
(No_Dynamic_Attachment
)
23393 and then RTU_Loaded
(Ada_Interrupts
)
23394 and then (Is_RTE
(Val
, RE_Is_Reserved
) or else
23395 Is_RTE
(Val
, RE_Is_Attached
) or else
23396 Is_RTE
(Val
, RE_Current_Handler
) or else
23397 Is_RTE
(Val
, RE_Attach_Handler
) or else
23398 Is_RTE
(Val
, RE_Exchange_Handler
) or else
23399 Is_RTE
(Val
, RE_Detach_Handler
) or else
23400 Is_RTE
(Val
, RE_Reference
))
23402 -- A special extra check, don't complain about a reference from within
23403 -- the Ada.Interrupts package itself!
23405 and then not In_Same_Extended_Unit
(N
, Val
)
23407 Check_Restriction
(No_Dynamic_Attachment
, Post_Node
);
23410 -- Check for No_Implementation_Identifiers
23412 if Restriction_Check_Required
(No_Implementation_Identifiers
) then
23414 -- We have an implementation defined entity if it is marked as
23415 -- implementation defined, or is defined in a package marked as
23416 -- implementation defined. However, library packages themselves
23417 -- are excluded (we don't want to flag Interfaces itself, just
23418 -- the entities within it).
23420 if (Is_Implementation_Defined
(Val
)
23422 (Present
(Scope
(Val
))
23423 and then Is_Implementation_Defined
(Scope
(Val
))))
23424 and then not (Ekind_In
(Val
, E_Package
, E_Generic_Package
)
23425 and then Is_Library_Level_Entity
(Val
))
23427 Check_Restriction
(No_Implementation_Identifiers
, Post_Node
);
23431 -- Do the style check
23434 and then not Suppress_Style_Checks
(Val
)
23435 and then not In_Instance
23437 if Nkind
(N
) = N_Identifier
then
23439 elsif Nkind
(N
) = N_Expanded_Name
then
23440 Nod
:= Selector_Name
(N
);
23445 -- A special situation arises for derived operations, where we want
23446 -- to do the check against the parent (since the Sloc of the derived
23447 -- operation points to the derived type declaration itself).
23450 while not Comes_From_Source
(Val_Actual
)
23451 and then Nkind
(Val_Actual
) in N_Entity
23452 and then (Ekind
(Val_Actual
) = E_Enumeration_Literal
23453 or else Is_Subprogram_Or_Generic_Subprogram
(Val_Actual
))
23454 and then Present
(Alias
(Val_Actual
))
23456 Val_Actual
:= Alias
(Val_Actual
);
23459 -- Renaming declarations for generic actuals do not come from source,
23460 -- and have a different name from that of the entity they rename, so
23461 -- there is no style check to perform here.
23463 if Chars
(Nod
) = Chars
(Val_Actual
) then
23464 Style
.Check_Identifier
(Nod
, Val_Actual
);
23468 Set_Entity
(N
, Val
);
23469 end Set_Entity_With_Checks
;
23471 ------------------------
23472 -- Set_Name_Entity_Id --
23473 ------------------------
23475 procedure Set_Name_Entity_Id
(Id
: Name_Id
; Val
: Entity_Id
) is
23477 Set_Name_Table_Int
(Id
, Int
(Val
));
23478 end Set_Name_Entity_Id
;
23480 ---------------------
23481 -- Set_Next_Actual --
23482 ---------------------
23484 procedure Set_Next_Actual
(Ass1_Id
: Node_Id
; Ass2_Id
: Node_Id
) is
23486 if Nkind
(Parent
(Ass1_Id
)) = N_Parameter_Association
then
23487 Set_First_Named_Actual
(Parent
(Ass1_Id
), Ass2_Id
);
23489 end Set_Next_Actual
;
23491 ----------------------------------
23492 -- Set_Optimize_Alignment_Flags --
23493 ----------------------------------
23495 procedure Set_Optimize_Alignment_Flags
(E
: Entity_Id
) is
23497 if Optimize_Alignment
= 'S' then
23498 Set_Optimize_Alignment_Space
(E
);
23499 elsif Optimize_Alignment
= 'T' then
23500 Set_Optimize_Alignment_Time
(E
);
23502 end Set_Optimize_Alignment_Flags
;
23504 -----------------------
23505 -- Set_Public_Status --
23506 -----------------------
23508 procedure Set_Public_Status
(Id
: Entity_Id
) is
23509 S
: constant Entity_Id
:= Current_Scope
;
23511 function Within_HSS_Or_If
(E
: Entity_Id
) return Boolean;
23512 -- Determines if E is defined within handled statement sequence or
23513 -- an if statement, returns True if so, False otherwise.
23515 ----------------------
23516 -- Within_HSS_Or_If --
23517 ----------------------
23519 function Within_HSS_Or_If
(E
: Entity_Id
) return Boolean is
23522 N
:= Declaration_Node
(E
);
23529 elsif Nkind_In
(N
, N_Handled_Sequence_Of_Statements
,
23535 end Within_HSS_Or_If
;
23537 -- Start of processing for Set_Public_Status
23540 -- Everything in the scope of Standard is public
23542 if S
= Standard_Standard
then
23543 Set_Is_Public
(Id
);
23545 -- Entity is definitely not public if enclosing scope is not public
23547 elsif not Is_Public
(S
) then
23550 -- An object or function declaration that occurs in a handled sequence
23551 -- of statements or within an if statement is the declaration for a
23552 -- temporary object or local subprogram generated by the expander. It
23553 -- never needs to be made public and furthermore, making it public can
23554 -- cause back end problems.
23556 elsif Nkind_In
(Parent
(Id
), N_Object_Declaration
,
23557 N_Function_Specification
)
23558 and then Within_HSS_Or_If
(Id
)
23562 -- Entities in public packages or records are public
23564 elsif Ekind
(S
) = E_Package
or Is_Record_Type
(S
) then
23565 Set_Is_Public
(Id
);
23567 -- The bounds of an entry family declaration can generate object
23568 -- declarations that are visible to the back-end, e.g. in the
23569 -- the declaration of a composite type that contains tasks.
23571 elsif Is_Concurrent_Type
(S
)
23572 and then not Has_Completion
(S
)
23573 and then Nkind
(Parent
(Id
)) = N_Object_Declaration
23575 Set_Is_Public
(Id
);
23577 end Set_Public_Status
;
23579 -----------------------------
23580 -- Set_Referenced_Modified --
23581 -----------------------------
23583 procedure Set_Referenced_Modified
(N
: Node_Id
; Out_Param
: Boolean) is
23587 -- Deal with indexed or selected component where prefix is modified
23589 if Nkind_In
(N
, N_Indexed_Component
, N_Selected_Component
) then
23590 Pref
:= Prefix
(N
);
23592 -- If prefix is access type, then it is the designated object that is
23593 -- being modified, which means we have no entity to set the flag on.
23595 if No
(Etype
(Pref
)) or else Is_Access_Type
(Etype
(Pref
)) then
23598 -- Otherwise chase the prefix
23601 Set_Referenced_Modified
(Pref
, Out_Param
);
23604 -- Otherwise see if we have an entity name (only other case to process)
23606 elsif Is_Entity_Name
(N
) and then Present
(Entity
(N
)) then
23607 Set_Referenced_As_LHS
(Entity
(N
), not Out_Param
);
23608 Set_Referenced_As_Out_Parameter
(Entity
(N
), Out_Param
);
23610 end Set_Referenced_Modified
;
23616 procedure Set_Rep_Info
(T1
: Entity_Id
; T2
: Entity_Id
) is
23618 Set_Is_Atomic
(T1
, Is_Atomic
(T2
));
23619 Set_Is_Independent
(T1
, Is_Independent
(T2
));
23620 Set_Is_Volatile_Full_Access
(T1
, Is_Volatile_Full_Access
(T2
));
23622 if Is_Base_Type
(T1
) then
23623 Set_Is_Volatile
(T1
, Is_Volatile
(T2
));
23627 ----------------------------
23628 -- Set_Scope_Is_Transient --
23629 ----------------------------
23631 procedure Set_Scope_Is_Transient
(V
: Boolean := True) is
23633 Scope_Stack
.Table
(Scope_Stack
.Last
).Is_Transient
:= V
;
23634 end Set_Scope_Is_Transient
;
23636 -------------------
23637 -- Set_Size_Info --
23638 -------------------
23640 procedure Set_Size_Info
(T1
, T2
: Entity_Id
) is
23642 -- We copy Esize, but not RM_Size, since in general RM_Size is
23643 -- subtype specific and does not get inherited by all subtypes.
23645 Set_Esize
(T1
, Esize
(T2
));
23646 Set_Has_Biased_Representation
(T1
, Has_Biased_Representation
(T2
));
23648 if Is_Discrete_Or_Fixed_Point_Type
(T1
)
23650 Is_Discrete_Or_Fixed_Point_Type
(T2
)
23652 Set_Is_Unsigned_Type
(T1
, Is_Unsigned_Type
(T2
));
23655 Set_Alignment
(T1
, Alignment
(T2
));
23658 ------------------------------
23659 -- Should_Ignore_Pragma_Par --
23660 ------------------------------
23662 function Should_Ignore_Pragma_Par
(Prag_Name
: Name_Id
) return Boolean is
23663 pragma Assert
(Compiler_State
= Parsing
);
23664 -- This one can't work during semantic analysis, because we don't have a
23665 -- correct Current_Source_File.
23667 Result
: constant Boolean :=
23668 Get_Name_Table_Boolean3
(Prag_Name
)
23669 and then not Is_Internal_File_Name
23670 (File_Name
(Current_Source_File
));
23673 end Should_Ignore_Pragma_Par
;
23675 ------------------------------
23676 -- Should_Ignore_Pragma_Sem --
23677 ------------------------------
23679 function Should_Ignore_Pragma_Sem
(N
: Node_Id
) return Boolean is
23680 pragma Assert
(Compiler_State
= Analyzing
);
23681 Prag_Name
: constant Name_Id
:= Pragma_Name
(N
);
23682 Result
: constant Boolean :=
23683 Get_Name_Table_Boolean3
(Prag_Name
)
23684 and then not In_Internal_Unit
(N
);
23688 end Should_Ignore_Pragma_Sem
;
23690 --------------------
23691 -- Static_Boolean --
23692 --------------------
23694 function Static_Boolean
(N
: Node_Id
) return Uint
is
23696 Analyze_And_Resolve
(N
, Standard_Boolean
);
23699 or else Error_Posted
(N
)
23700 or else Etype
(N
) = Any_Type
23705 if Is_OK_Static_Expression
(N
) then
23706 if not Raises_Constraint_Error
(N
) then
23707 return Expr_Value
(N
);
23712 elsif Etype
(N
) = Any_Type
then
23716 Flag_Non_Static_Expr
23717 ("static boolean expression required here", N
);
23720 end Static_Boolean
;
23722 --------------------
23723 -- Static_Integer --
23724 --------------------
23726 function Static_Integer
(N
: Node_Id
) return Uint
is
23728 Analyze_And_Resolve
(N
, Any_Integer
);
23731 or else Error_Posted
(N
)
23732 or else Etype
(N
) = Any_Type
23737 if Is_OK_Static_Expression
(N
) then
23738 if not Raises_Constraint_Error
(N
) then
23739 return Expr_Value
(N
);
23744 elsif Etype
(N
) = Any_Type
then
23748 Flag_Non_Static_Expr
23749 ("static integer expression required here", N
);
23752 end Static_Integer
;
23754 --------------------------
23755 -- Statically_Different --
23756 --------------------------
23758 function Statically_Different
(E1
, E2
: Node_Id
) return Boolean is
23759 R1
: constant Node_Id
:= Get_Referenced_Object
(E1
);
23760 R2
: constant Node_Id
:= Get_Referenced_Object
(E2
);
23762 return Is_Entity_Name
(R1
)
23763 and then Is_Entity_Name
(R2
)
23764 and then Entity
(R1
) /= Entity
(R2
)
23765 and then not Is_Formal
(Entity
(R1
))
23766 and then not Is_Formal
(Entity
(R2
));
23767 end Statically_Different
;
23769 --------------------------------------
23770 -- Subject_To_Loop_Entry_Attributes --
23771 --------------------------------------
23773 function Subject_To_Loop_Entry_Attributes
(N
: Node_Id
) return Boolean is
23779 -- The expansion mechanism transform a loop subject to at least one
23780 -- 'Loop_Entry attribute into a conditional block. Infinite loops lack
23781 -- the conditional part.
23783 if Nkind_In
(Stmt
, N_Block_Statement
, N_If_Statement
)
23784 and then Nkind
(Original_Node
(N
)) = N_Loop_Statement
23786 Stmt
:= Original_Node
(N
);
23790 Nkind
(Stmt
) = N_Loop_Statement
23791 and then Present
(Identifier
(Stmt
))
23792 and then Present
(Entity
(Identifier
(Stmt
)))
23793 and then Has_Loop_Entry_Attributes
(Entity
(Identifier
(Stmt
)));
23794 end Subject_To_Loop_Entry_Attributes
;
23796 -----------------------------
23797 -- Subprogram_Access_Level --
23798 -----------------------------
23800 function Subprogram_Access_Level
(Subp
: Entity_Id
) return Uint
is
23802 if Present
(Alias
(Subp
)) then
23803 return Subprogram_Access_Level
(Alias
(Subp
));
23805 return Scope_Depth
(Enclosing_Dynamic_Scope
(Subp
));
23807 end Subprogram_Access_Level
;
23809 ---------------------
23810 -- Subprogram_Name --
23811 ---------------------
23813 function Subprogram_Name
(N
: Node_Id
) return String is
23814 Buf
: Bounded_String
;
23815 Ent
: Node_Id
:= N
;
23819 while Present
(Ent
) loop
23820 case Nkind
(Ent
) is
23821 when N_Subprogram_Body
=>
23822 Ent
:= Defining_Unit_Name
(Specification
(Ent
));
23825 when N_Subprogram_Declaration
=>
23826 Nod
:= Corresponding_Body
(Ent
);
23828 if Present
(Nod
) then
23831 Ent
:= Defining_Unit_Name
(Specification
(Ent
));
23836 when N_Subprogram_Instantiation
23838 | N_Package_Specification
23840 Ent
:= Defining_Unit_Name
(Ent
);
23843 when N_Protected_Type_Declaration
=>
23844 Ent
:= Corresponding_Body
(Ent
);
23847 when N_Protected_Body
23850 Ent
:= Defining_Identifier
(Ent
);
23857 Ent
:= Parent
(Ent
);
23861 return "unknown subprogram:unknown file:0:0";
23864 -- If the subprogram is a child unit, use its simple name to start the
23865 -- construction of the fully qualified name.
23867 if Nkind
(Ent
) = N_Defining_Program_Unit_Name
then
23868 Ent
:= Defining_Identifier
(Ent
);
23871 Append_Entity_Name
(Buf
, Ent
);
23873 -- Append homonym number if needed
23875 if Nkind
(N
) in N_Entity
and then Has_Homonym
(N
) then
23877 H
: Entity_Id
:= Homonym
(N
);
23881 while Present
(H
) loop
23882 if Scope
(H
) = Scope
(N
) then
23896 -- Append source location of Ent to Buf so that the string will
23897 -- look like "subp:file:line:col".
23900 Loc
: constant Source_Ptr
:= Sloc
(Ent
);
23903 Append
(Buf
, Reference_Name
(Get_Source_File_Index
(Loc
)));
23905 Append
(Buf
, Nat
(Get_Logical_Line_Number
(Loc
)));
23907 Append
(Buf
, Nat
(Get_Column_Number
(Loc
)));
23911 end Subprogram_Name
;
23913 -------------------------------
23914 -- Support_Atomic_Primitives --
23915 -------------------------------
23917 function Support_Atomic_Primitives
(Typ
: Entity_Id
) return Boolean is
23921 -- Verify the alignment of Typ is known
23923 if not Known_Alignment
(Typ
) then
23927 if Known_Static_Esize
(Typ
) then
23928 Size
:= UI_To_Int
(Esize
(Typ
));
23930 -- If the Esize (Object_Size) is unknown at compile time, look at the
23931 -- RM_Size (Value_Size) which may have been set by an explicit rep item.
23933 elsif Known_Static_RM_Size
(Typ
) then
23934 Size
:= UI_To_Int
(RM_Size
(Typ
));
23936 -- Otherwise, the size is considered to be unknown.
23942 -- Check that the size of the component is 8, 16, 32, or 64 bits and
23943 -- that Typ is properly aligned.
23946 when 8 |
16 |
32 |
64 =>
23947 return Size
= UI_To_Int
(Alignment
(Typ
)) * 8;
23952 end Support_Atomic_Primitives
;
23958 procedure Trace_Scope
(N
: Node_Id
; E
: Entity_Id
; Msg
: String) is
23960 if Debug_Flag_W
then
23961 for J
in 0 .. Scope_Stack
.Last
loop
23966 Write_Name
(Chars
(E
));
23967 Write_Str
(" from ");
23968 Write_Location
(Sloc
(N
));
23973 -----------------------
23974 -- Transfer_Entities --
23975 -----------------------
23977 procedure Transfer_Entities
(From
: Entity_Id
; To
: Entity_Id
) is
23978 procedure Set_Public_Status_Of
(Id
: Entity_Id
);
23979 -- Set the Is_Public attribute of arbitrary entity Id by calling routine
23980 -- Set_Public_Status. If successful and Id denotes a record type, set
23981 -- the Is_Public attribute of its fields.
23983 --------------------------
23984 -- Set_Public_Status_Of --
23985 --------------------------
23987 procedure Set_Public_Status_Of
(Id
: Entity_Id
) is
23991 if not Is_Public
(Id
) then
23992 Set_Public_Status
(Id
);
23994 -- When the input entity is a public record type, ensure that all
23995 -- its internal fields are also exposed to the linker. The fields
23996 -- of a class-wide type are never made public.
23999 and then Is_Record_Type
(Id
)
24000 and then not Is_Class_Wide_Type
(Id
)
24002 Field
:= First_Entity
(Id
);
24003 while Present
(Field
) loop
24004 Set_Is_Public
(Field
);
24005 Next_Entity
(Field
);
24009 end Set_Public_Status_Of
;
24013 Full_Id
: Entity_Id
;
24016 -- Start of processing for Transfer_Entities
24019 Id
:= First_Entity
(From
);
24021 if Present
(Id
) then
24023 -- Merge the entity chain of the source scope with that of the
24024 -- destination scope.
24026 if Present
(Last_Entity
(To
)) then
24027 Set_Next_Entity
(Last_Entity
(To
), Id
);
24029 Set_First_Entity
(To
, Id
);
24032 Set_Last_Entity
(To
, Last_Entity
(From
));
24034 -- Inspect the entities of the source scope and update their Scope
24037 while Present
(Id
) loop
24038 Set_Scope
(Id
, To
);
24039 Set_Public_Status_Of
(Id
);
24041 -- Handle an internally generated full view for a private type
24043 if Is_Private_Type
(Id
)
24044 and then Present
(Full_View
(Id
))
24045 and then Is_Itype
(Full_View
(Id
))
24047 Full_Id
:= Full_View
(Id
);
24049 Set_Scope
(Full_Id
, To
);
24050 Set_Public_Status_Of
(Full_Id
);
24056 Set_First_Entity
(From
, Empty
);
24057 Set_Last_Entity
(From
, Empty
);
24059 end Transfer_Entities
;
24061 -----------------------
24062 -- Type_Access_Level --
24063 -----------------------
24065 function Type_Access_Level
(Typ
: Entity_Id
) return Uint
is
24069 Btyp
:= Base_Type
(Typ
);
24071 -- Ada 2005 (AI-230): For most cases of anonymous access types, we
24072 -- simply use the level where the type is declared. This is true for
24073 -- stand-alone object declarations, and for anonymous access types
24074 -- associated with components the level is the same as that of the
24075 -- enclosing composite type. However, special treatment is needed for
24076 -- the cases of access parameters, return objects of an anonymous access
24077 -- type, and, in Ada 95, access discriminants of limited types.
24079 if Is_Access_Type
(Btyp
) then
24080 if Ekind
(Btyp
) = E_Anonymous_Access_Type
then
24082 -- If the type is a nonlocal anonymous access type (such as for
24083 -- an access parameter) we treat it as being declared at the
24084 -- library level to ensure that names such as X.all'access don't
24085 -- fail static accessibility checks.
24087 if not Is_Local_Anonymous_Access
(Typ
) then
24088 return Scope_Depth
(Standard_Standard
);
24090 -- If this is a return object, the accessibility level is that of
24091 -- the result subtype of the enclosing function. The test here is
24092 -- little complicated, because we have to account for extended
24093 -- return statements that have been rewritten as blocks, in which
24094 -- case we have to find and the Is_Return_Object attribute of the
24095 -- itype's associated object. It would be nice to find a way to
24096 -- simplify this test, but it doesn't seem worthwhile to add a new
24097 -- flag just for purposes of this test. ???
24099 elsif Ekind
(Scope
(Btyp
)) = E_Return_Statement
24102 and then Nkind
(Associated_Node_For_Itype
(Btyp
)) =
24103 N_Object_Declaration
24104 and then Is_Return_Object
24105 (Defining_Identifier
24106 (Associated_Node_For_Itype
(Btyp
))))
24112 Scop
:= Scope
(Scope
(Btyp
));
24113 while Present
(Scop
) loop
24114 exit when Ekind
(Scop
) = E_Function
;
24115 Scop
:= Scope
(Scop
);
24118 -- Treat the return object's type as having the level of the
24119 -- function's result subtype (as per RM05-6.5(5.3/2)).
24121 return Type_Access_Level
(Etype
(Scop
));
24126 Btyp
:= Root_Type
(Btyp
);
24128 -- The accessibility level of anonymous access types associated with
24129 -- discriminants is that of the current instance of the type, and
24130 -- that's deeper than the type itself (AARM 3.10.2 (12.3.21)).
24132 -- AI-402: access discriminants have accessibility based on the
24133 -- object rather than the type in Ada 2005, so the above paragraph
24136 -- ??? Needs completion with rules from AI-416
24138 if Ada_Version
<= Ada_95
24139 and then Ekind
(Typ
) = E_Anonymous_Access_Type
24140 and then Present
(Associated_Node_For_Itype
(Typ
))
24141 and then Nkind
(Associated_Node_For_Itype
(Typ
)) =
24142 N_Discriminant_Specification
24144 return Scope_Depth
(Enclosing_Dynamic_Scope
(Btyp
)) + 1;
24148 -- Return library level for a generic formal type. This is done because
24149 -- RM(10.3.2) says that "The statically deeper relationship does not
24150 -- apply to ... a descendant of a generic formal type". Rather than
24151 -- checking at each point where a static accessibility check is
24152 -- performed to see if we are dealing with a formal type, this rule is
24153 -- implemented by having Type_Access_Level and Deepest_Type_Access_Level
24154 -- return extreme values for a formal type; Deepest_Type_Access_Level
24155 -- returns Int'Last. By calling the appropriate function from among the
24156 -- two, we ensure that the static accessibility check will pass if we
24157 -- happen to run into a formal type. More specifically, we should call
24158 -- Deepest_Type_Access_Level instead of Type_Access_Level whenever the
24159 -- call occurs as part of a static accessibility check and the error
24160 -- case is the case where the type's level is too shallow (as opposed
24163 if Is_Generic_Type
(Root_Type
(Btyp
)) then
24164 return Scope_Depth
(Standard_Standard
);
24167 return Scope_Depth
(Enclosing_Dynamic_Scope
(Btyp
));
24168 end Type_Access_Level
;
24170 ------------------------------------
24171 -- Type_Without_Stream_Operation --
24172 ------------------------------------
24174 function Type_Without_Stream_Operation
24176 Op
: TSS_Name_Type
:= TSS_Null
) return Entity_Id
24178 BT
: constant Entity_Id
:= Base_Type
(T
);
24179 Op_Missing
: Boolean;
24182 if not Restriction_Active
(No_Default_Stream_Attributes
) then
24186 if Is_Elementary_Type
(T
) then
24187 if Op
= TSS_Null
then
24189 No
(TSS
(BT
, TSS_Stream_Read
))
24190 or else No
(TSS
(BT
, TSS_Stream_Write
));
24193 Op_Missing
:= No
(TSS
(BT
, Op
));
24202 elsif Is_Array_Type
(T
) then
24203 return Type_Without_Stream_Operation
(Component_Type
(T
), Op
);
24205 elsif Is_Record_Type
(T
) then
24211 Comp
:= First_Component
(T
);
24212 while Present
(Comp
) loop
24213 C_Typ
:= Type_Without_Stream_Operation
(Etype
(Comp
), Op
);
24215 if Present
(C_Typ
) then
24219 Next_Component
(Comp
);
24225 elsif Is_Private_Type
(T
) and then Present
(Full_View
(T
)) then
24226 return Type_Without_Stream_Operation
(Full_View
(T
), Op
);
24230 end Type_Without_Stream_Operation
;
24232 ----------------------------
24233 -- Unique_Defining_Entity --
24234 ----------------------------
24236 function Unique_Defining_Entity
(N
: Node_Id
) return Entity_Id
is
24238 return Unique_Entity
(Defining_Entity
(N
));
24239 end Unique_Defining_Entity
;
24241 -------------------
24242 -- Unique_Entity --
24243 -------------------
24245 function Unique_Entity
(E
: Entity_Id
) return Entity_Id
is
24246 U
: Entity_Id
:= E
;
24252 if Present
(Full_View
(E
)) then
24253 U
:= Full_View
(E
);
24257 if Nkind
(Parent
(E
)) = N_Entry_Body
then
24259 Prot_Item
: Entity_Id
;
24260 Prot_Type
: Entity_Id
;
24263 if Ekind
(E
) = E_Entry
then
24264 Prot_Type
:= Scope
(E
);
24266 -- Bodies of entry families are nested within an extra scope
24267 -- that contains an entry index declaration.
24270 Prot_Type
:= Scope
(Scope
(E
));
24273 -- A protected type may be declared as a private type, in
24274 -- which case we need to get its full view.
24276 if Is_Private_Type
(Prot_Type
) then
24277 Prot_Type
:= Full_View
(Prot_Type
);
24280 -- Full view may not be present on error, in which case
24281 -- return E by default.
24283 if Present
(Prot_Type
) then
24284 pragma Assert
(Ekind
(Prot_Type
) = E_Protected_Type
);
24286 -- Traverse the entity list of the protected type and
24287 -- locate an entry declaration which matches the entry
24290 Prot_Item
:= First_Entity
(Prot_Type
);
24291 while Present
(Prot_Item
) loop
24292 if Ekind
(Prot_Item
) in Entry_Kind
24293 and then Corresponding_Body
(Parent
(Prot_Item
)) = E
24299 Next_Entity
(Prot_Item
);
24305 when Formal_Kind
=>
24306 if Present
(Spec_Entity
(E
)) then
24307 U
:= Spec_Entity
(E
);
24310 when E_Package_Body
=>
24313 if Nkind
(P
) = N_Defining_Program_Unit_Name
then
24317 if Nkind
(P
) = N_Package_Body
24318 and then Present
(Corresponding_Spec
(P
))
24320 U
:= Corresponding_Spec
(P
);
24322 elsif Nkind
(P
) = N_Package_Body_Stub
24323 and then Present
(Corresponding_Spec_Of_Stub
(P
))
24325 U
:= Corresponding_Spec_Of_Stub
(P
);
24328 when E_Protected_Body
=>
24331 if Nkind
(P
) = N_Protected_Body
24332 and then Present
(Corresponding_Spec
(P
))
24334 U
:= Corresponding_Spec
(P
);
24336 elsif Nkind
(P
) = N_Protected_Body_Stub
24337 and then Present
(Corresponding_Spec_Of_Stub
(P
))
24339 U
:= Corresponding_Spec_Of_Stub
(P
);
24341 if Is_Single_Protected_Object
(U
) then
24346 if Is_Private_Type
(U
) then
24347 U
:= Full_View
(U
);
24350 when E_Subprogram_Body
=>
24353 if Nkind
(P
) = N_Defining_Program_Unit_Name
then
24359 if Nkind
(P
) = N_Subprogram_Body
24360 and then Present
(Corresponding_Spec
(P
))
24362 U
:= Corresponding_Spec
(P
);
24364 elsif Nkind
(P
) = N_Subprogram_Body_Stub
24365 and then Present
(Corresponding_Spec_Of_Stub
(P
))
24367 U
:= Corresponding_Spec_Of_Stub
(P
);
24369 elsif Nkind
(P
) = N_Subprogram_Renaming_Declaration
then
24370 U
:= Corresponding_Spec
(P
);
24373 when E_Task_Body
=>
24376 if Nkind
(P
) = N_Task_Body
24377 and then Present
(Corresponding_Spec
(P
))
24379 U
:= Corresponding_Spec
(P
);
24381 elsif Nkind
(P
) = N_Task_Body_Stub
24382 and then Present
(Corresponding_Spec_Of_Stub
(P
))
24384 U
:= Corresponding_Spec_Of_Stub
(P
);
24386 if Is_Single_Task_Object
(U
) then
24391 if Is_Private_Type
(U
) then
24392 U
:= Full_View
(U
);
24396 if Present
(Full_View
(E
)) then
24397 U
:= Full_View
(E
);
24411 function Unique_Name
(E
: Entity_Id
) return String is
24413 -- Names in E_Subprogram_Body or E_Package_Body entities are not
24414 -- reliable, as they may not include the overloading suffix. Instead,
24415 -- when looking for the name of E or one of its enclosing scope, we get
24416 -- the name of the corresponding Unique_Entity.
24418 U
: constant Entity_Id
:= Unique_Entity
(E
);
24420 function This_Name
return String;
24426 function This_Name
return String is
24428 return Get_Name_String
(Chars
(U
));
24431 -- Start of processing for Unique_Name
24434 if E
= Standard_Standard
24435 or else Has_Fully_Qualified_Name
(E
)
24439 elsif Ekind
(E
) = E_Enumeration_Literal
then
24440 return Unique_Name
(Etype
(E
)) & "__" & This_Name
;
24444 S
: constant Entity_Id
:= Scope
(U
);
24445 pragma Assert
(Present
(S
));
24448 -- Prefix names of predefined types with standard__, but leave
24449 -- names of user-defined packages and subprograms without prefix
24450 -- (even if technically they are nested in the Standard package).
24452 if S
= Standard_Standard
then
24453 if Ekind
(U
) = E_Package
or else Is_Subprogram
(U
) then
24456 return Unique_Name
(S
) & "__" & This_Name
;
24459 -- For intances of generic subprograms use the name of the related
24460 -- instace and skip the scope of its wrapper package.
24462 elsif Is_Wrapper_Package
(S
) then
24463 pragma Assert
(Scope
(S
) = Scope
(Related_Instance
(S
)));
24464 -- Wrapper package and the instantiation are in the same scope
24467 Enclosing_Name
: constant String :=
24468 Unique_Name
(Scope
(S
)) & "__" &
24469 Get_Name_String
(Chars
(Related_Instance
(S
)));
24472 if Is_Subprogram
(U
)
24473 and then not Is_Generic_Actual_Subprogram
(U
)
24475 return Enclosing_Name
;
24477 return Enclosing_Name
& "__" & This_Name
;
24482 return Unique_Name
(S
) & "__" & This_Name
;
24488 ---------------------
24489 -- Unit_Is_Visible --
24490 ---------------------
24492 function Unit_Is_Visible
(U
: Entity_Id
) return Boolean is
24493 Curr
: constant Node_Id
:= Cunit
(Current_Sem_Unit
);
24494 Curr_Entity
: constant Entity_Id
:= Cunit_Entity
(Current_Sem_Unit
);
24496 function Unit_In_Parent_Context
(Par_Unit
: Node_Id
) return Boolean;
24497 -- For a child unit, check whether unit appears in a with_clause
24500 function Unit_In_Context
(Comp_Unit
: Node_Id
) return Boolean;
24501 -- Scan the context clause of one compilation unit looking for a
24502 -- with_clause for the unit in question.
24504 ----------------------------
24505 -- Unit_In_Parent_Context --
24506 ----------------------------
24508 function Unit_In_Parent_Context
(Par_Unit
: Node_Id
) return Boolean is
24510 if Unit_In_Context
(Par_Unit
) then
24513 elsif Is_Child_Unit
(Defining_Entity
(Unit
(Par_Unit
))) then
24514 return Unit_In_Parent_Context
(Parent_Spec
(Unit
(Par_Unit
)));
24519 end Unit_In_Parent_Context
;
24521 ---------------------
24522 -- Unit_In_Context --
24523 ---------------------
24525 function Unit_In_Context
(Comp_Unit
: Node_Id
) return Boolean is
24529 Clause
:= First
(Context_Items
(Comp_Unit
));
24530 while Present
(Clause
) loop
24531 if Nkind
(Clause
) = N_With_Clause
then
24532 if Library_Unit
(Clause
) = U
then
24535 -- The with_clause may denote a renaming of the unit we are
24536 -- looking for, eg. Text_IO which renames Ada.Text_IO.
24539 Renamed_Entity
(Entity
(Name
(Clause
))) =
24540 Defining_Entity
(Unit
(U
))
24550 end Unit_In_Context
;
24552 -- Start of processing for Unit_Is_Visible
24555 -- The currrent unit is directly visible
24560 elsif Unit_In_Context
(Curr
) then
24563 -- If the current unit is a body, check the context of the spec
24565 elsif Nkind
(Unit
(Curr
)) = N_Package_Body
24567 (Nkind
(Unit
(Curr
)) = N_Subprogram_Body
24568 and then not Acts_As_Spec
(Unit
(Curr
)))
24570 if Unit_In_Context
(Library_Unit
(Curr
)) then
24575 -- If the spec is a child unit, examine the parents
24577 if Is_Child_Unit
(Curr_Entity
) then
24578 if Nkind
(Unit
(Curr
)) in N_Unit_Body
then
24580 Unit_In_Parent_Context
24581 (Parent_Spec
(Unit
(Library_Unit
(Curr
))));
24583 return Unit_In_Parent_Context
(Parent_Spec
(Unit
(Curr
)));
24589 end Unit_Is_Visible
;
24591 ------------------------------
24592 -- Universal_Interpretation --
24593 ------------------------------
24595 function Universal_Interpretation
(Opnd
: Node_Id
) return Entity_Id
is
24596 Index
: Interp_Index
;
24600 -- The argument may be a formal parameter of an operator or subprogram
24601 -- with multiple interpretations, or else an expression for an actual.
24603 if Nkind
(Opnd
) = N_Defining_Identifier
24604 or else not Is_Overloaded
(Opnd
)
24606 if Etype
(Opnd
) = Universal_Integer
24607 or else Etype
(Opnd
) = Universal_Real
24609 return Etype
(Opnd
);
24615 Get_First_Interp
(Opnd
, Index
, It
);
24616 while Present
(It
.Typ
) loop
24617 if It
.Typ
= Universal_Integer
24618 or else It
.Typ
= Universal_Real
24623 Get_Next_Interp
(Index
, It
);
24628 end Universal_Interpretation
;
24634 function Unqualify
(Expr
: Node_Id
) return Node_Id
is
24636 -- Recurse to handle unlikely case of multiple levels of qualification
24638 if Nkind
(Expr
) = N_Qualified_Expression
then
24639 return Unqualify
(Expression
(Expr
));
24641 -- Normal case, not a qualified expression
24652 function Unqual_Conv
(Expr
: Node_Id
) return Node_Id
is
24654 -- Recurse to handle unlikely case of multiple levels of qualification
24655 -- and/or conversion.
24657 if Nkind_In
(Expr
, N_Qualified_Expression
,
24659 N_Unchecked_Type_Conversion
)
24661 return Unqual_Conv
(Expression
(Expr
));
24663 -- Normal case, not a qualified expression
24670 -----------------------
24671 -- Visible_Ancestors --
24672 -----------------------
24674 function Visible_Ancestors
(Typ
: Entity_Id
) return Elist_Id
is
24680 pragma Assert
(Is_Record_Type
(Typ
) and then Is_Tagged_Type
(Typ
));
24682 -- Collect all the parents and progenitors of Typ. If the full-view of
24683 -- private parents and progenitors is available then it is used to
24684 -- generate the list of visible ancestors; otherwise their partial
24685 -- view is added to the resulting list.
24690 Use_Full_View
=> True);
24694 Ifaces_List
=> List_2
,
24695 Exclude_Parents
=> True,
24696 Use_Full_View
=> True);
24698 -- Join the two lists. Avoid duplications because an interface may
24699 -- simultaneously be parent and progenitor of a type.
24701 Elmt
:= First_Elmt
(List_2
);
24702 while Present
(Elmt
) loop
24703 Append_Unique_Elmt
(Node
(Elmt
), List_1
);
24708 end Visible_Ancestors
;
24710 ----------------------
24711 -- Within_Init_Proc --
24712 ----------------------
24714 function Within_Init_Proc
return Boolean is
24718 S
:= Current_Scope
;
24719 while not Is_Overloadable
(S
) loop
24720 if S
= Standard_Standard
then
24727 return Is_Init_Proc
(S
);
24728 end Within_Init_Proc
;
24730 ---------------------------
24731 -- Within_Protected_Type --
24732 ---------------------------
24734 function Within_Protected_Type
(E
: Entity_Id
) return Boolean is
24735 Scop
: Entity_Id
:= Scope
(E
);
24738 while Present
(Scop
) loop
24739 if Ekind
(Scop
) = E_Protected_Type
then
24743 Scop
:= Scope
(Scop
);
24747 end Within_Protected_Type
;
24753 function Within_Scope
(E
: Entity_Id
; S
: Entity_Id
) return Boolean is
24755 return Scope_Within_Or_Same
(Scope
(E
), S
);
24758 ----------------------------
24759 -- Within_Subprogram_Call --
24760 ----------------------------
24762 function Within_Subprogram_Call
(N
: Node_Id
) return Boolean is
24766 -- Climb the parent chain looking for a function or procedure call
24769 while Present
(Par
) loop
24770 if Nkind_In
(Par
, N_Entry_Call_Statement
,
24772 N_Procedure_Call_Statement
)
24776 -- Prevent the search from going too far
24778 elsif Is_Body_Or_Package_Declaration
(Par
) then
24782 Par
:= Parent
(Par
);
24786 end Within_Subprogram_Call
;
24792 procedure Wrong_Type
(Expr
: Node_Id
; Expected_Type
: Entity_Id
) is
24793 Found_Type
: constant Entity_Id
:= First_Subtype
(Etype
(Expr
));
24794 Expec_Type
: constant Entity_Id
:= First_Subtype
(Expected_Type
);
24796 Matching_Field
: Entity_Id
;
24797 -- Entity to give a more precise suggestion on how to write a one-
24798 -- element positional aggregate.
24800 function Has_One_Matching_Field
return Boolean;
24801 -- Determines if Expec_Type is a record type with a single component or
24802 -- discriminant whose type matches the found type or is one dimensional
24803 -- array whose component type matches the found type. In the case of
24804 -- one discriminant, we ignore the variant parts. That's not accurate,
24805 -- but good enough for the warning.
24807 ----------------------------
24808 -- Has_One_Matching_Field --
24809 ----------------------------
24811 function Has_One_Matching_Field
return Boolean is
24815 Matching_Field
:= Empty
;
24817 if Is_Array_Type
(Expec_Type
)
24818 and then Number_Dimensions
(Expec_Type
) = 1
24819 and then Covers
(Etype
(Component_Type
(Expec_Type
)), Found_Type
)
24821 -- Use type name if available. This excludes multidimensional
24822 -- arrays and anonymous arrays.
24824 if Comes_From_Source
(Expec_Type
) then
24825 Matching_Field
:= Expec_Type
;
24827 -- For an assignment, use name of target
24829 elsif Nkind
(Parent
(Expr
)) = N_Assignment_Statement
24830 and then Is_Entity_Name
(Name
(Parent
(Expr
)))
24832 Matching_Field
:= Entity
(Name
(Parent
(Expr
)));
24837 elsif not Is_Record_Type
(Expec_Type
) then
24841 E
:= First_Entity
(Expec_Type
);
24846 elsif not Ekind_In
(E
, E_Discriminant
, E_Component
)
24847 or else Nam_In
(Chars
(E
), Name_uTag
, Name_uParent
)
24856 if not Covers
(Etype
(E
), Found_Type
) then
24859 elsif Present
(Next_Entity
(E
))
24860 and then (Ekind
(E
) = E_Component
24861 or else Ekind
(Next_Entity
(E
)) = E_Discriminant
)
24866 Matching_Field
:= E
;
24870 end Has_One_Matching_Field
;
24872 -- Start of processing for Wrong_Type
24875 -- Don't output message if either type is Any_Type, or if a message
24876 -- has already been posted for this node. We need to do the latter
24877 -- check explicitly (it is ordinarily done in Errout), because we
24878 -- are using ! to force the output of the error messages.
24880 if Expec_Type
= Any_Type
24881 or else Found_Type
= Any_Type
24882 or else Error_Posted
(Expr
)
24886 -- If one of the types is a Taft-Amendment type and the other it its
24887 -- completion, it must be an illegal use of a TAT in the spec, for
24888 -- which an error was already emitted. Avoid cascaded errors.
24890 elsif Is_Incomplete_Type
(Expec_Type
)
24891 and then Has_Completion_In_Body
(Expec_Type
)
24892 and then Full_View
(Expec_Type
) = Etype
(Expr
)
24896 elsif Is_Incomplete_Type
(Etype
(Expr
))
24897 and then Has_Completion_In_Body
(Etype
(Expr
))
24898 and then Full_View
(Etype
(Expr
)) = Expec_Type
24902 -- In an instance, there is an ongoing problem with completion of
24903 -- type derived from private types. Their structure is what Gigi
24904 -- expects, but the Etype is the parent type rather than the
24905 -- derived private type itself. Do not flag error in this case. The
24906 -- private completion is an entity without a parent, like an Itype.
24907 -- Similarly, full and partial views may be incorrect in the instance.
24908 -- There is no simple way to insure that it is consistent ???
24910 -- A similar view discrepancy can happen in an inlined body, for the
24911 -- same reason: inserted body may be outside of the original package
24912 -- and only partial views are visible at the point of insertion.
24914 elsif In_Instance
or else In_Inlined_Body
then
24915 if Etype
(Etype
(Expr
)) = Etype
(Expected_Type
)
24917 (Has_Private_Declaration
(Expected_Type
)
24918 or else Has_Private_Declaration
(Etype
(Expr
)))
24919 and then No
(Parent
(Expected_Type
))
24923 elsif Nkind
(Parent
(Expr
)) = N_Qualified_Expression
24924 and then Entity
(Subtype_Mark
(Parent
(Expr
))) = Expected_Type
24928 elsif Is_Private_Type
(Expected_Type
)
24929 and then Present
(Full_View
(Expected_Type
))
24930 and then Covers
(Full_View
(Expected_Type
), Etype
(Expr
))
24934 -- Conversely, type of expression may be the private one
24936 elsif Is_Private_Type
(Base_Type
(Etype
(Expr
)))
24937 and then Full_View
(Base_Type
(Etype
(Expr
))) = Expected_Type
24943 -- An interesting special check. If the expression is parenthesized
24944 -- and its type corresponds to the type of the sole component of the
24945 -- expected record type, or to the component type of the expected one
24946 -- dimensional array type, then assume we have a bad aggregate attempt.
24948 if Nkind
(Expr
) in N_Subexpr
24949 and then Paren_Count
(Expr
) /= 0
24950 and then Has_One_Matching_Field
24952 Error_Msg_N
("positional aggregate cannot have one component", Expr
);
24954 if Present
(Matching_Field
) then
24955 if Is_Array_Type
(Expec_Type
) then
24957 ("\write instead `&''First ='> ...`", Expr
, Matching_Field
);
24960 ("\write instead `& ='> ...`", Expr
, Matching_Field
);
24964 -- Another special check, if we are looking for a pool-specific access
24965 -- type and we found an E_Access_Attribute_Type, then we have the case
24966 -- of an Access attribute being used in a context which needs a pool-
24967 -- specific type, which is never allowed. The one extra check we make
24968 -- is that the expected designated type covers the Found_Type.
24970 elsif Is_Access_Type
(Expec_Type
)
24971 and then Ekind
(Found_Type
) = E_Access_Attribute_Type
24972 and then Ekind
(Base_Type
(Expec_Type
)) /= E_General_Access_Type
24973 and then Ekind
(Base_Type
(Expec_Type
)) /= E_Anonymous_Access_Type
24975 (Designated_Type
(Expec_Type
), Designated_Type
(Found_Type
))
24977 Error_Msg_N
-- CODEFIX
24978 ("result must be general access type!", Expr
);
24979 Error_Msg_NE
-- CODEFIX
24980 ("add ALL to }!", Expr
, Expec_Type
);
24982 -- Another special check, if the expected type is an integer type,
24983 -- but the expression is of type System.Address, and the parent is
24984 -- an addition or subtraction operation whose left operand is the
24985 -- expression in question and whose right operand is of an integral
24986 -- type, then this is an attempt at address arithmetic, so give
24987 -- appropriate message.
24989 elsif Is_Integer_Type
(Expec_Type
)
24990 and then Is_RTE
(Found_Type
, RE_Address
)
24991 and then Nkind_In
(Parent
(Expr
), N_Op_Add
, N_Op_Subtract
)
24992 and then Expr
= Left_Opnd
(Parent
(Expr
))
24993 and then Is_Integer_Type
(Etype
(Right_Opnd
(Parent
(Expr
))))
24996 ("address arithmetic not predefined in package System",
24999 ("\possible missing with/use of System.Storage_Elements",
25003 -- If the expected type is an anonymous access type, as for access
25004 -- parameters and discriminants, the error is on the designated types.
25006 elsif Ekind
(Expec_Type
) = E_Anonymous_Access_Type
then
25007 if Comes_From_Source
(Expec_Type
) then
25008 Error_Msg_NE
("expected}!", Expr
, Expec_Type
);
25011 ("expected an access type with designated}",
25012 Expr
, Designated_Type
(Expec_Type
));
25015 if Is_Access_Type
(Found_Type
)
25016 and then not Comes_From_Source
(Found_Type
)
25019 ("\\found an access type with designated}!",
25020 Expr
, Designated_Type
(Found_Type
));
25022 if From_Limited_With
(Found_Type
) then
25023 Error_Msg_NE
("\\found incomplete}!", Expr
, Found_Type
);
25024 Error_Msg_Qual_Level
:= 99;
25025 Error_Msg_NE
-- CODEFIX
25026 ("\\missing `WITH &;", Expr
, Scope
(Found_Type
));
25027 Error_Msg_Qual_Level
:= 0;
25029 Error_Msg_NE
("found}!", Expr
, Found_Type
);
25033 -- Normal case of one type found, some other type expected
25036 -- If the names of the two types are the same, see if some number
25037 -- of levels of qualification will help. Don't try more than three
25038 -- levels, and if we get to standard, it's no use (and probably
25039 -- represents an error in the compiler) Also do not bother with
25040 -- internal scope names.
25043 Expec_Scope
: Entity_Id
;
25044 Found_Scope
: Entity_Id
;
25047 Expec_Scope
:= Expec_Type
;
25048 Found_Scope
:= Found_Type
;
25050 for Levels
in Nat
range 0 .. 3 loop
25051 if Chars
(Expec_Scope
) /= Chars
(Found_Scope
) then
25052 Error_Msg_Qual_Level
:= Levels
;
25056 Expec_Scope
:= Scope
(Expec_Scope
);
25057 Found_Scope
:= Scope
(Found_Scope
);
25059 exit when Expec_Scope
= Standard_Standard
25060 or else Found_Scope
= Standard_Standard
25061 or else not Comes_From_Source
(Expec_Scope
)
25062 or else not Comes_From_Source
(Found_Scope
);
25066 if Is_Record_Type
(Expec_Type
)
25067 and then Present
(Corresponding_Remote_Type
(Expec_Type
))
25069 Error_Msg_NE
("expected}!", Expr
,
25070 Corresponding_Remote_Type
(Expec_Type
));
25072 Error_Msg_NE
("expected}!", Expr
, Expec_Type
);
25075 if Is_Entity_Name
(Expr
)
25076 and then Is_Package_Or_Generic_Package
(Entity
(Expr
))
25078 Error_Msg_N
("\\found package name!", Expr
);
25080 elsif Is_Entity_Name
(Expr
)
25081 and then Ekind_In
(Entity
(Expr
), E_Procedure
, E_Generic_Procedure
)
25083 if Ekind
(Expec_Type
) = E_Access_Subprogram_Type
then
25085 ("found procedure name, possibly missing Access attribute!",
25089 ("\\found procedure name instead of function!", Expr
);
25092 elsif Nkind
(Expr
) = N_Function_Call
25093 and then Ekind
(Expec_Type
) = E_Access_Subprogram_Type
25094 and then Etype
(Designated_Type
(Expec_Type
)) = Etype
(Expr
)
25095 and then No
(Parameter_Associations
(Expr
))
25098 ("found function name, possibly missing Access attribute!",
25101 -- Catch common error: a prefix or infix operator which is not
25102 -- directly visible because the type isn't.
25104 elsif Nkind
(Expr
) in N_Op
25105 and then Is_Overloaded
(Expr
)
25106 and then not Is_Immediately_Visible
(Expec_Type
)
25107 and then not Is_Potentially_Use_Visible
(Expec_Type
)
25108 and then not In_Use
(Expec_Type
)
25109 and then Has_Compatible_Type
(Right_Opnd
(Expr
), Expec_Type
)
25112 ("operator of the type is not directly visible!", Expr
);
25114 elsif Ekind
(Found_Type
) = E_Void
25115 and then Present
(Parent
(Found_Type
))
25116 and then Nkind
(Parent
(Found_Type
)) = N_Full_Type_Declaration
25118 Error_Msg_NE
("\\found premature usage of}!", Expr
, Found_Type
);
25121 Error_Msg_NE
("\\found}!", Expr
, Found_Type
);
25124 -- A special check for cases like M1 and M2 = 0 where M1 and M2 are
25125 -- of the same modular type, and (M1 and M2) = 0 was intended.
25127 if Expec_Type
= Standard_Boolean
25128 and then Is_Modular_Integer_Type
(Found_Type
)
25129 and then Nkind_In
(Parent
(Expr
), N_Op_And
, N_Op_Or
, N_Op_Xor
)
25130 and then Nkind
(Right_Opnd
(Parent
(Expr
))) in N_Op_Compare
25133 Op
: constant Node_Id
:= Right_Opnd
(Parent
(Expr
));
25134 L
: constant Node_Id
:= Left_Opnd
(Op
);
25135 R
: constant Node_Id
:= Right_Opnd
(Op
);
25138 -- The case for the message is when the left operand of the
25139 -- comparison is the same modular type, or when it is an
25140 -- integer literal (or other universal integer expression),
25141 -- which would have been typed as the modular type if the
25142 -- parens had been there.
25144 if (Etype
(L
) = Found_Type
25146 Etype
(L
) = Universal_Integer
)
25147 and then Is_Integer_Type
(Etype
(R
))
25150 ("\\possible missing parens for modular operation", Expr
);
25155 -- Reset error message qualification indication
25157 Error_Msg_Qual_Level
:= 0;
25161 --------------------------------
25162 -- Yields_Synchronized_Object --
25163 --------------------------------
25165 function Yields_Synchronized_Object
(Typ
: Entity_Id
) return Boolean is
25166 Has_Sync_Comp
: Boolean := False;
25170 -- An array type yields a synchronized object if its component type
25171 -- yields a synchronized object.
25173 if Is_Array_Type
(Typ
) then
25174 return Yields_Synchronized_Object
(Component_Type
(Typ
));
25176 -- A descendant of type Ada.Synchronous_Task_Control.Suspension_Object
25177 -- yields a synchronized object by default.
25179 elsif Is_Descendant_Of_Suspension_Object
(Typ
) then
25182 -- A protected type yields a synchronized object by default
25184 elsif Is_Protected_Type
(Typ
) then
25187 -- A record type or type extension yields a synchronized object when its
25188 -- discriminants (if any) lack default values and all components are of
25189 -- a type that yelds a synchronized object.
25191 elsif Is_Record_Type
(Typ
) then
25193 -- Inspect all entities defined in the scope of the type, looking for
25194 -- components of a type that does not yeld a synchronized object or
25195 -- for discriminants with default values.
25197 Id
:= First_Entity
(Typ
);
25198 while Present
(Id
) loop
25199 if Comes_From_Source
(Id
) then
25200 if Ekind
(Id
) = E_Component
then
25201 if Yields_Synchronized_Object
(Etype
(Id
)) then
25202 Has_Sync_Comp
:= True;
25204 -- The component does not yield a synchronized object
25210 elsif Ekind
(Id
) = E_Discriminant
25211 and then Present
(Expression
(Parent
(Id
)))
25220 -- Ensure that the parent type of a type extension yields a
25221 -- synchronized object.
25223 if Etype
(Typ
) /= Typ
25224 and then not Yields_Synchronized_Object
(Etype
(Typ
))
25229 -- If we get here, then all discriminants lack default values and all
25230 -- components are of a type that yields a synchronized object.
25232 return Has_Sync_Comp
;
25234 -- A synchronized interface type yields a synchronized object by default
25236 elsif Is_Synchronized_Interface
(Typ
) then
25239 -- A task type yelds a synchronized object by default
25241 elsif Is_Task_Type
(Typ
) then
25244 -- Otherwise the type does not yield a synchronized object
25249 end Yields_Synchronized_Object
;
25251 ---------------------------
25252 -- Yields_Universal_Type --
25253 ---------------------------
25255 function Yields_Universal_Type
(N
: Node_Id
) return Boolean is
25257 -- Integer and real literals are of a universal type
25259 if Nkind_In
(N
, N_Integer_Literal
, N_Real_Literal
) then
25262 -- The values of certain attributes are of a universal type
25264 elsif Nkind
(N
) = N_Attribute_Reference
then
25266 Universal_Type_Attribute
(Get_Attribute_Id
(Attribute_Name
(N
)));
25268 -- ??? There are possibly other cases to consider
25273 end Yields_Universal_Type
;
25276 Erroutc
.Subprogram_Name_Ptr
:= Subprogram_Name
'Access;