1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2006, 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 2, 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 COPYING. If not, write --
19 -- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
20 -- Boston, MA 02110-1301, USA. --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
25 ------------------------------------------------------------------------------
27 with Atree
; use Atree
;
28 with Checks
; use Checks
;
29 with Debug
; use Debug
;
30 with Debug_A
; use Debug_A
;
31 with Einfo
; use Einfo
;
32 with Errout
; use Errout
;
33 with Expander
; use Expander
;
34 with Exp_Disp
; use Exp_Disp
;
35 with Exp_Ch7
; use Exp_Ch7
;
36 with Exp_Tss
; use Exp_Tss
;
37 with Exp_Util
; use Exp_Util
;
38 with Freeze
; use Freeze
;
39 with Itypes
; use Itypes
;
41 with Lib
.Xref
; use Lib
.Xref
;
42 with Namet
; use Namet
;
43 with Nmake
; use Nmake
;
44 with Nlists
; use Nlists
;
46 with Output
; use Output
;
47 with Restrict
; use Restrict
;
48 with Rident
; use Rident
;
49 with Rtsfind
; use Rtsfind
;
51 with Sem_Aggr
; use Sem_Aggr
;
52 with Sem_Attr
; use Sem_Attr
;
53 with Sem_Cat
; use Sem_Cat
;
54 with Sem_Ch4
; use Sem_Ch4
;
55 with Sem_Ch6
; use Sem_Ch6
;
56 with Sem_Ch8
; use Sem_Ch8
;
57 with Sem_Disp
; use Sem_Disp
;
58 with Sem_Dist
; use Sem_Dist
;
59 with Sem_Elab
; use Sem_Elab
;
60 with Sem_Eval
; use Sem_Eval
;
61 with Sem_Intr
; use Sem_Intr
;
62 with Sem_Util
; use Sem_Util
;
63 with Sem_Type
; use Sem_Type
;
64 with Sem_Warn
; use Sem_Warn
;
65 with Sinfo
; use Sinfo
;
66 with Snames
; use Snames
;
67 with Stand
; use Stand
;
68 with Stringt
; use Stringt
;
69 with Targparm
; use Targparm
;
70 with Tbuild
; use Tbuild
;
71 with Uintp
; use Uintp
;
72 with Urealp
; use Urealp
;
74 package body Sem_Res
is
76 -----------------------
77 -- Local Subprograms --
78 -----------------------
80 -- Second pass (top-down) type checking and overload resolution procedures
81 -- Typ is the type required by context. These procedures propagate the
82 -- type information recursively to the descendants of N. If the node
83 -- is not overloaded, its Etype is established in the first pass. If
84 -- overloaded, the Resolve routines set the correct type. For arith.
85 -- operators, the Etype is the base type of the context.
87 -- Note that Resolve_Attribute is separated off in Sem_Attr
89 procedure Ambiguous_Character
(C
: Node_Id
);
90 -- Give list of candidate interpretations when a character literal cannot
93 procedure Check_Discriminant_Use
(N
: Node_Id
);
94 -- Enforce the restrictions on the use of discriminants when constraining
95 -- a component of a discriminated type (record or concurrent type).
97 procedure Check_For_Visible_Operator
(N
: Node_Id
; T
: Entity_Id
);
98 -- Given a node for an operator associated with type T, check that
99 -- the operator is visible. Operators all of whose operands are
100 -- universal must be checked for visibility during resolution
101 -- because their type is not determinable based on their operands.
103 procedure Check_Fully_Declared_Prefix
106 -- Check that the type of the prefix of a dereference is not incomplete
108 function Check_Infinite_Recursion
(N
: Node_Id
) return Boolean;
109 -- Given a call node, N, which is known to occur immediately within the
110 -- subprogram being called, determines whether it is a detectable case of
111 -- an infinite recursion, and if so, outputs appropriate messages. Returns
112 -- True if an infinite recursion is detected, and False otherwise.
114 procedure Check_Initialization_Call
(N
: Entity_Id
; Nam
: Entity_Id
);
115 -- If the type of the object being initialized uses the secondary stack
116 -- directly or indirectly, create a transient scope for the call to the
117 -- init proc. This is because we do not create transient scopes for the
118 -- initialization of individual components within the init proc itself.
119 -- Could be optimized away perhaps?
121 function Is_Predefined_Op
(Nam
: Entity_Id
) return Boolean;
122 -- Utility to check whether the name in the call is a predefined
123 -- operator, in which case the call is made into an operator node.
124 -- An instance of an intrinsic conversion operation may be given
125 -- an operator name, but is not treated like an operator.
127 procedure Replace_Actual_Discriminants
(N
: Node_Id
; Default
: Node_Id
);
128 -- If a default expression in entry call N depends on the discriminants
129 -- of the task, it must be replaced with a reference to the discriminant
130 -- of the task being called.
132 procedure Resolve_Allocator
(N
: Node_Id
; Typ
: Entity_Id
);
133 procedure Resolve_Arithmetic_Op
(N
: Node_Id
; Typ
: Entity_Id
);
134 procedure Resolve_Call
(N
: Node_Id
; Typ
: Entity_Id
);
135 procedure Resolve_Character_Literal
(N
: Node_Id
; Typ
: Entity_Id
);
136 procedure Resolve_Comparison_Op
(N
: Node_Id
; Typ
: Entity_Id
);
137 procedure Resolve_Conditional_Expression
(N
: Node_Id
; Typ
: Entity_Id
);
138 procedure Resolve_Equality_Op
(N
: Node_Id
; Typ
: Entity_Id
);
139 procedure Resolve_Explicit_Dereference
(N
: Node_Id
; Typ
: Entity_Id
);
140 procedure Resolve_Entity_Name
(N
: Node_Id
; Typ
: Entity_Id
);
141 procedure Resolve_Indexed_Component
(N
: Node_Id
; Typ
: Entity_Id
);
142 procedure Resolve_Integer_Literal
(N
: Node_Id
; Typ
: Entity_Id
);
143 procedure Resolve_Logical_Op
(N
: Node_Id
; Typ
: Entity_Id
);
144 procedure Resolve_Membership_Op
(N
: Node_Id
; Typ
: Entity_Id
);
145 procedure Resolve_Null
(N
: Node_Id
; Typ
: Entity_Id
);
146 procedure Resolve_Operator_Symbol
(N
: Node_Id
; Typ
: Entity_Id
);
147 procedure Resolve_Op_Concat
(N
: Node_Id
; Typ
: Entity_Id
);
148 procedure Resolve_Op_Expon
(N
: Node_Id
; Typ
: Entity_Id
);
149 procedure Resolve_Op_Not
(N
: Node_Id
; Typ
: Entity_Id
);
150 procedure Resolve_Qualified_Expression
(N
: Node_Id
; Typ
: Entity_Id
);
151 procedure Resolve_Range
(N
: Node_Id
; Typ
: Entity_Id
);
152 procedure Resolve_Real_Literal
(N
: Node_Id
; Typ
: Entity_Id
);
153 procedure Resolve_Reference
(N
: Node_Id
; Typ
: Entity_Id
);
154 procedure Resolve_Selected_Component
(N
: Node_Id
; Typ
: Entity_Id
);
155 procedure Resolve_Shift
(N
: Node_Id
; Typ
: Entity_Id
);
156 procedure Resolve_Short_Circuit
(N
: Node_Id
; Typ
: Entity_Id
);
157 procedure Resolve_Slice
(N
: Node_Id
; Typ
: Entity_Id
);
158 procedure Resolve_String_Literal
(N
: Node_Id
; Typ
: Entity_Id
);
159 procedure Resolve_Subprogram_Info
(N
: Node_Id
; Typ
: Entity_Id
);
160 procedure Resolve_Type_Conversion
(N
: Node_Id
; Typ
: Entity_Id
);
161 procedure Resolve_Unary_Op
(N
: Node_Id
; Typ
: Entity_Id
);
162 procedure Resolve_Unchecked_Expression
(N
: Node_Id
; Typ
: Entity_Id
);
163 procedure Resolve_Unchecked_Type_Conversion
(N
: Node_Id
; Typ
: Entity_Id
);
165 function Operator_Kind
167 Is_Binary
: Boolean) return Node_Kind
;
168 -- Utility to map the name of an operator into the corresponding Node. Used
169 -- by other node rewriting procedures.
171 procedure Resolve_Actuals
(N
: Node_Id
; Nam
: Entity_Id
);
172 -- Resolve actuals of call, and add default expressions for missing ones.
173 -- N is the Node_Id for the subprogram call, and Nam is the entity of the
174 -- called subprogram.
176 procedure Resolve_Entry_Call
(N
: Node_Id
; Typ
: Entity_Id
);
177 -- Called from Resolve_Call, when the prefix denotes an entry or element
178 -- of entry family. Actuals are resolved as for subprograms, and the node
179 -- is rebuilt as an entry call. Also called for protected operations. Typ
180 -- is the context type, which is used when the operation is a protected
181 -- function with no arguments, and the return value is indexed.
183 procedure Resolve_Intrinsic_Operator
(N
: Node_Id
; Typ
: Entity_Id
);
184 -- A call to a user-defined intrinsic operator is rewritten as a call
185 -- to the corresponding predefined operator, with suitable conversions.
187 procedure Resolve_Intrinsic_Unary_Operator
(N
: Node_Id
; Typ
: Entity_Id
);
188 -- Ditto, for unary operators (only arithmetic ones)
190 procedure Rewrite_Operator_As_Call
(N
: Node_Id
; Nam
: Entity_Id
);
191 -- If an operator node resolves to a call to a user-defined operator,
192 -- rewrite the node as a function call.
194 procedure Make_Call_Into_Operator
198 -- Inverse transformation: if an operator is given in functional notation,
199 -- then after resolving the node, transform into an operator node, so
200 -- that operands are resolved properly. Recall that predefined operators
201 -- do not have a full signature and special resolution rules apply.
203 procedure Rewrite_Renamed_Operator
207 -- An operator can rename another, e.g. in an instantiation. In that
208 -- case, the proper operator node must be constructed and resolved.
210 procedure Set_String_Literal_Subtype
(N
: Node_Id
; Typ
: Entity_Id
);
211 -- The String_Literal_Subtype is built for all strings that are not
212 -- operands of a static concatenation operation. If the argument is
213 -- not a N_String_Literal node, then the call has no effect.
215 procedure Set_Slice_Subtype
(N
: Node_Id
);
216 -- Build subtype of array type, with the range specified by the slice
218 function Unique_Fixed_Point_Type
(N
: Node_Id
) return Entity_Id
;
219 -- A universal_fixed expression in an universal context is unambiguous
220 -- if there is only one applicable fixed point type. Determining whether
221 -- there is only one requires a search over all visible entities, and
222 -- happens only in very pathological cases (see 6115-006).
224 function Valid_Conversion
227 Operand
: Node_Id
) return Boolean;
228 -- Verify legality rules given in 4.6 (8-23). Target is the target
229 -- type of the conversion, which may be an implicit conversion of
230 -- an actual parameter to an anonymous access type (in which case
231 -- N denotes the actual parameter and N = Operand).
233 -------------------------
234 -- Ambiguous_Character --
235 -------------------------
237 procedure Ambiguous_Character
(C
: Node_Id
) is
241 if Nkind
(C
) = N_Character_Literal
then
242 Error_Msg_N
("ambiguous character literal", C
);
244 ("\\possible interpretations: Character, Wide_Character!", C
);
246 E
:= Current_Entity
(C
);
247 while Present
(E
) loop
248 Error_Msg_NE
("\\possible interpretation:}!", C
, Etype
(E
));
252 end Ambiguous_Character
;
254 -------------------------
255 -- Analyze_And_Resolve --
256 -------------------------
258 procedure Analyze_And_Resolve
(N
: Node_Id
) is
262 end Analyze_And_Resolve
;
264 procedure Analyze_And_Resolve
(N
: Node_Id
; Typ
: Entity_Id
) is
268 end Analyze_And_Resolve
;
270 -- Version withs check(s) suppressed
272 procedure Analyze_And_Resolve
277 Scop
: constant Entity_Id
:= Current_Scope
;
280 if Suppress
= All_Checks
then
282 Svg
: constant Suppress_Array
:= Scope_Suppress
;
284 Scope_Suppress
:= (others => True);
285 Analyze_And_Resolve
(N
, Typ
);
286 Scope_Suppress
:= Svg
;
291 Svg
: constant Boolean := Scope_Suppress
(Suppress
);
294 Scope_Suppress
(Suppress
) := True;
295 Analyze_And_Resolve
(N
, Typ
);
296 Scope_Suppress
(Suppress
) := Svg
;
300 if Current_Scope
/= Scop
301 and then Scope_Is_Transient
303 -- This can only happen if a transient scope was created
304 -- for an inner expression, which will be removed upon
305 -- completion of the analysis of an enclosing construct.
306 -- The transient scope must have the suppress status of
307 -- the enclosing environment, not of this Analyze call.
309 Scope_Stack
.Table
(Scope_Stack
.Last
).Save_Scope_Suppress
:=
312 end Analyze_And_Resolve
;
314 procedure Analyze_And_Resolve
318 Scop
: constant Entity_Id
:= Current_Scope
;
321 if Suppress
= All_Checks
then
323 Svg
: constant Suppress_Array
:= Scope_Suppress
;
325 Scope_Suppress
:= (others => True);
326 Analyze_And_Resolve
(N
);
327 Scope_Suppress
:= Svg
;
332 Svg
: constant Boolean := Scope_Suppress
(Suppress
);
335 Scope_Suppress
(Suppress
) := True;
336 Analyze_And_Resolve
(N
);
337 Scope_Suppress
(Suppress
) := Svg
;
341 if Current_Scope
/= Scop
342 and then Scope_Is_Transient
344 Scope_Stack
.Table
(Scope_Stack
.Last
).Save_Scope_Suppress
:=
347 end Analyze_And_Resolve
;
349 ----------------------------
350 -- Check_Discriminant_Use --
351 ----------------------------
353 procedure Check_Discriminant_Use
(N
: Node_Id
) is
354 PN
: constant Node_Id
:= Parent
(N
);
355 Disc
: constant Entity_Id
:= Entity
(N
);
360 -- Any use in a default expression is legal
362 if In_Default_Expression
then
365 elsif Nkind
(PN
) = N_Range
then
367 -- Discriminant cannot be used to constrain a scalar type
371 if Nkind
(P
) = N_Range_Constraint
372 and then Nkind
(Parent
(P
)) = N_Subtype_Indication
373 and then Nkind
(Parent
(Parent
(P
))) = N_Component_Definition
375 Error_Msg_N
("discriminant cannot constrain scalar type", N
);
377 elsif Nkind
(P
) = N_Index_Or_Discriminant_Constraint
then
379 -- The following check catches the unusual case where
380 -- a discriminant appears within an index constraint
381 -- that is part of a larger expression within a constraint
382 -- on a component, e.g. "C : Int range 1 .. F (new A(1 .. D))".
383 -- For now we only check case of record components, and
384 -- note that a similar check should also apply in the
385 -- case of discriminant constraints below. ???
387 -- Note that the check for N_Subtype_Declaration below is to
388 -- detect the valid use of discriminants in the constraints of a
389 -- subtype declaration when this subtype declaration appears
390 -- inside the scope of a record type (which is syntactically
391 -- illegal, but which may be created as part of derived type
392 -- processing for records). See Sem_Ch3.Build_Derived_Record_Type
395 if Ekind
(Current_Scope
) = E_Record_Type
396 and then Scope
(Disc
) = Current_Scope
398 (Nkind
(Parent
(P
)) = N_Subtype_Indication
400 (Nkind
(Parent
(Parent
(P
))) = N_Component_Definition
402 Nkind
(Parent
(Parent
(P
))) = N_Subtype_Declaration
)
403 and then Paren_Count
(N
) = 0)
406 ("discriminant must appear alone in component constraint", N
);
410 -- Detect a common beginner error:
412 -- type R (D : Positive := 100) is record
413 -- Name : String (1 .. D);
416 -- The default value causes an object of type R to be
417 -- allocated with room for Positive'Last characters.
425 function Large_Storage_Type
(T
: Entity_Id
) return Boolean;
426 -- Return True if type T has a large enough range that
427 -- any array whose index type covered the whole range of
428 -- the type would likely raise Storage_Error.
430 ------------------------
431 -- Large_Storage_Type --
432 ------------------------
434 function Large_Storage_Type
(T
: Entity_Id
) return Boolean is
439 T
= Standard_Positive
441 T
= Standard_Natural
;
442 end Large_Storage_Type
;
445 -- Check that the Disc has a large range
447 if not Large_Storage_Type
(Etype
(Disc
)) then
451 -- If the enclosing type is limited, we allocate only the
452 -- default value, not the maximum, and there is no need for
455 if Is_Limited_Type
(Scope
(Disc
)) then
459 -- Check that it is the high bound
461 if N
/= High_Bound
(PN
)
462 or else No
(Discriminant_Default_Value
(Disc
))
467 -- Check the array allows a large range at this bound.
468 -- First find the array
472 if Nkind
(SI
) /= N_Subtype_Indication
then
476 T
:= Entity
(Subtype_Mark
(SI
));
478 if not Is_Array_Type
(T
) then
482 -- Next, find the dimension
484 TB
:= First_Index
(T
);
485 CB
:= First
(Constraints
(P
));
487 and then Present
(TB
)
488 and then Present
(CB
)
499 -- Now, check the dimension has a large range
501 if not Large_Storage_Type
(Etype
(TB
)) then
505 -- Warn about the danger
508 ("creation of & object may raise Storage_Error?",
517 -- Legal case is in index or discriminant constraint
519 elsif Nkind
(PN
) = N_Index_Or_Discriminant_Constraint
520 or else Nkind
(PN
) = N_Discriminant_Association
522 if Paren_Count
(N
) > 0 then
524 ("discriminant in constraint must appear alone", N
);
526 elsif Nkind
(N
) = N_Expanded_Name
527 and then Comes_From_Source
(N
)
530 ("discriminant must appear alone as a direct name", N
);
535 -- Otherwise, context is an expression. It should not be within
536 -- (i.e. a subexpression of) a constraint for a component.
541 while Nkind
(P
) /= N_Component_Declaration
542 and then Nkind
(P
) /= N_Subtype_Indication
543 and then Nkind
(P
) /= N_Entry_Declaration
550 -- If the discriminant is used in an expression that is a bound
551 -- of a scalar type, an Itype is created and the bounds are attached
552 -- to its range, not to the original subtype indication. Such use
553 -- is of course a double fault.
555 if (Nkind
(P
) = N_Subtype_Indication
557 (Nkind
(Parent
(P
)) = N_Component_Definition
559 Nkind
(Parent
(P
)) = N_Derived_Type_Definition
)
560 and then D
= Constraint
(P
))
562 -- The constraint itself may be given by a subtype indication,
563 -- rather than by a more common discrete range.
565 or else (Nkind
(P
) = N_Subtype_Indication
567 Nkind
(Parent
(P
)) = N_Index_Or_Discriminant_Constraint
)
568 or else Nkind
(P
) = N_Entry_Declaration
569 or else Nkind
(D
) = N_Defining_Identifier
572 ("discriminant in constraint must appear alone", N
);
575 end Check_Discriminant_Use
;
577 --------------------------------
578 -- Check_For_Visible_Operator --
579 --------------------------------
581 procedure Check_For_Visible_Operator
(N
: Node_Id
; T
: Entity_Id
) is
583 if Is_Invisible_Operator
(N
, T
) then
585 ("operator for} is not directly visible!", N
, First_Subtype
(T
));
586 Error_Msg_N
("use clause would make operation legal!", N
);
588 end Check_For_Visible_Operator
;
590 ----------------------------------
591 -- Check_Fully_Declared_Prefix --
592 ----------------------------------
594 procedure Check_Fully_Declared_Prefix
599 -- Check that the designated type of the prefix of a dereference is
600 -- not an incomplete type. This cannot be done unconditionally, because
601 -- dereferences of private types are legal in default expressions. This
602 -- case is taken care of in Check_Fully_Declared, called below. There
603 -- are also 2005 cases where it is legal for the prefix to be unfrozen.
605 -- This consideration also applies to similar checks for allocators,
606 -- qualified expressions, and type conversions.
608 -- An additional exception concerns other per-object expressions that
609 -- are not directly related to component declarations, in particular
610 -- representation pragmas for tasks. These will be per-object
611 -- expressions if they depend on discriminants or some global entity.
612 -- If the task has access discriminants, the designated type may be
613 -- incomplete at the point the expression is resolved. This resolution
614 -- takes place within the body of the initialization procedure, where
615 -- the discriminant is replaced by its discriminal.
617 if Is_Entity_Name
(Pref
)
618 and then Ekind
(Entity
(Pref
)) = E_In_Parameter
622 -- Ada 2005 (AI-326): Tagged incomplete types allowed. The wrong usages
623 -- are handled by Analyze_Access_Attribute, Analyze_Assignment,
624 -- Analyze_Object_Renaming, and Freeze_Entity.
626 elsif Ada_Version
>= Ada_05
627 and then Is_Entity_Name
(Pref
)
628 and then Ekind
(Directly_Designated_Type
(Etype
(Pref
))) =
630 and then Is_Tagged_Type
(Directly_Designated_Type
(Etype
(Pref
)))
634 Check_Fully_Declared
(Typ
, Parent
(Pref
));
636 end Check_Fully_Declared_Prefix
;
638 ------------------------------
639 -- Check_Infinite_Recursion --
640 ------------------------------
642 function Check_Infinite_Recursion
(N
: Node_Id
) return Boolean is
646 function Same_Argument_List
return Boolean;
647 -- Check whether list of actuals is identical to list of formals
648 -- of called function (which is also the enclosing scope).
650 ------------------------
651 -- Same_Argument_List --
652 ------------------------
654 function Same_Argument_List
return Boolean is
660 if not Is_Entity_Name
(Name
(N
)) then
663 Subp
:= Entity
(Name
(N
));
666 F
:= First_Formal
(Subp
);
667 A
:= First_Actual
(N
);
668 while Present
(F
) and then Present
(A
) loop
669 if not Is_Entity_Name
(A
)
670 or else Entity
(A
) /= F
680 end Same_Argument_List
;
682 -- Start of processing for Check_Infinite_Recursion
685 -- Loop moving up tree, quitting if something tells us we are
686 -- definitely not in an infinite recursion situation.
691 exit when Nkind
(P
) = N_Subprogram_Body
;
693 if Nkind
(P
) = N_Or_Else
or else
694 Nkind
(P
) = N_And_Then
or else
695 Nkind
(P
) = N_If_Statement
or else
696 Nkind
(P
) = N_Case_Statement
700 elsif Nkind
(P
) = N_Handled_Sequence_Of_Statements
701 and then C
/= First
(Statements
(P
))
703 -- If the call is the expression of a return statement and
704 -- the actuals are identical to the formals, it's worth a
705 -- warning. However, we skip this if there is an immediately
706 -- preceding raise statement, since the call is never executed.
708 -- Furthermore, this corresponds to a common idiom:
710 -- function F (L : Thing) return Boolean is
712 -- raise Program_Error;
716 -- for generating a stub function
718 if Nkind
(Parent
(N
)) = N_Return_Statement
719 and then Same_Argument_List
721 exit when not Is_List_Member
(Parent
(N
));
723 -- OK, return statement is in a statement list, look for raise
729 -- Skip past N_Freeze_Entity nodes generated by expansion
731 Nod
:= Prev
(Parent
(N
));
733 and then Nkind
(Nod
) = N_Freeze_Entity
738 -- If no raise statement, give warning
740 exit when Nkind
(Nod
) /= N_Raise_Statement
742 (Nkind
(Nod
) not in N_Raise_xxx_Error
743 or else Present
(Condition
(Nod
)));
754 Error_Msg_N
("possible infinite recursion?", N
);
755 Error_Msg_N
("\Storage_Error may be raised at run time?", N
);
758 end Check_Infinite_Recursion
;
760 -------------------------------
761 -- Check_Initialization_Call --
762 -------------------------------
764 procedure Check_Initialization_Call
(N
: Entity_Id
; Nam
: Entity_Id
) is
765 Typ
: constant Entity_Id
:= Etype
(First_Formal
(Nam
));
767 function Uses_SS
(T
: Entity_Id
) return Boolean;
768 -- Check whether the creation of an object of the type will involve
769 -- use of the secondary stack. If T is a record type, this is true
770 -- if the expression for some component uses the secondary stack, eg.
771 -- through a call to a function that returns an unconstrained value.
772 -- False if T is controlled, because cleanups occur elsewhere.
778 function Uses_SS
(T
: Entity_Id
) return Boolean is
783 if Is_Controlled
(T
) then
786 elsif Is_Array_Type
(T
) then
787 return Uses_SS
(Component_Type
(T
));
789 elsif Is_Record_Type
(T
) then
790 Comp
:= First_Component
(T
);
791 while Present
(Comp
) loop
792 if Ekind
(Comp
) = E_Component
793 and then Nkind
(Parent
(Comp
)) = N_Component_Declaration
795 Expr
:= Expression
(Parent
(Comp
));
797 -- The expression for a dynamic component may be
798 -- rewritten as a dereference. Retrieve original
801 if Nkind
(Original_Node
(Expr
)) = N_Function_Call
802 and then Requires_Transient_Scope
(Etype
(Expr
))
806 elsif Uses_SS
(Etype
(Comp
)) then
811 Next_Component
(Comp
);
821 -- Start of processing for Check_Initialization_Call
824 -- Nothing to do if functions do not use the secondary stack for
825 -- returns (i.e. they use a depressed stack pointer instead).
827 if Functions_Return_By_DSP_On_Target
then
830 -- Otherwise establish a transient scope if the type needs it
832 elsif Uses_SS
(Typ
) then
833 Establish_Transient_Scope
(First_Actual
(N
), Sec_Stack
=> True);
835 end Check_Initialization_Call
;
837 ------------------------------
838 -- Check_Parameterless_Call --
839 ------------------------------
841 procedure Check_Parameterless_Call
(N
: Node_Id
) is
844 function Prefix_Is_Access_Subp
return Boolean;
845 -- If the prefix is of an access_to_subprogram type, the node must be
846 -- rewritten as a call. Ditto if the prefix is overloaded and all its
847 -- interpretations are access to subprograms.
849 ---------------------------
850 -- Prefix_Is_Access_Subp --
851 ---------------------------
853 function Prefix_Is_Access_Subp
return Boolean is
858 if not Is_Overloaded
(N
) then
860 Ekind
(Etype
(N
)) = E_Subprogram_Type
861 and then Base_Type
(Etype
(Etype
(N
))) /= Standard_Void_Type
;
863 Get_First_Interp
(N
, I
, It
);
864 while Present
(It
.Typ
) loop
865 if Ekind
(It
.Typ
) /= E_Subprogram_Type
866 or else Base_Type
(Etype
(It
.Typ
)) = Standard_Void_Type
871 Get_Next_Interp
(I
, It
);
876 end Prefix_Is_Access_Subp
;
878 -- Start of processing for Check_Parameterless_Call
881 -- Defend against junk stuff if errors already detected
883 if Total_Errors_Detected
/= 0 then
884 if Nkind
(N
) in N_Has_Etype
and then Etype
(N
) = Any_Type
then
886 elsif Nkind
(N
) in N_Has_Chars
887 and then Chars
(N
) in Error_Name_Or_No_Name
895 -- If the context expects a value, and the name is a procedure,
896 -- this is most likely a missing 'Access. Do not try to resolve
897 -- the parameterless call, error will be caught when the outer
900 if Is_Entity_Name
(N
)
901 and then Ekind
(Entity
(N
)) = E_Procedure
902 and then not Is_Overloaded
(N
)
904 (Nkind
(Parent
(N
)) = N_Parameter_Association
905 or else Nkind
(Parent
(N
)) = N_Function_Call
906 or else Nkind
(Parent
(N
)) = N_Procedure_Call_Statement
)
911 -- Rewrite as call if overloadable entity that is (or could be, in
912 -- the overloaded case) a function call. If we know for sure that
913 -- the entity is an enumeration literal, we do not rewrite it.
915 if (Is_Entity_Name
(N
)
916 and then Is_Overloadable
(Entity
(N
))
917 and then (Ekind
(Entity
(N
)) /= E_Enumeration_Literal
918 or else Is_Overloaded
(N
)))
920 -- Rewrite as call if it is an explicit deference of an expression of
921 -- a subprogram access type, and the suprogram type is not that of a
922 -- procedure or entry.
925 (Nkind
(N
) = N_Explicit_Dereference
and then Prefix_Is_Access_Subp
)
927 -- Rewrite as call if it is a selected component which is a function,
928 -- this is the case of a call to a protected function (which may be
929 -- overloaded with other protected operations).
932 (Nkind
(N
) = N_Selected_Component
933 and then (Ekind
(Entity
(Selector_Name
(N
))) = E_Function
935 ((Ekind
(Entity
(Selector_Name
(N
))) = E_Entry
937 Ekind
(Entity
(Selector_Name
(N
))) = E_Procedure
)
938 and then Is_Overloaded
(Selector_Name
(N
)))))
940 -- If one of the above three conditions is met, rewrite as call.
941 -- Apply the rewriting only once.
944 if Nkind
(Parent
(N
)) /= N_Function_Call
945 or else N
/= Name
(Parent
(N
))
949 -- If overloaded, overload set belongs to new copy
951 Save_Interps
(N
, Nam
);
953 -- Change node to parameterless function call (note that the
954 -- Parameter_Associations associations field is left set to Empty,
955 -- its normal default value since there are no parameters)
957 Change_Node
(N
, N_Function_Call
);
959 Set_Sloc
(N
, Sloc
(Nam
));
963 elsif Nkind
(N
) = N_Parameter_Association
then
964 Check_Parameterless_Call
(Explicit_Actual_Parameter
(N
));
966 end Check_Parameterless_Call
;
968 ----------------------
969 -- Is_Predefined_Op --
970 ----------------------
972 function Is_Predefined_Op
(Nam
: Entity_Id
) return Boolean is
974 return Is_Intrinsic_Subprogram
(Nam
)
975 and then not Is_Generic_Instance
(Nam
)
976 and then Chars
(Nam
) in Any_Operator_Name
977 and then (No
(Alias
(Nam
))
978 or else Is_Predefined_Op
(Alias
(Nam
)));
979 end Is_Predefined_Op
;
981 -----------------------------
982 -- Make_Call_Into_Operator --
983 -----------------------------
985 procedure Make_Call_Into_Operator
990 Op_Name
: constant Name_Id
:= Chars
(Op_Id
);
991 Act1
: Node_Id
:= First_Actual
(N
);
992 Act2
: Node_Id
:= Next_Actual
(Act1
);
993 Error
: Boolean := False;
994 Func
: constant Entity_Id
:= Entity
(Name
(N
));
995 Is_Binary
: constant Boolean := Present
(Act2
);
997 Opnd_Type
: Entity_Id
;
998 Orig_Type
: Entity_Id
:= Empty
;
1001 type Kind_Test
is access function (E
: Entity_Id
) return Boolean;
1003 function Is_Definite_Access_Type
(E
: Entity_Id
) return Boolean;
1004 -- Determine whether E is an access type declared by an access decla-
1005 -- ration, and not an (anonymous) allocator type.
1007 function Operand_Type_In_Scope
(S
: Entity_Id
) return Boolean;
1008 -- If the operand is not universal, and the operator is given by a
1009 -- expanded name, verify that the operand has an interpretation with
1010 -- a type defined in the given scope of the operator.
1012 function Type_In_P
(Test
: Kind_Test
) return Entity_Id
;
1013 -- Find a type of the given class in the package Pack that contains
1016 -----------------------------
1017 -- Is_Definite_Access_Type --
1018 -----------------------------
1020 function Is_Definite_Access_Type
(E
: Entity_Id
) return Boolean is
1021 Btyp
: constant Entity_Id
:= Base_Type
(E
);
1023 return Ekind
(Btyp
) = E_Access_Type
1024 or else (Ekind
(Btyp
) = E_Access_Subprogram_Type
1025 and then Comes_From_Source
(Btyp
));
1026 end Is_Definite_Access_Type
;
1028 ---------------------------
1029 -- Operand_Type_In_Scope --
1030 ---------------------------
1032 function Operand_Type_In_Scope
(S
: Entity_Id
) return Boolean is
1033 Nod
: constant Node_Id
:= Right_Opnd
(Op_Node
);
1038 if not Is_Overloaded
(Nod
) then
1039 return Scope
(Base_Type
(Etype
(Nod
))) = S
;
1042 Get_First_Interp
(Nod
, I
, It
);
1043 while Present
(It
.Typ
) loop
1044 if Scope
(Base_Type
(It
.Typ
)) = S
then
1048 Get_Next_Interp
(I
, It
);
1053 end Operand_Type_In_Scope
;
1059 function Type_In_P
(Test
: Kind_Test
) return Entity_Id
is
1062 function In_Decl
return Boolean;
1063 -- Verify that node is not part of the type declaration for the
1064 -- candidate type, which would otherwise be invisible.
1070 function In_Decl
return Boolean is
1071 Decl_Node
: constant Node_Id
:= Parent
(E
);
1077 if Etype
(E
) = Any_Type
then
1080 elsif No
(Decl_Node
) then
1085 and then Nkind
(N2
) /= N_Compilation_Unit
1087 if N2
= Decl_Node
then
1098 -- Start of processing for Type_In_P
1101 -- If the context type is declared in the prefix package, this
1102 -- is the desired base type.
1104 if Scope
(Base_Type
(Typ
)) = Pack
1107 return Base_Type
(Typ
);
1110 E
:= First_Entity
(Pack
);
1111 while Present
(E
) loop
1113 and then not In_Decl
1125 -- Start of processing for Make_Call_Into_Operator
1128 Op_Node
:= New_Node
(Operator_Kind
(Op_Name
, Is_Binary
), Sloc
(N
));
1133 Set_Left_Opnd
(Op_Node
, Relocate_Node
(Act1
));
1134 Set_Right_Opnd
(Op_Node
, Relocate_Node
(Act2
));
1135 Save_Interps
(Act1
, Left_Opnd
(Op_Node
));
1136 Save_Interps
(Act2
, Right_Opnd
(Op_Node
));
1137 Act1
:= Left_Opnd
(Op_Node
);
1138 Act2
:= Right_Opnd
(Op_Node
);
1143 Set_Right_Opnd
(Op_Node
, Relocate_Node
(Act1
));
1144 Save_Interps
(Act1
, Right_Opnd
(Op_Node
));
1145 Act1
:= Right_Opnd
(Op_Node
);
1148 -- If the operator is denoted by an expanded name, and the prefix is
1149 -- not Standard, but the operator is a predefined one whose scope is
1150 -- Standard, then this is an implicit_operator, inserted as an
1151 -- interpretation by the procedure of the same name. This procedure
1152 -- overestimates the presence of implicit operators, because it does
1153 -- not examine the type of the operands. Verify now that the operand
1154 -- type appears in the given scope. If right operand is universal,
1155 -- check the other operand. In the case of concatenation, either
1156 -- argument can be the component type, so check the type of the result.
1157 -- If both arguments are literals, look for a type of the right kind
1158 -- defined in the given scope. This elaborate nonsense is brought to
1159 -- you courtesy of b33302a. The type itself must be frozen, so we must
1160 -- find the type of the proper class in the given scope.
1162 -- A final wrinkle is the multiplication operator for fixed point
1163 -- types, which is defined in Standard only, and not in the scope of
1164 -- the fixed_point type itself.
1166 if Nkind
(Name
(N
)) = N_Expanded_Name
then
1167 Pack
:= Entity
(Prefix
(Name
(N
)));
1169 -- If the entity being called is defined in the given package,
1170 -- it is a renaming of a predefined operator, and known to be
1173 if Scope
(Entity
(Name
(N
))) = Pack
1174 and then Pack
/= Standard_Standard
1178 -- Visibility does not need to be checked in an instance: if the
1179 -- operator was not visible in the generic it has been diagnosed
1180 -- already, else there is an implicit copy of it in the instance.
1182 elsif In_Instance
then
1185 elsif (Op_Name
= Name_Op_Multiply
1186 or else Op_Name
= Name_Op_Divide
)
1187 and then Is_Fixed_Point_Type
(Etype
(Left_Opnd
(Op_Node
)))
1188 and then Is_Fixed_Point_Type
(Etype
(Right_Opnd
(Op_Node
)))
1190 if Pack
/= Standard_Standard
then
1194 -- Ada 2005, AI-420: Predefined equality on Universal_Access
1197 elsif Ada_Version
>= Ada_05
1198 and then (Op_Name
= Name_Op_Eq
or else Op_Name
= Name_Op_Ne
)
1199 and then Ekind
(Etype
(Act1
)) = E_Anonymous_Access_Type
1204 Opnd_Type
:= Base_Type
(Etype
(Right_Opnd
(Op_Node
)));
1206 if Op_Name
= Name_Op_Concat
then
1207 Opnd_Type
:= Base_Type
(Typ
);
1209 elsif (Scope
(Opnd_Type
) = Standard_Standard
1211 or else (Nkind
(Right_Opnd
(Op_Node
)) = N_Attribute_Reference
1213 and then not Comes_From_Source
(Opnd_Type
))
1215 Opnd_Type
:= Base_Type
(Etype
(Left_Opnd
(Op_Node
)));
1218 if Scope
(Opnd_Type
) = Standard_Standard
then
1220 -- Verify that the scope contains a type that corresponds to
1221 -- the given literal. Optimize the case where Pack is Standard.
1223 if Pack
/= Standard_Standard
then
1225 if Opnd_Type
= Universal_Integer
then
1226 Orig_Type
:= Type_In_P
(Is_Integer_Type
'Access);
1228 elsif Opnd_Type
= Universal_Real
then
1229 Orig_Type
:= Type_In_P
(Is_Real_Type
'Access);
1231 elsif Opnd_Type
= Any_String
then
1232 Orig_Type
:= Type_In_P
(Is_String_Type
'Access);
1234 elsif Opnd_Type
= Any_Access
then
1235 Orig_Type
:= Type_In_P
(Is_Definite_Access_Type
'Access);
1237 elsif Opnd_Type
= Any_Composite
then
1238 Orig_Type
:= Type_In_P
(Is_Composite_Type
'Access);
1240 if Present
(Orig_Type
) then
1241 if Has_Private_Component
(Orig_Type
) then
1244 Set_Etype
(Act1
, Orig_Type
);
1247 Set_Etype
(Act2
, Orig_Type
);
1256 Error
:= No
(Orig_Type
);
1259 elsif Ekind
(Opnd_Type
) = E_Allocator_Type
1260 and then No
(Type_In_P
(Is_Definite_Access_Type
'Access))
1264 -- If the type is defined elsewhere, and the operator is not
1265 -- defined in the given scope (by a renaming declaration, e.g.)
1266 -- then this is an error as well. If an extension of System is
1267 -- present, and the type may be defined there, Pack must be
1270 elsif Scope
(Opnd_Type
) /= Pack
1271 and then Scope
(Op_Id
) /= Pack
1272 and then (No
(System_Aux_Id
)
1273 or else Scope
(Opnd_Type
) /= System_Aux_Id
1274 or else Pack
/= Scope
(System_Aux_Id
))
1276 if not Is_Overloaded
(Right_Opnd
(Op_Node
)) then
1279 Error
:= not Operand_Type_In_Scope
(Pack
);
1282 elsif Pack
= Standard_Standard
1283 and then not Operand_Type_In_Scope
(Standard_Standard
)
1290 Error_Msg_Node_2
:= Pack
;
1292 ("& not declared in&", N
, Selector_Name
(Name
(N
)));
1293 Set_Etype
(N
, Any_Type
);
1298 Set_Chars
(Op_Node
, Op_Name
);
1300 if not Is_Private_Type
(Etype
(N
)) then
1301 Set_Etype
(Op_Node
, Base_Type
(Etype
(N
)));
1303 Set_Etype
(Op_Node
, Etype
(N
));
1306 -- If this is a call to a function that renames a predefined equality,
1307 -- the renaming declaration provides a type that must be used to
1308 -- resolve the operands. This must be done now because resolution of
1309 -- the equality node will not resolve any remaining ambiguity, and it
1310 -- assumes that the first operand is not overloaded.
1312 if (Op_Name
= Name_Op_Eq
or else Op_Name
= Name_Op_Ne
)
1313 and then Ekind
(Func
) = E_Function
1314 and then Is_Overloaded
(Act1
)
1316 Resolve
(Act1
, Base_Type
(Etype
(First_Formal
(Func
))));
1317 Resolve
(Act2
, Base_Type
(Etype
(First_Formal
(Func
))));
1320 Set_Entity
(Op_Node
, Op_Id
);
1321 Generate_Reference
(Op_Id
, N
, ' ');
1322 Rewrite
(N
, Op_Node
);
1324 -- If this is an arithmetic operator and the result type is private,
1325 -- the operands and the result must be wrapped in conversion to
1326 -- expose the underlying numeric type and expand the proper checks,
1327 -- e.g. on division.
1329 if Is_Private_Type
(Typ
) then
1331 when N_Op_Add | N_Op_Subtract | N_Op_Multiply | N_Op_Divide |
1332 N_Op_Expon | N_Op_Mod | N_Op_Rem
=>
1333 Resolve_Intrinsic_Operator
(N
, Typ
);
1335 when N_Op_Plus | N_Op_Minus | N_Op_Abs
=>
1336 Resolve_Intrinsic_Unary_Operator
(N
, Typ
);
1345 -- For predefined operators on literals, the operation freezes
1348 if Present
(Orig_Type
) then
1349 Set_Etype
(Act1
, Orig_Type
);
1350 Freeze_Expression
(Act1
);
1352 end Make_Call_Into_Operator
;
1358 function Operator_Kind
1360 Is_Binary
: Boolean) return Node_Kind
1366 if Op_Name
= Name_Op_And
then Kind
:= N_Op_And
;
1367 elsif Op_Name
= Name_Op_Or
then Kind
:= N_Op_Or
;
1368 elsif Op_Name
= Name_Op_Xor
then Kind
:= N_Op_Xor
;
1369 elsif Op_Name
= Name_Op_Eq
then Kind
:= N_Op_Eq
;
1370 elsif Op_Name
= Name_Op_Ne
then Kind
:= N_Op_Ne
;
1371 elsif Op_Name
= Name_Op_Lt
then Kind
:= N_Op_Lt
;
1372 elsif Op_Name
= Name_Op_Le
then Kind
:= N_Op_Le
;
1373 elsif Op_Name
= Name_Op_Gt
then Kind
:= N_Op_Gt
;
1374 elsif Op_Name
= Name_Op_Ge
then Kind
:= N_Op_Ge
;
1375 elsif Op_Name
= Name_Op_Add
then Kind
:= N_Op_Add
;
1376 elsif Op_Name
= Name_Op_Subtract
then Kind
:= N_Op_Subtract
;
1377 elsif Op_Name
= Name_Op_Concat
then Kind
:= N_Op_Concat
;
1378 elsif Op_Name
= Name_Op_Multiply
then Kind
:= N_Op_Multiply
;
1379 elsif Op_Name
= Name_Op_Divide
then Kind
:= N_Op_Divide
;
1380 elsif Op_Name
= Name_Op_Mod
then Kind
:= N_Op_Mod
;
1381 elsif Op_Name
= Name_Op_Rem
then Kind
:= N_Op_Rem
;
1382 elsif Op_Name
= Name_Op_Expon
then Kind
:= N_Op_Expon
;
1384 raise Program_Error
;
1390 if Op_Name
= Name_Op_Add
then Kind
:= N_Op_Plus
;
1391 elsif Op_Name
= Name_Op_Subtract
then Kind
:= N_Op_Minus
;
1392 elsif Op_Name
= Name_Op_Abs
then Kind
:= N_Op_Abs
;
1393 elsif Op_Name
= Name_Op_Not
then Kind
:= N_Op_Not
;
1395 raise Program_Error
;
1402 -----------------------------
1403 -- Pre_Analyze_And_Resolve --
1404 -----------------------------
1406 procedure Pre_Analyze_And_Resolve
(N
: Node_Id
; T
: Entity_Id
) is
1407 Save_Full_Analysis
: constant Boolean := Full_Analysis
;
1410 Full_Analysis
:= False;
1411 Expander_Mode_Save_And_Set
(False);
1413 -- We suppress all checks for this analysis, since the checks will
1414 -- be applied properly, and in the right location, when the default
1415 -- expression is reanalyzed and reexpanded later on.
1417 Analyze_And_Resolve
(N
, T
, Suppress
=> All_Checks
);
1419 Expander_Mode_Restore
;
1420 Full_Analysis
:= Save_Full_Analysis
;
1421 end Pre_Analyze_And_Resolve
;
1423 -- Version without context type
1425 procedure Pre_Analyze_And_Resolve
(N
: Node_Id
) is
1426 Save_Full_Analysis
: constant Boolean := Full_Analysis
;
1429 Full_Analysis
:= False;
1430 Expander_Mode_Save_And_Set
(False);
1433 Resolve
(N
, Etype
(N
), Suppress
=> All_Checks
);
1435 Expander_Mode_Restore
;
1436 Full_Analysis
:= Save_Full_Analysis
;
1437 end Pre_Analyze_And_Resolve
;
1439 ----------------------------------
1440 -- Replace_Actual_Discriminants --
1441 ----------------------------------
1443 procedure Replace_Actual_Discriminants
(N
: Node_Id
; Default
: Node_Id
) is
1444 Loc
: constant Source_Ptr
:= Sloc
(N
);
1445 Tsk
: Node_Id
:= Empty
;
1447 function Process_Discr
(Nod
: Node_Id
) return Traverse_Result
;
1453 function Process_Discr
(Nod
: Node_Id
) return Traverse_Result
is
1457 if Nkind
(Nod
) = N_Identifier
then
1458 Ent
:= Entity
(Nod
);
1461 and then Ekind
(Ent
) = E_Discriminant
1464 Make_Selected_Component
(Loc
,
1465 Prefix
=> New_Copy_Tree
(Tsk
, New_Sloc
=> Loc
),
1466 Selector_Name
=> Make_Identifier
(Loc
, Chars
(Ent
))));
1468 Set_Etype
(Nod
, Etype
(Ent
));
1476 procedure Replace_Discrs
is new Traverse_Proc
(Process_Discr
);
1478 -- Start of processing for Replace_Actual_Discriminants
1481 if not Expander_Active
then
1485 if Nkind
(Name
(N
)) = N_Selected_Component
then
1486 Tsk
:= Prefix
(Name
(N
));
1488 elsif Nkind
(Name
(N
)) = N_Indexed_Component
then
1489 Tsk
:= Prefix
(Prefix
(Name
(N
)));
1495 Replace_Discrs
(Default
);
1497 end Replace_Actual_Discriminants
;
1503 procedure Resolve
(N
: Node_Id
; Typ
: Entity_Id
) is
1505 I1
: Interp_Index
:= 0; -- prevent junk warning
1508 Found
: Boolean := False;
1509 Seen
: Entity_Id
:= Empty
; -- prevent junk warning
1510 Ctx_Type
: Entity_Id
:= Typ
;
1511 Expr_Type
: Entity_Id
:= Empty
; -- prevent junk warning
1512 Err_Type
: Entity_Id
:= Empty
;
1513 Ambiguous
: Boolean := False;
1515 procedure Patch_Up_Value
(N
: Node_Id
; Typ
: Entity_Id
);
1516 -- Try and fix up a literal so that it matches its expected type. New
1517 -- literals are manufactured if necessary to avoid cascaded errors.
1519 procedure Resolution_Failed
;
1520 -- Called when attempt at resolving current expression fails
1522 --------------------
1523 -- Patch_Up_Value --
1524 --------------------
1526 procedure Patch_Up_Value
(N
: Node_Id
; Typ
: Entity_Id
) is
1528 if Nkind
(N
) = N_Integer_Literal
1529 and then Is_Real_Type
(Typ
)
1532 Make_Real_Literal
(Sloc
(N
),
1533 Realval
=> UR_From_Uint
(Intval
(N
))));
1534 Set_Etype
(N
, Universal_Real
);
1535 Set_Is_Static_Expression
(N
);
1537 elsif Nkind
(N
) = N_Real_Literal
1538 and then Is_Integer_Type
(Typ
)
1541 Make_Integer_Literal
(Sloc
(N
),
1542 Intval
=> UR_To_Uint
(Realval
(N
))));
1543 Set_Etype
(N
, Universal_Integer
);
1544 Set_Is_Static_Expression
(N
);
1545 elsif Nkind
(N
) = N_String_Literal
1546 and then Is_Character_Type
(Typ
)
1548 Set_Character_Literal_Name
(Char_Code
(Character'Pos ('A')));
1550 Make_Character_Literal
(Sloc
(N
),
1552 Char_Literal_Value
=>
1553 UI_From_Int
(Character'Pos ('A'))));
1554 Set_Etype
(N
, Any_Character
);
1555 Set_Is_Static_Expression
(N
);
1557 elsif Nkind
(N
) /= N_String_Literal
1558 and then Is_String_Type
(Typ
)
1561 Make_String_Literal
(Sloc
(N
),
1562 Strval
=> End_String
));
1564 elsif Nkind
(N
) = N_Range
then
1565 Patch_Up_Value
(Low_Bound
(N
), Typ
);
1566 Patch_Up_Value
(High_Bound
(N
), Typ
);
1570 -----------------------
1571 -- Resolution_Failed --
1572 -----------------------
1574 procedure Resolution_Failed
is
1576 Patch_Up_Value
(N
, Typ
);
1578 Debug_A_Exit
("resolving ", N
, " (done, resolution failed)");
1579 Set_Is_Overloaded
(N
, False);
1581 -- The caller will return without calling the expander, so we need
1582 -- to set the analyzed flag. Note that it is fine to set Analyzed
1583 -- to True even if we are in the middle of a shallow analysis,
1584 -- (see the spec of sem for more details) since this is an error
1585 -- situation anyway, and there is no point in repeating the
1586 -- analysis later (indeed it won't work to repeat it later, since
1587 -- we haven't got a clear resolution of which entity is being
1590 Set_Analyzed
(N
, True);
1592 end Resolution_Failed
;
1594 -- Start of processing for Resolve
1601 -- Access attribute on remote subprogram cannot be used for
1602 -- a non-remote access-to-subprogram type.
1604 if Nkind
(N
) = N_Attribute_Reference
1605 and then (Attribute_Name
(N
) = Name_Access
1606 or else Attribute_Name
(N
) = Name_Unrestricted_Access
1607 or else Attribute_Name
(N
) = Name_Unchecked_Access
)
1608 and then Comes_From_Source
(N
)
1609 and then Is_Entity_Name
(Prefix
(N
))
1610 and then Is_Subprogram
(Entity
(Prefix
(N
)))
1611 and then Is_Remote_Call_Interface
(Entity
(Prefix
(N
)))
1612 and then not Is_Remote_Access_To_Subprogram_Type
(Typ
)
1615 ("prefix must statically denote a non-remote subprogram", N
);
1618 -- If the context is a Remote_Access_To_Subprogram, access attributes
1619 -- must be resolved with the corresponding fat pointer. There is no need
1620 -- to check for the attribute name since the return type of an
1621 -- attribute is never a remote type.
1623 if Nkind
(N
) = N_Attribute_Reference
1624 and then Comes_From_Source
(N
)
1625 and then (Is_Remote_Call_Interface
(Typ
)
1626 or else Is_Remote_Types
(Typ
))
1629 Attr
: constant Attribute_Id
:=
1630 Get_Attribute_Id
(Attribute_Name
(N
));
1631 Pref
: constant Node_Id
:= Prefix
(N
);
1634 Is_Remote
: Boolean := True;
1637 -- Check that Typ is a remote access-to-subprogram type
1639 if Is_Remote_Access_To_Subprogram_Type
(Typ
) then
1640 -- Prefix (N) must statically denote a remote subprogram
1641 -- declared in a package specification.
1643 if Attr
= Attribute_Access
then
1644 Decl
:= Unit_Declaration_Node
(Entity
(Pref
));
1646 if Nkind
(Decl
) = N_Subprogram_Body
then
1647 Spec
:= Corresponding_Spec
(Decl
);
1649 if not No
(Spec
) then
1650 Decl
:= Unit_Declaration_Node
(Spec
);
1654 Spec
:= Parent
(Decl
);
1656 if not Is_Entity_Name
(Prefix
(N
))
1657 or else Nkind
(Spec
) /= N_Package_Specification
1659 not Is_Remote_Call_Interface
(Defining_Entity
(Spec
))
1663 ("prefix must statically denote a remote subprogram ",
1668 -- If we are generating code for a distributed program.
1669 -- perform semantic checks against the corresponding
1672 if (Attr
= Attribute_Access
1673 or else Attr
= Attribute_Unchecked_Access
1674 or else Attr
= Attribute_Unrestricted_Access
)
1675 and then Expander_Active
1676 and then Get_PCS_Name
/= Name_No_DSA
1678 Check_Subtype_Conformant
1679 (New_Id
=> Entity
(Prefix
(N
)),
1680 Old_Id
=> Designated_Type
1681 (Corresponding_Remote_Type
(Typ
)),
1684 Process_Remote_AST_Attribute
(N
, Typ
);
1691 Debug_A_Entry
("resolving ", N
);
1693 if Comes_From_Source
(N
) then
1694 if Is_Fixed_Point_Type
(Typ
) then
1695 Check_Restriction
(No_Fixed_Point
, N
);
1697 elsif Is_Floating_Point_Type
(Typ
)
1698 and then Typ
/= Universal_Real
1699 and then Typ
/= Any_Real
1701 Check_Restriction
(No_Floating_Point
, N
);
1705 -- Return if already analyzed
1707 if Analyzed
(N
) then
1708 Debug_A_Exit
("resolving ", N
, " (done, already analyzed)");
1711 -- Return if type = Any_Type (previous error encountered)
1713 elsif Etype
(N
) = Any_Type
then
1714 Debug_A_Exit
("resolving ", N
, " (done, Etype = Any_Type)");
1718 Check_Parameterless_Call
(N
);
1720 -- If not overloaded, then we know the type, and all that needs doing
1721 -- is to check that this type is compatible with the context.
1723 if not Is_Overloaded
(N
) then
1724 Found
:= Covers
(Typ
, Etype
(N
));
1725 Expr_Type
:= Etype
(N
);
1727 -- In the overloaded case, we must select the interpretation that
1728 -- is compatible with the context (i.e. the type passed to Resolve)
1731 -- Loop through possible interpretations
1733 Get_First_Interp
(N
, I
, It
);
1734 Interp_Loop
: while Present
(It
.Typ
) loop
1736 -- We are only interested in interpretations that are compatible
1737 -- with the expected type, any other interpretations are ignored
1739 if not Covers
(Typ
, It
.Typ
) then
1740 if Debug_Flag_V
then
1741 Write_Str
(" interpretation incompatible with context");
1746 -- First matching interpretation
1752 Expr_Type
:= It
.Typ
;
1754 -- Matching interpretation that is not the first, maybe an
1755 -- error, but there are some cases where preference rules are
1756 -- used to choose between the two possibilities. These and
1757 -- some more obscure cases are handled in Disambiguate.
1760 Error_Msg_Sloc
:= Sloc
(Seen
);
1761 It1
:= Disambiguate
(N
, I1
, I
, Typ
);
1763 -- Disambiguation has succeeded. Skip the remaining
1766 if It1
/= No_Interp
then
1768 Expr_Type
:= It1
.Typ
;
1770 while Present
(It
.Typ
) loop
1771 Get_Next_Interp
(I
, It
);
1775 -- Before we issue an ambiguity complaint, check for
1776 -- the case of a subprogram call where at least one
1777 -- of the arguments is Any_Type, and if so, suppress
1778 -- the message, since it is a cascaded error.
1780 if Nkind
(N
) = N_Function_Call
1781 or else Nkind
(N
) = N_Procedure_Call_Statement
1788 A
:= First_Actual
(N
);
1789 while Present
(A
) loop
1792 if Nkind
(E
) = N_Parameter_Association
then
1793 E
:= Explicit_Actual_Parameter
(E
);
1796 if Etype
(E
) = Any_Type
then
1797 if Debug_Flag_V
then
1798 Write_Str
("Any_Type in call");
1809 elsif Nkind
(N
) in N_Binary_Op
1810 and then (Etype
(Left_Opnd
(N
)) = Any_Type
1811 or else Etype
(Right_Opnd
(N
)) = Any_Type
)
1815 elsif Nkind
(N
) in N_Unary_Op
1816 and then Etype
(Right_Opnd
(N
)) = Any_Type
1821 -- Not that special case, so issue message using the
1822 -- flag Ambiguous to control printing of the header
1823 -- message only at the start of an ambiguous set.
1825 if not Ambiguous
then
1826 if Nkind
(N
) = N_Function_Call
1827 and then Nkind
(Name
(N
)) = N_Explicit_Dereference
1830 ("ambiguous expression "
1831 & "(cannot resolve indirect call)!", N
);
1834 ("ambiguous expression (cannot resolve&)!",
1839 ("\\possible interpretation#!", N
);
1843 Error_Msg_Sloc
:= Sloc
(It
.Nam
);
1845 -- By default, the error message refers to the candidate
1846 -- interpretation. But if it is a predefined operator,
1847 -- it is implicitly declared at the declaration of
1848 -- the type of the operand. Recover the sloc of that
1849 -- declaration for the error message.
1851 if Nkind
(N
) in N_Op
1852 and then Scope
(It
.Nam
) = Standard_Standard
1853 and then not Is_Overloaded
(Right_Opnd
(N
))
1854 and then Scope
(Base_Type
(Etype
(Right_Opnd
(N
))))
1855 /= Standard_Standard
1857 Err_Type
:= First_Subtype
(Etype
(Right_Opnd
(N
)));
1859 if Comes_From_Source
(Err_Type
)
1860 and then Present
(Parent
(Err_Type
))
1862 Error_Msg_Sloc
:= Sloc
(Parent
(Err_Type
));
1865 elsif Nkind
(N
) in N_Binary_Op
1866 and then Scope
(It
.Nam
) = Standard_Standard
1867 and then not Is_Overloaded
(Left_Opnd
(N
))
1868 and then Scope
(Base_Type
(Etype
(Left_Opnd
(N
))))
1869 /= Standard_Standard
1871 Err_Type
:= First_Subtype
(Etype
(Left_Opnd
(N
)));
1873 if Comes_From_Source
(Err_Type
)
1874 and then Present
(Parent
(Err_Type
))
1876 Error_Msg_Sloc
:= Sloc
(Parent
(Err_Type
));
1879 -- If this is an indirect call, use the subprogram_type
1880 -- in the message, to have a meaningful location.
1881 -- Indicate as well if this is an inherited operation,
1882 -- created by a type declaration.
1884 elsif Nkind
(N
) = N_Function_Call
1885 and then Nkind
(Name
(N
)) = N_Explicit_Dereference
1886 and then Is_Type
(It
.Nam
)
1890 Sloc
(Associated_Node_For_Itype
(Err_Type
));
1896 if Nkind
(N
) in N_Op
1897 and then Scope
(It
.Nam
) = Standard_Standard
1898 and then Present
(Err_Type
)
1901 ("\\possible interpretation (predefined)#!", N
);
1904 Nkind
(Parent
(It
.Nam
)) = N_Full_Type_Declaration
1907 ("\\possible interpretation (inherited)#!", N
);
1909 Error_Msg_N
("\\possible interpretation#!", N
);
1915 -- We have a matching interpretation, Expr_Type is the
1916 -- type from this interpretation, and Seen is the entity.
1918 -- For an operator, just set the entity name. The type will
1919 -- be set by the specific operator resolution routine.
1921 if Nkind
(N
) in N_Op
then
1922 Set_Entity
(N
, Seen
);
1923 Generate_Reference
(Seen
, N
);
1925 elsif Nkind
(N
) = N_Character_Literal
then
1926 Set_Etype
(N
, Expr_Type
);
1928 -- For an explicit dereference, attribute reference, range,
1929 -- short-circuit form (which is not an operator node),
1930 -- or a call with a name that is an explicit dereference,
1931 -- there is nothing to be done at this point.
1933 elsif Nkind
(N
) = N_Explicit_Dereference
1934 or else Nkind
(N
) = N_Attribute_Reference
1935 or else Nkind
(N
) = N_And_Then
1936 or else Nkind
(N
) = N_Indexed_Component
1937 or else Nkind
(N
) = N_Or_Else
1938 or else Nkind
(N
) = N_Range
1939 or else Nkind
(N
) = N_Selected_Component
1940 or else Nkind
(N
) = N_Slice
1941 or else Nkind
(Name
(N
)) = N_Explicit_Dereference
1945 -- For procedure or function calls, set the type of the
1946 -- name, and also the entity pointer for the prefix
1948 elsif (Nkind
(N
) = N_Procedure_Call_Statement
1949 or else Nkind
(N
) = N_Function_Call
)
1950 and then (Is_Entity_Name
(Name
(N
))
1951 or else Nkind
(Name
(N
)) = N_Operator_Symbol
)
1953 Set_Etype
(Name
(N
), Expr_Type
);
1954 Set_Entity
(Name
(N
), Seen
);
1955 Generate_Reference
(Seen
, Name
(N
));
1957 elsif Nkind
(N
) = N_Function_Call
1958 and then Nkind
(Name
(N
)) = N_Selected_Component
1960 Set_Etype
(Name
(N
), Expr_Type
);
1961 Set_Entity
(Selector_Name
(Name
(N
)), Seen
);
1962 Generate_Reference
(Seen
, Selector_Name
(Name
(N
)));
1964 -- For all other cases, just set the type of the Name
1967 Set_Etype
(Name
(N
), Expr_Type
);
1972 -- Move to next interpretation
1974 exit Interp_Loop
when No
(It
.Typ
);
1976 Get_Next_Interp
(I
, It
);
1977 end loop Interp_Loop
;
1980 -- At this stage Found indicates whether or not an acceptable
1981 -- interpretation exists. If not, then we have an error, except
1982 -- that if the context is Any_Type as a result of some other error,
1983 -- then we suppress the error report.
1986 if Typ
/= Any_Type
then
1988 -- If type we are looking for is Void, then this is the
1989 -- procedure call case, and the error is simply that what
1990 -- we gave is not a procedure name (we think of procedure
1991 -- calls as expressions with types internally, but the user
1992 -- doesn't think of them this way!)
1994 if Typ
= Standard_Void_Type
then
1996 -- Special case message if function used as a procedure
1998 if Nkind
(N
) = N_Procedure_Call_Statement
1999 and then Is_Entity_Name
(Name
(N
))
2000 and then Ekind
(Entity
(Name
(N
))) = E_Function
2003 ("cannot use function & in a procedure call",
2004 Name
(N
), Entity
(Name
(N
)));
2006 -- Otherwise give general message (not clear what cases
2007 -- this covers, but no harm in providing for them!)
2010 Error_Msg_N
("expect procedure name in procedure call", N
);
2015 -- Otherwise we do have a subexpression with the wrong type
2017 -- Check for the case of an allocator which uses an access
2018 -- type instead of the designated type. This is a common
2019 -- error and we specialize the message, posting an error
2020 -- on the operand of the allocator, complaining that we
2021 -- expected the designated type of the allocator.
2023 elsif Nkind
(N
) = N_Allocator
2024 and then Ekind
(Typ
) in Access_Kind
2025 and then Ekind
(Etype
(N
)) in Access_Kind
2026 and then Designated_Type
(Etype
(N
)) = Typ
2028 Wrong_Type
(Expression
(N
), Designated_Type
(Typ
));
2031 -- Check for view mismatch on Null in instances, for
2032 -- which the view-swapping mechanism has no identifier.
2034 elsif (In_Instance
or else In_Inlined_Body
)
2035 and then (Nkind
(N
) = N_Null
)
2036 and then Is_Private_Type
(Typ
)
2037 and then Is_Access_Type
(Full_View
(Typ
))
2039 Resolve
(N
, Full_View
(Typ
));
2043 -- Check for an aggregate. Sometimes we can get bogus aggregates
2044 -- from misuse of parentheses, and we are about to complain about
2045 -- the aggregate without even looking inside it.
2047 -- Instead, if we have an aggregate of type Any_Composite, then
2048 -- analyze and resolve the component fields, and then only issue
2049 -- another message if we get no errors doing this (otherwise
2050 -- assume that the errors in the aggregate caused the problem).
2052 elsif Nkind
(N
) = N_Aggregate
2053 and then Etype
(N
) = Any_Composite
2055 -- Disable expansion in any case. If there is a type mismatch
2056 -- it may be fatal to try to expand the aggregate. The flag
2057 -- would otherwise be set to false when the error is posted.
2059 Expander_Active
:= False;
2062 procedure Check_Aggr
(Aggr
: Node_Id
);
2063 -- Check one aggregate, and set Found to True if we have a
2064 -- definite error in any of its elements
2066 procedure Check_Elmt
(Aelmt
: Node_Id
);
2067 -- Check one element of aggregate and set Found to True if
2068 -- we definitely have an error in the element.
2074 procedure Check_Aggr
(Aggr
: Node_Id
) is
2078 if Present
(Expressions
(Aggr
)) then
2079 Elmt
:= First
(Expressions
(Aggr
));
2080 while Present
(Elmt
) loop
2086 if Present
(Component_Associations
(Aggr
)) then
2087 Elmt
:= First
(Component_Associations
(Aggr
));
2088 while Present
(Elmt
) loop
2090 -- Nothing to check is this is a default-
2091 -- initialized component. The box will be
2092 -- be replaced by the appropriate call during
2095 if not Box_Present
(Elmt
) then
2096 Check_Elmt
(Expression
(Elmt
));
2108 procedure Check_Elmt
(Aelmt
: Node_Id
) is
2110 -- If we have a nested aggregate, go inside it (to
2111 -- attempt a naked analyze-resolve of the aggregate
2112 -- can cause undesirable cascaded errors). Do not
2113 -- resolve expression if it needs a type from context,
2114 -- as for integer * fixed expression.
2116 if Nkind
(Aelmt
) = N_Aggregate
then
2122 if not Is_Overloaded
(Aelmt
)
2123 and then Etype
(Aelmt
) /= Any_Fixed
2128 if Etype
(Aelmt
) = Any_Type
then
2139 -- If an error message was issued already, Found got reset
2140 -- to True, so if it is still False, issue the standard
2141 -- Wrong_Type message.
2144 if Is_Overloaded
(N
)
2145 and then Nkind
(N
) = N_Function_Call
2148 Subp_Name
: Node_Id
;
2150 if Is_Entity_Name
(Name
(N
)) then
2151 Subp_Name
:= Name
(N
);
2153 elsif Nkind
(Name
(N
)) = N_Selected_Component
then
2155 -- Protected operation: retrieve operation name
2157 Subp_Name
:= Selector_Name
(Name
(N
));
2159 raise Program_Error
;
2162 Error_Msg_Node_2
:= Typ
;
2163 Error_Msg_NE
("no visible interpretation of&" &
2164 " matches expected type&", N
, Subp_Name
);
2167 if All_Errors_Mode
then
2169 Index
: Interp_Index
;
2173 Error_Msg_N
("\\possible interpretations:", N
);
2175 Get_First_Interp
(Name
(N
), Index
, It
);
2176 while Present
(It
.Nam
) loop
2177 Error_Msg_Sloc
:= Sloc
(It
.Nam
);
2178 Error_Msg_Node_2
:= It
.Typ
;
2179 Error_Msg_NE
("\& declared#, type&", N
, It
.Nam
);
2180 Get_Next_Interp
(Index
, It
);
2184 Error_Msg_N
("\use -gnatf for details", N
);
2187 Wrong_Type
(N
, Typ
);
2195 -- Test if we have more than one interpretation for the context
2197 elsif Ambiguous
then
2201 -- Here we have an acceptable interpretation for the context
2204 -- Propagate type information and normalize tree for various
2205 -- predefined operations. If the context only imposes a class of
2206 -- types, rather than a specific type, propagate the actual type
2209 if Typ
= Any_Integer
2210 or else Typ
= Any_Boolean
2211 or else Typ
= Any_Modular
2212 or else Typ
= Any_Real
2213 or else Typ
= Any_Discrete
2215 Ctx_Type
:= Expr_Type
;
2217 -- Any_Fixed is legal in a real context only if a specific
2218 -- fixed point type is imposed. If Norman Cohen can be
2219 -- confused by this, it deserves a separate message.
2222 and then Expr_Type
= Any_Fixed
2224 Error_Msg_N
("illegal context for mixed mode operation", N
);
2225 Set_Etype
(N
, Universal_Real
);
2226 Ctx_Type
:= Universal_Real
;
2230 -- A user-defined operator is tranformed into a function call at
2231 -- this point, so that further processing knows that operators are
2232 -- really operators (i.e. are predefined operators). User-defined
2233 -- operators that are intrinsic are just renamings of the predefined
2234 -- ones, and need not be turned into calls either, but if they rename
2235 -- a different operator, we must transform the node accordingly.
2236 -- Instantiations of Unchecked_Conversion are intrinsic but are
2237 -- treated as functions, even if given an operator designator.
2239 if Nkind
(N
) in N_Op
2240 and then Present
(Entity
(N
))
2241 and then Ekind
(Entity
(N
)) /= E_Operator
2244 if not Is_Predefined_Op
(Entity
(N
)) then
2245 Rewrite_Operator_As_Call
(N
, Entity
(N
));
2247 elsif Present
(Alias
(Entity
(N
)))
2249 Nkind
(Parent
(Parent
(Entity
(N
))))
2250 = N_Subprogram_Renaming_Declaration
2252 Rewrite_Renamed_Operator
(N
, Alias
(Entity
(N
)), Typ
);
2254 -- If the node is rewritten, it will be fully resolved in
2255 -- Rewrite_Renamed_Operator.
2257 if Analyzed
(N
) then
2263 case N_Subexpr
'(Nkind (N)) is
2265 when N_Aggregate => Resolve_Aggregate (N, Ctx_Type);
2267 when N_Allocator => Resolve_Allocator (N, Ctx_Type);
2269 when N_And_Then | N_Or_Else
2270 => Resolve_Short_Circuit (N, Ctx_Type);
2272 when N_Attribute_Reference
2273 => Resolve_Attribute (N, Ctx_Type);
2275 when N_Character_Literal
2276 => Resolve_Character_Literal (N, Ctx_Type);
2278 when N_Conditional_Expression
2279 => Resolve_Conditional_Expression (N, Ctx_Type);
2281 when N_Expanded_Name
2282 => Resolve_Entity_Name (N, Ctx_Type);
2284 when N_Extension_Aggregate
2285 => Resolve_Extension_Aggregate (N, Ctx_Type);
2287 when N_Explicit_Dereference
2288 => Resolve_Explicit_Dereference (N, Ctx_Type);
2290 when N_Function_Call
2291 => Resolve_Call (N, Ctx_Type);
2294 => Resolve_Entity_Name (N, Ctx_Type);
2296 when N_Membership_Test
2297 => Resolve_Membership_Op (N, Ctx_Type);
2299 when N_Indexed_Component
2300 => Resolve_Indexed_Component (N, Ctx_Type);
2302 when N_Integer_Literal
2303 => Resolve_Integer_Literal (N, Ctx_Type);
2305 when N_Null => Resolve_Null (N, Ctx_Type);
2307 when N_Op_And | N_Op_Or | N_Op_Xor
2308 => Resolve_Logical_Op (N, Ctx_Type);
2310 when N_Op_Eq | N_Op_Ne
2311 => Resolve_Equality_Op (N, Ctx_Type);
2313 when N_Op_Lt | N_Op_Le | N_Op_Gt | N_Op_Ge
2314 => Resolve_Comparison_Op (N, Ctx_Type);
2316 when N_Op_Not => Resolve_Op_Not (N, Ctx_Type);
2318 when N_Op_Add | N_Op_Subtract | N_Op_Multiply |
2319 N_Op_Divide | N_Op_Mod | N_Op_Rem
2321 => Resolve_Arithmetic_Op (N, Ctx_Type);
2323 when N_Op_Concat => Resolve_Op_Concat (N, Ctx_Type);
2325 when N_Op_Expon => Resolve_Op_Expon (N, Ctx_Type);
2327 when N_Op_Plus | N_Op_Minus | N_Op_Abs
2328 => Resolve_Unary_Op (N, Ctx_Type);
2330 when N_Op_Shift => Resolve_Shift (N, Ctx_Type);
2332 when N_Procedure_Call_Statement
2333 => Resolve_Call (N, Ctx_Type);
2335 when N_Operator_Symbol
2336 => Resolve_Operator_Symbol (N, Ctx_Type);
2338 when N_Qualified_Expression
2339 => Resolve_Qualified_Expression (N, Ctx_Type);
2341 when N_Raise_xxx_Error
2342 => Set_Etype (N, Ctx_Type);
2344 when N_Range => Resolve_Range (N, Ctx_Type);
2347 => Resolve_Real_Literal (N, Ctx_Type);
2349 when N_Reference => Resolve_Reference (N, Ctx_Type);
2351 when N_Selected_Component
2352 => Resolve_Selected_Component (N, Ctx_Type);
2354 when N_Slice => Resolve_Slice (N, Ctx_Type);
2356 when N_String_Literal
2357 => Resolve_String_Literal (N, Ctx_Type);
2359 when N_Subprogram_Info
2360 => Resolve_Subprogram_Info (N, Ctx_Type);
2362 when N_Type_Conversion
2363 => Resolve_Type_Conversion (N, Ctx_Type);
2365 when N_Unchecked_Expression =>
2366 Resolve_Unchecked_Expression (N, Ctx_Type);
2368 when N_Unchecked_Type_Conversion =>
2369 Resolve_Unchecked_Type_Conversion (N, Ctx_Type);
2373 -- If the subexpression was replaced by a non-subexpression, then
2374 -- all we do is to expand it. The only legitimate case we know of
2375 -- is converting procedure call statement to entry call statements,
2376 -- but there may be others, so we are making this test general.
2378 if Nkind (N) not in N_Subexpr then
2379 Debug_A_Exit ("resolving ", N, " (done)");
2384 -- The expression is definitely NOT overloaded at this point, so
2385 -- we reset the Is_Overloaded flag to avoid any confusion when
2386 -- reanalyzing the node.
2388 Set_Is_Overloaded (N, False);
2390 -- Freeze expression type, entity if it is a name, and designated
2391 -- type if it is an allocator (RM 13.14(10,11,13)).
2393 -- Now that the resolution of the type of the node is complete,
2394 -- and we did not detect an error, we can expand this node. We
2395 -- skip the expand call if we are in a default expression, see
2396 -- section "Handling of Default Expressions" in Sem spec.
2398 Debug_A_Exit ("resolving ", N, " (done)");
2400 -- We unconditionally freeze the expression, even if we are in
2401 -- default expression mode (the Freeze_Expression routine tests
2402 -- this flag and only freezes static types if it is set).
2404 Freeze_Expression (N);
2406 -- Now we can do the expansion
2416 -- Version with check(s) suppressed
2418 procedure Resolve (N : Node_Id; Typ : Entity_Id; Suppress : Check_Id) is
2420 if Suppress = All_Checks then
2422 Svg : constant Suppress_Array := Scope_Suppress;
2424 Scope_Suppress := (others => True);
2426 Scope_Suppress := Svg;
2431 Svg : constant Boolean := Scope_Suppress (Suppress);
2433 Scope_Suppress (Suppress) := True;
2435 Scope_Suppress (Suppress) := Svg;
2444 -- Version with implicit type
2446 procedure Resolve (N : Node_Id) is
2448 Resolve (N, Etype (N));
2451 ---------------------
2452 -- Resolve_Actuals --
2453 ---------------------
2455 procedure Resolve_Actuals (N : Node_Id; Nam : Entity_Id) is
2456 Loc : constant Source_Ptr := Sloc (N);
2461 Prev : Node_Id := Empty;
2463 procedure Insert_Default;
2464 -- If the actual is missing in a call, insert in the actuals list
2465 -- an instance of the default expression. The insertion is always
2466 -- a named association.
2468 function Same_Ancestor (T1, T2 : Entity_Id) return Boolean;
2469 -- Check whether T1 and T2, or their full views, are derived from a
2470 -- common type. Used to enforce the restrictions on array conversions
2473 --------------------
2474 -- Insert_Default --
2475 --------------------
2477 procedure Insert_Default is
2482 -- Missing argument in call, nothing to insert
2484 if No (Default_Value (F)) then
2488 -- Note that we do a full New_Copy_Tree, so that any associated
2489 -- Itypes are properly copied. This may not be needed any more,
2490 -- but it does no harm as a safety measure! Defaults of a generic
2491 -- formal may be out of bounds of the corresponding actual (see
2492 -- cc1311b) and an additional check may be required.
2494 Actval := New_Copy_Tree (Default_Value (F),
2495 New_Scope => Current_Scope, New_Sloc => Loc);
2497 if Is_Concurrent_Type (Scope (Nam))
2498 and then Has_Discriminants (Scope (Nam))
2500 Replace_Actual_Discriminants (N, Actval);
2503 if Is_Overloadable (Nam)
2504 and then Present (Alias (Nam))
2506 if Base_Type (Etype (F)) /= Base_Type (Etype (Actval))
2507 and then not Is_Tagged_Type (Etype (F))
2509 -- If default is a real literal, do not introduce a
2510 -- conversion whose effect may depend on the run-time
2511 -- size of universal real.
2513 if Nkind (Actval) = N_Real_Literal then
2514 Set_Etype (Actval, Base_Type (Etype (F)));
2516 Actval := Unchecked_Convert_To (Etype (F), Actval);
2520 if Is_Scalar_Type (Etype (F)) then
2521 Enable_Range_Check (Actval);
2524 Set_Parent (Actval, N);
2526 -- Resolve aggregates with their base type, to avoid scope
2527 -- anomalies: the subtype was first built in the suprogram
2528 -- declaration, and the current call may be nested.
2530 if Nkind (Actval) = N_Aggregate
2531 and then Has_Discriminants (Etype (Actval))
2533 Analyze_And_Resolve (Actval, Base_Type (Etype (Actval)));
2535 Analyze_And_Resolve (Actval, Etype (Actval));
2539 Set_Parent (Actval, N);
2541 -- See note above concerning aggregates
2543 if Nkind (Actval) = N_Aggregate
2544 and then Has_Discriminants (Etype (Actval))
2546 Analyze_And_Resolve (Actval, Base_Type (Etype (Actval)));
2548 -- Resolve entities with their own type, which may differ
2549 -- from the type of a reference in a generic context (the
2550 -- view swapping mechanism did not anticipate the re-analysis
2551 -- of default values in calls).
2553 elsif Is_Entity_Name (Actval) then
2554 Analyze_And_Resolve (Actval, Etype (Entity (Actval)));
2557 Analyze_And_Resolve (Actval, Etype (Actval));
2561 -- If default is a tag indeterminate function call, propagate
2562 -- tag to obtain proper dispatching.
2564 if Is_Controlling_Formal (F)
2565 and then Nkind (Default_Value (F)) = N_Function_Call
2567 Set_Is_Controlling_Actual (Actval);
2572 -- If the default expression raises constraint error, then just
2573 -- silently replace it with an N_Raise_Constraint_Error node,
2574 -- since we already gave the warning on the subprogram spec.
2576 if Raises_Constraint_Error (Actval) then
2578 Make_Raise_Constraint_Error (Loc,
2579 Reason => CE_Range_Check_Failed));
2580 Set_Raises_Constraint_Error (Actval);
2581 Set_Etype (Actval, Etype (F));
2585 Make_Parameter_Association (Loc,
2586 Explicit_Actual_Parameter => Actval,
2587 Selector_Name => Make_Identifier (Loc, Chars (F)));
2589 -- Case of insertion is first named actual
2591 if No (Prev) or else
2592 Nkind (Parent (Prev)) /= N_Parameter_Association
2594 Set_Next_Named_Actual (Assoc, First_Named_Actual (N));
2595 Set_First_Named_Actual (N, Actval);
2598 if No (Parameter_Associations (N)) then
2599 Set_Parameter_Associations (N, New_List (Assoc));
2601 Append (Assoc, Parameter_Associations (N));
2605 Insert_After (Prev, Assoc);
2608 -- Case of insertion is not first named actual
2611 Set_Next_Named_Actual
2612 (Assoc, Next_Named_Actual (Parent (Prev)));
2613 Set_Next_Named_Actual (Parent (Prev), Actval);
2614 Append (Assoc, Parameter_Associations (N));
2617 Mark_Rewrite_Insertion (Assoc);
2618 Mark_Rewrite_Insertion (Actval);
2627 function Same_Ancestor (T1, T2 : Entity_Id) return Boolean is
2628 FT1 : Entity_Id := T1;
2629 FT2 : Entity_Id := T2;
2632 if Is_Private_Type (T1)
2633 and then Present (Full_View (T1))
2635 FT1 := Full_View (T1);
2638 if Is_Private_Type (T2)
2639 and then Present (Full_View (T2))
2641 FT2 := Full_View (T2);
2644 return Root_Type (Base_Type (FT1)) = Root_Type (Base_Type (FT2));
2647 -- Start of processing for Resolve_Actuals
2650 A := First_Actual (N);
2651 F := First_Formal (Nam);
2652 while Present (F) loop
2653 if No (A) and then Needs_No_Actuals (Nam) then
2656 -- If we have an error in any actual or formal, indicated by
2657 -- a type of Any_Type, then abandon resolution attempt, and
2658 -- set result type to Any_Type.
2660 elsif (Present (A) and then Etype (A) = Any_Type)
2661 or else Etype (F) = Any_Type
2663 Set_Etype (N, Any_Type);
2668 and then (Nkind (Parent (A)) /= N_Parameter_Association
2670 Chars (Selector_Name (Parent (A))) = Chars (F))
2672 -- If the formal is Out or In_Out, do not resolve and expand the
2673 -- conversion, because it is subsequently expanded into explicit
2674 -- temporaries and assignments. However, the object of the
2675 -- conversion can be resolved. An exception is the case of tagged
2676 -- type conversion with a class-wide actual. In that case we want
2677 -- the tag check to occur and no temporary will be needed (no
2678 -- representation change can occur) and the parameter is passed by
2679 -- reference, so we go ahead and resolve the type conversion.
2680 -- Another exception is the case of reference to component or
2681 -- subcomponent of a bit-packed array, in which case we want to
2682 -- defer expansion to the point the in and out assignments are
2685 if Ekind (F) /= E_In_Parameter
2686 and then Nkind (A) = N_Type_Conversion
2687 and then not Is_Class_Wide_Type (Etype (Expression (A)))
2689 if Ekind (F) = E_In_Out_Parameter
2690 and then Is_Array_Type (Etype (F))
2692 if Has_Aliased_Components (Etype (Expression (A)))
2693 /= Has_Aliased_Components (Etype (F))
2695 if Ada_Version < Ada_05 then
2697 ("both component types in a view conversion must be"
2698 & " aliased, or neither", A);
2700 -- Ada 2005: rule is relaxed (see AI-363)
2702 elsif Has_Aliased_Components (Etype (F))
2704 not Has_Aliased_Components (Etype (Expression (A)))
2707 ("view conversion operand must have aliased " &
2710 ("\since target type has aliased components", N);
2713 elsif not Same_Ancestor (Etype (F), Etype (Expression (A)))
2715 (Is_By_Reference_Type (Etype (F))
2716 or else Is_By_Reference_Type (Etype (Expression (A))))
2719 ("view conversion between unrelated by reference " &
2720 "array types not allowed (\'A
'I-00246)", A);
2724 if (Conversion_OK (A)
2725 or else Valid_Conversion (A, Etype (A), Expression (A)))
2726 and then not Is_Ref_To_Bit_Packed_Array (Expression (A))
2728 Resolve (Expression (A));
2732 if Nkind (A) = N_Type_Conversion
2733 and then Is_Array_Type (Etype (F))
2734 and then not Same_Ancestor (Etype (F), Etype (Expression (A)))
2736 (Is_Limited_Type (Etype (F))
2737 or else Is_Limited_Type (Etype (Expression (A))))
2740 ("conversion between unrelated
limited array types
" &
2741 "not allowed
(\A\I-00246)", A);
2743 if Is_Limited_Type (Etype (F)) then
2744 Explain_Limited_Type (Etype (F), A);
2747 if Is_Limited_Type (Etype (Expression (A))) then
2748 Explain_Limited_Type (Etype (Expression (A)), A);
2752 -- (Ada 2005: AI-251): If the actual is an allocator whose
2753 -- directly designated type is a class-wide interface, we build
2754 -- an anonymous access type to use it as the type of the
2755 -- allocator. Later, when the subprogram call is expanded, if
2756 -- the interface has a secondary dispatch table the expander
2757 -- will add a type conversion to force the correct displacement
2760 if Nkind (A) = N_Allocator then
2762 DDT : constant Entity_Id :=
2763 Directly_Designated_Type (Base_Type (Etype (F)));
2764 New_Itype : Entity_Id;
2766 if Is_Class_Wide_Type (DDT)
2767 and then Is_Interface (DDT)
2769 New_Itype := Create_Itype (E_Anonymous_Access_Type, A);
2770 Set_Etype (New_Itype, Etype (A));
2771 Init_Size_Align (New_Itype);
2772 Set_Directly_Designated_Type (New_Itype,
2773 Directly_Designated_Type (Etype (A)));
2774 Set_Etype (A, New_Itype);
2779 Resolve (A, Etype (F));
2785 -- Perform error checks for IN and IN OUT parameters
2787 if Ekind (F) /= E_Out_Parameter then
2789 -- Check unset reference. For scalar parameters, it is clearly
2790 -- wrong to pass an uninitialized value as either an IN or
2791 -- IN-OUT parameter. For composites, it is also clearly an
2792 -- error to pass a completely uninitialized value as an IN
2793 -- parameter, but the case of IN OUT is trickier. We prefer
2794 -- not to give a warning here. For example, suppose there is
2795 -- a routine that sets some component of a record to False.
2796 -- It is perfectly reasonable to make this IN-OUT and allow
2797 -- either initialized or uninitialized records to be passed
2800 -- For partially initialized composite values, we also avoid
2801 -- warnings, since it is quite likely that we are passing a
2802 -- partially initialized value and only the initialized fields
2803 -- will in fact be read in the subprogram.
2805 if Is_Scalar_Type (A_Typ)
2806 or else (Ekind (F) = E_In_Parameter
2807 and then not Is_Partially_Initialized_Type (A_Typ))
2809 Check_Unset_Reference (A);
2812 -- In Ada 83 we cannot pass an OUT parameter as an IN or IN OUT
2813 -- actual to a nested call, since this is case of reading an
2814 -- out parameter, which is not allowed.
2816 if Ada_Version = Ada_83
2817 and then Is_Entity_Name (A)
2818 and then Ekind (Entity (A)) = E_Out_Parameter
2820 Error_Msg_N ("(Ada
83) illegal reading
of out parameter
", A);
2824 if Ekind (F) /= E_In_Parameter
2825 and then not Is_OK_Variable_For_Out_Formal (A)
2827 Error_Msg_NE ("actual
for& must be a variable
", A, F);
2829 if Is_Entity_Name (A) then
2830 Kill_Checks (Entity (A));
2836 if Etype (A) = Any_Type then
2837 Set_Etype (N, Any_Type);
2841 -- Apply appropriate range checks for in, out, and in-out
2842 -- parameters. Out and in-out parameters also need a separate
2843 -- check, if there is a type conversion, to make sure the return
2844 -- value meets the constraints of the variable before the
2847 -- Gigi looks at the check flag and uses the appropriate types.
2848 -- For now since one flag is used there is an optimization which
2849 -- might not be done in the In Out case since Gigi does not do
2850 -- any analysis. More thought required about this ???
2852 if Ekind (F) = E_In_Parameter
2853 or else Ekind (F) = E_In_Out_Parameter
2855 if Is_Scalar_Type (Etype (A)) then
2856 Apply_Scalar_Range_Check (A, F_Typ);
2858 elsif Is_Array_Type (Etype (A)) then
2859 Apply_Length_Check (A, F_Typ);
2861 elsif Is_Record_Type (F_Typ)
2862 and then Has_Discriminants (F_Typ)
2863 and then Is_Constrained (F_Typ)
2864 and then (not Is_Derived_Type (F_Typ)
2865 or else Comes_From_Source (Nam))
2867 Apply_Discriminant_Check (A, F_Typ);
2869 elsif Is_Access_Type (F_Typ)
2870 and then Is_Array_Type (Designated_Type (F_Typ))
2871 and then Is_Constrained (Designated_Type (F_Typ))
2873 Apply_Length_Check (A, F_Typ);
2875 elsif Is_Access_Type (F_Typ)
2876 and then Has_Discriminants (Designated_Type (F_Typ))
2877 and then Is_Constrained (Designated_Type (F_Typ))
2879 Apply_Discriminant_Check (A, F_Typ);
2882 Apply_Range_Check (A, F_Typ);
2885 -- Ada 2005 (AI-231)
2887 if Ada_Version >= Ada_05
2888 and then Is_Access_Type (F_Typ)
2889 and then Can_Never_Be_Null (F_Typ)
2890 and then Nkind (A) = N_Null
2892 Apply_Compile_Time_Constraint_Error
2894 Msg => "(Ada
2005) NULL not allowed
in "
2895 & "null-excluding formal?
",
2896 Reason => CE_Null_Not_Allowed);
2900 if Ekind (F) = E_Out_Parameter
2901 or else Ekind (F) = E_In_Out_Parameter
2903 if Nkind (A) = N_Type_Conversion then
2904 if Is_Scalar_Type (A_Typ) then
2905 Apply_Scalar_Range_Check
2906 (Expression (A), Etype (Expression (A)), A_Typ);
2909 (Expression (A), Etype (Expression (A)), A_Typ);
2913 if Is_Scalar_Type (F_Typ) then
2914 Apply_Scalar_Range_Check (A, A_Typ, F_Typ);
2916 elsif Is_Array_Type (F_Typ)
2917 and then Ekind (F) = E_Out_Parameter
2919 Apply_Length_Check (A, F_Typ);
2922 Apply_Range_Check (A, A_Typ, F_Typ);
2927 -- An actual associated with an access parameter is implicitly
2928 -- converted to the anonymous access type of the formal and
2929 -- must satisfy the legality checks for access conversions.
2931 if Ekind (F_Typ) = E_Anonymous_Access_Type then
2932 if not Valid_Conversion (A, F_Typ, A) then
2934 ("invalid implicit conversion
for access parameter
", A);
2938 -- Check bad case of atomic/volatile argument (RM C.6(12))
2940 if Is_By_Reference_Type (Etype (F))
2941 and then Comes_From_Source (N)
2943 if Is_Atomic_Object (A)
2944 and then not Is_Atomic (Etype (F))
2947 ("cannot pass atomic argument to non
-atomic formal
",
2950 elsif Is_Volatile_Object (A)
2951 and then not Is_Volatile (Etype (F))
2954 ("cannot pass volatile argument to non
-volatile formal
",
2959 -- Check that subprograms don't have improper controlling
2960 -- arguments (RM 3.9.2 (9))
2962 if Is_Controlling_Formal (F) then
2963 Set_Is_Controlling_Actual (A);
2964 elsif Nkind (A) = N_Explicit_Dereference then
2965 Validate_Remote_Access_To_Class_Wide_Type (A);
2968 if (Is_Class_Wide_Type (A_Typ) or else Is_Dynamically_Tagged (A))
2969 and then not Is_Class_Wide_Type (F_Typ)
2970 and then not Is_Controlling_Formal (F)
2972 Error_Msg_N ("class
-wide argument
not allowed here
!", A);
2974 if Is_Subprogram (Nam)
2975 and then Comes_From_Source (Nam)
2977 Error_Msg_Node_2 := F_Typ;
2979 ("& is not a dispatching operation
of &!", A, Nam);
2982 elsif Is_Access_Type (A_Typ)
2983 and then Is_Access_Type (F_Typ)
2984 and then Ekind (F_Typ) /= E_Access_Subprogram_Type
2985 and then (Is_Class_Wide_Type (Designated_Type (A_Typ))
2986 or else (Nkind (A) = N_Attribute_Reference
2988 Is_Class_Wide_Type (Etype (Prefix (A)))))
2989 and then not Is_Class_Wide_Type (Designated_Type (F_Typ))
2990 and then not Is_Controlling_Formal (F)
2993 ("access to class
-wide argument
not allowed here
!", A);
2995 if Is_Subprogram (Nam)
2996 and then Comes_From_Source (Nam)
2998 Error_Msg_Node_2 := Designated_Type (F_Typ);
3000 ("& is not a dispatching operation
of &!", A, Nam);
3006 -- If it is a named association, treat the selector_name as
3007 -- a proper identifier, and mark the corresponding entity.
3009 if Nkind (Parent (A)) = N_Parameter_Association then
3010 Set_Entity (Selector_Name (Parent (A)), F);
3011 Generate_Reference (F, Selector_Name (Parent (A)));
3012 Set_Etype (Selector_Name (Parent (A)), F_Typ);
3013 Generate_Reference (F_Typ, N, ' ');
3018 if Ekind (F) /= E_Out_Parameter then
3019 Check_Unset_Reference (A);
3024 -- Case where actual is not present
3032 end Resolve_Actuals;
3034 -----------------------
3035 -- Resolve_Allocator --
3036 -----------------------
3038 procedure Resolve_Allocator (N : Node_Id; Typ : Entity_Id) is
3039 E : constant Node_Id := Expression (N);
3041 Discrim : Entity_Id;
3045 function In_Dispatching_Context return Boolean;
3046 -- If the allocator is an actual in a call, it is allowed to be
3047 -- class-wide when the context is not because it is a controlling
3050 ----------------------------
3051 -- In_Dispatching_Context --
3052 ----------------------------
3054 function In_Dispatching_Context return Boolean is
3055 Par : constant Node_Id := Parent (N);
3058 return (Nkind (Par) = N_Function_Call
3059 or else Nkind (Par) = N_Procedure_Call_Statement)
3060 and then Is_Entity_Name (Name (Par))
3061 and then Is_Dispatching_Operation (Entity (Name (Par)));
3062 end In_Dispatching_Context;
3064 -- Start of processing for Resolve_Allocator
3067 -- Replace general access with specific type
3069 if Ekind (Etype (N)) = E_Allocator_Type then
3070 Set_Etype (N, Base_Type (Typ));
3073 if Is_Abstract (Typ) then
3074 Error_Msg_N ("type of allocator cannot be
abstract", N);
3077 -- For qualified expression, resolve the expression using the
3078 -- given subtype (nothing to do for type mark, subtype indication)
3080 if Nkind (E) = N_Qualified_Expression then
3081 if Is_Class_Wide_Type (Etype (E))
3082 and then not Is_Class_Wide_Type (Designated_Type (Typ))
3083 and then not In_Dispatching_Context
3086 ("class
-wide allocator
not allowed
for this
access type", N);
3089 Resolve (Expression (E), Etype (E));
3090 Check_Unset_Reference (Expression (E));
3092 -- A qualified expression requires an exact match of the type,
3093 -- class-wide matching is not allowed.
3095 if (Is_Class_Wide_Type (Etype (Expression (E)))
3096 or else Is_Class_Wide_Type (Etype (E)))
3097 and then Base_Type (Etype (Expression (E))) /= Base_Type (Etype (E))
3099 Wrong_Type (Expression (E), Etype (E));
3102 -- For a subtype mark or subtype indication, freeze the subtype
3105 Freeze_Expression (E);
3107 if Is_Access_Constant (Typ) and then not No_Initialization (N) then
3109 ("initialization required
for access-to
-constant allocator
", N);
3112 -- A special accessibility check is needed for allocators that
3113 -- constrain access discriminants. The level of the type of the
3114 -- expression used to contrain an access discriminant cannot be
3115 -- deeper than the type of the allocator (in constrast to access
3116 -- parameters, where the level of the actual can be arbitrary).
3117 -- We can't use Valid_Conversion to perform this check because
3118 -- in general the type of the allocator is unrelated to the type
3119 -- of the access discriminant. Note that specialized checks are
3120 -- needed for the cases of a constraint expression which is an
3121 -- access attribute or an access discriminant.
3123 if Nkind (Original_Node (E)) = N_Subtype_Indication
3124 and then Ekind (Typ) /= E_Anonymous_Access_Type
3126 Subtyp := Entity (Subtype_Mark (Original_Node (E)));
3128 if Has_Discriminants (Subtyp) then
3129 Discrim := First_Discriminant (Base_Type (Subtyp));
3130 Constr := First (Constraints (Constraint (Original_Node (E))));
3131 while Present (Discrim) and then Present (Constr) loop
3132 if Ekind (Etype (Discrim)) = E_Anonymous_Access_Type then
3133 if Nkind (Constr) = N_Discriminant_Association then
3134 Disc_Exp := Original_Node (Expression (Constr));
3136 Disc_Exp := Original_Node (Constr);
3139 if Type_Access_Level (Etype (Disc_Exp))
3140 > Type_Access_Level (Typ)
3143 ("operand
type has deeper level than allocator
type",
3146 elsif Nkind (Disc_Exp) = N_Attribute_Reference
3147 and then Get_Attribute_Id (Attribute_Name (Disc_Exp))
3149 and then Object_Access_Level (Prefix (Disc_Exp))
3150 > Type_Access_Level (Typ)
3153 ("prefix
of attribute has deeper level than
"
3154 & " allocator
type", Disc_Exp);
3156 -- When the operand is an access discriminant the check
3157 -- is against the level of the prefix object.
3159 elsif Ekind (Etype (Disc_Exp)) = E_Anonymous_Access_Type
3160 and then Nkind (Disc_Exp) = N_Selected_Component
3161 and then Object_Access_Level (Prefix (Disc_Exp))
3162 > Type_Access_Level (Typ)
3165 ("access discriminant has deeper level than
"
3166 & " allocator
type", Disc_Exp);
3169 Next_Discriminant (Discrim);
3176 -- Ada 2005 (AI-344): A class-wide allocator requires an accessibility
3177 -- check that the level of the type of the created object is not deeper
3178 -- than the level of the allocator's access type, since extensions can
3179 -- now occur at deeper levels than their ancestor types. This is a
3180 -- static accessibility level check; a run-time check is also needed in
3181 -- the case of an initialized allocator with a class-wide argument (see
3182 -- Expand_Allocator_Expression).
3184 if Ada_Version >= Ada_05
3185 and then Is_Class_Wide_Type (Designated_Type (Typ))
3188 Exp_Typ : Entity_Id;
3191 if Nkind (E) = N_Qualified_Expression then
3192 Exp_Typ := Etype (E);
3193 elsif Nkind (E) = N_Subtype_Indication then
3194 Exp_Typ := Entity (Subtype_Mark (Original_Node (E)));
3196 Exp_Typ := Entity (E);
3199 if Type_Access_Level (Exp_Typ) > Type_Access_Level (Typ) then
3200 if In_Instance_Body then
3201 Error_Msg_N ("?
type in allocator has deeper level than
" &
3202 " designated class
-wide
type", E);
3203 Error_Msg_N ("\?Program_Error will be raised
at run time
",
3206 Make_Raise_Program_Error (Sloc (N),
3207 Reason => PE_Accessibility_Check_Failed));
3210 -- Do not apply Ada 2005 accessibility checks on a class-wide
3211 -- allocator if the type given in the allocator is a formal
3212 -- type. A run-time check will be performed in the instance.
3214 elsif not Is_Generic_Type (Exp_Typ) then
3215 Error_Msg_N ("type in allocator has deeper level than
" &
3216 " designated class
-wide
type", E);
3222 -- Check for allocation from an empty storage pool
3224 if No_Pool_Assigned (Typ) then
3226 Loc : constant Source_Ptr := Sloc (N);
3228 Error_Msg_N ("?allocation from empty storage pool
", N);
3229 Error_Msg_N ("\?Storage_Error will be raised
at run time
", N);
3231 Make_Raise_Storage_Error (Loc,
3232 Reason => SE_Empty_Storage_Pool));
3235 -- If the context is an unchecked conversion, as may happen within
3236 -- an inlined subprogram, the allocator is being resolved with its
3237 -- own anonymous type. In that case, if the target type has a specific
3238 -- storage pool, it must be inherited explicitly by the allocator type.
3240 elsif Nkind (Parent (N)) = N_Unchecked_Type_Conversion
3241 and then No (Associated_Storage_Pool (Typ))
3243 Set_Associated_Storage_Pool
3244 (Typ, Associated_Storage_Pool (Etype (Parent (N))));
3246 end Resolve_Allocator;
3248 ---------------------------
3249 -- Resolve_Arithmetic_Op --
3250 ---------------------------
3252 -- Used for resolving all arithmetic operators except exponentiation
3254 procedure Resolve_Arithmetic_Op (N : Node_Id; Typ : Entity_Id) is
3255 L : constant Node_Id := Left_Opnd (N);
3256 R : constant Node_Id := Right_Opnd (N);
3257 TL : constant Entity_Id := Base_Type (Etype (L));
3258 TR : constant Entity_Id := Base_Type (Etype (R));
3262 B_Typ : constant Entity_Id := Base_Type (Typ);
3263 -- We do the resolution using the base type, because intermediate values
3264 -- in expressions always are of the base type, not a subtype of it.
3266 function Expected_Type_Is_Any_Real (N : Node_Id) return Boolean;
3267 -- Returns True if N is in a context that expects "any real
type"
3269 function Is_Integer_Or_Universal (N : Node_Id) return Boolean;
3270 -- Return True iff given type is Integer or universal real/integer
3272 procedure Set_Mixed_Mode_Operand (N : Node_Id; T : Entity_Id);
3273 -- Choose type of integer literal in fixed-point operation to conform
3274 -- to available fixed-point type. T is the type of the other operand,
3275 -- which is needed to determine the expected type of N.
3277 procedure Set_Operand_Type (N : Node_Id);
3278 -- Set operand type to T if universal
3280 -------------------------------
3281 -- Expected_Type_Is_Any_Real --
3282 -------------------------------
3284 function Expected_Type_Is_Any_Real (N : Node_Id) return Boolean is
3286 -- N is the expression after "delta" in a fixed_point_definition;
3289 return Nkind (Parent (N)) = N_Ordinary_Fixed_Point_Definition
3290 or else Nkind (Parent (N)) = N_Decimal_Fixed_Point_Definition
3292 -- N is one of the bounds in a real_range_specification;
3295 or else Nkind (Parent (N)) = N_Real_Range_Specification
3297 -- N is the expression of a delta_constraint;
3300 or else Nkind (Parent (N)) = N_Delta_Constraint;
3301 end Expected_Type_Is_Any_Real;
3303 -----------------------------
3304 -- Is_Integer_Or_Universal --
3305 -----------------------------
3307 function Is_Integer_Or_Universal (N : Node_Id) return Boolean is
3309 Index : Interp_Index;
3313 if not Is_Overloaded (N) then
3315 return Base_Type (T) = Base_Type (Standard_Integer)
3316 or else T = Universal_Integer
3317 or else T = Universal_Real;
3319 Get_First_Interp (N, Index, It);
3320 while Present (It.Typ) loop
3321 if Base_Type (It.Typ) = Base_Type (Standard_Integer)
3322 or else It.Typ = Universal_Integer
3323 or else It.Typ = Universal_Real
3328 Get_Next_Interp (Index, It);
3333 end Is_Integer_Or_Universal;
3335 ----------------------------
3336 -- Set_Mixed_Mode_Operand --
3337 ----------------------------
3339 procedure Set_Mixed_Mode_Operand (N : Node_Id; T : Entity_Id) is
3340 Index : Interp_Index;
3344 if Universal_Interpretation (N) = Universal_Integer then
3346 -- A universal integer literal is resolved as standard integer
3347 -- except in the case of a fixed-point result, where we leave it
3348 -- as universal (to be handled by Exp_Fixd later on)
3350 if Is_Fixed_Point_Type (T) then
3351 Resolve (N, Universal_Integer);
3353 Resolve (N, Standard_Integer);
3356 elsif Universal_Interpretation (N) = Universal_Real
3357 and then (T = Base_Type (Standard_Integer)
3358 or else T = Universal_Integer
3359 or else T = Universal_Real)
3361 -- A universal real can appear in a fixed-type context. We resolve
3362 -- the literal with that context, even though this might raise an
3363 -- exception prematurely (the other operand may be zero).
3367 elsif Etype (N) = Base_Type (Standard_Integer)
3368 and then T = Universal_Real
3369 and then Is_Overloaded (N)
3371 -- Integer arg in mixed-mode operation. Resolve with universal
3372 -- type, in case preference rule must be applied.
3374 Resolve (N, Universal_Integer);
3377 and then B_Typ /= Universal_Fixed
3379 -- Not a mixed-mode operation, resolve with context
3383 elsif Etype (N) = Any_Fixed then
3385 -- N may itself be a mixed-mode operation, so use context type
3389 elsif Is_Fixed_Point_Type (T)
3390 and then B_Typ = Universal_Fixed
3391 and then Is_Overloaded (N)
3393 -- Must be (fixed * fixed) operation, operand must have one
3394 -- compatible interpretation.
3396 Resolve (N, Any_Fixed);
3398 elsif Is_Fixed_Point_Type (B_Typ)
3399 and then (T = Universal_Real
3400 or else Is_Fixed_Point_Type (T))
3401 and then Is_Overloaded (N)
3403 -- C * F(X) in a fixed context, where C is a real literal or a
3404 -- fixed-point expression. F must have either a fixed type
3405 -- interpretation or an integer interpretation, but not both.
3407 Get_First_Interp (N, Index, It);
3408 while Present (It.Typ) loop
3409 if Base_Type (It.Typ) = Base_Type (Standard_Integer) then
3411 if Analyzed (N) then
3412 Error_Msg_N ("ambiguous operand
in fixed operation
", N);
3414 Resolve (N, Standard_Integer);
3417 elsif Is_Fixed_Point_Type (It.Typ) then
3419 if Analyzed (N) then
3420 Error_Msg_N ("ambiguous operand
in fixed operation
", N);
3422 Resolve (N, It.Typ);
3426 Get_Next_Interp (Index, It);
3429 -- Reanalyze the literal with the fixed type of the context. If
3430 -- context is Universal_Fixed, we are within a conversion, leave
3431 -- the literal as a universal real because there is no usable
3432 -- fixed type, and the target of the conversion plays no role in
3446 if B_Typ = Universal_Fixed
3447 and then Nkind (Op2) = N_Real_Literal
3449 T2 := Universal_Real;
3454 Set_Analyzed (Op2, False);
3461 end Set_Mixed_Mode_Operand;
3463 ----------------------
3464 -- Set_Operand_Type --
3465 ----------------------
3467 procedure Set_Operand_Type (N : Node_Id) is
3469 if Etype (N) = Universal_Integer
3470 or else Etype (N) = Universal_Real
3474 end Set_Operand_Type;
3476 -- Start of processing for Resolve_Arithmetic_Op
3479 if Comes_From_Source (N)
3480 and then Ekind (Entity (N)) = E_Function
3481 and then Is_Imported (Entity (N))
3482 and then Is_Intrinsic_Subprogram (Entity (N))
3484 Resolve_Intrinsic_Operator (N, Typ);
3487 -- Special-case for mixed-mode universal expressions or fixed point
3488 -- type operation: each argument is resolved separately. The same
3489 -- treatment is required if one of the operands of a fixed point
3490 -- operation is universal real, since in this case we don't do a
3491 -- conversion to a specific fixed-point type (instead the expander
3492 -- takes care of the case).
3494 elsif (B_Typ = Universal_Integer
3495 or else B_Typ = Universal_Real)
3496 and then Present (Universal_Interpretation (L))
3497 and then Present (Universal_Interpretation (R))
3499 Resolve (L, Universal_Interpretation (L));
3500 Resolve (R, Universal_Interpretation (R));
3501 Set_Etype (N, B_Typ);
3503 elsif (B_Typ = Universal_Real
3504 or else Etype (N) = Universal_Fixed
3505 or else (Etype (N) = Any_Fixed
3506 and then Is_Fixed_Point_Type (B_Typ))
3507 or else (Is_Fixed_Point_Type (B_Typ)
3508 and then (Is_Integer_Or_Universal (L)
3510 Is_Integer_Or_Universal (R))))
3511 and then (Nkind (N) = N_Op_Multiply or else
3512 Nkind (N) = N_Op_Divide)
3514 if TL = Universal_Integer or else TR = Universal_Integer then
3515 Check_For_Visible_Operator (N, B_Typ);
3518 -- If context is a fixed type and one operand is integer, the
3519 -- other is resolved with the type of the context.
3521 if Is_Fixed_Point_Type (B_Typ)
3522 and then (Base_Type (TL) = Base_Type (Standard_Integer)
3523 or else TL = Universal_Integer)
3528 elsif Is_Fixed_Point_Type (B_Typ)
3529 and then (Base_Type (TR) = Base_Type (Standard_Integer)
3530 or else TR = Universal_Integer)
3536 Set_Mixed_Mode_Operand (L, TR);
3537 Set_Mixed_Mode_Operand (R, TL);
3540 -- Check the rule in RM05-4.5.5(19.1/2) disallowing the
3541 -- universal_fixed multiplying operators from being used when the
3542 -- expected type is also universal_fixed. Note that B_Typ will be
3543 -- Universal_Fixed in some cases where the expected type is actually
3544 -- Any_Real; Expected_Type_Is_Any_Real takes care of that case.
3546 if Etype (N) = Universal_Fixed
3547 or else Etype (N) = Any_Fixed
3549 if B_Typ = Universal_Fixed
3550 and then not Expected_Type_Is_Any_Real (N)
3551 and then Nkind (Parent (N)) /= N_Type_Conversion
3552 and then Nkind (Parent (N)) /= N_Unchecked_Type_Conversion
3555 ("type cannot be determined from context
!", N);
3557 ("\explicit conversion to result
type required
", N);
3559 Set_Etype (L, Any_Type);
3560 Set_Etype (R, Any_Type);
3563 if Ada_Version = Ada_83
3564 and then Etype (N) = Universal_Fixed
3565 and then Nkind (Parent (N)) /= N_Type_Conversion
3566 and then Nkind (Parent (N)) /= N_Unchecked_Type_Conversion
3569 ("(Ada
83) fixed
-point operation
" &
3570 "needs explicit conversion
",
3574 -- The expected type is "any real
type" in contexts like
3575 -- type T is delta <universal_fixed-expression> ...
3576 -- in which case we need to set the type to Universal_Real
3577 -- so that static expression evaluation will work properly.
3579 if Expected_Type_Is_Any_Real (N) then
3580 Set_Etype (N, Universal_Real);
3582 Set_Etype (N, B_Typ);
3586 elsif Is_Fixed_Point_Type (B_Typ)
3587 and then (Is_Integer_Or_Universal (L)
3588 or else Nkind (L) = N_Real_Literal
3589 or else Nkind (R) = N_Real_Literal
3591 Is_Integer_Or_Universal (R))
3593 Set_Etype (N, B_Typ);
3595 elsif Etype (N) = Any_Fixed then
3597 -- If no previous errors, this is only possible if one operand
3598 -- is overloaded and the context is universal. Resolve as such.
3600 Set_Etype (N, B_Typ);
3604 if (TL = Universal_Integer or else TL = Universal_Real)
3605 and then (TR = Universal_Integer or else TR = Universal_Real)
3607 Check_For_Visible_Operator (N, B_Typ);
3610 -- If the context is Universal_Fixed and the operands are also
3611 -- universal fixed, this is an error, unless there is only one
3612 -- applicable fixed_point type (usually duration).
3614 if B_Typ = Universal_Fixed
3615 and then Etype (L) = Universal_Fixed
3617 T := Unique_Fixed_Point_Type (N);
3619 if T = Any_Type then
3632 -- If one of the arguments was resolved to a non-universal type.
3633 -- label the result of the operation itself with the same type.
3634 -- Do the same for the universal argument, if any.
3636 T := Intersect_Types (L, R);
3637 Set_Etype (N, Base_Type (T));
3638 Set_Operand_Type (L);
3639 Set_Operand_Type (R);
3642 Generate_Operator_Reference (N, Typ);
3643 Eval_Arithmetic_Op (N);
3645 -- Set overflow and division checking bit. Much cleverer code needed
3646 -- here eventually and perhaps the Resolve routines should be separated
3647 -- for the various arithmetic operations, since they will need
3648 -- different processing. ???
3650 if Nkind (N) in N_Op then
3651 if not Overflow_Checks_Suppressed (Etype (N)) then
3652 Enable_Overflow_Check (N);
3655 -- Give warning if explicit division by zero
3657 if (Nkind (N) = N_Op_Divide
3658 or else Nkind (N) = N_Op_Rem
3659 or else Nkind (N) = N_Op_Mod)
3660 and then not Division_Checks_Suppressed (Etype (N))
3662 Rop := Right_Opnd (N);
3664 if Compile_Time_Known_Value (Rop)
3665 and then ((Is_Integer_Type (Etype (Rop))
3666 and then Expr_Value (Rop) = Uint_0)
3668 (Is_Real_Type (Etype (Rop))
3669 and then Expr_Value_R (Rop) = Ureal_0))
3671 -- Specialize the warning message according to the operation
3675 Apply_Compile_Time_Constraint_Error
3676 (N, "division by zero?
", CE_Divide_By_Zero,
3677 Loc => Sloc (Right_Opnd (N)));
3680 Apply_Compile_Time_Constraint_Error
3681 (N, "rem with zero divisor?
", CE_Divide_By_Zero,
3682 Loc => Sloc (Right_Opnd (N)));
3685 Apply_Compile_Time_Constraint_Error
3686 (N, "mod with zero divisor?
", CE_Divide_By_Zero,
3687 Loc => Sloc (Right_Opnd (N)));
3689 -- Division by zero can only happen with division, rem,
3690 -- and mod operations.
3693 raise Program_Error;
3696 -- Otherwise just set the flag to check at run time
3699 Set_Do_Division_Check (N);
3704 Check_Unset_Reference (L);
3705 Check_Unset_Reference (R);
3706 end Resolve_Arithmetic_Op;
3712 procedure Resolve_Call (N : Node_Id; Typ : Entity_Id) is
3713 Loc : constant Source_Ptr := Sloc (N);
3714 Subp : constant Node_Id := Name (N);
3723 -- The context imposes a unique interpretation with type Typ on a
3724 -- procedure or function call. Find the entity of the subprogram that
3725 -- yields the expected type, and propagate the corresponding formal
3726 -- constraints on the actuals. The caller has established that an
3727 -- interpretation exists, and emitted an error if not unique.
3729 -- First deal with the case of a call to an access-to-subprogram,
3730 -- dereference made explicit in Analyze_Call.
3732 if Ekind (Etype (Subp)) = E_Subprogram_Type then
3733 if not Is_Overloaded (Subp) then
3734 Nam := Etype (Subp);
3737 -- Find the interpretation whose type (a subprogram type) has a
3738 -- return type that is compatible with the context. Analysis of
3739 -- the node has established that one exists.
3743 Get_First_Interp (Subp, I, It);
3744 while Present (It.Typ) loop
3745 if Covers (Typ, Etype (It.Typ)) then
3750 Get_Next_Interp (I, It);
3754 raise Program_Error;
3758 -- If the prefix is not an entity, then resolve it
3760 if not Is_Entity_Name (Subp) then
3761 Resolve (Subp, Nam);
3764 -- For an indirect call, we always invalidate checks, since we do not
3765 -- know whether the subprogram is local or global. Yes we could do
3766 -- better here, e.g. by knowing that there are no local subprograms,
3767 -- but it does not seem worth the effort. Similarly, we kill all
3768 -- knowledge of current constant values.
3770 Kill_Current_Values;
3772 -- If this is a procedure call which is really an entry call, do the
3773 -- conversion of the procedure call to an entry call. Protected
3774 -- operations use the same circuitry because the name in the call can be
3775 -- an arbitrary expression with special resolution rules.
3777 elsif Nkind (Subp) = N_Selected_Component
3778 or else Nkind (Subp) = N_Indexed_Component
3779 or else (Is_Entity_Name (Subp)
3780 and then Ekind (Entity (Subp)) = E_Entry)
3782 Resolve_Entry_Call (N, Typ);
3783 Check_Elab_Call (N);
3785 -- Kill checks and constant values, as above for indirect case
3786 -- Who knows what happens when another task is activated?
3788 Kill_Current_Values;
3791 -- Normal subprogram call with name established in Resolve
3793 elsif not (Is_Type (Entity (Subp))) then
3794 Nam := Entity (Subp);
3795 Set_Entity_With_Style_Check (Subp, Nam);
3796 Generate_Reference (Nam, Subp);
3798 -- Otherwise we must have the case of an overloaded call
3801 pragma Assert (Is_Overloaded (Subp));
3802 Nam := Empty; -- We know that it will be assigned in loop below
3804 Get_First_Interp (Subp, I, It);
3805 while Present (It.Typ) loop
3806 if Covers (Typ, It.Typ) then
3808 Set_Entity_With_Style_Check (Subp, Nam);
3809 Generate_Reference (Nam, Subp);
3813 Get_Next_Interp (I, It);
3817 -- Check that a call to Current_Task does not occur in an entry body
3819 if Is_RTE (Nam, RE_Current_Task) then
3829 if Nkind (P) = N_Entry_Body
3830 or else (Nkind (P) = N_Subprogram_Body
3831 and then Is_Entry_Barrier_Function (P))
3835 ("& should
not be used
in entry body ('R'M C.7(17))?",
3838 ("\Program_Error will be raised at run time?", N, Nam);
3840 Make_Raise_Program_Error (Loc,
3841 Reason => PE_Current_Task_In_Entry_Body));
3842 Set_Etype (N, Rtype);
3849 -- Cannot call thread body directly
3851 if Is_Thread_Body (Nam) then
3852 Error_Msg_N ("cannot call thread body directly", N);
3855 -- Check that a procedure call does not occur in the context of the
3856 -- entry call statement of a conditional or timed entry call. Note that
3857 -- the case of a call to a subprogram renaming of an entry will also be
3858 -- rejected. The test for N not being an N_Entry_Call_Statement is
3859 -- defensive, covering the possibility that the processing of entry
3860 -- calls might reach this point due to later modifications of the code
3863 if Nkind (Parent (N)) = N_Entry_Call_Alternative
3864 and then Nkind (N) /= N_Entry_Call_Statement
3865 and then Entry_Call_Statement (Parent (N)) = N
3867 if Ada_Version < Ada_05 then
3868 Error_Msg_N ("entry call required in select statement", N);
3870 -- Ada 2005 (AI-345): If a procedure_call_statement is used
3871 -- for a procedure_or_entry_call, the procedure_name or pro-
3872 -- cedure_prefix of the procedure_call_statement shall denote
3873 -- an entry renamed by a procedure, or (a view of) a primitive
3874 -- subprogram of a limited interface whose first parameter is
3875 -- a controlling parameter.
3877 elsif Nkind (N) = N_Procedure_Call_Statement
3878 and then not Is_Renamed_Entry (Nam)
3879 and then not Is_Controlling_Limited_Procedure (Nam)
3882 ("entry call or dispatching primitive of interface required", N);
3886 -- Check that this is not a call to a protected procedure or
3887 -- entry from within a protected function.
3889 if Ekind (Current_Scope) = E_Function
3890 and then Ekind (Scope (Current_Scope)) = E_Protected_Type
3891 and then Ekind (Nam) /= E_Function
3892 and then Scope (Nam) = Scope (Current_Scope)
3894 Error_Msg_N ("within protected function, protected " &
3895 "object is constant", N);
3896 Error_Msg_N ("\cannot call operation that may modify it", N);
3899 -- Freeze the subprogram name if not in default expression. Note that we
3900 -- freeze procedure calls as well as function calls. Procedure calls are
3901 -- not frozen according to the rules (RM 13.14(14)) because it is
3902 -- impossible to have a procedure call to a non-frozen procedure in pure
3903 -- Ada, but in the code that we generate in the expander, this rule
3904 -- needs extending because we can generate procedure calls that need
3907 if Is_Entity_Name (Subp) and then not In_Default_Expression then
3908 Freeze_Expression (Subp);
3911 -- For a predefined operator, the type of the result is the type imposed
3912 -- by context, except for a predefined operation on universal fixed.
3913 -- Otherwise The type of the call is the type returned by the subprogram
3916 if Is_Predefined_Op (Nam) then
3917 if Etype (N) /= Universal_Fixed then
3921 -- If the subprogram returns an array type, and the context requires the
3922 -- component type of that array type, the node is really an indexing of
3923 -- the parameterless call. Resolve as such. A pathological case occurs
3924 -- when the type of the component is an access to the array type. In
3925 -- this case the call is truly ambiguous.
3927 elsif Needs_No_Actuals (Nam)
3929 ((Is_Array_Type (Etype (Nam))
3930 and then Covers (Typ, Component_Type (Etype (Nam))))
3931 or else (Is_Access_Type (Etype (Nam))
3932 and then Is_Array_Type (Designated_Type (Etype (Nam)))
3935 Component_Type (Designated_Type (Etype (Nam))))))
3938 Index_Node : Node_Id;
3940 Ret_Type : constant Entity_Id := Etype (Nam);
3943 if Is_Access_Type (Ret_Type)
3944 and then Ret_Type = Component_Type (Designated_Type (Ret_Type))
3947 ("cannot disambiguate function call and indexing", N);
3949 New_Subp := Relocate_Node (Subp);
3950 Set_Entity (Subp, Nam);
3952 if Component_Type (Ret_Type) /= Any_Type then
3954 Make_Indexed_Component (Loc,
3956 Make_Function_Call (Loc,
3958 Expressions => Parameter_Associations (N));
3960 -- Since we are correcting a node classification error made
3961 -- by the parser, we call Replace rather than Rewrite.
3963 Replace (N, Index_Node);
3964 Set_Etype (Prefix (N), Ret_Type);
3966 Resolve_Indexed_Component (N, Typ);
3967 Check_Elab_Call (Prefix (N));
3975 Set_Etype (N, Etype (Nam));
3978 -- In the case where the call is to an overloaded subprogram, Analyze
3979 -- calls Normalize_Actuals once per overloaded subprogram. Therefore in
3980 -- such a case Normalize_Actuals needs to be called once more to order
3981 -- the actuals correctly. Otherwise the call will have the ordering
3982 -- given by the last overloaded subprogram whether this is the correct
3983 -- one being called or not.
3985 if Is_Overloaded (Subp) then
3986 Normalize_Actuals (N, Nam, False, Norm_OK);
3987 pragma Assert (Norm_OK);
3990 -- In any case, call is fully resolved now. Reset Overload flag, to
3991 -- prevent subsequent overload resolution if node is analyzed again
3993 Set_Is_Overloaded (Subp, False);
3994 Set_Is_Overloaded (N, False);
3996 -- If we are calling the current subprogram from immediately within its
3997 -- body, then that is the case where we can sometimes detect cases of
3998 -- infinite recursion statically. Do not try this in case restriction
3999 -- No_Recursion is in effect anyway.
4001 Scop := Current_Scope;
4004 and then not Restriction_Active (No_Recursion)
4005 and then Check_Infinite_Recursion (N)
4007 -- Here we detected and flagged an infinite recursion, so we do
4008 -- not need to test the case below for further warnings.
4012 -- If call is to immediately containing subprogram, then check for
4013 -- the case of a possible run-time detectable infinite recursion.
4016 Scope_Loop : while Scop /= Standard_Standard loop
4019 -- Although in general recursion is not statically checkable,
4020 -- the case of calling an immediately containing subprogram
4021 -- is easy to catch.
4023 Check_Restriction (No_Recursion, N);
4025 -- If the recursive call is to a parameterless subprogram, then
4026 -- even if we can't statically detect infinite recursion, this
4027 -- is pretty suspicious, and we output a warning. Furthermore,
4028 -- we will try later to detect some cases here at run time by
4029 -- expanding checking code (see Detect_Infinite_Recursion in
4030 -- package Exp_Ch6).
4032 -- If the recursive call is within a handler we do not emit a
4033 -- warning, because this is a common idiom: loop until input
4034 -- is correct, catch illegal input in handler and restart.
4036 if No (First_Formal (Nam))
4037 and then Etype (Nam) = Standard_Void_Type
4038 and then not Error_Posted (N)
4039 and then Nkind (Parent (N)) /= N_Exception_Handler
4041 -- For the case of a procedure call. We give the message
4042 -- only if the call is the first statement in a sequence of
4043 -- statements, or if all previous statements are simple
4044 -- assignments. This is simply a heuristic to decrease false
4045 -- positives, without losing too many good warnings. The
4046 -- idea is that these previous statements may affect global
4047 -- variables the procedure depends on.
4049 if Nkind (N) = N_Procedure_Call_Statement
4050 and then Is_List_Member (N)
4056 while Present (P) loop
4057 if Nkind (P) /= N_Assignment_Statement then
4066 -- Do not give warning if we are in a conditional context
4069 K : constant Node_Kind := Nkind (Parent (N));
4071 if (K = N_Loop_Statement
4072 and then Present (Iteration_Scheme (Parent (N))))
4073 or else K = N_If_Statement
4074 or else K = N_Elsif_Part
4075 or else K = N_Case_Statement_Alternative
4081 -- Here warning is to be issued
4083 Set_Has_Recursive_Call (Nam);
4084 Error_Msg_N ("possible infinite recursion?", N);
4085 Error_Msg_N ("\Storage_Error may be raised at run time?", N);
4091 Scop := Scope (Scop);
4092 end loop Scope_Loop;
4095 -- If subprogram name is a predefined operator, it was given in
4096 -- functional notation. Replace call node with operator node, so
4097 -- that actuals can be resolved appropriately.
4099 if Is_Predefined_Op (Nam) or else Ekind (Nam) = E_Operator then
4100 Make_Call_Into_Operator (N, Typ, Entity (Name (N)));
4103 elsif Present (Alias (Nam))
4104 and then Is_Predefined_Op (Alias (Nam))
4106 Resolve_Actuals (N, Nam);
4107 Make_Call_Into_Operator (N, Typ, Alias (Nam));
4111 -- Create a transient scope if the resulting type requires it
4113 -- There are 3 notable exceptions: in init procs, the transient scope
4114 -- overhead is not needed and even incorrect due to the actual expansion
4115 -- of adjust calls; the second case is enumeration literal pseudo calls,
4116 -- the other case is intrinsic subprograms (Unchecked_Conversion and
4117 -- source information functions) that do not use the secondary stack
4118 -- even though the return type is unconstrained.
4120 -- If this is an initialization call for a type whose initialization
4121 -- uses the secondary stack, we also need to create a transient scope
4122 -- for it, precisely because we will not do it within the init proc
4125 -- If the subprogram is marked Inlined_Always, then even if it returns
4126 -- an unconstrained type the call does not require use of the secondary
4130 and then Present (First_Rep_Item (Nam))
4131 and then Nkind (First_Rep_Item (Nam)) = N_Pragma
4132 and then Chars (First_Rep_Item (Nam)) = Name_Inline_Always
4136 elsif Expander_Active
4137 and then Is_Type (Etype (Nam))
4138 and then Requires_Transient_Scope (Etype (Nam))
4139 and then Ekind (Nam) /= E_Enumeration_Literal
4140 and then not Within_Init_Proc
4141 and then not Is_Intrinsic_Subprogram (Nam)
4143 Establish_Transient_Scope
4144 (N, Sec_Stack => not Functions_Return_By_DSP_On_Target);
4146 -- If the call appears within the bounds of a loop, it will
4147 -- be rewritten and reanalyzed, nothing left to do here.
4149 if Nkind (N) /= N_Function_Call then
4153 elsif Is_Init_Proc (Nam)
4154 and then not Within_Init_Proc
4156 Check_Initialization_Call (N, Nam);
4159 -- A protected function cannot be called within the definition of the
4160 -- enclosing protected type.
4162 if Is_Protected_Type (Scope (Nam))
4163 and then In_Open_Scopes (Scope (Nam))
4164 and then not Has_Completion (Scope (Nam))
4167 ("& cannot be called before end of protected definition", N, Nam);
4170 -- Propagate interpretation to actuals, and add default expressions
4173 if Present (First_Formal (Nam)) then
4174 Resolve_Actuals (N, Nam);
4176 -- Overloaded literals are rewritten as function calls, for
4177 -- purpose of resolution. After resolution, we can replace
4178 -- the call with the literal itself.
4180 elsif Ekind (Nam) = E_Enumeration_Literal then
4181 Copy_Node (Subp, N);
4182 Resolve_Entity_Name (N, Typ);
4184 -- Avoid validation, since it is a static function call
4189 -- If the subprogram is not global, then kill all checks. This is a bit
4190 -- conservative, since in many cases we could do better, but it is not
4191 -- worth the effort. Similarly, we kill constant values. However we do
4192 -- not need to do this for internal entities (unless they are inherited
4193 -- user-defined subprograms), since they are not in the business of
4194 -- molesting global values.
4196 -- Note: we do not do this step till after resolving the actuals. That
4197 -- way we still take advantage of the current value information while
4198 -- scanning the actuals.
4200 if not Is_Library_Level_Entity (Nam)
4201 and then (Comes_From_Source (Nam)
4202 or else (Present (Alias (Nam))
4203 and then Comes_From_Source (Alias (Nam))))
4205 Kill_Current_Values;
4208 -- If the subprogram is a primitive operation, check whether or not
4209 -- it is a correct dispatching call.
4211 if Is_Overloadable (Nam)
4212 and then Is_Dispatching_Operation (Nam)
4214 Check_Dispatching_Call (N);
4216 elsif Is_Abstract (Nam)
4217 and then not In_Instance
4219 Error_Msg_NE ("cannot call abstract subprogram &!", N, Nam);
4222 if Is_Intrinsic_Subprogram (Nam) then
4223 Check_Intrinsic_Call (N);
4227 Check_Elab_Call (N);
4230 -------------------------------
4231 -- Resolve_Character_Literal --
4232 -------------------------------
4234 procedure Resolve_Character_Literal (N : Node_Id; Typ : Entity_Id) is
4235 B_Typ : constant Entity_Id := Base_Type (Typ);
4239 -- Verify that the character does belong to the type of the context
4241 Set_Etype (N, B_Typ);
4242 Eval_Character_Literal (N);
4244 -- Wide_Wide_Character literals must always be defined, since the set
4245 -- of wide wide character literals is complete, i.e. if a character
4246 -- literal is accepted by the parser, then it is OK for wide wide
4247 -- character (out of range character literals are rejected).
4249 if Root_Type (B_Typ) = Standard_Wide_Wide_Character then
4252 -- Always accept character literal for type Any_Character, which
4253 -- occurs in error situations and in comparisons of literals, both
4254 -- of which should accept all literals.
4256 elsif B_Typ = Any_Character then
4259 -- For Standard.Character or a type derived from it, check that
4260 -- the literal is in range
4262 elsif Root_Type (B_Typ) = Standard_Character then
4263 if In_Character_Range (UI_To_CC (Char_Literal_Value (N))) then
4267 -- For Standard.Wide_Character or a type derived from it, check
4268 -- that the literal is in range
4270 elsif Root_Type (B_Typ) = Standard_Wide_Character then
4271 if In_Wide_Character_Range (UI_To_CC (Char_Literal_Value (N))) then
4275 -- For Standard.Wide_Wide_Character or a type derived from it, we
4276 -- know the literal is in range, since the parser checked!
4278 elsif Root_Type (B_Typ) = Standard_Wide_Wide_Character then
4281 -- If the entity is already set, this has already been resolved in
4282 -- a generic context, or comes from expansion. Nothing else to do.
4284 elsif Present (Entity (N)) then
4287 -- Otherwise we have a user defined character type, and we can use
4288 -- the standard visibility mechanisms to locate the referenced entity
4291 C := Current_Entity (N);
4292 while Present (C) loop
4293 if Etype (C) = B_Typ then
4294 Set_Entity_With_Style_Check (N, C);
4295 Generate_Reference (C, N);
4303 -- If we fall through, then the literal does not match any of the
4304 -- entries of the enumeration type. This isn't just a constraint
4305 -- error situation, it is an illegality (see RM 4.2).
4308 ("character not defined for }", N, First_Subtype (B_Typ));
4309 end Resolve_Character_Literal;
4311 ---------------------------
4312 -- Resolve_Comparison_Op --
4313 ---------------------------
4315 -- Context requires a boolean type, and plays no role in resolution.
4316 -- Processing identical to that for equality operators. The result
4317 -- type is the base type, which matters when pathological subtypes of
4318 -- booleans with limited ranges are used.
4320 procedure Resolve_Comparison_Op (N : Node_Id; Typ : Entity_Id) is
4321 L : constant Node_Id := Left_Opnd (N);
4322 R : constant Node_Id := Right_Opnd (N);
4326 -- If this is an intrinsic operation which is not predefined, use
4327 -- the types of its declared arguments to resolve the possibly
4328 -- overloaded operands. Otherwise the operands are unambiguous and
4329 -- specify the expected type.
4331 if Scope (Entity (N)) /= Standard_Standard then
4332 T := Etype (First_Entity (Entity (N)));
4335 T := Find_Unique_Type (L, R);
4337 if T = Any_Fixed then
4338 T := Unique_Fixed_Point_Type (L);
4342 Set_Etype (N, Base_Type (Typ));
4343 Generate_Reference (T, N, ' ');
4345 if T /= Any_Type then
4347 or else T = Any_Composite
4348 or else T = Any_Character
4350 if T = Any_Character then
4351 Ambiguous_Character (L);
4353 Error_Msg_N ("ambiguous operands for comparison", N);
4356 Set_Etype (N, Any_Type);
4362 Check_Unset_Reference (L);
4363 Check_Unset_Reference (R);
4364 Generate_Operator_Reference (N, T);
4365 Eval_Relational_Op (N);
4368 end Resolve_Comparison_Op;
4370 ------------------------------------
4371 -- Resolve_Conditional_Expression --
4372 ------------------------------------
4374 procedure Resolve_Conditional_Expression (N : Node_Id; Typ : Entity_Id) is
4375 Condition : constant Node_Id := First (Expressions (N));
4376 Then_Expr : constant Node_Id := Next (Condition);
4377 Else_Expr : constant Node_Id := Next (Then_Expr);
4380 Resolve (Condition, Standard_Boolean);
4381 Resolve (Then_Expr, Typ);
4382 Resolve (Else_Expr, Typ);
4385 Eval_Conditional_Expression (N);
4386 end Resolve_Conditional_Expression;
4388 -----------------------------------------
4389 -- Resolve_Discrete_Subtype_Indication --
4390 -----------------------------------------
4392 procedure Resolve_Discrete_Subtype_Indication
4400 Analyze (Subtype_Mark (N));
4401 S := Entity (Subtype_Mark (N));
4403 if Nkind (Constraint (N)) /= N_Range_Constraint then
4404 Error_Msg_N ("expect range constraint for discrete type", N);
4405 Set_Etype (N, Any_Type);
4408 R := Range_Expression (Constraint (N));
4416 if Base_Type (S) /= Base_Type (Typ) then
4418 ("expect subtype of }", N, First_Subtype (Typ));
4420 -- Rewrite the constraint as a range of Typ
4421 -- to allow compilation to proceed further.
4424 Rewrite (Low_Bound (R),
4425 Make_Attribute_Reference (Sloc (Low_Bound (R)),
4426 Prefix => New_Occurrence_Of (Typ, Sloc (R)),
4427 Attribute_Name => Name_First));
4428 Rewrite (High_Bound (R),
4429 Make_Attribute_Reference (Sloc (High_Bound (R)),
4430 Prefix => New_Occurrence_Of (Typ, Sloc (R)),
4431 Attribute_Name => Name_First));
4435 Set_Etype (N, Etype (R));
4437 -- Additionally, we must check that the bounds are compatible
4438 -- with the given subtype, which might be different from the
4439 -- type of the context.
4441 Apply_Range_Check (R, S);
4443 -- ??? If the above check statically detects a Constraint_Error
4444 -- it replaces the offending bound(s) of the range R with a
4445 -- Constraint_Error node. When the itype which uses these bounds
4446 -- is frozen the resulting call to Duplicate_Subexpr generates
4447 -- a new temporary for the bounds.
4449 -- Unfortunately there are other itypes that are also made depend
4450 -- on these bounds, so when Duplicate_Subexpr is called they get
4451 -- a forward reference to the newly created temporaries and Gigi
4452 -- aborts on such forward references. This is probably sign of a
4453 -- more fundamental problem somewhere else in either the order of
4454 -- itype freezing or the way certain itypes are constructed.
4456 -- To get around this problem we call Remove_Side_Effects right
4457 -- away if either bounds of R are a Constraint_Error.
4460 L : constant Node_Id := Low_Bound (R);
4461 H : constant Node_Id := High_Bound (R);
4464 if Nkind (L) = N_Raise_Constraint_Error then
4465 Remove_Side_Effects (L);
4468 if Nkind (H) = N_Raise_Constraint_Error then
4469 Remove_Side_Effects (H);
4473 Check_Unset_Reference (Low_Bound (R));
4474 Check_Unset_Reference (High_Bound (R));
4477 end Resolve_Discrete_Subtype_Indication;
4479 -------------------------
4480 -- Resolve_Entity_Name --
4481 -------------------------
4483 -- Used to resolve identifiers and expanded names
4485 procedure Resolve_Entity_Name (N : Node_Id; Typ : Entity_Id) is
4486 E : constant Entity_Id := Entity (N);
4489 -- If garbage from errors, set to Any_Type and return
4491 if No (E) and then Total_Errors_Detected /= 0 then
4492 Set_Etype (N, Any_Type);
4496 -- Replace named numbers by corresponding literals. Note that this is
4497 -- the one case where Resolve_Entity_Name must reset the Etype, since
4498 -- it is currently marked as universal.
4500 if Ekind (E) = E_Named_Integer then
4502 Eval_Named_Integer (N);
4504 elsif Ekind (E) = E_Named_Real then
4506 Eval_Named_Real (N);
4508 -- Allow use of subtype only if it is a concurrent type where we are
4509 -- currently inside the body. This will eventually be expanded
4510 -- into a call to Self (for tasks) or _object (for protected
4511 -- objects). Any other use of a subtype is invalid.
4513 elsif Is_Type (E) then
4514 if Is_Concurrent_Type (E)
4515 and then In_Open_Scopes (E)
4520 ("invalid use of subtype mark in expression or call", N);
4523 -- Check discriminant use if entity is discriminant in current scope,
4524 -- i.e. discriminant of record or concurrent type currently being
4525 -- analyzed. Uses in corresponding body are unrestricted.
4527 elsif Ekind (E) = E_Discriminant
4528 and then Scope (E) = Current_Scope
4529 and then not Has_Completion (Current_Scope)
4531 Check_Discriminant_Use (N);
4533 -- A parameterless generic function cannot appear in a context that
4534 -- requires resolution.
4536 elsif Ekind (E) = E_Generic_Function then
4537 Error_Msg_N ("illegal use of generic function", N);
4539 elsif Ekind (E) = E_Out_Parameter
4540 and then Ada_Version = Ada_83
4541 and then (Nkind (Parent (N)) in N_Op
4542 or else (Nkind (Parent (N)) = N_Assignment_Statement
4543 and then N = Expression (Parent (N)))
4544 or else Nkind (Parent (N)) = N_Explicit_Dereference)
4546 Error_Msg_N ("(Ada 83) illegal reading of out parameter", N);
4548 -- In all other cases, just do the possible static evaluation
4551 -- A deferred constant that appears in an expression must have
4552 -- a completion, unless it has been removed by in-place expansion
4555 if Ekind (E) = E_Constant
4556 and then Comes_From_Source (E)
4557 and then No (Constant_Value (E))
4558 and then Is_Frozen (Etype (E))
4559 and then not In_Default_Expression
4560 and then not Is_Imported (E)
4563 if No_Initialization (Parent (E))
4564 or else (Present (Full_View (E))
4565 and then No_Initialization (Parent (Full_View (E))))
4570 "deferred constant is frozen before completion", N);
4574 Eval_Entity_Name (N);
4576 end Resolve_Entity_Name;
4582 procedure Resolve_Entry (Entry_Name : Node_Id) is
4583 Loc : constant Source_Ptr := Sloc (Entry_Name);
4591 function Actual_Index_Type (E : Entity_Id) return Entity_Id;
4592 -- If the bounds of the entry family being called depend on task
4593 -- discriminants, build a new index subtype where a discriminant is
4594 -- replaced with the value of the discriminant of the target task.
4595 -- The target task is the prefix of the entry name in the call.
4597 -----------------------
4598 -- Actual_Index_Type --
4599 -----------------------
4601 function Actual_Index_Type (E : Entity_Id) return Entity_Id is
4602 Typ : constant Entity_Id := Entry_Index_Type (E);
4603 Tsk : constant Entity_Id := Scope (E);
4604 Lo : constant Node_Id := Type_Low_Bound (Typ);
4605 Hi : constant Node_Id := Type_High_Bound (Typ);
4608 function Actual_Discriminant_Ref (Bound : Node_Id) return Node_Id;
4609 -- If the bound is given by a discriminant, replace with a reference
4610 -- to the discriminant of the same name in the target task.
4611 -- If the entry name is the target of a requeue statement and the
4612 -- entry is in the current protected object, the bound to be used
4613 -- is the discriminal of the object (see apply_range_checks for
4614 -- details of the transformation).
4616 -----------------------------
4617 -- Actual_Discriminant_Ref --
4618 -----------------------------
4620 function Actual_Discriminant_Ref (Bound : Node_Id) return Node_Id is
4621 Typ : constant Entity_Id := Etype (Bound);
4625 Remove_Side_Effects (Bound);
4627 if not Is_Entity_Name (Bound)
4628 or else Ekind (Entity (Bound)) /= E_Discriminant
4632 elsif Is_Protected_Type (Tsk)
4633 and then In_Open_Scopes (Tsk)
4634 and then Nkind (Parent (Entry_Name)) = N_Requeue_Statement
4636 return New_Occurrence_Of (Discriminal (Entity (Bound)), Loc);
4640 Make_Selected_Component (Loc,
4641 Prefix => New_Copy_Tree (Prefix (Prefix (Entry_Name))),
4642 Selector_Name => New_Occurrence_Of (Entity (Bound), Loc));
4647 end Actual_Discriminant_Ref;
4649 -- Start of processing for Actual_Index_Type
4652 if not Has_Discriminants (Tsk)
4653 or else (not Is_Entity_Name (Lo)
4654 and then not Is_Entity_Name (Hi))
4656 return Entry_Index_Type (E);
4659 New_T := Create_Itype (Ekind (Typ), Parent (Entry_Name));
4660 Set_Etype (New_T, Base_Type (Typ));
4661 Set_Size_Info (New_T, Typ);
4662 Set_RM_Size (New_T, RM_Size (Typ));
4663 Set_Scalar_Range (New_T,
4664 Make_Range (Sloc (Entry_Name),
4665 Low_Bound => Actual_Discriminant_Ref (Lo),
4666 High_Bound => Actual_Discriminant_Ref (Hi)));
4670 end Actual_Index_Type;
4672 -- Start of processing of Resolve_Entry
4675 -- Find name of entry being called, and resolve prefix of name
4676 -- with its own type. The prefix can be overloaded, and the name
4677 -- and signature of the entry must be taken into account.
4679 if Nkind (Entry_Name) = N_Indexed_Component then
4681 -- Case of dealing with entry family within the current tasks
4683 E_Name := Prefix (Entry_Name);
4686 E_Name := Entry_Name;
4689 if Is_Entity_Name (E_Name) then
4690 -- Entry call to an entry (or entry family) in the current task.
4691 -- This is legal even though the task will deadlock. Rewrite as
4692 -- call to current task.
4694 -- This can also be a call to an entry in an enclosing task.
4695 -- If this is a single task, we have to retrieve its name,
4696 -- because the scope of the entry is the task type, not the
4697 -- object. If the enclosing task is a task type, the identity
4698 -- of the task is given by its own self variable.
4700 -- Finally this can be a requeue on an entry of the same task
4701 -- or protected object.
4703 S := Scope (Entity (E_Name));
4705 for J in reverse 0 .. Scope_Stack.Last loop
4707 if Is_Task_Type (Scope_Stack.Table (J).Entity)
4708 and then not Comes_From_Source (S)
4710 -- S is an enclosing task or protected object. The concurrent
4711 -- declaration has been converted into a type declaration, and
4712 -- the object itself has an object declaration that follows
4713 -- the type in the same declarative part.
4715 Tsk := Next_Entity (S);
4716 while Etype (Tsk) /= S loop
4723 elsif S = Scope_Stack.Table (J).Entity then
4725 -- Call to current task. Will be transformed into call to Self
4733 Make_Selected_Component (Loc,
4734 Prefix => New_Occurrence_Of (S, Loc),
4736 New_Occurrence_Of (Entity (E_Name), Loc));
4737 Rewrite (E_Name, New_N);
4740 elsif Nkind (Entry_Name) = N_Selected_Component
4741 and then Is_Overloaded (Prefix (Entry_Name))
4743 -- Use the entry name (which must be unique at this point) to
4744 -- find the prefix that returns the corresponding task type or
4748 Pref : constant Node_Id := Prefix (Entry_Name);
4749 Ent : constant Entity_Id := Entity (Selector_Name (Entry_Name));
4754 Get_First_Interp (Pref, I, It);
4755 while Present (It.Typ) loop
4756 if Scope (Ent) = It.Typ then
4757 Set_Etype (Pref, It.Typ);
4761 Get_Next_Interp (I, It);
4766 if Nkind (Entry_Name) = N_Selected_Component then
4767 Resolve (Prefix (Entry_Name));
4769 else pragma Assert (Nkind (Entry_Name) = N_Indexed_Component);
4770 Nam := Entity (Selector_Name (Prefix (Entry_Name)));
4771 Resolve (Prefix (Prefix (Entry_Name)));
4772 Index := First (Expressions (Entry_Name));
4773 Resolve (Index, Entry_Index_Type (Nam));
4775 -- Up to this point the expression could have been the actual
4776 -- in a simple entry call, and be given by a named association.
4778 if Nkind (Index) = N_Parameter_Association then
4779 Error_Msg_N ("expect expression for entry index", Index);
4781 Apply_Range_Check (Index, Actual_Index_Type (Nam));
4786 ------------------------
4787 -- Resolve_Entry_Call --
4788 ------------------------
4790 procedure Resolve_Entry_Call (N : Node_Id; Typ : Entity_Id) is
4791 Entry_Name : constant Node_Id := Name (N);
4792 Loc : constant Source_Ptr := Sloc (Entry_Name);
4794 First_Named : Node_Id;
4801 -- We kill all checks here, because it does not seem worth the
4802 -- effort to do anything better, an entry call is a big operation.
4806 -- Processing of the name is similar for entry calls and protected
4807 -- operation calls. Once the entity is determined, we can complete
4808 -- the resolution of the actuals.
4810 -- The selector may be overloaded, in the case of a protected object
4811 -- with overloaded functions. The type of the context is used for
4814 if Nkind (Entry_Name) = N_Selected_Component
4815 and then Is_Overloaded (Selector_Name (Entry_Name))
4816 and then Typ /= Standard_Void_Type
4823 Get_First_Interp (Selector_Name (Entry_Name), I, It);
4824 while Present (It.Typ) loop
4825 if Covers (Typ, It.Typ) then
4826 Set_Entity (Selector_Name (Entry_Name), It.Nam);
4827 Set_Etype (Entry_Name, It.Typ);
4829 Generate_Reference (It.Typ, N, ' ');
4832 Get_Next_Interp (I, It);
4837 Resolve_Entry (Entry_Name);
4839 if Nkind (Entry_Name) = N_Selected_Component then
4841 -- Simple entry call
4843 Nam := Entity (Selector_Name (Entry_Name));
4844 Obj := Prefix (Entry_Name);
4845 Was_Over := Is_Overloaded (Selector_Name (Entry_Name));
4847 else pragma Assert (Nkind (Entry_Name) = N_Indexed_Component);
4849 -- Call to member of entry family
4851 Nam := Entity (Selector_Name (Prefix (Entry_Name)));
4852 Obj := Prefix (Prefix (Entry_Name));
4853 Was_Over := Is_Overloaded (Selector_Name (Prefix (Entry_Name)));
4856 -- We cannot in general check the maximum depth of protected entry
4857 -- calls at compile time. But we can tell that any protected entry
4858 -- call at all violates a specified nesting depth of zero.
4860 if Is_Protected_Type (Scope (Nam)) then
4861 Check_Restriction (Max_Entry_Queue_Length, N);
4864 -- Use context type to disambiguate a protected function that can be
4865 -- called without actuals and that returns an array type, and where
4866 -- the argument list may be an indexing of the returned value.
4868 if Ekind (Nam) = E_Function
4869 and then Needs_No_Actuals (Nam)
4870 and then Present (Parameter_Associations (N))
4872 ((Is_Array_Type (Etype (Nam))
4873 and then Covers (Typ, Component_Type (Etype (Nam))))
4875 or else (Is_Access_Type (Etype (Nam))
4876 and then Is_Array_Type (Designated_Type (Etype (Nam)))
4877 and then Covers (Typ,
4878 Component_Type (Designated_Type (Etype (Nam))))))
4881 Index_Node : Node_Id;
4885 Make_Indexed_Component (Loc,
4887 Make_Function_Call (Loc,
4888 Name => Relocate_Node (Entry_Name)),
4889 Expressions => Parameter_Associations (N));
4891 -- Since we are correcting a node classification error made by
4892 -- the parser, we call Replace rather than Rewrite.
4894 Replace (N, Index_Node);
4895 Set_Etype (Prefix (N), Etype (Nam));
4897 Resolve_Indexed_Component (N, Typ);
4902 -- The operation name may have been overloaded. Order the actuals
4903 -- according to the formals of the resolved entity, and set the
4904 -- return type to that of the operation.
4907 Normalize_Actuals (N, Nam, False, Norm_OK);
4908 pragma Assert (Norm_OK);
4909 Set_Etype (N, Etype (Nam));
4912 Resolve_Actuals (N, Nam);
4913 Generate_Reference (Nam, Entry_Name);
4915 if Ekind (Nam) = E_Entry
4916 or else Ekind (Nam) = E_Entry_Family
4918 Check_Potentially_Blocking_Operation (N);
4921 -- Verify that a procedure call cannot masquerade as an entry
4922 -- call where an entry call is expected.
4924 if Ekind (Nam) = E_Procedure then
4925 if Nkind (Parent (N)) = N_Entry_Call_Alternative
4926 and then N = Entry_Call_Statement (Parent (N))
4928 Error_Msg_N ("entry call required in select statement", N);
4930 elsif Nkind (Parent (N)) = N_Triggering_Alternative
4931 and then N = Triggering_Statement (Parent (N))
4933 Error_Msg_N ("triggering statement cannot be procedure call", N);
4935 elsif Ekind (Scope (Nam)) = E_Task_Type
4936 and then not In_Open_Scopes (Scope (Nam))
4938 Error_Msg_N ("task has no entry with this name", Entry_Name);
4942 -- After resolution, entry calls and protected procedure calls
4943 -- are changed into entry calls, for expansion. The structure
4944 -- of the node does not change, so it can safely be done in place.
4945 -- Protected function calls must keep their structure because they
4946 -- are subexpressions.
4948 if Ekind (Nam) /= E_Function then
4950 -- A protected operation that is not a function may modify the
4951 -- corresponding object, and cannot apply to a constant.
4952 -- If this is an internal call, the prefix is the type itself.
4954 if Is_Protected_Type (Scope (Nam))
4955 and then not Is_Variable (Obj)
4956 and then (not Is_Entity_Name (Obj)
4957 or else not Is_Type (Entity (Obj)))
4960 ("prefix of protected procedure or entry call must be variable",
4964 Actuals := Parameter_Associations (N);
4965 First_Named := First_Named_Actual (N);
4968 Make_Entry_Call_Statement (Loc,
4970 Parameter_Associations => Actuals));
4972 Set_First_Named_Actual (N, First_Named);
4973 Set_Analyzed (N, True);
4975 -- Protected functions can return on the secondary stack, in which
4976 -- case we must trigger the transient scope mechanism.
4978 elsif Expander_Active
4979 and then Requires_Transient_Scope (Etype (Nam))
4981 Establish_Transient_Scope (N,
4982 Sec_Stack => not Functions_Return_By_DSP_On_Target);
4984 end Resolve_Entry_Call;
4986 -------------------------
4987 -- Resolve_Equality_Op --
4988 -------------------------
4990 -- Both arguments must have the same type, and the boolean context
4991 -- does not participate in the resolution. The first pass verifies
4992 -- that the interpretation is not ambiguous, and the type of the left
4993 -- argument is correctly set, or is Any_Type in case of ambiguity.
4994 -- If both arguments are strings or aggregates, allocators, or Null,
4995 -- they are ambiguous even though they carry a single (universal) type.
4996 -- Diagnose this case here.
4998 procedure Resolve_Equality_Op (N : Node_Id; Typ : Entity_Id) is
4999 L : constant Node_Id := Left_Opnd (N);
5000 R : constant Node_Id := Right_Opnd (N);
5001 T : Entity_Id := Find_Unique_Type (L, R);
5003 function Find_Unique_Access_Type return Entity_Id;
5004 -- In the case of allocators, make a last-ditch attempt to find a single
5005 -- access type with the right designated type. This is semantically
5006 -- dubious, and of no interest to any real code, but c48008a makes it
5009 -----------------------------
5010 -- Find_Unique_Access_Type --
5011 -----------------------------
5013 function Find_Unique_Access_Type return Entity_Id is
5019 if Ekind (Etype (R)) = E_Allocator_Type then
5020 Acc := Designated_Type (Etype (R));
5022 elsif Ekind (Etype (L)) = E_Allocator_Type then
5023 Acc := Designated_Type (Etype (L));
5030 while S /= Standard_Standard loop
5031 E := First_Entity (S);
5032 while Present (E) loop
5034 and then Is_Access_Type (E)
5035 and then Ekind (E) /= E_Allocator_Type
5036 and then Designated_Type (E) = Base_Type (Acc)
5048 end Find_Unique_Access_Type;
5050 -- Start of processing for Resolve_Equality_Op
5053 Set_Etype (N, Base_Type (Typ));
5054 Generate_Reference (T, N, ' ');
5056 if T = Any_Fixed then
5057 T := Unique_Fixed_Point_Type (L);
5060 if T /= Any_Type then
5062 or else T = Any_Composite
5063 or else T = Any_Character
5065 if T = Any_Character then
5066 Ambiguous_Character (L);
5068 Error_Msg_N ("ambiguous operands for equality", N);
5071 Set_Etype (N, Any_Type);
5074 elsif T = Any_Access
5075 or else Ekind (T) = E_Allocator_Type
5077 T := Find_Unique_Access_Type;
5080 Error_Msg_N ("ambiguous operands for equality", N);
5081 Set_Etype (N, Any_Type);
5089 if Warn_On_Redundant_Constructs
5090 and then Comes_From_Source (N)
5091 and then Is_Entity_Name (R)
5092 and then Entity (R) = Standard_True
5093 and then Comes_From_Source (R)
5095 Error_Msg_N ("comparison with True is redundant?", R);
5098 Check_Unset_Reference (L);
5099 Check_Unset_Reference (R);
5100 Generate_Operator_Reference (N, T);
5102 -- If this is an inequality, it may be the implicit inequality
5103 -- created for a user-defined operation, in which case the corres-
5104 -- ponding equality operation is not intrinsic, and the operation
5105 -- cannot be constant-folded. Else fold.
5107 if Nkind (N) = N_Op_Eq
5108 or else Comes_From_Source (Entity (N))
5109 or else Ekind (Entity (N)) = E_Operator
5110 or else Is_Intrinsic_Subprogram
5111 (Corresponding_Equality (Entity (N)))
5113 Eval_Relational_Op (N);
5114 elsif Nkind (N) = N_Op_Ne
5115 and then Is_Abstract (Entity (N))
5117 Error_Msg_NE ("cannot call abstract subprogram &!", N, Entity (N));
5120 -- Ada 2005: If one operand is an anonymous access type, convert
5121 -- the other operand to it, to ensure that the underlying types
5122 -- match in the back-end.
5123 -- We apply the same conversion in the case one of the operands is
5124 -- a private subtype of the type of the other.
5127 and then (Ekind (T) = E_Anonymous_Access_Type
5128 or else Is_Private_Type (T))
5130 if Etype (L) /= T then
5132 Make_Unchecked_Type_Conversion (Sloc (L),
5133 Subtype_Mark => New_Occurrence_Of (T, Sloc (L)),
5134 Expression => Relocate_Node (L)));
5135 Analyze_And_Resolve (L, T);
5138 if (Etype (R)) /= T then
5140 Make_Unchecked_Type_Conversion (Sloc (R),
5141 Subtype_Mark => New_Occurrence_Of (Etype (L), Sloc (R)),
5142 Expression => Relocate_Node (R)));
5143 Analyze_And_Resolve (R, T);
5147 end Resolve_Equality_Op;
5149 ----------------------------------
5150 -- Resolve_Explicit_Dereference --
5151 ----------------------------------
5153 procedure Resolve_Explicit_Dereference (N : Node_Id; Typ : Entity_Id) is
5154 Loc : constant Source_Ptr := Sloc (N);
5156 P : constant Node_Id := Prefix (N);
5161 Check_Fully_Declared_Prefix (Typ, P);
5163 if Is_Overloaded (P) then
5165 -- Use the context type to select the prefix that has the correct
5168 Get_First_Interp (P, I, It);
5169 while Present (It.Typ) loop
5170 exit when Is_Access_Type (It.Typ)
5171 and then Covers (Typ, Designated_Type (It.Typ));
5172 Get_Next_Interp (I, It);
5175 if Present (It.Typ) then
5176 Resolve (P, It.Typ);
5178 -- If no interpretation covers the designated type of the prefix,
5179 -- this is the pathological case where not all implementations of
5180 -- the prefix allow the interpretation of the node as a call. Now
5181 -- that the expected type is known, Remove other interpretations
5182 -- from prefix, rewrite it as a call, and resolve again, so that
5183 -- the proper call node is generated.
5185 Get_First_Interp (P, I, It);
5186 while Present (It.Typ) loop
5187 if Ekind (It.Typ) /= E_Access_Subprogram_Type then
5191 Get_Next_Interp (I, It);
5195 Make_Function_Call (Loc,
5197 Make_Explicit_Dereference (Loc,
5199 Parameter_Associations => New_List);
5201 Save_Interps (N, New_N);
5203 Analyze_And_Resolve (N, Typ);
5207 Set_Etype (N, Designated_Type (It.Typ));
5213 if Is_Access_Type (Etype (P)) then
5214 Apply_Access_Check (N);
5217 -- If the designated type is a packed unconstrained array type, and the
5218 -- explicit dereference is not in the context of an attribute reference,
5219 -- then we must compute and set the actual subtype, since it is needed
5220 -- by Gigi. The reason we exclude the attribute case is that this is
5221 -- handled fine by Gigi, and in fact we use such attributes to build the
5222 -- actual subtype. We also exclude generated code (which builds actual
5223 -- subtypes directly if they are needed).
5225 if Is_Array_Type (Etype (N))
5226 and then Is_Packed (Etype (N))
5227 and then not Is_Constrained (Etype (N))
5228 and then Nkind (Parent (N)) /= N_Attribute_Reference
5229 and then Comes_From_Source (N)
5231 Set_Etype (N, Get_Actual_Subtype (N));
5234 -- Note: there is no Eval processing required for an explicit deference,
5235 -- because the type is known to be an allocators, and allocator
5236 -- expressions can never be static.
5238 end Resolve_Explicit_Dereference;
5240 -------------------------------
5241 -- Resolve_Indexed_Component --
5242 -------------------------------
5244 procedure Resolve_Indexed_Component (N : Node_Id; Typ : Entity_Id) is
5245 Name : constant Node_Id := Prefix (N);
5247 Array_Type : Entity_Id := Empty; -- to prevent junk warning
5251 if Is_Overloaded (Name) then
5253 -- Use the context type to select the prefix that yields the correct
5259 I1 : Interp_Index := 0;
5260 P : constant Node_Id := Prefix (N);
5261 Found : Boolean := False;
5264 Get_First_Interp (P, I, It);
5265 while Present (It.Typ) loop
5266 if (Is_Array_Type (It.Typ)
5267 and then Covers (Typ, Component_Type (It.Typ)))
5268 or else (Is_Access_Type (It.Typ)
5269 and then Is_Array_Type (Designated_Type (It.Typ))
5271 (Typ, Component_Type (Designated_Type (It.Typ))))
5274 It := Disambiguate (P, I1, I, Any_Type);
5276 if It = No_Interp then
5277 Error_Msg_N ("ambiguous prefix for indexing", N);
5283 Array_Type := It.Typ;
5289 Array_Type := It.Typ;
5294 Get_Next_Interp (I, It);
5299 Array_Type := Etype (Name);
5302 Resolve (Name, Array_Type);
5303 Array_Type := Get_Actual_Subtype_If_Available (Name);
5305 -- If prefix is access type, dereference to get real array type.
5306 -- Note: we do not apply an access check because the expander always
5307 -- introduces an explicit dereference, and the check will happen there.
5309 if Is_Access_Type (Array_Type) then
5310 Array_Type := Designated_Type (Array_Type);
5313 -- If name was overloaded, set component type correctly now
5315 Set_Etype (N, Component_Type (Array_Type));
5317 Index := First_Index (Array_Type);
5318 Expr := First (Expressions (N));
5320 -- The prefix may have resolved to a string literal, in which case its
5321 -- etype has a special representation. This is only possible currently
5322 -- if the prefix is a static concatenation, written in functional
5325 if Ekind (Array_Type) = E_String_Literal_Subtype then
5326 Resolve (Expr, Standard_Positive);
5329 while Present (Index) and Present (Expr) loop
5330 Resolve (Expr, Etype (Index));
5331 Check_Unset_Reference (Expr);
5333 if Is_Scalar_Type (Etype (Expr)) then
5334 Apply_Scalar_Range_Check (Expr, Etype (Index));
5336 Apply_Range_Check (Expr, Get_Actual_Subtype (Index));
5344 Warn_On_Suspicious_Index (Name, First (Expressions (N)));
5345 Eval_Indexed_Component (N);
5346 end Resolve_Indexed_Component;
5348 -----------------------------
5349 -- Resolve_Integer_Literal --
5350 -----------------------------
5352 procedure Resolve_Integer_Literal (N : Node_Id; Typ : Entity_Id) is
5355 Eval_Integer_Literal (N);
5356 end Resolve_Integer_Literal;
5358 --------------------------------
5359 -- Resolve_Intrinsic_Operator --
5360 --------------------------------
5362 procedure Resolve_Intrinsic_Operator (N : Node_Id; Typ : Entity_Id) is
5363 Btyp : constant Entity_Id := Base_Type (Underlying_Type (Typ));
5370 while Scope (Op) /= Standard_Standard loop
5372 pragma Assert (Present (Op));
5376 Set_Is_Overloaded (N, False);
5378 -- If the operand type is private, rewrite with suitable conversions on
5379 -- the operands and the result, to expose the proper underlying numeric
5382 if Is_Private_Type (Typ) then
5383 Arg1 := Unchecked_Convert_To (Btyp, Left_Opnd (N));
5385 if Nkind (N) = N_Op_Expon then
5386 Arg2 := Unchecked_Convert_To (Standard_Integer, Right_Opnd (N));
5388 Arg2 := Unchecked_Convert_To (Btyp, Right_Opnd (N));
5391 Save_Interps (Left_Opnd (N), Expression (Arg1));
5392 Save_Interps (Right_Opnd (N), Expression (Arg2));
5394 Set_Left_Opnd (N, Arg1);
5395 Set_Right_Opnd (N, Arg2);
5397 Set_Etype (N, Btyp);
5398 Rewrite (N, Unchecked_Convert_To (Typ, N));
5401 elsif Typ /= Etype (Left_Opnd (N))
5402 or else Typ /= Etype (Right_Opnd (N))
5404 -- Add explicit conversion where needed, and save interpretations
5405 -- in case operands are overloaded.
5407 Arg1 := Convert_To (Typ, Left_Opnd (N));
5408 Arg2 := Convert_To (Typ, Right_Opnd (N));
5410 if Nkind (Arg1) = N_Type_Conversion then
5411 Save_Interps (Left_Opnd (N), Expression (Arg1));
5413 Save_Interps (Left_Opnd (N), Arg1);
5416 if Nkind (Arg2) = N_Type_Conversion then
5417 Save_Interps (Right_Opnd (N), Expression (Arg2));
5419 Save_Interps (Right_Opnd (N), Arg2);
5422 Rewrite (Left_Opnd (N), Arg1);
5423 Rewrite (Right_Opnd (N), Arg2);
5426 Resolve_Arithmetic_Op (N, Typ);
5429 Resolve_Arithmetic_Op (N, Typ);
5431 end Resolve_Intrinsic_Operator;
5433 --------------------------------------
5434 -- Resolve_Intrinsic_Unary_Operator --
5435 --------------------------------------
5437 procedure Resolve_Intrinsic_Unary_Operator
5441 Btyp : constant Entity_Id := Base_Type (Underlying_Type (Typ));
5447 while Scope (Op) /= Standard_Standard loop
5449 pragma Assert (Present (Op));
5454 if Is_Private_Type (Typ) then
5455 Arg2 := Unchecked_Convert_To (Btyp, Right_Opnd (N));
5456 Save_Interps (Right_Opnd (N), Expression (Arg2));
5458 Set_Right_Opnd (N, Arg2);
5460 Set_Etype (N, Btyp);
5461 Rewrite (N, Unchecked_Convert_To (Typ, N));
5465 Resolve_Unary_Op (N, Typ);
5467 end Resolve_Intrinsic_Unary_Operator;
5469 ------------------------
5470 -- Resolve_Logical_Op --
5471 ------------------------
5473 procedure Resolve_Logical_Op (N : Node_Id; Typ : Entity_Id) is
5475 N_Opr : constant Node_Kind := Nkind (N);
5478 -- Predefined operations on scalar types yield the base type. On the
5479 -- other hand, logical operations on arrays yield the type of the
5480 -- arguments (and the context).
5482 if Is_Array_Type (Typ) then
5485 B_Typ := Base_Type (Typ);
5488 -- The following test is required because the operands of the operation
5489 -- may be literals, in which case the resulting type appears to be
5490 -- compatible with a signed integer type, when in fact it is compatible
5491 -- only with modular types. If the context itself is universal, the
5492 -- operation is illegal.
5494 if not Valid_Boolean_Arg (Typ) then
5495 Error_Msg_N ("invalid context for logical operation", N);
5496 Set_Etype (N, Any_Type);
5499 elsif Typ = Any_Modular then
5501 ("no modular type available in this context", N);
5502 Set_Etype (N, Any_Type);
5504 elsif Is_Modular_Integer_Type (Typ)
5505 and then Etype (Left_Opnd (N)) = Universal_Integer
5506 and then Etype (Right_Opnd (N)) = Universal_Integer
5508 Check_For_Visible_Operator (N, B_Typ);
5511 Resolve (Left_Opnd (N), B_Typ);
5512 Resolve (Right_Opnd (N), B_Typ);
5514 Check_Unset_Reference (Left_Opnd (N));
5515 Check_Unset_Reference (Right_Opnd (N));
5517 Set_Etype (N, B_Typ);
5518 Generate_Operator_Reference (N, B_Typ);
5519 Eval_Logical_Op (N);
5521 -- Check for violation of restriction No_Direct_Boolean_Operators
5522 -- if the operator was not eliminated by the Eval_Logical_Op call.
5524 if Nkind (N) = N_Opr
5525 and then Root_Type (Etype (Left_Opnd (N))) = Standard_Boolean
5527 Check_Restriction (No_Direct_Boolean_Operators, N);
5529 end Resolve_Logical_Op;
5531 ---------------------------
5532 -- Resolve_Membership_Op --
5533 ---------------------------
5535 -- The context can only be a boolean type, and does not determine
5536 -- the arguments. Arguments should be unambiguous, but the preference
5537 -- rule for universal types applies.
5539 procedure Resolve_Membership_Op (N : Node_Id; Typ : Entity_Id) is
5540 pragma Warnings (Off, Typ);
5542 L : constant Node_Id := Left_Opnd (N);
5543 R : constant Node_Id := Right_Opnd (N);
5547 if L = Error or else R = Error then
5551 if not Is_Overloaded (R)
5553 (Etype (R) = Universal_Integer or else
5554 Etype (R) = Universal_Real)
5555 and then Is_Overloaded (L)
5559 -- Ada 2005 (AI-251): Give support to the following case:
5561 -- type I is interface;
5562 -- type T is tagged ...
5564 -- function Test (O : I'Class) is
5566 -- return O in T'Class.
5569 -- In this case we have nothing else to do; the membership test will be
5570 -- done at run-time.
5572 elsif Ada_Version >= Ada_05
5573 and then Is_Class_Wide_Type (Etype (L))
5574 and then Is_Interface (Etype (L))
5575 and then Is_Class_Wide_Type (Etype (R))
5576 and then not Is_Interface (Etype (R))
5581 T := Intersect_Types (L, R);
5585 Check_Unset_Reference (L);
5587 if Nkind (R) = N_Range
5588 and then not Is_Scalar_Type (T)
5590 Error_Msg_N ("scalar type required for range", R);
5593 if Is_Entity_Name (R) then
5594 Freeze_Expression (R);
5597 Check_Unset_Reference (R);
5600 Eval_Membership_Op (N);
5601 end Resolve_Membership_Op;
5607 procedure Resolve_Null (N : Node_Id; Typ : Entity_Id) is
5609 -- Handle restriction against anonymous null access values This
5610 -- restriction can be turned off using -gnatdh.
5612 -- Ada 2005 (AI-231): Remove restriction
5614 if Ada_Version < Ada_05
5615 and then not Debug_Flag_J
5616 and then Ekind (Typ) = E_Anonymous_Access_Type
5617 and then Comes_From_Source (N)
5619 -- In the common case of a call which uses an explicitly null
5620 -- value for an access parameter, give specialized error msg
5622 if Nkind (Parent (N)) = N_Procedure_Call_Statement
5624 Nkind (Parent (N)) = N_Function_Call
5627 ("null is not allowed as argument for an access parameter", N);
5629 -- Standard message for all other cases (are there any?)
5633 ("null cannot be of an anonymous access type", N);
5637 -- In a distributed context, null for a remote access to subprogram
5638 -- may need to be replaced with a special record aggregate. In this
5639 -- case, return after having done the transformation.
5641 if (Ekind (Typ) = E_Record_Type
5642 or else Is_Remote_Access_To_Subprogram_Type (Typ))
5643 and then Remote_AST_Null_Value (N, Typ)
5648 -- The null literal takes its type from the context
5653 -----------------------
5654 -- Resolve_Op_Concat --
5655 -----------------------
5657 procedure Resolve_Op_Concat (N : Node_Id; Typ : Entity_Id) is
5658 Btyp : constant Entity_Id := Base_Type (Typ);
5659 Op1 : constant Node_Id := Left_Opnd (N);
5660 Op2 : constant Node_Id := Right_Opnd (N);
5662 procedure Resolve_Concatenation_Arg (Arg : Node_Id; Is_Comp : Boolean);
5663 -- Internal procedure to resolve one operand of concatenation operator.
5664 -- The operand is either of the array type or of the component type.
5665 -- If the operand is an aggregate, and the component type is composite,
5666 -- this is ambiguous if component type has aggregates.
5668 -------------------------------
5669 -- Resolve_Concatenation_Arg --
5670 -------------------------------
5672 procedure Resolve_Concatenation_Arg (Arg : Node_Id; Is_Comp : Boolean) is
5676 or else (not Is_Overloaded (Arg)
5677 and then Etype (Arg) /= Any_Composite
5678 and then Covers (Component_Type (Typ), Etype (Arg)))
5680 Resolve (Arg, Component_Type (Typ));
5682 Resolve (Arg, Btyp);
5685 elsif Has_Compatible_Type (Arg, Component_Type (Typ)) then
5687 if Nkind (Arg) = N_Aggregate
5688 and then Is_Composite_Type (Component_Type (Typ))
5690 if Is_Private_Type (Component_Type (Typ)) then
5691 Resolve (Arg, Btyp);
5694 Error_Msg_N ("ambiguous aggregate must be qualified", Arg);
5695 Set_Etype (Arg, Any_Type);
5699 if Is_Overloaded (Arg)
5700 and then Has_Compatible_Type (Arg, Typ)
5701 and then Etype (Arg) /= Any_Type
5710 Get_First_Interp (Arg, I, It);
5712 Get_Next_Interp (I, It);
5714 -- Special-case the error message when the overloading
5715 -- is caused by a function that yields and array and
5716 -- can be called without parameters.
5718 if It.Nam = Func then
5719 Error_Msg_Sloc := Sloc (Func);
5720 Error_Msg_N ("\ambiguous call to function#", Arg);
5722 ("\\interpretation as call yields&", Arg, Typ);
5724 ("\\interpretation as indexing of call yields&",
5725 Arg, Component_Type (Typ));
5729 ("ambiguous operand for concatenation!", Arg);
5730 Get_First_Interp (Arg, I, It);
5731 while Present (It.Nam) loop
5732 Error_Msg_Sloc := Sloc (It.Nam);
5734 if Base_Type (It.Typ) = Base_Type (Typ)
5735 or else Base_Type (It.Typ) =
5736 Base_Type (Component_Type (Typ))
5738 Error_Msg_N ("\\possible interpretation#", Arg);
5741 Get_Next_Interp (I, It);
5747 Resolve (Arg, Component_Type (Typ));
5749 if Nkind (Arg) = N_String_Literal then
5750 Set_Etype (Arg, Component_Type (Typ));
5753 if Arg = Left_Opnd (N) then
5754 Set_Is_Component_Left_Opnd (N);
5756 Set_Is_Component_Right_Opnd (N);
5761 Resolve (Arg, Btyp);
5764 Check_Unset_Reference (Arg);
5765 end Resolve_Concatenation_Arg;
5767 -- Start of processing for Resolve_Op_Concat
5770 Set_Etype (N, Btyp);
5772 if Is_Limited_Composite (Btyp) then
5773 Error_Msg_N ("concatenation not available for limited array", N);
5774 Explain_Limited_Type (Btyp, N);
5777 -- If the operands are themselves concatenations, resolve them as such
5778 -- directly. This removes several layers of recursion and allows GNAT to
5779 -- handle larger multiple concatenations.
5781 if Nkind (Op1) = N_Op_Concat
5782 and then not Is_Array_Type (Component_Type (Typ))
5783 and then Entity (Op1) = Entity (N)
5785 Resolve_Op_Concat (Op1, Typ);
5787 Resolve_Concatenation_Arg
5788 (Op1, Is_Component_Left_Opnd (N));
5791 if Nkind (Op2) = N_Op_Concat
5792 and then not Is_Array_Type (Component_Type (Typ))
5793 and then Entity (Op2) = Entity (N)
5795 Resolve_Op_Concat (Op2, Typ);
5797 Resolve_Concatenation_Arg
5798 (Op2, Is_Component_Right_Opnd (N));
5801 Generate_Operator_Reference (N, Typ);
5803 if Is_String_Type (Typ) then
5804 Eval_Concatenation (N);
5807 -- If this is not a static concatenation, but the result is a
5808 -- string type (and not an array of strings) insure that static
5809 -- string operands have their subtypes properly constructed.
5811 if Nkind (N) /= N_String_Literal
5812 and then Is_Character_Type (Component_Type (Typ))
5814 Set_String_Literal_Subtype (Op1, Typ);
5815 Set_String_Literal_Subtype (Op2, Typ);
5817 end Resolve_Op_Concat;
5819 ----------------------
5820 -- Resolve_Op_Expon --
5821 ----------------------
5823 procedure Resolve_Op_Expon (N : Node_Id; Typ : Entity_Id) is
5824 B_Typ : constant Entity_Id := Base_Type (Typ);
5827 -- Catch attempts to do fixed-point exponentation with universal
5828 -- operands, which is a case where the illegality is not caught during
5829 -- normal operator analysis.
5831 if Is_Fixed_Point_Type (Typ) and then Comes_From_Source (N) then
5832 Error_Msg_N ("exponentiation not available for fixed point", N);
5836 if Comes_From_Source (N)
5837 and then Ekind (Entity (N)) = E_Function
5838 and then Is_Imported (Entity (N))
5839 and then Is_Intrinsic_Subprogram (Entity (N))
5841 Resolve_Intrinsic_Operator (N, Typ);
5845 if Etype (Left_Opnd (N)) = Universal_Integer
5846 or else Etype (Left_Opnd (N)) = Universal_Real
5848 Check_For_Visible_Operator (N, B_Typ);
5851 -- We do the resolution using the base type, because intermediate values
5852 -- in expressions always are of the base type, not a subtype of it.
5854 Resolve (Left_Opnd (N), B_Typ);
5855 Resolve (Right_Opnd (N), Standard_Integer);
5857 Check_Unset_Reference (Left_Opnd (N));
5858 Check_Unset_Reference (Right_Opnd (N));
5860 Set_Etype (N, B_Typ);
5861 Generate_Operator_Reference (N, B_Typ);
5864 -- Set overflow checking bit. Much cleverer code needed here eventually
5865 -- and perhaps the Resolve routines should be separated for the various
5866 -- arithmetic operations, since they will need different processing. ???
5868 if Nkind (N) in N_Op then
5869 if not Overflow_Checks_Suppressed (Etype (N)) then
5870 Enable_Overflow_Check (N);
5873 end Resolve_Op_Expon;
5875 --------------------
5876 -- Resolve_Op_Not --
5877 --------------------
5879 procedure Resolve_Op_Not (N : Node_Id; Typ : Entity_Id) is
5882 function Parent_Is_Boolean return Boolean;
5883 -- This function determines if the parent node is a boolean operator
5884 -- or operation (comparison op, membership test, or short circuit form)
5885 -- and the not in question is the left operand of this operation.
5886 -- Note that if the not is in parens, then false is returned.
5888 -----------------------
5889 -- Parent_Is_Boolean --
5890 -----------------------
5892 function Parent_Is_Boolean return Boolean is
5894 if Paren_Count (N) /= 0 then
5898 case Nkind (Parent (N)) is
5913 return Left_Opnd (Parent (N)) = N;
5919 end Parent_Is_Boolean;
5921 -- Start of processing for Resolve_Op_Not
5924 -- Predefined operations on scalar types yield the base type. On the
5925 -- other hand, logical operations on arrays yield the type of the
5926 -- arguments (and the context).
5928 if Is_Array_Type (Typ) then
5931 B_Typ := Base_Type (Typ);
5934 -- Straigtforward case of incorrect arguments
5936 if not Valid_Boolean_Arg (Typ) then
5937 Error_Msg_N ("invalid operand type for operator&", N);
5938 Set_Etype (N, Any_Type);
5941 -- Special case of probable missing parens
5943 elsif Typ = Universal_Integer or else Typ = Any_Modular then
5944 if Parent_Is_Boolean then
5946 ("operand of not must be enclosed in parentheses",
5950 ("no modular type available in this context", N);
5953 Set_Etype (N, Any_Type);
5956 -- OK resolution of not
5959 -- Warn if non-boolean types involved. This is a case like not a < b
5960 -- where a and b are modular, where we will get (not a) < b and most
5961 -- likely not (a < b) was intended.
5963 if Warn_On_Questionable_Missing_Parens
5964 and then not Is_Boolean_Type (Typ)
5965 and then Parent_Is_Boolean
5967 Error_Msg_N ("?not expression should be parenthesized here", N);
5970 Resolve (Right_Opnd (N), B_Typ);
5971 Check_Unset_Reference (Right_Opnd (N));
5972 Set_Etype (N, B_Typ);
5973 Generate_Operator_Reference (N, B_Typ);
5978 -----------------------------
5979 -- Resolve_Operator_Symbol --
5980 -----------------------------
5982 -- Nothing to be done, all resolved already
5984 procedure Resolve_Operator_Symbol (N : Node_Id; Typ : Entity_Id) is
5985 pragma Warnings (Off, N);
5986 pragma Warnings (Off, Typ);
5990 end Resolve_Operator_Symbol;
5992 ----------------------------------
5993 -- Resolve_Qualified_Expression --
5994 ----------------------------------
5996 procedure Resolve_Qualified_Expression (N : Node_Id; Typ : Entity_Id) is
5997 pragma Warnings (Off, Typ);
5999 Target_Typ : constant Entity_Id := Entity (Subtype_Mark (N));
6000 Expr : constant Node_Id := Expression (N);
6003 Resolve (Expr, Target_Typ);
6005 -- A qualified expression requires an exact match of the type,
6006 -- class-wide matching is not allowed. However, if the qualifying
6007 -- type is specific and the expression has a class-wide type, it
6008 -- may still be okay, since it can be the result of the expansion
6009 -- of a call to a dispatching function, so we also have to check
6010 -- class-wideness of the type of the expression's original node.
6012 if (Is_Class_Wide_Type (Target_Typ)
6014 (Is_Class_Wide_Type (Etype (Expr))
6015 and then Is_Class_Wide_Type (Etype (Original_Node (Expr)))))
6016 and then Base_Type (Etype (Expr)) /= Base_Type (Target_Typ)
6018 Wrong_Type (Expr, Target_Typ);
6021 -- If the target type is unconstrained, then we reset the type of
6022 -- the result from the type of the expression. For other cases, the
6023 -- actual subtype of the expression is the target type.
6025 if Is_Composite_Type (Target_Typ)
6026 and then not Is_Constrained (Target_Typ)
6028 Set_Etype (N, Etype (Expr));
6031 Eval_Qualified_Expression (N);
6032 end Resolve_Qualified_Expression;
6038 procedure Resolve_Range (N : Node_Id; Typ : Entity_Id) is
6039 L : constant Node_Id := Low_Bound (N);
6040 H : constant Node_Id := High_Bound (N);
6047 Check_Unset_Reference (L);
6048 Check_Unset_Reference (H);
6050 -- We have to check the bounds for being within the base range as
6051 -- required for a non-static context. Normally this is automatic and
6052 -- done as part of evaluating expressions, but the N_Range node is an
6053 -- exception, since in GNAT we consider this node to be a subexpression,
6054 -- even though in Ada it is not. The circuit in Sem_Eval could check for
6055 -- this, but that would put the test on the main evaluation path for
6058 Check_Non_Static_Context (L);
6059 Check_Non_Static_Context (H);
6061 -- If bounds are static, constant-fold them, so size computations
6062 -- are identical between front-end and back-end. Do not perform this
6063 -- transformation while analyzing generic units, as type information
6064 -- would then be lost when reanalyzing the constant node in the
6067 if Is_Discrete_Type (Typ) and then Expander_Active then
6068 if Is_OK_Static_Expression (L) then
6069 Fold_Uint (L, Expr_Value (L), Is_Static_Expression (L));
6072 if Is_OK_Static_Expression (H) then
6073 Fold_Uint (H, Expr_Value (H), Is_Static_Expression (H));
6078 --------------------------
6079 -- Resolve_Real_Literal --
6080 --------------------------
6082 procedure Resolve_Real_Literal (N : Node_Id; Typ : Entity_Id) is
6083 Actual_Typ : constant Entity_Id := Etype (N);
6086 -- Special processing for fixed-point literals to make sure that the
6087 -- value is an exact multiple of small where this is required. We
6088 -- skip this for the universal real case, and also for generic types.
6090 if Is_Fixed_Point_Type (Typ)
6091 and then Typ /= Universal_Fixed
6092 and then Typ /= Any_Fixed
6093 and then not Is_Generic_Type (Typ)
6096 Val : constant Ureal := Realval (N);
6097 Cintr : constant Ureal := Val / Small_Value (Typ);
6098 Cint : constant Uint := UR_Trunc (Cintr);
6099 Den : constant Uint := Norm_Den (Cintr);
6103 -- Case of literal is not an exact multiple of the Small
6107 -- For a source program literal for a decimal fixed-point
6108 -- type, this is statically illegal (RM 4.9(36)).
6110 if Is_Decimal_Fixed_Point_Type (Typ)
6111 and then Actual_Typ = Universal_Real
6112 and then Comes_From_Source (N)
6114 Error_Msg_N ("value has extraneous low order digits", N);
6117 -- Generate a warning if literal from source
6119 if Is_Static_Expression (N)
6120 and then Warn_On_Bad_Fixed_Value
6123 ("static fixed-point value is not a multiple of Small?",
6127 -- Replace literal by a value that is the exact representation
6128 -- of a value of the type, i.e. a multiple of the small value,
6129 -- by truncation, since Machine_Rounds is false for all GNAT
6130 -- fixed-point types (RM 4.9(38)).
6132 Stat := Is_Static_Expression (N);
6134 Make_Real_Literal (Sloc (N),
6135 Realval => Small_Value (Typ) * Cint));
6137 Set_Is_Static_Expression (N, Stat);
6140 -- In all cases, set the corresponding integer field
6142 Set_Corresponding_Integer_Value (N, Cint);
6146 -- Now replace the actual type by the expected type as usual
6149 Eval_Real_Literal (N);
6150 end Resolve_Real_Literal;
6152 -----------------------
6153 -- Resolve_Reference --
6154 -----------------------
6156 procedure Resolve_Reference (N : Node_Id; Typ : Entity_Id) is
6157 P : constant Node_Id := Prefix (N);
6160 -- Replace general access with specific type
6162 if Ekind (Etype (N)) = E_Allocator_Type then
6163 Set_Etype (N, Base_Type (Typ));
6166 Resolve (P, Designated_Type (Etype (N)));
6168 -- If we are taking the reference of a volatile entity, then treat
6169 -- it as a potential modification of this entity. This is much too
6170 -- conservative, but is necessary because remove side effects can
6171 -- result in transformations of normal assignments into reference
6172 -- sequences that otherwise fail to notice the modification.
6174 if Is_Entity_Name (P) and then Treat_As_Volatile (Entity (P)) then
6175 Note_Possible_Modification (P);
6177 end Resolve_Reference;
6179 --------------------------------
6180 -- Resolve_Selected_Component --
6181 --------------------------------
6183 procedure Resolve_Selected_Component (N : Node_Id; Typ : Entity_Id) is
6185 Comp1 : Entity_Id := Empty; -- prevent junk warning
6186 P : constant Node_Id := Prefix (N);
6187 S : constant Node_Id := Selector_Name (N);
6188 T : Entity_Id := Etype (P);
6190 I1 : Interp_Index := 0; -- prevent junk warning
6195 function Init_Component return Boolean;
6196 -- Check whether this is the initialization of a component within an
6197 -- init proc (by assignment or call to another init proc). If true,
6198 -- there is no need for a discriminant check.
6200 --------------------
6201 -- Init_Component --
6202 --------------------
6204 function Init_Component return Boolean is
6206 return Inside_Init_Proc
6207 and then Nkind (Prefix (N)) = N_Identifier
6208 and then Chars (Prefix (N)) = Name_uInit
6209 and then Nkind (Parent (Parent (N))) = N_Case_Statement_Alternative;
6212 -- Start of processing for Resolve_Selected_Component
6215 if Is_Overloaded (P) then
6217 -- Use the context type to select the prefix that has a selector
6218 -- of the correct name and type.
6221 Get_First_Interp (P, I, It);
6223 Search : while Present (It.Typ) loop
6224 if Is_Access_Type (It.Typ) then
6225 T := Designated_Type (It.Typ);
6230 if Is_Record_Type (T) then
6231 Comp := First_Entity (T);
6232 while Present (Comp) loop
6233 if Chars (Comp) = Chars (S)
6234 and then Covers (Etype (Comp), Typ)
6243 It := Disambiguate (P, I1, I, Any_Type);
6245 if It = No_Interp then
6247 ("ambiguous prefix for selected component", N);
6254 -- There may be an implicit dereference. Retrieve
6255 -- designated record type.
6257 if Is_Access_Type (It1.Typ) then
6258 T := Designated_Type (It1.Typ);
6263 if Scope (Comp1) /= T then
6265 -- Resolution chooses the new interpretation.
6266 -- Find the component with the right name.
6268 Comp1 := First_Entity (T);
6269 while Present (Comp1)
6270 and then Chars (Comp1) /= Chars (S)
6272 Comp1 := Next_Entity (Comp1);
6281 Comp := Next_Entity (Comp);
6286 Get_Next_Interp (I, It);
6289 Resolve (P, It1.Typ);
6291 Set_Entity_With_Style_Check (S, Comp1);
6294 -- Resolve prefix with its type
6299 -- Generate cross-reference. We needed to wait until full overloading
6300 -- resolution was complete to do this, since otherwise we can't tell if
6301 -- we are an Lvalue of not.
6303 if May_Be_Lvalue (N) then
6304 Generate_Reference (Entity (S), S, 'm
');
6306 Generate_Reference (Entity (S), S, 'r
');
6309 -- If prefix is an access type, the node will be transformed into an
6310 -- explicit dereference during expansion. The type of the node is the
6311 -- designated type of that of the prefix.
6313 if Is_Access_Type (Etype (P)) then
6314 T := Designated_Type (Etype (P));
6315 Check_Fully_Declared_Prefix (T, P);
6320 if Has_Discriminants (T)
6321 and then (Ekind (Entity (S)) = E_Component
6323 Ekind (Entity (S)) = E_Discriminant)
6324 and then Present (Original_Record_Component (Entity (S)))
6325 and then Ekind (Original_Record_Component (Entity (S))) = E_Component
6326 and then Present (Discriminant_Checking_Func
6327 (Original_Record_Component (Entity (S))))
6328 and then not Discriminant_Checks_Suppressed (T)
6329 and then not Init_Component
6331 Set_Do_Discriminant_Check (N);
6334 if Ekind (Entity (S)) = E_Void then
6335 Error_Msg_N ("premature use of component", S);
6338 -- If the prefix is a record conversion, this may be a renamed
6339 -- discriminant whose bounds differ from those of the original
6340 -- one, so we must ensure that a range check is performed.
6342 if Nkind (P) = N_Type_Conversion
6343 and then Ekind (Entity (S)) = E_Discriminant
6344 and then Is_Discrete_Type (Typ)
6346 Set_Etype (N, Base_Type (Typ));
6349 -- Note: No Eval processing is required, because the prefix is of a
6350 -- record type, or protected type, and neither can possibly be static.
6352 end Resolve_Selected_Component;
6358 procedure Resolve_Shift (N : Node_Id; Typ : Entity_Id) is
6359 B_Typ : constant Entity_Id := Base_Type (Typ);
6360 L : constant Node_Id := Left_Opnd (N);
6361 R : constant Node_Id := Right_Opnd (N);
6364 -- We do the resolution using the base type, because intermediate values
6365 -- in expressions always are of the base type, not a subtype of it.
6368 Resolve (R, Standard_Natural);
6370 Check_Unset_Reference (L);
6371 Check_Unset_Reference (R);
6373 Set_Etype (N, B_Typ);
6374 Generate_Operator_Reference (N, B_Typ);
6378 ---------------------------
6379 -- Resolve_Short_Circuit --
6380 ---------------------------
6382 procedure Resolve_Short_Circuit (N : Node_Id; Typ : Entity_Id) is
6383 B_Typ : constant Entity_Id := Base_Type (Typ);
6384 L : constant Node_Id := Left_Opnd (N);
6385 R : constant Node_Id := Right_Opnd (N);
6391 Check_Unset_Reference (L);
6392 Check_Unset_Reference (R);
6394 Set_Etype (N, B_Typ);
6395 Eval_Short_Circuit (N);
6396 end Resolve_Short_Circuit;
6402 procedure Resolve_Slice (N : Node_Id; Typ : Entity_Id) is
6403 Name : constant Node_Id := Prefix (N);
6404 Drange : constant Node_Id := Discrete_Range (N);
6405 Array_Type : Entity_Id := Empty;
6409 if Is_Overloaded (Name) then
6411 -- Use the context type to select the prefix that yields the
6412 -- correct array type.
6416 I1 : Interp_Index := 0;
6418 P : constant Node_Id := Prefix (N);
6419 Found : Boolean := False;
6422 Get_First_Interp (P, I, It);
6423 while Present (It.Typ) loop
6424 if (Is_Array_Type (It.Typ)
6425 and then Covers (Typ, It.Typ))
6426 or else (Is_Access_Type (It.Typ)
6427 and then Is_Array_Type (Designated_Type (It.Typ))
6428 and then Covers (Typ, Designated_Type (It.Typ)))
6431 It := Disambiguate (P, I1, I, Any_Type);
6433 if It = No_Interp then
6434 Error_Msg_N ("ambiguous prefix for slicing", N);
6439 Array_Type := It.Typ;
6444 Array_Type := It.Typ;
6449 Get_Next_Interp (I, It);
6454 Array_Type := Etype (Name);
6457 Resolve (Name, Array_Type);
6459 if Is_Access_Type (Array_Type) then
6460 Apply_Access_Check (N);
6461 Array_Type := Designated_Type (Array_Type);
6463 -- If the prefix is an access to an unconstrained array, we must use
6464 -- the actual subtype of the object to perform the index checks. The
6465 -- object denoted by the prefix is implicit in the node, so we build
6466 -- an explicit representation for it in order to compute the actual
6469 if not Is_Constrained (Array_Type) then
6470 Remove_Side_Effects (Prefix (N));
6473 Obj : constant Node_Id :=
6474 Make_Explicit_Dereference (Sloc (N),
6475 Prefix => New_Copy_Tree (Prefix (N)));
6477 Set_Etype (Obj, Array_Type);
6478 Set_Parent (Obj, Parent (N));
6479 Array_Type := Get_Actual_Subtype (Obj);
6483 elsif Is_Entity_Name (Name)
6484 or else (Nkind (Name) = N_Function_Call
6485 and then not Is_Constrained (Etype (Name)))
6487 Array_Type := Get_Actual_Subtype (Name);
6490 -- If name was overloaded, set slice type correctly now
6492 Set_Etype (N, Array_Type);
6494 -- If the range is specified by a subtype mark, no resolution is
6495 -- necessary. Else resolve the bounds, and apply needed checks.
6497 if not Is_Entity_Name (Drange) then
6498 Index := First_Index (Array_Type);
6499 Resolve (Drange, Base_Type (Etype (Index)));
6501 if Nkind (Drange) = N_Range then
6502 Apply_Range_Check (Drange, Etype (Index));
6506 Set_Slice_Subtype (N);
6508 if Nkind (Drange) = N_Range then
6509 Warn_On_Suspicious_Index (Name, Low_Bound (Drange));
6510 Warn_On_Suspicious_Index (Name, High_Bound (Drange));
6516 ----------------------------
6517 -- Resolve_String_Literal --
6518 ----------------------------
6520 procedure Resolve_String_Literal (N : Node_Id; Typ : Entity_Id) is
6521 C_Typ : constant Entity_Id := Component_Type (Typ);
6522 R_Typ : constant Entity_Id := Root_Type (C_Typ);
6523 Loc : constant Source_Ptr := Sloc (N);
6524 Str : constant String_Id := Strval (N);
6525 Strlen : constant Nat := String_Length (Str);
6526 Subtype_Id : Entity_Id;
6527 Need_Check : Boolean;
6530 -- For a string appearing in a concatenation, defer creation of the
6531 -- string_literal_subtype until the end of the resolution of the
6532 -- concatenation, because the literal may be constant-folded away. This
6533 -- is a useful optimization for long concatenation expressions.
6535 -- If the string is an aggregate built for a single character (which
6536 -- happens in a non-static context) or a is null string to which special
6537 -- checks may apply, we build the subtype. Wide strings must also get a
6538 -- string subtype if they come from a one character aggregate. Strings
6539 -- generated by attributes might be static, but it is often hard to
6540 -- determine whether the enclosing context is static, so we generate
6541 -- subtypes for them as well, thus losing some rarer optimizations ???
6542 -- Same for strings that come from a static conversion.
6545 (Strlen = 0 and then Typ /= Standard_String)
6546 or else Nkind (Parent (N)) /= N_Op_Concat
6547 or else (N /= Left_Opnd (Parent (N))
6548 and then N /= Right_Opnd (Parent (N)))
6549 or else ((Typ = Standard_Wide_String
6550 or else Typ = Standard_Wide_Wide_String)
6551 and then Nkind (Original_Node (N)) /= N_String_Literal);
6553 -- If the resolving type is itself a string literal subtype, we
6554 -- can just reuse it, since there is no point in creating another.
6556 if Ekind (Typ) = E_String_Literal_Subtype then
6559 elsif Nkind (Parent (N)) = N_Op_Concat
6560 and then not Need_Check
6561 and then Nkind (Original_Node (N)) /= N_Character_Literal
6562 and then Nkind (Original_Node (N)) /= N_Attribute_Reference
6563 and then Nkind (Original_Node (N)) /= N_Qualified_Expression
6564 and then Nkind (Original_Node (N)) /= N_Type_Conversion
6568 -- Otherwise we must create a string literal subtype. Note that the
6569 -- whole idea of string literal subtypes is simply to avoid the need
6570 -- for building a full fledged array subtype for each literal.
6572 Set_String_Literal_Subtype (N, Typ);
6573 Subtype_Id := Etype (N);
6576 if Nkind (Parent (N)) /= N_Op_Concat
6579 Set_Etype (N, Subtype_Id);
6580 Eval_String_Literal (N);
6583 if Is_Limited_Composite (Typ)
6584 or else Is_Private_Composite (Typ)
6586 Error_Msg_N ("string literal not available for private array", N);
6587 Set_Etype (N, Any_Type);
6591 -- The validity of a null string has been checked in the
6592 -- call to Eval_String_Literal.
6597 -- Always accept string literal with component type Any_Character, which
6598 -- occurs in error situations and in comparisons of literals, both of
6599 -- which should accept all literals.
6601 elsif R_Typ = Any_Character then
6604 -- If the type is bit-packed, then we always tranform the string literal
6605 -- into a full fledged aggregate.
6607 elsif Is_Bit_Packed_Array (Typ) then
6610 -- Deal with cases of Wide_Wide_String, Wide_String, and String
6613 -- For Standard.Wide_Wide_String, or any other type whose component
6614 -- type is Standard.Wide_Wide_Character, we know that all the
6615 -- characters in the string must be acceptable, since the parser
6616 -- accepted the characters as valid character literals.
6618 if R_Typ = Standard_Wide_Wide_Character then
6621 -- For the case of Standard.String, or any other type whose component
6622 -- type is Standard.Character, we must make sure that there are no
6623 -- wide characters in the string, i.e. that it is entirely composed
6624 -- of characters in range of type Character.
6626 -- If the string literal is the result of a static concatenation, the
6627 -- test has already been performed on the components, and need not be
6630 elsif R_Typ = Standard_Character
6631 and then Nkind (Original_Node (N)) /= N_Op_Concat
6633 for J in 1 .. Strlen loop
6634 if not In_Character_Range (Get_String_Char (Str, J)) then
6636 -- If we are out of range, post error. This is one of the
6637 -- very few places that we place the flag in the middle of
6638 -- a token, right under the offending wide character.
6641 ("literal out of range of type Standard.Character",
6642 Source_Ptr (Int (Loc) + J));
6647 -- For the case of Standard.Wide_String, or any other type whose
6648 -- component type is Standard.Wide_Character, we must make sure that
6649 -- there are no wide characters in the string, i.e. that it is
6650 -- entirely composed of characters in range of type Wide_Character.
6652 -- If the string literal is the result of a static concatenation,
6653 -- the test has already been performed on the components, and need
6656 elsif R_Typ = Standard_Wide_Character
6657 and then Nkind (Original_Node (N)) /= N_Op_Concat
6659 for J in 1 .. Strlen loop
6660 if not In_Wide_Character_Range (Get_String_Char (Str, J)) then
6662 -- If we are out of range, post error. This is one of the
6663 -- very few places that we place the flag in the middle of
6664 -- a token, right under the offending wide character.
6666 -- This is not quite right, because characters in general
6667 -- will take more than one character position ???
6670 ("literal out of range of type Standard.Wide_Character",
6671 Source_Ptr (Int (Loc) + J));
6676 -- If the root type is not a standard character, then we will convert
6677 -- the string into an aggregate and will let the aggregate code do
6678 -- the checking. Standard Wide_Wide_Character is also OK here.
6684 -- See if the component type of the array corresponding to the string
6685 -- has compile time known bounds. If yes we can directly check
6686 -- whether the evaluation of the string will raise constraint error.
6687 -- Otherwise we need to transform the string literal into the
6688 -- corresponding character aggregate and let the aggregate
6689 -- code do the checking.
6691 if R_Typ = Standard_Character
6692 or else R_Typ = Standard_Wide_Character
6693 or else R_Typ = Standard_Wide_Wide_Character
6695 -- Check for the case of full range, where we are definitely OK
6697 if Component_Type (Typ) = Base_Type (Component_Type (Typ)) then
6701 -- Here the range is not the complete base type range, so check
6704 Comp_Typ_Lo : constant Node_Id :=
6705 Type_Low_Bound (Component_Type (Typ));
6706 Comp_Typ_Hi : constant Node_Id :=
6707 Type_High_Bound (Component_Type (Typ));
6712 if Compile_Time_Known_Value (Comp_Typ_Lo)
6713 and then Compile_Time_Known_Value (Comp_Typ_Hi)
6715 for J in 1 .. Strlen loop
6716 Char_Val := UI_From_Int (Int (Get_String_Char (Str, J)));
6718 if Char_Val < Expr_Value (Comp_Typ_Lo)
6719 or else Char_Val > Expr_Value (Comp_Typ_Hi)
6721 Apply_Compile_Time_Constraint_Error
6722 (N, "character out of range?", CE_Range_Check_Failed,
6723 Loc => Source_Ptr (Int (Loc) + J));
6733 -- If we got here we meed to transform the string literal into the
6734 -- equivalent qualified positional array aggregate. This is rather
6735 -- heavy artillery for this situation, but it is hard work to avoid.
6738 Lits : constant List_Id := New_List;
6739 P : Source_Ptr := Loc + 1;
6743 -- Build the character literals, we give them source locations that
6744 -- correspond to the string positions, which is a bit tricky given
6745 -- the possible presence of wide character escape sequences.
6747 for J in 1 .. Strlen loop
6748 C := Get_String_Char (Str, J);
6749 Set_Character_Literal_Name (C);
6752 Make_Character_Literal (P,
6754 Char_Literal_Value => UI_From_CC (C)));
6756 if In_Character_Range (C) then
6759 -- Should we have a call to Skip_Wide here ???
6767 Make_Qualified_Expression (Loc,
6768 Subtype_Mark => New_Reference_To (Typ, Loc),
6770 Make_Aggregate (Loc, Expressions => Lits)));
6772 Analyze_And_Resolve (N, Typ);
6774 end Resolve_String_Literal;
6776 -----------------------------
6777 -- Resolve_Subprogram_Info --
6778 -----------------------------
6780 procedure Resolve_Subprogram_Info (N : Node_Id; Typ : Entity_Id) is
6783 end Resolve_Subprogram_Info;
6785 -----------------------------
6786 -- Resolve_Type_Conversion --
6787 -----------------------------
6789 procedure Resolve_Type_Conversion (N : Node_Id; Typ : Entity_Id) is
6790 Conv_OK : constant Boolean := Conversion_OK (N);
6791 Target_Type : Entity_Id := Etype (N);
6793 Opnd_Type : Entity_Id;
6799 Operand := Expression (N);
6802 and then not Valid_Conversion (N, Target_Type, Operand)
6807 if Etype (Operand) = Any_Fixed then
6809 -- Mixed-mode operation involving a literal. Context must be a fixed
6810 -- type which is applied to the literal subsequently.
6812 if Is_Fixed_Point_Type (Typ) then
6813 Set_Etype (Operand, Universal_Real);
6815 elsif Is_Numeric_Type (Typ)
6816 and then (Nkind (Operand) = N_Op_Multiply
6817 or else Nkind (Operand) = N_Op_Divide)
6818 and then (Etype (Right_Opnd (Operand)) = Universal_Real
6819 or else Etype (Left_Opnd (Operand)) = Universal_Real)
6821 -- Return if expression is ambiguous
6823 if Unique_Fixed_Point_Type (N) = Any_Type then
6826 -- If nothing else, the available fixed type is Duration
6829 Set_Etype (Operand, Standard_Duration);
6832 -- Resolve the real operand with largest available precision
6834 if Etype (Right_Opnd (Operand)) = Universal_Real then
6835 Rop := New_Copy_Tree (Right_Opnd (Operand));
6837 Rop := New_Copy_Tree (Left_Opnd (Operand));
6840 Resolve (Rop, Universal_Real);
6842 -- If the operand is a literal (it could be a non-static and
6843 -- illegal exponentiation) check whether the use of Duration
6844 -- is potentially inaccurate.
6846 if Nkind (Rop) = N_Real_Literal
6847 and then Realval (Rop) /= Ureal_0
6848 and then abs (Realval (Rop)) < Delta_Value (Standard_Duration)
6851 ("universal real operand can only " &
6852 "be interpreted as Duration?",
6855 ("\precision will be lost in the conversion", Rop);
6858 elsif Is_Numeric_Type (Typ)
6859 and then Nkind (Operand) in N_Op
6860 and then Unique_Fixed_Point_Type (N) /= Any_Type
6862 Set_Etype (Operand, Standard_Duration);
6865 Error_Msg_N ("invalid context for mixed mode operation", N);
6866 Set_Etype (Operand, Any_Type);
6871 Opnd_Type := Etype (Operand);
6874 -- Note: we do the Eval_Type_Conversion call before applying the
6875 -- required checks for a subtype conversion. This is important,
6876 -- since both are prepared under certain circumstances to change
6877 -- the type conversion to a constraint error node, but in the case
6878 -- of Eval_Type_Conversion this may reflect an illegality in the
6879 -- static case, and we would miss the illegality (getting only a
6880 -- warning message), if we applied the type conversion checks first.
6882 Eval_Type_Conversion (N);
6884 -- If after evaluation, we still have a type conversion, then we
6885 -- may need to apply checks required for a subtype conversion.
6887 -- Skip these type conversion checks if universal fixed operands
6888 -- operands involved, since range checks are handled separately for
6889 -- these cases (in the appropriate Expand routines in unit Exp_Fixd).
6891 if Nkind (N) = N_Type_Conversion
6892 and then not Is_Generic_Type (Root_Type (Target_Type))
6893 and then Target_Type /= Universal_Fixed
6894 and then Opnd_Type /= Universal_Fixed
6896 Apply_Type_Conversion_Checks (N);
6899 -- Issue warning for conversion of simple object to its own type
6900 -- We have to test the original nodes, since they may have been
6901 -- rewritten by various optimizations.
6903 Orig_N := Original_Node (N);
6905 if Warn_On_Redundant_Constructs
6906 and then Comes_From_Source (Orig_N)
6907 and then Nkind (Orig_N) = N_Type_Conversion
6908 and then not In_Instance
6910 Orig_N := Original_Node (Expression (Orig_N));
6911 Orig_T := Target_Type;
6913 -- If the node is part of a larger expression, the Target_Type
6914 -- may not be the original type of the node if the context is a
6915 -- condition. Recover original type to see if conversion is needed.
6917 if Is_Boolean_Type (Orig_T)
6918 and then Nkind (Parent (N)) in N_Op
6920 Orig_T := Etype (Parent (N));
6923 if Is_Entity_Name (Orig_N)
6924 and then Etype (Entity (Orig_N)) = Orig_T
6927 ("?useless conversion, & has this type", N, Entity (Orig_N));
6931 -- Ada 2005 (AI-251): Handle conversions to abstract interface types
6933 if Ada_Version >= Ada_05 and then Expander_Active then
6934 if Is_Access_Type (Target_Type) then
6935 Target_Type := Directly_Designated_Type (Target_Type);
6938 if Is_Class_Wide_Type (Target_Type) then
6939 Target_Type := Etype (Target_Type);
6942 if Is_Interface (Target_Type) then
6943 if Is_Access_Type (Opnd_Type) then
6944 Opnd_Type := Directly_Designated_Type (Opnd_Type);
6947 if Is_Class_Wide_Type (Opnd_Type) then
6948 Opnd_Type := Etype (Opnd_Type);
6953 if Ekind (Opnd_Type) = E_Protected_Subtype
6954 or else Ekind (Opnd_Type) = E_Task_Subtype
6956 Opnd_Type := Etype (Opnd_Type);
6959 if not Interface_Present_In_Ancestor
6961 Iface => Target_Type)
6963 -- The static analysis is not enough to know if the interface
6964 -- is implemented or not. Hence we must pass the work to the
6965 -- expander to generate the required code to evaluate the
6966 -- conversion at run-time.
6968 Expand_Interface_Conversion (N, Is_Static => False);
6971 Expand_Interface_Conversion (N);
6974 -- Ada 2005 (AI-251): Conversion from a class-wide interface to a
6977 elsif Is_Class_Wide_Type (Opnd_Type)
6978 and then Is_Interface (Opnd_Type)
6980 Expand_Interface_Conversion (N, Is_Static => False);
6983 end Resolve_Type_Conversion;
6985 ----------------------
6986 -- Resolve_Unary_Op --
6987 ----------------------
6989 procedure Resolve_Unary_Op (N : Node_Id; Typ : Entity_Id) is
6990 B_Typ : constant Entity_Id := Base_Type (Typ);
6991 R : constant Node_Id := Right_Opnd (N);
6997 -- Generate warning for expressions like -5 mod 3
6999 if Warn_On_Questionable_Missing_Parens
7000 and then Paren_Count (N) = 0
7001 and then (Nkind (N) = N_Op_Minus or else Nkind (N) = N_Op_Plus)
7002 and then Paren_Count (Right_Opnd (N)) = 0
7003 and then Nkind (Right_Opnd (N)) in N_Multiplying_Operator
7004 and then Comes_From_Source (N)
7007 ("?unary minus expression should be parenthesized here", N);
7010 if Comes_From_Source (N)
7011 and then Ekind (Entity (N)) = E_Function
7012 and then Is_Imported (Entity (N))
7013 and then Is_Intrinsic_Subprogram (Entity (N))
7015 Resolve_Intrinsic_Unary_Operator (N, Typ);
7019 if Etype (R) = Universal_Integer
7020 or else Etype (R) = Universal_Real
7022 Check_For_Visible_Operator (N, B_Typ);
7025 Set_Etype (N, B_Typ);
7028 -- Generate warning for expressions like abs (x mod 2)
7030 if Warn_On_Redundant_Constructs
7031 and then Nkind (N) = N_Op_Abs
7033 Determine_Range (Right_Opnd (N), OK, Lo, Hi);
7035 if OK and then Hi >= Lo and then Lo >= 0 then
7037 ("?abs applied to known non-negative value has no effect", N);
7041 Check_Unset_Reference (R);
7042 Generate_Operator_Reference (N, B_Typ);
7045 -- Set overflow checking bit. Much cleverer code needed here eventually
7046 -- and perhaps the Resolve routines should be separated for the various
7047 -- arithmetic operations, since they will need different processing ???
7049 if Nkind (N) in N_Op then
7050 if not Overflow_Checks_Suppressed (Etype (N)) then
7051 Enable_Overflow_Check (N);
7054 end Resolve_Unary_Op;
7056 ----------------------------------
7057 -- Resolve_Unchecked_Expression --
7058 ----------------------------------
7060 procedure Resolve_Unchecked_Expression
7065 Resolve (Expression (N), Typ, Suppress => All_Checks);
7067 end Resolve_Unchecked_Expression;
7069 ---------------------------------------
7070 -- Resolve_Unchecked_Type_Conversion --
7071 ---------------------------------------
7073 procedure Resolve_Unchecked_Type_Conversion
7077 pragma Warnings (Off, Typ);
7079 Operand : constant Node_Id := Expression (N);
7080 Opnd_Type : constant Entity_Id := Etype (Operand);
7083 -- Resolve operand using its own type
7085 Resolve (Operand, Opnd_Type);
7086 Eval_Unchecked_Conversion (N);
7088 end Resolve_Unchecked_Type_Conversion;
7090 ------------------------------
7091 -- Rewrite_Operator_As_Call --
7092 ------------------------------
7094 procedure Rewrite_Operator_As_Call (N : Node_Id; Nam : Entity_Id) is
7095 Loc : constant Source_Ptr := Sloc (N);
7096 Actuals : constant List_Id := New_List;
7100 if Nkind (N) in N_Binary_Op then
7101 Append (Left_Opnd (N), Actuals);
7104 Append (Right_Opnd (N), Actuals);
7107 Make_Function_Call (Sloc => Loc,
7108 Name => New_Occurrence_Of (Nam, Loc),
7109 Parameter_Associations => Actuals);
7111 Preserve_Comes_From_Source (New_N, N);
7112 Preserve_Comes_From_Source (Name (New_N), N);
7114 Set_Etype (N, Etype (Nam));
7115 end Rewrite_Operator_As_Call;
7117 ------------------------------
7118 -- Rewrite_Renamed_Operator --
7119 ------------------------------
7121 procedure Rewrite_Renamed_Operator
7126 Nam : constant Name_Id := Chars (Op);
7127 Is_Binary : constant Boolean := Nkind (N) in N_Binary_Op;
7131 -- Rewrite the operator node using the real operator, not its
7132 -- renaming. Exclude user-defined intrinsic operations of the same
7133 -- name, which are treated separately and rewritten as calls.
7135 if Ekind (Op) /= E_Function
7136 or else Chars (N) /= Nam
7138 Op_Node := New_Node (Operator_Kind (Nam, Is_Binary), Sloc (N));
7139 Set_Chars (Op_Node, Nam);
7140 Set_Etype (Op_Node, Etype (N));
7141 Set_Entity (Op_Node, Op);
7142 Set_Right_Opnd (Op_Node, Right_Opnd (N));
7144 -- Indicate that both the original entity and its renaming
7145 -- are referenced at this point.
7147 Generate_Reference (Entity (N), N);
7148 Generate_Reference (Op, N);
7151 Set_Left_Opnd (Op_Node, Left_Opnd (N));
7154 Rewrite (N, Op_Node);
7156 -- If the context type is private, add the appropriate conversions
7157 -- so that the operator is applied to the full view. This is done
7158 -- in the routines that resolve intrinsic operators,
7160 if Is_Intrinsic_Subprogram (Op)
7161 and then Is_Private_Type (Typ)
7164 when N_Op_Add | N_Op_Subtract | N_Op_Multiply | N_Op_Divide |
7165 N_Op_Expon | N_Op_Mod | N_Op_Rem =>
7166 Resolve_Intrinsic_Operator (N, Typ);
7168 when N_Op_Plus | N_Op_Minus | N_Op_Abs =>
7169 Resolve_Intrinsic_Unary_Operator (N, Typ);
7176 elsif Ekind (Op) = E_Function
7177 and then Is_Intrinsic_Subprogram (Op)
7179 -- Operator renames a user-defined operator of the same name. Use
7180 -- the original operator in the node, which is the one that gigi
7184 Set_Is_Overloaded (N, False);
7186 end Rewrite_Renamed_Operator;
7188 -----------------------
7189 -- Set_Slice_Subtype --
7190 -----------------------
7192 -- Build an implicit subtype declaration to represent the type delivered
7193 -- by the slice. This is an abbreviated version of an array subtype. We
7194 -- define an index subtype for the slice, using either the subtype name
7195 -- or the discrete range of the slice. To be consistent with index usage
7196 -- elsewhere, we create a list header to hold the single index. This list
7197 -- is not otherwise attached to the syntax tree.
7199 procedure Set_Slice_Subtype (N : Node_Id) is
7200 Loc : constant Source_Ptr := Sloc (N);
7201 Index_List : constant List_Id := New_List;
7203 Index_Subtype : Entity_Id;
7204 Index_Type : Entity_Id;
7205 Slice_Subtype : Entity_Id;
7206 Drange : constant Node_Id := Discrete_Range (N);
7209 if Is_Entity_Name (Drange) then
7210 Index_Subtype := Entity (Drange);
7213 -- We force the evaluation of a range. This is definitely needed in
7214 -- the renamed case, and seems safer to do unconditionally. Note in
7215 -- any case that since we will create and insert an Itype referring
7216 -- to this range, we must make sure any side effect removal actions
7217 -- are inserted before the Itype definition.
7219 if Nkind (Drange) = N_Range then
7220 Force_Evaluation (Low_Bound (Drange));
7221 Force_Evaluation (High_Bound (Drange));
7224 Index_Type := Base_Type (Etype (Drange));
7226 Index_Subtype := Create_Itype (Subtype_Kind (Ekind (Index_Type)), N);
7228 Set_Scalar_Range (Index_Subtype, Drange);
7229 Set_Etype (Index_Subtype, Index_Type);
7230 Set_Size_Info (Index_Subtype, Index_Type);
7231 Set_RM_Size (Index_Subtype, RM_Size (Index_Type));
7234 Slice_Subtype := Create_Itype (E_Array_Subtype, N);
7236 Index := New_Occurrence_Of (Index_Subtype, Loc);
7237 Set_Etype (Index, Index_Subtype);
7238 Append (Index, Index_List);
7240 Set_First_Index (Slice_Subtype, Index);
7241 Set_Etype (Slice_Subtype, Base_Type (Etype (N)));
7242 Set_Is_Constrained (Slice_Subtype, True);
7243 Init_Size_Align (Slice_Subtype);
7245 Check_Compile_Time_Size (Slice_Subtype);
7247 -- The Etype of the existing Slice node is reset to this slice
7248 -- subtype. Its bounds are obtained from its first index.
7250 Set_Etype (N, Slice_Subtype);
7252 -- In the packed case, this must be immediately frozen
7254 -- Couldn't we always freeze here??? and if we did, then the above
7255 -- call to Check_Compile_Time_Size could be eliminated, which would
7256 -- be nice, because then that routine could be made private to Freeze.
7258 if Is_Packed (Slice_Subtype) and not In_Default_Expression then
7259 Freeze_Itype (Slice_Subtype, N);
7262 end Set_Slice_Subtype;
7264 --------------------------------
7265 -- Set_String_Literal_Subtype --
7266 --------------------------------
7268 procedure Set_String_Literal_Subtype (N : Node_Id; Typ : Entity_Id) is
7269 Loc : constant Source_Ptr := Sloc (N);
7270 Low_Bound : constant Node_Id :=
7271 Type_Low_Bound (Etype (First_Index (Typ)));
7272 Subtype_Id : Entity_Id;
7275 if Nkind (N) /= N_String_Literal then
7279 Subtype_Id := Create_Itype (E_String_Literal_Subtype, N);
7280 Set_String_Literal_Length (Subtype_Id, UI_From_Int
7281 (String_Length (Strval (N))));
7282 Set_Etype (Subtype_Id, Base_Type (Typ));
7283 Set_Is_Constrained (Subtype_Id);
7284 Set_Etype (N, Subtype_Id);
7286 if Is_OK_Static_Expression (Low_Bound) then
7288 -- The low bound is set from the low bound of the corresponding
7289 -- index type. Note that we do not store the high bound in the
7290 -- string literal subtype, but it can be deduced if necessary
7291 -- from the length and the low bound.
7293 Set_String_Literal_Low_Bound (Subtype_Id, Low_Bound);
7296 Set_String_Literal_Low_Bound
7297 (Subtype_Id, Make_Integer_Literal (Loc, 1));
7298 Set_Etype (String_Literal_Low_Bound (Subtype_Id), Standard_Positive);
7300 -- Build bona fide subtypes for the string, and wrap it in an
7301 -- unchecked conversion, because the backend expects the
7302 -- String_Literal_Subtype to have a static lower bound.
7305 Index_List : constant List_Id := New_List;
7306 Index_Type : constant Entity_Id := Etype (First_Index (Typ));
7307 High_Bound : constant Node_Id :=
7309 Left_Opnd => New_Copy_Tree (Low_Bound),
7311 Make_Integer_Literal (Loc,
7312 String_Length (Strval (N)) - 1));
7313 Array_Subtype : Entity_Id;
7314 Index_Subtype : Entity_Id;
7320 Create_Itype (Subtype_Kind (Ekind (Index_Type)), N);
7321 Drange := Make_Range (Loc, Low_Bound, High_Bound);
7322 Set_Scalar_Range (Index_Subtype, Drange);
7323 Set_Parent (Drange, N);
7324 Analyze_And_Resolve (Drange, Index_Type);
7326 Set_Etype (Index_Subtype, Index_Type);
7327 Set_Size_Info (Index_Subtype, Index_Type);
7328 Set_RM_Size (Index_Subtype, RM_Size (Index_Type));
7330 Array_Subtype := Create_Itype (E_Array_Subtype, N);
7332 Index := New_Occurrence_Of (Index_Subtype, Loc);
7333 Set_Etype (Index, Index_Subtype);
7334 Append (Index, Index_List);
7336 Set_First_Index (Array_Subtype, Index);
7337 Set_Etype (Array_Subtype, Base_Type (Typ));
7338 Set_Is_Constrained (Array_Subtype, True);
7339 Init_Size_Align (Array_Subtype);
7342 Make_Unchecked_Type_Conversion (Loc,
7343 Subtype_Mark => New_Occurrence_Of (Array_Subtype, Loc),
7344 Expression => Relocate_Node (N)));
7345 Set_Etype (N, Array_Subtype);
7348 end Set_String_Literal_Subtype;
7350 -----------------------------
7351 -- Unique_Fixed_Point_Type --
7352 -----------------------------
7354 function Unique_Fixed_Point_Type (N : Node_Id) return Entity_Id is
7355 T1 : Entity_Id := Empty;
7360 procedure Fixed_Point_Error;
7361 -- If true ambiguity, give details
7363 -----------------------
7364 -- Fixed_Point_Error --
7365 -----------------------
7367 procedure Fixed_Point_Error is
7369 Error_Msg_N ("ambiguous universal_fixed_expression", N);
7370 Error_Msg_NE ("\\possible interpretation as}", N, T1);
7371 Error_Msg_NE ("\\possible interpretation as}", N, T2);
7372 end Fixed_Point_Error;
7374 -- Start of processing for Unique_Fixed_Point_Type
7377 -- The operations on Duration are visible, so Duration is always a
7378 -- possible interpretation.
7380 T1 := Standard_Duration;
7382 -- Look for fixed-point types in enclosing scopes
7384 Scop := Current_Scope;
7385 while Scop /= Standard_Standard loop
7386 T2 := First_Entity (Scop);
7387 while Present (T2) loop
7388 if Is_Fixed_Point_Type (T2)
7389 and then Current_Entity (T2) = T2
7390 and then Scope (Base_Type (T2)) = Scop
7392 if Present (T1) then
7403 Scop := Scope (Scop);
7406 -- Look for visible fixed type declarations in the context
7408 Item := First (Context_Items (Cunit (Current_Sem_Unit)));
7409 while Present (Item) loop
7410 if Nkind (Item) = N_With_Clause then
7411 Scop := Entity (Name (Item));
7412 T2 := First_Entity (Scop);
7413 while Present (T2) loop
7414 if Is_Fixed_Point_Type (T2)
7415 and then Scope (Base_Type (T2)) = Scop
7416 and then (Is_Potentially_Use_Visible (T2)
7417 or else In_Use (T2))
7419 if Present (T1) then
7434 if Nkind (N) = N_Real_Literal then
7435 Error_Msg_NE ("real literal interpreted as }?", N, T1);
7438 Error_Msg_NE ("universal_fixed expression interpreted as }?", N, T1);
7442 end Unique_Fixed_Point_Type;
7444 ----------------------
7445 -- Valid_Conversion --
7446 ----------------------
7448 function Valid_Conversion
7451 Operand : Node_Id) return Boolean
7453 Target_Type : constant Entity_Id := Base_Type (Target);
7454 Opnd_Type : Entity_Id := Etype (Operand);
7456 function Conversion_Check
7458 Msg : String) return Boolean;
7459 -- Little routine to post Msg if Valid is False, returns Valid value
7461 function Valid_Tagged_Conversion
7462 (Target_Type : Entity_Id;
7463 Opnd_Type : Entity_Id) return Boolean;
7464 -- Specifically test for validity of tagged conversions
7466 function Valid_Array_Conversion return Boolean;
7467 -- Check index and component conformance, and accessibility levels
7468 -- if the component types are anonymous access types (Ada 2005)
7470 ----------------------
7471 -- Conversion_Check --
7472 ----------------------
7474 function Conversion_Check
7476 Msg : String) return Boolean
7480 Error_Msg_N (Msg, Operand);
7484 end Conversion_Check;
7486 ----------------------------
7487 -- Valid_Array_Conversion --
7488 ----------------------------
7490 function Valid_Array_Conversion return Boolean
7492 Opnd_Comp_Type : constant Entity_Id := Component_Type (Opnd_Type);
7493 Opnd_Comp_Base : constant Entity_Id := Base_Type (Opnd_Comp_Type);
7495 Opnd_Index : Node_Id;
7496 Opnd_Index_Type : Entity_Id;
7498 Target_Comp_Type : constant Entity_Id :=
7499 Component_Type (Target_Type);
7500 Target_Comp_Base : constant Entity_Id :=
7501 Base_Type (Target_Comp_Type);
7503 Target_Index : Node_Id;
7504 Target_Index_Type : Entity_Id;
7507 -- Error if wrong number of dimensions
7510 Number_Dimensions (Target_Type) /= Number_Dimensions (Opnd_Type)
7513 ("incompatible number of dimensions for conversion", Operand);
7516 -- Number of dimensions matches
7519 -- Loop through indexes of the two arrays
7521 Target_Index := First_Index (Target_Type);
7522 Opnd_Index := First_Index (Opnd_Type);
7523 while Present (Target_Index) and then Present (Opnd_Index) loop
7524 Target_Index_Type := Etype (Target_Index);
7525 Opnd_Index_Type := Etype (Opnd_Index);
7527 -- Error if index types are incompatible
7529 if not (Is_Integer_Type (Target_Index_Type)
7530 and then Is_Integer_Type (Opnd_Index_Type))
7531 and then (Root_Type (Target_Index_Type)
7532 /= Root_Type (Opnd_Index_Type))
7535 ("incompatible index types for array conversion",
7540 Next_Index (Target_Index);
7541 Next_Index (Opnd_Index);
7544 -- If component types have same base type, all set
7546 if Target_Comp_Base = Opnd_Comp_Base then
7549 -- Here if base types of components are not the same. The only
7550 -- time this is allowed is if we have anonymous access types.
7552 -- The conversion of arrays of anonymous access types can lead
7553 -- to dangling pointers. AI-392 formalizes the accessibility
7554 -- checks that must be applied to such conversions to prevent
7555 -- out-of-scope references.
7558 (Ekind (Target_Comp_Base) = E_Anonymous_Access_Type
7560 Ekind (Target_Comp_Base) = E_Anonymous_Access_Subprogram_Type)
7561 and then Ekind (Opnd_Comp_Base) = Ekind (Target_Comp_Base)
7563 Subtypes_Statically_Match (Target_Comp_Type, Opnd_Comp_Type)
7565 if Type_Access_Level (Target_Type) <
7566 Type_Access_Level (Opnd_Type)
7568 if In_Instance_Body then
7569 Error_Msg_N ("?source array type " &
7570 "has deeper accessibility level than target", Operand);
7571 Error_Msg_N ("\?Program_Error will be raised at run time",
7574 Make_Raise_Program_Error (Sloc (N),
7575 Reason => PE_Accessibility_Check_Failed));
7576 Set_Etype (N, Target_Type);
7579 -- Conversion not allowed because of accessibility levels
7582 Error_Msg_N ("source array type " &
7583 "has deeper accessibility level than target", Operand);
7590 -- All other cases where component base types do not match
7594 ("incompatible component types for array conversion",
7599 -- Check that component subtypes statically match
7601 if Is_Constrained (Target_Comp_Type) /=
7602 Is_Constrained (Opnd_Comp_Type)
7603 or else not Subtypes_Statically_Match
7604 (Target_Comp_Type, Opnd_Comp_Type)
7607 ("component subtypes must statically match", Operand);
7613 end Valid_Array_Conversion;
7615 -----------------------------
7616 -- Valid_Tagged_Conversion --
7617 -----------------------------
7619 function Valid_Tagged_Conversion
7620 (Target_Type : Entity_Id;
7621 Opnd_Type : Entity_Id) return Boolean
7624 -- Upward conversions are allowed (RM 4.6(22))
7626 if Covers (Target_Type, Opnd_Type)
7627 or else Is_Ancestor (Target_Type, Opnd_Type)
7631 -- Downward conversion are allowed if the operand is class-wide
7634 elsif Is_Class_Wide_Type (Opnd_Type)
7635 and then Covers (Opnd_Type, Target_Type)
7639 elsif Covers (Opnd_Type, Target_Type)
7640 or else Is_Ancestor (Opnd_Type, Target_Type)
7643 Conversion_Check (False,
7644 "downward conversion of tagged objects not allowed");
7646 -- Ada 2005 (AI-251): The conversion of a tagged type to an
7647 -- abstract interface type is always valid
7649 elsif Is_Interface (Target_Type) then
7652 elsif Is_Access_Type (Opnd_Type)
7653 and then Is_Interface (Directly_Designated_Type (Opnd_Type))
7659 ("invalid tagged conversion, not compatible with}",
7660 N, First_Subtype (Opnd_Type));
7663 end Valid_Tagged_Conversion;
7665 -- Start of processing for Valid_Conversion
7668 Check_Parameterless_Call (Operand);
7670 if Is_Overloaded (Operand) then
7679 -- Remove procedure calls, which syntactically cannot appear
7680 -- in this context, but which cannot be removed by type checking,
7681 -- because the context does not impose a type.
7683 -- When compiling for VMS, spurious ambiguities can be produced
7684 -- when arithmetic operations have a literal operand and return
7685 -- System.Address or a descendant of it. These ambiguities are
7686 -- otherwise resolved by the context, but for conversions there
7687 -- is no context type and the removal of the spurious operations
7688 -- must be done explicitly here.
7690 -- The node may be labelled overloaded, but still contain only
7691 -- one interpretation because others were discarded in previous
7692 -- filters. If this is the case, retain the single interpretation
7695 Get_First_Interp (Operand, I, It);
7696 Opnd_Type := It.Typ;
7697 Get_Next_Interp (I, It);
7700 and then Opnd_Type /= Standard_Void_Type
7702 -- More than one candidate interpretation is available
7704 Get_First_Interp (Operand, I, It);
7705 while Present (It.Typ) loop
7706 if It.Typ = Standard_Void_Type then
7710 if Present (System_Aux_Id)
7711 and then Is_Descendent_Of_Address (It.Typ)
7716 Get_Next_Interp (I, It);
7720 Get_First_Interp (Operand, I, It);
7725 Error_Msg_N ("illegal operand in conversion", Operand);
7729 Get_Next_Interp (I, It);
7731 if Present (It.Typ) then
7733 It1 := Disambiguate (Operand, I1, I, Any_Type);
7735 if It1 = No_Interp then
7736 Error_Msg_N ("ambiguous operand in conversion", Operand);
7738 Error_Msg_Sloc := Sloc (It.Nam);
7739 Error_Msg_N ("\\possible interpretation#!", Operand);
7741 Error_Msg_Sloc := Sloc (N1);
7742 Error_Msg_N ("\\possible interpretation#!", Operand);
7748 Set_Etype (Operand, It1.Typ);
7749 Opnd_Type := It1.Typ;
7755 if Is_Numeric_Type (Target_Type) then
7757 -- A universal fixed expression can be converted to any numeric type
7759 if Opnd_Type = Universal_Fixed then
7762 -- Also no need to check when in an instance or inlined body, because
7763 -- the legality has been established when the template was analyzed.
7764 -- Furthermore, numeric conversions may occur where only a private
7765 -- view of the operand type is visible at the instanciation point.
7766 -- This results in a spurious error if we check that the operand type
7767 -- is a numeric type.
7769 -- Note: in a previous version of this unit, the following tests were
7770 -- applied only for generated code (Comes_From_Source set to False),
7771 -- but in fact the test is required for source code as well, since
7772 -- this situation can arise in source code.
7774 elsif In_Instance or else In_Inlined_Body then
7777 -- Otherwise we need the conversion check
7780 return Conversion_Check
7781 (Is_Numeric_Type (Opnd_Type),
7782 "illegal operand for numeric conversion");
7787 elsif Is_Array_Type (Target_Type) then
7788 if not Is_Array_Type (Opnd_Type)
7789 or else Opnd_Type = Any_Composite
7790 or else Opnd_Type = Any_String
7793 ("illegal operand for array conversion", Operand);
7796 return Valid_Array_Conversion;
7799 -- Anonymous access types where target references an interface
7801 elsif (Ekind (Target_Type) = E_General_Access_Type
7803 Ekind (Target_Type) = E_Anonymous_Access_Type)
7804 and then Is_Interface (Directly_Designated_Type (Target_Type))
7806 -- Check the static accessibility rule of 4.6(17). Note that the
7807 -- check is not enforced when within an instance body, since the RM
7808 -- requires such cases to be caught at run time.
7810 if Ekind (Target_Type) /= E_Anonymous_Access_Type then
7811 if Type_Access_Level (Opnd_Type) >
7812 Type_Access_Level (Target_Type)
7814 -- In an instance, this is a run-time check, but one we know
7815 -- will fail, so generate an appropriate warning. The raise
7816 -- will be generated by Expand_N_Type_Conversion.
7818 if In_Instance_Body then
7820 ("?cannot convert local pointer to non-local access type",
7823 ("\?Program_Error will be raised at run time", Operand);
7826 ("cannot convert local pointer to non-local access type",
7831 -- Special accessibility checks are needed in the case of access
7832 -- discriminants declared for a limited type.
7834 elsif Ekind (Opnd_Type) = E_Anonymous_Access_Type
7835 and then not Is_Local_Anonymous_Access (Opnd_Type)
7837 -- When the operand is a selected access discriminant the check
7838 -- needs to be made against the level of the object denoted by
7839 -- the prefix of the selected name. (Object_Access_Level
7840 -- handles checking the prefix of the operand for this case.)
7842 if Nkind (Operand) = N_Selected_Component
7843 and then Object_Access_Level (Operand) >
7844 Type_Access_Level (Target_Type)
7846 -- In an instance, this is a run-time check, but one we
7847 -- know will fail, so generate an appropriate warning.
7848 -- The raise will be generated by Expand_N_Type_Conversion.
7850 if In_Instance_Body then
7852 ("?cannot convert access discriminant to non-local" &
7853 " access type", Operand);
7855 ("\?Program_Error will be raised at run time", Operand);
7858 ("cannot convert access discriminant to non-local" &
7859 " access type", Operand);
7864 -- The case of a reference to an access discriminant from
7865 -- within a limited type declaration (which will appear as
7866 -- a discriminal) is always illegal because the level of the
7867 -- discriminant is considered to be deeper than any (namable)
7870 if Is_Entity_Name (Operand)
7871 and then not Is_Local_Anonymous_Access (Opnd_Type)
7872 and then (Ekind (Entity (Operand)) = E_In_Parameter
7873 or else Ekind (Entity (Operand)) = E_Constant)
7874 and then Present (Discriminal_Link (Entity (Operand)))
7877 ("discriminant has deeper accessibility level than target",
7886 -- General and anonymous access types
7888 elsif (Ekind (Target_Type) = E_General_Access_Type
7889 or else Ekind (Target_Type) = E_Anonymous_Access_Type)
7892 (Is_Access_Type (Opnd_Type)
7893 and then Ekind (Opnd_Type) /=
7894 E_Access_Subprogram_Type
7895 and then Ekind (Opnd_Type) /=
7896 E_Access_Protected_Subprogram_Type,
7897 "must be an access-to-object type")
7899 if Is_Access_Constant (Opnd_Type)
7900 and then not Is_Access_Constant (Target_Type)
7903 ("access-to-constant operand type not allowed", Operand);
7907 -- Check the static accessibility rule of 4.6(17). Note that the
7908 -- check is not enforced when within an instance body, since the RM
7909 -- requires such cases to be caught at run time.
7911 if Ekind (Target_Type) /= E_Anonymous_Access_Type
7912 or else Is_Local_Anonymous_Access (Target_Type)
7914 if Type_Access_Level (Opnd_Type)
7915 > Type_Access_Level (Target_Type)
7917 -- In an instance, this is a run-time check, but one we
7918 -- know will fail, so generate an appropriate warning.
7919 -- The raise will be generated by Expand_N_Type_Conversion.
7921 if In_Instance_Body then
7923 ("?cannot convert local pointer to non-local access type",
7926 ("\?Program_Error will be raised at run time", Operand);
7930 ("cannot convert local pointer to non-local access type",
7935 -- Special accessibility checks are needed in the case of access
7936 -- discriminants declared for a limited type.
7938 elsif Ekind (Opnd_Type) = E_Anonymous_Access_Type
7939 and then not Is_Local_Anonymous_Access (Opnd_Type)
7942 -- When the operand is a selected access discriminant the check
7943 -- needs to be made against the level of the object denoted by
7944 -- the prefix of the selected name. (Object_Access_Level
7945 -- handles checking the prefix of the operand for this case.)
7947 if Nkind (Operand) = N_Selected_Component
7948 and then Object_Access_Level (Operand)
7949 > Type_Access_Level (Target_Type)
7951 -- In an instance, this is a run-time check, but one we
7952 -- know will fail, so generate an appropriate warning.
7953 -- The raise will be generated by Expand_N_Type_Conversion.
7955 if In_Instance_Body then
7957 ("?cannot convert access discriminant to non-local" &
7958 " access type", Operand);
7960 ("\?Program_Error will be raised at run time",
7965 ("cannot convert access discriminant to non-local" &
7966 " access type", Operand);
7971 -- The case of a reference to an access discriminant from
7972 -- within a limited type declaration (which will appear as
7973 -- a discriminal) is always illegal because the level of the
7974 -- discriminant is considered to be deeper than any (namable)
7977 if Is_Entity_Name (Operand)
7978 and then (Ekind (Entity (Operand)) = E_In_Parameter
7979 or else Ekind (Entity (Operand)) = E_Constant)
7980 and then Present (Discriminal_Link (Entity (Operand)))
7983 ("discriminant has deeper accessibility level than target",
7991 Target : constant Entity_Id := Designated_Type (Target_Type);
7992 Opnd : constant Entity_Id := Designated_Type (Opnd_Type);
7995 if Is_Tagged_Type (Target) then
7996 return Valid_Tagged_Conversion (Target, Opnd);
7999 if Base_Type (Target) /= Base_Type (Opnd) then
8001 ("target designated type not compatible with }",
8002 N, Base_Type (Opnd));
8005 -- Ada 2005 AI-384: legality rule is symmetric in both
8006 -- designated types. The conversion is legal (with possible
8007 -- constraint check) if either designated type is
8010 elsif Subtypes_Statically_Match (Target, Opnd)
8012 (Has_Discriminants (Target)
8014 (not Is_Constrained (Opnd)
8015 or else not Is_Constrained (Target)))
8021 ("target designated subtype not compatible with }",
8028 -- Subprogram access types
8030 elsif (Ekind (Target_Type) = E_Access_Subprogram_Type
8032 Ekind (Target_Type) = E_Anonymous_Access_Subprogram_Type)
8033 and then No (Corresponding_Remote_Type (Opnd_Type))
8034 and then Conversion_Check
8035 (Ekind (Base_Type (Opnd_Type)) = E_Access_Subprogram_Type,
8036 "illegal operand for access subprogram conversion")
8038 -- Check that the designated types are subtype conformant
8040 Check_Subtype_Conformant (New_Id => Designated_Type (Target_Type),
8041 Old_Id => Designated_Type (Opnd_Type),
8044 -- Check the static accessibility rule of 4.6(20)
8046 if Type_Access_Level (Opnd_Type) >
8047 Type_Access_Level (Target_Type)
8050 ("operand type has deeper accessibility level than target",
8053 -- Check that if the operand type is declared in a generic body,
8054 -- then the target type must be declared within that same body
8055 -- (enforces last sentence of 4.6(20)).
8057 elsif Present (Enclosing_Generic_Body (Opnd_Type)) then
8059 O_Gen : constant Node_Id :=
8060 Enclosing_Generic_Body (Opnd_Type);
8065 T_Gen := Enclosing_Generic_Body (Target_Type);
8066 while Present (T_Gen) and then T_Gen /= O_Gen loop
8067 T_Gen := Enclosing_Generic_Body (T_Gen);
8070 if T_Gen /= O_Gen then
8072 ("target type must be declared in same generic body"
8073 & " as operand type", N);
8080 -- Remote subprogram access types
8082 elsif Is_Remote_Access_To_Subprogram_Type (Target_Type)
8083 and then Is_Remote_Access_To_Subprogram_Type (Opnd_Type)
8085 -- It is valid to convert from one RAS type to another provided
8086 -- that their specification statically match.
8088 Check_Subtype_Conformant
8090 Designated_Type (Corresponding_Remote_Type (Target_Type)),
8092 Designated_Type (Corresponding_Remote_Type (Opnd_Type)),
8099 elsif Is_Tagged_Type (Target_Type) then
8100 return Valid_Tagged_Conversion (Target_Type, Opnd_Type);
8102 -- Types derived from the same root type are convertible
8104 elsif Root_Type (Target_Type) = Root_Type (Opnd_Type) then
8107 -- In an instance, there may be inconsistent views of the same
8108 -- type, or types derived from the same type.
8111 and then Underlying_Type (Target_Type) = Underlying_Type (Opnd_Type)
8115 -- Special check for common access type error case
8117 elsif Ekind (Target_Type) = E_Access_Type
8118 and then Is_Access_Type (Opnd_Type)
8120 Error_Msg_N ("target type must be general access type!", N);
8121 Error_Msg_NE ("add ALL to }!", N, Target_Type);
8126 Error_Msg_NE ("invalid conversion, not compatible with }",
8131 end Valid_Conversion;