1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2021, Free Software Foundation, Inc. --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 ------------------------------------------------------------------------------
26 with Aspects
; use Aspects
;
27 with Atree
; use Atree
;
28 with Checks
; use Checks
;
29 with Debug
; use Debug
;
30 with Einfo
; use Einfo
;
31 with Einfo
.Entities
; use Einfo
.Entities
;
32 with Einfo
.Utils
; use Einfo
.Utils
;
33 with Elists
; use Elists
;
34 with Errout
; use Errout
;
35 with Exp_Aggr
; use Exp_Aggr
;
36 with Exp_Atag
; use Exp_Atag
;
37 with Exp_Ch3
; use Exp_Ch3
;
38 with Exp_Ch6
; use Exp_Ch6
;
39 with Exp_Ch7
; use Exp_Ch7
;
40 with Exp_Ch9
; use Exp_Ch9
;
41 with Exp_Disp
; use Exp_Disp
;
42 with Exp_Fixd
; use Exp_Fixd
;
43 with Exp_Intr
; use Exp_Intr
;
44 with Exp_Pakd
; use Exp_Pakd
;
45 with Exp_Tss
; use Exp_Tss
;
46 with Exp_Util
; use Exp_Util
;
47 with Freeze
; use Freeze
;
48 with Inline
; use Inline
;
49 with Namet
; use Namet
;
50 with Nlists
; use Nlists
;
51 with Nmake
; use Nmake
;
53 with Par_SCO
; use Par_SCO
;
54 with Restrict
; use Restrict
;
55 with Rident
; use Rident
;
56 with Rtsfind
; use Rtsfind
;
58 with Sem_Aux
; use Sem_Aux
;
59 with Sem_Cat
; use Sem_Cat
;
60 with Sem_Ch3
; use Sem_Ch3
;
61 with Sem_Ch13
; use Sem_Ch13
;
62 with Sem_Eval
; use Sem_Eval
;
63 with Sem_Res
; use Sem_Res
;
64 with Sem_Type
; use Sem_Type
;
65 with Sem_Util
; use Sem_Util
;
66 with Sem_Warn
; use Sem_Warn
;
67 with Sinfo
; use Sinfo
;
68 with Sinfo
.Nodes
; use Sinfo
.Nodes
;
69 with Sinfo
.Utils
; use Sinfo
.Utils
;
70 with Snames
; use Snames
;
71 with Stand
; use Stand
;
72 with SCIL_LL
; use SCIL_LL
;
73 with Targparm
; use Targparm
;
74 with Tbuild
; use Tbuild
;
75 with Ttypes
; use Ttypes
;
76 with Uintp
; use Uintp
;
77 with Urealp
; use Urealp
;
78 with Validsw
; use Validsw
;
79 with Warnsw
; use Warnsw
;
81 package body Exp_Ch4
is
83 -----------------------
84 -- Local Subprograms --
85 -----------------------
87 procedure Binary_Op_Validity_Checks
(N
: Node_Id
);
88 pragma Inline
(Binary_Op_Validity_Checks
);
89 -- Performs validity checks for a binary operator
91 procedure Build_Boolean_Array_Proc_Call
95 -- If a boolean array assignment can be done in place, build call to
96 -- corresponding library procedure.
98 procedure Displace_Allocator_Pointer
(N
: Node_Id
);
99 -- Ada 2005 (AI-251): Subsidiary procedure to Expand_N_Allocator and
100 -- Expand_Allocator_Expression. Allocating class-wide interface objects
101 -- this routine displaces the pointer to the allocated object to reference
102 -- the component referencing the corresponding secondary dispatch table.
104 procedure Expand_Allocator_Expression
(N
: Node_Id
);
105 -- Subsidiary to Expand_N_Allocator, for the case when the expression
106 -- is a qualified expression.
108 procedure Expand_Array_Comparison
(N
: Node_Id
);
109 -- This routine handles expansion of the comparison operators (N_Op_Lt,
110 -- N_Op_Le, N_Op_Gt, N_Op_Ge) when operating on an array type. The basic
111 -- code for these operators is similar, differing only in the details of
112 -- the actual comparison call that is made. Special processing (call a
115 function Expand_Array_Equality
120 Typ
: Entity_Id
) return Node_Id
;
121 -- Expand an array equality into a call to a function implementing this
122 -- equality, and a call to it. Loc is the location for the generated nodes.
123 -- Lhs and Rhs are the array expressions to be compared. Bodies is a list
124 -- on which to attach bodies of local functions that are created in the
125 -- process. It is the responsibility of the caller to insert those bodies
126 -- at the right place. Nod provides the Sloc value for the generated code.
127 -- Normally the types used for the generated equality routine are taken
128 -- from Lhs and Rhs. However, in some situations of generated code, the
129 -- Etype fields of Lhs and Rhs are not set yet. In such cases, Typ supplies
130 -- the type to be used for the formal parameters.
132 procedure Expand_Boolean_Operator
(N
: Node_Id
);
133 -- Common expansion processing for Boolean operators (And, Or, Xor) for the
134 -- case of array type arguments.
136 procedure Expand_Nonbinary_Modular_Op
(N
: Node_Id
);
137 -- When generating C code, convert nonbinary modular arithmetic operations
138 -- into code that relies on the front-end expansion of operator Mod. No
139 -- expansion is performed if N is not a nonbinary modular operand.
141 procedure Expand_Short_Circuit_Operator
(N
: Node_Id
);
142 -- Common expansion processing for short-circuit boolean operators
144 procedure Expand_Compare_Minimize_Eliminate_Overflow
(N
: Node_Id
);
145 -- Deal with comparison in MINIMIZED/ELIMINATED overflow mode. This is
146 -- where we allow comparison of "out of range" values.
148 function Expand_Composite_Equality
152 Rhs
: Node_Id
) return Node_Id
;
153 -- Local recursive function used to expand equality for nested composite
154 -- types. Used by Expand_Record/Array_Equality. Nod provides the Sloc value
155 -- for generated code. Lhs and Rhs are the left and right sides for the
156 -- comparison, and Typ is the type of the objects to compare.
158 procedure Expand_Concatenate
(Cnode
: Node_Id
; Opnds
: List_Id
);
159 -- Routine to expand concatenation of a sequence of two or more operands
160 -- (in the list Operands) and replace node Cnode with the result of the
161 -- concatenation. The operands can be of any appropriate type, and can
162 -- include both arrays and singleton elements.
164 procedure Expand_Membership_Minimize_Eliminate_Overflow
(N
: Node_Id
);
165 -- N is an N_In membership test mode, with the overflow check mode set to
166 -- MINIMIZED or ELIMINATED, and the type of the left operand is a signed
167 -- integer type. This is a case where top level processing is required to
168 -- handle overflow checks in subtrees.
170 procedure Fixup_Universal_Fixed_Operation
(N
: Node_Id
);
171 -- N is a N_Op_Divide or N_Op_Multiply node whose result is universal
172 -- fixed. We do not have such a type at runtime, so the purpose of this
173 -- routine is to find the real type by looking up the tree. We also
174 -- determine if the operation must be rounded.
176 function Get_Size_For_Range
(Lo
, Hi
: Uint
) return Uint
;
177 -- Return the size of a small signed integer type covering Lo .. Hi, the
178 -- main goal being to return a size lower than that of standard types.
180 procedure Insert_Dereference_Action
(N
: Node_Id
);
181 -- N is an expression whose type is an access. When the type of the
182 -- associated storage pool is derived from Checked_Pool, generate a
183 -- call to the 'Dereference' primitive operation.
185 function Make_Array_Comparison_Op
187 Nod
: Node_Id
) return Node_Id
;
188 -- Comparisons between arrays are expanded in line. This function produces
189 -- the body of the implementation of (a > b), where a and b are one-
190 -- dimensional arrays of some discrete type. The original node is then
191 -- expanded into the appropriate call to this function. Nod provides the
192 -- Sloc value for the generated code.
194 function Make_Boolean_Array_Op
196 N
: Node_Id
) return Node_Id
;
197 -- Boolean operations on boolean arrays are expanded in line. This function
198 -- produce the body for the node N, which is (a and b), (a or b), or (a xor
199 -- b). It is used only the normal case and not the packed case. The type
200 -- involved, Typ, is the Boolean array type, and the logical operations in
201 -- the body are simple boolean operations. Note that Typ is always a
202 -- constrained type (the caller has ensured this by using
203 -- Convert_To_Actual_Subtype if necessary).
205 function Minimized_Eliminated_Overflow_Check
(N
: Node_Id
) return Boolean;
206 -- For signed arithmetic operations when the current overflow mode is
207 -- MINIMIZED or ELIMINATED, we must call Apply_Arithmetic_Overflow_Checks
208 -- as the first thing we do. We then return. We count on the recursive
209 -- apparatus for overflow checks to call us back with an equivalent
210 -- operation that is in CHECKED mode, avoiding a recursive entry into this
211 -- routine, and that is when we will proceed with the expansion of the
212 -- operator (e.g. converting X+0 to X, or X**2 to X*X). We cannot do
213 -- these optimizations without first making this check, since there may be
214 -- operands further down the tree that are relying on the recursive calls
215 -- triggered by the top level nodes to properly process overflow checking
216 -- and remaining expansion on these nodes. Note that this call back may be
217 -- skipped if the operation is done in Bignum mode but that's fine, since
218 -- the Bignum call takes care of everything.
220 procedure Narrow_Large_Operation
(N
: Node_Id
);
221 -- Try to compute the result of a large operation in a narrower type than
222 -- its nominal type. This is mainly aimed at getting rid of operations done
223 -- in Universal_Integer that can be generated for attributes.
225 procedure Optimize_Length_Comparison
(N
: Node_Id
);
226 -- Given an expression, if it is of the form X'Length op N (or the other
227 -- way round), where N is known at compile time to be 0 or 1, or something
228 -- else where the value is known to be nonnegative and in the 32-bit range,
229 -- and X is a simple entity, and op is a comparison operator, optimizes it
230 -- into a comparison of X'First and X'Last.
232 procedure Process_If_Case_Statements
(N
: Node_Id
; Stmts
: List_Id
);
233 -- Inspect and process statement list Stmt of if or case expression N for
234 -- transient objects. If such objects are found, the routine generates code
235 -- to clean them up when the context of the expression is evaluated.
237 procedure Process_Transient_In_Expression
241 -- Subsidiary routine to the expansion of expression_with_actions, if and
242 -- case expressions. Generate all necessary code to finalize a transient
243 -- object when the enclosing context is elaborated or evaluated. Obj_Decl
244 -- denotes the declaration of the transient object, which is usually the
245 -- result of a controlled function call. Expr denotes the expression with
246 -- actions, if expression, or case expression node. Stmts denotes the
247 -- statement list which contains Decl, either at the top level or within a
250 procedure Rewrite_Comparison
(N
: Node_Id
);
251 -- If N is the node for a comparison whose outcome can be determined at
252 -- compile time, then the node N can be rewritten with True or False. If
253 -- the outcome cannot be determined at compile time, the call has no
254 -- effect. If N is a type conversion, then this processing is applied to
255 -- its expression. If N is neither comparison nor a type conversion, the
256 -- call has no effect.
258 procedure Tagged_Membership
260 SCIL_Node
: out Node_Id
;
261 Result
: out Node_Id
);
262 -- Construct the expression corresponding to the tagged membership test.
263 -- Deals with a second operand being (or not) a class-wide type.
265 function Safe_In_Place_Array_Op
268 Op2
: Node_Id
) return Boolean;
269 -- In the context of an assignment, where the right-hand side is a boolean
270 -- operation on arrays, check whether operation can be performed in place.
272 procedure Unary_Op_Validity_Checks
(N
: Node_Id
);
273 pragma Inline
(Unary_Op_Validity_Checks
);
274 -- Performs validity checks for a unary operator
276 -------------------------------
277 -- Binary_Op_Validity_Checks --
278 -------------------------------
280 procedure Binary_Op_Validity_Checks
(N
: Node_Id
) is
282 if Validity_Checks_On
and Validity_Check_Operands
then
283 Ensure_Valid
(Left_Opnd
(N
));
284 Ensure_Valid
(Right_Opnd
(N
));
286 end Binary_Op_Validity_Checks
;
288 ------------------------------------
289 -- Build_Boolean_Array_Proc_Call --
290 ------------------------------------
292 procedure Build_Boolean_Array_Proc_Call
297 Loc
: constant Source_Ptr
:= Sloc
(N
);
298 Kind
: constant Node_Kind
:= Nkind
(Expression
(N
));
299 Target
: constant Node_Id
:=
300 Make_Attribute_Reference
(Loc
,
302 Attribute_Name
=> Name_Address
);
304 Arg1
: Node_Id
:= Op1
;
305 Arg2
: Node_Id
:= Op2
;
307 Proc_Name
: Entity_Id
;
310 if Kind
= N_Op_Not
then
311 if Nkind
(Op1
) in N_Binary_Op
then
313 -- Use negated version of the binary operators
315 if Nkind
(Op1
) = N_Op_And
then
316 Proc_Name
:= RTE
(RE_Vector_Nand
);
318 elsif Nkind
(Op1
) = N_Op_Or
then
319 Proc_Name
:= RTE
(RE_Vector_Nor
);
321 else pragma Assert
(Nkind
(Op1
) = N_Op_Xor
);
322 Proc_Name
:= RTE
(RE_Vector_Xor
);
326 Make_Procedure_Call_Statement
(Loc
,
327 Name
=> New_Occurrence_Of
(Proc_Name
, Loc
),
329 Parameter_Associations
=> New_List
(
331 Make_Attribute_Reference
(Loc
,
332 Prefix
=> Left_Opnd
(Op1
),
333 Attribute_Name
=> Name_Address
),
335 Make_Attribute_Reference
(Loc
,
336 Prefix
=> Right_Opnd
(Op1
),
337 Attribute_Name
=> Name_Address
),
339 Make_Attribute_Reference
(Loc
,
340 Prefix
=> Left_Opnd
(Op1
),
341 Attribute_Name
=> Name_Length
)));
344 Proc_Name
:= RTE
(RE_Vector_Not
);
347 Make_Procedure_Call_Statement
(Loc
,
348 Name
=> New_Occurrence_Of
(Proc_Name
, Loc
),
349 Parameter_Associations
=> New_List
(
352 Make_Attribute_Reference
(Loc
,
354 Attribute_Name
=> Name_Address
),
356 Make_Attribute_Reference
(Loc
,
358 Attribute_Name
=> Name_Length
)));
362 -- We use the following equivalences:
364 -- (not X) or (not Y) = not (X and Y) = Nand (X, Y)
365 -- (not X) and (not Y) = not (X or Y) = Nor (X, Y)
366 -- (not X) xor (not Y) = X xor Y
367 -- X xor (not Y) = not (X xor Y) = Nxor (X, Y)
369 if Nkind
(Op1
) = N_Op_Not
then
370 Arg1
:= Right_Opnd
(Op1
);
371 Arg2
:= Right_Opnd
(Op2
);
373 if Kind
= N_Op_And
then
374 Proc_Name
:= RTE
(RE_Vector_Nor
);
375 elsif Kind
= N_Op_Or
then
376 Proc_Name
:= RTE
(RE_Vector_Nand
);
378 Proc_Name
:= RTE
(RE_Vector_Xor
);
382 if Kind
= N_Op_And
then
383 Proc_Name
:= RTE
(RE_Vector_And
);
384 elsif Kind
= N_Op_Or
then
385 Proc_Name
:= RTE
(RE_Vector_Or
);
386 elsif Nkind
(Op2
) = N_Op_Not
then
387 Proc_Name
:= RTE
(RE_Vector_Nxor
);
388 Arg2
:= Right_Opnd
(Op2
);
390 Proc_Name
:= RTE
(RE_Vector_Xor
);
395 Make_Procedure_Call_Statement
(Loc
,
396 Name
=> New_Occurrence_Of
(Proc_Name
, Loc
),
397 Parameter_Associations
=> New_List
(
399 Make_Attribute_Reference
(Loc
,
401 Attribute_Name
=> Name_Address
),
402 Make_Attribute_Reference
(Loc
,
404 Attribute_Name
=> Name_Address
),
405 Make_Attribute_Reference
(Loc
,
407 Attribute_Name
=> Name_Length
)));
410 Rewrite
(N
, Call_Node
);
414 when RE_Not_Available
=>
416 end Build_Boolean_Array_Proc_Call
;
418 -----------------------
420 -----------------------
422 function Build_Eq_Call
426 Rhs
: Node_Id
) return Node_Id
432 Prim_E
:= First_Elmt
(Collect_Primitive_Operations
(Typ
));
433 while Present
(Prim_E
) loop
434 Prim
:= Node
(Prim_E
);
436 -- Locate primitive equality with the right signature
438 if Chars
(Prim
) = Name_Op_Eq
439 and then Etype
(First_Formal
(Prim
)) =
440 Etype
(Next_Formal
(First_Formal
(Prim
)))
441 and then Etype
(Prim
) = Standard_Boolean
443 if Is_Abstract_Subprogram
(Prim
) then
445 Make_Raise_Program_Error
(Loc
,
446 Reason
=> PE_Explicit_Raise
);
450 Make_Function_Call
(Loc
,
451 Name
=> New_Occurrence_Of
(Prim
, Loc
),
452 Parameter_Associations
=> New_List
(Lhs
, Rhs
));
459 -- If not found, predefined operation will be used
464 --------------------------------
465 -- Displace_Allocator_Pointer --
466 --------------------------------
468 procedure Displace_Allocator_Pointer
(N
: Node_Id
) is
469 Loc
: constant Source_Ptr
:= Sloc
(N
);
470 Orig_Node
: constant Node_Id
:= Original_Node
(N
);
476 -- Do nothing in case of VM targets: the virtual machine will handle
477 -- interfaces directly.
479 if not Tagged_Type_Expansion
then
483 pragma Assert
(Nkind
(N
) = N_Identifier
484 and then Nkind
(Orig_Node
) = N_Allocator
);
486 PtrT
:= Etype
(Orig_Node
);
487 Dtyp
:= Available_View
(Designated_Type
(PtrT
));
488 Etyp
:= Etype
(Expression
(Orig_Node
));
490 if Is_Class_Wide_Type
(Dtyp
) and then Is_Interface
(Dtyp
) then
492 -- If the type of the allocator expression is not an interface type
493 -- we can generate code to reference the record component containing
494 -- the pointer to the secondary dispatch table.
496 if not Is_Interface
(Etyp
) then
498 Saved_Typ
: constant Entity_Id
:= Etype
(Orig_Node
);
501 -- 1) Get access to the allocated object
504 Make_Explicit_Dereference
(Loc
, Relocate_Node
(N
)));
508 -- 2) Add the conversion to displace the pointer to reference
509 -- the secondary dispatch table.
511 Rewrite
(N
, Convert_To
(Dtyp
, Relocate_Node
(N
)));
512 Analyze_And_Resolve
(N
, Dtyp
);
514 -- 3) The 'access to the secondary dispatch table will be used
515 -- as the value returned by the allocator.
518 Make_Attribute_Reference
(Loc
,
519 Prefix
=> Relocate_Node
(N
),
520 Attribute_Name
=> Name_Access
));
521 Set_Etype
(N
, Saved_Typ
);
525 -- If the type of the allocator expression is an interface type we
526 -- generate a run-time call to displace "this" to reference the
527 -- component containing the pointer to the secondary dispatch table
528 -- or else raise Constraint_Error if the actual object does not
529 -- implement the target interface. This case corresponds to the
530 -- following example:
532 -- function Op (Obj : Iface_1'Class) return access Iface_2'Class is
534 -- return new Iface_2'Class'(Obj);
539 Unchecked_Convert_To
(PtrT
,
540 Make_Function_Call
(Loc
,
541 Name
=> New_Occurrence_Of
(RTE
(RE_Displace
), Loc
),
542 Parameter_Associations
=> New_List
(
543 Unchecked_Convert_To
(RTE
(RE_Address
),
549 (Access_Disp_Table
(Etype
(Base_Type
(Dtyp
))))),
551 Analyze_And_Resolve
(N
, PtrT
);
554 end Displace_Allocator_Pointer
;
556 ---------------------------------
557 -- Expand_Allocator_Expression --
558 ---------------------------------
560 procedure Expand_Allocator_Expression
(N
: Node_Id
) is
561 Loc
: constant Source_Ptr
:= Sloc
(N
);
562 Exp
: constant Node_Id
:= Expression
(Expression
(N
));
563 PtrT
: constant Entity_Id
:= Etype
(N
);
564 DesigT
: constant Entity_Id
:= Designated_Type
(PtrT
);
566 procedure Apply_Accessibility_Check
568 Built_In_Place
: Boolean := False);
569 -- Ada 2005 (AI-344): For an allocator with a class-wide designated
570 -- type, generate an accessibility check to verify that the level of the
571 -- type of the created object is not deeper than the level of the access
572 -- type. If the type of the qualified expression is class-wide, then
573 -- always generate the check (except in the case where it is known to be
574 -- unnecessary, see comment below). Otherwise, only generate the check
575 -- if the level of the qualified expression type is statically deeper
576 -- than the access type.
578 -- Although the static accessibility will generally have been performed
579 -- as a legality check, it won't have been done in cases where the
580 -- allocator appears in generic body, so a run-time check is needed in
581 -- general. One special case is when the access type is declared in the
582 -- same scope as the class-wide allocator, in which case the check can
583 -- never fail, so it need not be generated.
585 -- As an open issue, there seem to be cases where the static level
586 -- associated with the class-wide object's underlying type is not
587 -- sufficient to perform the proper accessibility check, such as for
588 -- allocators in nested subprograms or accept statements initialized by
589 -- class-wide formals when the actual originates outside at a deeper
590 -- static level. The nested subprogram case might require passing
591 -- accessibility levels along with class-wide parameters, and the task
592 -- case seems to be an actual gap in the language rules that needs to
593 -- be fixed by the ARG. ???
595 -------------------------------
596 -- Apply_Accessibility_Check --
597 -------------------------------
599 procedure Apply_Accessibility_Check
601 Built_In_Place
: Boolean := False)
603 Pool_Id
: constant Entity_Id
:= Associated_Storage_Pool
(PtrT
);
611 if Ada_Version
>= Ada_2005
612 and then Is_Class_Wide_Type
(DesigT
)
613 and then Tagged_Type_Expansion
614 and then not Scope_Suppress
.Suppress
(Accessibility_Check
)
615 and then not No_Dynamic_Accessibility_Checks_Enabled
(Ref
)
617 (Type_Access_Level
(Etype
(Exp
)) > Type_Access_Level
(PtrT
)
619 (Is_Class_Wide_Type
(Etype
(Exp
))
620 and then Scope
(PtrT
) /= Current_Scope
))
622 -- If the allocator was built in place, Ref is already a reference
623 -- to the access object initialized to the result of the allocator
624 -- (see Exp_Ch6.Make_Build_In_Place_Call_In_Allocator). We call
625 -- Remove_Side_Effects for cases where the build-in-place call may
626 -- still be the prefix of the reference (to avoid generating
627 -- duplicate calls). Otherwise, it is the entity associated with
628 -- the object containing the address of the allocated object.
630 if Built_In_Place
then
631 Remove_Side_Effects
(Ref
);
632 Obj_Ref
:= New_Copy_Tree
(Ref
);
634 Obj_Ref
:= New_Occurrence_Of
(Ref
, Loc
);
637 -- For access to interface types we must generate code to displace
638 -- the pointer to the base of the object since the subsequent code
639 -- references components located in the TSD of the object (which
640 -- is associated with the primary dispatch table --see a-tags.ads)
641 -- and also generates code invoking Free, which requires also a
642 -- reference to the base of the unallocated object.
644 if Is_Interface
(DesigT
) and then Tagged_Type_Expansion
then
646 Unchecked_Convert_To
(Etype
(Obj_Ref
),
647 Make_Function_Call
(Loc
,
649 New_Occurrence_Of
(RTE
(RE_Base_Address
), Loc
),
650 Parameter_Associations
=> New_List
(
651 Unchecked_Convert_To
(RTE
(RE_Address
),
652 New_Copy_Tree
(Obj_Ref
)))));
655 -- Step 1: Create the object clean up code
659 -- Deallocate the object if the accessibility check fails. This
660 -- is done only on targets or profiles that support deallocation.
664 if RTE_Available
(RE_Free
) then
665 Free_Stmt
:= Make_Free_Statement
(Loc
, New_Copy_Tree
(Obj_Ref
));
666 Set_Storage_Pool
(Free_Stmt
, Pool_Id
);
668 Append_To
(Stmts
, Free_Stmt
);
670 -- The target or profile cannot deallocate objects
676 -- Finalize the object if applicable. Generate:
678 -- [Deep_]Finalize (Obj_Ref.all);
680 if Needs_Finalization
(DesigT
)
681 and then not No_Heap_Finalization
(PtrT
)
686 Make_Explicit_Dereference
(Loc
, New_Copy
(Obj_Ref
)),
689 -- Guard against a missing [Deep_]Finalize when the designated
690 -- type was not properly frozen.
692 if No
(Fin_Call
) then
693 Fin_Call
:= Make_Null_Statement
(Loc
);
696 -- When the target or profile supports deallocation, wrap the
697 -- finalization call in a block to ensure proper deallocation
698 -- even if finalization fails. Generate:
708 if Present
(Free_Stmt
) then
710 Make_Block_Statement
(Loc
,
711 Handled_Statement_Sequence
=>
712 Make_Handled_Sequence_Of_Statements
(Loc
,
713 Statements
=> New_List
(Fin_Call
),
715 Exception_Handlers
=> New_List
(
716 Make_Exception_Handler
(Loc
,
717 Exception_Choices
=> New_List
(
718 Make_Others_Choice
(Loc
)),
719 Statements
=> New_List
(
720 New_Copy_Tree
(Free_Stmt
),
721 Make_Raise_Statement
(Loc
))))));
724 Prepend_To
(Stmts
, Fin_Call
);
727 -- Signal the accessibility failure through a Program_Error
730 Make_Raise_Program_Error
(Loc
,
731 Reason
=> PE_Accessibility_Check_Failed
));
733 -- Step 2: Create the accessibility comparison
739 Make_Attribute_Reference
(Loc
,
741 Attribute_Name
=> Name_Tag
);
743 -- For tagged types, determine the accessibility level by looking
744 -- at the type specific data of the dispatch table. Generate:
746 -- Type_Specific_Data (Address (Ref'Tag)).Access_Level
748 if Tagged_Type_Expansion
then
749 Cond
:= Build_Get_Access_Level
(Loc
, Obj_Ref
);
751 -- Use a runtime call to determine the accessibility level when
752 -- compiling on virtual machine targets. Generate:
754 -- Get_Access_Level (Ref'Tag)
758 Make_Function_Call
(Loc
,
760 New_Occurrence_Of
(RTE
(RE_Get_Access_Level
), Loc
),
761 Parameter_Associations
=> New_List
(Obj_Ref
));
767 Right_Opnd
=> Accessibility_Level
(N
, Dynamic_Level
));
769 -- Due to the complexity and side effects of the check, utilize an
770 -- if statement instead of the regular Program_Error circuitry.
773 Make_Implicit_If_Statement
(N
,
775 Then_Statements
=> Stmts
));
777 end Apply_Accessibility_Check
;
781 Indic
: constant Node_Id
:= Subtype_Mark
(Expression
(N
));
782 T
: constant Entity_Id
:= Entity
(Indic
);
784 Aggr_In_Place
: Boolean;
786 Tag_Assign
: Node_Id
;
790 TagT
: Entity_Id
:= Empty
;
791 -- Type used as source for tag assignment
793 TagR
: Node_Id
:= Empty
;
794 -- Target reference for tag assignment
796 -- Start of processing for Expand_Allocator_Expression
799 -- Handle call to C++ constructor
801 if Is_CPP_Constructor_Call
(Exp
) then
802 Make_CPP_Constructor_Call_In_Allocator
804 Function_Call
=> Exp
);
809 -- type A is access T1;
810 -- X : A := new T2'(...);
811 -- T1 and T2 can be different subtypes, and we might need to check
812 -- both constraints. First check against the type of the qualified
815 Apply_Constraint_Check
(Exp
, T
, No_Sliding
=> True);
817 Apply_Predicate_Check
(Exp
, T
);
819 -- Check that any anonymous access discriminants are suitable
820 -- for use in an allocator.
822 -- Note: This check is performed here instead of during analysis so that
823 -- we can check against the fully resolved etype of Exp.
825 if Is_Entity_Name
(Exp
)
826 and then Has_Anonymous_Access_Discriminant
(Etype
(Exp
))
827 and then Static_Accessibility_Level
(Exp
, Object_Decl_Level
)
828 > Static_Accessibility_Level
(N
, Object_Decl_Level
)
830 -- A dynamic check and a warning are generated when we are within
835 Make_Raise_Program_Error
(Loc
,
836 Reason
=> PE_Accessibility_Check_Failed
));
838 Error_Msg_N
("anonymous access discriminant is too deep for use"
839 & " in allocator<<", N
);
840 Error_Msg_N
("\Program_Error [<<", N
);
842 -- Otherwise, make the error static
845 Error_Msg_N
("anonymous access discriminant is too deep for use"
846 & " in allocator", N
);
850 if Do_Range_Check
(Exp
) then
851 Generate_Range_Check
(Exp
, T
, CE_Range_Check_Failed
);
854 -- A check is also needed in cases where the designated subtype is
855 -- constrained and differs from the subtype given in the qualified
856 -- expression. Note that the check on the qualified expression does
857 -- not allow sliding, but this check does (a relaxation from Ada 83).
859 if Is_Constrained
(DesigT
)
860 and then not Subtypes_Statically_Match
(T
, DesigT
)
862 Apply_Constraint_Check
(Exp
, DesigT
, No_Sliding
=> False);
864 Apply_Predicate_Check
(Exp
, DesigT
);
866 if Do_Range_Check
(Exp
) then
867 Generate_Range_Check
(Exp
, DesigT
, CE_Range_Check_Failed
);
871 if Nkind
(Exp
) = N_Raise_Constraint_Error
then
872 Rewrite
(N
, New_Copy
(Exp
));
877 Aggr_In_Place
:= Is_Delayed_Aggregate
(Exp
);
879 -- Case of tagged type or type requiring finalization
881 if Is_Tagged_Type
(T
) or else Needs_Finalization
(T
) then
883 -- Ada 2005 (AI-318-02): If the initialization expression is a call
884 -- to a build-in-place function, then access to the allocated object
885 -- must be passed to the function.
887 if Is_Build_In_Place_Function_Call
(Exp
) then
888 Make_Build_In_Place_Call_In_Allocator
(N
, Exp
);
889 Apply_Accessibility_Check
(N
, Built_In_Place
=> True);
892 -- Ada 2005 (AI-318-02): Specialization of the previous case for
893 -- expressions containing a build-in-place function call whose
894 -- returned object covers interface types, and Expr has calls to
895 -- Ada.Tags.Displace to displace the pointer to the returned build-
896 -- in-place object to reference the secondary dispatch table of a
897 -- covered interface type.
899 elsif Present
(Unqual_BIP_Iface_Function_Call
(Exp
)) then
900 Make_Build_In_Place_Iface_Call_In_Allocator
(N
, Exp
);
901 Apply_Accessibility_Check
(N
, Built_In_Place
=> True);
905 -- Actions inserted before:
906 -- Temp : constant ptr_T := new T'(Expression);
907 -- Temp._tag = T'tag; -- when not class-wide
908 -- [Deep_]Adjust (Temp.all);
910 -- We analyze by hand the new internal allocator to avoid any
911 -- recursion and inappropriate call to Initialize.
913 -- We don't want to remove side effects when the expression must be
914 -- built in place. In the case of a build-in-place function call,
915 -- that could lead to a duplication of the call, which was already
916 -- substituted for the allocator.
918 if not Aggr_In_Place
then
919 Remove_Side_Effects
(Exp
);
922 Temp
:= Make_Temporary
(Loc
, 'P', N
);
924 -- For a class wide allocation generate the following code:
926 -- type Equiv_Record is record ... end record;
927 -- implicit subtype CW is <Class_Wide_Subytpe>;
928 -- temp : PtrT := new CW'(CW!(expr));
930 if Is_Class_Wide_Type
(T
) then
931 Expand_Subtype_From_Expr
(Empty
, T
, Indic
, Exp
);
933 -- Ada 2005 (AI-251): If the expression is a class-wide interface
934 -- object we generate code to move up "this" to reference the
935 -- base of the object before allocating the new object.
937 -- Note that Exp'Address is recursively expanded into a call
938 -- to Base_Address (Exp.Tag)
940 if Is_Class_Wide_Type
(Etype
(Exp
))
941 and then Is_Interface
(Etype
(Exp
))
942 and then Tagged_Type_Expansion
946 Unchecked_Convert_To
(Entity
(Indic
),
947 Make_Explicit_Dereference
(Loc
,
948 Unchecked_Convert_To
(RTE
(RE_Tag_Ptr
),
949 Make_Attribute_Reference
(Loc
,
951 Attribute_Name
=> Name_Address
)))));
955 Unchecked_Convert_To
(Entity
(Indic
), Exp
));
958 Analyze_And_Resolve
(Expression
(N
), Entity
(Indic
));
961 -- Processing for allocators returning non-interface types
963 if not Is_Interface
(Directly_Designated_Type
(PtrT
)) then
964 if Aggr_In_Place
then
966 Make_Object_Declaration
(Loc
,
967 Defining_Identifier
=> Temp
,
968 Object_Definition
=> New_Occurrence_Of
(PtrT
, Loc
),
972 New_Occurrence_Of
(Etype
(Exp
), Loc
)));
974 -- Copy the Comes_From_Source flag for the allocator we just
975 -- built, since logically this allocator is a replacement of
976 -- the original allocator node. This is for proper handling of
977 -- restriction No_Implicit_Heap_Allocations.
979 Preserve_Comes_From_Source
980 (Expression
(Temp_Decl
), N
);
982 Set_No_Initialization
(Expression
(Temp_Decl
));
983 Insert_Action
(N
, Temp_Decl
);
985 Build_Allocate_Deallocate_Proc
(Temp_Decl
, True);
986 Convert_Aggr_In_Allocator
(N
, Temp_Decl
, Exp
);
989 Node
:= Relocate_Node
(N
);
993 Make_Object_Declaration
(Loc
,
994 Defining_Identifier
=> Temp
,
995 Constant_Present
=> True,
996 Object_Definition
=> New_Occurrence_Of
(PtrT
, Loc
),
999 Insert_Action
(N
, Temp_Decl
);
1000 Build_Allocate_Deallocate_Proc
(Temp_Decl
, True);
1003 -- Ada 2005 (AI-251): Handle allocators whose designated type is an
1004 -- interface type. In this case we use the type of the qualified
1005 -- expression to allocate the object.
1009 Def_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T');
1014 Make_Full_Type_Declaration
(Loc
,
1015 Defining_Identifier
=> Def_Id
,
1017 Make_Access_To_Object_Definition
(Loc
,
1018 All_Present
=> True,
1019 Null_Exclusion_Present
=> False,
1021 Is_Access_Constant
(Etype
(N
)),
1022 Subtype_Indication
=>
1023 New_Occurrence_Of
(Etype
(Exp
), Loc
)));
1025 Insert_Action
(N
, New_Decl
);
1027 -- Inherit the allocation-related attributes from the original
1030 Set_Finalization_Master
1031 (Def_Id
, Finalization_Master
(PtrT
));
1033 Set_Associated_Storage_Pool
1034 (Def_Id
, Associated_Storage_Pool
(PtrT
));
1036 -- Declare the object using the previous type declaration
1038 if Aggr_In_Place
then
1040 Make_Object_Declaration
(Loc
,
1041 Defining_Identifier
=> Temp
,
1042 Object_Definition
=> New_Occurrence_Of
(Def_Id
, Loc
),
1044 Make_Allocator
(Loc
,
1045 New_Occurrence_Of
(Etype
(Exp
), Loc
)));
1047 -- Copy the Comes_From_Source flag for the allocator we just
1048 -- built, since logically this allocator is a replacement of
1049 -- the original allocator node. This is for proper handling
1050 -- of restriction No_Implicit_Heap_Allocations.
1052 Set_Comes_From_Source
1053 (Expression
(Temp_Decl
), Comes_From_Source
(N
));
1055 Set_No_Initialization
(Expression
(Temp_Decl
));
1056 Insert_Action
(N
, Temp_Decl
);
1058 Build_Allocate_Deallocate_Proc
(Temp_Decl
, True);
1059 Convert_Aggr_In_Allocator
(N
, Temp_Decl
, Exp
);
1062 Node
:= Relocate_Node
(N
);
1063 Set_Analyzed
(Node
);
1066 Make_Object_Declaration
(Loc
,
1067 Defining_Identifier
=> Temp
,
1068 Constant_Present
=> True,
1069 Object_Definition
=> New_Occurrence_Of
(Def_Id
, Loc
),
1070 Expression
=> Node
);
1072 Insert_Action
(N
, Temp_Decl
);
1073 Build_Allocate_Deallocate_Proc
(Temp_Decl
, True);
1076 -- Generate an additional object containing the address of the
1077 -- returned object. The type of this second object declaration
1078 -- is the correct type required for the common processing that
1079 -- is still performed by this subprogram. The displacement of
1080 -- this pointer to reference the component associated with the
1081 -- interface type will be done at the end of common processing.
1084 Make_Object_Declaration
(Loc
,
1085 Defining_Identifier
=> Make_Temporary
(Loc
, 'P'),
1086 Object_Definition
=> New_Occurrence_Of
(PtrT
, Loc
),
1088 Unchecked_Convert_To
(PtrT
,
1089 New_Occurrence_Of
(Temp
, Loc
)));
1091 Insert_Action
(N
, New_Decl
);
1093 Temp_Decl
:= New_Decl
;
1094 Temp
:= Defining_Identifier
(New_Decl
);
1098 -- Generate the tag assignment
1100 -- Suppress the tag assignment for VM targets because VM tags are
1101 -- represented implicitly in objects.
1103 if not Tagged_Type_Expansion
then
1106 -- Ada 2005 (AI-251): Suppress the tag assignment with class-wide
1107 -- interface objects because in this case the tag does not change.
1109 elsif Is_Interface
(Directly_Designated_Type
(Etype
(N
))) then
1110 pragma Assert
(Is_Class_Wide_Type
1111 (Directly_Designated_Type
(Etype
(N
))));
1114 elsif Is_Tagged_Type
(T
) and then not Is_Class_Wide_Type
(T
) then
1117 Make_Explicit_Dereference
(Loc
,
1118 Prefix
=> New_Occurrence_Of
(Temp
, Loc
));
1120 elsif Is_Private_Type
(T
)
1121 and then Is_Tagged_Type
(Underlying_Type
(T
))
1123 TagT
:= Underlying_Type
(T
);
1125 Unchecked_Convert_To
(Underlying_Type
(T
),
1126 Make_Explicit_Dereference
(Loc
,
1127 Prefix
=> New_Occurrence_Of
(Temp
, Loc
)));
1130 if Present
(TagT
) then
1132 Full_T
: constant Entity_Id
:= Underlying_Type
(TagT
);
1136 Make_Assignment_Statement
(Loc
,
1138 Make_Selected_Component
(Loc
,
1142 (First_Tag_Component
(Full_T
), Loc
)),
1145 Unchecked_Convert_To
(RTE
(RE_Tag
),
1148 (First_Elmt
(Access_Disp_Table
(Full_T
))), Loc
)));
1151 -- The previous assignment has to be done in any case
1153 Set_Assignment_OK
(Name
(Tag_Assign
));
1154 Insert_Action
(N
, Tag_Assign
);
1157 -- Generate an Adjust call if the object will be moved. In Ada 2005,
1158 -- the object may be inherently limited, in which case there is no
1159 -- Adjust procedure, and the object is built in place. In Ada 95, the
1160 -- object can be limited but not inherently limited if this allocator
1161 -- came from a return statement (we're allocating the result on the
1162 -- secondary stack). In that case, the object will be moved, so we do
1163 -- want to Adjust. However, if it's a nonlimited build-in-place
1164 -- function call, Adjust is not wanted.
1166 -- Needs_Finalization (DesigT) can differ from Needs_Finalization (T)
1167 -- if one of the two types is class-wide, and the other is not.
1169 if Needs_Finalization
(DesigT
)
1170 and then Needs_Finalization
(T
)
1171 and then not Aggr_In_Place
1172 and then not Is_Limited_View
(T
)
1173 and then not Alloc_For_BIP_Return
(N
)
1174 and then not Is_Build_In_Place_Function_Call
(Expression
(N
))
1176 -- An unchecked conversion is needed in the classwide case because
1177 -- the designated type can be an ancestor of the subtype mark of
1183 Unchecked_Convert_To
(T
,
1184 Make_Explicit_Dereference
(Loc
,
1185 Prefix
=> New_Occurrence_Of
(Temp
, Loc
))),
1188 if Present
(Adj_Call
) then
1189 Insert_Action
(N
, Adj_Call
);
1193 -- Note: the accessibility check must be inserted after the call to
1194 -- [Deep_]Adjust to ensure proper completion of the assignment.
1196 Apply_Accessibility_Check
(Temp
);
1198 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
1199 Analyze_And_Resolve
(N
, PtrT
);
1201 -- Ada 2005 (AI-251): Displace the pointer to reference the record
1202 -- component containing the secondary dispatch table of the interface
1205 if Is_Interface
(Directly_Designated_Type
(PtrT
)) then
1206 Displace_Allocator_Pointer
(N
);
1209 -- Always force the generation of a temporary for aggregates when
1210 -- generating C code, to simplify the work in the code generator.
1213 or else (Modify_Tree_For_C
and then Nkind
(Exp
) = N_Aggregate
)
1215 Temp
:= Make_Temporary
(Loc
, 'P', N
);
1217 Make_Object_Declaration
(Loc
,
1218 Defining_Identifier
=> Temp
,
1219 Object_Definition
=> New_Occurrence_Of
(PtrT
, Loc
),
1221 Make_Allocator
(Loc
,
1222 Expression
=> New_Occurrence_Of
(Etype
(Exp
), Loc
)));
1224 -- Copy the Comes_From_Source flag for the allocator we just built,
1225 -- since logically this allocator is a replacement of the original
1226 -- allocator node. This is for proper handling of restriction
1227 -- No_Implicit_Heap_Allocations.
1229 Set_Comes_From_Source
1230 (Expression
(Temp_Decl
), Comes_From_Source
(N
));
1232 Set_No_Initialization
(Expression
(Temp_Decl
));
1233 Insert_Action
(N
, Temp_Decl
);
1235 Build_Allocate_Deallocate_Proc
(Temp_Decl
, True);
1236 Convert_Aggr_In_Allocator
(N
, Temp_Decl
, Exp
);
1238 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
1239 Analyze_And_Resolve
(N
, PtrT
);
1241 elsif Is_Access_Type
(T
) and then Can_Never_Be_Null
(T
) then
1242 Install_Null_Excluding_Check
(Exp
);
1244 elsif Is_Access_Type
(DesigT
)
1245 and then Nkind
(Exp
) = N_Allocator
1246 and then Nkind
(Expression
(Exp
)) /= N_Qualified_Expression
1248 -- Apply constraint to designated subtype indication
1250 Apply_Constraint_Check
1251 (Expression
(Exp
), Designated_Type
(DesigT
), No_Sliding
=> True);
1253 if Nkind
(Expression
(Exp
)) = N_Raise_Constraint_Error
then
1255 -- Propagate constraint_error to enclosing allocator
1257 Rewrite
(Exp
, New_Copy
(Expression
(Exp
)));
1261 Build_Allocate_Deallocate_Proc
(N
, True);
1263 -- For an access to unconstrained packed array, GIGI needs to see an
1264 -- expression with a constrained subtype in order to compute the
1265 -- proper size for the allocator.
1267 if Is_Packed_Array
(T
)
1268 and then not Is_Constrained
(T
)
1271 ConstrT
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A');
1272 Internal_Exp
: constant Node_Id
:= Relocate_Node
(Exp
);
1275 Make_Subtype_Declaration
(Loc
,
1276 Defining_Identifier
=> ConstrT
,
1277 Subtype_Indication
=>
1278 Make_Subtype_From_Expr
(Internal_Exp
, T
)));
1279 Freeze_Itype
(ConstrT
, Exp
);
1280 Rewrite
(Exp
, OK_Convert_To
(ConstrT
, Internal_Exp
));
1284 -- Ada 2005 (AI-318-02): If the initialization expression is a call
1285 -- to a build-in-place function, then access to the allocated object
1286 -- must be passed to the function.
1288 if Is_Build_In_Place_Function_Call
(Exp
) then
1289 Make_Build_In_Place_Call_In_Allocator
(N
, Exp
);
1294 when RE_Not_Available
=>
1296 end Expand_Allocator_Expression
;
1298 -----------------------------
1299 -- Expand_Array_Comparison --
1300 -----------------------------
1302 -- Expansion is only required in the case of array types. For the unpacked
1303 -- case, an appropriate runtime routine is called. For packed cases, and
1304 -- also in some other cases where a runtime routine cannot be called, the
1305 -- form of the expansion is:
1307 -- [body for greater_nn; boolean_expression]
1309 -- The body is built by Make_Array_Comparison_Op, and the form of the
1310 -- Boolean expression depends on the operator involved.
1312 procedure Expand_Array_Comparison
(N
: Node_Id
) is
1313 Loc
: constant Source_Ptr
:= Sloc
(N
);
1314 Op1
: Node_Id
:= Left_Opnd
(N
);
1315 Op2
: Node_Id
:= Right_Opnd
(N
);
1316 Typ1
: constant Entity_Id
:= Base_Type
(Etype
(Op1
));
1317 Ctyp
: constant Entity_Id
:= Component_Type
(Typ1
);
1320 Func_Body
: Node_Id
;
1321 Func_Name
: Entity_Id
;
1325 Byte_Addressable
: constant Boolean := System_Storage_Unit
= Byte
'Size;
1326 -- True for byte addressable target
1328 function Length_Less_Than_4
(Opnd
: Node_Id
) return Boolean;
1329 -- Returns True if the length of the given operand is known to be less
1330 -- than 4. Returns False if this length is known to be four or greater
1331 -- or is not known at compile time.
1333 ------------------------
1334 -- Length_Less_Than_4 --
1335 ------------------------
1337 function Length_Less_Than_4
(Opnd
: Node_Id
) return Boolean is
1338 Otyp
: constant Entity_Id
:= Etype
(Opnd
);
1341 if Ekind
(Otyp
) = E_String_Literal_Subtype
then
1342 return String_Literal_Length
(Otyp
) < 4;
1346 Ityp
: constant Entity_Id
:= Etype
(First_Index
(Otyp
));
1347 Lo
: constant Node_Id
:= Type_Low_Bound
(Ityp
);
1348 Hi
: constant Node_Id
:= Type_High_Bound
(Ityp
);
1353 if Compile_Time_Known_Value
(Lo
) then
1354 Lov
:= Expr_Value
(Lo
);
1359 if Compile_Time_Known_Value
(Hi
) then
1360 Hiv
:= Expr_Value
(Hi
);
1365 return Hiv
< Lov
+ 3;
1368 end Length_Less_Than_4
;
1370 -- Start of processing for Expand_Array_Comparison
1373 -- Deal first with unpacked case, where we can call a runtime routine
1374 -- except that we avoid this for targets for which are not addressable
1377 if not Is_Bit_Packed_Array
(Typ1
) and then Byte_Addressable
then
1378 -- The call we generate is:
1380 -- Compare_Array_xn[_Unaligned]
1381 -- (left'address, right'address, left'length, right'length) <op> 0
1383 -- x = U for unsigned, S for signed
1384 -- n = 8,16,32,64,128 for component size
1385 -- Add _Unaligned if length < 4 and component size is 8.
1386 -- <op> is the standard comparison operator
1388 if Component_Size
(Typ1
) = 8 then
1389 if Length_Less_Than_4
(Op1
)
1391 Length_Less_Than_4
(Op2
)
1393 if Is_Unsigned_Type
(Ctyp
) then
1394 Comp
:= RE_Compare_Array_U8_Unaligned
;
1396 Comp
:= RE_Compare_Array_S8_Unaligned
;
1400 if Is_Unsigned_Type
(Ctyp
) then
1401 Comp
:= RE_Compare_Array_U8
;
1403 Comp
:= RE_Compare_Array_S8
;
1407 elsif Component_Size
(Typ1
) = 16 then
1408 if Is_Unsigned_Type
(Ctyp
) then
1409 Comp
:= RE_Compare_Array_U16
;
1411 Comp
:= RE_Compare_Array_S16
;
1414 elsif Component_Size
(Typ1
) = 32 then
1415 if Is_Unsigned_Type
(Ctyp
) then
1416 Comp
:= RE_Compare_Array_U32
;
1418 Comp
:= RE_Compare_Array_S32
;
1421 elsif Component_Size
(Typ1
) = 64 then
1422 if Is_Unsigned_Type
(Ctyp
) then
1423 Comp
:= RE_Compare_Array_U64
;
1425 Comp
:= RE_Compare_Array_S64
;
1428 else pragma Assert
(Component_Size
(Typ1
) = 128);
1429 if Is_Unsigned_Type
(Ctyp
) then
1430 Comp
:= RE_Compare_Array_U128
;
1432 Comp
:= RE_Compare_Array_S128
;
1436 if RTE_Available
(Comp
) then
1438 -- Expand to a call only if the runtime function is available,
1439 -- otherwise fall back to inline code.
1441 Remove_Side_Effects
(Op1
, Name_Req
=> True);
1442 Remove_Side_Effects
(Op2
, Name_Req
=> True);
1445 Make_Function_Call
(Sloc
(Op1
),
1446 Name
=> New_Occurrence_Of
(RTE
(Comp
), Loc
),
1448 Parameter_Associations
=> New_List
(
1449 Make_Attribute_Reference
(Loc
,
1450 Prefix
=> Relocate_Node
(Op1
),
1451 Attribute_Name
=> Name_Address
),
1453 Make_Attribute_Reference
(Loc
,
1454 Prefix
=> Relocate_Node
(Op2
),
1455 Attribute_Name
=> Name_Address
),
1457 Make_Attribute_Reference
(Loc
,
1458 Prefix
=> Relocate_Node
(Op1
),
1459 Attribute_Name
=> Name_Length
),
1461 Make_Attribute_Reference
(Loc
,
1462 Prefix
=> Relocate_Node
(Op2
),
1463 Attribute_Name
=> Name_Length
))));
1466 Make_Integer_Literal
(Sloc
(Op2
),
1469 Analyze_And_Resolve
(Op1
, Standard_Integer
);
1470 Analyze_And_Resolve
(Op2
, Standard_Integer
);
1475 -- Cases where we cannot make runtime call
1477 -- For (a <= b) we convert to not (a > b)
1479 if Chars
(N
) = Name_Op_Le
then
1485 Right_Opnd
=> Op2
)));
1486 Analyze_And_Resolve
(N
, Standard_Boolean
);
1489 -- For < the Boolean expression is
1490 -- greater__nn (op2, op1)
1492 elsif Chars
(N
) = Name_Op_Lt
then
1493 Func_Body
:= Make_Array_Comparison_Op
(Typ1
, N
);
1497 Op1
:= Right_Opnd
(N
);
1498 Op2
:= Left_Opnd
(N
);
1500 -- For (a >= b) we convert to not (a < b)
1502 elsif Chars
(N
) = Name_Op_Ge
then
1508 Right_Opnd
=> Op2
)));
1509 Analyze_And_Resolve
(N
, Standard_Boolean
);
1512 -- For > the Boolean expression is
1513 -- greater__nn (op1, op2)
1516 pragma Assert
(Chars
(N
) = Name_Op_Gt
);
1517 Func_Body
:= Make_Array_Comparison_Op
(Typ1
, N
);
1520 Func_Name
:= Defining_Unit_Name
(Specification
(Func_Body
));
1522 Make_Function_Call
(Loc
,
1523 Name
=> New_Occurrence_Of
(Func_Name
, Loc
),
1524 Parameter_Associations
=> New_List
(Op1
, Op2
));
1526 Insert_Action
(N
, Func_Body
);
1528 Analyze_And_Resolve
(N
, Standard_Boolean
);
1529 end Expand_Array_Comparison
;
1531 ---------------------------
1532 -- Expand_Array_Equality --
1533 ---------------------------
1535 -- Expand an equality function for multi-dimensional arrays. Here is an
1536 -- example of such a function for Nb_Dimension = 2
1538 -- function Enn (A : atyp; B : btyp) return boolean is
1540 -- if (A'length (1) = 0 or else A'length (2) = 0)
1542 -- (B'length (1) = 0 or else B'length (2) = 0)
1544 -- return true; -- RM 4.5.2(22)
1547 -- if A'length (1) /= B'length (1)
1549 -- A'length (2) /= B'length (2)
1551 -- return false; -- RM 4.5.2(23)
1555 -- A1 : Index_T1 := A'first (1);
1556 -- B1 : Index_T1 := B'first (1);
1560 -- A2 : Index_T2 := A'first (2);
1561 -- B2 : Index_T2 := B'first (2);
1564 -- if A (A1, A2) /= B (B1, B2) then
1568 -- exit when A2 = A'last (2);
1569 -- A2 := Index_T2'succ (A2);
1570 -- B2 := Index_T2'succ (B2);
1574 -- exit when A1 = A'last (1);
1575 -- A1 := Index_T1'succ (A1);
1576 -- B1 := Index_T1'succ (B1);
1583 -- Note on the formal types used (atyp and btyp). If either of the arrays
1584 -- is of a private type, we use the underlying type, and do an unchecked
1585 -- conversion of the actual. If either of the arrays has a bound depending
1586 -- on a discriminant, then we use the base type since otherwise we have an
1587 -- escaped discriminant in the function.
1589 -- If both arrays are constrained and have the same bounds, we can generate
1590 -- a loop with an explicit iteration scheme using a 'Range attribute over
1593 function Expand_Array_Equality
1598 Typ
: Entity_Id
) return Node_Id
1600 Loc
: constant Source_Ptr
:= Sloc
(Nod
);
1601 Decls
: constant List_Id
:= New_List
;
1602 Index_List1
: constant List_Id
:= New_List
;
1603 Index_List2
: constant List_Id
:= New_List
;
1605 First_Idx
: Node_Id
;
1607 Func_Name
: Entity_Id
;
1608 Func_Body
: Node_Id
;
1610 A
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uA
);
1611 B
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uB
);
1615 -- The parameter types to be used for the formals
1619 -- The LHS and RHS converted to the parameter types
1624 Dim
: Pos
) return Node_Id
;
1625 -- This builds the attribute reference Arr'Nam (Dim)
1627 function Component_Equality
(Typ
: Entity_Id
) return Node_Id
;
1628 -- Create one statement to compare corresponding components, designated
1629 -- by a full set of indexes.
1631 function Get_Arg_Type
(N
: Node_Id
) return Entity_Id
;
1632 -- Given one of the arguments, computes the appropriate type to be used
1633 -- for that argument in the corresponding function formal
1635 function Handle_One_Dimension
1637 Index
: Node_Id
) return Node_Id
;
1638 -- This procedure returns the following code
1641 -- An : Index_T := A'First (N);
1642 -- Bn : Index_T := B'First (N);
1646 -- exit when An = A'Last (N);
1647 -- An := Index_T'Succ (An)
1648 -- Bn := Index_T'Succ (Bn)
1652 -- If both indexes are constrained and identical, the procedure
1653 -- returns a simpler loop:
1655 -- for An in A'Range (N) loop
1659 -- N is the dimension for which we are generating a loop. Index is the
1660 -- N'th index node, whose Etype is Index_Type_n in the above code. The
1661 -- xxx statement is either the loop or declare for the next dimension
1662 -- or if this is the last dimension the comparison of corresponding
1663 -- components of the arrays.
1665 -- The actual way the code works is to return the comparison of
1666 -- corresponding components for the N+1 call. That's neater.
1668 function Test_Empty_Arrays
return Node_Id
;
1669 -- This function constructs the test for both arrays being empty
1670 -- (A'length (1) = 0 or else A'length (2) = 0 or else ...)
1672 -- (B'length (1) = 0 or else B'length (2) = 0 or else ...)
1674 function Test_Lengths_Correspond
return Node_Id
;
1675 -- This function constructs the test for arrays having different lengths
1676 -- in at least one index position, in which case the resulting code is:
1678 -- A'length (1) /= B'length (1)
1680 -- A'length (2) /= B'length (2)
1691 Dim
: Pos
) return Node_Id
1695 Make_Attribute_Reference
(Loc
,
1696 Attribute_Name
=> Nam
,
1697 Prefix
=> New_Occurrence_Of
(Arr
, Loc
),
1698 Expressions
=> New_List
(Make_Integer_Literal
(Loc
, Dim
)));
1701 ------------------------
1702 -- Component_Equality --
1703 ------------------------
1705 function Component_Equality
(Typ
: Entity_Id
) return Node_Id
is
1710 -- if a(i1...) /= b(j1...) then return false; end if;
1713 Make_Indexed_Component
(Loc
,
1714 Prefix
=> Make_Identifier
(Loc
, Chars
(A
)),
1715 Expressions
=> Index_List1
);
1718 Make_Indexed_Component
(Loc
,
1719 Prefix
=> Make_Identifier
(Loc
, Chars
(B
)),
1720 Expressions
=> Index_List2
);
1722 Test
:= Expand_Composite_Equality
(Nod
, Component_Type
(Typ
), L
, R
);
1724 -- If some (sub)component is an unchecked_union, the whole operation
1725 -- will raise program error.
1727 if Nkind
(Test
) = N_Raise_Program_Error
then
1729 -- This node is going to be inserted at a location where a
1730 -- statement is expected: clear its Etype so analysis will set
1731 -- it to the expected Standard_Void_Type.
1733 Set_Etype
(Test
, Empty
);
1738 Make_Implicit_If_Statement
(Nod
,
1739 Condition
=> Make_Op_Not
(Loc
, Right_Opnd
=> Test
),
1740 Then_Statements
=> New_List
(
1741 Make_Simple_Return_Statement
(Loc
,
1742 Expression
=> New_Occurrence_Of
(Standard_False
, Loc
))));
1744 end Component_Equality
;
1750 function Get_Arg_Type
(N
: Node_Id
) return Entity_Id
is
1761 T
:= Underlying_Type
(T
);
1763 X
:= First_Index
(T
);
1764 while Present
(X
) loop
1765 if Denotes_Discriminant
(Type_Low_Bound
(Etype
(X
)))
1767 Denotes_Discriminant
(Type_High_Bound
(Etype
(X
)))
1780 --------------------------
1781 -- Handle_One_Dimension --
1782 ---------------------------
1784 function Handle_One_Dimension
1786 Index
: Node_Id
) return Node_Id
1788 Need_Separate_Indexes
: constant Boolean :=
1789 Ltyp
/= Rtyp
or else not Is_Constrained
(Ltyp
);
1790 -- If the index types are identical, and we are working with
1791 -- constrained types, then we can use the same index for both
1794 An
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A');
1797 Index_T
: Entity_Id
;
1802 if N
> Number_Dimensions
(Ltyp
) then
1803 return Component_Equality
(Ltyp
);
1806 -- Case where we generate a loop
1808 Index_T
:= Base_Type
(Etype
(Index
));
1810 if Need_Separate_Indexes
then
1811 Bn
:= Make_Temporary
(Loc
, 'B');
1816 Append
(New_Occurrence_Of
(An
, Loc
), Index_List1
);
1817 Append
(New_Occurrence_Of
(Bn
, Loc
), Index_List2
);
1819 Stm_List
:= New_List
(
1820 Handle_One_Dimension
(N
+ 1, Next_Index
(Index
)));
1822 if Need_Separate_Indexes
then
1824 -- Generate guard for loop, followed by increments of indexes
1826 Append_To
(Stm_List
,
1827 Make_Exit_Statement
(Loc
,
1830 Left_Opnd
=> New_Occurrence_Of
(An
, Loc
),
1831 Right_Opnd
=> Arr_Attr
(A
, Name_Last
, N
))));
1833 Append_To
(Stm_List
,
1834 Make_Assignment_Statement
(Loc
,
1835 Name
=> New_Occurrence_Of
(An
, Loc
),
1837 Make_Attribute_Reference
(Loc
,
1838 Prefix
=> New_Occurrence_Of
(Index_T
, Loc
),
1839 Attribute_Name
=> Name_Succ
,
1840 Expressions
=> New_List
(
1841 New_Occurrence_Of
(An
, Loc
)))));
1843 Append_To
(Stm_List
,
1844 Make_Assignment_Statement
(Loc
,
1845 Name
=> New_Occurrence_Of
(Bn
, Loc
),
1847 Make_Attribute_Reference
(Loc
,
1848 Prefix
=> New_Occurrence_Of
(Index_T
, Loc
),
1849 Attribute_Name
=> Name_Succ
,
1850 Expressions
=> New_List
(
1851 New_Occurrence_Of
(Bn
, Loc
)))));
1854 -- If separate indexes, we need a declare block for An and Bn, and a
1855 -- loop without an iteration scheme.
1857 if Need_Separate_Indexes
then
1859 Make_Implicit_Loop_Statement
(Nod
, Statements
=> Stm_List
);
1862 Make_Block_Statement
(Loc
,
1863 Declarations
=> New_List
(
1864 Make_Object_Declaration
(Loc
,
1865 Defining_Identifier
=> An
,
1866 Object_Definition
=> New_Occurrence_Of
(Index_T
, Loc
),
1867 Expression
=> Arr_Attr
(A
, Name_First
, N
)),
1869 Make_Object_Declaration
(Loc
,
1870 Defining_Identifier
=> Bn
,
1871 Object_Definition
=> New_Occurrence_Of
(Index_T
, Loc
),
1872 Expression
=> Arr_Attr
(B
, Name_First
, N
))),
1874 Handled_Statement_Sequence
=>
1875 Make_Handled_Sequence_Of_Statements
(Loc
,
1876 Statements
=> New_List
(Loop_Stm
)));
1878 -- If no separate indexes, return loop statement with explicit
1879 -- iteration scheme on its own.
1883 Make_Implicit_Loop_Statement
(Nod
,
1884 Statements
=> Stm_List
,
1886 Make_Iteration_Scheme
(Loc
,
1887 Loop_Parameter_Specification
=>
1888 Make_Loop_Parameter_Specification
(Loc
,
1889 Defining_Identifier
=> An
,
1890 Discrete_Subtype_Definition
=>
1891 Arr_Attr
(A
, Name_Range
, N
))));
1894 end Handle_One_Dimension
;
1896 -----------------------
1897 -- Test_Empty_Arrays --
1898 -----------------------
1900 function Test_Empty_Arrays
return Node_Id
is
1901 Alist
: Node_Id
:= Empty
;
1902 Blist
: Node_Id
:= Empty
;
1905 for J
in 1 .. Number_Dimensions
(Ltyp
) loop
1906 Evolve_Or_Else
(Alist
,
1908 Left_Opnd
=> Arr_Attr
(A
, Name_Length
, J
),
1909 Right_Opnd
=> Make_Integer_Literal
(Loc
, Uint_0
)));
1911 Evolve_Or_Else
(Blist
,
1913 Left_Opnd
=> Arr_Attr
(B
, Name_Length
, J
),
1914 Right_Opnd
=> Make_Integer_Literal
(Loc
, Uint_0
)));
1920 Right_Opnd
=> Blist
);
1921 end Test_Empty_Arrays
;
1923 -----------------------------
1924 -- Test_Lengths_Correspond --
1925 -----------------------------
1927 function Test_Lengths_Correspond
return Node_Id
is
1928 Result
: Node_Id
:= Empty
;
1931 for J
in 1 .. Number_Dimensions
(Ltyp
) loop
1932 Evolve_Or_Else
(Result
,
1934 Left_Opnd
=> Arr_Attr
(A
, Name_Length
, J
),
1935 Right_Opnd
=> Arr_Attr
(B
, Name_Length
, J
)));
1939 end Test_Lengths_Correspond
;
1941 -- Start of processing for Expand_Array_Equality
1944 Ltyp
:= Get_Arg_Type
(Lhs
);
1945 Rtyp
:= Get_Arg_Type
(Rhs
);
1947 -- For now, if the argument types are not the same, go to the base type,
1948 -- since the code assumes that the formals have the same type. This is
1949 -- fixable in future ???
1951 if Ltyp
/= Rtyp
then
1952 Ltyp
:= Base_Type
(Ltyp
);
1953 Rtyp
:= Base_Type
(Rtyp
);
1954 pragma Assert
(Ltyp
= Rtyp
);
1957 -- If the array type is distinct from the type of the arguments, it
1958 -- is the full view of a private type. Apply an unchecked conversion
1959 -- to ensure that analysis of the code below succeeds.
1962 or else Base_Type
(Etype
(Lhs
)) /= Base_Type
(Ltyp
)
1964 New_Lhs
:= OK_Convert_To
(Ltyp
, Lhs
);
1970 or else Base_Type
(Etype
(Rhs
)) /= Base_Type
(Rtyp
)
1972 New_Rhs
:= OK_Convert_To
(Rtyp
, Rhs
);
1977 First_Idx
:= First_Index
(Ltyp
);
1979 -- If optimization is enabled and the array boils down to a couple of
1980 -- consecutive elements, generate a simple conjunction of comparisons
1981 -- which should be easier to optimize by the code generator.
1983 if Optimization_Level
> 0
1984 and then Ltyp
= Rtyp
1985 and then Is_Constrained
(Ltyp
)
1986 and then Number_Dimensions
(Ltyp
) = 1
1987 and then Compile_Time_Known_Bounds
(Ltyp
)
1988 and then Expr_Value
(Type_High_Bound
(Etype
(First_Idx
))) =
1989 Expr_Value
(Type_Low_Bound
(Etype
(First_Idx
))) + 1
1992 Ctyp
: constant Entity_Id
:= Component_Type
(Ltyp
);
1993 Low_B
: constant Node_Id
:=
1994 Type_Low_Bound
(Etype
(First_Idx
));
1995 High_B
: constant Node_Id
:=
1996 Type_High_Bound
(Etype
(First_Idx
));
1998 TestL
, TestH
: Node_Id
;
2002 Make_Indexed_Component
(Loc
,
2003 Prefix
=> New_Copy_Tree
(New_Lhs
),
2004 Expressions
=> New_List
(New_Copy_Tree
(Low_B
)));
2007 Make_Indexed_Component
(Loc
,
2008 Prefix
=> New_Copy_Tree
(New_Rhs
),
2009 Expressions
=> New_List
(New_Copy_Tree
(Low_B
)));
2011 TestL
:= Expand_Composite_Equality
(Nod
, Ctyp
, L
, R
);
2014 Make_Indexed_Component
(Loc
,
2016 Expressions
=> New_List
(New_Copy_Tree
(High_B
)));
2019 Make_Indexed_Component
(Loc
,
2021 Expressions
=> New_List
(New_Copy_Tree
(High_B
)));
2023 TestH
:= Expand_Composite_Equality
(Nod
, Ctyp
, L
, R
);
2026 Make_And_Then
(Loc
, Left_Opnd
=> TestL
, Right_Opnd
=> TestH
);
2030 -- Build list of formals for function
2032 Formals
:= New_List
(
2033 Make_Parameter_Specification
(Loc
,
2034 Defining_Identifier
=> A
,
2035 Parameter_Type
=> New_Occurrence_Of
(Ltyp
, Loc
)),
2037 Make_Parameter_Specification
(Loc
,
2038 Defining_Identifier
=> B
,
2039 Parameter_Type
=> New_Occurrence_Of
(Rtyp
, Loc
)));
2041 Func_Name
:= Make_Temporary
(Loc
, 'E');
2043 -- Build statement sequence for function
2046 Make_Subprogram_Body
(Loc
,
2048 Make_Function_Specification
(Loc
,
2049 Defining_Unit_Name
=> Func_Name
,
2050 Parameter_Specifications
=> Formals
,
2051 Result_Definition
=> New_Occurrence_Of
(Standard_Boolean
, Loc
)),
2053 Declarations
=> Decls
,
2055 Handled_Statement_Sequence
=>
2056 Make_Handled_Sequence_Of_Statements
(Loc
,
2057 Statements
=> New_List
(
2059 Make_Implicit_If_Statement
(Nod
,
2060 Condition
=> Test_Empty_Arrays
,
2061 Then_Statements
=> New_List
(
2062 Make_Simple_Return_Statement
(Loc
,
2064 New_Occurrence_Of
(Standard_True
, Loc
)))),
2066 Make_Implicit_If_Statement
(Nod
,
2067 Condition
=> Test_Lengths_Correspond
,
2068 Then_Statements
=> New_List
(
2069 Make_Simple_Return_Statement
(Loc
,
2070 Expression
=> New_Occurrence_Of
(Standard_False
, Loc
)))),
2072 Handle_One_Dimension
(1, First_Idx
),
2074 Make_Simple_Return_Statement
(Loc
,
2075 Expression
=> New_Occurrence_Of
(Standard_True
, Loc
)))));
2077 Set_Has_Completion
(Func_Name
, True);
2078 Set_Is_Inlined
(Func_Name
);
2080 Append_To
(Bodies
, Func_Body
);
2083 Make_Function_Call
(Loc
,
2084 Name
=> New_Occurrence_Of
(Func_Name
, Loc
),
2085 Parameter_Associations
=> New_List
(New_Lhs
, New_Rhs
));
2086 end Expand_Array_Equality
;
2088 -----------------------------
2089 -- Expand_Boolean_Operator --
2090 -----------------------------
2092 -- Note that we first get the actual subtypes of the operands, since we
2093 -- always want to deal with types that have bounds.
2095 procedure Expand_Boolean_Operator
(N
: Node_Id
) is
2096 Typ
: constant Entity_Id
:= Etype
(N
);
2099 -- Special case of bit packed array where both operands are known to be
2100 -- properly aligned. In this case we use an efficient run time routine
2101 -- to carry out the operation (see System.Bit_Ops).
2103 if Is_Bit_Packed_Array
(Typ
)
2104 and then not Is_Possibly_Unaligned_Object
(Left_Opnd
(N
))
2105 and then not Is_Possibly_Unaligned_Object
(Right_Opnd
(N
))
2107 Expand_Packed_Boolean_Operator
(N
);
2111 -- For the normal non-packed case, the general expansion is to build
2112 -- function for carrying out the comparison (use Make_Boolean_Array_Op)
2113 -- and then inserting it into the tree. The original operator node is
2114 -- then rewritten as a call to this function. We also use this in the
2115 -- packed case if either operand is a possibly unaligned object.
2118 Loc
: constant Source_Ptr
:= Sloc
(N
);
2119 L
: constant Node_Id
:= Relocate_Node
(Left_Opnd
(N
));
2120 R
: Node_Id
:= Relocate_Node
(Right_Opnd
(N
));
2121 Func_Body
: Node_Id
;
2122 Func_Name
: Entity_Id
;
2125 Convert_To_Actual_Subtype
(L
);
2126 Convert_To_Actual_Subtype
(R
);
2127 Ensure_Defined
(Etype
(L
), N
);
2128 Ensure_Defined
(Etype
(R
), N
);
2129 Apply_Length_Check
(R
, Etype
(L
));
2131 if Nkind
(N
) = N_Op_Xor
then
2132 R
:= Duplicate_Subexpr
(R
);
2133 Silly_Boolean_Array_Xor_Test
(N
, R
, Etype
(L
));
2136 if Nkind
(Parent
(N
)) = N_Assignment_Statement
2137 and then Safe_In_Place_Array_Op
(Name
(Parent
(N
)), L
, R
)
2139 Build_Boolean_Array_Proc_Call
(Parent
(N
), L
, R
);
2141 elsif Nkind
(Parent
(N
)) = N_Op_Not
2142 and then Nkind
(N
) = N_Op_And
2143 and then Nkind
(Parent
(Parent
(N
))) = N_Assignment_Statement
2144 and then Safe_In_Place_Array_Op
(Name
(Parent
(Parent
(N
))), L
, R
)
2148 Func_Body
:= Make_Boolean_Array_Op
(Etype
(L
), N
);
2149 Func_Name
:= Defining_Unit_Name
(Specification
(Func_Body
));
2150 Insert_Action
(N
, Func_Body
);
2152 -- Now rewrite the expression with a call
2154 if Transform_Function_Array
then
2156 Temp_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T');
2165 Make_Object_Declaration
(Loc
,
2166 Defining_Identifier
=> Temp_Id
,
2167 Object_Definition
=>
2168 New_Occurrence_Of
(Etype
(L
), Loc
));
2171 -- Proc_Call (L, R, Temp);
2174 Make_Procedure_Call_Statement
(Loc
,
2175 Name
=> New_Occurrence_Of
(Func_Name
, Loc
),
2176 Parameter_Associations
=>
2179 Make_Type_Conversion
2180 (Loc
, New_Occurrence_Of
(Etype
(L
), Loc
), R
),
2181 New_Occurrence_Of
(Temp_Id
, Loc
)));
2183 Insert_Actions
(Parent
(N
), New_List
(Decl
, Call
));
2184 Rewrite
(N
, New_Occurrence_Of
(Temp_Id
, Loc
));
2188 Make_Function_Call
(Loc
,
2189 Name
=> New_Occurrence_Of
(Func_Name
, Loc
),
2190 Parameter_Associations
=>
2193 Make_Type_Conversion
2194 (Loc
, New_Occurrence_Of
(Etype
(L
), Loc
), R
))));
2197 Analyze_And_Resolve
(N
, Typ
);
2200 end Expand_Boolean_Operator
;
2202 ------------------------------------------------
2203 -- Expand_Compare_Minimize_Eliminate_Overflow --
2204 ------------------------------------------------
2206 procedure Expand_Compare_Minimize_Eliminate_Overflow
(N
: Node_Id
) is
2207 Loc
: constant Source_Ptr
:= Sloc
(N
);
2209 Result_Type
: constant Entity_Id
:= Etype
(N
);
2210 -- Capture result type (could be a derived boolean type)
2215 LLIB
: constant Entity_Id
:= Base_Type
(Standard_Long_Long_Integer
);
2216 -- Entity for Long_Long_Integer'Base
2219 procedure Set_False
;
2220 -- These procedures rewrite N with an occurrence of Standard_True or
2221 -- Standard_False, and then makes a call to Warn_On_Known_Condition.
2227 procedure Set_False
is
2229 Rewrite
(N
, New_Occurrence_Of
(Standard_False
, Loc
));
2230 Warn_On_Known_Condition
(N
);
2237 procedure Set_True
is
2239 Rewrite
(N
, New_Occurrence_Of
(Standard_True
, Loc
));
2240 Warn_On_Known_Condition
(N
);
2243 -- Start of processing for Expand_Compare_Minimize_Eliminate_Overflow
2246 -- OK, this is the case we are interested in. First step is to process
2247 -- our operands using the Minimize_Eliminate circuitry which applies
2248 -- this processing to the two operand subtrees.
2250 Minimize_Eliminate_Overflows
2251 (Left_Opnd
(N
), Llo
, Lhi
, Top_Level
=> False);
2252 Minimize_Eliminate_Overflows
2253 (Right_Opnd
(N
), Rlo
, Rhi
, Top_Level
=> False);
2255 -- See if the range information decides the result of the comparison.
2256 -- We can only do this if we in fact have full range information (which
2257 -- won't be the case if either operand is bignum at this stage).
2259 if Present
(Llo
) and then Present
(Rlo
) then
2260 case N_Op_Compare
(Nkind
(N
)) is
2262 if Llo
= Lhi
and then Rlo
= Rhi
and then Llo
= Rlo
then
2264 elsif Llo
> Rhi
or else Lhi
< Rlo
then
2271 elsif Lhi
< Rlo
then
2278 elsif Lhi
<= Rlo
then
2285 elsif Lhi
<= Rlo
then
2292 elsif Lhi
< Rlo
then
2297 if Llo
= Lhi
and then Rlo
= Rhi
and then Llo
= Rlo
then
2299 elsif Llo
> Rhi
or else Lhi
< Rlo
then
2304 -- All done if we did the rewrite
2306 if Nkind
(N
) not in N_Op_Compare
then
2311 -- Otherwise, time to do the comparison
2314 Ltype
: constant Entity_Id
:= Etype
(Left_Opnd
(N
));
2315 Rtype
: constant Entity_Id
:= Etype
(Right_Opnd
(N
));
2318 -- If the two operands have the same signed integer type we are
2319 -- all set, nothing more to do. This is the case where either
2320 -- both operands were unchanged, or we rewrote both of them to
2321 -- be Long_Long_Integer.
2323 -- Note: Entity for the comparison may be wrong, but it's not worth
2324 -- the effort to change it, since the back end does not use it.
2326 if Is_Signed_Integer_Type
(Ltype
)
2327 and then Base_Type
(Ltype
) = Base_Type
(Rtype
)
2331 -- Here if bignums are involved (can only happen in ELIMINATED mode)
2333 elsif Is_RTE
(Ltype
, RE_Bignum
) or else Is_RTE
(Rtype
, RE_Bignum
) then
2335 Left
: Node_Id
:= Left_Opnd
(N
);
2336 Right
: Node_Id
:= Right_Opnd
(N
);
2337 -- Bignum references for left and right operands
2340 if not Is_RTE
(Ltype
, RE_Bignum
) then
2341 Left
:= Convert_To_Bignum
(Left
);
2342 elsif not Is_RTE
(Rtype
, RE_Bignum
) then
2343 Right
:= Convert_To_Bignum
(Right
);
2346 -- We rewrite our node with:
2349 -- Bnn : Result_Type;
2351 -- M : Mark_Id := SS_Mark;
2353 -- Bnn := Big_xx (Left, Right); (xx = EQ, NT etc)
2361 Blk
: constant Node_Id
:= Make_Bignum_Block
(Loc
);
2362 Bnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'B', N
);
2366 case N_Op_Compare
(Nkind
(N
)) is
2367 when N_Op_Eq
=> Ent
:= RE_Big_EQ
;
2368 when N_Op_Ge
=> Ent
:= RE_Big_GE
;
2369 when N_Op_Gt
=> Ent
:= RE_Big_GT
;
2370 when N_Op_Le
=> Ent
:= RE_Big_LE
;
2371 when N_Op_Lt
=> Ent
:= RE_Big_LT
;
2372 when N_Op_Ne
=> Ent
:= RE_Big_NE
;
2375 -- Insert assignment to Bnn into the bignum block
2378 (First
(Statements
(Handled_Statement_Sequence
(Blk
))),
2379 Make_Assignment_Statement
(Loc
,
2380 Name
=> New_Occurrence_Of
(Bnn
, Loc
),
2382 Make_Function_Call
(Loc
,
2384 New_Occurrence_Of
(RTE
(Ent
), Loc
),
2385 Parameter_Associations
=> New_List
(Left
, Right
))));
2387 -- Now do the rewrite with expression actions
2390 Make_Expression_With_Actions
(Loc
,
2391 Actions
=> New_List
(
2392 Make_Object_Declaration
(Loc
,
2393 Defining_Identifier
=> Bnn
,
2394 Object_Definition
=>
2395 New_Occurrence_Of
(Result_Type
, Loc
)),
2397 Expression
=> New_Occurrence_Of
(Bnn
, Loc
)));
2398 Analyze_And_Resolve
(N
, Result_Type
);
2402 -- No bignums involved, but types are different, so we must have
2403 -- rewritten one of the operands as a Long_Long_Integer but not
2406 -- If left operand is Long_Long_Integer, convert right operand
2407 -- and we are done (with a comparison of two Long_Long_Integers).
2409 elsif Ltype
= LLIB
then
2410 Convert_To_And_Rewrite
(LLIB
, Right_Opnd
(N
));
2411 Analyze_And_Resolve
(Right_Opnd
(N
), LLIB
, Suppress
=> All_Checks
);
2414 -- If right operand is Long_Long_Integer, convert left operand
2415 -- and we are done (with a comparison of two Long_Long_Integers).
2417 -- This is the only remaining possibility
2419 else pragma Assert
(Rtype
= LLIB
);
2420 Convert_To_And_Rewrite
(LLIB
, Left_Opnd
(N
));
2421 Analyze_And_Resolve
(Left_Opnd
(N
), LLIB
, Suppress
=> All_Checks
);
2425 end Expand_Compare_Minimize_Eliminate_Overflow
;
2427 -------------------------------
2428 -- Expand_Composite_Equality --
2429 -------------------------------
2431 -- This function is only called for comparing internal fields of composite
2432 -- types when these fields are themselves composites. This is a special
2433 -- case because it is not possible to respect normal Ada visibility rules.
2435 function Expand_Composite_Equality
2439 Rhs
: Node_Id
) return Node_Id
2441 Loc
: constant Source_Ptr
:= Sloc
(Nod
);
2442 Full_Type
: Entity_Id
;
2446 if Is_Private_Type
(Typ
) then
2447 Full_Type
:= Underlying_Type
(Typ
);
2452 -- If the private type has no completion the context may be the
2453 -- expansion of a composite equality for a composite type with some
2454 -- still incomplete components. The expression will not be analyzed
2455 -- until the enclosing type is completed, at which point this will be
2456 -- properly expanded, unless there is a bona fide completion error.
2458 if No
(Full_Type
) then
2459 return Make_Op_Eq
(Loc
, Left_Opnd
=> Lhs
, Right_Opnd
=> Rhs
);
2462 Full_Type
:= Base_Type
(Full_Type
);
2464 -- When the base type itself is private, use the full view to expand
2465 -- the composite equality.
2467 if Is_Private_Type
(Full_Type
) then
2468 Full_Type
:= Underlying_Type
(Full_Type
);
2471 -- Case of tagged record types
2473 if Is_Tagged_Type
(Full_Type
) then
2474 Eq_Op
:= Find_Primitive_Eq
(Typ
);
2475 pragma Assert
(Present
(Eq_Op
));
2478 Make_Function_Call
(Loc
,
2479 Name
=> New_Occurrence_Of
(Eq_Op
, Loc
),
2480 Parameter_Associations
=>
2482 (Unchecked_Convert_To
(Etype
(First_Formal
(Eq_Op
)), Lhs
),
2483 Unchecked_Convert_To
(Etype
(First_Formal
(Eq_Op
)), Rhs
)));
2485 -- Case of untagged record types
2487 elsif Is_Record_Type
(Full_Type
) then
2488 Eq_Op
:= TSS
(Full_Type
, TSS_Composite_Equality
);
2490 if Present
(Eq_Op
) then
2491 if Etype
(First_Formal
(Eq_Op
)) /= Full_Type
then
2493 -- Inherited equality from parent type. Convert the actuals to
2494 -- match signature of operation.
2497 T
: constant Entity_Id
:= Etype
(First_Formal
(Eq_Op
));
2501 Make_Function_Call
(Loc
,
2502 Name
=> New_Occurrence_Of
(Eq_Op
, Loc
),
2503 Parameter_Associations
=> New_List
(
2504 OK_Convert_To
(T
, Lhs
),
2505 OK_Convert_To
(T
, Rhs
)));
2509 -- Comparison between Unchecked_Union components
2511 if Is_Unchecked_Union
(Full_Type
) then
2513 Lhs_Type
: Node_Id
:= Full_Type
;
2514 Rhs_Type
: Node_Id
:= Full_Type
;
2515 Lhs_Discr_Val
: Node_Id
;
2516 Rhs_Discr_Val
: Node_Id
;
2521 if Nkind
(Lhs
) = N_Selected_Component
then
2522 Lhs_Type
:= Etype
(Entity
(Selector_Name
(Lhs
)));
2527 if Nkind
(Rhs
) = N_Selected_Component
then
2528 Rhs_Type
:= Etype
(Entity
(Selector_Name
(Rhs
)));
2531 -- Lhs of the composite equality
2533 if Is_Constrained
(Lhs_Type
) then
2535 -- Since the enclosing record type can never be an
2536 -- Unchecked_Union (this code is executed for records
2537 -- that do not have variants), we may reference its
2540 if Nkind
(Lhs
) = N_Selected_Component
2541 and then Has_Per_Object_Constraint
2542 (Entity
(Selector_Name
(Lhs
)))
2545 Make_Selected_Component
(Loc
,
2546 Prefix
=> Prefix
(Lhs
),
2549 (Get_Discriminant_Value
2550 (First_Discriminant
(Lhs_Type
),
2552 Stored_Constraint
(Lhs_Type
))));
2557 (Get_Discriminant_Value
2558 (First_Discriminant
(Lhs_Type
),
2560 Stored_Constraint
(Lhs_Type
)));
2564 -- It is not possible to infer the discriminant since
2565 -- the subtype is not constrained.
2568 Make_Raise_Program_Error
(Loc
,
2569 Reason
=> PE_Unchecked_Union_Restriction
);
2572 -- Rhs of the composite equality
2574 if Is_Constrained
(Rhs_Type
) then
2575 if Nkind
(Rhs
) = N_Selected_Component
2576 and then Has_Per_Object_Constraint
2577 (Entity
(Selector_Name
(Rhs
)))
2580 Make_Selected_Component
(Loc
,
2581 Prefix
=> Prefix
(Rhs
),
2584 (Get_Discriminant_Value
2585 (First_Discriminant
(Rhs_Type
),
2587 Stored_Constraint
(Rhs_Type
))));
2592 (Get_Discriminant_Value
2593 (First_Discriminant
(Rhs_Type
),
2595 Stored_Constraint
(Rhs_Type
)));
2600 Make_Raise_Program_Error
(Loc
,
2601 Reason
=> PE_Unchecked_Union_Restriction
);
2604 -- Call the TSS equality function with the inferred
2605 -- discriminant values.
2608 Make_Function_Call
(Loc
,
2609 Name
=> New_Occurrence_Of
(Eq_Op
, Loc
),
2610 Parameter_Associations
=> New_List
(
2617 -- All cases other than comparing Unchecked_Union types
2621 T
: constant Entity_Id
:= Etype
(First_Formal
(Eq_Op
));
2624 Make_Function_Call
(Loc
,
2626 New_Occurrence_Of
(Eq_Op
, Loc
),
2627 Parameter_Associations
=> New_List
(
2628 OK_Convert_To
(T
, Lhs
),
2629 OK_Convert_To
(T
, Rhs
)));
2634 -- Equality composes in Ada 2012 for untagged record types. It also
2635 -- composes for bounded strings, because they are part of the
2636 -- predefined environment. We could make it compose for bounded
2637 -- strings by making them tagged, or by making sure all subcomponents
2638 -- are set to the same value, even when not used. Instead, we have
2639 -- this special case in the compiler, because it's more efficient.
2641 elsif Ada_Version
>= Ada_2012
or else Is_Bounded_String
(Typ
) then
2643 -- If no TSS has been created for the type, check whether there is
2644 -- a primitive equality declared for it.
2647 Op
: constant Node_Id
:= Build_Eq_Call
(Typ
, Loc
, Lhs
, Rhs
);
2650 -- Use user-defined primitive if it exists, otherwise use
2651 -- predefined equality.
2653 if Present
(Op
) then
2656 return Make_Op_Eq
(Loc
, Lhs
, Rhs
);
2661 return Expand_Record_Equality
(Nod
, Full_Type
, Lhs
, Rhs
);
2664 -- Case of non-record types (always use predefined equality)
2667 return Make_Op_Eq
(Loc
, Left_Opnd
=> Lhs
, Right_Opnd
=> Rhs
);
2669 end Expand_Composite_Equality
;
2671 ------------------------
2672 -- Expand_Concatenate --
2673 ------------------------
2675 procedure Expand_Concatenate
(Cnode
: Node_Id
; Opnds
: List_Id
) is
2676 Loc
: constant Source_Ptr
:= Sloc
(Cnode
);
2678 Atyp
: constant Entity_Id
:= Base_Type
(Etype
(Cnode
));
2679 -- Result type of concatenation
2681 Ctyp
: constant Entity_Id
:= Base_Type
(Component_Type
(Etype
(Cnode
)));
2682 -- Component type. Elements of this component type can appear as one
2683 -- of the operands of concatenation as well as arrays.
2685 Istyp
: constant Entity_Id
:= Etype
(First_Index
(Atyp
));
2688 Ityp
: constant Entity_Id
:= Base_Type
(Istyp
);
2689 -- Index type. This is the base type of the index subtype, and is used
2690 -- for all computed bounds (which may be out of range of Istyp in the
2691 -- case of null ranges).
2694 -- This is the type we use to do arithmetic to compute the bounds and
2695 -- lengths of operands. The choice of this type is a little subtle and
2696 -- is discussed in a separate section at the start of the body code.
2698 Concatenation_Error
: exception;
2699 -- Raised if concatenation is sure to raise a CE
2701 Result_May_Be_Null
: Boolean := True;
2702 -- Reset to False if at least one operand is encountered which is known
2703 -- at compile time to be non-null. Used for handling the special case
2704 -- of setting the high bound to the last operand high bound for a null
2705 -- result, thus ensuring a proper high bound in the super-flat case.
2707 N
: constant Nat
:= List_Length
(Opnds
);
2708 -- Number of concatenation operands including possibly null operands
2711 -- Number of operands excluding any known to be null, except that the
2712 -- last operand is always retained, in case it provides the bounds for
2715 Opnd
: Node_Id
:= Empty
;
2716 -- Current operand being processed in the loop through operands. After
2717 -- this loop is complete, always contains the last operand (which is not
2718 -- the same as Operands (NN), since null operands are skipped).
2720 -- Arrays describing the operands, only the first NN entries of each
2721 -- array are set (NN < N when we exclude known null operands).
2723 Is_Fixed_Length
: array (1 .. N
) of Boolean;
2724 -- True if length of corresponding operand known at compile time
2726 Operands
: array (1 .. N
) of Node_Id
;
2727 -- Set to the corresponding entry in the Opnds list (but note that null
2728 -- operands are excluded, so not all entries in the list are stored).
2730 Fixed_Length
: array (1 .. N
) of Uint
;
2731 -- Set to length of operand. Entries in this array are set only if the
2732 -- corresponding entry in Is_Fixed_Length is True.
2734 Opnd_Low_Bound
: array (1 .. N
) of Node_Id
;
2735 -- Set to lower bound of operand. Either an integer literal in the case
2736 -- where the bound is known at compile time, else actual lower bound.
2737 -- The operand low bound is of type Ityp.
2739 Var_Length
: array (1 .. N
) of Entity_Id
;
2740 -- Set to an entity of type Natural that contains the length of an
2741 -- operand whose length is not known at compile time. Entries in this
2742 -- array are set only if the corresponding entry in Is_Fixed_Length
2743 -- is False. The entity is of type Artyp.
2745 Aggr_Length
: array (0 .. N
) of Node_Id
;
2746 -- The J'th entry in an expression node that represents the total length
2747 -- of operands 1 through J. It is either an integer literal node, or a
2748 -- reference to a constant entity with the right value, so it is fine
2749 -- to just do a Copy_Node to get an appropriate copy. The extra zeroth
2750 -- entry always is set to zero. The length is of type Artyp.
2752 Low_Bound
: Node_Id
:= Empty
;
2753 -- A tree node representing the low bound of the result (of type Ityp).
2754 -- This is either an integer literal node, or an identifier reference to
2755 -- a constant entity initialized to the appropriate value.
2757 Last_Opnd_Low_Bound
: Node_Id
:= Empty
;
2758 -- A tree node representing the low bound of the last operand. This
2759 -- need only be set if the result could be null. It is used for the
2760 -- special case of setting the right low bound for a null result.
2761 -- This is of type Ityp.
2763 Last_Opnd_High_Bound
: Node_Id
:= Empty
;
2764 -- A tree node representing the high bound of the last operand. This
2765 -- need only be set if the result could be null. It is used for the
2766 -- special case of setting the right high bound for a null result.
2767 -- This is of type Ityp.
2769 High_Bound
: Node_Id
:= Empty
;
2770 -- A tree node representing the high bound of the result (of type Ityp)
2772 Result
: Node_Id
:= Empty
;
2773 -- Result of the concatenation (of type Ityp)
2775 Actions
: constant List_Id
:= New_List
;
2776 -- Collect actions to be inserted
2778 Known_Non_Null_Operand_Seen
: Boolean;
2779 -- Set True during generation of the assignments of operands into
2780 -- result once an operand known to be non-null has been seen.
2782 function Library_Level_Target
return Boolean;
2783 -- Return True if the concatenation is within the expression of the
2784 -- declaration of a library-level object.
2786 function Make_Artyp_Literal
(Val
: Nat
) return Node_Id
;
2787 -- This function makes an N_Integer_Literal node that is returned in
2788 -- analyzed form with the type set to Artyp. Importantly this literal
2789 -- is not flagged as static, so that if we do computations with it that
2790 -- result in statically detected out of range conditions, we will not
2791 -- generate error messages but instead warning messages.
2793 function To_Artyp
(X
: Node_Id
) return Node_Id
;
2794 -- Given a node of type Ityp, returns the corresponding value of type
2795 -- Artyp. For non-enumeration types, this is a plain integer conversion.
2796 -- For enum types, the Pos of the value is returned.
2798 function To_Ityp
(X
: Node_Id
) return Node_Id
;
2799 -- The inverse function (uses Val in the case of enumeration types)
2801 --------------------------
2802 -- Library_Level_Target --
2803 --------------------------
2805 function Library_Level_Target
return Boolean is
2806 P
: Node_Id
:= Parent
(Cnode
);
2809 while Present
(P
) loop
2810 if Nkind
(P
) = N_Object_Declaration
then
2811 return Is_Library_Level_Entity
(Defining_Identifier
(P
));
2813 -- Prevent the search from going too far
2815 elsif Is_Body_Or_Package_Declaration
(P
) then
2823 end Library_Level_Target
;
2825 ------------------------
2826 -- Make_Artyp_Literal --
2827 ------------------------
2829 function Make_Artyp_Literal
(Val
: Nat
) return Node_Id
is
2830 Result
: constant Node_Id
:= Make_Integer_Literal
(Loc
, Val
);
2832 Set_Etype
(Result
, Artyp
);
2833 Set_Analyzed
(Result
, True);
2834 Set_Is_Static_Expression
(Result
, False);
2836 end Make_Artyp_Literal
;
2842 function To_Artyp
(X
: Node_Id
) return Node_Id
is
2844 if Ityp
= Base_Type
(Artyp
) then
2847 elsif Is_Enumeration_Type
(Ityp
) then
2849 Make_Attribute_Reference
(Loc
,
2850 Prefix
=> New_Occurrence_Of
(Ityp
, Loc
),
2851 Attribute_Name
=> Name_Pos
,
2852 Expressions
=> New_List
(X
));
2855 return Convert_To
(Artyp
, X
);
2863 function To_Ityp
(X
: Node_Id
) return Node_Id
is
2865 if Is_Enumeration_Type
(Ityp
) then
2867 Make_Attribute_Reference
(Loc
,
2868 Prefix
=> New_Occurrence_Of
(Ityp
, Loc
),
2869 Attribute_Name
=> Name_Val
,
2870 Expressions
=> New_List
(X
));
2872 -- Case where we will do a type conversion
2875 if Ityp
= Base_Type
(Artyp
) then
2878 return Convert_To
(Ityp
, X
);
2883 -- Local Declarations
2885 Opnd_Typ
: Entity_Id
;
2886 Subtyp_Ind
: Entity_Id
;
2893 -- Start of processing for Expand_Concatenate
2896 -- Choose an appropriate computational type
2898 -- We will be doing calculations of lengths and bounds in this routine
2899 -- and computing one from the other in some cases, e.g. getting the high
2900 -- bound by adding the length-1 to the low bound.
2902 -- We can't just use the index type, or even its base type for this
2903 -- purpose for two reasons. First it might be an enumeration type which
2904 -- is not suitable for computations of any kind, and second it may
2905 -- simply not have enough range. For example if the index type is
2906 -- -128..+127 then lengths can be up to 256, which is out of range of
2909 -- For enumeration types, we can simply use Standard_Integer, this is
2910 -- sufficient since the actual number of enumeration literals cannot
2911 -- possibly exceed the range of integer (remember we will be doing the
2912 -- arithmetic with POS values, not representation values).
2914 if Is_Enumeration_Type
(Ityp
) then
2915 Artyp
:= Standard_Integer
;
2917 -- For modular types, we use a 32-bit modular type for types whose size
2918 -- is in the range 1-31 bits. For 32-bit unsigned types, we use the
2919 -- identity type, and for larger unsigned types we use a 64-bit type.
2921 elsif Is_Modular_Integer_Type
(Ityp
) then
2922 if RM_Size
(Ityp
) < Standard_Integer_Size
then
2923 Artyp
:= Standard_Unsigned
;
2924 elsif RM_Size
(Ityp
) = Standard_Integer_Size
then
2927 Artyp
:= Standard_Long_Long_Unsigned
;
2930 -- Similar treatment for signed types
2933 if RM_Size
(Ityp
) < Standard_Integer_Size
then
2934 Artyp
:= Standard_Integer
;
2935 elsif RM_Size
(Ityp
) = Standard_Integer_Size
then
2938 Artyp
:= Standard_Long_Long_Integer
;
2942 -- Supply dummy entry at start of length array
2944 Aggr_Length
(0) := Make_Artyp_Literal
(0);
2946 -- Go through operands setting up the above arrays
2950 Opnd
:= Remove_Head
(Opnds
);
2951 Opnd_Typ
:= Etype
(Opnd
);
2953 -- The parent got messed up when we put the operands in a list,
2954 -- so now put back the proper parent for the saved operand, that
2955 -- is to say the concatenation node, to make sure that each operand
2956 -- is seen as a subexpression, e.g. if actions must be inserted.
2958 Set_Parent
(Opnd
, Cnode
);
2960 -- Set will be True when we have setup one entry in the array
2964 -- Singleton element (or character literal) case
2966 if Base_Type
(Opnd_Typ
) = Ctyp
then
2968 Operands
(NN
) := Opnd
;
2969 Is_Fixed_Length
(NN
) := True;
2970 Fixed_Length
(NN
) := Uint_1
;
2971 Result_May_Be_Null
:= False;
2973 -- Set low bound of operand (no need to set Last_Opnd_High_Bound
2974 -- since we know that the result cannot be null).
2976 Opnd_Low_Bound
(NN
) :=
2977 Make_Attribute_Reference
(Loc
,
2978 Prefix
=> New_Occurrence_Of
(Istyp
, Loc
),
2979 Attribute_Name
=> Name_First
);
2983 -- String literal case (can only occur for strings of course)
2985 elsif Nkind
(Opnd
) = N_String_Literal
then
2986 Len
:= String_Literal_Length
(Opnd_Typ
);
2989 Result_May_Be_Null
:= False;
2992 -- Capture last operand low and high bound if result could be null
2994 if J
= N
and then Result_May_Be_Null
then
2995 Last_Opnd_Low_Bound
:=
2996 New_Copy_Tree
(String_Literal_Low_Bound
(Opnd_Typ
));
2998 Last_Opnd_High_Bound
:=
2999 Make_Op_Subtract
(Loc
,
3001 New_Copy_Tree
(String_Literal_Low_Bound
(Opnd_Typ
)),
3002 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1));
3005 -- Skip null string literal
3007 if J
< N
and then Len
= 0 then
3012 Operands
(NN
) := Opnd
;
3013 Is_Fixed_Length
(NN
) := True;
3015 -- Set length and bounds
3017 Fixed_Length
(NN
) := Len
;
3019 Opnd_Low_Bound
(NN
) :=
3020 New_Copy_Tree
(String_Literal_Low_Bound
(Opnd_Typ
));
3027 -- Check constrained case with known bounds
3029 if Is_Constrained
(Opnd_Typ
) then
3031 Index
: constant Node_Id
:= First_Index
(Opnd_Typ
);
3032 Indx_Typ
: constant Entity_Id
:= Etype
(Index
);
3033 Lo
: constant Node_Id
:= Type_Low_Bound
(Indx_Typ
);
3034 Hi
: constant Node_Id
:= Type_High_Bound
(Indx_Typ
);
3037 -- Fixed length constrained array type with known at compile
3038 -- time bounds is last case of fixed length operand.
3040 if Compile_Time_Known_Value
(Lo
)
3042 Compile_Time_Known_Value
(Hi
)
3045 Loval
: constant Uint
:= Expr_Value
(Lo
);
3046 Hival
: constant Uint
:= Expr_Value
(Hi
);
3047 Len
: constant Uint
:=
3048 UI_Max
(Hival
- Loval
+ 1, Uint_0
);
3052 Result_May_Be_Null
:= False;
3055 -- Capture last operand bounds if result could be null
3057 if J
= N
and then Result_May_Be_Null
then
3058 Last_Opnd_Low_Bound
:=
3060 Make_Integer_Literal
(Loc
, Expr_Value
(Lo
)));
3062 Last_Opnd_High_Bound
:=
3064 Make_Integer_Literal
(Loc
, Expr_Value
(Hi
)));
3067 -- Exclude null length case unless last operand
3069 if J
< N
and then Len
= 0 then
3074 Operands
(NN
) := Opnd
;
3075 Is_Fixed_Length
(NN
) := True;
3076 Fixed_Length
(NN
) := Len
;
3078 Opnd_Low_Bound
(NN
) :=
3080 (Make_Integer_Literal
(Loc
, Expr_Value
(Lo
)));
3087 -- All cases where the length is not known at compile time, or the
3088 -- special case of an operand which is known to be null but has a
3089 -- lower bound other than 1 or is other than a string type.
3094 -- Capture operand bounds
3096 Opnd_Low_Bound
(NN
) :=
3097 Make_Attribute_Reference
(Loc
,
3099 Duplicate_Subexpr
(Opnd
, Name_Req
=> True),
3100 Attribute_Name
=> Name_First
);
3102 -- Capture last operand bounds if result could be null
3104 if J
= N
and Result_May_Be_Null
then
3105 Last_Opnd_Low_Bound
:=
3107 Make_Attribute_Reference
(Loc
,
3109 Duplicate_Subexpr
(Opnd
, Name_Req
=> True),
3110 Attribute_Name
=> Name_First
));
3112 Last_Opnd_High_Bound
:=
3114 Make_Attribute_Reference
(Loc
,
3116 Duplicate_Subexpr
(Opnd
, Name_Req
=> True),
3117 Attribute_Name
=> Name_Last
));
3120 -- Capture length of operand in entity
3122 Operands
(NN
) := Opnd
;
3123 Is_Fixed_Length
(NN
) := False;
3125 Var_Length
(NN
) := Make_Temporary
(Loc
, 'L');
3128 Make_Object_Declaration
(Loc
,
3129 Defining_Identifier
=> Var_Length
(NN
),
3130 Constant_Present
=> True,
3131 Object_Definition
=> New_Occurrence_Of
(Artyp
, Loc
),
3133 Make_Attribute_Reference
(Loc
,
3135 Duplicate_Subexpr
(Opnd
, Name_Req
=> True),
3136 Attribute_Name
=> Name_Length
)));
3140 -- Set next entry in aggregate length array
3142 -- For first entry, make either integer literal for fixed length
3143 -- or a reference to the saved length for variable length.
3146 if Is_Fixed_Length
(1) then
3147 Aggr_Length
(1) := Make_Integer_Literal
(Loc
, Fixed_Length
(1));
3149 Aggr_Length
(1) := New_Occurrence_Of
(Var_Length
(1), Loc
);
3152 -- If entry is fixed length and only fixed lengths so far, make
3153 -- appropriate new integer literal adding new length.
3155 elsif Is_Fixed_Length
(NN
)
3156 and then Nkind
(Aggr_Length
(NN
- 1)) = N_Integer_Literal
3159 Make_Integer_Literal
(Loc
,
3160 Intval
=> Fixed_Length
(NN
) + Intval
(Aggr_Length
(NN
- 1)));
3162 -- All other cases, construct an addition node for the length and
3163 -- create an entity initialized to this length.
3166 Ent
:= Make_Temporary
(Loc
, 'L');
3168 if Is_Fixed_Length
(NN
) then
3169 Clen
:= Make_Integer_Literal
(Loc
, Fixed_Length
(NN
));
3171 Clen
:= New_Occurrence_Of
(Var_Length
(NN
), Loc
);
3175 Make_Object_Declaration
(Loc
,
3176 Defining_Identifier
=> Ent
,
3177 Constant_Present
=> True,
3178 Object_Definition
=> New_Occurrence_Of
(Artyp
, Loc
),
3181 Left_Opnd
=> New_Copy_Tree
(Aggr_Length
(NN
- 1)),
3182 Right_Opnd
=> Clen
)));
3184 Aggr_Length
(NN
) := Make_Identifier
(Loc
, Chars
=> Chars
(Ent
));
3191 -- If we have only skipped null operands, return the last operand
3198 -- If we have only one non-null operand, return it and we are done.
3199 -- There is one case in which this cannot be done, and that is when
3200 -- the sole operand is of the element type, in which case it must be
3201 -- converted to an array, and the easiest way of doing that is to go
3202 -- through the normal general circuit.
3204 if NN
= 1 and then Base_Type
(Etype
(Operands
(1))) /= Ctyp
then
3205 Result
:= Operands
(1);
3209 -- Cases where we have a real concatenation
3211 -- Next step is to find the low bound for the result array that we
3212 -- will allocate. The rules for this are in (RM 4.5.6(5-7)).
3214 -- If the ultimate ancestor of the index subtype is a constrained array
3215 -- definition, then the lower bound is that of the index subtype as
3216 -- specified by (RM 4.5.3(6)).
3218 -- The right test here is to go to the root type, and then the ultimate
3219 -- ancestor is the first subtype of this root type.
3221 if Is_Constrained
(First_Subtype
(Root_Type
(Atyp
))) then
3223 Make_Attribute_Reference
(Loc
,
3225 New_Occurrence_Of
(First_Subtype
(Root_Type
(Atyp
)), Loc
),
3226 Attribute_Name
=> Name_First
);
3228 -- If the first operand in the list has known length we know that
3229 -- the lower bound of the result is the lower bound of this operand.
3231 elsif Is_Fixed_Length
(1) then
3232 Low_Bound
:= Opnd_Low_Bound
(1);
3234 -- OK, we don't know the lower bound, we have to build a horrible
3235 -- if expression node of the form
3237 -- if Cond1'Length /= 0 then
3240 -- if Opnd2'Length /= 0 then
3245 -- The nesting ends either when we hit an operand whose length is known
3246 -- at compile time, or on reaching the last operand, whose low bound we
3247 -- take unconditionally whether or not it is null. It's easiest to do
3248 -- this with a recursive procedure:
3252 function Get_Known_Bound
(J
: Nat
) return Node_Id
;
3253 -- Returns the lower bound determined by operands J .. NN
3255 ---------------------
3256 -- Get_Known_Bound --
3257 ---------------------
3259 function Get_Known_Bound
(J
: Nat
) return Node_Id
is
3261 if Is_Fixed_Length
(J
) or else J
= NN
then
3262 return New_Copy_Tree
(Opnd_Low_Bound
(J
));
3266 Make_If_Expression
(Loc
,
3267 Expressions
=> New_List
(
3271 New_Occurrence_Of
(Var_Length
(J
), Loc
),
3273 Make_Integer_Literal
(Loc
, 0)),
3275 New_Copy_Tree
(Opnd_Low_Bound
(J
)),
3276 Get_Known_Bound
(J
+ 1)));
3278 end Get_Known_Bound
;
3281 Ent
:= Make_Temporary
(Loc
, 'L');
3284 Make_Object_Declaration
(Loc
,
3285 Defining_Identifier
=> Ent
,
3286 Constant_Present
=> True,
3287 Object_Definition
=> New_Occurrence_Of
(Ityp
, Loc
),
3288 Expression
=> Get_Known_Bound
(1)));
3290 Low_Bound
:= New_Occurrence_Of
(Ent
, Loc
);
3294 pragma Assert
(Present
(Low_Bound
));
3296 -- Now we can safely compute the upper bound, normally
3297 -- Low_Bound + Length - 1.
3302 Left_Opnd
=> To_Artyp
(New_Copy_Tree
(Low_Bound
)),
3304 Make_Op_Subtract
(Loc
,
3305 Left_Opnd
=> New_Copy_Tree
(Aggr_Length
(NN
)),
3306 Right_Opnd
=> Make_Artyp_Literal
(1))));
3308 -- Note that calculation of the high bound may cause overflow in some
3309 -- very weird cases, so in the general case we need an overflow check on
3310 -- the high bound. We can avoid this for the common case of string types
3311 -- and other types whose index is Positive, since we chose a wider range
3312 -- for the arithmetic type. If checks are suppressed we do not set the
3313 -- flag, and possibly superfluous warnings will be omitted.
3315 if Istyp
/= Standard_Positive
3316 and then not Overflow_Checks_Suppressed
(Istyp
)
3318 Activate_Overflow_Check
(High_Bound
);
3321 -- Handle the exceptional case where the result is null, in which case
3322 -- case the bounds come from the last operand (so that we get the proper
3323 -- bounds if the last operand is super-flat).
3325 if Result_May_Be_Null
then
3327 Make_If_Expression
(Loc
,
3328 Expressions
=> New_List
(
3330 Left_Opnd
=> New_Copy_Tree
(Aggr_Length
(NN
)),
3331 Right_Opnd
=> Make_Artyp_Literal
(0)),
3332 Last_Opnd_Low_Bound
,
3336 Make_If_Expression
(Loc
,
3337 Expressions
=> New_List
(
3339 Left_Opnd
=> New_Copy_Tree
(Aggr_Length
(NN
)),
3340 Right_Opnd
=> Make_Artyp_Literal
(0)),
3341 Last_Opnd_High_Bound
,
3345 -- Here is where we insert the saved up actions
3347 Insert_Actions
(Cnode
, Actions
, Suppress
=> All_Checks
);
3349 -- Now we construct an array object with appropriate bounds. We mark
3350 -- the target as internal to prevent useless initialization when
3351 -- Initialize_Scalars is enabled. Also since this is the actual result
3352 -- entity, we make sure we have debug information for the result.
3355 Make_Subtype_Indication
(Loc
,
3356 Subtype_Mark
=> New_Occurrence_Of
(Atyp
, Loc
),
3358 Make_Index_Or_Discriminant_Constraint
(Loc
,
3359 Constraints
=> New_List
(
3361 Low_Bound
=> Low_Bound
,
3362 High_Bound
=> High_Bound
))));
3364 Ent
:= Make_Temporary
(Loc
, 'S');
3365 Set_Is_Internal
(Ent
);
3366 Set_Debug_Info_Needed
(Ent
);
3368 -- If we are concatenating strings and the current scope already uses
3369 -- the secondary stack, allocate the resulting string also on the
3370 -- secondary stack to avoid putting too much pressure on the primary
3372 -- Don't do this if -gnatd.h is set, as this will break the wrapping of
3373 -- Cnode in an Expression_With_Actions, see Expand_N_Op_Concat.
3375 if Atyp
= Standard_String
3376 and then Uses_Sec_Stack
(Current_Scope
)
3377 and then RTE_Available
(RE_SS_Pool
)
3378 and then not Debug_Flag_Dot_H
3381 -- subtype Axx is ...;
3382 -- type Ayy is access Axx;
3383 -- Rxx : Ayy := new <subtype> [storage_pool = ss_pool];
3384 -- Sxx : <subtype> renames Rxx.all;
3388 ConstrT
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A');
3389 Acc_Typ
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A');
3393 Insert_Action
(Cnode
,
3394 Make_Subtype_Declaration
(Loc
,
3395 Defining_Identifier
=> ConstrT
,
3396 Subtype_Indication
=> Subtyp_Ind
),
3397 Suppress
=> All_Checks
);
3398 Freeze_Itype
(ConstrT
, Cnode
);
3400 Insert_Action
(Cnode
,
3401 Make_Full_Type_Declaration
(Loc
,
3402 Defining_Identifier
=> Acc_Typ
,
3404 Make_Access_To_Object_Definition
(Loc
,
3405 Subtype_Indication
=> New_Occurrence_Of
(ConstrT
, Loc
))),
3406 Suppress
=> All_Checks
);
3408 Make_Allocator
(Loc
,
3409 Expression
=> New_Occurrence_Of
(ConstrT
, Loc
));
3411 -- Allocate on the secondary stack. This is currently done
3412 -- only for type String, which normally doesn't have default
3413 -- initialization, but we need to Set_No_Initialization in case
3414 -- of Initialize_Scalars or Normalize_Scalars; otherwise, the
3415 -- allocator will get transformed and will not use the secondary
3418 Set_Storage_Pool
(Alloc
, RTE
(RE_SS_Pool
));
3419 Set_Procedure_To_Call
(Alloc
, RTE
(RE_SS_Allocate
));
3420 Set_No_Initialization
(Alloc
);
3422 Temp
:= Make_Temporary
(Loc
, 'R', Alloc
);
3423 Insert_Action
(Cnode
,
3424 Make_Object_Declaration
(Loc
,
3425 Defining_Identifier
=> Temp
,
3426 Object_Definition
=> New_Occurrence_Of
(Acc_Typ
, Loc
),
3427 Expression
=> Alloc
),
3428 Suppress
=> All_Checks
);
3430 Insert_Action
(Cnode
,
3431 Make_Object_Renaming_Declaration
(Loc
,
3432 Defining_Identifier
=> Ent
,
3433 Subtype_Mark
=> New_Occurrence_Of
(ConstrT
, Loc
),
3435 Make_Explicit_Dereference
(Loc
,
3436 Prefix
=> New_Occurrence_Of
(Temp
, Loc
))),
3437 Suppress
=> All_Checks
);
3440 -- If the bound is statically known to be out of range, we do not
3441 -- want to abort, we want a warning and a runtime constraint error.
3442 -- Note that we have arranged that the result will not be treated as
3443 -- a static constant, so we won't get an illegality during this
3445 -- We also enable checks (in particular range checks) in case the
3446 -- bounds of Subtyp_Ind are out of range.
3448 Insert_Action
(Cnode
,
3449 Make_Object_Declaration
(Loc
,
3450 Defining_Identifier
=> Ent
,
3451 Object_Definition
=> Subtyp_Ind
));
3454 -- If the result of the concatenation appears as the initializing
3455 -- expression of an object declaration, we can just rename the
3456 -- result, rather than copying it.
3458 Set_OK_To_Rename
(Ent
);
3460 -- Catch the static out of range case now
3462 if Raises_Constraint_Error
(High_Bound
) then
3463 raise Concatenation_Error
;
3466 -- Now we will generate the assignments to do the actual concatenation
3468 -- There is one case in which we will not do this, namely when all the
3469 -- following conditions are met:
3471 -- The result type is Standard.String
3473 -- There are nine or fewer retained (non-null) operands
3475 -- The optimization level is -O0 or the debug flag gnatd.C is set,
3476 -- and the debug flag gnatd.c is not set.
3478 -- The corresponding System.Concat_n.Str_Concat_n routine is
3479 -- available in the run time.
3481 -- If all these conditions are met then we generate a call to the
3482 -- relevant concatenation routine. The purpose of this is to avoid
3483 -- undesirable code bloat at -O0.
3485 -- If the concatenation is within the declaration of a library-level
3486 -- object, we call the built-in concatenation routines to prevent code
3487 -- bloat, regardless of the optimization level. This is space efficient
3488 -- and prevents linking problems when units are compiled with different
3489 -- optimization levels.
3491 if Atyp
= Standard_String
3492 and then NN
in 2 .. 9
3493 and then (((Optimization_Level
= 0 or else Debug_Flag_Dot_CC
)
3494 and then not Debug_Flag_Dot_C
)
3495 or else Library_Level_Target
)
3498 RR
: constant array (Nat
range 2 .. 9) of RE_Id
:=
3509 if RTE_Available
(RR
(NN
)) then
3511 Opnds
: constant List_Id
:=
3512 New_List
(New_Occurrence_Of
(Ent
, Loc
));
3515 for J
in 1 .. NN
loop
3516 if Is_List_Member
(Operands
(J
)) then
3517 Remove
(Operands
(J
));
3520 if Base_Type
(Etype
(Operands
(J
))) = Ctyp
then
3522 Make_Aggregate
(Loc
,
3523 Component_Associations
=> New_List
(
3524 Make_Component_Association
(Loc
,
3525 Choices
=> New_List
(
3526 Make_Integer_Literal
(Loc
, 1)),
3527 Expression
=> Operands
(J
)))));
3530 Append_To
(Opnds
, Operands
(J
));
3534 Insert_Action
(Cnode
,
3535 Make_Procedure_Call_Statement
(Loc
,
3536 Name
=> New_Occurrence_Of
(RTE
(RR
(NN
)), Loc
),
3537 Parameter_Associations
=> Opnds
));
3539 Result
:= New_Occurrence_Of
(Ent
, Loc
);
3546 -- Not special case so generate the assignments
3548 Known_Non_Null_Operand_Seen
:= False;
3550 for J
in 1 .. NN
loop
3552 Lo
: constant Node_Id
:=
3554 Left_Opnd
=> To_Artyp
(New_Copy_Tree
(Low_Bound
)),
3555 Right_Opnd
=> Aggr_Length
(J
- 1));
3557 Hi
: constant Node_Id
:=
3559 Left_Opnd
=> To_Artyp
(New_Copy_Tree
(Low_Bound
)),
3561 Make_Op_Subtract
(Loc
,
3562 Left_Opnd
=> Aggr_Length
(J
),
3563 Right_Opnd
=> Make_Artyp_Literal
(1)));
3566 -- Singleton case, simple assignment
3568 if Base_Type
(Etype
(Operands
(J
))) = Ctyp
then
3569 Known_Non_Null_Operand_Seen
:= True;
3570 Insert_Action
(Cnode
,
3571 Make_Assignment_Statement
(Loc
,
3573 Make_Indexed_Component
(Loc
,
3574 Prefix
=> New_Occurrence_Of
(Ent
, Loc
),
3575 Expressions
=> New_List
(To_Ityp
(Lo
))),
3576 Expression
=> Operands
(J
)),
3577 Suppress
=> All_Checks
);
3579 -- Array case, slice assignment, skipped when argument is fixed
3580 -- length and known to be null.
3582 elsif (not Is_Fixed_Length
(J
)) or else (Fixed_Length
(J
) > 0) then
3585 Make_Assignment_Statement
(Loc
,
3589 New_Occurrence_Of
(Ent
, Loc
),
3592 Low_Bound
=> To_Ityp
(Lo
),
3593 High_Bound
=> To_Ityp
(Hi
))),
3594 Expression
=> Operands
(J
));
3596 if Is_Fixed_Length
(J
) then
3597 Known_Non_Null_Operand_Seen
:= True;
3599 elsif not Known_Non_Null_Operand_Seen
then
3601 -- Here if operand length is not statically known and no
3602 -- operand known to be non-null has been processed yet.
3603 -- If operand length is 0, we do not need to perform the
3604 -- assignment, and we must avoid the evaluation of the
3605 -- high bound of the slice, since it may underflow if the
3606 -- low bound is Ityp'First.
3609 Make_Implicit_If_Statement
(Cnode
,
3613 New_Occurrence_Of
(Var_Length
(J
), Loc
),
3614 Right_Opnd
=> Make_Integer_Literal
(Loc
, 0)),
3615 Then_Statements
=> New_List
(Assign
));
3618 Insert_Action
(Cnode
, Assign
, Suppress
=> All_Checks
);
3624 -- Finally we build the result, which is a reference to the array object
3626 Result
:= New_Occurrence_Of
(Ent
, Loc
);
3629 pragma Assert
(Present
(Result
));
3630 Rewrite
(Cnode
, Result
);
3631 Analyze_And_Resolve
(Cnode
, Atyp
);
3634 when Concatenation_Error
=>
3636 -- Kill warning generated for the declaration of the static out of
3637 -- range high bound, and instead generate a Constraint_Error with
3638 -- an appropriate specific message.
3640 Kill_Dead_Code
(Declaration_Node
(Entity
(High_Bound
)));
3641 Apply_Compile_Time_Constraint_Error
3643 Msg
=> "concatenation result upper bound out of range??",
3644 Reason
=> CE_Range_Check_Failed
);
3645 end Expand_Concatenate
;
3647 ---------------------------------------------------
3648 -- Expand_Membership_Minimize_Eliminate_Overflow --
3649 ---------------------------------------------------
3651 procedure Expand_Membership_Minimize_Eliminate_Overflow
(N
: Node_Id
) is
3652 pragma Assert
(Nkind
(N
) = N_In
);
3653 -- Despite the name, this routine applies only to N_In, not to
3654 -- N_Not_In. The latter is always rewritten as not (X in Y).
3656 Result_Type
: constant Entity_Id
:= Etype
(N
);
3657 -- Capture result type, may be a derived boolean type
3659 Loc
: constant Source_Ptr
:= Sloc
(N
);
3660 Lop
: constant Node_Id
:= Left_Opnd
(N
);
3661 Rop
: constant Node_Id
:= Right_Opnd
(N
);
3663 -- Note: there are many referencs to Etype (Lop) and Etype (Rop). It
3664 -- is thus tempting to capture these values, but due to the rewrites
3665 -- that occur as a result of overflow checking, these values change
3666 -- as we go along, and it is safe just to always use Etype explicitly.
3668 Restype
: constant Entity_Id
:= Etype
(N
);
3672 -- Bounds in Minimize calls, not used currently
3674 LLIB
: constant Entity_Id
:= Base_Type
(Standard_Long_Long_Integer
);
3675 -- Entity for Long_Long_Integer'Base
3678 Minimize_Eliminate_Overflows
(Lop
, Lo
, Hi
, Top_Level
=> False);
3680 -- If right operand is a subtype name, and the subtype name has no
3681 -- predicate, then we can just replace the right operand with an
3682 -- explicit range T'First .. T'Last, and use the explicit range code.
3684 if Nkind
(Rop
) /= N_Range
3685 and then No
(Predicate_Function
(Etype
(Rop
)))
3688 Rtyp
: constant Entity_Id
:= Etype
(Rop
);
3693 Make_Attribute_Reference
(Loc
,
3694 Attribute_Name
=> Name_First
,
3695 Prefix
=> New_Occurrence_Of
(Rtyp
, Loc
)),
3697 Make_Attribute_Reference
(Loc
,
3698 Attribute_Name
=> Name_Last
,
3699 Prefix
=> New_Occurrence_Of
(Rtyp
, Loc
))));
3700 Analyze_And_Resolve
(Rop
, Rtyp
, Suppress
=> All_Checks
);
3704 -- Here for the explicit range case. Note that the bounds of the range
3705 -- have not been processed for minimized or eliminated checks.
3707 if Nkind
(Rop
) = N_Range
then
3708 Minimize_Eliminate_Overflows
3709 (Low_Bound
(Rop
), Lo
, Hi
, Top_Level
=> False);
3710 Minimize_Eliminate_Overflows
3711 (High_Bound
(Rop
), Lo
, Hi
, Top_Level
=> False);
3713 -- We have A in B .. C, treated as A >= B and then A <= C
3717 if Is_RTE
(Etype
(Lop
), RE_Bignum
)
3718 or else Is_RTE
(Etype
(Low_Bound
(Rop
)), RE_Bignum
)
3719 or else Is_RTE
(Etype
(High_Bound
(Rop
)), RE_Bignum
)
3722 Blk
: constant Node_Id
:= Make_Bignum_Block
(Loc
);
3723 Bnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'B', N
);
3724 L
: constant Entity_Id
:=
3725 Make_Defining_Identifier
(Loc
, Name_uL
);
3726 Lopnd
: constant Node_Id
:= Convert_To_Bignum
(Lop
);
3727 Lbound
: constant Node_Id
:=
3728 Convert_To_Bignum
(Low_Bound
(Rop
));
3729 Hbound
: constant Node_Id
:=
3730 Convert_To_Bignum
(High_Bound
(Rop
));
3732 -- Now we rewrite the membership test node to look like
3735 -- Bnn : Result_Type;
3737 -- M : Mark_Id := SS_Mark;
3738 -- L : Bignum := Lopnd;
3740 -- Bnn := Big_GE (L, Lbound) and then Big_LE (L, Hbound)
3748 -- Insert declaration of L into declarations of bignum block
3751 (Last
(Declarations
(Blk
)),
3752 Make_Object_Declaration
(Loc
,
3753 Defining_Identifier
=> L
,
3754 Object_Definition
=>
3755 New_Occurrence_Of
(RTE
(RE_Bignum
), Loc
),
3756 Expression
=> Lopnd
));
3758 -- Insert assignment to Bnn into expressions of bignum block
3761 (First
(Statements
(Handled_Statement_Sequence
(Blk
))),
3762 Make_Assignment_Statement
(Loc
,
3763 Name
=> New_Occurrence_Of
(Bnn
, Loc
),
3767 Make_Function_Call
(Loc
,
3769 New_Occurrence_Of
(RTE
(RE_Big_GE
), Loc
),
3770 Parameter_Associations
=> New_List
(
3771 New_Occurrence_Of
(L
, Loc
),
3775 Make_Function_Call
(Loc
,
3777 New_Occurrence_Of
(RTE
(RE_Big_LE
), Loc
),
3778 Parameter_Associations
=> New_List
(
3779 New_Occurrence_Of
(L
, Loc
),
3782 -- Now rewrite the node
3785 Make_Expression_With_Actions
(Loc
,
3786 Actions
=> New_List
(
3787 Make_Object_Declaration
(Loc
,
3788 Defining_Identifier
=> Bnn
,
3789 Object_Definition
=>
3790 New_Occurrence_Of
(Result_Type
, Loc
)),
3792 Expression
=> New_Occurrence_Of
(Bnn
, Loc
)));
3793 Analyze_And_Resolve
(N
, Result_Type
);
3797 -- Here if no bignums around
3800 -- Case where types are all the same
3802 if Base_Type
(Etype
(Lop
)) = Base_Type
(Etype
(Low_Bound
(Rop
)))
3804 Base_Type
(Etype
(Lop
)) = Base_Type
(Etype
(High_Bound
(Rop
)))
3808 -- If types are not all the same, it means that we have rewritten
3809 -- at least one of them to be of type Long_Long_Integer, and we
3810 -- will convert the other operands to Long_Long_Integer.
3813 Convert_To_And_Rewrite
(LLIB
, Lop
);
3814 Set_Analyzed
(Lop
, False);
3815 Analyze_And_Resolve
(Lop
, LLIB
);
3817 -- For the right operand, avoid unnecessary recursion into
3818 -- this routine, we know that overflow is not possible.
3820 Convert_To_And_Rewrite
(LLIB
, Low_Bound
(Rop
));
3821 Convert_To_And_Rewrite
(LLIB
, High_Bound
(Rop
));
3822 Set_Analyzed
(Rop
, False);
3823 Analyze_And_Resolve
(Rop
, LLIB
, Suppress
=> Overflow_Check
);
3826 -- Now the three operands are of the same signed integer type,
3827 -- so we can use the normal expansion routine for membership,
3828 -- setting the flag to prevent recursion into this procedure.
3830 Set_No_Minimize_Eliminate
(N
);
3834 -- Right operand is a subtype name and the subtype has a predicate. We
3835 -- have to make sure the predicate is checked, and for that we need to
3836 -- use the standard N_In circuitry with appropriate types.
3839 pragma Assert
(Present
(Predicate_Function
(Etype
(Rop
))));
3841 -- If types are "right", just call Expand_N_In preventing recursion
3843 if Base_Type
(Etype
(Lop
)) = Base_Type
(Etype
(Rop
)) then
3844 Set_No_Minimize_Eliminate
(N
);
3849 elsif Is_RTE
(Etype
(Lop
), RE_Bignum
) then
3851 -- For X in T, we want to rewrite our node as
3854 -- Bnn : Result_Type;
3857 -- M : Mark_Id := SS_Mark;
3858 -- Lnn : Long_Long_Integer'Base
3864 -- if not Bignum_In_LLI_Range (Nnn) then
3867 -- Lnn := From_Bignum (Nnn);
3869 -- Lnn in LLIB (T'Base'First) .. LLIB (T'Base'Last)
3870 -- and then T'Base (Lnn) in T;
3879 -- A bit gruesome, but there doesn't seem to be a simpler way
3882 Blk
: constant Node_Id
:= Make_Bignum_Block
(Loc
);
3883 Bnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'B', N
);
3884 Lnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'L', N
);
3885 Nnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'N', N
);
3886 T
: constant Entity_Id
:= Etype
(Rop
);
3887 TB
: constant Entity_Id
:= Base_Type
(T
);
3891 -- Mark the last membership operation to prevent recursion
3895 Left_Opnd
=> Convert_To
(TB
, New_Occurrence_Of
(Lnn
, Loc
)),
3896 Right_Opnd
=> New_Occurrence_Of
(T
, Loc
));
3897 Set_No_Minimize_Eliminate
(Nin
);
3899 -- Now decorate the block
3902 (Last
(Declarations
(Blk
)),
3903 Make_Object_Declaration
(Loc
,
3904 Defining_Identifier
=> Lnn
,
3905 Object_Definition
=> New_Occurrence_Of
(LLIB
, Loc
)));
3908 (Last
(Declarations
(Blk
)),
3909 Make_Object_Declaration
(Loc
,
3910 Defining_Identifier
=> Nnn
,
3911 Object_Definition
=>
3912 New_Occurrence_Of
(RTE
(RE_Bignum
), Loc
)));
3915 (First
(Statements
(Handled_Statement_Sequence
(Blk
))),
3917 Make_Assignment_Statement
(Loc
,
3918 Name
=> New_Occurrence_Of
(Nnn
, Loc
),
3919 Expression
=> Relocate_Node
(Lop
)),
3921 Make_Implicit_If_Statement
(N
,
3925 Make_Function_Call
(Loc
,
3928 (RTE
(RE_Bignum_In_LLI_Range
), Loc
),
3929 Parameter_Associations
=> New_List
(
3930 New_Occurrence_Of
(Nnn
, Loc
)))),
3932 Then_Statements
=> New_List
(
3933 Make_Assignment_Statement
(Loc
,
3934 Name
=> New_Occurrence_Of
(Bnn
, Loc
),
3936 New_Occurrence_Of
(Standard_False
, Loc
))),
3938 Else_Statements
=> New_List
(
3939 Make_Assignment_Statement
(Loc
,
3940 Name
=> New_Occurrence_Of
(Lnn
, Loc
),
3942 Make_Function_Call
(Loc
,
3944 New_Occurrence_Of
(RTE
(RE_From_Bignum
), Loc
),
3945 Parameter_Associations
=> New_List
(
3946 New_Occurrence_Of
(Nnn
, Loc
)))),
3948 Make_Assignment_Statement
(Loc
,
3949 Name
=> New_Occurrence_Of
(Bnn
, Loc
),
3954 Left_Opnd
=> New_Occurrence_Of
(Lnn
, Loc
),
3959 Make_Attribute_Reference
(Loc
,
3960 Attribute_Name
=> Name_First
,
3962 New_Occurrence_Of
(TB
, Loc
))),
3966 Make_Attribute_Reference
(Loc
,
3967 Attribute_Name
=> Name_Last
,
3969 New_Occurrence_Of
(TB
, Loc
))))),
3971 Right_Opnd
=> Nin
))))));
3973 -- Now we can do the rewrite
3976 Make_Expression_With_Actions
(Loc
,
3977 Actions
=> New_List
(
3978 Make_Object_Declaration
(Loc
,
3979 Defining_Identifier
=> Bnn
,
3980 Object_Definition
=>
3981 New_Occurrence_Of
(Result_Type
, Loc
)),
3983 Expression
=> New_Occurrence_Of
(Bnn
, Loc
)));
3984 Analyze_And_Resolve
(N
, Result_Type
);
3988 -- Not bignum case, but types don't match (this means we rewrote the
3989 -- left operand to be Long_Long_Integer).
3992 pragma Assert
(Base_Type
(Etype
(Lop
)) = LLIB
);
3994 -- We rewrite the membership test as (where T is the type with
3995 -- the predicate, i.e. the type of the right operand)
3997 -- Lop in LLIB (T'Base'First) .. LLIB (T'Base'Last)
3998 -- and then T'Base (Lop) in T
4001 T
: constant Entity_Id
:= Etype
(Rop
);
4002 TB
: constant Entity_Id
:= Base_Type
(T
);
4006 -- The last membership test is marked to prevent recursion
4010 Left_Opnd
=> Convert_To
(TB
, Duplicate_Subexpr
(Lop
)),
4011 Right_Opnd
=> New_Occurrence_Of
(T
, Loc
));
4012 Set_No_Minimize_Eliminate
(Nin
);
4014 -- Now do the rewrite
4025 Make_Attribute_Reference
(Loc
,
4026 Attribute_Name
=> Name_First
,
4028 New_Occurrence_Of
(TB
, Loc
))),
4031 Make_Attribute_Reference
(Loc
,
4032 Attribute_Name
=> Name_Last
,
4034 New_Occurrence_Of
(TB
, Loc
))))),
4035 Right_Opnd
=> Nin
));
4036 Set_Analyzed
(N
, False);
4037 Analyze_And_Resolve
(N
, Restype
);
4041 end Expand_Membership_Minimize_Eliminate_Overflow
;
4043 ---------------------------------
4044 -- Expand_Nonbinary_Modular_Op --
4045 ---------------------------------
4047 procedure Expand_Nonbinary_Modular_Op
(N
: Node_Id
) is
4048 Loc
: constant Source_Ptr
:= Sloc
(N
);
4049 Typ
: constant Entity_Id
:= Etype
(N
);
4051 procedure Expand_Modular_Addition
;
4052 -- Expand the modular addition, handling the special case of adding a
4055 procedure Expand_Modular_Op
;
4056 -- Compute the general rule: (lhs OP rhs) mod Modulus
4058 procedure Expand_Modular_Subtraction
;
4059 -- Expand the modular addition, handling the special case of subtracting
4062 -----------------------------
4063 -- Expand_Modular_Addition --
4064 -----------------------------
4066 procedure Expand_Modular_Addition
is
4068 -- If this is not the addition of a constant then compute it using
4069 -- the general rule: (lhs + rhs) mod Modulus
4071 if Nkind
(Right_Opnd
(N
)) /= N_Integer_Literal
then
4074 -- If this is an addition of a constant, convert it to a subtraction
4075 -- plus a conditional expression since we can compute it faster than
4076 -- computing the modulus.
4078 -- modMinusRhs = Modulus - rhs
4079 -- if lhs < modMinusRhs then lhs + rhs
4080 -- else lhs - modMinusRhs
4084 Mod_Minus_Right
: constant Uint
:=
4085 Modulus
(Typ
) - Intval
(Right_Opnd
(N
));
4087 Exprs
: constant List_Id
:= New_List
;
4088 Cond_Expr
: constant Node_Id
:= New_Op_Node
(N_Op_Lt
, Loc
);
4089 Then_Expr
: constant Node_Id
:= New_Op_Node
(N_Op_Add
, Loc
);
4090 Else_Expr
: constant Node_Id
:= New_Op_Node
(N_Op_Subtract
,
4093 -- To prevent spurious visibility issues, convert all
4094 -- operands to Standard.Unsigned.
4096 Set_Left_Opnd
(Cond_Expr
,
4097 Unchecked_Convert_To
(Standard_Unsigned
,
4098 New_Copy_Tree
(Left_Opnd
(N
))));
4099 Set_Right_Opnd
(Cond_Expr
,
4100 Make_Integer_Literal
(Loc
, Mod_Minus_Right
));
4101 Append_To
(Exprs
, Cond_Expr
);
4103 Set_Left_Opnd
(Then_Expr
,
4104 Unchecked_Convert_To
(Standard_Unsigned
,
4105 New_Copy_Tree
(Left_Opnd
(N
))));
4106 Set_Right_Opnd
(Then_Expr
,
4107 Make_Integer_Literal
(Loc
, Intval
(Right_Opnd
(N
))));
4108 Append_To
(Exprs
, Then_Expr
);
4110 Set_Left_Opnd
(Else_Expr
,
4111 Unchecked_Convert_To
(Standard_Unsigned
,
4112 New_Copy_Tree
(Left_Opnd
(N
))));
4113 Set_Right_Opnd
(Else_Expr
,
4114 Make_Integer_Literal
(Loc
, Mod_Minus_Right
));
4115 Append_To
(Exprs
, Else_Expr
);
4118 Unchecked_Convert_To
(Typ
,
4119 Make_If_Expression
(Loc
, Expressions
=> Exprs
)));
4122 end Expand_Modular_Addition
;
4124 -----------------------
4125 -- Expand_Modular_Op --
4126 -----------------------
4128 procedure Expand_Modular_Op
is
4129 Op_Expr
: constant Node_Id
:= New_Op_Node
(Nkind
(N
), Loc
);
4130 Mod_Expr
: constant Node_Id
:= New_Op_Node
(N_Op_Mod
, Loc
);
4132 Target_Type
: Entity_Id
;
4135 -- Convert nonbinary modular type operands into integer values. Thus
4136 -- we avoid never-ending loops expanding them, and we also ensure
4137 -- the back end never receives nonbinary modular type expressions.
4139 if Nkind
(N
) in N_Op_And | N_Op_Or | N_Op_Xor
then
4140 Set_Left_Opnd
(Op_Expr
,
4141 Unchecked_Convert_To
(Standard_Unsigned
,
4142 New_Copy_Tree
(Left_Opnd
(N
))));
4143 Set_Right_Opnd
(Op_Expr
,
4144 Unchecked_Convert_To
(Standard_Unsigned
,
4145 New_Copy_Tree
(Right_Opnd
(N
))));
4146 Set_Left_Opnd
(Mod_Expr
,
4147 Unchecked_Convert_To
(Standard_Integer
, Op_Expr
));
4150 -- If the modulus of the type is larger than Integer'Last use a
4151 -- larger type for the operands, to prevent spurious constraint
4152 -- errors on large legal literals of the type.
4154 if Modulus
(Etype
(N
)) > Int
(Integer'Last) then
4155 Target_Type
:= Standard_Long_Long_Integer
;
4157 Target_Type
:= Standard_Integer
;
4160 Set_Left_Opnd
(Op_Expr
,
4161 Unchecked_Convert_To
(Target_Type
,
4162 New_Copy_Tree
(Left_Opnd
(N
))));
4163 Set_Right_Opnd
(Op_Expr
,
4164 Unchecked_Convert_To
(Target_Type
,
4165 New_Copy_Tree
(Right_Opnd
(N
))));
4167 -- Link this node to the tree to analyze it
4169 -- If the parent node is an expression with actions we link it to
4170 -- N since otherwise Force_Evaluation cannot identify if this node
4171 -- comes from the Expression and rejects generating the temporary.
4173 if Nkind
(Parent
(N
)) = N_Expression_With_Actions
then
4174 Set_Parent
(Op_Expr
, N
);
4179 Set_Parent
(Op_Expr
, Parent
(N
));
4184 -- Force generating a temporary because in the expansion of this
4185 -- expression we may generate code that performs this computation
4188 Force_Evaluation
(Op_Expr
, Mode
=> Strict
);
4190 Set_Left_Opnd
(Mod_Expr
, Op_Expr
);
4193 Set_Right_Opnd
(Mod_Expr
,
4194 Make_Integer_Literal
(Loc
, Modulus
(Typ
)));
4197 Unchecked_Convert_To
(Typ
, Mod_Expr
));
4198 end Expand_Modular_Op
;
4200 --------------------------------
4201 -- Expand_Modular_Subtraction --
4202 --------------------------------
4204 procedure Expand_Modular_Subtraction
is
4206 -- If this is not the addition of a constant then compute it using
4207 -- the general rule: (lhs + rhs) mod Modulus
4209 if Nkind
(Right_Opnd
(N
)) /= N_Integer_Literal
then
4212 -- If this is an addition of a constant, convert it to a subtraction
4213 -- plus a conditional expression since we can compute it faster than
4214 -- computing the modulus.
4216 -- modMinusRhs = Modulus - rhs
4217 -- if lhs < rhs then lhs + modMinusRhs
4222 Mod_Minus_Right
: constant Uint
:=
4223 Modulus
(Typ
) - Intval
(Right_Opnd
(N
));
4225 Exprs
: constant List_Id
:= New_List
;
4226 Cond_Expr
: constant Node_Id
:= New_Op_Node
(N_Op_Lt
, Loc
);
4227 Then_Expr
: constant Node_Id
:= New_Op_Node
(N_Op_Add
, Loc
);
4228 Else_Expr
: constant Node_Id
:= New_Op_Node
(N_Op_Subtract
,
4231 Set_Left_Opnd
(Cond_Expr
,
4232 Unchecked_Convert_To
(Standard_Unsigned
,
4233 New_Copy_Tree
(Left_Opnd
(N
))));
4234 Set_Right_Opnd
(Cond_Expr
,
4235 Make_Integer_Literal
(Loc
, Intval
(Right_Opnd
(N
))));
4236 Append_To
(Exprs
, Cond_Expr
);
4238 Set_Left_Opnd
(Then_Expr
,
4239 Unchecked_Convert_To
(Standard_Unsigned
,
4240 New_Copy_Tree
(Left_Opnd
(N
))));
4241 Set_Right_Opnd
(Then_Expr
,
4242 Make_Integer_Literal
(Loc
, Mod_Minus_Right
));
4243 Append_To
(Exprs
, Then_Expr
);
4245 Set_Left_Opnd
(Else_Expr
,
4246 Unchecked_Convert_To
(Standard_Unsigned
,
4247 New_Copy_Tree
(Left_Opnd
(N
))));
4248 Set_Right_Opnd
(Else_Expr
,
4249 Unchecked_Convert_To
(Standard_Unsigned
,
4250 New_Copy_Tree
(Right_Opnd
(N
))));
4251 Append_To
(Exprs
, Else_Expr
);
4254 Unchecked_Convert_To
(Typ
,
4255 Make_If_Expression
(Loc
, Expressions
=> Exprs
)));
4258 end Expand_Modular_Subtraction
;
4260 -- Start of processing for Expand_Nonbinary_Modular_Op
4263 -- No action needed if front-end expansion is not required or if we
4264 -- have a binary modular operand.
4266 if not Expand_Nonbinary_Modular_Ops
4267 or else not Non_Binary_Modulus
(Typ
)
4274 Expand_Modular_Addition
;
4276 when N_Op_Subtract
=>
4277 Expand_Modular_Subtraction
;
4281 -- Expand -expr into (0 - expr)
4284 Make_Op_Subtract
(Loc
,
4285 Left_Opnd
=> Make_Integer_Literal
(Loc
, 0),
4286 Right_Opnd
=> Right_Opnd
(N
)));
4287 Analyze_And_Resolve
(N
, Typ
);
4293 Analyze_And_Resolve
(N
, Typ
);
4294 end Expand_Nonbinary_Modular_Op
;
4296 ------------------------
4297 -- Expand_N_Allocator --
4298 ------------------------
4300 procedure Expand_N_Allocator
(N
: Node_Id
) is
4301 Etyp
: constant Entity_Id
:= Etype
(Expression
(N
));
4302 Loc
: constant Source_Ptr
:= Sloc
(N
);
4303 PtrT
: constant Entity_Id
:= Etype
(N
);
4305 procedure Rewrite_Coextension
(N
: Node_Id
);
4306 -- Static coextensions have the same lifetime as the entity they
4307 -- constrain. Such occurrences can be rewritten as aliased objects
4308 -- and their unrestricted access used instead of the coextension.
4310 function Size_In_Storage_Elements
(E
: Entity_Id
) return Node_Id
;
4311 -- Given a constrained array type E, returns a node representing the
4312 -- code to compute a close approximation of the size in storage elements
4313 -- for the given type; for indexes that are modular types we compute
4314 -- 'Last - First (instead of 'Length) because for large arrays computing
4315 -- 'Last -'First + 1 causes overflow. This is done without using the
4316 -- attribute 'Size_In_Storage_Elements (which malfunctions for large
4319 -------------------------
4320 -- Rewrite_Coextension --
4321 -------------------------
4323 procedure Rewrite_Coextension
(N
: Node_Id
) is
4324 Temp_Id
: constant Node_Id
:= Make_Temporary
(Loc
, 'C');
4325 Temp_Decl
: Node_Id
;
4329 -- Cnn : aliased Etyp;
4332 Make_Object_Declaration
(Loc
,
4333 Defining_Identifier
=> Temp_Id
,
4334 Aliased_Present
=> True,
4335 Object_Definition
=> New_Occurrence_Of
(Etyp
, Loc
));
4337 if Nkind
(Expression
(N
)) = N_Qualified_Expression
then
4338 Set_Expression
(Temp_Decl
, Expression
(Expression
(N
)));
4341 Insert_Action
(N
, Temp_Decl
);
4343 Make_Attribute_Reference
(Loc
,
4344 Prefix
=> New_Occurrence_Of
(Temp_Id
, Loc
),
4345 Attribute_Name
=> Name_Unrestricted_Access
));
4347 Analyze_And_Resolve
(N
, PtrT
);
4348 end Rewrite_Coextension
;
4350 ------------------------------
4351 -- Size_In_Storage_Elements --
4352 ------------------------------
4354 function Size_In_Storage_Elements
(E
: Entity_Id
) return Node_Id
is
4356 -- Logically this just returns E'Max_Size_In_Storage_Elements.
4357 -- However, the reason for the existence of this function is
4358 -- to construct a test for sizes too large, which means near the
4359 -- 32-bit limit on a 32-bit machine, and precisely the trouble
4360 -- is that we get overflows when sizes are greater than 2**31.
4362 -- So what we end up doing for array types is to use the expression:
4364 -- number-of-elements * component_type'Max_Size_In_Storage_Elements
4366 -- which avoids this problem. All this is a bit bogus, but it does
4367 -- mean we catch common cases of trying to allocate arrays that
4368 -- are too large, and which in the absence of a check results in
4369 -- undetected chaos ???
4372 Idx
: Node_Id
:= First_Index
(E
);
4374 Res
: Node_Id
:= Empty
;
4377 for J
in 1 .. Number_Dimensions
(E
) loop
4379 if not Is_Modular_Integer_Type
(Etype
(Idx
)) then
4381 Make_Attribute_Reference
(Loc
,
4382 Prefix
=> New_Occurrence_Of
(E
, Loc
),
4383 Attribute_Name
=> Name_Length
,
4384 Expressions
=> New_List
4385 (Make_Integer_Literal
(Loc
, J
)));
4387 -- For indexes that are modular types we cannot generate code
4388 -- to compute 'Length since for large arrays 'Last -'First + 1
4389 -- causes overflow; therefore we compute 'Last - 'First (which
4390 -- is not the exact number of components but it is valid for
4391 -- the purpose of this runtime check on 32-bit targets).
4395 Len_Minus_1_Expr
: Node_Id
;
4401 Make_Attribute_Reference
(Loc
,
4402 Prefix
=> New_Occurrence_Of
(E
, Loc
),
4403 Attribute_Name
=> Name_Last
,
4405 New_List
(Make_Integer_Literal
(Loc
, J
))),
4406 Make_Attribute_Reference
(Loc
,
4407 Prefix
=> New_Occurrence_Of
(E
, Loc
),
4408 Attribute_Name
=> Name_First
,
4410 New_List
(Make_Integer_Literal
(Loc
, J
))));
4413 Convert_To
(Standard_Unsigned
,
4414 Make_Op_Subtract
(Loc
,
4415 Make_Attribute_Reference
(Loc
,
4416 Prefix
=> New_Occurrence_Of
(E
, Loc
),
4417 Attribute_Name
=> Name_Last
,
4420 (Make_Integer_Literal
(Loc
, J
))),
4421 Make_Attribute_Reference
(Loc
,
4422 Prefix
=> New_Occurrence_Of
(E
, Loc
),
4423 Attribute_Name
=> Name_First
,
4426 (Make_Integer_Literal
(Loc
, J
)))));
4428 -- Handle superflat arrays, i.e. arrays with such bounds
4429 -- as 4 .. 2, to ensure that the result is correct.
4432 -- (if X'Last > X'First then X'Last - X'First else 0)
4435 Make_If_Expression
(Loc
,
4436 Expressions
=> New_List
(
4439 Make_Integer_Literal
(Loc
, Uint_0
)));
4447 pragma Assert
(Present
(Res
));
4449 Make_Op_Multiply
(Loc
,
4458 Make_Op_Multiply
(Loc
,
4461 Make_Attribute_Reference
(Loc
,
4462 Prefix
=> New_Occurrence_Of
(Component_Type
(E
), Loc
),
4463 Attribute_Name
=> Name_Max_Size_In_Storage_Elements
));
4465 end Size_In_Storage_Elements
;
4469 Dtyp
: constant Entity_Id
:= Available_View
(Designated_Type
(PtrT
));
4473 Rel_Typ
: Entity_Id
;
4476 -- Start of processing for Expand_N_Allocator
4479 -- Warn on the presence of an allocator of an anonymous access type when
4480 -- enabled, except when it's an object declaration at library level.
4482 if Warn_On_Anonymous_Allocators
4483 and then Ekind
(PtrT
) = E_Anonymous_Access_Type
4484 and then not (Is_Library_Level_Entity
(PtrT
)
4485 and then Nkind
(Associated_Node_For_Itype
(PtrT
)) =
4486 N_Object_Declaration
)
4488 Error_Msg_N
("?_a?use of an anonymous access type allocator", N
);
4491 -- RM E.2.2(17). We enforce that the expected type of an allocator
4492 -- shall not be a remote access-to-class-wide-limited-private type.
4493 -- We probably shouldn't be doing this legality check during expansion,
4494 -- but this is only an issue for Annex E users, and is unlikely to be a
4495 -- problem in practice.
4497 Validate_Remote_Access_To_Class_Wide_Type
(N
);
4499 -- Processing for anonymous access-to-controlled types. These access
4500 -- types receive a special finalization master which appears in the
4501 -- declarations of the enclosing semantic unit. This expansion is done
4502 -- now to ensure that any additional types generated by this routine or
4503 -- Expand_Allocator_Expression inherit the proper type attributes.
4505 if (Ekind
(PtrT
) = E_Anonymous_Access_Type
4506 or else (Is_Itype
(PtrT
) and then No
(Finalization_Master
(PtrT
))))
4507 and then Needs_Finalization
(Dtyp
)
4509 -- Detect the allocation of an anonymous controlled object where the
4510 -- type of the context is named. For example:
4512 -- procedure Proc (Ptr : Named_Access_Typ);
4513 -- Proc (new Designated_Typ);
4515 -- Regardless of the anonymous-to-named access type conversion, the
4516 -- lifetime of the object must be associated with the named access
4517 -- type. Use the finalization-related attributes of this type.
4519 if Nkind
(Parent
(N
)) in N_Type_Conversion
4520 | N_Unchecked_Type_Conversion
4521 and then Ekind
(Etype
(Parent
(N
))) in E_Access_Subtype
4523 | E_General_Access_Type
4525 Rel_Typ
:= Etype
(Parent
(N
));
4530 -- Anonymous access-to-controlled types allocate on the global pool.
4531 -- Note that this is a "root type only" attribute.
4533 if No
(Associated_Storage_Pool
(PtrT
)) then
4534 if Present
(Rel_Typ
) then
4535 Set_Associated_Storage_Pool
4536 (Root_Type
(PtrT
), Associated_Storage_Pool
(Rel_Typ
));
4538 Set_Associated_Storage_Pool
4539 (Root_Type
(PtrT
), RTE
(RE_Global_Pool_Object
));
4543 -- The finalization master must be inserted and analyzed as part of
4544 -- the current semantic unit. Note that the master is updated when
4545 -- analysis changes current units. Note that this is a "root type
4548 if Present
(Rel_Typ
) then
4549 Set_Finalization_Master
4550 (Root_Type
(PtrT
), Finalization_Master
(Rel_Typ
));
4552 Build_Anonymous_Master
(Root_Type
(PtrT
));
4556 -- Set the storage pool and find the appropriate version of Allocate to
4557 -- call. Do not overwrite the storage pool if it is already set, which
4558 -- can happen for build-in-place function returns (see
4559 -- Exp_Ch4.Expand_N_Extended_Return_Statement).
4561 if No
(Storage_Pool
(N
)) then
4562 Pool
:= Associated_Storage_Pool
(Root_Type
(PtrT
));
4564 if Present
(Pool
) then
4565 Set_Storage_Pool
(N
, Pool
);
4567 if Is_RTE
(Pool
, RE_SS_Pool
) then
4568 Check_Restriction
(No_Secondary_Stack
, N
);
4569 Set_Procedure_To_Call
(N
, RTE
(RE_SS_Allocate
));
4571 -- In the case of an allocator for a simple storage pool, locate
4572 -- and save a reference to the pool type's Allocate routine.
4574 elsif Present
(Get_Rep_Pragma
4575 (Etype
(Pool
), Name_Simple_Storage_Pool_Type
))
4578 Pool_Type
: constant Entity_Id
:= Base_Type
(Etype
(Pool
));
4579 Alloc_Op
: Entity_Id
;
4581 Alloc_Op
:= Get_Name_Entity_Id
(Name_Allocate
);
4582 while Present
(Alloc_Op
) loop
4583 if Scope
(Alloc_Op
) = Scope
(Pool_Type
)
4584 and then Present
(First_Formal
(Alloc_Op
))
4585 and then Etype
(First_Formal
(Alloc_Op
)) = Pool_Type
4587 Set_Procedure_To_Call
(N
, Alloc_Op
);
4590 Alloc_Op
:= Homonym
(Alloc_Op
);
4595 elsif Is_Class_Wide_Type
(Etype
(Pool
)) then
4596 Set_Procedure_To_Call
(N
, RTE
(RE_Allocate_Any
));
4599 Set_Procedure_To_Call
(N
,
4600 Find_Storage_Op
(Etype
(Pool
), Name_Allocate
));
4605 -- Under certain circumstances we can replace an allocator by an access
4606 -- to statically allocated storage. The conditions, as noted in AARM
4607 -- 3.10 (10c) are as follows:
4609 -- Size and initial value is known at compile time
4610 -- Access type is access-to-constant
4612 -- The allocator is not part of a constraint on a record component,
4613 -- because in that case the inserted actions are delayed until the
4614 -- record declaration is fully analyzed, which is too late for the
4615 -- analysis of the rewritten allocator.
4617 if Is_Access_Constant
(PtrT
)
4618 and then Nkind
(Expression
(N
)) = N_Qualified_Expression
4619 and then Compile_Time_Known_Value
(Expression
(Expression
(N
)))
4620 and then Size_Known_At_Compile_Time
4621 (Etype
(Expression
(Expression
(N
))))
4622 and then not Is_Record_Type
(Current_Scope
)
4624 -- Here we can do the optimization. For the allocator
4628 -- We insert an object declaration
4630 -- Tnn : aliased x := y;
4632 -- and replace the allocator by Tnn'Unrestricted_Access. Tnn is
4633 -- marked as requiring static allocation.
4635 Temp
:= Make_Temporary
(Loc
, 'T', Expression
(Expression
(N
)));
4636 Desig
:= Subtype_Mark
(Expression
(N
));
4638 -- If context is constrained, use constrained subtype directly,
4639 -- so that the constant is not labelled as having a nominally
4640 -- unconstrained subtype.
4642 if Entity
(Desig
) = Base_Type
(Dtyp
) then
4643 Desig
:= New_Occurrence_Of
(Dtyp
, Loc
);
4647 Make_Object_Declaration
(Loc
,
4648 Defining_Identifier
=> Temp
,
4649 Aliased_Present
=> True,
4650 Constant_Present
=> Is_Access_Constant
(PtrT
),
4651 Object_Definition
=> Desig
,
4652 Expression
=> Expression
(Expression
(N
))));
4655 Make_Attribute_Reference
(Loc
,
4656 Prefix
=> New_Occurrence_Of
(Temp
, Loc
),
4657 Attribute_Name
=> Name_Unrestricted_Access
));
4659 Analyze_And_Resolve
(N
, PtrT
);
4661 -- We set the variable as statically allocated, since we don't want
4662 -- it going on the stack of the current procedure.
4664 Set_Is_Statically_Allocated
(Temp
);
4668 -- Same if the allocator is an access discriminant for a local object:
4669 -- instead of an allocator we create a local value and constrain the
4670 -- enclosing object with the corresponding access attribute.
4672 if Is_Static_Coextension
(N
) then
4673 Rewrite_Coextension
(N
);
4677 -- Check for size too large, we do this because the back end misses
4678 -- proper checks here and can generate rubbish allocation calls when
4679 -- we are near the limit. We only do this for the 32-bit address case
4680 -- since that is from a practical point of view where we see a problem.
4682 if System_Address_Size
= 32
4683 and then not Storage_Checks_Suppressed
(PtrT
)
4684 and then not Storage_Checks_Suppressed
(Dtyp
)
4685 and then not Storage_Checks_Suppressed
(Etyp
)
4687 -- The check we want to generate should look like
4689 -- if Etyp'Max_Size_In_Storage_Elements > 3.5 gigabytes then
4690 -- raise Storage_Error;
4693 -- where 3.5 gigabytes is a constant large enough to accommodate any
4694 -- reasonable request for. But we can't do it this way because at
4695 -- least at the moment we don't compute this attribute right, and
4696 -- can silently give wrong results when the result gets large. Since
4697 -- this is all about large results, that's bad, so instead we only
4698 -- apply the check for constrained arrays, and manually compute the
4699 -- value of the attribute ???
4701 -- The check on No_Initialization is used here to prevent generating
4702 -- this runtime check twice when the allocator is locally replaced by
4703 -- the expander with another one.
4705 if Is_Array_Type
(Etyp
) and then not No_Initialization
(N
) then
4708 Ins_Nod
: Node_Id
:= N
;
4709 Siz_Typ
: Entity_Id
:= Etyp
;
4713 -- For unconstrained array types initialized with a qualified
4714 -- expression we use its type to perform this check
4716 if not Is_Constrained
(Etyp
)
4717 and then not No_Initialization
(N
)
4718 and then Nkind
(Expression
(N
)) = N_Qualified_Expression
4720 Expr
:= Expression
(Expression
(N
));
4721 Siz_Typ
:= Etype
(Expression
(Expression
(N
)));
4723 -- If the qualified expression has been moved to an internal
4724 -- temporary (to remove side effects) then we must insert
4725 -- the runtime check before its declaration to ensure that
4726 -- the check is performed before the execution of the code
4727 -- computing the qualified expression.
4729 if Nkind
(Expr
) = N_Identifier
4730 and then Is_Internal_Name
(Chars
(Expr
))
4732 Nkind
(Parent
(Entity
(Expr
))) = N_Object_Declaration
4734 Ins_Nod
:= Parent
(Entity
(Expr
));
4740 if Is_Constrained
(Siz_Typ
)
4741 and then Ekind
(Siz_Typ
) /= E_String_Literal_Subtype
4743 -- For CCG targets, the largest array may have up to 2**31-1
4744 -- components (i.e. 2 gigabytes if each array component is
4745 -- one byte). This ensures that fat pointer fields do not
4746 -- overflow, since they are 32-bit integer types, and also
4747 -- ensures that 'Length can be computed at run time.
4749 if Modify_Tree_For_C
then
4752 Left_Opnd
=> Size_In_Storage_Elements
(Siz_Typ
),
4753 Right_Opnd
=> Make_Integer_Literal
(Loc
,
4754 Uint_2
** 31 - Uint_1
));
4756 -- For native targets the largest object is 3.5 gigabytes
4761 Left_Opnd
=> Size_In_Storage_Elements
(Siz_Typ
),
4762 Right_Opnd
=> Make_Integer_Literal
(Loc
,
4763 Uint_7
* (Uint_2
** 29)));
4766 Insert_Action
(Ins_Nod
,
4767 Make_Raise_Storage_Error
(Loc
,
4769 Reason
=> SE_Object_Too_Large
));
4771 if Entity
(Cond
) = Standard_True
then
4773 ("object too large: Storage_Error will be raised at "
4781 -- If no storage pool has been specified, or the storage pool
4782 -- is System.Pool_Global.Global_Pool_Object, and the restriction
4783 -- No_Standard_Allocators_After_Elaboration is present, then generate
4784 -- a call to Elaboration_Allocators.Check_Standard_Allocator.
4786 if Nkind
(N
) = N_Allocator
4787 and then (No
(Storage_Pool
(N
))
4788 or else Is_RTE
(Storage_Pool
(N
), RE_Global_Pool_Object
))
4789 and then Restriction_Active
(No_Standard_Allocators_After_Elaboration
)
4792 Make_Procedure_Call_Statement
(Loc
,
4794 New_Occurrence_Of
(RTE
(RE_Check_Standard_Allocator
), Loc
)));
4797 -- Handle case of qualified expression (other than optimization above)
4799 if Nkind
(Expression
(N
)) = N_Qualified_Expression
then
4800 Expand_Allocator_Expression
(N
);
4804 -- If the allocator is for a type which requires initialization, and
4805 -- there is no initial value (i.e. operand is a subtype indication
4806 -- rather than a qualified expression), then we must generate a call to
4807 -- the initialization routine using an expressions action node:
4809 -- [Pnnn : constant ptr_T := new (T); Init (Pnnn.all,...); Pnnn]
4811 -- Here ptr_T is the pointer type for the allocator, and T is the
4812 -- subtype of the allocator. A special case arises if the designated
4813 -- type of the access type is a task or contains tasks. In this case
4814 -- the call to Init (Temp.all ...) is replaced by code that ensures
4815 -- that tasks get activated (see Exp_Ch9.Build_Task_Allocate_Block
4816 -- for details). In addition, if the type T is a task type, then the
4817 -- first argument to Init must be converted to the task record type.
4820 T
: constant Entity_Id
:= Etype
(Expression
(N
));
4826 Init_Arg1
: Node_Id
;
4827 Init_Call
: Node_Id
;
4828 Temp_Decl
: Node_Id
;
4829 Temp_Type
: Entity_Id
;
4832 -- Apply constraint checks against designated subtype (RM 4.8(10/2))
4833 -- but ignore the expression if the No_Initialization flag is set.
4834 -- Discriminant checks will be generated by the expansion below.
4836 if Is_Array_Type
(Dtyp
) and then not No_Initialization
(N
) then
4837 Apply_Constraint_Check
(Expression
(N
), Dtyp
, No_Sliding
=> True);
4839 Apply_Predicate_Check
(Expression
(N
), Dtyp
);
4841 if Nkind
(Expression
(N
)) = N_Raise_Constraint_Error
then
4842 Rewrite
(N
, New_Copy
(Expression
(N
)));
4843 Set_Etype
(N
, PtrT
);
4848 if No_Initialization
(N
) then
4850 -- Even though this might be a simple allocation, create a custom
4851 -- Allocate if the context requires it.
4853 if Present
(Finalization_Master
(PtrT
)) then
4854 Build_Allocate_Deallocate_Proc
4856 Is_Allocate
=> True);
4859 -- Optimize the default allocation of an array object when pragma
4860 -- Initialize_Scalars or Normalize_Scalars is in effect. Construct an
4861 -- in-place initialization aggregate which may be convert into a fast
4862 -- memset by the backend.
4864 elsif Init_Or_Norm_Scalars
4865 and then Is_Array_Type
(T
)
4867 -- The array must lack atomic components because they are treated
4868 -- as non-static, and as a result the backend will not initialize
4869 -- the memory in one go.
4871 and then not Has_Atomic_Components
(T
)
4873 -- The array must not be packed because the invalid values in
4874 -- System.Scalar_Values are multiples of Storage_Unit.
4876 and then not Is_Packed
(T
)
4878 -- The array must have static non-empty ranges, otherwise the
4879 -- backend cannot initialize the memory in one go.
4881 and then Has_Static_Non_Empty_Array_Bounds
(T
)
4883 -- The optimization is only relevant for arrays of scalar types
4885 and then Is_Scalar_Type
(Component_Type
(T
))
4887 -- Similar to regular array initialization using a type init proc,
4888 -- predicate checks are not performed because the initialization
4889 -- values are intentionally invalid, and may violate the predicate.
4891 and then not Has_Predicates
(Component_Type
(T
))
4893 -- The component type must have a single initialization value
4895 and then Needs_Simple_Initialization
4896 (Typ
=> Component_Type
(T
),
4897 Consider_IS
=> True)
4900 Temp
:= Make_Temporary
(Loc
, 'P');
4903 -- Temp : Ptr_Typ := new ...;
4908 Make_Object_Declaration
(Loc
,
4909 Defining_Identifier
=> Temp
,
4910 Object_Definition
=> New_Occurrence_Of
(PtrT
, Loc
),
4911 Expression
=> Relocate_Node
(N
)),
4912 Suppress
=> All_Checks
);
4915 -- Temp.all := (others => ...);
4920 Make_Assignment_Statement
(Loc
,
4922 Make_Explicit_Dereference
(Loc
,
4923 Prefix
=> New_Occurrence_Of
(Temp
, Loc
)),
4928 Size
=> Esize
(Component_Type
(T
)))),
4929 Suppress
=> All_Checks
);
4931 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
4932 Analyze_And_Resolve
(N
, PtrT
);
4934 -- Case of no initialization procedure present
4936 elsif not Has_Non_Null_Base_Init_Proc
(T
) then
4938 -- Case of simple initialization required
4940 if Needs_Simple_Initialization
(T
) then
4941 Check_Restriction
(No_Default_Initialization
, N
);
4942 Rewrite
(Expression
(N
),
4943 Make_Qualified_Expression
(Loc
,
4944 Subtype_Mark
=> New_Occurrence_Of
(T
, Loc
),
4945 Expression
=> Get_Simple_Init_Val
(T
, N
)));
4947 Analyze_And_Resolve
(Expression
(Expression
(N
)), T
);
4948 Analyze_And_Resolve
(Expression
(N
), T
);
4949 Set_Paren_Count
(Expression
(Expression
(N
)), 1);
4950 Expand_N_Allocator
(N
);
4952 -- No initialization required
4955 Build_Allocate_Deallocate_Proc
4957 Is_Allocate
=> True);
4960 -- Case of initialization procedure present, must be called
4962 -- NOTE: There is a *huge* amount of code duplication here from
4963 -- Build_Initialization_Call. We should probably refactor???
4966 Check_Restriction
(No_Default_Initialization
, N
);
4968 if not Restriction_Active
(No_Default_Initialization
) then
4969 Init
:= Base_Init_Proc
(T
);
4971 Temp
:= Make_Temporary
(Loc
, 'P');
4973 -- Construct argument list for the initialization routine call
4976 Make_Explicit_Dereference
(Loc
,
4978 New_Occurrence_Of
(Temp
, Loc
));
4980 Set_Assignment_OK
(Init_Arg1
);
4983 -- The initialization procedure expects a specific type. if the
4984 -- context is access to class wide, indicate that the object
4985 -- being allocated has the right specific type.
4987 if Is_Class_Wide_Type
(Dtyp
) then
4988 Init_Arg1
:= Unchecked_Convert_To
(T
, Init_Arg1
);
4991 -- If designated type is a concurrent type or if it is private
4992 -- type whose definition is a concurrent type, the first
4993 -- argument in the Init routine has to be unchecked conversion
4994 -- to the corresponding record type. If the designated type is
4995 -- a derived type, also convert the argument to its root type.
4997 if Is_Concurrent_Type
(T
) then
4999 Unchecked_Convert_To
(
5000 Corresponding_Record_Type
(T
), Init_Arg1
);
5002 elsif Is_Private_Type
(T
)
5003 and then Present
(Full_View
(T
))
5004 and then Is_Concurrent_Type
(Full_View
(T
))
5007 Unchecked_Convert_To
5008 (Corresponding_Record_Type
(Full_View
(T
)), Init_Arg1
);
5010 elsif Etype
(First_Formal
(Init
)) /= Base_Type
(T
) then
5012 Ftyp
: constant Entity_Id
:= Etype
(First_Formal
(Init
));
5015 Init_Arg1
:= OK_Convert_To
(Etype
(Ftyp
), Init_Arg1
);
5016 Set_Etype
(Init_Arg1
, Ftyp
);
5020 Args
:= New_List
(Init_Arg1
);
5022 -- For the task case, pass the Master_Id of the access type as
5023 -- the value of the _Master parameter, and _Chain as the value
5024 -- of the _Chain parameter (_Chain will be defined as part of
5025 -- the generated code for the allocator).
5027 -- In Ada 2005, the context may be a function that returns an
5028 -- anonymous access type. In that case the Master_Id has been
5029 -- created when expanding the function declaration.
5031 if Has_Task
(T
) then
5032 if No
(Master_Id
(Base_Type
(PtrT
))) then
5034 -- The designated type was an incomplete type, and the
5035 -- access type did not get expanded. Salvage it now.
5037 if Present
(Parent
(Base_Type
(PtrT
))) then
5038 Expand_N_Full_Type_Declaration
5039 (Parent
(Base_Type
(PtrT
)));
5041 -- The only other possibility is an itype. For this
5042 -- case, the master must exist in the context. This is
5043 -- the case when the allocator initializes an access
5044 -- component in an init-proc.
5047 pragma Assert
(Is_Itype
(PtrT
));
5048 Build_Master_Renaming
(PtrT
, N
);
5052 -- If the context of the allocator is a declaration or an
5053 -- assignment, we can generate a meaningful image for it,
5054 -- even though subsequent assignments might remove the
5055 -- connection between task and entity. We build this image
5056 -- when the left-hand side is a simple variable, a simple
5057 -- indexed assignment or a simple selected component.
5059 if Nkind
(Parent
(N
)) = N_Assignment_Statement
then
5061 Nam
: constant Node_Id
:= Name
(Parent
(N
));
5064 if Is_Entity_Name
(Nam
) then
5066 Build_Task_Image_Decls
5069 (Entity
(Nam
), Sloc
(Nam
)), T
);
5071 elsif Nkind
(Nam
) in N_Indexed_Component
5072 | N_Selected_Component
5073 and then Is_Entity_Name
(Prefix
(Nam
))
5076 Build_Task_Image_Decls
5077 (Loc
, Nam
, Etype
(Prefix
(Nam
)));
5079 Decls
:= Build_Task_Image_Decls
(Loc
, T
, T
);
5083 elsif Nkind
(Parent
(N
)) = N_Object_Declaration
then
5085 Build_Task_Image_Decls
5086 (Loc
, Defining_Identifier
(Parent
(N
)), T
);
5089 Decls
:= Build_Task_Image_Decls
(Loc
, T
, T
);
5092 if Restriction_Active
(No_Task_Hierarchy
) then
5094 (Args
, Make_Integer_Literal
(Loc
, Library_Task_Level
));
5098 (Master_Id
(Base_Type
(Root_Type
(PtrT
))), Loc
));
5101 Append_To
(Args
, Make_Identifier
(Loc
, Name_uChain
));
5103 Decl
:= Last
(Decls
);
5105 New_Occurrence_Of
(Defining_Identifier
(Decl
), Loc
));
5107 -- Has_Task is false, Decls not used
5113 -- Add discriminants if discriminated type
5116 Dis
: Boolean := False;
5117 Typ
: Entity_Id
:= Empty
;
5120 if Has_Discriminants
(T
) then
5124 -- Type may be a private type with no visible discriminants
5125 -- in which case check full view if in scope, or the
5126 -- underlying_full_view if dealing with a type whose full
5127 -- view may be derived from a private type whose own full
5128 -- view has discriminants.
5130 elsif Is_Private_Type
(T
) then
5131 if Present
(Full_View
(T
))
5132 and then Has_Discriminants
(Full_View
(T
))
5135 Typ
:= Full_View
(T
);
5137 elsif Present
(Underlying_Full_View
(T
))
5138 and then Has_Discriminants
(Underlying_Full_View
(T
))
5141 Typ
:= Underlying_Full_View
(T
);
5147 -- If the allocated object will be constrained by the
5148 -- default values for discriminants, then build a subtype
5149 -- with those defaults, and change the allocated subtype
5150 -- to that. Note that this happens in fewer cases in Ada
5153 if not Is_Constrained
(Typ
)
5154 and then Present
(Discriminant_Default_Value
5155 (First_Discriminant
(Typ
)))
5156 and then (Ada_Version
< Ada_2005
5158 Object_Type_Has_Constrained_Partial_View
5159 (Typ
, Current_Scope
))
5161 Typ
:= Build_Default_Subtype
(Typ
, N
);
5162 Set_Expression
(N
, New_Occurrence_Of
(Typ
, Loc
));
5165 Discr
:= First_Elmt
(Discriminant_Constraint
(Typ
));
5166 while Present
(Discr
) loop
5167 Nod
:= Node
(Discr
);
5168 Append
(New_Copy_Tree
(Node
(Discr
)), Args
);
5170 -- AI-416: when the discriminant constraint is an
5171 -- anonymous access type make sure an accessibility
5172 -- check is inserted if necessary (3.10.2(22.q/2))
5174 if Ada_Version
>= Ada_2005
5176 Ekind
(Etype
(Nod
)) = E_Anonymous_Access_Type
5178 No_Dynamic_Accessibility_Checks_Enabled
(Nod
)
5180 Apply_Accessibility_Check
5181 (Nod
, Typ
, Insert_Node
=> Nod
);
5189 -- We set the allocator as analyzed so that when we analyze
5190 -- the if expression node, we do not get an unwanted recursive
5191 -- expansion of the allocator expression.
5193 Set_Analyzed
(N
, True);
5194 Nod
:= Relocate_Node
(N
);
5196 -- Here is the transformation:
5197 -- input: new Ctrl_Typ
5198 -- output: Temp : constant Ctrl_Typ_Ptr := new Ctrl_Typ;
5199 -- Ctrl_TypIP (Temp.all, ...);
5200 -- [Deep_]Initialize (Temp.all);
5202 -- Here Ctrl_Typ_Ptr is the pointer type for the allocator, and
5203 -- is the subtype of the allocator.
5206 Make_Object_Declaration
(Loc
,
5207 Defining_Identifier
=> Temp
,
5208 Constant_Present
=> True,
5209 Object_Definition
=> New_Occurrence_Of
(Temp_Type
, Loc
),
5212 Set_Assignment_OK
(Temp_Decl
);
5213 Insert_Action
(N
, Temp_Decl
, Suppress
=> All_Checks
);
5215 Build_Allocate_Deallocate_Proc
(Temp_Decl
, True);
5217 -- If the designated type is a task type or contains tasks,
5218 -- create block to activate created tasks, and insert
5219 -- declaration for Task_Image variable ahead of call.
5221 if Has_Task
(T
) then
5223 L
: constant List_Id
:= New_List
;
5226 Build_Task_Allocate_Block
(L
, Nod
, Args
);
5228 Insert_List_Before
(First
(Declarations
(Blk
)), Decls
);
5229 Insert_Actions
(N
, L
);
5234 Make_Procedure_Call_Statement
(Loc
,
5235 Name
=> New_Occurrence_Of
(Init
, Loc
),
5236 Parameter_Associations
=> Args
));
5239 if Needs_Finalization
(T
) then
5242 -- [Deep_]Initialize (Init_Arg1);
5246 (Obj_Ref
=> New_Copy_Tree
(Init_Arg1
),
5249 -- Guard against a missing [Deep_]Initialize when the
5250 -- designated type was not properly frozen.
5252 if Present
(Init_Call
) then
5253 Insert_Action
(N
, Init_Call
);
5257 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
5258 Analyze_And_Resolve
(N
, PtrT
);
5260 -- When designated type has Default_Initial_Condition aspects,
5261 -- make a call to the type's DIC procedure to perform the
5262 -- checks. Theoretically this might also be needed for cases
5263 -- where the type doesn't have an init proc, but those should
5264 -- be very uncommon, and for now we only support the init proc
5268 and then Present
(DIC_Procedure
(Dtyp
))
5269 and then not Has_Null_Body
(DIC_Procedure
(Dtyp
))
5272 Build_DIC_Call
(Loc
,
5273 Make_Explicit_Dereference
(Loc
,
5274 Prefix
=> New_Occurrence_Of
(Temp
, Loc
)),
5281 -- Ada 2005 (AI-251): If the allocator is for a class-wide interface
5282 -- object that has been rewritten as a reference, we displace "this"
5283 -- to reference properly its secondary dispatch table.
5285 if Nkind
(N
) = N_Identifier
and then Is_Interface
(Dtyp
) then
5286 Displace_Allocator_Pointer
(N
);
5290 when RE_Not_Available
=>
5292 end Expand_N_Allocator
;
5294 -----------------------
5295 -- Expand_N_And_Then --
5296 -----------------------
5298 procedure Expand_N_And_Then
(N
: Node_Id
)
5299 renames Expand_Short_Circuit_Operator
;
5301 ------------------------------
5302 -- Expand_N_Case_Expression --
5303 ------------------------------
5305 procedure Expand_N_Case_Expression
(N
: Node_Id
) is
5306 function Is_Copy_Type
(Typ
: Entity_Id
) return Boolean;
5307 -- Return True if we can copy objects of this type when expanding a case
5314 function Is_Copy_Type
(Typ
: Entity_Id
) return Boolean is
5316 -- If Minimize_Expression_With_Actions is True, we can afford to copy
5317 -- large objects, as long as they are constrained and not limited.
5320 Is_Elementary_Type
(Underlying_Type
(Typ
))
5322 (Minimize_Expression_With_Actions
5323 and then Is_Constrained
(Underlying_Type
(Typ
))
5324 and then not Is_Limited_Type
(Underlying_Type
(Typ
)));
5329 Loc
: constant Source_Ptr
:= Sloc
(N
);
5330 Par
: constant Node_Id
:= Parent
(N
);
5331 Typ
: constant Entity_Id
:= Etype
(N
);
5335 Case_Stmt
: Node_Id
;
5338 Target
: Entity_Id
:= Empty
;
5339 Target_Typ
: Entity_Id
;
5341 In_Predicate
: Boolean := False;
5342 -- Flag set when the case expression appears within a predicate
5344 Optimize_Return_Stmt
: Boolean := False;
5345 -- Flag set when the case expression can be optimized in the context of
5346 -- a simple return statement.
5348 -- Start of processing for Expand_N_Case_Expression
5351 -- Check for MINIMIZED/ELIMINATED overflow mode
5353 if Minimized_Eliminated_Overflow_Check
(N
) then
5354 Apply_Arithmetic_Overflow_Check
(N
);
5358 -- If the case expression is a predicate specification, and the type
5359 -- to which it applies has a static predicate aspect, do not expand,
5360 -- because it will be converted to the proper predicate form later.
5362 if Ekind
(Current_Scope
) in E_Function | E_Procedure
5363 and then Is_Predicate_Function
(Current_Scope
)
5365 In_Predicate
:= True;
5367 if Has_Static_Predicate_Aspect
(Etype
(First_Entity
(Current_Scope
)))
5373 -- When the type of the case expression is elementary, expand
5375 -- (case X is when A => AX, when B => BX ...)
5390 -- In all other cases expand into
5393 -- type Ptr_Typ is access all Typ;
5394 -- Target : Ptr_Typ;
5397 -- Target := AX'Unrestricted_Access;
5399 -- Target := BX'Unrestricted_Access;
5402 -- in Target.all end;
5404 -- This approach avoids extra copies of potentially large objects. It
5405 -- also allows handling of values of limited or unconstrained types.
5406 -- Note that we do the copy also for constrained, nonlimited types
5407 -- when minimizing expressions with actions (e.g. when generating C
5408 -- code) since it allows us to do the optimization below in more cases.
5410 -- Small optimization: when the case expression appears in the context
5411 -- of a simple return statement, expand into
5422 Make_Case_Statement
(Loc
,
5423 Expression
=> Expression
(N
),
5424 Alternatives
=> New_List
);
5426 -- Preserve the original context for which the case statement is being
5427 -- generated. This is needed by the finalization machinery to prevent
5428 -- the premature finalization of controlled objects found within the
5431 Set_From_Conditional_Expression
(Case_Stmt
);
5436 if Is_Copy_Type
(Typ
) then
5439 -- Do not perform the optimization when the return statement is
5440 -- within a predicate function, as this causes spurious errors.
5442 Optimize_Return_Stmt
:=
5443 Nkind
(Par
) = N_Simple_Return_Statement
and then not In_Predicate
;
5445 -- Otherwise create an access type to handle the general case using
5446 -- 'Unrestricted_Access.
5449 -- type Ptr_Typ is access all Typ;
5452 if Generate_C_Code
then
5454 -- We cannot ensure that correct C code will be generated if any
5455 -- temporary is created down the line (to e.g. handle checks or
5456 -- capture values) since we might end up with dangling references
5457 -- to local variables, so better be safe and reject the construct.
5460 ("case expression too complex, use case statement instead", N
);
5463 Target_Typ
:= Make_Temporary
(Loc
, 'P');
5466 Make_Full_Type_Declaration
(Loc
,
5467 Defining_Identifier
=> Target_Typ
,
5469 Make_Access_To_Object_Definition
(Loc
,
5470 All_Present
=> True,
5471 Subtype_Indication
=> New_Occurrence_Of
(Typ
, Loc
))));
5474 -- Create the declaration of the target which captures the value of the
5478 -- Target : [Ptr_]Typ;
5480 if not Optimize_Return_Stmt
then
5481 Target
:= Make_Temporary
(Loc
, 'T');
5484 Make_Object_Declaration
(Loc
,
5485 Defining_Identifier
=> Target
,
5486 Object_Definition
=> New_Occurrence_Of
(Target_Typ
, Loc
));
5487 Set_No_Initialization
(Decl
);
5489 Append_To
(Acts
, Decl
);
5492 -- Process the alternatives
5494 Alt
:= First
(Alternatives
(N
));
5495 while Present
(Alt
) loop
5497 Alt_Expr
: Node_Id
:= Expression
(Alt
);
5498 Alt_Loc
: constant Source_Ptr
:= Sloc
(Alt_Expr
);
5503 -- Take the unrestricted access of the expression value for non-
5504 -- scalar types. This approach avoids big copies and covers the
5505 -- limited and unconstrained cases.
5508 -- AX'Unrestricted_Access
5510 if not Is_Copy_Type
(Typ
) then
5512 Make_Attribute_Reference
(Alt_Loc
,
5513 Prefix
=> Relocate_Node
(Alt_Expr
),
5514 Attribute_Name
=> Name_Unrestricted_Access
);
5518 -- return AX['Unrestricted_Access];
5520 if Optimize_Return_Stmt
then
5522 Make_Simple_Return_Statement
(Alt_Loc
,
5523 Expression
=> Alt_Expr
));
5526 -- Target := AX['Unrestricted_Access];
5529 LHS
:= New_Occurrence_Of
(Target
, Loc
);
5530 Set_Assignment_OK
(LHS
);
5533 Make_Assignment_Statement
(Alt_Loc
,
5535 Expression
=> Alt_Expr
));
5538 -- Propagate declarations inserted in the node by Insert_Actions
5539 -- (for example, temporaries generated to remove side effects).
5540 -- These actions must remain attached to the alternative, given
5541 -- that they are generated by the corresponding expression.
5543 if Present
(Actions
(Alt
)) then
5544 Prepend_List
(Actions
(Alt
), Stmts
);
5547 -- Finalize any transient objects on exit from the alternative.
5548 -- This is done only in the return optimization case because
5549 -- otherwise the case expression is converted into an expression
5550 -- with actions which already contains this form of processing.
5552 if Optimize_Return_Stmt
then
5553 Process_If_Case_Statements
(N
, Stmts
);
5557 (Alternatives
(Case_Stmt
),
5558 Make_Case_Statement_Alternative
(Sloc
(Alt
),
5559 Discrete_Choices
=> Discrete_Choices
(Alt
),
5560 Statements
=> Stmts
));
5566 -- Rewrite the parent return statement as a case statement
5568 if Optimize_Return_Stmt
then
5569 Rewrite
(Par
, Case_Stmt
);
5572 -- Otherwise convert the case expression into an expression with actions
5575 Append_To
(Acts
, Case_Stmt
);
5577 if Is_Copy_Type
(Typ
) then
5578 Expr
:= New_Occurrence_Of
(Target
, Loc
);
5582 Make_Explicit_Dereference
(Loc
,
5583 Prefix
=> New_Occurrence_Of
(Target
, Loc
));
5589 -- in Target[.all] end;
5592 Make_Expression_With_Actions
(Loc
,
5596 Analyze_And_Resolve
(N
, Typ
);
5598 end Expand_N_Case_Expression
;
5600 -----------------------------------
5601 -- Expand_N_Explicit_Dereference --
5602 -----------------------------------
5604 procedure Expand_N_Explicit_Dereference
(N
: Node_Id
) is
5606 -- Insert explicit dereference call for the checked storage pool case
5608 Insert_Dereference_Action
(Prefix
(N
));
5610 -- If the type is an Atomic type for which Atomic_Sync is enabled, then
5611 -- we set the atomic sync flag.
5613 if Is_Atomic
(Etype
(N
))
5614 and then not Atomic_Synchronization_Disabled
(Etype
(N
))
5616 Activate_Atomic_Synchronization
(N
);
5618 end Expand_N_Explicit_Dereference
;
5620 --------------------------------------
5621 -- Expand_N_Expression_With_Actions --
5622 --------------------------------------
5624 procedure Expand_N_Expression_With_Actions
(N
: Node_Id
) is
5625 Acts
: constant List_Id
:= Actions
(N
);
5627 procedure Force_Boolean_Evaluation
(Expr
: Node_Id
);
5628 -- Force the evaluation of Boolean expression Expr
5630 function Process_Action
(Act
: Node_Id
) return Traverse_Result
;
5631 -- Inspect and process a single action of an expression_with_actions for
5632 -- transient objects. If such objects are found, the routine generates
5633 -- code to clean them up when the context of the expression is evaluated
5636 ------------------------------
5637 -- Force_Boolean_Evaluation --
5638 ------------------------------
5640 procedure Force_Boolean_Evaluation
(Expr
: Node_Id
) is
5641 Loc
: constant Source_Ptr
:= Sloc
(N
);
5642 Flag_Decl
: Node_Id
;
5643 Flag_Id
: Entity_Id
;
5646 -- Relocate the expression to the actions list by capturing its value
5647 -- in a Boolean flag. Generate:
5648 -- Flag : constant Boolean := Expr;
5650 Flag_Id
:= Make_Temporary
(Loc
, 'F');
5653 Make_Object_Declaration
(Loc
,
5654 Defining_Identifier
=> Flag_Id
,
5655 Constant_Present
=> True,
5656 Object_Definition
=> New_Occurrence_Of
(Standard_Boolean
, Loc
),
5657 Expression
=> Relocate_Node
(Expr
));
5659 Append
(Flag_Decl
, Acts
);
5660 Analyze
(Flag_Decl
);
5662 -- Replace the expression with a reference to the flag
5664 Rewrite
(Expression
(N
), New_Occurrence_Of
(Flag_Id
, Loc
));
5665 Analyze
(Expression
(N
));
5666 end Force_Boolean_Evaluation
;
5668 --------------------
5669 -- Process_Action --
5670 --------------------
5672 function Process_Action
(Act
: Node_Id
) return Traverse_Result
is
5674 if Nkind
(Act
) = N_Object_Declaration
5675 and then Is_Finalizable_Transient
(Act
, N
)
5677 Process_Transient_In_Expression
(Act
, N
, Acts
);
5680 -- Avoid processing temporary function results multiple times when
5681 -- dealing with nested expression_with_actions.
5682 -- Similarly, do not process temporary function results in loops.
5683 -- This is done by Expand_N_Loop_Statement and Build_Finalizer.
5684 -- Note that we used to wrongly return Abandon instead of Skip here:
5685 -- this is wrong since it means that we were ignoring lots of
5686 -- relevant subsequent statements.
5688 elsif Nkind
(Act
) in N_Expression_With_Actions | N_Loop_Statement
then
5695 procedure Process_Single_Action
is new Traverse_Proc
(Process_Action
);
5701 -- Start of processing for Expand_N_Expression_With_Actions
5704 -- Do not evaluate the expression when it denotes an entity because the
5705 -- expression_with_actions node will be replaced by the reference.
5707 if Is_Entity_Name
(Expression
(N
)) then
5710 -- Do not evaluate the expression when there are no actions because the
5711 -- expression_with_actions node will be replaced by the expression.
5713 elsif No
(Acts
) or else Is_Empty_List
(Acts
) then
5716 -- Force the evaluation of the expression by capturing its value in a
5717 -- temporary. This ensures that aliases of transient objects do not leak
5718 -- to the expression of the expression_with_actions node:
5721 -- Trans_Id : Ctrl_Typ := ...;
5722 -- Alias : ... := Trans_Id;
5723 -- in ... Alias ... end;
5725 -- In the example above, Trans_Id cannot be finalized at the end of the
5726 -- actions list because this may affect the alias and the final value of
5727 -- the expression_with_actions. Forcing the evaluation encapsulates the
5728 -- reference to the Alias within the actions list:
5731 -- Trans_Id : Ctrl_Typ := ...;
5732 -- Alias : ... := Trans_Id;
5733 -- Val : constant Boolean := ... Alias ...;
5734 -- <finalize Trans_Id>
5737 -- Once this transformation is performed, it is safe to finalize the
5738 -- transient object at the end of the actions list.
5740 -- Note that Force_Evaluation does not remove side effects in operators
5741 -- because it assumes that all operands are evaluated and side effect
5742 -- free. This is not the case when an operand depends implicitly on the
5743 -- transient object through the use of access types.
5745 elsif Is_Boolean_Type
(Etype
(Expression
(N
))) then
5746 Force_Boolean_Evaluation
(Expression
(N
));
5748 -- The expression of an expression_with_actions node may not necessarily
5749 -- be Boolean when the node appears in an if expression. In this case do
5750 -- the usual forced evaluation to encapsulate potential aliasing.
5753 Force_Evaluation
(Expression
(N
));
5756 -- Process all transient objects found within the actions of the EWA
5759 Act
:= First
(Acts
);
5760 while Present
(Act
) loop
5761 Process_Single_Action
(Act
);
5765 -- Deal with case where there are no actions. In this case we simply
5766 -- rewrite the node with its expression since we don't need the actions
5767 -- and the specification of this node does not allow a null action list.
5769 -- Note: we use Rewrite instead of Replace, because Codepeer is using
5770 -- the expanded tree and relying on being able to retrieve the original
5771 -- tree in cases like this. This raises a whole lot of issues of whether
5772 -- we have problems elsewhere, which will be addressed in the future???
5774 if Is_Empty_List
(Acts
) then
5775 Rewrite
(N
, Relocate_Node
(Expression
(N
)));
5777 end Expand_N_Expression_With_Actions
;
5779 ----------------------------
5780 -- Expand_N_If_Expression --
5781 ----------------------------
5783 -- Deal with limited types and condition actions
5785 procedure Expand_N_If_Expression
(N
: Node_Id
) is
5786 Cond
: constant Node_Id
:= First
(Expressions
(N
));
5787 Loc
: constant Source_Ptr
:= Sloc
(N
);
5788 Thenx
: constant Node_Id
:= Next
(Cond
);
5789 Elsex
: constant Node_Id
:= Next
(Thenx
);
5790 Typ
: constant Entity_Id
:= Etype
(N
);
5798 -- Determine if we are dealing with a special case of a conditional
5799 -- expression used as an actual for an anonymous access type which
5800 -- forces us to transform the if expression into an expression with
5801 -- actions in order to create a temporary to capture the level of the
5802 -- expression in each branch.
5804 Force_Expand
: constant Boolean := Is_Anonymous_Access_Actual
(N
);
5806 -- Start of processing for Expand_N_If_Expression
5809 -- Check for MINIMIZED/ELIMINATED overflow mode.
5810 -- Apply_Arithmetic_Overflow_Check will not deal with Then/Else_Actions
5811 -- so skip this step if any actions are present.
5813 if Minimized_Eliminated_Overflow_Check
(N
)
5814 and then No
(Then_Actions
(N
))
5815 and then No
(Else_Actions
(N
))
5817 Apply_Arithmetic_Overflow_Check
(N
);
5821 -- Fold at compile time if condition known. We have already folded
5822 -- static if expressions, but it is possible to fold any case in which
5823 -- the condition is known at compile time, even though the result is
5826 -- Note that we don't do the fold of such cases in Sem_Elab because
5827 -- it can cause infinite loops with the expander adding a conditional
5828 -- expression, and Sem_Elab circuitry removing it repeatedly.
5830 if Compile_Time_Known_Value
(Cond
) then
5832 function Fold_Known_Value
(Cond
: Node_Id
) return Boolean;
5833 -- Fold at compile time. Assumes condition known. Return True if
5834 -- folding occurred, meaning we're done.
5836 ----------------------
5837 -- Fold_Known_Value --
5838 ----------------------
5840 function Fold_Known_Value
(Cond
: Node_Id
) return Boolean is
5842 if Is_True
(Expr_Value
(Cond
)) then
5844 Actions
:= Then_Actions
(N
);
5847 Actions
:= Else_Actions
(N
);
5852 if Present
(Actions
) then
5854 -- To minimize the use of Expression_With_Actions, just skip
5855 -- the optimization as it is not critical for correctness.
5857 if Minimize_Expression_With_Actions
then
5862 Make_Expression_With_Actions
(Loc
,
5863 Expression
=> Relocate_Node
(Expr
),
5864 Actions
=> Actions
));
5865 Analyze_And_Resolve
(N
, Typ
);
5868 Rewrite
(N
, Relocate_Node
(Expr
));
5871 -- Note that the result is never static (legitimate cases of
5872 -- static if expressions were folded in Sem_Eval).
5874 Set_Is_Static_Expression
(N
, False);
5876 end Fold_Known_Value
;
5879 if Fold_Known_Value
(Cond
) then
5885 -- If the type is limited, and the back end does not handle limited
5886 -- types, then we expand as follows to avoid the possibility of
5887 -- improper copying.
5889 -- type Ptr is access all Typ;
5893 -- Cnn := then-expr'Unrestricted_Access;
5896 -- Cnn := else-expr'Unrestricted_Access;
5899 -- and replace the if expression by a reference to Cnn.all.
5901 -- This special case can be skipped if the back end handles limited
5902 -- types properly and ensures that no incorrect copies are made.
5904 if Is_By_Reference_Type
(Typ
)
5905 and then not Back_End_Handles_Limited_Types
5907 -- When the "then" or "else" expressions involve controlled function
5908 -- calls, generated temporaries are chained on the corresponding list
5909 -- of actions. These temporaries need to be finalized after the if
5910 -- expression is evaluated.
5912 Process_If_Case_Statements
(N
, Then_Actions
(N
));
5913 Process_If_Case_Statements
(N
, Else_Actions
(N
));
5916 Cnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'C', N
);
5917 Ptr_Typ
: constant Entity_Id
:= Make_Temporary
(Loc
, 'A');
5921 -- type Ann is access all Typ;
5924 Make_Full_Type_Declaration
(Loc
,
5925 Defining_Identifier
=> Ptr_Typ
,
5927 Make_Access_To_Object_Definition
(Loc
,
5928 All_Present
=> True,
5929 Subtype_Indication
=> New_Occurrence_Of
(Typ
, Loc
))));
5935 Make_Object_Declaration
(Loc
,
5936 Defining_Identifier
=> Cnn
,
5937 Object_Definition
=> New_Occurrence_Of
(Ptr_Typ
, Loc
));
5941 -- Cnn := <Thenx>'Unrestricted_Access;
5943 -- Cnn := <Elsex>'Unrestricted_Access;
5947 Make_Implicit_If_Statement
(N
,
5948 Condition
=> Relocate_Node
(Cond
),
5949 Then_Statements
=> New_List
(
5950 Make_Assignment_Statement
(Sloc
(Thenx
),
5951 Name
=> New_Occurrence_Of
(Cnn
, Sloc
(Thenx
)),
5953 Make_Attribute_Reference
(Loc
,
5954 Prefix
=> Relocate_Node
(Thenx
),
5955 Attribute_Name
=> Name_Unrestricted_Access
))),
5957 Else_Statements
=> New_List
(
5958 Make_Assignment_Statement
(Sloc
(Elsex
),
5959 Name
=> New_Occurrence_Of
(Cnn
, Sloc
(Elsex
)),
5961 Make_Attribute_Reference
(Loc
,
5962 Prefix
=> Relocate_Node
(Elsex
),
5963 Attribute_Name
=> Name_Unrestricted_Access
))));
5965 -- Preserve the original context for which the if statement is
5966 -- being generated. This is needed by the finalization machinery
5967 -- to prevent the premature finalization of controlled objects
5968 -- found within the if statement.
5970 Set_From_Conditional_Expression
(New_If
);
5973 Make_Explicit_Dereference
(Loc
,
5974 Prefix
=> New_Occurrence_Of
(Cnn
, Loc
));
5977 -- If the result is an unconstrained array and the if expression is in a
5978 -- context other than the initializing expression of the declaration of
5979 -- an object, then we pull out the if expression as follows:
5981 -- Cnn : constant typ := if-expression
5983 -- and then replace the if expression with an occurrence of Cnn. This
5984 -- avoids the need in the back end to create on-the-fly variable length
5985 -- temporaries (which it cannot do!)
5987 -- Note that the test for being in an object declaration avoids doing an
5988 -- unnecessary expansion, and also avoids infinite recursion.
5990 elsif Is_Array_Type
(Typ
) and then not Is_Constrained
(Typ
)
5991 and then (Nkind
(Parent
(N
)) /= N_Object_Declaration
5992 or else Expression
(Parent
(N
)) /= N
)
5995 Cnn
: constant Node_Id
:= Make_Temporary
(Loc
, 'C', N
);
5999 Make_Object_Declaration
(Loc
,
6000 Defining_Identifier
=> Cnn
,
6001 Constant_Present
=> True,
6002 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
),
6003 Expression
=> Relocate_Node
(N
),
6004 Has_Init_Expression
=> True));
6006 Rewrite
(N
, New_Occurrence_Of
(Cnn
, Loc
));
6010 -- For other types, we only need to expand if there are other actions
6011 -- associated with either branch or we need to force expansion to deal
6012 -- with if expressions used as an actual of an anonymous access type.
6014 elsif Present
(Then_Actions
(N
))
6015 or else Present
(Else_Actions
(N
))
6016 or else Force_Expand
6019 -- We now wrap the actions into the appropriate expression
6021 if Minimize_Expression_With_Actions
6022 and then (Is_Elementary_Type
(Underlying_Type
(Typ
))
6023 or else Is_Constrained
(Underlying_Type
(Typ
)))
6025 -- If we can't use N_Expression_With_Actions nodes, then we insert
6026 -- the following sequence of actions (using Insert_Actions):
6031 -- Cnn := then-expr;
6037 -- and replace the if expression by a reference to Cnn
6040 Cnn
: constant Node_Id
:= Make_Temporary
(Loc
, 'C', N
);
6044 Make_Object_Declaration
(Loc
,
6045 Defining_Identifier
=> Cnn
,
6046 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
));
6049 Make_Implicit_If_Statement
(N
,
6050 Condition
=> Relocate_Node
(Cond
),
6052 Then_Statements
=> New_List
(
6053 Make_Assignment_Statement
(Sloc
(Thenx
),
6054 Name
=> New_Occurrence_Of
(Cnn
, Sloc
(Thenx
)),
6055 Expression
=> Relocate_Node
(Thenx
))),
6057 Else_Statements
=> New_List
(
6058 Make_Assignment_Statement
(Sloc
(Elsex
),
6059 Name
=> New_Occurrence_Of
(Cnn
, Sloc
(Elsex
)),
6060 Expression
=> Relocate_Node
(Elsex
))));
6062 Set_Assignment_OK
(Name
(First
(Then_Statements
(New_If
))));
6063 Set_Assignment_OK
(Name
(First
(Else_Statements
(New_If
))));
6065 New_N
:= New_Occurrence_Of
(Cnn
, Loc
);
6068 -- Regular path using Expression_With_Actions
6071 if Present
(Then_Actions
(N
)) then
6073 Make_Expression_With_Actions
(Sloc
(Thenx
),
6074 Actions
=> Then_Actions
(N
),
6075 Expression
=> Relocate_Node
(Thenx
)));
6077 Set_Then_Actions
(N
, No_List
);
6078 Analyze_And_Resolve
(Thenx
, Typ
);
6081 if Present
(Else_Actions
(N
)) then
6083 Make_Expression_With_Actions
(Sloc
(Elsex
),
6084 Actions
=> Else_Actions
(N
),
6085 Expression
=> Relocate_Node
(Elsex
)));
6087 Set_Else_Actions
(N
, No_List
);
6088 Analyze_And_Resolve
(Elsex
, Typ
);
6091 -- We must force expansion into an expression with actions when
6092 -- an if expression gets used directly as an actual for an
6093 -- anonymous access type.
6095 if Force_Expand
then
6097 Cnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'C');
6106 Make_Object_Declaration
(Loc
,
6107 Defining_Identifier
=> Cnn
,
6108 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
));
6109 Append_To
(Acts
, Decl
);
6111 Set_No_Initialization
(Decl
);
6121 Make_Implicit_If_Statement
(N
,
6122 Condition
=> Relocate_Node
(Cond
),
6123 Then_Statements
=> New_List
(
6124 Make_Assignment_Statement
(Sloc
(Thenx
),
6125 Name
=> New_Occurrence_Of
(Cnn
, Sloc
(Thenx
)),
6126 Expression
=> Relocate_Node
(Thenx
))),
6128 Else_Statements
=> New_List
(
6129 Make_Assignment_Statement
(Sloc
(Elsex
),
6130 Name
=> New_Occurrence_Of
(Cnn
, Sloc
(Elsex
)),
6131 Expression
=> Relocate_Node
(Elsex
))));
6132 Append_To
(Acts
, New_If
);
6140 Make_Expression_With_Actions
(Loc
,
6141 Expression
=> New_Occurrence_Of
(Cnn
, Loc
),
6143 Analyze_And_Resolve
(N
, Typ
);
6150 -- For the sake of GNATcoverage, generate an intermediate temporary in
6151 -- the case where the if-expression is a condition in an outer decision,
6152 -- in order to make sure that no branch is shared between the decisions.
6154 elsif Opt
.Suppress_Control_Flow_Optimizations
6155 and then Nkind
(Original_Node
(Parent
(N
))) in N_Case_Expression
6159 | N_Goto_When_Statement
6161 | N_Return_When_Statement
6165 Cnn
: constant Entity_Id
:= Make_Temporary
(Loc
, 'C');
6171 -- Cnn : constant Typ := N;
6175 Make_Object_Declaration
(Loc
,
6176 Defining_Identifier
=> Cnn
,
6177 Constant_Present
=> True,
6178 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
),
6179 Expression
=> Relocate_Node
(N
)));
6182 Make_Expression_With_Actions
(Loc
,
6183 Expression
=> New_Occurrence_Of
(Cnn
, Loc
),
6186 Analyze_And_Resolve
(N
, Typ
);
6190 -- If no actions then no expansion needed, gigi will handle it using the
6191 -- same approach as a C conditional expression.
6197 -- Fall through here for either the limited expansion, or the case of
6198 -- inserting actions for nonlimited types. In both these cases, we must
6199 -- move the SLOC of the parent If statement to the newly created one and
6200 -- change it to the SLOC of the expression which, after expansion, will
6201 -- correspond to what is being evaluated.
6203 if Present
(Parent
(N
)) and then Nkind
(Parent
(N
)) = N_If_Statement
then
6204 Set_Sloc
(New_If
, Sloc
(Parent
(N
)));
6205 Set_Sloc
(Parent
(N
), Loc
);
6208 -- Make sure Then_Actions and Else_Actions are appropriately moved
6209 -- to the new if statement.
6211 if Present
(Then_Actions
(N
)) then
6213 (First
(Then_Statements
(New_If
)), Then_Actions
(N
));
6216 if Present
(Else_Actions
(N
)) then
6218 (First
(Else_Statements
(New_If
)), Else_Actions
(N
));
6221 Insert_Action
(N
, Decl
);
6222 Insert_Action
(N
, New_If
);
6224 Analyze_And_Resolve
(N
, Typ
);
6225 end Expand_N_If_Expression
;
6231 procedure Expand_N_In
(N
: Node_Id
) is
6232 Loc
: constant Source_Ptr
:= Sloc
(N
);
6233 Restyp
: constant Entity_Id
:= Etype
(N
);
6234 Lop
: constant Node_Id
:= Left_Opnd
(N
);
6235 Rop
: constant Node_Id
:= Right_Opnd
(N
);
6236 Static
: constant Boolean := Is_OK_Static_Expression
(N
);
6238 procedure Substitute_Valid_Check
;
6239 -- Replaces node N by Lop'Valid. This is done when we have an explicit
6240 -- test for the left operand being in range of its subtype.
6242 ----------------------------
6243 -- Substitute_Valid_Check --
6244 ----------------------------
6246 procedure Substitute_Valid_Check
is
6247 function Is_OK_Object_Reference
(Nod
: Node_Id
) return Boolean;
6248 -- Determine whether arbitrary node Nod denotes a source object that
6249 -- may safely act as prefix of attribute 'Valid.
6251 ----------------------------
6252 -- Is_OK_Object_Reference --
6253 ----------------------------
6255 function Is_OK_Object_Reference
(Nod
: Node_Id
) return Boolean is
6259 -- Inspect the original operand
6261 Obj_Ref
:= Original_Node
(Nod
);
6263 -- The object reference must be a source construct, otherwise the
6264 -- codefix suggestion may refer to nonexistent code from a user
6267 if Comes_From_Source
(Obj_Ref
) then
6269 if Nkind
(Obj_Ref
) in
6271 N_Unchecked_Type_Conversion |
6272 N_Qualified_Expression
6274 Obj_Ref
:= Expression
(Obj_Ref
);
6280 return Is_Object_Reference
(Obj_Ref
);
6284 end Is_OK_Object_Reference
;
6286 -- Start of processing for Substitute_Valid_Check
6290 Make_Attribute_Reference
(Loc
,
6291 Prefix
=> Relocate_Node
(Lop
),
6292 Attribute_Name
=> Name_Valid
));
6294 Analyze_And_Resolve
(N
, Restyp
);
6296 -- Emit a warning when the left-hand operand of the membership test
6297 -- is a source object, otherwise the use of attribute 'Valid would be
6298 -- illegal. The warning is not given when overflow checking is either
6299 -- MINIMIZED or ELIMINATED, as the danger of optimization has been
6300 -- eliminated above.
6302 if Is_OK_Object_Reference
(Lop
)
6303 and then Overflow_Check_Mode
not in Minimized_Or_Eliminated
6306 ("??explicit membership test may be optimized away", N
);
6307 Error_Msg_N
-- CODEFIX
6308 ("\??use ''Valid attribute instead", N
);
6310 end Substitute_Valid_Check
;
6317 -- Start of processing for Expand_N_In
6320 -- If set membership case, expand with separate procedure
6322 if Present
(Alternatives
(N
)) then
6323 Expand_Set_Membership
(N
);
6327 -- Not set membership, proceed with expansion
6329 Ltyp
:= Etype
(Left_Opnd
(N
));
6330 Rtyp
:= Etype
(Right_Opnd
(N
));
6332 -- If MINIMIZED/ELIMINATED overflow mode and type is a signed integer
6333 -- type, then expand with a separate procedure. Note the use of the
6334 -- flag No_Minimize_Eliminate to prevent infinite recursion.
6336 if Minimized_Eliminated_Overflow_Check
(Left_Opnd
(N
))
6337 and then not No_Minimize_Eliminate
(N
)
6339 Expand_Membership_Minimize_Eliminate_Overflow
(N
);
6343 -- Check case of explicit test for an expression in range of its
6344 -- subtype. This is suspicious usage and we replace it with a 'Valid
6345 -- test and give a warning for scalar types.
6347 if Is_Scalar_Type
(Ltyp
)
6349 -- Only relevant for source comparisons
6351 and then Comes_From_Source
(N
)
6353 -- In floating-point this is a standard way to check for finite values
6354 -- and using 'Valid would typically be a pessimization.
6356 and then not Is_Floating_Point_Type
(Ltyp
)
6358 -- Don't give the message unless right operand is a type entity and
6359 -- the type of the left operand matches this type. Note that this
6360 -- eliminates the cases where MINIMIZED/ELIMINATED mode overflow
6361 -- checks have changed the type of the left operand.
6363 and then Nkind
(Rop
) in N_Has_Entity
6364 and then Ltyp
= Entity
(Rop
)
6366 -- Skip this for predicated types, where such expressions are a
6367 -- reasonable way of testing if something meets the predicate.
6369 and then not Present
(Predicate_Function
(Ltyp
))
6371 Substitute_Valid_Check
;
6375 -- Do validity check on operands
6377 if Validity_Checks_On
and Validity_Check_Operands
then
6378 Ensure_Valid
(Left_Opnd
(N
));
6379 Validity_Check_Range
(Right_Opnd
(N
));
6382 -- Case of explicit range
6384 if Nkind
(Rop
) = N_Range
then
6386 Lo
: constant Node_Id
:= Low_Bound
(Rop
);
6387 Hi
: constant Node_Id
:= High_Bound
(Rop
);
6389 Lo_Orig
: constant Node_Id
:= Original_Node
(Lo
);
6390 Hi_Orig
: constant Node_Id
:= Original_Node
(Hi
);
6392 Lcheck
: Compare_Result
;
6393 Ucheck
: Compare_Result
;
6395 Warn1
: constant Boolean :=
6396 Constant_Condition_Warnings
6397 and then Comes_From_Source
(N
)
6398 and then not In_Instance
;
6399 -- This must be true for any of the optimization warnings, we
6400 -- clearly want to give them only for source with the flag on. We
6401 -- also skip these warnings in an instance since it may be the
6402 -- case that different instantiations have different ranges.
6404 Warn2
: constant Boolean :=
6406 and then Nkind
(Original_Node
(Rop
)) = N_Range
6407 and then Is_Integer_Type
(Etype
(Lo
));
6408 -- For the case where only one bound warning is elided, we also
6409 -- insist on an explicit range and an integer type. The reason is
6410 -- that the use of enumeration ranges including an end point is
6411 -- common, as is the use of a subtype name, one of whose bounds is
6412 -- the same as the type of the expression.
6415 -- If test is explicit x'First .. x'Last, replace by valid check
6417 if Is_Scalar_Type
(Ltyp
)
6419 -- And left operand is X'First where X matches left operand
6420 -- type (this eliminates cases of type mismatch, including
6421 -- the cases where ELIMINATED/MINIMIZED mode has changed the
6422 -- type of the left operand.
6424 and then Nkind
(Lo_Orig
) = N_Attribute_Reference
6425 and then Attribute_Name
(Lo_Orig
) = Name_First
6426 and then Nkind
(Prefix
(Lo_Orig
)) in N_Has_Entity
6427 and then Entity
(Prefix
(Lo_Orig
)) = Ltyp
6429 -- Same tests for right operand
6431 and then Nkind
(Hi_Orig
) = N_Attribute_Reference
6432 and then Attribute_Name
(Hi_Orig
) = Name_Last
6433 and then Nkind
(Prefix
(Hi_Orig
)) in N_Has_Entity
6434 and then Entity
(Prefix
(Hi_Orig
)) = Ltyp
6436 -- Relevant only for source cases
6438 and then Comes_From_Source
(N
)
6440 Substitute_Valid_Check
;
6444 -- If bounds of type are known at compile time, and the end points
6445 -- are known at compile time and identical, this is another case
6446 -- for substituting a valid test. We only do this for discrete
6447 -- types, since it won't arise in practice for float types.
6449 if Comes_From_Source
(N
)
6450 and then Is_Discrete_Type
(Ltyp
)
6451 and then Compile_Time_Known_Value
(Type_High_Bound
(Ltyp
))
6452 and then Compile_Time_Known_Value
(Type_Low_Bound
(Ltyp
))
6453 and then Compile_Time_Known_Value
(Lo
)
6454 and then Compile_Time_Known_Value
(Hi
)
6455 and then Expr_Value
(Type_High_Bound
(Ltyp
)) = Expr_Value
(Hi
)
6456 and then Expr_Value
(Type_Low_Bound
(Ltyp
)) = Expr_Value
(Lo
)
6458 -- Kill warnings in instances, since they may be cases where we
6459 -- have a test in the generic that makes sense with some types
6460 -- and not with other types.
6462 -- Similarly, do not rewrite membership as a validity check if
6463 -- within the predicate function for the type.
6465 -- Finally, if the original bounds are type conversions, even
6466 -- if they have been folded into constants, there are different
6467 -- types involved and 'Valid is not appropriate.
6471 or else (Ekind
(Current_Scope
) = E_Function
6472 and then Is_Predicate_Function
(Current_Scope
))
6476 elsif Nkind
(Lo_Orig
) = N_Type_Conversion
6477 or else Nkind
(Hi_Orig
) = N_Type_Conversion
6482 Substitute_Valid_Check
;
6487 -- If we have an explicit range, do a bit of optimization based on
6488 -- range analysis (we may be able to kill one or both checks).
6490 Lcheck
:= Compile_Time_Compare
(Lop
, Lo
, Assume_Valid
=> False);
6491 Ucheck
:= Compile_Time_Compare
(Lop
, Hi
, Assume_Valid
=> False);
6493 -- If either check is known to fail, replace result by False since
6494 -- the other check does not matter. Preserve the static flag for
6495 -- legality checks, because we are constant-folding beyond RM 4.9.
6497 if Lcheck
= LT
or else Ucheck
= GT
then
6499 Error_Msg_N
("?c?range test optimized away", N
);
6500 Error_Msg_N
("\?c?value is known to be out of range", N
);
6503 Rewrite
(N
, New_Occurrence_Of
(Standard_False
, Loc
));
6504 Analyze_And_Resolve
(N
, Restyp
);
6505 Set_Is_Static_Expression
(N
, Static
);
6508 -- If both checks are known to succeed, replace result by True,
6509 -- since we know we are in range.
6511 elsif Lcheck
in Compare_GE
and then Ucheck
in Compare_LE
then
6513 Error_Msg_N
("?c?range test optimized away", N
);
6514 Error_Msg_N
("\?c?value is known to be in range", N
);
6517 Rewrite
(N
, New_Occurrence_Of
(Standard_True
, Loc
));
6518 Analyze_And_Resolve
(N
, Restyp
);
6519 Set_Is_Static_Expression
(N
, Static
);
6522 -- If lower bound check succeeds and upper bound check is not
6523 -- known to succeed or fail, then replace the range check with
6524 -- a comparison against the upper bound.
6526 elsif Lcheck
in Compare_GE
then
6527 if Warn2
and then not In_Instance
then
6528 Error_Msg_N
("??lower bound test optimized away", Lo
);
6529 Error_Msg_N
("\??value is known to be in range", Lo
);
6535 Right_Opnd
=> High_Bound
(Rop
)));
6536 Analyze_And_Resolve
(N
, Restyp
);
6539 -- If upper bound check succeeds and lower bound check is not
6540 -- known to succeed or fail, then replace the range check with
6541 -- a comparison against the lower bound.
6543 elsif Ucheck
in Compare_LE
then
6544 if Warn2
and then not In_Instance
then
6545 Error_Msg_N
("??upper bound test optimized away", Hi
);
6546 Error_Msg_N
("\??value is known to be in range", Hi
);
6552 Right_Opnd
=> Low_Bound
(Rop
)));
6553 Analyze_And_Resolve
(N
, Restyp
);
6557 -- We couldn't optimize away the range check, but there is one
6558 -- more issue. If we are checking constant conditionals, then we
6559 -- see if we can determine the outcome assuming everything is
6560 -- valid, and if so give an appropriate warning.
6562 if Warn1
and then not Assume_No_Invalid_Values
then
6563 Lcheck
:= Compile_Time_Compare
(Lop
, Lo
, Assume_Valid
=> True);
6564 Ucheck
:= Compile_Time_Compare
(Lop
, Hi
, Assume_Valid
=> True);
6566 -- Result is out of range for valid value
6568 if Lcheck
= LT
or else Ucheck
= GT
then
6570 ("?c?value can only be in range if it is invalid", N
);
6572 -- Result is in range for valid value
6574 elsif Lcheck
in Compare_GE
and then Ucheck
in Compare_LE
then
6576 ("?c?value can only be out of range if it is invalid", N
);
6578 -- Lower bound check succeeds if value is valid
6580 elsif Warn2
and then Lcheck
in Compare_GE
then
6582 ("?c?lower bound check only fails if it is invalid", Lo
);
6584 -- Upper bound check succeeds if value is valid
6586 elsif Warn2
and then Ucheck
in Compare_LE
then
6588 ("?c?upper bound check only fails for invalid values", Hi
);
6593 -- Try to narrow the operation
6595 if Ltyp
= Universal_Integer
and then Nkind
(N
) = N_In
then
6596 Narrow_Large_Operation
(N
);
6599 -- For all other cases of an explicit range, nothing to be done
6603 -- Here right operand is a subtype mark
6607 Typ
: Entity_Id
:= Etype
(Rop
);
6608 Is_Acc
: constant Boolean := Is_Access_Type
(Typ
);
6609 Check_Null_Exclusion
: Boolean;
6610 Cond
: Node_Id
:= Empty
;
6612 Obj
: Node_Id
:= Lop
;
6613 SCIL_Node
: Node_Id
;
6616 Remove_Side_Effects
(Obj
);
6618 -- For tagged type, do tagged membership operation
6620 if Is_Tagged_Type
(Typ
) then
6622 -- No expansion will be performed for VM targets, as the VM
6623 -- back ends will handle the membership tests directly.
6625 if Tagged_Type_Expansion
then
6626 Tagged_Membership
(N
, SCIL_Node
, New_N
);
6628 Analyze_And_Resolve
(N
, Restyp
, Suppress
=> All_Checks
);
6630 -- Update decoration of relocated node referenced by the
6633 if Generate_SCIL
and then Present
(SCIL_Node
) then
6634 Set_SCIL_Node
(N
, SCIL_Node
);
6640 -- If type is scalar type, rewrite as x in t'First .. t'Last.
6641 -- This reason we do this is that the bounds may have the wrong
6642 -- type if they come from the original type definition. Also this
6643 -- way we get all the processing above for an explicit range.
6645 -- Don't do this for predicated types, since in this case we
6646 -- want to check the predicate.
6648 elsif Is_Scalar_Type
(Typ
) then
6649 if No
(Predicate_Function
(Typ
)) then
6653 Make_Attribute_Reference
(Loc
,
6654 Attribute_Name
=> Name_First
,
6655 Prefix
=> New_Occurrence_Of
(Typ
, Loc
)),
6658 Make_Attribute_Reference
(Loc
,
6659 Attribute_Name
=> Name_Last
,
6660 Prefix
=> New_Occurrence_Of
(Typ
, Loc
))));
6661 Analyze_And_Resolve
(N
, Restyp
);
6666 -- Ada 2005 (AI95-0216 amended by AI12-0162): Program_Error is
6667 -- raised when evaluating an individual membership test if the
6668 -- subtype mark denotes a constrained Unchecked_Union subtype
6669 -- and the expression lacks inferable discriminants.
6671 elsif Is_Unchecked_Union
(Base_Type
(Typ
))
6672 and then Is_Constrained
(Typ
)
6673 and then not Has_Inferable_Discriminants
(Lop
)
6676 Make_Expression_With_Actions
(Loc
,
6678 New_List
(Make_Raise_Program_Error
(Loc
,
6679 Reason
=> PE_Unchecked_Union_Restriction
)),
6681 New_Occurrence_Of
(Standard_False
, Loc
)));
6682 Analyze_And_Resolve
(N
, Restyp
);
6687 -- Here we have a non-scalar type
6691 -- If the null exclusion checks are not compatible, need to
6692 -- perform further checks. In other words, we cannot have
6693 -- Ltyp including null and Typ excluding null. All other cases
6696 Check_Null_Exclusion
:=
6697 Can_Never_Be_Null
(Typ
) and then not Can_Never_Be_Null
(Ltyp
);
6698 Typ
:= Designated_Type
(Typ
);
6701 if not Is_Constrained
(Typ
) then
6702 Cond
:= New_Occurrence_Of
(Standard_True
, Loc
);
6704 -- For the constrained array case, we have to check the subscripts
6705 -- for an exact match if the lengths are non-zero (the lengths
6706 -- must match in any case).
6708 elsif Is_Array_Type
(Typ
) then
6709 Check_Subscripts
: declare
6710 function Build_Attribute_Reference
6713 Dim
: Nat
) return Node_Id
;
6714 -- Build attribute reference E'Nam (Dim)
6716 -------------------------------
6717 -- Build_Attribute_Reference --
6718 -------------------------------
6720 function Build_Attribute_Reference
6723 Dim
: Nat
) return Node_Id
6727 Make_Attribute_Reference
(Loc
,
6729 Attribute_Name
=> Nam
,
6730 Expressions
=> New_List
(
6731 Make_Integer_Literal
(Loc
, Dim
)));
6732 end Build_Attribute_Reference
;
6734 -- Start of processing for Check_Subscripts
6737 for J
in 1 .. Number_Dimensions
(Typ
) loop
6738 Evolve_And_Then
(Cond
,
6741 Build_Attribute_Reference
6742 (Duplicate_Subexpr_No_Checks
(Obj
),
6745 Build_Attribute_Reference
6746 (New_Occurrence_Of
(Typ
, Loc
), Name_First
, J
)));
6748 Evolve_And_Then
(Cond
,
6751 Build_Attribute_Reference
6752 (Duplicate_Subexpr_No_Checks
(Obj
),
6755 Build_Attribute_Reference
6756 (New_Occurrence_Of
(Typ
, Loc
), Name_Last
, J
)));
6758 end Check_Subscripts
;
6760 -- These are the cases where constraint checks may be required,
6761 -- e.g. records with possible discriminants
6764 -- Expand the test into a series of discriminant comparisons.
6765 -- The expression that is built is the negation of the one that
6766 -- is used for checking discriminant constraints.
6768 Obj
:= Relocate_Node
(Left_Opnd
(N
));
6770 if Has_Discriminants
(Typ
) then
6771 Cond
:= Make_Op_Not
(Loc
,
6772 Right_Opnd
=> Build_Discriminant_Checks
(Obj
, Typ
));
6774 Cond
:= New_Occurrence_Of
(Standard_True
, Loc
);
6779 if Check_Null_Exclusion
then
6780 Cond
:= Make_And_Then
(Loc
,
6784 Right_Opnd
=> Make_Null
(Loc
)),
6785 Right_Opnd
=> Cond
);
6787 Cond
:= Make_Or_Else
(Loc
,
6791 Right_Opnd
=> Make_Null
(Loc
)),
6792 Right_Opnd
=> Cond
);
6797 Analyze_And_Resolve
(N
, Restyp
);
6799 -- Ada 2012 (AI05-0149): Handle membership tests applied to an
6800 -- expression of an anonymous access type. This can involve an
6801 -- accessibility test and a tagged type membership test in the
6802 -- case of tagged designated types.
6804 if Ada_Version
>= Ada_2012
6806 and then Ekind
(Ltyp
) = E_Anonymous_Access_Type
6809 Expr_Entity
: Entity_Id
:= Empty
;
6811 Param_Level
: Node_Id
;
6812 Type_Level
: Node_Id
;
6815 if Is_Entity_Name
(Lop
) then
6816 Expr_Entity
:= Param_Entity
(Lop
);
6818 if not Present
(Expr_Entity
) then
6819 Expr_Entity
:= Entity
(Lop
);
6823 -- When restriction No_Dynamic_Accessibility_Checks is in
6824 -- effect, expand the membership test to a static value
6825 -- since we cannot rely on dynamic levels.
6827 if No_Dynamic_Accessibility_Checks_Enabled
(Lop
) then
6828 if Static_Accessibility_Level
6829 (Lop
, Object_Decl_Level
)
6830 > Type_Access_Level
(Rtyp
)
6832 Rewrite
(N
, New_Occurrence_Of
(Standard_False
, Loc
));
6834 Rewrite
(N
, New_Occurrence_Of
(Standard_True
, Loc
));
6836 Analyze_And_Resolve
(N
, Restyp
);
6838 -- If a conversion of the anonymous access value to the
6839 -- tested type would be illegal, then the result is False.
6841 elsif not Valid_Conversion
6842 (Lop
, Rtyp
, Lop
, Report_Errs
=> False)
6844 Rewrite
(N
, New_Occurrence_Of
(Standard_False
, Loc
));
6845 Analyze_And_Resolve
(N
, Restyp
);
6847 -- Apply an accessibility check if the access object has an
6848 -- associated access level and when the level of the type is
6849 -- less deep than the level of the access parameter. This
6850 -- can only occur for access parameters and stand-alone
6851 -- objects of an anonymous access type.
6854 Param_Level
:= Accessibility_Level
6855 (Expr_Entity
, Dynamic_Level
);
6858 Make_Integer_Literal
(Loc
, Type_Access_Level
(Rtyp
));
6860 -- Return True only if the accessibility level of the
6861 -- expression entity is not deeper than the level of
6862 -- the tested access type.
6866 Left_Opnd
=> Relocate_Node
(N
),
6867 Right_Opnd
=> Make_Op_Le
(Loc
,
6868 Left_Opnd
=> Param_Level
,
6869 Right_Opnd
=> Type_Level
)));
6871 Analyze_And_Resolve
(N
);
6873 -- If the designated type is tagged, do tagged membership
6876 if Is_Tagged_Type
(Typ
) then
6878 -- No expansion will be performed for VM targets, as
6879 -- the VM back ends will handle the membership tests
6882 if Tagged_Type_Expansion
then
6884 -- Note that we have to pass Original_Node, because
6885 -- the membership test might already have been
6886 -- rewritten by earlier parts of membership test.
6889 (Original_Node
(N
), SCIL_Node
, New_N
);
6891 -- Update decoration of relocated node referenced
6892 -- by the SCIL node.
6894 if Generate_SCIL
and then Present
(SCIL_Node
) then
6895 Set_SCIL_Node
(New_N
, SCIL_Node
);
6900 Left_Opnd
=> Relocate_Node
(N
),
6901 Right_Opnd
=> New_N
));
6903 Analyze_And_Resolve
(N
, Restyp
);
6912 -- At this point, we have done the processing required for the basic
6913 -- membership test, but not yet dealt with the predicate.
6917 -- If a predicate is present, then we do the predicate test, but we
6918 -- most certainly want to omit this if we are within the predicate
6919 -- function itself, since otherwise we have an infinite recursion.
6920 -- The check should also not be emitted when testing against a range
6921 -- (the check is only done when the right operand is a subtype; see
6922 -- RM12-4.5.2 (28.1/3-30/3)).
6924 Predicate_Check
: declare
6925 function In_Range_Check
return Boolean;
6926 -- Within an expanded range check that may raise Constraint_Error do
6927 -- not generate a predicate check as well. It is redundant because
6928 -- the context will add an explicit predicate check, and it will
6929 -- raise the wrong exception if it fails.
6931 --------------------
6932 -- In_Range_Check --
6933 --------------------
6935 function In_Range_Check
return Boolean is
6939 while Present
(P
) loop
6940 if Nkind
(P
) = N_Raise_Constraint_Error
then
6943 elsif Nkind
(P
) in N_Statement_Other_Than_Procedure_Call
6944 or else Nkind
(P
) = N_Procedure_Call_Statement
6945 or else Nkind
(P
) in N_Declaration
6958 PFunc
: constant Entity_Id
:= Predicate_Function
(Rtyp
);
6961 -- Start of processing for Predicate_Check
6965 and then Current_Scope
/= PFunc
6966 and then Nkind
(Rop
) /= N_Range
6968 if not In_Range_Check
then
6969 R_Op
:= Make_Predicate_Call
(Rtyp
, Lop
, Mem
=> True);
6971 R_Op
:= New_Occurrence_Of
(Standard_True
, Loc
);
6976 Left_Opnd
=> Relocate_Node
(N
),
6977 Right_Opnd
=> R_Op
));
6979 -- Analyze new expression, mark left operand as analyzed to
6980 -- avoid infinite recursion adding predicate calls. Similarly,
6981 -- suppress further range checks on the call.
6983 Set_Analyzed
(Left_Opnd
(N
));
6984 Analyze_And_Resolve
(N
, Standard_Boolean
, Suppress
=> All_Checks
);
6986 -- All done, skip attempt at compile time determination of result
6990 end Predicate_Check
;
6993 --------------------------------
6994 -- Expand_N_Indexed_Component --
6995 --------------------------------
6997 procedure Expand_N_Indexed_Component
(N
: Node_Id
) is
6999 Wild_Reads_May_Have_Bad_Side_Effects
: Boolean
7000 renames Validity_Check_Subscripts
;
7001 -- This Boolean needs to be True if reading from a bad address can
7002 -- have a bad side effect (e.g., a segmentation fault that is not
7003 -- transformed into a Storage_Error exception, or interactions with
7004 -- memory-mapped I/O) that needs to be prevented. This refers to the
7005 -- act of reading itself, not to any damage that might be caused later
7006 -- by making use of whatever value was read. We assume here that
7007 -- Validity_Check_Subscripts meets this requirement, but introduce
7008 -- this declaration in order to document this assumption.
7010 function Is_Renamed_Variable_Name
(N
: Node_Id
) return Boolean;
7011 -- Returns True if the given name occurs as part of the renaming
7012 -- of a variable. In this case, the indexing operation should be
7013 -- treated as a write, rather than a read, with respect to validity
7014 -- checking. This is because the renamed variable can later be
7017 function Type_Requires_Subscript_Validity_Checks_For_Reads
7018 (Typ
: Entity_Id
) return Boolean;
7019 -- If Wild_Reads_May_Have_Bad_Side_Effects is False and we are indexing
7020 -- into an array of characters in order to read an element, it is ok
7021 -- if an invalid index value goes undetected. But if it is an array of
7022 -- pointers or an array of tasks, the consequences of such a read are
7023 -- potentially more severe and so we want to detect an invalid index
7024 -- value. This function captures that distinction; this is intended to
7025 -- be consistent with the "but does not by itself lead to erroneous
7026 -- ... execution" rule of RM 13.9.1(11).
7028 ------------------------------
7029 -- Is_Renamed_Variable_Name --
7030 ------------------------------
7032 function Is_Renamed_Variable_Name
(N
: Node_Id
) return Boolean is
7033 Rover
: Node_Id
:= N
;
7035 if Is_Variable
(N
) then
7038 Rover_Parent
: constant Node_Id
:= Parent
(Rover
);
7040 case Nkind
(Rover_Parent
) is
7041 when N_Object_Renaming_Declaration
=>
7042 return Rover
= Name
(Rover_Parent
);
7044 when N_Indexed_Component
7046 | N_Selected_Component
7048 exit when Rover
/= Prefix
(Rover_Parent
);
7049 Rover
:= Rover_Parent
;
7051 -- No need to check for qualified expressions or type
7052 -- conversions here, mostly because of the Is_Variable
7053 -- test. It is possible to have a view conversion for
7054 -- which Is_Variable yields True and which occurs as
7055 -- part of an object renaming, but only if the type is
7056 -- tagged; in that case this function will not be called.
7065 end Is_Renamed_Variable_Name
;
7067 -------------------------------------------------------
7068 -- Type_Requires_Subscript_Validity_Checks_For_Reads --
7069 -------------------------------------------------------
7071 function Type_Requires_Subscript_Validity_Checks_For_Reads
7072 (Typ
: Entity_Id
) return Boolean
7074 -- a shorter name for recursive calls
7075 function Needs_Check
(Typ
: Entity_Id
) return Boolean renames
7076 Type_Requires_Subscript_Validity_Checks_For_Reads
;
7078 if Is_Access_Type
(Typ
)
7079 or else Is_Tagged_Type
(Typ
)
7080 or else Is_Concurrent_Type
(Typ
)
7081 or else (Is_Array_Type
(Typ
)
7082 and then Needs_Check
(Component_Type
(Typ
)))
7083 or else (Is_Scalar_Type
(Typ
)
7084 and then Has_Aspect
(Typ
, Aspect_Default_Value
))
7089 if Is_Record_Type
(Typ
) then
7091 Comp
: Entity_Id
:= First_Component_Or_Discriminant
(Typ
);
7093 while Present
(Comp
) loop
7094 if Needs_Check
(Etype
(Comp
)) then
7098 Next_Component_Or_Discriminant
(Comp
);
7104 end Type_Requires_Subscript_Validity_Checks_For_Reads
;
7108 Loc
: constant Source_Ptr
:= Sloc
(N
);
7109 Typ
: constant Entity_Id
:= Etype
(N
);
7110 P
: constant Node_Id
:= Prefix
(N
);
7111 T
: constant Entity_Id
:= Etype
(P
);
7113 -- Start of processing for Expand_N_Indexed_Component
7116 -- A special optimization, if we have an indexed component that is
7117 -- selecting from a slice, then we can eliminate the slice, since, for
7118 -- example, x (i .. j)(k) is identical to x(k). The only difference is
7119 -- the range check required by the slice. The range check for the slice
7120 -- itself has already been generated. The range check for the
7121 -- subscripting operation is ensured by converting the subject to
7122 -- the subtype of the slice.
7124 -- This optimization not only generates better code, avoiding slice
7125 -- messing especially in the packed case, but more importantly bypasses
7126 -- some problems in handling this peculiar case, for example, the issue
7127 -- of dealing specially with object renamings.
7129 if Nkind
(P
) = N_Slice
7131 -- This optimization is disabled for CodePeer because it can transform
7132 -- an index-check constraint_error into a range-check constraint_error
7133 -- and CodePeer cares about that distinction.
7135 and then not CodePeer_Mode
7138 Make_Indexed_Component
(Loc
,
7139 Prefix
=> Prefix
(P
),
7140 Expressions
=> New_List
(
7142 (Etype
(First_Index
(Etype
(P
))),
7143 First
(Expressions
(N
))))));
7144 Analyze_And_Resolve
(N
, Typ
);
7148 -- Ada 2005 (AI-318-02): If the prefix is a call to a build-in-place
7149 -- function, then additional actuals must be passed.
7151 if Is_Build_In_Place_Function_Call
(P
) then
7152 Make_Build_In_Place_Call_In_Anonymous_Context
(P
);
7154 -- Ada 2005 (AI-318-02): Specialization of the previous case for prefix
7155 -- containing build-in-place function calls whose returned object covers
7158 elsif Present
(Unqual_BIP_Iface_Function_Call
(P
)) then
7159 Make_Build_In_Place_Iface_Call_In_Anonymous_Context
(P
);
7162 -- Generate index and validity checks
7165 Dims_Checked
: Dimension_Set
(Dimensions
=>
7166 (if Is_Array_Type
(T
)
7167 then Number_Dimensions
(T
)
7169 -- Dims_Checked is used to avoid generating two checks (one in
7170 -- Generate_Index_Checks, one in Apply_Subscript_Validity_Checks)
7171 -- for the same index value in cases where the index check eliminates
7172 -- the need for the validity check. The Is_Array_Type test avoids
7173 -- cascading errors.
7176 Generate_Index_Checks
(N
, Checks_Generated
=> Dims_Checked
);
7178 if Validity_Checks_On
7179 and then (Validity_Check_Subscripts
7180 or else Wild_Reads_May_Have_Bad_Side_Effects
7181 or else Type_Requires_Subscript_Validity_Checks_For_Reads
7183 or else Is_Renamed_Variable_Name
(N
))
7185 if Validity_Check_Subscripts
then
7186 -- If we index into an array with an uninitialized variable
7187 -- and we generate an index check that passes at run time,
7188 -- passing that check does not ensure that the variable is
7189 -- valid (although it does in the common case where the
7190 -- object's subtype matches the index subtype).
7191 -- Consider an uninitialized variable with subtype 1 .. 10
7192 -- used to index into an array with bounds 1 .. 20 when the
7193 -- value of the uninitialized variable happens to be 15.
7194 -- The index check will succeed but the variable is invalid.
7195 -- If Validity_Check_Subscripts is True then we need to
7196 -- ensure validity, so we adjust Dims_Checked accordingly.
7197 Dims_Checked
.Elements
:= (others => False);
7199 elsif Is_Array_Type
(T
) then
7200 -- We are only adding extra validity checks here to
7201 -- deal with uninitialized variables (but this includes
7202 -- assigning one uninitialized variable to another). Other
7203 -- ways of producing invalid objects imply erroneousness, so
7204 -- the compiler can do whatever it wants for those cases.
7205 -- If an index type has the Default_Value aspect specified,
7206 -- then we don't have to worry about the possibility of an
7207 -- uninitialized variable, so no need for these extra
7211 Idx
: Node_Id
:= First_Index
(T
);
7213 for No_Check_Needed
of Dims_Checked
.Elements
loop
7214 No_Check_Needed
:= No_Check_Needed
7215 or else Has_Aspect
(Etype
(Idx
), Aspect_Default_Value
);
7221 Apply_Subscript_Validity_Checks
7222 (N
, No_Check_Needed
=> Dims_Checked
);
7226 -- If selecting from an array with atomic components, and atomic sync
7227 -- is not suppressed for this array type, set atomic sync flag.
7229 if (Has_Atomic_Components
(T
)
7230 and then not Atomic_Synchronization_Disabled
(T
))
7231 or else (Is_Atomic
(Typ
)
7232 and then not Atomic_Synchronization_Disabled
(Typ
))
7233 or else (Is_Entity_Name
(P
)
7234 and then Has_Atomic_Components
(Entity
(P
))
7235 and then not Atomic_Synchronization_Disabled
(Entity
(P
)))
7237 Activate_Atomic_Synchronization
(N
);
7240 -- All done if the prefix is not a packed array implemented specially
7242 if not (Is_Packed
(Etype
(Prefix
(N
)))
7243 and then Present
(Packed_Array_Impl_Type
(Etype
(Prefix
(N
)))))
7248 -- For packed arrays that are not bit-packed (i.e. the case of an array
7249 -- with one or more index types with a non-contiguous enumeration type),
7250 -- we can always use the normal packed element get circuit.
7252 if not Is_Bit_Packed_Array
(Etype
(Prefix
(N
))) then
7253 Expand_Packed_Element_Reference
(N
);
7257 -- For a reference to a component of a bit packed array, we convert it
7258 -- to a reference to the corresponding Packed_Array_Impl_Type. We only
7259 -- want to do this for simple references, and not for:
7261 -- Left side of assignment, or prefix of left side of assignment, or
7262 -- prefix of the prefix, to handle packed arrays of packed arrays,
7263 -- This case is handled in Exp_Ch5.Expand_N_Assignment_Statement
7265 -- Renaming objects in renaming associations
7266 -- This case is handled when a use of the renamed variable occurs
7268 -- Actual parameters for a subprogram call
7269 -- This case is handled in Exp_Ch6.Expand_Actuals
7271 -- The second expression in a 'Read attribute reference
7273 -- The prefix of an address or bit or size attribute reference
7275 -- The following circuit detects these exceptions. Note that we need to
7276 -- deal with implicit dereferences when climbing up the parent chain,
7277 -- with the additional difficulty that the type of parents may have yet
7278 -- to be resolved since prefixes are usually resolved first.
7281 Child
: Node_Id
:= N
;
7282 Parnt
: Node_Id
:= Parent
(N
);
7286 if Nkind
(Parnt
) = N_Unchecked_Expression
then
7289 elsif Nkind
(Parnt
) = N_Object_Renaming_Declaration
then
7292 elsif Nkind
(Parnt
) in N_Subprogram_Call
7293 or else (Nkind
(Parnt
) = N_Parameter_Association
7294 and then Nkind
(Parent
(Parnt
)) in N_Subprogram_Call
)
7298 elsif Nkind
(Parnt
) = N_Attribute_Reference
7299 and then Attribute_Name
(Parnt
) in Name_Address
7302 and then Prefix
(Parnt
) = Child
7306 elsif Nkind
(Parnt
) = N_Assignment_Statement
7307 and then Name
(Parnt
) = Child
7311 -- If the expression is an index of an indexed component, it must
7312 -- be expanded regardless of context.
7314 elsif Nkind
(Parnt
) = N_Indexed_Component
7315 and then Child
/= Prefix
(Parnt
)
7317 Expand_Packed_Element_Reference
(N
);
7320 elsif Nkind
(Parent
(Parnt
)) = N_Assignment_Statement
7321 and then Name
(Parent
(Parnt
)) = Parnt
7325 elsif Nkind
(Parnt
) = N_Attribute_Reference
7326 and then Attribute_Name
(Parnt
) = Name_Read
7327 and then Next
(First
(Expressions
(Parnt
))) = Child
7331 elsif Nkind
(Parnt
) = N_Indexed_Component
7332 and then Prefix
(Parnt
) = Child
7336 elsif Nkind
(Parnt
) = N_Selected_Component
7337 and then Prefix
(Parnt
) = Child
7338 and then not (Present
(Etype
(Selector_Name
(Parnt
)))
7340 Is_Access_Type
(Etype
(Selector_Name
(Parnt
))))
7344 -- If the parent is a dereference, either implicit or explicit,
7345 -- then the packed reference needs to be expanded.
7348 Expand_Packed_Element_Reference
(N
);
7352 -- Keep looking up tree for unchecked expression, or if we are the
7353 -- prefix of a possible assignment left side.
7356 Parnt
:= Parent
(Child
);
7359 end Expand_N_Indexed_Component
;
7361 ---------------------
7362 -- Expand_N_Not_In --
7363 ---------------------
7365 -- Replace a not in b by not (a in b) so that the expansions for (a in b)
7366 -- can be done. This avoids needing to duplicate this expansion code.
7368 procedure Expand_N_Not_In
(N
: Node_Id
) is
7369 Loc
: constant Source_Ptr
:= Sloc
(N
);
7370 Typ
: constant Entity_Id
:= Etype
(N
);
7371 Cfs
: constant Boolean := Comes_From_Source
(N
);
7378 Left_Opnd
=> Left_Opnd
(N
),
7379 Right_Opnd
=> Right_Opnd
(N
))));
7381 -- If this is a set membership, preserve list of alternatives
7383 Set_Alternatives
(Right_Opnd
(N
), Alternatives
(Original_Node
(N
)));
7385 -- We want this to appear as coming from source if original does (see
7386 -- transformations in Expand_N_In).
7388 Set_Comes_From_Source
(N
, Cfs
);
7389 Set_Comes_From_Source
(Right_Opnd
(N
), Cfs
);
7391 -- Now analyze transformed node
7393 Analyze_And_Resolve
(N
, Typ
);
7394 end Expand_N_Not_In
;
7400 -- The only replacement required is for the case of a null of a type that
7401 -- is an access to protected subprogram, or a subtype thereof. We represent
7402 -- such access values as a record, and so we must replace the occurrence of
7403 -- null by the equivalent record (with a null address and a null pointer in
7404 -- it), so that the back end creates the proper value.
7406 procedure Expand_N_Null
(N
: Node_Id
) is
7407 Loc
: constant Source_Ptr
:= Sloc
(N
);
7408 Typ
: constant Entity_Id
:= Base_Type
(Etype
(N
));
7412 if Is_Access_Protected_Subprogram_Type
(Typ
) then
7414 Make_Aggregate
(Loc
,
7415 Expressions
=> New_List
(
7416 New_Occurrence_Of
(RTE
(RE_Null_Address
), Loc
),
7420 Analyze_And_Resolve
(N
, Equivalent_Type
(Typ
));
7422 -- For subsequent semantic analysis, the node must retain its type.
7423 -- Gigi in any case replaces this type by the corresponding record
7424 -- type before processing the node.
7430 when RE_Not_Available
=>
7434 ---------------------
7435 -- Expand_N_Op_Abs --
7436 ---------------------
7438 procedure Expand_N_Op_Abs
(N
: Node_Id
) is
7439 Loc
: constant Source_Ptr
:= Sloc
(N
);
7440 Expr
: constant Node_Id
:= Right_Opnd
(N
);
7441 Typ
: constant Entity_Id
:= Etype
(N
);
7444 Unary_Op_Validity_Checks
(N
);
7446 -- Check for MINIMIZED/ELIMINATED overflow mode
7448 if Minimized_Eliminated_Overflow_Check
(N
) then
7449 Apply_Arithmetic_Overflow_Check
(N
);
7453 -- Try to narrow the operation
7455 if Typ
= Universal_Integer
then
7456 Narrow_Large_Operation
(N
);
7458 if Nkind
(N
) /= N_Op_Abs
then
7463 -- Deal with software overflow checking
7465 if Is_Signed_Integer_Type
(Typ
)
7466 and then Do_Overflow_Check
(N
)
7468 -- The only case to worry about is when the argument is equal to the
7469 -- largest negative number, so what we do is to insert the check:
7471 -- [constraint_error when Expr = typ'Base'First]
7473 -- with the usual Duplicate_Subexpr use coding for expr
7476 Make_Raise_Constraint_Error
(Loc
,
7479 Left_Opnd
=> Duplicate_Subexpr
(Expr
),
7481 Make_Attribute_Reference
(Loc
,
7483 New_Occurrence_Of
(Base_Type
(Etype
(Expr
)), Loc
),
7484 Attribute_Name
=> Name_First
)),
7485 Reason
=> CE_Overflow_Check_Failed
));
7487 Set_Do_Overflow_Check
(N
, False);
7489 end Expand_N_Op_Abs
;
7491 ---------------------
7492 -- Expand_N_Op_Add --
7493 ---------------------
7495 procedure Expand_N_Op_Add
(N
: Node_Id
) is
7496 Typ
: constant Entity_Id
:= Etype
(N
);
7499 Binary_Op_Validity_Checks
(N
);
7501 -- Check for MINIMIZED/ELIMINATED overflow mode
7503 if Minimized_Eliminated_Overflow_Check
(N
) then
7504 Apply_Arithmetic_Overflow_Check
(N
);
7508 -- N + 0 = 0 + N = N for integer types
7510 if Is_Integer_Type
(Typ
) then
7511 if Compile_Time_Known_Value
(Right_Opnd
(N
))
7512 and then Expr_Value
(Right_Opnd
(N
)) = Uint_0
7514 Rewrite
(N
, Left_Opnd
(N
));
7517 elsif Compile_Time_Known_Value
(Left_Opnd
(N
))
7518 and then Expr_Value
(Left_Opnd
(N
)) = Uint_0
7520 Rewrite
(N
, Right_Opnd
(N
));
7525 -- Try to narrow the operation
7527 if Typ
= Universal_Integer
then
7528 Narrow_Large_Operation
(N
);
7530 if Nkind
(N
) /= N_Op_Add
then
7535 -- Arithmetic overflow checks for signed integer/fixed point types
7537 if Is_Signed_Integer_Type
(Typ
) or else Is_Fixed_Point_Type
(Typ
) then
7538 Apply_Arithmetic_Overflow_Check
(N
);
7542 -- Overflow checks for floating-point if -gnateF mode active
7544 Check_Float_Op_Overflow
(N
);
7546 Expand_Nonbinary_Modular_Op
(N
);
7547 end Expand_N_Op_Add
;
7549 ---------------------
7550 -- Expand_N_Op_And --
7551 ---------------------
7553 procedure Expand_N_Op_And
(N
: Node_Id
) is
7554 Typ
: constant Entity_Id
:= Etype
(N
);
7557 Binary_Op_Validity_Checks
(N
);
7559 if Is_Array_Type
(Etype
(N
)) then
7560 Expand_Boolean_Operator
(N
);
7562 elsif Is_Boolean_Type
(Etype
(N
)) then
7563 Adjust_Condition
(Left_Opnd
(N
));
7564 Adjust_Condition
(Right_Opnd
(N
));
7565 Set_Etype
(N
, Standard_Boolean
);
7566 Adjust_Result_Type
(N
, Typ
);
7568 elsif Is_Intrinsic_Subprogram
(Entity
(N
)) then
7569 Expand_Intrinsic_Call
(N
, Entity
(N
));
7572 Expand_Nonbinary_Modular_Op
(N
);
7573 end Expand_N_Op_And
;
7575 ------------------------
7576 -- Expand_N_Op_Concat --
7577 ------------------------
7579 procedure Expand_N_Op_Concat
(N
: Node_Id
) is
7581 -- List of operands to be concatenated
7584 -- Node which is to be replaced by the result of concatenating the nodes
7585 -- in the list Opnds.
7588 -- Ensure validity of both operands
7590 Binary_Op_Validity_Checks
(N
);
7592 -- If we are the left operand of a concatenation higher up the tree,
7593 -- then do nothing for now, since we want to deal with a series of
7594 -- concatenations as a unit.
7596 if Nkind
(Parent
(N
)) = N_Op_Concat
7597 and then N
= Left_Opnd
(Parent
(N
))
7602 -- We get here with a concatenation whose left operand may be a
7603 -- concatenation itself with a consistent type. We need to process
7604 -- these concatenation operands from left to right, which means
7605 -- from the deepest node in the tree to the highest node.
7608 while Nkind
(Left_Opnd
(Cnode
)) = N_Op_Concat
loop
7609 Cnode
:= Left_Opnd
(Cnode
);
7612 -- Now Cnode is the deepest concatenation, and its parents are the
7613 -- concatenation nodes above, so now we process bottom up, doing the
7616 -- The outer loop runs more than once if more than one concatenation
7617 -- type is involved.
7620 Opnds
:= New_List
(Left_Opnd
(Cnode
), Right_Opnd
(Cnode
));
7621 Set_Parent
(Opnds
, N
);
7623 -- The inner loop gathers concatenation operands
7625 Inner
: while Cnode
/= N
7626 and then Base_Type
(Etype
(Cnode
)) =
7627 Base_Type
(Etype
(Parent
(Cnode
)))
7629 Cnode
:= Parent
(Cnode
);
7630 Append
(Right_Opnd
(Cnode
), Opnds
);
7633 -- Note: The following code is a temporary workaround for N731-034
7634 -- and N829-028 and will be kept until the general issue of internal
7635 -- symbol serialization is addressed. The workaround is kept under a
7636 -- debug switch to avoid permiating into the general case.
7638 -- Wrap the node to concatenate into an expression actions node to
7639 -- keep it nicely packaged. This is useful in the case of an assert
7640 -- pragma with a concatenation where we want to be able to delete
7641 -- the concatenation and all its expansion stuff.
7643 if Debug_Flag_Dot_H
then
7645 Cnod
: constant Node_Id
:= New_Copy_Tree
(Cnode
);
7646 Typ
: constant Entity_Id
:= Base_Type
(Etype
(Cnode
));
7649 -- Note: use Rewrite rather than Replace here, so that for
7650 -- example Why_Not_Static can find the original concatenation
7654 Make_Expression_With_Actions
(Sloc
(Cnode
),
7655 Actions
=> New_List
(Make_Null_Statement
(Sloc
(Cnode
))),
7656 Expression
=> Cnod
));
7658 Expand_Concatenate
(Cnod
, Opnds
);
7659 Analyze_And_Resolve
(Cnode
, Typ
);
7665 Expand_Concatenate
(Cnode
, Opnds
);
7668 exit Outer
when Cnode
= N
;
7669 Cnode
:= Parent
(Cnode
);
7671 end Expand_N_Op_Concat
;
7673 ------------------------
7674 -- Expand_N_Op_Divide --
7675 ------------------------
7677 procedure Expand_N_Op_Divide
(N
: Node_Id
) is
7678 Loc
: constant Source_Ptr
:= Sloc
(N
);
7679 Lopnd
: constant Node_Id
:= Left_Opnd
(N
);
7680 Ropnd
: constant Node_Id
:= Right_Opnd
(N
);
7681 Ltyp
: constant Entity_Id
:= Etype
(Lopnd
);
7682 Rtyp
: constant Entity_Id
:= Etype
(Ropnd
);
7683 Typ
: Entity_Id
:= Etype
(N
);
7684 Rknow
: constant Boolean := Is_Integer_Type
(Typ
)
7686 Compile_Time_Known_Value
(Ropnd
);
7690 Binary_Op_Validity_Checks
(N
);
7692 -- Check for MINIMIZED/ELIMINATED overflow mode
7694 if Minimized_Eliminated_Overflow_Check
(N
) then
7695 Apply_Arithmetic_Overflow_Check
(N
);
7699 -- Otherwise proceed with expansion of division
7702 Rval
:= Expr_Value
(Ropnd
);
7705 -- N / 1 = N for integer types
7707 if Rknow
and then Rval
= Uint_1
then
7712 -- Try to narrow the operation
7714 if Typ
= Universal_Integer
then
7715 Narrow_Large_Operation
(N
);
7717 if Nkind
(N
) /= N_Op_Divide
then
7722 -- Convert x / 2 ** y to Shift_Right (x, y). Note that the fact that
7723 -- Is_Power_Of_2_For_Shift is set means that we know that our left
7724 -- operand is an unsigned integer, as required for this to work.
7726 if Nkind
(Ropnd
) = N_Op_Expon
7727 and then Is_Power_Of_2_For_Shift
(Ropnd
)
7729 -- We cannot do this transformation in configurable run time mode if we
7730 -- have 64-bit integers and long shifts are not available.
7732 and then (Esize
(Ltyp
) <= 32 or else Support_Long_Shifts_On_Target
)
7735 Make_Op_Shift_Right
(Loc
,
7738 Convert_To
(Standard_Natural
, Right_Opnd
(Ropnd
))));
7739 Analyze_And_Resolve
(N
, Typ
);
7743 -- Do required fixup of universal fixed operation
7745 if Typ
= Universal_Fixed
then
7746 Fixup_Universal_Fixed_Operation
(N
);
7750 -- Divisions with fixed-point results
7752 if Is_Fixed_Point_Type
(Typ
) then
7754 if Is_Integer_Type
(Rtyp
) then
7755 Expand_Divide_Fixed_By_Integer_Giving_Fixed
(N
);
7757 Expand_Divide_Fixed_By_Fixed_Giving_Fixed
(N
);
7760 -- Deal with divide-by-zero check if back end cannot handle them
7761 -- and the flag is set indicating that we need such a check. Note
7762 -- that we don't need to bother here with the case of mixed-mode
7763 -- (Right operand an integer type), since these will be rewritten
7764 -- with conversions to a divide with a fixed-point right operand.
7766 if Nkind
(N
) = N_Op_Divide
7767 and then Do_Division_Check
(N
)
7768 and then not Backend_Divide_Checks_On_Target
7769 and then not Is_Integer_Type
(Rtyp
)
7771 Set_Do_Division_Check
(N
, False);
7773 Make_Raise_Constraint_Error
(Loc
,
7776 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Ropnd
),
7777 Right_Opnd
=> Make_Real_Literal
(Loc
, Ureal_0
)),
7778 Reason
=> CE_Divide_By_Zero
));
7781 -- Other cases of division of fixed-point operands
7783 elsif Is_Fixed_Point_Type
(Ltyp
) or else Is_Fixed_Point_Type
(Rtyp
) then
7784 if Is_Integer_Type
(Typ
) then
7785 Expand_Divide_Fixed_By_Fixed_Giving_Integer
(N
);
7787 pragma Assert
(Is_Floating_Point_Type
(Typ
));
7788 Expand_Divide_Fixed_By_Fixed_Giving_Float
(N
);
7791 -- Mixed-mode operations can appear in a non-static universal context,
7792 -- in which case the integer argument must be converted explicitly.
7794 elsif Typ
= Universal_Real
and then Is_Integer_Type
(Rtyp
) then
7796 Convert_To
(Universal_Real
, Relocate_Node
(Ropnd
)));
7798 Analyze_And_Resolve
(Ropnd
, Universal_Real
);
7800 elsif Typ
= Universal_Real
and then Is_Integer_Type
(Ltyp
) then
7802 Convert_To
(Universal_Real
, Relocate_Node
(Lopnd
)));
7804 Analyze_And_Resolve
(Lopnd
, Universal_Real
);
7806 -- Non-fixed point cases, do integer zero divide and overflow checks
7808 elsif Is_Integer_Type
(Typ
) then
7809 Apply_Divide_Checks
(N
);
7812 -- Overflow checks for floating-point if -gnateF mode active
7814 Check_Float_Op_Overflow
(N
);
7816 Expand_Nonbinary_Modular_Op
(N
);
7817 end Expand_N_Op_Divide
;
7819 --------------------
7820 -- Expand_N_Op_Eq --
7821 --------------------
7823 procedure Expand_N_Op_Eq
(N
: Node_Id
) is
7824 Loc
: constant Source_Ptr
:= Sloc
(N
);
7825 Typ
: constant Entity_Id
:= Etype
(N
);
7826 Lhs
: constant Node_Id
:= Left_Opnd
(N
);
7827 Rhs
: constant Node_Id
:= Right_Opnd
(N
);
7828 Bodies
: constant List_Id
:= New_List
;
7829 A_Typ
: constant Entity_Id
:= Etype
(Lhs
);
7831 procedure Build_Equality_Call
(Eq
: Entity_Id
);
7832 -- If a constructed equality exists for the type or for its parent,
7833 -- build and analyze call, adding conversions if the operation is
7836 function Is_Equality
(Subp
: Entity_Id
;
7837 Typ
: Entity_Id
:= Empty
) return Boolean;
7838 -- Determine whether arbitrary Entity_Id denotes a function with the
7839 -- right name and profile for an equality op, specifically for the
7840 -- base type Typ if Typ is nonempty.
7842 function Find_Equality
(Prims
: Elist_Id
) return Entity_Id
;
7843 -- Find a primitive equality function within primitive operation list
7846 function User_Defined_Primitive_Equality_Op
7847 (Typ
: Entity_Id
) return Entity_Id
;
7848 -- Find a user-defined primitive equality function for a given untagged
7849 -- record type, ignoring visibility. Return Empty if no such op found.
7851 function Has_Unconstrained_UU_Component
(Typ
: Entity_Id
) return Boolean;
7852 -- Determines whether a type has a subcomponent of an unconstrained
7853 -- Unchecked_Union subtype. Typ is a record type.
7855 -------------------------
7856 -- Build_Equality_Call --
7857 -------------------------
7859 procedure Build_Equality_Call
(Eq
: Entity_Id
) is
7860 Op_Type
: constant Entity_Id
:= Etype
(First_Formal
(Eq
));
7861 L_Exp
: Node_Id
:= Relocate_Node
(Lhs
);
7862 R_Exp
: Node_Id
:= Relocate_Node
(Rhs
);
7865 -- Adjust operands if necessary to comparison type
7867 if Base_Type
(Op_Type
) /= Base_Type
(A_Typ
)
7868 and then not Is_Class_Wide_Type
(A_Typ
)
7870 L_Exp
:= OK_Convert_To
(Op_Type
, L_Exp
);
7871 R_Exp
:= OK_Convert_To
(Op_Type
, R_Exp
);
7874 -- If we have an Unchecked_Union, we need to add the inferred
7875 -- discriminant values as actuals in the function call. At this
7876 -- point, the expansion has determined that both operands have
7877 -- inferable discriminants.
7879 if Is_Unchecked_Union
(Op_Type
) then
7881 Lhs_Type
: constant Entity_Id
:= Etype
(L_Exp
);
7882 Rhs_Type
: constant Entity_Id
:= Etype
(R_Exp
);
7884 Lhs_Discr_Vals
: Elist_Id
;
7885 -- List of inferred discriminant values for left operand.
7887 Rhs_Discr_Vals
: Elist_Id
;
7888 -- List of inferred discriminant values for right operand.
7893 Lhs_Discr_Vals
:= New_Elmt_List
;
7894 Rhs_Discr_Vals
:= New_Elmt_List
;
7896 -- Per-object constrained selected components require special
7897 -- attention. If the enclosing scope of the component is an
7898 -- Unchecked_Union, we cannot reference its discriminants
7899 -- directly. This is why we use the extra parameters of the
7900 -- equality function of the enclosing Unchecked_Union.
7902 -- type UU_Type (Discr : Integer := 0) is
7905 -- pragma Unchecked_Union (UU_Type);
7907 -- 1. Unchecked_Union enclosing record:
7909 -- type Enclosing_UU_Type (Discr : Integer := 0) is record
7911 -- Comp : UU_Type (Discr);
7913 -- end Enclosing_UU_Type;
7914 -- pragma Unchecked_Union (Enclosing_UU_Type);
7916 -- Obj1 : Enclosing_UU_Type;
7917 -- Obj2 : Enclosing_UU_Type (1);
7919 -- [. . .] Obj1 = Obj2 [. . .]
7923 -- if not (uu_typeEQ (obj1.comp, obj2.comp, a, b)) then
7925 -- A and B are the formal parameters of the equality function
7926 -- of Enclosing_UU_Type. The function always has two extra
7927 -- formals to capture the inferred discriminant values for
7928 -- each discriminant of the type.
7930 -- 2. Non-Unchecked_Union enclosing record:
7933 -- Enclosing_Non_UU_Type (Discr : Integer := 0)
7936 -- Comp : UU_Type (Discr);
7938 -- end Enclosing_Non_UU_Type;
7940 -- Obj1 : Enclosing_Non_UU_Type;
7941 -- Obj2 : Enclosing_Non_UU_Type (1);
7943 -- ... Obj1 = Obj2 ...
7947 -- if not (uu_typeEQ (obj1.comp, obj2.comp,
7948 -- obj1.discr, obj2.discr)) then
7950 -- In this case we can directly reference the discriminants of
7951 -- the enclosing record.
7953 -- Process left operand of equality
7955 if Nkind
(Lhs
) = N_Selected_Component
7957 Has_Per_Object_Constraint
(Entity
(Selector_Name
(Lhs
)))
7959 -- If enclosing record is an Unchecked_Union, use formals
7960 -- corresponding to each discriminant. The name of the
7961 -- formal is that of the discriminant, with added suffix,
7962 -- see Exp_Ch3.Build_Record_Equality for details.
7964 if Is_Unchecked_Union
(Scope
(Entity
(Selector_Name
(Lhs
))))
7968 (Scope
(Entity
(Selector_Name
(Lhs
))));
7969 while Present
(Discr
) loop
7971 (Make_Identifier
(Loc
,
7972 Chars
=> New_External_Name
(Chars
(Discr
), 'A')),
7973 To
=> Lhs_Discr_Vals
);
7974 Next_Discriminant
(Discr
);
7977 -- If enclosing record is of a non-Unchecked_Union type, it
7978 -- is possible to reference its discriminants directly.
7981 Discr
:= First_Discriminant
(Lhs_Type
);
7982 while Present
(Discr
) loop
7984 (Make_Selected_Component
(Loc
,
7985 Prefix
=> Prefix
(Lhs
),
7988 (Get_Discriminant_Value
(Discr
,
7990 Stored_Constraint
(Lhs_Type
)))),
7991 To
=> Lhs_Discr_Vals
);
7992 Next_Discriminant
(Discr
);
7996 -- Otherwise operand is on object with a constrained type.
7997 -- Infer the discriminant values from the constraint.
8000 Discr
:= First_Discriminant
(Lhs_Type
);
8001 while Present
(Discr
) loop
8004 (Get_Discriminant_Value
(Discr
,
8006 Stored_Constraint
(Lhs_Type
))),
8007 To
=> Lhs_Discr_Vals
);
8008 Next_Discriminant
(Discr
);
8012 -- Similar processing for right operand of equality
8014 if Nkind
(Rhs
) = N_Selected_Component
8016 Has_Per_Object_Constraint
(Entity
(Selector_Name
(Rhs
)))
8018 if Is_Unchecked_Union
8019 (Scope
(Entity
(Selector_Name
(Rhs
))))
8023 (Scope
(Entity
(Selector_Name
(Rhs
))));
8024 while Present
(Discr
) loop
8026 (Make_Identifier
(Loc
,
8027 Chars
=> New_External_Name
(Chars
(Discr
), 'B')),
8028 To
=> Rhs_Discr_Vals
);
8029 Next_Discriminant
(Discr
);
8033 Discr
:= First_Discriminant
(Rhs_Type
);
8034 while Present
(Discr
) loop
8036 (Make_Selected_Component
(Loc
,
8037 Prefix
=> Prefix
(Rhs
),
8039 New_Copy
(Get_Discriminant_Value
8042 Stored_Constraint
(Rhs_Type
)))),
8043 To
=> Rhs_Discr_Vals
);
8044 Next_Discriminant
(Discr
);
8049 Discr
:= First_Discriminant
(Rhs_Type
);
8050 while Present
(Discr
) loop
8052 (New_Copy
(Get_Discriminant_Value
8055 Stored_Constraint
(Rhs_Type
))),
8056 To
=> Rhs_Discr_Vals
);
8057 Next_Discriminant
(Discr
);
8061 -- Now merge the list of discriminant values so that values
8062 -- of corresponding discriminants are adjacent.
8070 Params
:= New_List
(L_Exp
, R_Exp
);
8071 L_Elmt
:= First_Elmt
(Lhs_Discr_Vals
);
8072 R_Elmt
:= First_Elmt
(Rhs_Discr_Vals
);
8073 while Present
(L_Elmt
) loop
8074 Append_To
(Params
, Node
(L_Elmt
));
8075 Append_To
(Params
, Node
(R_Elmt
));
8081 Make_Function_Call
(Loc
,
8082 Name
=> New_Occurrence_Of
(Eq
, Loc
),
8083 Parameter_Associations
=> Params
));
8087 -- Normal case, not an unchecked union
8091 Make_Function_Call
(Loc
,
8092 Name
=> New_Occurrence_Of
(Eq
, Loc
),
8093 Parameter_Associations
=> New_List
(L_Exp
, R_Exp
)));
8096 Analyze_And_Resolve
(N
, Standard_Boolean
, Suppress
=> All_Checks
);
8097 end Build_Equality_Call
;
8103 function Is_Equality
(Subp
: Entity_Id
;
8104 Typ
: Entity_Id
:= Empty
) return Boolean is
8105 Formal_1
: Entity_Id
;
8106 Formal_2
: Entity_Id
;
8108 -- The equality function carries name "=", returns Boolean, and has
8109 -- exactly two formal parameters of an identical type.
8111 if Ekind
(Subp
) = E_Function
8112 and then Chars
(Subp
) = Name_Op_Eq
8113 and then Base_Type
(Etype
(Subp
)) = Standard_Boolean
8115 Formal_1
:= First_Formal
(Subp
);
8118 if Present
(Formal_1
) then
8119 Formal_2
:= Next_Formal
(Formal_1
);
8124 and then Present
(Formal_2
)
8125 and then No
(Next_Formal
(Formal_2
))
8126 and then Base_Type
(Etype
(Formal_1
)) =
8127 Base_Type
(Etype
(Formal_2
))
8130 or else Implementation_Base_Type
(Etype
(Formal_1
)) = Typ
);
8140 function Find_Equality
(Prims
: Elist_Id
) return Entity_Id
is
8141 function Find_Aliased_Equality
(Prim
: Entity_Id
) return Entity_Id
;
8142 -- Find an equality in a possible alias chain starting from primitive
8145 ---------------------------
8146 -- Find_Aliased_Equality --
8147 ---------------------------
8149 function Find_Aliased_Equality
(Prim
: Entity_Id
) return Entity_Id
is
8153 -- Inspect each candidate in the alias chain, checking whether it
8154 -- denotes an equality.
8157 while Present
(Candid
) loop
8158 if Is_Equality
(Candid
) then
8162 Candid
:= Alias
(Candid
);
8166 end Find_Aliased_Equality
;
8170 Eq_Prim
: Entity_Id
;
8171 Prim_Elmt
: Elmt_Id
;
8173 -- Start of processing for Find_Equality
8176 -- Assume that the tagged type lacks an equality
8180 -- Inspect the list of primitives looking for a suitable equality
8181 -- within a possible chain of aliases.
8183 Prim_Elmt
:= First_Elmt
(Prims
);
8184 while Present
(Prim_Elmt
) and then No
(Eq_Prim
) loop
8185 Eq_Prim
:= Find_Aliased_Equality
(Node
(Prim_Elmt
));
8187 Next_Elmt
(Prim_Elmt
);
8190 -- A tagged type should always have an equality
8192 pragma Assert
(Present
(Eq_Prim
));
8197 ----------------------------------------
8198 -- User_Defined_Primitive_Equality_Op --
8199 ----------------------------------------
8201 function User_Defined_Primitive_Equality_Op
8202 (Typ
: Entity_Id
) return Entity_Id
8204 Enclosing_Scope
: constant Entity_Id
:= Scope
(Typ
);
8207 for Private_Entities
in Boolean loop
8208 if Private_Entities
then
8209 if Ekind
(Enclosing_Scope
) /= E_Package
then
8212 E
:= First_Private_Entity
(Enclosing_Scope
);
8215 E
:= First_Entity
(Enclosing_Scope
);
8218 while Present
(E
) loop
8219 if Is_Equality
(E
, Typ
) then
8226 if Is_Derived_Type
(Typ
) then
8227 return User_Defined_Primitive_Equality_Op
8228 (Implementation_Base_Type
(Etype
(Typ
)));
8232 end User_Defined_Primitive_Equality_Op
;
8234 ------------------------------------
8235 -- Has_Unconstrained_UU_Component --
8236 ------------------------------------
8238 function Has_Unconstrained_UU_Component
8239 (Typ
: Entity_Id
) return Boolean
8241 function Unconstrained_UU_In_Component_Declaration
8242 (N
: Node_Id
) return Boolean;
8244 function Unconstrained_UU_In_Component_Items
8245 (L
: List_Id
) return Boolean;
8247 function Unconstrained_UU_In_Component_List
8248 (N
: Node_Id
) return Boolean;
8250 function Unconstrained_UU_In_Variant_Part
8251 (N
: Node_Id
) return Boolean;
8252 -- A family of routines that determine whether a particular construct
8253 -- of a record type definition contains a subcomponent of an
8254 -- unchecked union type whose nominal subtype is unconstrained.
8256 -- Individual routines correspond to the production rules of the Ada
8257 -- grammar, as described in the Ada RM (P).
8259 -----------------------------------------------
8260 -- Unconstrained_UU_In_Component_Declaration --
8261 -----------------------------------------------
8263 function Unconstrained_UU_In_Component_Declaration
8264 (N
: Node_Id
) return Boolean
8266 pragma Assert
(Nkind
(N
) = N_Component_Declaration
);
8268 Sindic
: constant Node_Id
:=
8269 Subtype_Indication
(Component_Definition
(N
));
8271 -- If the component declaration includes a subtype indication
8272 -- it is not an unchecked_union. Otherwise verify that it carries
8273 -- the Unchecked_Union flag and is either a record or a private
8274 -- type. A Record_Subtype declared elsewhere does not qualify,
8275 -- even if its parent type carries the flag.
8277 return Nkind
(Sindic
) in N_Expanded_Name | N_Identifier
8278 and then Is_Unchecked_Union
(Base_Type
(Etype
(Sindic
)))
8279 and then (Ekind
(Entity
(Sindic
)) in
8280 E_Private_Type | E_Record_Type
);
8281 end Unconstrained_UU_In_Component_Declaration
;
8283 -----------------------------------------
8284 -- Unconstrained_UU_In_Component_Items --
8285 -----------------------------------------
8287 function Unconstrained_UU_In_Component_Items
8288 (L
: List_Id
) return Boolean
8290 N
: Node_Id
:= First
(L
);
8292 while Present
(N
) loop
8293 if Nkind
(N
) = N_Component_Declaration
8294 and then Unconstrained_UU_In_Component_Declaration
(N
)
8303 end Unconstrained_UU_In_Component_Items
;
8305 ----------------------------------------
8306 -- Unconstrained_UU_In_Component_List --
8307 ----------------------------------------
8309 function Unconstrained_UU_In_Component_List
8310 (N
: Node_Id
) return Boolean
8312 pragma Assert
(Nkind
(N
) = N_Component_List
);
8314 Optional_Variant_Part
: Node_Id
;
8316 if Unconstrained_UU_In_Component_Items
(Component_Items
(N
)) then
8320 Optional_Variant_Part
:= Variant_Part
(N
);
8323 Present
(Optional_Variant_Part
)
8325 Unconstrained_UU_In_Variant_Part
(Optional_Variant_Part
);
8326 end Unconstrained_UU_In_Component_List
;
8328 --------------------------------------
8329 -- Unconstrained_UU_In_Variant_Part --
8330 --------------------------------------
8332 function Unconstrained_UU_In_Variant_Part
8333 (N
: Node_Id
) return Boolean
8335 pragma Assert
(Nkind
(N
) = N_Variant_Part
);
8337 Variant
: Node_Id
:= First
(Variants
(N
));
8340 if Unconstrained_UU_In_Component_List
(Component_List
(Variant
))
8346 exit when No
(Variant
);
8350 end Unconstrained_UU_In_Variant_Part
;
8352 Typ_Def
: constant Node_Id
:=
8353 Type_Definition
(Declaration_Node
(Base_Type
(Typ
)));
8355 Optional_Component_List
: constant Node_Id
:=
8356 Component_List
(Typ_Def
);
8358 -- Start of processing for Has_Unconstrained_UU_Component
8361 return Present
(Optional_Component_List
)
8363 Unconstrained_UU_In_Component_List
(Optional_Component_List
);
8364 end Has_Unconstrained_UU_Component
;
8370 -- Start of processing for Expand_N_Op_Eq
8373 Binary_Op_Validity_Checks
(N
);
8375 -- Deal with private types
8379 if Ekind
(Typl
) = E_Private_Type
then
8380 Typl
:= Underlying_Type
(Typl
);
8382 elsif Ekind
(Typl
) = E_Private_Subtype
then
8383 Typl
:= Underlying_Type
(Base_Type
(Typl
));
8386 -- It may happen in error situations that the underlying type is not
8387 -- set. The error will be detected later, here we just defend the
8394 -- Now get the implementation base type (note that plain Base_Type here
8395 -- might lead us back to the private type, which is not what we want!)
8397 Typl
:= Implementation_Base_Type
(Typl
);
8399 -- Equality between variant records results in a call to a routine
8400 -- that has conditional tests of the discriminant value(s), and hence
8401 -- violates the No_Implicit_Conditionals restriction.
8403 if Has_Variant_Part
(Typl
) then
8408 Check_Restriction
(Msg
, No_Implicit_Conditionals
, N
);
8412 ("\comparison of variant records tests discriminants", N
);
8418 -- Deal with overflow checks in MINIMIZED/ELIMINATED mode and if that
8419 -- means we no longer have a comparison operation, we are all done.
8421 if Minimized_Eliminated_Overflow_Check
(Left_Opnd
(N
)) then
8422 Expand_Compare_Minimize_Eliminate_Overflow
(N
);
8425 if Nkind
(N
) /= N_Op_Eq
then
8429 -- Boolean types (requiring handling of non-standard case)
8431 if Is_Boolean_Type
(Typl
) then
8432 Adjust_Condition
(Left_Opnd
(N
));
8433 Adjust_Condition
(Right_Opnd
(N
));
8434 Set_Etype
(N
, Standard_Boolean
);
8435 Adjust_Result_Type
(N
, Typ
);
8439 elsif Is_Array_Type
(Typl
) then
8441 -- If we are doing full validity checking, and it is possible for the
8442 -- array elements to be invalid then expand out array comparisons to
8443 -- make sure that we check the array elements.
8445 if Validity_Check_Operands
8446 and then not Is_Known_Valid
(Component_Type
(Typl
))
8449 Save_Force_Validity_Checks
: constant Boolean :=
8450 Force_Validity_Checks
;
8452 Force_Validity_Checks
:= True;
8454 Expand_Array_Equality
8456 Relocate_Node
(Lhs
),
8457 Relocate_Node
(Rhs
),
8460 Insert_Actions
(N
, Bodies
);
8461 Analyze_And_Resolve
(N
, Standard_Boolean
);
8462 Force_Validity_Checks
:= Save_Force_Validity_Checks
;
8465 -- Packed case where both operands are known aligned
8467 elsif Is_Bit_Packed_Array
(Typl
)
8468 and then not Is_Possibly_Unaligned_Object
(Lhs
)
8469 and then not Is_Possibly_Unaligned_Object
(Rhs
)
8471 Expand_Packed_Eq
(N
);
8473 -- Where the component type is elementary we can use a block bit
8474 -- comparison (if supported on the target) exception in the case
8475 -- of floating-point (negative zero issues require element by
8476 -- element comparison), and full access types (where we must be sure
8477 -- to load elements independently) and possibly unaligned arrays.
8479 elsif Is_Elementary_Type
(Component_Type
(Typl
))
8480 and then not Is_Floating_Point_Type
(Component_Type
(Typl
))
8481 and then not Is_Full_Access
(Component_Type
(Typl
))
8482 and then not Is_Possibly_Unaligned_Object
(Lhs
)
8483 and then not Is_Possibly_Unaligned_Slice
(Lhs
)
8484 and then not Is_Possibly_Unaligned_Object
(Rhs
)
8485 and then not Is_Possibly_Unaligned_Slice
(Rhs
)
8486 and then Support_Composite_Compare_On_Target
8490 -- For composite and floating-point cases, expand equality loop to
8491 -- make sure of using proper comparisons for tagged types, and
8492 -- correctly handling the floating-point case.
8496 Expand_Array_Equality
8498 Relocate_Node
(Lhs
),
8499 Relocate_Node
(Rhs
),
8502 Insert_Actions
(N
, Bodies
, Suppress
=> All_Checks
);
8503 Analyze_And_Resolve
(N
, Standard_Boolean
, Suppress
=> All_Checks
);
8508 elsif Is_Record_Type
(Typl
) then
8510 -- For tagged types, use the primitive "="
8512 if Is_Tagged_Type
(Typl
) then
8514 -- No need to do anything else compiling under restriction
8515 -- No_Dispatching_Calls. During the semantic analysis we
8516 -- already notified such violation.
8518 if Restriction_Active
(No_Dispatching_Calls
) then
8522 -- If this is an untagged private type completed with a derivation
8523 -- of an untagged private type whose full view is a tagged type,
8524 -- we use the primitive operations of the private type (since it
8525 -- does not have a full view, and also because its equality
8526 -- primitive may have been overridden in its untagged full view).
8528 if Inherits_From_Tagged_Full_View
(A_Typ
) then
8530 (Find_Equality
(Collect_Primitive_Operations
(A_Typ
)));
8532 -- Find the type's predefined equality or an overriding
8533 -- user-defined equality. The reason for not simply calling
8534 -- Find_Prim_Op here is that there may be a user-defined
8535 -- overloaded equality op that precedes the equality that we
8536 -- want, so we have to explicitly search (e.g., there could be
8537 -- an equality with two different parameter types).
8540 if Is_Class_Wide_Type
(Typl
) then
8541 Typl
:= Find_Specific_Type
(Typl
);
8545 (Find_Equality
(Primitive_Operations
(Typl
)));
8548 -- See AI12-0101 (which only removes a legality rule) and then
8549 -- AI05-0123 (which then applies in the previously illegal case).
8550 -- AI12-0101 is a binding interpretation.
8552 elsif Ada_Version
>= Ada_2012
8553 and then Present
(User_Defined_Primitive_Equality_Op
(Typl
))
8555 Build_Equality_Call
(User_Defined_Primitive_Equality_Op
(Typl
));
8557 -- Ada 2005 (AI-216): Program_Error is raised when evaluating the
8558 -- predefined equality operator for a type which has a subcomponent
8559 -- of an Unchecked_Union type whose nominal subtype is unconstrained.
8561 elsif Has_Unconstrained_UU_Component
(Typl
) then
8563 Make_Raise_Program_Error
(Loc
,
8564 Reason
=> PE_Unchecked_Union_Restriction
));
8566 -- Prevent Gigi from generating incorrect code by rewriting the
8567 -- equality as a standard False. (is this documented somewhere???)
8570 New_Occurrence_Of
(Standard_False
, Loc
));
8572 elsif Is_Unchecked_Union
(Typl
) then
8574 -- If we can infer the discriminants of the operands, we make a
8575 -- call to the TSS equality function.
8577 if Has_Inferable_Discriminants
(Lhs
)
8579 Has_Inferable_Discriminants
(Rhs
)
8582 (TSS
(Root_Type
(Typl
), TSS_Composite_Equality
));
8585 -- Ada 2005 (AI-216): Program_Error is raised when evaluating
8586 -- the predefined equality operator for an Unchecked_Union type
8587 -- if either of the operands lack inferable discriminants.
8590 Make_Raise_Program_Error
(Loc
,
8591 Reason
=> PE_Unchecked_Union_Restriction
));
8593 -- Emit a warning on source equalities only, otherwise the
8594 -- message may appear out of place due to internal use. The
8595 -- warning is unconditional because it is required by the
8598 if Comes_From_Source
(N
) then
8600 ("Unchecked_Union discriminants cannot be determined??",
8603 ("\Program_Error will be raised for equality operation??",
8607 -- Prevent Gigi from generating incorrect code by rewriting
8608 -- the equality as a standard False (documented where???).
8611 New_Occurrence_Of
(Standard_False
, Loc
));
8614 -- If a type support function is present (for complex cases), use it
8616 elsif Present
(TSS
(Root_Type
(Typl
), TSS_Composite_Equality
)) then
8618 (TSS
(Root_Type
(Typl
), TSS_Composite_Equality
));
8620 -- When comparing two Bounded_Strings, use the primitive equality of
8621 -- the root Super_String type.
8623 elsif Is_Bounded_String
(Typl
) then
8626 (Collect_Primitive_Operations
(Root_Type
(Typl
))));
8628 -- Otherwise expand the component by component equality. Note that
8629 -- we never use block-bit comparisons for records, because of the
8630 -- problems with gaps. The back end will often be able to recombine
8631 -- the separate comparisons that we generate here.
8634 Remove_Side_Effects
(Lhs
);
8635 Remove_Side_Effects
(Rhs
);
8636 Rewrite
(N
, Expand_Record_Equality
(N
, Typl
, Lhs
, Rhs
));
8638 Analyze_And_Resolve
(N
, Standard_Boolean
, Suppress
=> All_Checks
);
8641 -- If unnesting, handle elementary types whose Equivalent_Types are
8642 -- records because there may be padding or undefined fields.
8644 elsif Unnest_Subprogram_Mode
8645 and then Ekind
(Typl
) in E_Class_Wide_Type
8646 | E_Class_Wide_Subtype
8647 | E_Access_Subprogram_Type
8648 | E_Access_Protected_Subprogram_Type
8649 | E_Anonymous_Access_Protected_Subprogram_Type
8651 and then Present
(Equivalent_Type
(Typl
))
8652 and then Is_Record_Type
(Equivalent_Type
(Typl
))
8654 Typl
:= Equivalent_Type
(Typl
);
8655 Remove_Side_Effects
(Lhs
);
8656 Remove_Side_Effects
(Rhs
);
8658 Expand_Record_Equality
(N
, Typl
,
8659 Unchecked_Convert_To
(Typl
, Lhs
),
8660 Unchecked_Convert_To
(Typl
, Rhs
)));
8662 Analyze_And_Resolve
(N
, Standard_Boolean
, Suppress
=> All_Checks
);
8665 -- Test if result is known at compile time
8667 Rewrite_Comparison
(N
);
8669 -- Try to narrow the operation
8671 if Typl
= Universal_Integer
and then Nkind
(N
) = N_Op_Eq
then
8672 Narrow_Large_Operation
(N
);
8675 -- Special optimization of length comparison
8677 Optimize_Length_Comparison
(N
);
8679 -- One more special case: if we have a comparison of X'Result = expr
8680 -- in floating-point, then if not already there, change expr to be
8681 -- f'Machine (expr) to eliminate surprise from extra precision.
8683 if Is_Floating_Point_Type
(Typl
)
8684 and then Is_Attribute_Result
(Original_Node
(Lhs
))
8686 -- Stick in the Typ'Machine call if not already there
8688 if Nkind
(Rhs
) /= N_Attribute_Reference
8689 or else Attribute_Name
(Rhs
) /= Name_Machine
8692 Make_Attribute_Reference
(Loc
,
8693 Prefix
=> New_Occurrence_Of
(Typl
, Loc
),
8694 Attribute_Name
=> Name_Machine
,
8695 Expressions
=> New_List
(Relocate_Node
(Rhs
))));
8696 Analyze_And_Resolve
(Rhs
, Typl
);
8701 -----------------------
8702 -- Expand_N_Op_Expon --
8703 -----------------------
8705 procedure Expand_N_Op_Expon
(N
: Node_Id
) is
8706 Loc
: constant Source_Ptr
:= Sloc
(N
);
8707 Ovflo
: constant Boolean := Do_Overflow_Check
(N
);
8708 Typ
: constant Entity_Id
:= Etype
(N
);
8709 Rtyp
: constant Entity_Id
:= Root_Type
(Typ
);
8713 function Wrap_MA
(Exp
: Node_Id
) return Node_Id
;
8714 -- Given an expression Exp, if the root type is Float or Long_Float,
8715 -- then wrap the expression in a call of Bastyp'Machine, to stop any
8716 -- extra precision. This is done to ensure that X**A = X**B when A is
8717 -- a static constant and B is a variable with the same value. For any
8718 -- other type, the node Exp is returned unchanged.
8724 function Wrap_MA
(Exp
: Node_Id
) return Node_Id
is
8725 Loc
: constant Source_Ptr
:= Sloc
(Exp
);
8728 if Rtyp
= Standard_Float
or else Rtyp
= Standard_Long_Float
then
8730 Make_Attribute_Reference
(Loc
,
8731 Attribute_Name
=> Name_Machine
,
8732 Prefix
=> New_Occurrence_Of
(Bastyp
, Loc
),
8733 Expressions
=> New_List
(Relocate_Node
(Exp
)));
8751 -- Start of processing for Expand_N_Op_Expon
8754 Binary_Op_Validity_Checks
(N
);
8756 -- CodePeer wants to see the unexpanded N_Op_Expon node
8758 if CodePeer_Mode
then
8762 -- Relocation of left and right operands must be done after performing
8763 -- the validity checks since the generation of validation checks may
8764 -- remove side effects.
8766 Base
:= Relocate_Node
(Left_Opnd
(N
));
8767 Bastyp
:= Etype
(Base
);
8768 Exp
:= Relocate_Node
(Right_Opnd
(N
));
8769 Exptyp
:= Etype
(Exp
);
8771 -- If either operand is of a private type, then we have the use of an
8772 -- intrinsic operator, and we get rid of the privateness, by using root
8773 -- types of underlying types for the actual operation. Otherwise the
8774 -- private types will cause trouble if we expand multiplications or
8775 -- shifts etc. We also do this transformation if the result type is
8776 -- different from the base type.
8778 if Is_Private_Type
(Etype
(Base
))
8779 or else Is_Private_Type
(Typ
)
8780 or else Is_Private_Type
(Exptyp
)
8781 or else Rtyp
/= Root_Type
(Bastyp
)
8784 Bt
: constant Entity_Id
:= Root_Type
(Underlying_Type
(Bastyp
));
8785 Et
: constant Entity_Id
:= Root_Type
(Underlying_Type
(Exptyp
));
8788 Unchecked_Convert_To
(Typ
,
8790 Left_Opnd
=> Unchecked_Convert_To
(Bt
, Base
),
8791 Right_Opnd
=> Unchecked_Convert_To
(Et
, Exp
))));
8792 Analyze_And_Resolve
(N
, Typ
);
8797 -- Check for MINIMIZED/ELIMINATED overflow mode
8799 if Minimized_Eliminated_Overflow_Check
(N
) then
8800 Apply_Arithmetic_Overflow_Check
(N
);
8804 -- Test for case of known right argument where we can replace the
8805 -- exponentiation by an equivalent expression using multiplication.
8807 -- Note: use CRT_Safe version of Compile_Time_Known_Value because in
8808 -- configurable run-time mode, we may not have the exponentiation
8809 -- routine available, and we don't want the legality of the program
8810 -- to depend on how clever the compiler is in knowing values.
8812 if CRT_Safe_Compile_Time_Known_Value
(Exp
) then
8813 Expv
:= Expr_Value
(Exp
);
8815 -- We only fold small non-negative exponents. You might think we
8816 -- could fold small negative exponents for the real case, but we
8817 -- can't because we are required to raise Constraint_Error for
8818 -- the case of 0.0 ** (negative) even if Machine_Overflows = False.
8819 -- See ACVC test C4A012B, and it is not worth generating the test.
8821 -- For small negative exponents, we return the reciprocal of
8822 -- the folding of the exponentiation for the opposite (positive)
8823 -- exponent, as required by Ada RM 4.5.6(11/3).
8825 if abs Expv
<= 4 then
8827 -- X ** 0 = 1 (or 1.0)
8831 -- Call Remove_Side_Effects to ensure that any side effects
8832 -- in the ignored left operand (in particular function calls
8833 -- to user defined functions) are properly executed.
8835 Remove_Side_Effects
(Base
);
8837 if Ekind
(Typ
) in Integer_Kind
then
8838 Xnode
:= Make_Integer_Literal
(Loc
, Intval
=> 1);
8840 Xnode
:= Make_Real_Literal
(Loc
, Ureal_1
);
8853 Make_Op_Multiply
(Loc
,
8854 Left_Opnd
=> Duplicate_Subexpr
(Base
),
8855 Right_Opnd
=> Duplicate_Subexpr_No_Checks
(Base
)));
8857 -- X ** 3 = X * X * X
8862 Make_Op_Multiply
(Loc
,
8864 Make_Op_Multiply
(Loc
,
8865 Left_Opnd
=> Duplicate_Subexpr
(Base
),
8866 Right_Opnd
=> Duplicate_Subexpr_No_Checks
(Base
)),
8867 Right_Opnd
=> Duplicate_Subexpr_No_Checks
(Base
)));
8872 -- En : constant base'type := base * base;
8877 Temp
:= Make_Temporary
(Loc
, 'E', Base
);
8880 Make_Expression_With_Actions
(Loc
,
8881 Actions
=> New_List
(
8882 Make_Object_Declaration
(Loc
,
8883 Defining_Identifier
=> Temp
,
8884 Constant_Present
=> True,
8885 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
),
8888 Make_Op_Multiply
(Loc
,
8890 Duplicate_Subexpr
(Base
),
8892 Duplicate_Subexpr_No_Checks
(Base
))))),
8896 Make_Op_Multiply
(Loc
,
8897 Left_Opnd
=> New_Occurrence_Of
(Temp
, Loc
),
8898 Right_Opnd
=> New_Occurrence_Of
(Temp
, Loc
))));
8900 -- X ** N = 1.0 / X ** (-N)
8905 (Expv
= -1 or Expv
= -2 or Expv
= -3 or Expv
= -4);
8908 Make_Op_Divide
(Loc
,
8910 Make_Float_Literal
(Loc
,
8912 Significand
=> Uint_1
,
8913 Exponent
=> Uint_0
),
8916 Left_Opnd
=> Duplicate_Subexpr
(Base
),
8918 Make_Integer_Literal
(Loc
,
8923 Analyze_And_Resolve
(N
, Typ
);
8928 -- Deal with optimizing 2 ** expression to shift where possible
8930 -- Note: we used to check that Exptyp was an unsigned type. But that is
8931 -- an unnecessary check, since if Exp is negative, we have a run-time
8932 -- error that is either caught (so we get the right result) or we have
8933 -- suppressed the check, in which case the code is erroneous anyway.
8935 if Is_Integer_Type
(Rtyp
)
8937 -- The base value must be "safe compile-time known", and exactly 2
8939 and then Nkind
(Base
) = N_Integer_Literal
8940 and then CRT_Safe_Compile_Time_Known_Value
(Base
)
8941 and then Expr_Value
(Base
) = Uint_2
8943 -- We only handle cases where the right type is a integer
8945 and then Is_Integer_Type
(Root_Type
(Exptyp
))
8946 and then Esize
(Root_Type
(Exptyp
)) <= Standard_Integer_Size
8948 -- This transformation is not applicable for a modular type with a
8949 -- nonbinary modulus because we do not handle modular reduction in
8950 -- a correct manner if we attempt this transformation in this case.
8952 and then not Non_Binary_Modulus
(Typ
)
8954 -- Handle the cases where our parent is a division or multiplication
8955 -- specially. In these cases we can convert to using a shift at the
8956 -- parent level if we are not doing overflow checking, since it is
8957 -- too tricky to combine the overflow check at the parent level.
8960 and then Nkind
(Parent
(N
)) in N_Op_Divide | N_Op_Multiply
8963 P
: constant Node_Id
:= Parent
(N
);
8964 L
: constant Node_Id
:= Left_Opnd
(P
);
8965 R
: constant Node_Id
:= Right_Opnd
(P
);
8968 if (Nkind
(P
) = N_Op_Multiply
8970 ((Is_Integer_Type
(Etype
(L
)) and then R
= N
)
8972 (Is_Integer_Type
(Etype
(R
)) and then L
= N
))
8973 and then not Do_Overflow_Check
(P
))
8976 (Nkind
(P
) = N_Op_Divide
8977 and then Is_Integer_Type
(Etype
(L
))
8978 and then Is_Unsigned_Type
(Etype
(L
))
8980 and then not Do_Overflow_Check
(P
))
8982 Set_Is_Power_Of_2_For_Shift
(N
);
8987 -- Here we just have 2 ** N on its own, so we can convert this to a
8988 -- shift node. We are prepared to deal with overflow here, and we
8989 -- also have to handle proper modular reduction for binary modular.
8998 -- Maximum shift count with no overflow
9001 -- Set True if we must test the shift count
9004 -- Node for test against TestS
9007 -- Compute maximum shift based on the underlying size. For a
9008 -- modular type this is one less than the size.
9010 if Is_Modular_Integer_Type
(Typ
) then
9012 -- For modular integer types, this is the size of the value
9013 -- being shifted minus one. Any larger values will cause
9014 -- modular reduction to a result of zero. Note that we do
9015 -- want the RM_Size here (e.g. mod 2 ** 7, we want a result
9016 -- of 6, since 2**7 should be reduced to zero).
9018 MaxS
:= RM_Size
(Rtyp
) - 1;
9020 -- For signed integer types, we use the size of the value
9021 -- being shifted minus 2. Larger values cause overflow.
9024 MaxS
:= Esize
(Rtyp
) - 2;
9027 -- Determine range to see if it can be larger than MaxS
9029 Determine_Range
(Exp
, OK
, Lo
, Hi
, Assume_Valid
=> True);
9030 TestS
:= (not OK
) or else Hi
> MaxS
;
9032 -- Signed integer case
9034 if Is_Signed_Integer_Type
(Typ
) then
9036 -- Generate overflow check if overflow is active. Note that
9037 -- we can simply ignore the possibility of overflow if the
9038 -- flag is not set (means that overflow cannot happen or
9039 -- that overflow checks are suppressed).
9041 if Ovflo
and TestS
then
9043 Make_Raise_Constraint_Error
(Loc
,
9046 Left_Opnd
=> Duplicate_Subexpr
(Exp
),
9047 Right_Opnd
=> Make_Integer_Literal
(Loc
, MaxS
)),
9048 Reason
=> CE_Overflow_Check_Failed
));
9051 -- Now rewrite node as Shift_Left (1, right-operand)
9054 Make_Op_Shift_Left
(Loc
,
9055 Left_Opnd
=> Make_Integer_Literal
(Loc
, Uint_1
),
9056 Right_Opnd
=> Exp
));
9058 -- Modular integer case
9060 else pragma Assert
(Is_Modular_Integer_Type
(Typ
));
9062 -- If shift count can be greater than MaxS, we need to wrap
9063 -- the shift in a test that will reduce the result value to
9064 -- zero if this shift count is exceeded.
9068 -- Note: build node for the comparison first, before we
9069 -- reuse the Right_Opnd, so that we have proper parents
9070 -- in place for the Duplicate_Subexpr call.
9074 Left_Opnd
=> Duplicate_Subexpr
(Exp
),
9075 Right_Opnd
=> Make_Integer_Literal
(Loc
, MaxS
));
9078 Make_If_Expression
(Loc
,
9079 Expressions
=> New_List
(
9081 Make_Integer_Literal
(Loc
, Uint_0
),
9082 Make_Op_Shift_Left
(Loc
,
9083 Left_Opnd
=> Make_Integer_Literal
(Loc
, Uint_1
),
9084 Right_Opnd
=> Exp
))));
9086 -- If we know shift count cannot be greater than MaxS, then
9087 -- it is safe to just rewrite as a shift with no test.
9091 Make_Op_Shift_Left
(Loc
,
9092 Left_Opnd
=> Make_Integer_Literal
(Loc
, Uint_1
),
9093 Right_Opnd
=> Exp
));
9097 Analyze_And_Resolve
(N
, Typ
);
9103 -- Fall through if exponentiation must be done using a runtime routine
9105 -- First deal with modular case
9107 if Is_Modular_Integer_Type
(Rtyp
) then
9109 -- Nonbinary modular case, we call the special exponentiation
9110 -- routine for the nonbinary case, converting the argument to
9111 -- Long_Long_Integer and passing the modulus value. Then the
9112 -- result is converted back to the base type.
9114 if Non_Binary_Modulus
(Rtyp
) then
9117 Make_Function_Call
(Loc
,
9119 New_Occurrence_Of
(RTE
(RE_Exp_Modular
), Loc
),
9120 Parameter_Associations
=> New_List
(
9121 Convert_To
(RTE
(RE_Unsigned
), Base
),
9122 Make_Integer_Literal
(Loc
, Modulus
(Rtyp
)),
9125 -- Binary modular case, in this case, we call one of three routines,
9126 -- either the unsigned integer case, or the unsigned long long
9127 -- integer case, or the unsigned long long long integer case, with a
9128 -- final "and" operation to do the required mod.
9131 if Esize
(Rtyp
) <= Standard_Integer_Size
then
9132 Ent
:= RTE
(RE_Exp_Unsigned
);
9133 elsif Esize
(Rtyp
) <= Standard_Long_Long_Integer_Size
then
9134 Ent
:= RTE
(RE_Exp_Long_Long_Unsigned
);
9136 Ent
:= RTE
(RE_Exp_Long_Long_Long_Unsigned
);
9143 Make_Function_Call
(Loc
,
9144 Name
=> New_Occurrence_Of
(Ent
, Loc
),
9145 Parameter_Associations
=> New_List
(
9146 Convert_To
(Etype
(First_Formal
(Ent
)), Base
),
9149 Make_Integer_Literal
(Loc
, Modulus
(Rtyp
) - 1))));
9153 -- Common exit point for modular type case
9155 Analyze_And_Resolve
(N
, Typ
);
9158 -- Signed integer cases, using either Integer, Long_Long_Integer or
9159 -- Long_Long_Long_Integer. It is not worth also having routines for
9160 -- Short_[Short_]Integer, since for most machines it would not help,
9161 -- and it would generate more code that might need certification when
9162 -- a certified run time is required.
9164 -- In the integer cases, we have two routines, one for when overflow
9165 -- checks are required, and one when they are not required, since there
9166 -- is a real gain in omitting checks on many machines.
9168 elsif Is_Signed_Integer_Type
(Rtyp
) then
9169 if Esize
(Rtyp
) <= Standard_Integer_Size
then
9170 Etyp
:= Standard_Integer
;
9173 Rent
:= RE_Exp_Integer
;
9175 Rent
:= RE_Exn_Integer
;
9178 elsif Esize
(Rtyp
) <= Standard_Long_Long_Integer_Size
then
9179 Etyp
:= Standard_Long_Long_Integer
;
9182 Rent
:= RE_Exp_Long_Long_Integer
;
9184 Rent
:= RE_Exn_Long_Long_Integer
;
9188 Etyp
:= Standard_Long_Long_Long_Integer
;
9191 Rent
:= RE_Exp_Long_Long_Long_Integer
;
9193 Rent
:= RE_Exn_Long_Long_Long_Integer
;
9197 -- Floating-point cases. We do not need separate routines for the
9198 -- overflow case here, since in the case of floating-point, we generate
9199 -- infinities anyway as a rule (either that or we automatically trap
9200 -- overflow), and if there is an infinity generated and a range check
9201 -- is required, the check will fail anyway.
9204 pragma Assert
(Is_Floating_Point_Type
(Rtyp
));
9206 -- Short_Float and Float are the same type for GNAT
9208 if Rtyp
= Standard_Short_Float
or else Rtyp
= Standard_Float
then
9209 Etyp
:= Standard_Float
;
9210 Rent
:= RE_Exn_Float
;
9212 elsif Rtyp
= Standard_Long_Float
then
9213 Etyp
:= Standard_Long_Float
;
9214 Rent
:= RE_Exn_Long_Float
;
9217 Etyp
:= Standard_Long_Long_Float
;
9218 Rent
:= RE_Exn_Long_Long_Float
;
9222 -- Common processing for integer cases and floating-point cases.
9223 -- If we are in the right type, we can call runtime routine directly
9226 and then not Is_Universal_Numeric_Type
(Rtyp
)
9230 Make_Function_Call
(Loc
,
9231 Name
=> New_Occurrence_Of
(RTE
(Rent
), Loc
),
9232 Parameter_Associations
=> New_List
(Base
, Exp
))));
9234 -- Otherwise we have to introduce conversions (conversions are also
9235 -- required in the universal cases, since the runtime routine is
9236 -- typed using one of the standard types).
9241 Make_Function_Call
(Loc
,
9242 Name
=> New_Occurrence_Of
(RTE
(Rent
), Loc
),
9243 Parameter_Associations
=> New_List
(
9244 Convert_To
(Etyp
, Base
),
9248 Analyze_And_Resolve
(N
, Typ
);
9252 when RE_Not_Available
=>
9254 end Expand_N_Op_Expon
;
9256 --------------------
9257 -- Expand_N_Op_Ge --
9258 --------------------
9260 procedure Expand_N_Op_Ge
(N
: Node_Id
) is
9261 Typ
: constant Entity_Id
:= Etype
(N
);
9262 Op1
: constant Node_Id
:= Left_Opnd
(N
);
9263 Op2
: constant Node_Id
:= Right_Opnd
(N
);
9264 Typ1
: constant Entity_Id
:= Base_Type
(Etype
(Op1
));
9267 Binary_Op_Validity_Checks
(N
);
9269 -- Deal with overflow checks in MINIMIZED/ELIMINATED mode and if that
9270 -- means we no longer have a comparison operation, we are all done.
9272 if Minimized_Eliminated_Overflow_Check
(Op1
) then
9273 Expand_Compare_Minimize_Eliminate_Overflow
(N
);
9276 if Nkind
(N
) /= N_Op_Ge
then
9282 if Is_Array_Type
(Typ1
) then
9283 Expand_Array_Comparison
(N
);
9287 -- Deal with boolean operands
9289 if Is_Boolean_Type
(Typ1
) then
9290 Adjust_Condition
(Op1
);
9291 Adjust_Condition
(Op2
);
9292 Set_Etype
(N
, Standard_Boolean
);
9293 Adjust_Result_Type
(N
, Typ
);
9296 Rewrite_Comparison
(N
);
9298 -- Try to narrow the operation
9300 if Typ1
= Universal_Integer
and then Nkind
(N
) = N_Op_Ge
then
9301 Narrow_Large_Operation
(N
);
9304 Optimize_Length_Comparison
(N
);
9307 --------------------
9308 -- Expand_N_Op_Gt --
9309 --------------------
9311 procedure Expand_N_Op_Gt
(N
: Node_Id
) is
9312 Typ
: constant Entity_Id
:= Etype
(N
);
9313 Op1
: constant Node_Id
:= Left_Opnd
(N
);
9314 Op2
: constant Node_Id
:= Right_Opnd
(N
);
9315 Typ1
: constant Entity_Id
:= Base_Type
(Etype
(Op1
));
9318 Binary_Op_Validity_Checks
(N
);
9320 -- Deal with overflow checks in MINIMIZED/ELIMINATED mode and if that
9321 -- means we no longer have a comparison operation, we are all done.
9323 if Minimized_Eliminated_Overflow_Check
(Op1
) then
9324 Expand_Compare_Minimize_Eliminate_Overflow
(N
);
9327 if Nkind
(N
) /= N_Op_Gt
then
9331 -- Deal with array type operands
9333 if Is_Array_Type
(Typ1
) then
9334 Expand_Array_Comparison
(N
);
9338 -- Deal with boolean type operands
9340 if Is_Boolean_Type
(Typ1
) then
9341 Adjust_Condition
(Op1
);
9342 Adjust_Condition
(Op2
);
9343 Set_Etype
(N
, Standard_Boolean
);
9344 Adjust_Result_Type
(N
, Typ
);
9347 Rewrite_Comparison
(N
);
9349 -- Try to narrow the operation
9351 if Typ1
= Universal_Integer
and then Nkind
(N
) = N_Op_Gt
then
9352 Narrow_Large_Operation
(N
);
9355 Optimize_Length_Comparison
(N
);
9358 --------------------
9359 -- Expand_N_Op_Le --
9360 --------------------
9362 procedure Expand_N_Op_Le
(N
: Node_Id
) is
9363 Typ
: constant Entity_Id
:= Etype
(N
);
9364 Op1
: constant Node_Id
:= Left_Opnd
(N
);
9365 Op2
: constant Node_Id
:= Right_Opnd
(N
);
9366 Typ1
: constant Entity_Id
:= Base_Type
(Etype
(Op1
));
9369 Binary_Op_Validity_Checks
(N
);
9371 -- Deal with overflow checks in MINIMIZED/ELIMINATED mode and if that
9372 -- means we no longer have a comparison operation, we are all done.
9374 if Minimized_Eliminated_Overflow_Check
(Op1
) then
9375 Expand_Compare_Minimize_Eliminate_Overflow
(N
);
9378 if Nkind
(N
) /= N_Op_Le
then
9382 -- Deal with array type operands
9384 if Is_Array_Type
(Typ1
) then
9385 Expand_Array_Comparison
(N
);
9389 -- Deal with Boolean type operands
9391 if Is_Boolean_Type
(Typ1
) then
9392 Adjust_Condition
(Op1
);
9393 Adjust_Condition
(Op2
);
9394 Set_Etype
(N
, Standard_Boolean
);
9395 Adjust_Result_Type
(N
, Typ
);
9398 Rewrite_Comparison
(N
);
9400 -- Try to narrow the operation
9402 if Typ1
= Universal_Integer
and then Nkind
(N
) = N_Op_Le
then
9403 Narrow_Large_Operation
(N
);
9406 Optimize_Length_Comparison
(N
);
9409 --------------------
9410 -- Expand_N_Op_Lt --
9411 --------------------
9413 procedure Expand_N_Op_Lt
(N
: Node_Id
) is
9414 Typ
: constant Entity_Id
:= Etype
(N
);
9415 Op1
: constant Node_Id
:= Left_Opnd
(N
);
9416 Op2
: constant Node_Id
:= Right_Opnd
(N
);
9417 Typ1
: constant Entity_Id
:= Base_Type
(Etype
(Op1
));
9420 Binary_Op_Validity_Checks
(N
);
9422 -- Deal with overflow checks in MINIMIZED/ELIMINATED mode and if that
9423 -- means we no longer have a comparison operation, we are all done.
9425 if Minimized_Eliminated_Overflow_Check
(Op1
) then
9426 Expand_Compare_Minimize_Eliminate_Overflow
(N
);
9429 if Nkind
(N
) /= N_Op_Lt
then
9433 -- Deal with array type operands
9435 if Is_Array_Type
(Typ1
) then
9436 Expand_Array_Comparison
(N
);
9440 -- Deal with Boolean type operands
9442 if Is_Boolean_Type
(Typ1
) then
9443 Adjust_Condition
(Op1
);
9444 Adjust_Condition
(Op2
);
9445 Set_Etype
(N
, Standard_Boolean
);
9446 Adjust_Result_Type
(N
, Typ
);
9449 Rewrite_Comparison
(N
);
9451 -- Try to narrow the operation
9453 if Typ1
= Universal_Integer
and then Nkind
(N
) = N_Op_Lt
then
9454 Narrow_Large_Operation
(N
);
9457 Optimize_Length_Comparison
(N
);
9460 -----------------------
9461 -- Expand_N_Op_Minus --
9462 -----------------------
9464 procedure Expand_N_Op_Minus
(N
: Node_Id
) is
9465 Loc
: constant Source_Ptr
:= Sloc
(N
);
9466 Typ
: constant Entity_Id
:= Etype
(N
);
9469 Unary_Op_Validity_Checks
(N
);
9471 -- Check for MINIMIZED/ELIMINATED overflow mode
9473 if Minimized_Eliminated_Overflow_Check
(N
) then
9474 Apply_Arithmetic_Overflow_Check
(N
);
9478 -- Try to narrow the operation
9480 if Typ
= Universal_Integer
then
9481 Narrow_Large_Operation
(N
);
9483 if Nkind
(N
) /= N_Op_Minus
then
9488 if not Backend_Overflow_Checks_On_Target
9489 and then Is_Signed_Integer_Type
(Typ
)
9490 and then Do_Overflow_Check
(N
)
9492 -- Software overflow checking expands -expr into (0 - expr)
9495 Make_Op_Subtract
(Loc
,
9496 Left_Opnd
=> Make_Integer_Literal
(Loc
, 0),
9497 Right_Opnd
=> Right_Opnd
(N
)));
9499 Analyze_And_Resolve
(N
, Typ
);
9502 Expand_Nonbinary_Modular_Op
(N
);
9503 end Expand_N_Op_Minus
;
9505 ---------------------
9506 -- Expand_N_Op_Mod --
9507 ---------------------
9509 procedure Expand_N_Op_Mod
(N
: Node_Id
) is
9510 Loc
: constant Source_Ptr
:= Sloc
(N
);
9511 Typ
: constant Entity_Id
:= Etype
(N
);
9512 DDC
: constant Boolean := Do_Division_Check
(N
);
9525 pragma Warnings
(Off
, Lhi
);
9528 Binary_Op_Validity_Checks
(N
);
9530 -- Check for MINIMIZED/ELIMINATED overflow mode
9532 if Minimized_Eliminated_Overflow_Check
(N
) then
9533 Apply_Arithmetic_Overflow_Check
(N
);
9537 -- Try to narrow the operation
9539 if Typ
= Universal_Integer
then
9540 Narrow_Large_Operation
(N
);
9542 if Nkind
(N
) /= N_Op_Mod
then
9547 if Is_Integer_Type
(Typ
) then
9548 Apply_Divide_Checks
(N
);
9550 -- All done if we don't have a MOD any more, which can happen as a
9551 -- result of overflow expansion in MINIMIZED or ELIMINATED modes.
9553 if Nkind
(N
) /= N_Op_Mod
then
9558 -- Proceed with expansion of mod operator
9560 Left
:= Left_Opnd
(N
);
9561 Right
:= Right_Opnd
(N
);
9563 Determine_Range
(Right
, ROK
, Rlo
, Rhi
, Assume_Valid
=> True);
9564 Determine_Range
(Left
, LOK
, Llo
, Lhi
, Assume_Valid
=> True);
9566 -- Convert mod to rem if operands are both known to be non-negative, or
9567 -- both known to be non-positive (these are the cases in which rem and
9568 -- mod are the same, see (RM 4.5.5(28-30)). We do this since it is quite
9569 -- likely that this will improve the quality of code, (the operation now
9570 -- corresponds to the hardware remainder), and it does not seem likely
9571 -- that it could be harmful. It also avoids some cases of the elaborate
9572 -- expansion in Modify_Tree_For_C mode below (since Ada rem = C %).
9575 and then ((Llo
>= 0 and then Rlo
>= 0)
9577 (Lhi
<= 0 and then Rhi
<= 0))
9580 Make_Op_Rem
(Sloc
(N
),
9581 Left_Opnd
=> Left_Opnd
(N
),
9582 Right_Opnd
=> Right_Opnd
(N
)));
9584 -- Instead of reanalyzing the node we do the analysis manually. This
9585 -- avoids anomalies when the replacement is done in an instance and
9586 -- is epsilon more efficient.
9588 Set_Entity
(N
, Standard_Entity
(S_Op_Rem
));
9590 Set_Do_Division_Check
(N
, DDC
);
9591 Expand_N_Op_Rem
(N
);
9595 -- Otherwise, normal mod processing
9598 -- Apply optimization x mod 1 = 0. We don't really need that with
9599 -- gcc, but it is useful with other back ends and is certainly
9602 if Is_Integer_Type
(Etype
(N
))
9603 and then Compile_Time_Known_Value
(Right
)
9604 and then Expr_Value
(Right
) = Uint_1
9606 -- Call Remove_Side_Effects to ensure that any side effects in
9607 -- the ignored left operand (in particular function calls to
9608 -- user defined functions) are properly executed.
9610 Remove_Side_Effects
(Left
);
9612 Rewrite
(N
, Make_Integer_Literal
(Loc
, 0));
9613 Analyze_And_Resolve
(N
, Typ
);
9617 -- If we still have a mod operator and we are in Modify_Tree_For_C
9618 -- mode, and we have a signed integer type, then here is where we do
9619 -- the rewrite in terms of Rem. Note this rewrite bypasses the need
9620 -- for the special handling of the annoying case of largest negative
9621 -- number mod minus one.
9623 if Nkind
(N
) = N_Op_Mod
9624 and then Is_Signed_Integer_Type
(Typ
)
9625 and then Modify_Tree_For_C
9627 -- In the general case, we expand A mod B as
9629 -- Tnn : constant typ := A rem B;
9631 -- (if (A >= 0) = (B >= 0) then Tnn
9632 -- elsif Tnn = 0 then 0
9635 -- The comparison can be written simply as A >= 0 if we know that
9636 -- B >= 0 which is a very common case.
9638 -- An important optimization is when B is known at compile time
9639 -- to be 2**K for some constant. In this case we can simply AND
9640 -- the left operand with the bit string 2**K-1 (i.e. K 1-bits)
9641 -- and that works for both the positive and negative cases.
9644 P2
: constant Nat
:= Power_Of_Two
(Right
);
9649 Unchecked_Convert_To
(Typ
,
9652 Unchecked_Convert_To
9653 (Corresponding_Unsigned_Type
(Typ
), Left
),
9655 Make_Integer_Literal
(Loc
, 2 ** P2
- 1))));
9656 Analyze_And_Resolve
(N
, Typ
);
9661 -- Here for the full rewrite
9664 Tnn
: constant Entity_Id
:= Make_Temporary
(Sloc
(N
), 'T', N
);
9670 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Left
),
9671 Right_Opnd
=> Make_Integer_Literal
(Loc
, 0));
9673 if not LOK
or else Rlo
< 0 then
9679 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Right
),
9680 Right_Opnd
=> Make_Integer_Literal
(Loc
, 0)));
9684 Make_Object_Declaration
(Loc
,
9685 Defining_Identifier
=> Tnn
,
9686 Constant_Present
=> True,
9687 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
),
9691 Right_Opnd
=> Right
)));
9694 Make_If_Expression
(Loc
,
9695 Expressions
=> New_List
(
9697 New_Occurrence_Of
(Tnn
, Loc
),
9698 Make_If_Expression
(Loc
,
9700 Expressions
=> New_List
(
9702 Left_Opnd
=> New_Occurrence_Of
(Tnn
, Loc
),
9703 Right_Opnd
=> Make_Integer_Literal
(Loc
, 0)),
9704 Make_Integer_Literal
(Loc
, 0),
9706 Left_Opnd
=> New_Occurrence_Of
(Tnn
, Loc
),
9708 Duplicate_Subexpr_No_Checks
(Right
)))))));
9710 Analyze_And_Resolve
(N
, Typ
);
9715 -- Deal with annoying case of largest negative number mod minus one.
9716 -- Gigi may not handle this case correctly, because on some targets,
9717 -- the mod value is computed using a divide instruction which gives
9718 -- an overflow trap for this case.
9720 -- It would be a bit more efficient to figure out which targets
9721 -- this is really needed for, but in practice it is reasonable
9722 -- to do the following special check in all cases, since it means
9723 -- we get a clearer message, and also the overhead is minimal given
9724 -- that division is expensive in any case.
9726 -- In fact the check is quite easy, if the right operand is -1, then
9727 -- the mod value is always 0, and we can just ignore the left operand
9728 -- completely in this case.
9730 -- This only applies if we still have a mod operator. Skip if we
9731 -- have already rewritten this (e.g. in the case of eliminated
9732 -- overflow checks which have driven us into bignum mode).
9734 if Nkind
(N
) = N_Op_Mod
then
9736 -- The operand type may be private (e.g. in the expansion of an
9737 -- intrinsic operation) so we must use the underlying type to get
9738 -- the bounds, and convert the literals explicitly.
9742 (Type_Low_Bound
(Base_Type
(Underlying_Type
(Etype
(Left
)))));
9744 if ((not ROK
) or else (Rlo
<= (-1) and then (-1) <= Rhi
))
9745 and then ((not LOK
) or else (Llo
= LLB
))
9746 and then not CodePeer_Mode
9749 Make_If_Expression
(Loc
,
9750 Expressions
=> New_List
(
9752 Left_Opnd
=> Duplicate_Subexpr
(Right
),
9754 Unchecked_Convert_To
(Typ
,
9755 Make_Integer_Literal
(Loc
, -1))),
9756 Unchecked_Convert_To
(Typ
,
9757 Make_Integer_Literal
(Loc
, Uint_0
)),
9758 Relocate_Node
(N
))));
9760 Set_Analyzed
(Next
(Next
(First
(Expressions
(N
)))));
9761 Analyze_And_Resolve
(N
, Typ
);
9765 end Expand_N_Op_Mod
;
9767 --------------------------
9768 -- Expand_N_Op_Multiply --
9769 --------------------------
9771 procedure Expand_N_Op_Multiply
(N
: Node_Id
) is
9772 Loc
: constant Source_Ptr
:= Sloc
(N
);
9773 Lop
: constant Node_Id
:= Left_Opnd
(N
);
9774 Rop
: constant Node_Id
:= Right_Opnd
(N
);
9776 Lp2
: constant Boolean :=
9777 Nkind
(Lop
) = N_Op_Expon
and then Is_Power_Of_2_For_Shift
(Lop
);
9778 Rp2
: constant Boolean :=
9779 Nkind
(Rop
) = N_Op_Expon
and then Is_Power_Of_2_For_Shift
(Rop
);
9781 Ltyp
: constant Entity_Id
:= Etype
(Lop
);
9782 Rtyp
: constant Entity_Id
:= Etype
(Rop
);
9783 Typ
: Entity_Id
:= Etype
(N
);
9786 Binary_Op_Validity_Checks
(N
);
9788 -- Check for MINIMIZED/ELIMINATED overflow mode
9790 if Minimized_Eliminated_Overflow_Check
(N
) then
9791 Apply_Arithmetic_Overflow_Check
(N
);
9795 -- Special optimizations for integer types
9797 if Is_Integer_Type
(Typ
) then
9799 -- N * 0 = 0 for integer types
9801 if Compile_Time_Known_Value
(Rop
)
9802 and then Expr_Value
(Rop
) = Uint_0
9804 -- Call Remove_Side_Effects to ensure that any side effects in
9805 -- the ignored left operand (in particular function calls to
9806 -- user defined functions) are properly executed.
9808 Remove_Side_Effects
(Lop
);
9810 Rewrite
(N
, Make_Integer_Literal
(Loc
, Uint_0
));
9811 Analyze_And_Resolve
(N
, Typ
);
9815 -- Similar handling for 0 * N = 0
9817 if Compile_Time_Known_Value
(Lop
)
9818 and then Expr_Value
(Lop
) = Uint_0
9820 Remove_Side_Effects
(Rop
);
9821 Rewrite
(N
, Make_Integer_Literal
(Loc
, Uint_0
));
9822 Analyze_And_Resolve
(N
, Typ
);
9826 -- N * 1 = 1 * N = N for integer types
9828 -- This optimisation is not done if we are going to
9829 -- rewrite the product 1 * 2 ** N to a shift.
9831 if Compile_Time_Known_Value
(Rop
)
9832 and then Expr_Value
(Rop
) = Uint_1
9838 elsif Compile_Time_Known_Value
(Lop
)
9839 and then Expr_Value
(Lop
) = Uint_1
9847 -- Convert x * 2 ** y to Shift_Left (x, y). Note that the fact that
9848 -- Is_Power_Of_2_For_Shift is set means that we know that our left
9849 -- operand is an integer, as required for this to work.
9854 -- Convert 2 ** A * 2 ** B into 2 ** (A + B)
9858 Left_Opnd
=> Make_Integer_Literal
(Loc
, 2),
9861 Left_Opnd
=> Right_Opnd
(Lop
),
9862 Right_Opnd
=> Right_Opnd
(Rop
))));
9863 Analyze_And_Resolve
(N
, Typ
);
9867 -- If the result is modular, perform the reduction of the result
9870 if Is_Modular_Integer_Type
(Typ
)
9871 and then not Non_Binary_Modulus
(Typ
)
9876 Make_Op_Shift_Left
(Loc
,
9879 Convert_To
(Standard_Natural
, Right_Opnd
(Rop
))),
9881 Make_Integer_Literal
(Loc
, Modulus
(Typ
) - 1)));
9885 Make_Op_Shift_Left
(Loc
,
9888 Convert_To
(Standard_Natural
, Right_Opnd
(Rop
))));
9891 Analyze_And_Resolve
(N
, Typ
);
9895 -- Same processing for the operands the other way round
9898 if Is_Modular_Integer_Type
(Typ
)
9899 and then not Non_Binary_Modulus
(Typ
)
9904 Make_Op_Shift_Left
(Loc
,
9907 Convert_To
(Standard_Natural
, Right_Opnd
(Lop
))),
9909 Make_Integer_Literal
(Loc
, Modulus
(Typ
) - 1)));
9913 Make_Op_Shift_Left
(Loc
,
9916 Convert_To
(Standard_Natural
, Right_Opnd
(Lop
))));
9919 Analyze_And_Resolve
(N
, Typ
);
9923 -- Try to narrow the operation
9925 if Typ
= Universal_Integer
then
9926 Narrow_Large_Operation
(N
);
9928 if Nkind
(N
) /= N_Op_Multiply
then
9933 -- Do required fixup of universal fixed operation
9935 if Typ
= Universal_Fixed
then
9936 Fixup_Universal_Fixed_Operation
(N
);
9940 -- Multiplications with fixed-point results
9942 if Is_Fixed_Point_Type
(Typ
) then
9944 -- Case of fixed * integer => fixed
9946 if Is_Integer_Type
(Rtyp
) then
9947 Expand_Multiply_Fixed_By_Integer_Giving_Fixed
(N
);
9949 -- Case of integer * fixed => fixed
9951 elsif Is_Integer_Type
(Ltyp
) then
9952 Expand_Multiply_Integer_By_Fixed_Giving_Fixed
(N
);
9954 -- Case of fixed * fixed => fixed
9957 Expand_Multiply_Fixed_By_Fixed_Giving_Fixed
(N
);
9960 -- Other cases of multiplication of fixed-point operands
9962 elsif Is_Fixed_Point_Type
(Ltyp
) or else Is_Fixed_Point_Type
(Rtyp
) then
9963 if Is_Integer_Type
(Typ
) then
9964 Expand_Multiply_Fixed_By_Fixed_Giving_Integer
(N
);
9966 pragma Assert
(Is_Floating_Point_Type
(Typ
));
9967 Expand_Multiply_Fixed_By_Fixed_Giving_Float
(N
);
9970 -- Mixed-mode operations can appear in a non-static universal context,
9971 -- in which case the integer argument must be converted explicitly.
9973 elsif Typ
= Universal_Real
and then Is_Integer_Type
(Rtyp
) then
9974 Rewrite
(Rop
, Convert_To
(Universal_Real
, Relocate_Node
(Rop
)));
9975 Analyze_And_Resolve
(Rop
, Universal_Real
);
9977 elsif Typ
= Universal_Real
and then Is_Integer_Type
(Ltyp
) then
9978 Rewrite
(Lop
, Convert_To
(Universal_Real
, Relocate_Node
(Lop
)));
9979 Analyze_And_Resolve
(Lop
, Universal_Real
);
9981 -- Non-fixed point cases, check software overflow checking required
9983 elsif Is_Signed_Integer_Type
(Etype
(N
)) then
9984 Apply_Arithmetic_Overflow_Check
(N
);
9987 -- Overflow checks for floating-point if -gnateF mode active
9989 Check_Float_Op_Overflow
(N
);
9991 Expand_Nonbinary_Modular_Op
(N
);
9992 end Expand_N_Op_Multiply
;
9994 --------------------
9995 -- Expand_N_Op_Ne --
9996 --------------------
9998 procedure Expand_N_Op_Ne
(N
: Node_Id
) is
9999 Typ
: constant Entity_Id
:= Etype
(Left_Opnd
(N
));
10002 -- Case of elementary type with standard operator. But if unnesting,
10003 -- handle elementary types whose Equivalent_Types are records because
10004 -- there may be padding or undefined fields.
10006 if Is_Elementary_Type
(Typ
)
10007 and then Sloc
(Entity
(N
)) = Standard_Location
10008 and then not (Ekind
(Typ
) in E_Class_Wide_Type
10009 | E_Class_Wide_Subtype
10010 | E_Access_Subprogram_Type
10011 | E_Access_Protected_Subprogram_Type
10012 | E_Anonymous_Access_Protected_Subprogram_Type
10014 and then Present
(Equivalent_Type
(Typ
))
10015 and then Is_Record_Type
(Equivalent_Type
(Typ
)))
10017 Binary_Op_Validity_Checks
(N
);
10019 -- Deal with overflow checks in MINIMIZED/ELIMINATED mode and if
10020 -- means we no longer have a /= operation, we are all done.
10022 if Minimized_Eliminated_Overflow_Check
(Left_Opnd
(N
)) then
10023 Expand_Compare_Minimize_Eliminate_Overflow
(N
);
10026 if Nkind
(N
) /= N_Op_Ne
then
10030 -- Boolean types (requiring handling of non-standard case)
10032 if Is_Boolean_Type
(Typ
) then
10033 Adjust_Condition
(Left_Opnd
(N
));
10034 Adjust_Condition
(Right_Opnd
(N
));
10035 Set_Etype
(N
, Standard_Boolean
);
10036 Adjust_Result_Type
(N
, Typ
);
10039 Rewrite_Comparison
(N
);
10041 -- Try to narrow the operation
10043 if Typ
= Universal_Integer
and then Nkind
(N
) = N_Op_Ne
then
10044 Narrow_Large_Operation
(N
);
10047 -- For all cases other than elementary types, we rewrite node as the
10048 -- negation of an equality operation, and reanalyze. The equality to be
10049 -- used is defined in the same scope and has the same signature. This
10050 -- signature must be set explicitly since in an instance it may not have
10051 -- the same visibility as in the generic unit. This avoids duplicating
10052 -- or factoring the complex code for record/array equality tests etc.
10054 -- This case is also used for the minimal expansion performed in
10059 Loc
: constant Source_Ptr
:= Sloc
(N
);
10061 Ne
: constant Entity_Id
:= Entity
(N
);
10064 Binary_Op_Validity_Checks
(N
);
10070 Left_Opnd
=> Left_Opnd
(N
),
10071 Right_Opnd
=> Right_Opnd
(N
)));
10073 -- The level of parentheses is useless in GNATprove mode, and
10074 -- bumping its level here leads to wrong columns being used in
10075 -- check messages, hence skip it in this mode.
10077 if not GNATprove_Mode
then
10078 Set_Paren_Count
(Right_Opnd
(Neg
), 1);
10081 if Scope
(Ne
) /= Standard_Standard
then
10082 Set_Entity
(Right_Opnd
(Neg
), Corresponding_Equality
(Ne
));
10085 -- For navigation purposes, we want to treat the inequality as an
10086 -- implicit reference to the corresponding equality. Preserve the
10087 -- Comes_From_ source flag to generate proper Xref entries.
10089 Preserve_Comes_From_Source
(Neg
, N
);
10090 Preserve_Comes_From_Source
(Right_Opnd
(Neg
), N
);
10092 Analyze_And_Resolve
(N
, Standard_Boolean
);
10096 -- No need for optimization in GNATprove mode, where we would rather see
10097 -- the original source expression.
10099 if not GNATprove_Mode
then
10100 Optimize_Length_Comparison
(N
);
10102 end Expand_N_Op_Ne
;
10104 ---------------------
10105 -- Expand_N_Op_Not --
10106 ---------------------
10108 -- If the argument is other than a Boolean array type, there is no special
10109 -- expansion required, except for dealing with validity checks, and non-
10110 -- standard boolean representations.
10112 -- For the packed array case, we call the special routine in Exp_Pakd,
10113 -- except that if the component size is greater than one, we use the
10114 -- standard routine generating a gruesome loop (it is so peculiar to have
10115 -- packed arrays with non-standard Boolean representations anyway, so it
10116 -- does not matter that we do not handle this case efficiently).
10118 -- For the unpacked array case (and for the special packed case where we
10119 -- have non standard Booleans, as discussed above), we generate and insert
10120 -- into the tree the following function definition:
10122 -- function Nnnn (A : arr) is
10125 -- for J in a'range loop
10126 -- B (J) := not A (J);
10131 -- or in the case of Transform_Function_Array:
10133 -- procedure Nnnn (A : arr; RESULT : out arr) is
10135 -- for J in a'range loop
10136 -- RESULT (J) := not A (J);
10140 -- Here arr is the actual subtype of the parameter (and hence always
10141 -- constrained). Then we replace the not with a call to this subprogram.
10143 procedure Expand_N_Op_Not
(N
: Node_Id
) is
10144 Loc
: constant Source_Ptr
:= Sloc
(N
);
10145 Typ
: constant Entity_Id
:= Etype
(Right_Opnd
(N
));
10154 Func_Name
: Entity_Id
;
10155 Loop_Statement
: Node_Id
;
10158 Unary_Op_Validity_Checks
(N
);
10160 -- For boolean operand, deal with non-standard booleans
10162 if Is_Boolean_Type
(Typ
) then
10163 Adjust_Condition
(Right_Opnd
(N
));
10164 Set_Etype
(N
, Standard_Boolean
);
10165 Adjust_Result_Type
(N
, Typ
);
10169 -- Only array types need any other processing
10171 if not Is_Array_Type
(Typ
) then
10175 -- Case of array operand. If bit packed with a component size of 1,
10176 -- handle it in Exp_Pakd if the operand is known to be aligned.
10178 if Is_Bit_Packed_Array
(Typ
)
10179 and then Component_Size
(Typ
) = 1
10180 and then not Is_Possibly_Unaligned_Object
(Right_Opnd
(N
))
10182 Expand_Packed_Not
(N
);
10186 -- Case of array operand which is not bit-packed. If the context is
10187 -- a safe assignment, call in-place operation, If context is a larger
10188 -- boolean expression in the context of a safe assignment, expansion is
10189 -- done by enclosing operation.
10191 Opnd
:= Relocate_Node
(Right_Opnd
(N
));
10192 Convert_To_Actual_Subtype
(Opnd
);
10193 Arr
:= Etype
(Opnd
);
10194 Ensure_Defined
(Arr
, N
);
10195 Silly_Boolean_Array_Not_Test
(N
, Arr
);
10197 if Nkind
(Parent
(N
)) = N_Assignment_Statement
then
10198 if Safe_In_Place_Array_Op
(Name
(Parent
(N
)), N
, Empty
) then
10199 Build_Boolean_Array_Proc_Call
(Parent
(N
), Opnd
, Empty
);
10202 -- Special case the negation of a binary operation
10204 elsif Nkind
(Opnd
) in N_Op_And | N_Op_Or | N_Op_Xor
10205 and then Safe_In_Place_Array_Op
10206 (Name
(Parent
(N
)), Left_Opnd
(Opnd
), Right_Opnd
(Opnd
))
10208 Build_Boolean_Array_Proc_Call
(Parent
(N
), Opnd
, Empty
);
10212 elsif Nkind
(Parent
(N
)) in N_Binary_Op
10213 and then Nkind
(Parent
(Parent
(N
))) = N_Assignment_Statement
10216 Op1
: constant Node_Id
:= Left_Opnd
(Parent
(N
));
10217 Op2
: constant Node_Id
:= Right_Opnd
(Parent
(N
));
10218 Lhs
: constant Node_Id
:= Name
(Parent
(Parent
(N
)));
10221 if Safe_In_Place_Array_Op
(Lhs
, Op1
, Op2
) then
10223 -- (not A) op (not B) can be reduced to a single call
10225 if N
= Op1
and then Nkind
(Op2
) = N_Op_Not
then
10228 elsif N
= Op2
and then Nkind
(Op1
) = N_Op_Not
then
10231 -- A xor (not B) can also be special-cased
10233 elsif N
= Op2
and then Nkind
(Parent
(N
)) = N_Op_Xor
then
10240 A
:= Make_Defining_Identifier
(Loc
, Name_uA
);
10242 if Transform_Function_Array
then
10243 B
:= Make_Defining_Identifier
(Loc
, Name_UP_RESULT
);
10245 B
:= Make_Defining_Identifier
(Loc
, Name_uB
);
10248 J
:= Make_Defining_Identifier
(Loc
, Name_uJ
);
10251 Make_Indexed_Component
(Loc
,
10252 Prefix
=> New_Occurrence_Of
(A
, Loc
),
10253 Expressions
=> New_List
(New_Occurrence_Of
(J
, Loc
)));
10256 Make_Indexed_Component
(Loc
,
10257 Prefix
=> New_Occurrence_Of
(B
, Loc
),
10258 Expressions
=> New_List
(New_Occurrence_Of
(J
, Loc
)));
10261 Make_Implicit_Loop_Statement
(N
,
10262 Identifier
=> Empty
,
10264 Iteration_Scheme
=>
10265 Make_Iteration_Scheme
(Loc
,
10266 Loop_Parameter_Specification
=>
10267 Make_Loop_Parameter_Specification
(Loc
,
10268 Defining_Identifier
=> J
,
10269 Discrete_Subtype_Definition
=>
10270 Make_Attribute_Reference
(Loc
,
10271 Prefix
=> Make_Identifier
(Loc
, Chars
(A
)),
10272 Attribute_Name
=> Name_Range
))),
10274 Statements
=> New_List
(
10275 Make_Assignment_Statement
(Loc
,
10277 Expression
=> Make_Op_Not
(Loc
, A_J
))));
10279 Func_Name
:= Make_Temporary
(Loc
, 'N');
10280 Set_Is_Inlined
(Func_Name
);
10282 if Transform_Function_Array
then
10284 Make_Subprogram_Body
(Loc
,
10286 Make_Procedure_Specification
(Loc
,
10287 Defining_Unit_Name
=> Func_Name
,
10288 Parameter_Specifications
=> New_List
(
10289 Make_Parameter_Specification
(Loc
,
10290 Defining_Identifier
=> A
,
10291 Parameter_Type
=> New_Occurrence_Of
(Typ
, Loc
)),
10292 Make_Parameter_Specification
(Loc
,
10293 Defining_Identifier
=> B
,
10294 Out_Present
=> True,
10295 Parameter_Type
=> New_Occurrence_Of
(Typ
, Loc
)))),
10297 Declarations
=> New_List
,
10299 Handled_Statement_Sequence
=>
10300 Make_Handled_Sequence_Of_Statements
(Loc
,
10301 Statements
=> New_List
(Loop_Statement
))));
10304 Temp_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T');
10313 Make_Object_Declaration
(Loc
,
10314 Defining_Identifier
=> Temp_Id
,
10315 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
));
10318 -- Proc_Call (Opnd, Temp);
10321 Make_Procedure_Call_Statement
(Loc
,
10322 Name
=> New_Occurrence_Of
(Func_Name
, Loc
),
10323 Parameter_Associations
=>
10324 New_List
(Opnd
, New_Occurrence_Of
(Temp_Id
, Loc
)));
10326 Insert_Actions
(Parent
(N
), New_List
(Decl
, Call
));
10327 Rewrite
(N
, New_Occurrence_Of
(Temp_Id
, Loc
));
10331 Make_Subprogram_Body
(Loc
,
10333 Make_Function_Specification
(Loc
,
10334 Defining_Unit_Name
=> Func_Name
,
10335 Parameter_Specifications
=> New_List
(
10336 Make_Parameter_Specification
(Loc
,
10337 Defining_Identifier
=> A
,
10338 Parameter_Type
=> New_Occurrence_Of
(Typ
, Loc
))),
10339 Result_Definition
=> New_Occurrence_Of
(Typ
, Loc
)),
10341 Declarations
=> New_List
(
10342 Make_Object_Declaration
(Loc
,
10343 Defining_Identifier
=> B
,
10344 Object_Definition
=> New_Occurrence_Of
(Arr
, Loc
))),
10346 Handled_Statement_Sequence
=>
10347 Make_Handled_Sequence_Of_Statements
(Loc
,
10348 Statements
=> New_List
(
10350 Make_Simple_Return_Statement
(Loc
,
10351 Expression
=> Make_Identifier
(Loc
, Chars
(B
)))))));
10354 Make_Function_Call
(Loc
,
10355 Name
=> New_Occurrence_Of
(Func_Name
, Loc
),
10356 Parameter_Associations
=> New_List
(Opnd
)));
10359 Analyze_And_Resolve
(N
, Typ
);
10360 end Expand_N_Op_Not
;
10362 --------------------
10363 -- Expand_N_Op_Or --
10364 --------------------
10366 procedure Expand_N_Op_Or
(N
: Node_Id
) is
10367 Typ
: constant Entity_Id
:= Etype
(N
);
10370 Binary_Op_Validity_Checks
(N
);
10372 if Is_Array_Type
(Etype
(N
)) then
10373 Expand_Boolean_Operator
(N
);
10375 elsif Is_Boolean_Type
(Etype
(N
)) then
10376 Adjust_Condition
(Left_Opnd
(N
));
10377 Adjust_Condition
(Right_Opnd
(N
));
10378 Set_Etype
(N
, Standard_Boolean
);
10379 Adjust_Result_Type
(N
, Typ
);
10381 elsif Is_Intrinsic_Subprogram
(Entity
(N
)) then
10382 Expand_Intrinsic_Call
(N
, Entity
(N
));
10385 Expand_Nonbinary_Modular_Op
(N
);
10386 end Expand_N_Op_Or
;
10388 ----------------------
10389 -- Expand_N_Op_Plus --
10390 ----------------------
10392 procedure Expand_N_Op_Plus
(N
: Node_Id
) is
10393 Typ
: constant Entity_Id
:= Etype
(N
);
10396 Unary_Op_Validity_Checks
(N
);
10398 -- Check for MINIMIZED/ELIMINATED overflow mode
10400 if Minimized_Eliminated_Overflow_Check
(N
) then
10401 Apply_Arithmetic_Overflow_Check
(N
);
10405 -- Try to narrow the operation
10407 if Typ
= Universal_Integer
then
10408 Narrow_Large_Operation
(N
);
10410 end Expand_N_Op_Plus
;
10412 ---------------------
10413 -- Expand_N_Op_Rem --
10414 ---------------------
10416 procedure Expand_N_Op_Rem
(N
: Node_Id
) is
10417 Loc
: constant Source_Ptr
:= Sloc
(N
);
10418 Typ
: constant Entity_Id
:= Etype
(N
);
10429 -- Set if corresponding operand can be negative
10431 pragma Unreferenced
(Hi
);
10434 Binary_Op_Validity_Checks
(N
);
10436 -- Check for MINIMIZED/ELIMINATED overflow mode
10438 if Minimized_Eliminated_Overflow_Check
(N
) then
10439 Apply_Arithmetic_Overflow_Check
(N
);
10443 -- Try to narrow the operation
10445 if Typ
= Universal_Integer
then
10446 Narrow_Large_Operation
(N
);
10448 if Nkind
(N
) /= N_Op_Rem
then
10453 if Is_Integer_Type
(Etype
(N
)) then
10454 Apply_Divide_Checks
(N
);
10456 -- All done if we don't have a REM any more, which can happen as a
10457 -- result of overflow expansion in MINIMIZED or ELIMINATED modes.
10459 if Nkind
(N
) /= N_Op_Rem
then
10464 -- Proceed with expansion of REM
10466 Left
:= Left_Opnd
(N
);
10467 Right
:= Right_Opnd
(N
);
10469 -- Apply optimization x rem 1 = 0. We don't really need that with gcc,
10470 -- but it is useful with other back ends, and is certainly harmless.
10472 if Is_Integer_Type
(Etype
(N
))
10473 and then Compile_Time_Known_Value
(Right
)
10474 and then Expr_Value
(Right
) = Uint_1
10476 -- Call Remove_Side_Effects to ensure that any side effects in the
10477 -- ignored left operand (in particular function calls to user defined
10478 -- functions) are properly executed.
10480 Remove_Side_Effects
(Left
);
10482 Rewrite
(N
, Make_Integer_Literal
(Loc
, 0));
10483 Analyze_And_Resolve
(N
, Typ
);
10487 -- Deal with annoying case of largest negative number remainder minus
10488 -- one. Gigi may not handle this case correctly, because on some
10489 -- targets, the mod value is computed using a divide instruction
10490 -- which gives an overflow trap for this case.
10492 -- It would be a bit more efficient to figure out which targets this
10493 -- is really needed for, but in practice it is reasonable to do the
10494 -- following special check in all cases, since it means we get a clearer
10495 -- message, and also the overhead is minimal given that division is
10496 -- expensive in any case.
10498 -- In fact the check is quite easy, if the right operand is -1, then
10499 -- the remainder is always 0, and we can just ignore the left operand
10500 -- completely in this case.
10502 Determine_Range
(Right
, OK
, Lo
, Hi
, Assume_Valid
=> True);
10503 Lneg
:= (not OK
) or else Lo
< 0;
10505 Determine_Range
(Left
, OK
, Lo
, Hi
, Assume_Valid
=> True);
10506 Rneg
:= (not OK
) or else Lo
< 0;
10508 -- We won't mess with trying to find out if the left operand can really
10509 -- be the largest negative number (that's a pain in the case of private
10510 -- types and this is really marginal). We will just assume that we need
10511 -- the test if the left operand can be negative at all.
10514 and then not CodePeer_Mode
10517 Make_If_Expression
(Loc
,
10518 Expressions
=> New_List
(
10520 Left_Opnd
=> Duplicate_Subexpr
(Right
),
10522 Unchecked_Convert_To
(Typ
, Make_Integer_Literal
(Loc
, -1))),
10524 Unchecked_Convert_To
(Typ
,
10525 Make_Integer_Literal
(Loc
, Uint_0
)),
10527 Relocate_Node
(N
))));
10529 Set_Analyzed
(Next
(Next
(First
(Expressions
(N
)))));
10530 Analyze_And_Resolve
(N
, Typ
);
10532 end Expand_N_Op_Rem
;
10534 -----------------------------
10535 -- Expand_N_Op_Rotate_Left --
10536 -----------------------------
10538 procedure Expand_N_Op_Rotate_Left
(N
: Node_Id
) is
10540 Binary_Op_Validity_Checks
(N
);
10542 -- If we are in Modify_Tree_For_C mode, there is no rotate left in C,
10543 -- so we rewrite in terms of logical shifts
10545 -- Shift_Left (Num, Bits) or Shift_Right (num, Esize - Bits)
10547 -- where Bits is the shift count mod Esize (the mod operation here
10548 -- deals with ludicrous large shift counts, which are apparently OK).
10550 if Modify_Tree_For_C
then
10552 Loc
: constant Source_Ptr
:= Sloc
(N
);
10553 Rtp
: constant Entity_Id
:= Etype
(Right_Opnd
(N
));
10554 Typ
: constant Entity_Id
:= Etype
(N
);
10557 -- Sem_Intr should prevent getting there with a non binary modulus
10559 pragma Assert
(not Non_Binary_Modulus
(Typ
));
10561 Rewrite
(Right_Opnd
(N
),
10563 Left_Opnd
=> Relocate_Node
(Right_Opnd
(N
)),
10564 Right_Opnd
=> Make_Integer_Literal
(Loc
, Esize
(Typ
))));
10566 Analyze_And_Resolve
(Right_Opnd
(N
), Rtp
);
10571 Make_Op_Shift_Left
(Loc
,
10572 Left_Opnd
=> Left_Opnd
(N
),
10573 Right_Opnd
=> Right_Opnd
(N
)),
10576 Make_Op_Shift_Right
(Loc
,
10577 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Left_Opnd
(N
)),
10579 Make_Op_Subtract
(Loc
,
10580 Left_Opnd
=> Make_Integer_Literal
(Loc
, Esize
(Typ
)),
10582 Duplicate_Subexpr_No_Checks
(Right_Opnd
(N
))))));
10584 Analyze_And_Resolve
(N
, Typ
);
10587 end Expand_N_Op_Rotate_Left
;
10589 ------------------------------
10590 -- Expand_N_Op_Rotate_Right --
10591 ------------------------------
10593 procedure Expand_N_Op_Rotate_Right
(N
: Node_Id
) is
10595 Binary_Op_Validity_Checks
(N
);
10597 -- If we are in Modify_Tree_For_C mode, there is no rotate right in C,
10598 -- so we rewrite in terms of logical shifts
10600 -- Shift_Right (Num, Bits) or Shift_Left (num, Esize - Bits)
10602 -- where Bits is the shift count mod Esize (the mod operation here
10603 -- deals with ludicrous large shift counts, which are apparently OK).
10605 if Modify_Tree_For_C
then
10607 Loc
: constant Source_Ptr
:= Sloc
(N
);
10608 Rtp
: constant Entity_Id
:= Etype
(Right_Opnd
(N
));
10609 Typ
: constant Entity_Id
:= Etype
(N
);
10612 -- Sem_Intr should prevent getting there with a non binary modulus
10614 pragma Assert
(not Non_Binary_Modulus
(Typ
));
10616 Rewrite
(Right_Opnd
(N
),
10618 Left_Opnd
=> Relocate_Node
(Right_Opnd
(N
)),
10619 Right_Opnd
=> Make_Integer_Literal
(Loc
, Esize
(Typ
))));
10621 Analyze_And_Resolve
(Right_Opnd
(N
), Rtp
);
10626 Make_Op_Shift_Right
(Loc
,
10627 Left_Opnd
=> Left_Opnd
(N
),
10628 Right_Opnd
=> Right_Opnd
(N
)),
10631 Make_Op_Shift_Left
(Loc
,
10632 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Left_Opnd
(N
)),
10634 Make_Op_Subtract
(Loc
,
10635 Left_Opnd
=> Make_Integer_Literal
(Loc
, Esize
(Typ
)),
10637 Duplicate_Subexpr_No_Checks
(Right_Opnd
(N
))))));
10639 Analyze_And_Resolve
(N
, Typ
);
10642 end Expand_N_Op_Rotate_Right
;
10644 ----------------------------
10645 -- Expand_N_Op_Shift_Left --
10646 ----------------------------
10648 -- Note: nothing in this routine depends on left as opposed to right shifts
10649 -- so we share the routine for expanding shift right operations.
10651 procedure Expand_N_Op_Shift_Left
(N
: Node_Id
) is
10653 Binary_Op_Validity_Checks
(N
);
10655 -- If we are in Modify_Tree_For_C mode, then ensure that the right
10656 -- operand is not greater than the word size (since that would not
10657 -- be defined properly by the corresponding C shift operator).
10659 if Modify_Tree_For_C
then
10661 Right
: constant Node_Id
:= Right_Opnd
(N
);
10662 Loc
: constant Source_Ptr
:= Sloc
(Right
);
10663 Typ
: constant Entity_Id
:= Etype
(N
);
10664 Siz
: constant Uint
:= Esize
(Typ
);
10671 -- Sem_Intr should prevent getting there with a non binary modulus
10673 pragma Assert
(not Non_Binary_Modulus
(Typ
));
10675 if Compile_Time_Known_Value
(Right
) then
10676 if Expr_Value
(Right
) >= Siz
then
10677 Rewrite
(N
, Make_Integer_Literal
(Loc
, 0));
10678 Analyze_And_Resolve
(N
, Typ
);
10681 -- Not compile time known, find range
10684 Determine_Range
(Right
, OK
, Lo
, Hi
, Assume_Valid
=> True);
10686 -- Nothing to do if known to be OK range, otherwise expand
10688 if not OK
or else Hi
>= Siz
then
10690 -- Prevent recursion on copy of shift node
10692 Orig
:= Relocate_Node
(N
);
10693 Set_Analyzed
(Orig
);
10695 -- Now do the rewrite
10698 Make_If_Expression
(Loc
,
10699 Expressions
=> New_List
(
10701 Left_Opnd
=> Duplicate_Subexpr_Move_Checks
(Right
),
10702 Right_Opnd
=> Make_Integer_Literal
(Loc
, Siz
)),
10703 Make_Integer_Literal
(Loc
, 0),
10705 Analyze_And_Resolve
(N
, Typ
);
10710 end Expand_N_Op_Shift_Left
;
10712 -----------------------------
10713 -- Expand_N_Op_Shift_Right --
10714 -----------------------------
10716 procedure Expand_N_Op_Shift_Right
(N
: Node_Id
) is
10718 -- Share shift left circuit
10720 Expand_N_Op_Shift_Left
(N
);
10721 end Expand_N_Op_Shift_Right
;
10723 ----------------------------------------
10724 -- Expand_N_Op_Shift_Right_Arithmetic --
10725 ----------------------------------------
10727 procedure Expand_N_Op_Shift_Right_Arithmetic
(N
: Node_Id
) is
10729 Binary_Op_Validity_Checks
(N
);
10731 -- If we are in Modify_Tree_For_C mode, there is no shift right
10732 -- arithmetic in C, so we rewrite in terms of logical shifts for
10733 -- modular integers, and keep the Shift_Right intrinsic for signed
10734 -- integers: even though doing a shift on a signed integer is not
10735 -- fully guaranteed by the C standard, this is what C compilers
10736 -- implement in practice.
10737 -- Consider also taking advantage of this for modular integers by first
10738 -- performing an unchecked conversion of the modular integer to a signed
10739 -- integer of the same sign, and then convert back.
10741 -- Shift_Right (Num, Bits) or
10743 -- then not (Shift_Right (Mask, bits))
10746 -- Here Mask is all 1 bits (2**size - 1), and Sign is 2**(size - 1)
10748 -- Note: the above works fine for shift counts greater than or equal
10749 -- to the word size, since in this case (not (Shift_Right (Mask, bits)))
10750 -- generates all 1'bits.
10752 if Modify_Tree_For_C
and then Is_Modular_Integer_Type
(Etype
(N
)) then
10754 Loc
: constant Source_Ptr
:= Sloc
(N
);
10755 Typ
: constant Entity_Id
:= Etype
(N
);
10756 Sign
: constant Uint
:= 2 ** (Esize
(Typ
) - 1);
10757 Mask
: constant Uint
:= (2 ** Esize
(Typ
)) - 1;
10758 Left
: constant Node_Id
:= Left_Opnd
(N
);
10759 Right
: constant Node_Id
:= Right_Opnd
(N
);
10763 -- Sem_Intr should prevent getting there with a non binary modulus
10765 pragma Assert
(not Non_Binary_Modulus
(Typ
));
10767 -- Here if not (Shift_Right (Mask, bits)) can be computed at
10768 -- compile time as a single constant.
10770 if Compile_Time_Known_Value
(Right
) then
10772 Val
: constant Uint
:= Expr_Value
(Right
);
10775 if Val
>= Esize
(Typ
) then
10776 Maskx
:= Make_Integer_Literal
(Loc
, Mask
);
10780 Make_Integer_Literal
(Loc
,
10781 Intval
=> Mask
- (Mask
/ (2 ** Expr_Value
(Right
))));
10789 Make_Op_Shift_Right
(Loc
,
10790 Left_Opnd
=> Make_Integer_Literal
(Loc
, Mask
),
10791 Right_Opnd
=> Duplicate_Subexpr_No_Checks
(Right
)));
10794 -- Now do the rewrite
10799 Make_Op_Shift_Right
(Loc
,
10801 Right_Opnd
=> Right
),
10803 Make_If_Expression
(Loc
,
10804 Expressions
=> New_List
(
10806 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Left
),
10807 Right_Opnd
=> Make_Integer_Literal
(Loc
, Sign
)),
10809 Make_Integer_Literal
(Loc
, 0)))));
10810 Analyze_And_Resolve
(N
, Typ
);
10813 end Expand_N_Op_Shift_Right_Arithmetic
;
10815 --------------------------
10816 -- Expand_N_Op_Subtract --
10817 --------------------------
10819 procedure Expand_N_Op_Subtract
(N
: Node_Id
) is
10820 Typ
: constant Entity_Id
:= Etype
(N
);
10823 Binary_Op_Validity_Checks
(N
);
10825 -- Check for MINIMIZED/ELIMINATED overflow mode
10827 if Minimized_Eliminated_Overflow_Check
(N
) then
10828 Apply_Arithmetic_Overflow_Check
(N
);
10832 -- Try to narrow the operation
10834 if Typ
= Universal_Integer
then
10835 Narrow_Large_Operation
(N
);
10837 if Nkind
(N
) /= N_Op_Subtract
then
10842 -- N - 0 = N for integer types
10844 if Is_Integer_Type
(Typ
)
10845 and then Compile_Time_Known_Value
(Right_Opnd
(N
))
10846 and then Expr_Value
(Right_Opnd
(N
)) = 0
10848 Rewrite
(N
, Left_Opnd
(N
));
10852 -- Arithmetic overflow checks for signed integer/fixed point types
10854 if Is_Signed_Integer_Type
(Typ
) or else Is_Fixed_Point_Type
(Typ
) then
10855 Apply_Arithmetic_Overflow_Check
(N
);
10858 -- Overflow checks for floating-point if -gnateF mode active
10860 Check_Float_Op_Overflow
(N
);
10862 Expand_Nonbinary_Modular_Op
(N
);
10863 end Expand_N_Op_Subtract
;
10865 ---------------------
10866 -- Expand_N_Op_Xor --
10867 ---------------------
10869 procedure Expand_N_Op_Xor
(N
: Node_Id
) is
10870 Typ
: constant Entity_Id
:= Etype
(N
);
10873 Binary_Op_Validity_Checks
(N
);
10875 if Is_Array_Type
(Etype
(N
)) then
10876 Expand_Boolean_Operator
(N
);
10878 elsif Is_Boolean_Type
(Etype
(N
)) then
10879 Adjust_Condition
(Left_Opnd
(N
));
10880 Adjust_Condition
(Right_Opnd
(N
));
10881 Set_Etype
(N
, Standard_Boolean
);
10882 Adjust_Result_Type
(N
, Typ
);
10884 elsif Is_Intrinsic_Subprogram
(Entity
(N
)) then
10885 Expand_Intrinsic_Call
(N
, Entity
(N
));
10888 Expand_Nonbinary_Modular_Op
(N
);
10889 end Expand_N_Op_Xor
;
10891 ----------------------
10892 -- Expand_N_Or_Else --
10893 ----------------------
10895 procedure Expand_N_Or_Else
(N
: Node_Id
)
10896 renames Expand_Short_Circuit_Operator
;
10898 -----------------------------------
10899 -- Expand_N_Qualified_Expression --
10900 -----------------------------------
10902 procedure Expand_N_Qualified_Expression
(N
: Node_Id
) is
10903 Operand
: constant Node_Id
:= Expression
(N
);
10904 Target_Type
: constant Entity_Id
:= Entity
(Subtype_Mark
(N
));
10907 -- Do validity check if validity checking operands
10909 if Validity_Checks_On
and Validity_Check_Operands
then
10910 Ensure_Valid
(Operand
);
10913 -- Apply possible constraint check
10915 Apply_Constraint_Check
(Operand
, Target_Type
, No_Sliding
=> True);
10917 -- Apply possible predicate check
10919 Apply_Predicate_Check
(Operand
, Target_Type
);
10921 if Do_Range_Check
(Operand
) then
10922 Generate_Range_Check
(Operand
, Target_Type
, CE_Range_Check_Failed
);
10924 end Expand_N_Qualified_Expression
;
10926 ------------------------------------
10927 -- Expand_N_Quantified_Expression --
10928 ------------------------------------
10932 -- for all X in range => Cond
10937 -- for X in range loop
10938 -- if not Cond then
10944 -- Similarly, an existentially quantified expression:
10946 -- for some X in range => Cond
10951 -- for X in range loop
10958 -- In both cases, the iteration may be over a container in which case it is
10959 -- given by an iterator specification, not a loop parameter specification.
10961 procedure Expand_N_Quantified_Expression
(N
: Node_Id
) is
10962 Actions
: constant List_Id
:= New_List
;
10963 For_All
: constant Boolean := All_Present
(N
);
10964 Iter_Spec
: constant Node_Id
:= Iterator_Specification
(N
);
10965 Loc
: constant Source_Ptr
:= Sloc
(N
);
10966 Loop_Spec
: constant Node_Id
:= Loop_Parameter_Specification
(N
);
10974 -- Ensure that the bound variable as well as the type of Name of the
10975 -- Iter_Spec if present are properly frozen. We must do this before
10976 -- expansion because the expression is about to be converted into a
10977 -- loop, and resulting freeze nodes may end up in the wrong place in the
10980 if Present
(Iter_Spec
) then
10981 Var
:= Defining_Identifier
(Iter_Spec
);
10983 Var
:= Defining_Identifier
(Loop_Spec
);
10987 P
: Node_Id
:= Parent
(N
);
10989 while Nkind
(P
) in N_Subexpr
loop
10993 if Present
(Iter_Spec
) then
10994 Freeze_Before
(P
, Etype
(Name
(Iter_Spec
)));
10997 Freeze_Before
(P
, Etype
(Var
));
11000 -- Create the declaration of the flag which tracks the status of the
11001 -- quantified expression. Generate:
11003 -- Flag : Boolean := (True | False);
11005 Flag
:= Make_Temporary
(Loc
, 'T', N
);
11007 Append_To
(Actions
,
11008 Make_Object_Declaration
(Loc
,
11009 Defining_Identifier
=> Flag
,
11010 Object_Definition
=> New_Occurrence_Of
(Standard_Boolean
, Loc
),
11012 New_Occurrence_Of
(Boolean_Literals
(For_All
), Loc
)));
11014 -- Construct the circuitry which tracks the status of the quantified
11015 -- expression. Generate:
11017 -- if [not] Cond then
11018 -- Flag := (False | True);
11022 Cond
:= Relocate_Node
(Condition
(N
));
11025 Cond
:= Make_Op_Not
(Loc
, Cond
);
11028 Stmts
:= New_List
(
11029 Make_Implicit_If_Statement
(N
,
11031 Then_Statements
=> New_List
(
11032 Make_Assignment_Statement
(Loc
,
11033 Name
=> New_Occurrence_Of
(Flag
, Loc
),
11035 New_Occurrence_Of
(Boolean_Literals
(not For_All
), Loc
)),
11036 Make_Exit_Statement
(Loc
))));
11038 -- Build the loop equivalent of the quantified expression
11040 if Present
(Iter_Spec
) then
11042 Make_Iteration_Scheme
(Loc
,
11043 Iterator_Specification
=> Iter_Spec
);
11046 Make_Iteration_Scheme
(Loc
,
11047 Loop_Parameter_Specification
=> Loop_Spec
);
11050 Append_To
(Actions
,
11051 Make_Loop_Statement
(Loc
,
11052 Iteration_Scheme
=> Scheme
,
11053 Statements
=> Stmts
,
11054 End_Label
=> Empty
));
11056 -- Transform the quantified expression
11059 Make_Expression_With_Actions
(Loc
,
11060 Expression
=> New_Occurrence_Of
(Flag
, Loc
),
11061 Actions
=> Actions
));
11062 Analyze_And_Resolve
(N
, Standard_Boolean
);
11063 end Expand_N_Quantified_Expression
;
11065 ---------------------------------
11066 -- Expand_N_Selected_Component --
11067 ---------------------------------
11069 procedure Expand_N_Selected_Component
(N
: Node_Id
) is
11070 Loc
: constant Source_Ptr
:= Sloc
(N
);
11071 Par
: constant Node_Id
:= Parent
(N
);
11072 P
: constant Node_Id
:= Prefix
(N
);
11073 S
: constant Node_Id
:= Selector_Name
(N
);
11074 Ptyp
: constant Entity_Id
:= Underlying_Type
(Etype
(P
));
11080 function In_Left_Hand_Side
(Comp
: Node_Id
) return Boolean;
11081 -- Gigi needs a temporary for prefixes that depend on a discriminant,
11082 -- unless the context of an assignment can provide size information.
11083 -- Don't we have a general routine that does this???
11085 function Is_Subtype_Declaration
return Boolean;
11086 -- The replacement of a discriminant reference by its value is required
11087 -- if this is part of the initialization of an temporary generated by a
11088 -- change of representation. This shows up as the construction of a
11089 -- discriminant constraint for a subtype declared at the same point as
11090 -- the entity in the prefix of the selected component. We recognize this
11091 -- case when the context of the reference is:
11092 -- subtype ST is T(Obj.D);
11093 -- where the entity for Obj comes from source, and ST has the same sloc.
11095 -----------------------
11096 -- In_Left_Hand_Side --
11097 -----------------------
11099 function In_Left_Hand_Side
(Comp
: Node_Id
) return Boolean is
11101 return (Nkind
(Parent
(Comp
)) = N_Assignment_Statement
11102 and then Comp
= Name
(Parent
(Comp
)))
11103 or else (Present
(Parent
(Comp
))
11104 and then Nkind
(Parent
(Comp
)) in N_Subexpr
11105 and then In_Left_Hand_Side
(Parent
(Comp
)));
11106 end In_Left_Hand_Side
;
11108 -----------------------------
11109 -- Is_Subtype_Declaration --
11110 -----------------------------
11112 function Is_Subtype_Declaration
return Boolean is
11113 Par
: constant Node_Id
:= Parent
(N
);
11116 Nkind
(Par
) = N_Index_Or_Discriminant_Constraint
11117 and then Nkind
(Parent
(Parent
(Par
))) = N_Subtype_Declaration
11118 and then Comes_From_Source
(Entity
(Prefix
(N
)))
11119 and then Sloc
(Par
) = Sloc
(Entity
(Prefix
(N
)));
11120 end Is_Subtype_Declaration
;
11122 -- Start of processing for Expand_N_Selected_Component
11125 -- Deal with discriminant check required
11127 if Do_Discriminant_Check
(N
) then
11128 if Present
(Discriminant_Checking_Func
11129 (Original_Record_Component
(Entity
(S
))))
11131 -- Present the discriminant checking function to the backend, so
11132 -- that it can inline the call to the function.
11135 (Discriminant_Checking_Func
11136 (Original_Record_Component
(Entity
(S
))),
11139 -- Now reset the flag and generate the call
11141 Set_Do_Discriminant_Check
(N
, False);
11142 Generate_Discriminant_Check
(N
);
11144 -- In the case of Unchecked_Union, no discriminant checking is
11145 -- actually performed.
11148 Set_Do_Discriminant_Check
(N
, False);
11152 -- Ada 2005 (AI-318-02): If the prefix is a call to a build-in-place
11153 -- function, then additional actuals must be passed.
11155 if Is_Build_In_Place_Function_Call
(P
) then
11156 Make_Build_In_Place_Call_In_Anonymous_Context
(P
);
11158 -- Ada 2005 (AI-318-02): Specialization of the previous case for prefix
11159 -- containing build-in-place function calls whose returned object covers
11160 -- interface types.
11162 elsif Present
(Unqual_BIP_Iface_Function_Call
(P
)) then
11163 Make_Build_In_Place_Iface_Call_In_Anonymous_Context
(P
);
11166 -- Gigi cannot handle unchecked conversions that are the prefix of a
11167 -- selected component with discriminants. This must be checked during
11168 -- expansion, because during analysis the type of the selector is not
11169 -- known at the point the prefix is analyzed. If the conversion is the
11170 -- target of an assignment, then we cannot force the evaluation.
11172 if Nkind
(Prefix
(N
)) = N_Unchecked_Type_Conversion
11173 and then Has_Discriminants
(Etype
(N
))
11174 and then not In_Left_Hand_Side
(N
)
11176 Force_Evaluation
(Prefix
(N
));
11179 -- Remaining processing applies only if selector is a discriminant
11181 if Ekind
(Entity
(Selector_Name
(N
))) = E_Discriminant
then
11183 -- If the selector is a discriminant of a constrained record type,
11184 -- we may be able to rewrite the expression with the actual value
11185 -- of the discriminant, a useful optimization in some cases.
11187 if Is_Record_Type
(Ptyp
)
11188 and then Has_Discriminants
(Ptyp
)
11189 and then Is_Constrained
(Ptyp
)
11191 -- Do this optimization for discrete types only, and not for
11192 -- access types (access discriminants get us into trouble).
11194 if not Is_Discrete_Type
(Etype
(N
)) then
11197 -- Don't do this on the left-hand side of an assignment statement.
11198 -- Normally one would think that references like this would not
11199 -- occur, but they do in generated code, and mean that we really
11200 -- do want to assign the discriminant.
11202 elsif Nkind
(Par
) = N_Assignment_Statement
11203 and then Name
(Par
) = N
11207 -- Don't do this optimization for the prefix of an attribute or
11208 -- the name of an object renaming declaration since these are
11209 -- contexts where we do not want the value anyway.
11211 elsif (Nkind
(Par
) = N_Attribute_Reference
11212 and then Prefix
(Par
) = N
)
11213 or else Is_Renamed_Object
(N
)
11217 -- Don't do this optimization if we are within the code for a
11218 -- discriminant check, since the whole point of such a check may
11219 -- be to verify the condition on which the code below depends.
11221 elsif Is_In_Discriminant_Check
(N
) then
11224 -- Green light to see if we can do the optimization. There is
11225 -- still one condition that inhibits the optimization below but
11226 -- now is the time to check the particular discriminant.
11229 -- Loop through discriminants to find the matching discriminant
11230 -- constraint to see if we can copy it.
11232 Disc
:= First_Discriminant
(Ptyp
);
11233 Dcon
:= First_Elmt
(Discriminant_Constraint
(Ptyp
));
11234 Discr_Loop
: while Present
(Dcon
) loop
11235 Dval
:= Node
(Dcon
);
11237 -- Check if this is the matching discriminant and if the
11238 -- discriminant value is simple enough to make sense to
11239 -- copy. We don't want to copy complex expressions, and
11240 -- indeed to do so can cause trouble (before we put in
11241 -- this guard, a discriminant expression containing an
11242 -- AND THEN was copied, causing problems for coverage
11243 -- analysis tools).
11245 -- However, if the reference is part of the initialization
11246 -- code generated for an object declaration, we must use
11247 -- the discriminant value from the subtype constraint,
11248 -- because the selected component may be a reference to the
11249 -- object being initialized, whose discriminant is not yet
11250 -- set. This only happens in complex cases involving changes
11251 -- of representation.
11253 if Disc
= Entity
(Selector_Name
(N
))
11254 and then (Is_Entity_Name
(Dval
)
11255 or else Compile_Time_Known_Value
(Dval
)
11256 or else Is_Subtype_Declaration
)
11258 -- Here we have the matching discriminant. Check for
11259 -- the case of a discriminant of a component that is
11260 -- constrained by an outer discriminant, which cannot
11261 -- be optimized away.
11263 if Denotes_Discriminant
(Dval
, Check_Concurrent
=> True)
11267 -- Do not retrieve value if constraint is not static. It
11268 -- is generally not useful, and the constraint may be a
11269 -- rewritten outer discriminant in which case it is in
11272 elsif Is_Entity_Name
(Dval
)
11274 Nkind
(Parent
(Entity
(Dval
))) = N_Object_Declaration
11275 and then Present
(Expression
(Parent
(Entity
(Dval
))))
11277 Is_OK_Static_Expression
11278 (Expression
(Parent
(Entity
(Dval
))))
11282 -- In the context of a case statement, the expression may
11283 -- have the base type of the discriminant, and we need to
11284 -- preserve the constraint to avoid spurious errors on
11287 elsif Nkind
(Parent
(N
)) = N_Case_Statement
11288 and then Etype
(Dval
) /= Etype
(Disc
)
11291 Make_Qualified_Expression
(Loc
,
11293 New_Occurrence_Of
(Etype
(Disc
), Loc
),
11295 New_Copy_Tree
(Dval
)));
11296 Analyze_And_Resolve
(N
, Etype
(Disc
));
11298 -- In case that comes out as a static expression,
11299 -- reset it (a selected component is never static).
11301 Set_Is_Static_Expression
(N
, False);
11304 -- Otherwise we can just copy the constraint, but the
11305 -- result is certainly not static. In some cases the
11306 -- discriminant constraint has been analyzed in the
11307 -- context of the original subtype indication, but for
11308 -- itypes the constraint might not have been analyzed
11309 -- yet, and this must be done now.
11312 Rewrite
(N
, New_Copy_Tree
(Dval
));
11313 Analyze_And_Resolve
(N
);
11314 Set_Is_Static_Expression
(N
, False);
11320 Next_Discriminant
(Disc
);
11321 end loop Discr_Loop
;
11323 -- Note: the above loop should always find a matching
11324 -- discriminant, but if it does not, we just missed an
11325 -- optimization due to some glitch (perhaps a previous
11326 -- error), so ignore.
11331 -- The only remaining processing is in the case of a discriminant of
11332 -- a concurrent object, where we rewrite the prefix to denote the
11333 -- corresponding record type. If the type is derived and has renamed
11334 -- discriminants, use corresponding discriminant, which is the one
11335 -- that appears in the corresponding record.
11337 if not Is_Concurrent_Type
(Ptyp
) then
11341 Disc
:= Entity
(Selector_Name
(N
));
11343 if Is_Derived_Type
(Ptyp
)
11344 and then Present
(Corresponding_Discriminant
(Disc
))
11346 Disc
:= Corresponding_Discriminant
(Disc
);
11350 Make_Selected_Component
(Loc
,
11352 Unchecked_Convert_To
(Corresponding_Record_Type
(Ptyp
),
11353 New_Copy_Tree
(P
)),
11354 Selector_Name
=> Make_Identifier
(Loc
, Chars
(Disc
)));
11356 Rewrite
(N
, New_N
);
11360 -- Set Atomic_Sync_Required if necessary for atomic component
11362 if Nkind
(N
) = N_Selected_Component
then
11364 E
: constant Entity_Id
:= Entity
(Selector_Name
(N
));
11368 -- If component is atomic, but type is not, setting depends on
11369 -- disable/enable state for the component.
11371 if Is_Atomic
(E
) and then not Is_Atomic
(Etype
(E
)) then
11372 Set
:= not Atomic_Synchronization_Disabled
(E
);
11374 -- If component is not atomic, but its type is atomic, setting
11375 -- depends on disable/enable state for the type.
11377 elsif not Is_Atomic
(E
) and then Is_Atomic
(Etype
(E
)) then
11378 Set
:= not Atomic_Synchronization_Disabled
(Etype
(E
));
11380 -- If both component and type are atomic, we disable if either
11381 -- component or its type have sync disabled.
11383 elsif Is_Atomic
(E
) and then Is_Atomic
(Etype
(E
)) then
11384 Set
:= (not Atomic_Synchronization_Disabled
(E
))
11386 (not Atomic_Synchronization_Disabled
(Etype
(E
)));
11392 -- Set flag if required
11395 Activate_Atomic_Synchronization
(N
);
11399 end Expand_N_Selected_Component
;
11401 --------------------
11402 -- Expand_N_Slice --
11403 --------------------
11405 procedure Expand_N_Slice
(N
: Node_Id
) is
11406 Loc
: constant Source_Ptr
:= Sloc
(N
);
11407 Typ
: constant Entity_Id
:= Etype
(N
);
11409 function Is_Procedure_Actual
(N
: Node_Id
) return Boolean;
11410 -- Check whether the argument is an actual for a procedure call, in
11411 -- which case the expansion of a bit-packed slice is deferred until the
11412 -- call itself is expanded. The reason this is required is that we might
11413 -- have an IN OUT or OUT parameter, and the copy out is essential, and
11414 -- that copy out would be missed if we created a temporary here in
11415 -- Expand_N_Slice. Note that we don't bother to test specifically for an
11416 -- IN OUT or OUT mode parameter, since it is a bit tricky to do, and it
11417 -- is harmless to defer expansion in the IN case, since the call
11418 -- processing will still generate the appropriate copy in operation,
11419 -- which will take care of the slice.
11421 procedure Make_Temporary_For_Slice
;
11422 -- Create a named variable for the value of the slice, in cases where
11423 -- the back end cannot handle it properly, e.g. when packed types or
11424 -- unaligned slices are involved.
11426 -------------------------
11427 -- Is_Procedure_Actual --
11428 -------------------------
11430 function Is_Procedure_Actual
(N
: Node_Id
) return Boolean is
11431 Par
: Node_Id
:= Parent
(N
);
11435 -- If our parent is a procedure call we can return
11437 if Nkind
(Par
) = N_Procedure_Call_Statement
then
11440 -- If our parent is a type conversion, keep climbing the tree,
11441 -- since a type conversion can be a procedure actual. Also keep
11442 -- climbing if parameter association or a qualified expression,
11443 -- since these are additional cases that do can appear on
11444 -- procedure actuals.
11446 elsif Nkind
(Par
) in N_Type_Conversion
11447 | N_Parameter_Association
11448 | N_Qualified_Expression
11450 Par
:= Parent
(Par
);
11452 -- Any other case is not what we are looking for
11458 end Is_Procedure_Actual
;
11460 ------------------------------
11461 -- Make_Temporary_For_Slice --
11462 ------------------------------
11464 procedure Make_Temporary_For_Slice
is
11465 Ent
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T', N
);
11470 Make_Object_Declaration
(Loc
,
11471 Defining_Identifier
=> Ent
,
11472 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
));
11474 Set_No_Initialization
(Decl
);
11476 Insert_Actions
(N
, New_List
(
11478 Make_Assignment_Statement
(Loc
,
11479 Name
=> New_Occurrence_Of
(Ent
, Loc
),
11480 Expression
=> Relocate_Node
(N
))));
11482 Rewrite
(N
, New_Occurrence_Of
(Ent
, Loc
));
11483 Analyze_And_Resolve
(N
, Typ
);
11484 end Make_Temporary_For_Slice
;
11488 Pref
: constant Node_Id
:= Prefix
(N
);
11490 -- Start of processing for Expand_N_Slice
11493 -- Ada 2005 (AI-318-02): If the prefix is a call to a build-in-place
11494 -- function, then additional actuals must be passed.
11496 if Is_Build_In_Place_Function_Call
(Pref
) then
11497 Make_Build_In_Place_Call_In_Anonymous_Context
(Pref
);
11499 -- Ada 2005 (AI-318-02): Specialization of the previous case for prefix
11500 -- containing build-in-place function calls whose returned object covers
11501 -- interface types.
11503 elsif Present
(Unqual_BIP_Iface_Function_Call
(Pref
)) then
11504 Make_Build_In_Place_Iface_Call_In_Anonymous_Context
(Pref
);
11507 -- The remaining case to be handled is packed slices. We can leave
11508 -- packed slices as they are in the following situations:
11510 -- 1. Right or left side of an assignment (we can handle this
11511 -- situation correctly in the assignment statement expansion).
11513 -- 2. Prefix of indexed component (the slide is optimized away in this
11514 -- case, see the start of Expand_N_Indexed_Component.)
11516 -- 3. Object renaming declaration, since we want the name of the
11517 -- slice, not the value.
11519 -- 4. Argument to procedure call, since copy-in/copy-out handling may
11520 -- be required, and this is handled in the expansion of call
11523 -- 5. Prefix of an address attribute (this is an error which is caught
11524 -- elsewhere, and the expansion would interfere with generating the
11525 -- error message) or of a size attribute (because 'Size may change
11526 -- when applied to the temporary instead of the slice directly).
11528 if not Is_Packed
(Typ
) then
11530 -- Apply transformation for actuals of a function call, where
11531 -- Expand_Actuals is not used.
11533 if Nkind
(Parent
(N
)) = N_Function_Call
11534 and then Is_Possibly_Unaligned_Slice
(N
)
11536 Make_Temporary_For_Slice
;
11539 elsif Nkind
(Parent
(N
)) = N_Assignment_Statement
11540 or else (Nkind
(Parent
(Parent
(N
))) = N_Assignment_Statement
11541 and then Parent
(N
) = Name
(Parent
(Parent
(N
))))
11545 elsif Nkind
(Parent
(N
)) = N_Indexed_Component
11546 or else Is_Renamed_Object
(N
)
11547 or else Is_Procedure_Actual
(N
)
11551 elsif Nkind
(Parent
(N
)) = N_Attribute_Reference
11552 and then (Attribute_Name
(Parent
(N
)) = Name_Address
11553 or else Attribute_Name
(Parent
(N
)) = Name_Size
)
11558 Make_Temporary_For_Slice
;
11560 end Expand_N_Slice
;
11562 ------------------------------
11563 -- Expand_N_Type_Conversion --
11564 ------------------------------
11566 procedure Expand_N_Type_Conversion
(N
: Node_Id
) is
11567 Loc
: constant Source_Ptr
:= Sloc
(N
);
11568 Operand
: constant Node_Id
:= Expression
(N
);
11569 Operand_Acc
: Node_Id
:= Operand
;
11570 Target_Type
: Entity_Id
:= Etype
(N
);
11571 Operand_Type
: Entity_Id
:= Etype
(Operand
);
11573 procedure Discrete_Range_Check
;
11574 -- Handles generation of range check for discrete target value
11576 procedure Handle_Changed_Representation
;
11577 -- This is called in the case of record and array type conversions to
11578 -- see if there is a change of representation to be handled. Change of
11579 -- representation is actually handled at the assignment statement level,
11580 -- and what this procedure does is rewrite node N conversion as an
11581 -- assignment to temporary. If there is no change of representation,
11582 -- then the conversion node is unchanged.
11584 procedure Raise_Accessibility_Error
;
11585 -- Called when we know that an accessibility check will fail. Rewrites
11586 -- node N to an appropriate raise statement and outputs warning msgs.
11587 -- The Etype of the raise node is set to Target_Type. Note that in this
11588 -- case the rest of the processing should be skipped (i.e. the call to
11589 -- this procedure will be followed by "goto Done").
11591 procedure Real_Range_Check
;
11592 -- Handles generation of range check for real target value
11594 function Has_Extra_Accessibility
(Id
: Entity_Id
) return Boolean;
11595 -- True iff Present (Effective_Extra_Accessibility (Id)) successfully
11596 -- evaluates to True.
11598 function Statically_Deeper_Relation_Applies
(Targ_Typ
: Entity_Id
)
11600 -- Given a target type for a conversion, determine whether the
11601 -- statically deeper accessibility rules apply to it.
11603 --------------------------
11604 -- Discrete_Range_Check --
11605 --------------------------
11607 -- Case of conversions to a discrete type. We let Generate_Range_Check
11608 -- do the heavy lifting, after converting a fixed-point operand to an
11609 -- appropriate integer type.
11611 procedure Discrete_Range_Check
is
11615 procedure Generate_Temporary
;
11616 -- Generate a temporary to facilitate in the C backend the code
11617 -- generation of the unchecked conversion since the size of the
11618 -- source type may differ from the size of the target type.
11620 ------------------------
11621 -- Generate_Temporary --
11622 ------------------------
11624 procedure Generate_Temporary
is
11626 if Esize
(Etype
(Expr
)) < Esize
(Etype
(Ityp
)) then
11628 Exp_Type
: constant Entity_Id
:= Ityp
;
11629 Def_Id
: constant Entity_Id
:=
11630 Make_Temporary
(Loc
, 'R', Expr
);
11635 Set_Is_Internal
(Def_Id
);
11636 Set_Etype
(Def_Id
, Exp_Type
);
11637 Res
:= New_Occurrence_Of
(Def_Id
, Loc
);
11640 Make_Object_Declaration
(Loc
,
11641 Defining_Identifier
=> Def_Id
,
11642 Object_Definition
=> New_Occurrence_Of
11644 Constant_Present
=> True,
11645 Expression
=> Relocate_Node
(Expr
));
11647 Set_Assignment_OK
(E
);
11648 Insert_Action
(Expr
, E
);
11650 Set_Assignment_OK
(Res
, Assignment_OK
(Expr
));
11652 Rewrite
(Expr
, Res
);
11653 Analyze_And_Resolve
(Expr
, Exp_Type
);
11656 end Generate_Temporary
;
11658 -- Start of processing for Discrete_Range_Check
11661 -- Nothing more to do if conversion was rewritten
11663 if Nkind
(N
) /= N_Type_Conversion
then
11667 Expr
:= Expression
(N
);
11669 -- Clear the Do_Range_Check flag on Expr
11671 Set_Do_Range_Check
(Expr
, False);
11673 -- Nothing to do if range checks suppressed
11675 if Range_Checks_Suppressed
(Target_Type
) then
11679 -- Nothing to do if expression is an entity on which checks have been
11682 if Is_Entity_Name
(Expr
)
11683 and then Range_Checks_Suppressed
(Entity
(Expr
))
11688 -- Before we do a range check, we have to deal with treating
11689 -- a fixed-point operand as an integer. The way we do this
11690 -- is simply to do an unchecked conversion to an appropriate
11691 -- integer type with the smallest size, so that we can suppress
11694 if Is_Fixed_Point_Type
(Etype
(Expr
)) then
11695 Ityp
:= Small_Integer_Type_For
11696 (Esize
(Base_Type
(Etype
(Expr
))), False);
11698 -- Generate a temporary with the integer type to facilitate in the
11699 -- C backend the code generation for the unchecked conversion.
11701 if Modify_Tree_For_C
then
11702 Generate_Temporary
;
11705 Rewrite
(Expr
, Unchecked_Convert_To
(Ityp
, Expr
));
11708 -- Reset overflow flag, since the range check will include
11709 -- dealing with possible overflow, and generate the check.
11711 Set_Do_Overflow_Check
(N
, False);
11713 Generate_Range_Check
(Expr
, Target_Type
, CE_Range_Check_Failed
);
11714 end Discrete_Range_Check
;
11716 -----------------------------------
11717 -- Handle_Changed_Representation --
11718 -----------------------------------
11720 procedure Handle_Changed_Representation
is
11728 -- Nothing else to do if no change of representation
11730 if Has_Compatible_Representation
(Target_Type
, Operand_Type
) then
11733 -- The real change of representation work is done by the assignment
11734 -- statement processing. So if this type conversion is appearing as
11735 -- the expression of an assignment statement, nothing needs to be
11736 -- done to the conversion.
11738 elsif Nkind
(Parent
(N
)) = N_Assignment_Statement
then
11741 -- Otherwise we need to generate a temporary variable, and do the
11742 -- change of representation assignment into that temporary variable.
11743 -- The conversion is then replaced by a reference to this variable.
11748 -- If type is unconstrained we have to add a constraint, copied
11749 -- from the actual value of the left-hand side.
11751 if not Is_Constrained
(Target_Type
) then
11752 if Has_Discriminants
(Operand_Type
) then
11754 -- A change of representation can only apply to untagged
11755 -- types. We need to build the constraint that applies to
11756 -- the target type, using the constraints of the operand.
11757 -- The analysis is complicated if there are both inherited
11758 -- discriminants and constrained discriminants.
11759 -- We iterate over the discriminants of the target, and
11760 -- find the discriminant of the same name:
11762 -- a) If there is a corresponding discriminant in the object
11763 -- then the value is a selected component of the operand.
11765 -- b) Otherwise the value of a constrained discriminant is
11766 -- found in the stored constraint of the operand.
11769 Stored
: constant Elist_Id
:=
11770 Stored_Constraint
(Operand_Type
);
11774 Disc_O
: Entity_Id
;
11775 -- Discriminant of the operand type. Its value in the
11776 -- object is captured in a selected component.
11778 Disc_S
: Entity_Id
;
11779 -- Stored discriminant of the operand. If present, it
11780 -- corresponds to a constrained discriminant of the
11783 Disc_T
: Entity_Id
;
11784 -- Discriminant of the target type
11787 Disc_T
:= First_Discriminant
(Target_Type
);
11788 Disc_O
:= First_Discriminant
(Operand_Type
);
11789 Disc_S
:= First_Stored_Discriminant
(Operand_Type
);
11791 if Present
(Stored
) then
11792 Elmt
:= First_Elmt
(Stored
);
11794 Elmt
:= No_Elmt
; -- init to avoid warning
11798 while Present
(Disc_T
) loop
11799 if Present
(Disc_O
)
11800 and then Chars
(Disc_T
) = Chars
(Disc_O
)
11803 Make_Selected_Component
(Loc
,
11805 Duplicate_Subexpr_Move_Checks
(Operand
),
11807 Make_Identifier
(Loc
, Chars
(Disc_O
))));
11808 Next_Discriminant
(Disc_O
);
11810 elsif Present
(Disc_S
) then
11811 Append_To
(Cons
, New_Copy_Tree
(Node
(Elmt
)));
11815 Next_Discriminant
(Disc_T
);
11819 elsif Is_Array_Type
(Operand_Type
) then
11820 N_Ix
:= First_Index
(Target_Type
);
11823 for J
in 1 .. Number_Dimensions
(Operand_Type
) loop
11825 -- We convert the bounds explicitly. We use an unchecked
11826 -- conversion because bounds checks are done elsewhere.
11831 Unchecked_Convert_To
(Etype
(N_Ix
),
11832 Make_Attribute_Reference
(Loc
,
11834 Duplicate_Subexpr_No_Checks
11835 (Operand
, Name_Req
=> True),
11836 Attribute_Name
=> Name_First
,
11837 Expressions
=> New_List
(
11838 Make_Integer_Literal
(Loc
, J
)))),
11841 Unchecked_Convert_To
(Etype
(N_Ix
),
11842 Make_Attribute_Reference
(Loc
,
11844 Duplicate_Subexpr_No_Checks
11845 (Operand
, Name_Req
=> True),
11846 Attribute_Name
=> Name_Last
,
11847 Expressions
=> New_List
(
11848 Make_Integer_Literal
(Loc
, J
))))));
11855 Odef
:= New_Occurrence_Of
(Target_Type
, Loc
);
11857 if Present
(Cons
) then
11859 Make_Subtype_Indication
(Loc
,
11860 Subtype_Mark
=> Odef
,
11862 Make_Index_Or_Discriminant_Constraint
(Loc
,
11863 Constraints
=> Cons
));
11866 Temp
:= Make_Temporary
(Loc
, 'C');
11868 Make_Object_Declaration
(Loc
,
11869 Defining_Identifier
=> Temp
,
11870 Object_Definition
=> Odef
);
11872 Set_No_Initialization
(Decl
, True);
11874 -- Insert required actions. It is essential to suppress checks
11875 -- since we have suppressed default initialization, which means
11876 -- that the variable we create may have no discriminants.
11881 Make_Assignment_Statement
(Loc
,
11882 Name
=> New_Occurrence_Of
(Temp
, Loc
),
11883 Expression
=> Relocate_Node
(N
))),
11884 Suppress
=> All_Checks
);
11886 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
11889 end Handle_Changed_Representation
;
11891 -------------------------------
11892 -- Raise_Accessibility_Error --
11893 -------------------------------
11895 procedure Raise_Accessibility_Error
is
11897 Error_Msg_Warn
:= SPARK_Mode
/= On
;
11899 Make_Raise_Program_Error
(Sloc
(N
),
11900 Reason
=> PE_Accessibility_Check_Failed
));
11901 Set_Etype
(N
, Target_Type
);
11903 Error_Msg_N
("<<accessibility check failure", N
);
11904 Error_Msg_NE
("\<<& [", N
, Standard_Program_Error
);
11905 end Raise_Accessibility_Error
;
11907 ----------------------
11908 -- Real_Range_Check --
11909 ----------------------
11911 -- Case of conversions to floating-point or fixed-point. If range checks
11912 -- are enabled and the target type has a range constraint, we convert:
11918 -- Tnn : typ'Base := typ'Base (x);
11919 -- [constraint_error when Tnn < typ'First or else Tnn > typ'Last]
11922 -- This is necessary when there is a conversion of integer to float or
11923 -- to fixed-point to ensure that the correct checks are made. It is not
11924 -- necessary for the float-to-float case where it is enough to just set
11925 -- the Do_Range_Check flag on the expression.
11927 procedure Real_Range_Check
is
11928 Btyp
: constant Entity_Id
:= Base_Type
(Target_Type
);
11929 Lo
: constant Node_Id
:= Type_Low_Bound
(Target_Type
);
11930 Hi
: constant Node_Id
:= Type_High_Bound
(Target_Type
);
11941 -- Nothing more to do if conversion was rewritten
11943 if Nkind
(N
) /= N_Type_Conversion
then
11947 Expr
:= Expression
(N
);
11949 -- Clear the Do_Range_Check flag on Expr
11951 Set_Do_Range_Check
(Expr
, False);
11953 -- Nothing to do if range checks suppressed, or target has the same
11954 -- range as the base type (or is the base type).
11956 if Range_Checks_Suppressed
(Target_Type
)
11957 or else (Lo
= Type_Low_Bound
(Btyp
)
11959 Hi
= Type_High_Bound
(Btyp
))
11964 -- Nothing to do if expression is an entity on which checks have been
11967 if Is_Entity_Name
(Expr
)
11968 and then Range_Checks_Suppressed
(Entity
(Expr
))
11973 -- Nothing to do if expression was rewritten into a float-to-float
11974 -- conversion, since this kind of conversion is handled elsewhere.
11976 if Is_Floating_Point_Type
(Etype
(Expr
))
11977 and then Is_Floating_Point_Type
(Target_Type
)
11982 -- Nothing to do if bounds are all static and we can tell that the
11983 -- expression is within the bounds of the target. Note that if the
11984 -- operand is of an unconstrained floating-point type, then we do
11985 -- not trust it to be in range (might be infinite)
11988 S_Lo
: constant Node_Id
:= Type_Low_Bound
(Etype
(Expr
));
11989 S_Hi
: constant Node_Id
:= Type_High_Bound
(Etype
(Expr
));
11992 if (not Is_Floating_Point_Type
(Etype
(Expr
))
11993 or else Is_Constrained
(Etype
(Expr
)))
11994 and then Compile_Time_Known_Value
(S_Lo
)
11995 and then Compile_Time_Known_Value
(S_Hi
)
11996 and then Compile_Time_Known_Value
(Hi
)
11997 and then Compile_Time_Known_Value
(Lo
)
12000 D_Lov
: constant Ureal
:= Expr_Value_R
(Lo
);
12001 D_Hiv
: constant Ureal
:= Expr_Value_R
(Hi
);
12006 if Is_Real_Type
(Etype
(Expr
)) then
12007 S_Lov
:= Expr_Value_R
(S_Lo
);
12008 S_Hiv
:= Expr_Value_R
(S_Hi
);
12010 S_Lov
:= UR_From_Uint
(Expr_Value
(S_Lo
));
12011 S_Hiv
:= UR_From_Uint
(Expr_Value
(S_Hi
));
12015 and then S_Lov
>= D_Lov
12016 and then S_Hiv
<= D_Hiv
12024 -- Otherwise rewrite the conversion as described above
12026 Conv
:= Convert_To
(Btyp
, Expr
);
12028 -- If a conversion is necessary, then copy the specific flags from
12029 -- the original one and also move the Do_Overflow_Check flag since
12030 -- this new conversion is to the base type.
12032 if Nkind
(Conv
) = N_Type_Conversion
then
12033 Set_Conversion_OK
(Conv
, Conversion_OK
(N
));
12034 Set_Float_Truncate
(Conv
, Float_Truncate
(N
));
12035 Set_Rounded_Result
(Conv
, Rounded_Result
(N
));
12037 if Do_Overflow_Check
(N
) then
12038 Set_Do_Overflow_Check
(Conv
);
12039 Set_Do_Overflow_Check
(N
, False);
12043 Tnn
:= Make_Temporary
(Loc
, 'T', Conv
);
12045 -- For a conversion from Float to Fixed where the bounds of the
12046 -- fixed-point type are static, we can obtain a more accurate
12047 -- fixed-point value by converting the result of the floating-
12048 -- point expression to an appropriate integer type, and then
12049 -- performing an unchecked conversion to the target fixed-point
12050 -- type. The range check can then use the corresponding integer
12051 -- value of the bounds instead of requiring further conversions.
12052 -- This preserves the identity:
12054 -- Fix_Val = Fixed_Type (Float_Type (Fix_Val))
12056 -- which used to fail when Fix_Val was a bound of the type and
12057 -- the 'Small was not a representable number.
12058 -- This transformation requires an integer type large enough to
12059 -- accommodate a fixed-point value.
12061 if Is_Ordinary_Fixed_Point_Type
(Target_Type
)
12062 and then Is_Floating_Point_Type
(Etype
(Expr
))
12063 and then RM_Size
(Btyp
) <= System_Max_Integer_Size
12064 and then Nkind
(Lo
) = N_Real_Literal
12065 and then Nkind
(Hi
) = N_Real_Literal
12068 Expr_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'T', Conv
);
12069 Int_Typ
: constant Entity_Id
:=
12070 Small_Integer_Type_For
(RM_Size
(Btyp
), False);
12073 -- Generate a temporary with the integer value. Required in the
12074 -- CCG compiler to ensure that run-time checks reference this
12075 -- integer expression (instead of the resulting fixed-point
12076 -- value because fixed-point values are handled by means of
12077 -- unsigned integer types).
12080 Make_Object_Declaration
(Loc
,
12081 Defining_Identifier
=> Expr_Id
,
12082 Object_Definition
=> New_Occurrence_Of
(Int_Typ
, Loc
),
12083 Constant_Present
=> True,
12085 Convert_To
(Int_Typ
, Expression
(Conv
))));
12087 -- Create integer objects for range checking of result.
12090 Unchecked_Convert_To
12091 (Int_Typ
, New_Occurrence_Of
(Expr_Id
, Loc
));
12094 Make_Integer_Literal
(Loc
, Corresponding_Integer_Value
(Lo
));
12097 Unchecked_Convert_To
12098 (Int_Typ
, New_Occurrence_Of
(Expr_Id
, Loc
));
12101 Make_Integer_Literal
(Loc
, Corresponding_Integer_Value
(Hi
));
12103 -- Rewrite conversion as an integer conversion of the
12104 -- original floating-point expression, followed by an
12105 -- unchecked conversion to the target fixed-point type.
12108 Unchecked_Convert_To
12109 (Target_Type
, New_Occurrence_Of
(Expr_Id
, Loc
));
12112 -- All other conversions
12115 Lo_Arg
:= New_Occurrence_Of
(Tnn
, Loc
);
12117 Make_Attribute_Reference
(Loc
,
12118 Prefix
=> New_Occurrence_Of
(Target_Type
, Loc
),
12119 Attribute_Name
=> Name_First
);
12121 Hi_Arg
:= New_Occurrence_Of
(Tnn
, Loc
);
12123 Make_Attribute_Reference
(Loc
,
12124 Prefix
=> New_Occurrence_Of
(Target_Type
, Loc
),
12125 Attribute_Name
=> Name_Last
);
12128 -- Build code for range checking. Note that checks are suppressed
12129 -- here since we don't want a recursive range check popping up.
12131 Insert_Actions
(N
, New_List
(
12132 Make_Object_Declaration
(Loc
,
12133 Defining_Identifier
=> Tnn
,
12134 Object_Definition
=> New_Occurrence_Of
(Btyp
, Loc
),
12135 Constant_Present
=> True,
12136 Expression
=> Conv
),
12138 Make_Raise_Constraint_Error
(Loc
,
12143 Left_Opnd
=> Lo_Arg
,
12144 Right_Opnd
=> Lo_Val
),
12148 Left_Opnd
=> Hi_Arg
,
12149 Right_Opnd
=> Hi_Val
)),
12150 Reason
=> CE_Range_Check_Failed
)),
12151 Suppress
=> All_Checks
);
12153 Rewrite
(Expr
, New_Occurrence_Of
(Tnn
, Loc
));
12154 end Real_Range_Check
;
12156 -----------------------------
12157 -- Has_Extra_Accessibility --
12158 -----------------------------
12160 -- Returns true for a formal of an anonymous access type or for an Ada
12161 -- 2012-style stand-alone object of an anonymous access type.
12163 function Has_Extra_Accessibility
(Id
: Entity_Id
) return Boolean is
12165 if Is_Formal
(Id
) or else Ekind
(Id
) in E_Constant | E_Variable
then
12166 return Present
(Effective_Extra_Accessibility
(Id
));
12170 end Has_Extra_Accessibility
;
12172 ----------------------------------------
12173 -- Statically_Deeper_Relation_Applies --
12174 ----------------------------------------
12176 function Statically_Deeper_Relation_Applies
(Targ_Typ
: Entity_Id
)
12180 -- The case where the target type is an anonymous access type is
12181 -- ignored since they have different semantics and get covered by
12182 -- various runtime checks depending on context.
12184 -- Note, the current implementation of this predicate is incomplete
12185 -- and doesn't fully reflect the rules given in RM 3.10.2 (19) and
12188 return Ekind
(Targ_Typ
) /= E_Anonymous_Access_Type
;
12189 end Statically_Deeper_Relation_Applies
;
12191 -- Start of processing for Expand_N_Type_Conversion
12194 -- First remove check marks put by the semantic analysis on the type
12195 -- conversion between array types. We need these checks, and they will
12196 -- be generated by this expansion routine, but we do not depend on these
12197 -- flags being set, and since we do intend to expand the checks in the
12198 -- front end, we don't want them on the tree passed to the back end.
12200 if Is_Array_Type
(Target_Type
) then
12201 if Is_Constrained
(Target_Type
) then
12202 Set_Do_Length_Check
(N
, False);
12204 Set_Do_Range_Check
(Operand
, False);
12208 -- Nothing at all to do if conversion is to the identical type so remove
12209 -- the conversion completely, it is useless, except that it may carry
12210 -- an Assignment_OK attribute, which must be propagated to the operand
12211 -- and the Do_Range_Check flag on the operand must be cleared, if any.
12213 if Operand_Type
= Target_Type
then
12214 if Assignment_OK
(N
) then
12215 Set_Assignment_OK
(Operand
);
12218 Set_Do_Range_Check
(Operand
, False);
12220 Rewrite
(N
, Relocate_Node
(Operand
));
12225 -- Nothing to do if this is the second argument of read. This is a
12226 -- "backwards" conversion that will be handled by the specialized code
12227 -- in attribute processing.
12229 if Nkind
(Parent
(N
)) = N_Attribute_Reference
12230 and then Attribute_Name
(Parent
(N
)) = Name_Read
12231 and then Next
(First
(Expressions
(Parent
(N
)))) = N
12236 -- Check for case of converting to a type that has an invariant
12237 -- associated with it. This requires an invariant check. We insert
12240 -- invariant_check (typ (expr))
12242 -- in the code, after removing side effects from the expression.
12243 -- This is clearer than replacing the conversion into an expression
12244 -- with actions, because the context may impose additional actions
12245 -- (tag checks, membership tests, etc.) that conflict with this
12246 -- rewriting (used previously).
12248 -- Note: the Comes_From_Source check, and then the resetting of this
12249 -- flag prevents what would otherwise be an infinite recursion.
12251 if Has_Invariants
(Target_Type
)
12252 and then Present
(Invariant_Procedure
(Target_Type
))
12253 and then Comes_From_Source
(N
)
12255 Set_Comes_From_Source
(N
, False);
12256 Remove_Side_Effects
(N
);
12257 Insert_Action
(N
, Make_Invariant_Call
(Duplicate_Subexpr
(N
)));
12260 -- AI12-0042: For a view conversion to a class-wide type occurring
12261 -- within the immediate scope of T, from a specific type that is
12262 -- a descendant of T (including T itself), an invariant check is
12263 -- performed on the part of the object that is of type T. (We don't
12264 -- need to explicitly check for the operand type being a descendant,
12265 -- just that it's a specific type, because the conversion would be
12266 -- illegal if it's specific and not a descendant -- downward conversion
12267 -- is not allowed).
12269 elsif Is_Class_Wide_Type
(Target_Type
)
12270 and then not Is_Class_Wide_Type
(Etype
(Expression
(N
)))
12271 and then Present
(Invariant_Procedure
(Root_Type
(Target_Type
)))
12272 and then Comes_From_Source
(N
)
12273 and then Within_Scope
(Find_Enclosing_Scope
(N
), Scope
(Target_Type
))
12275 Remove_Side_Effects
(N
);
12277 -- Perform the invariant check on a conversion to the class-wide
12278 -- type's root type.
12281 Root_Conv
: constant Node_Id
:=
12282 Make_Type_Conversion
(Loc
,
12284 New_Occurrence_Of
(Root_Type
(Target_Type
), Loc
),
12285 Expression
=> Duplicate_Subexpr
(Expression
(N
)));
12287 Set_Etype
(Root_Conv
, Root_Type
(Target_Type
));
12289 Insert_Action
(N
, Make_Invariant_Call
(Root_Conv
));
12294 -- Here if we may need to expand conversion
12296 -- If the operand of the type conversion is an arithmetic operation on
12297 -- signed integers, and the based type of the signed integer type in
12298 -- question is smaller than Standard.Integer, we promote both of the
12299 -- operands to type Integer.
12301 -- For example, if we have
12303 -- target-type (opnd1 + opnd2)
12305 -- and opnd1 and opnd2 are of type short integer, then we rewrite
12308 -- target-type (integer(opnd1) + integer(opnd2))
12310 -- We do this because we are always allowed to compute in a larger type
12311 -- if we do the right thing with the result, and in this case we are
12312 -- going to do a conversion which will do an appropriate check to make
12313 -- sure that things are in range of the target type in any case. This
12314 -- avoids some unnecessary intermediate overflows.
12316 -- We might consider a similar transformation in the case where the
12317 -- target is a real type or a 64-bit integer type, and the operand
12318 -- is an arithmetic operation using a 32-bit integer type. However,
12319 -- we do not bother with this case, because it could cause significant
12320 -- inefficiencies on 32-bit machines. On a 64-bit machine it would be
12321 -- much cheaper, but we don't want different behavior on 32-bit and
12322 -- 64-bit machines. Note that the exclusion of the 64-bit case also
12323 -- handles the configurable run-time cases where 64-bit arithmetic
12324 -- may simply be unavailable.
12326 -- Note: this circuit is partially redundant with respect to the circuit
12327 -- in Checks.Apply_Arithmetic_Overflow_Check, but we catch more cases in
12328 -- the processing here. Also we still need the Checks circuit, since we
12329 -- have to be sure not to generate junk overflow checks in the first
12330 -- place, since it would be tricky to remove them here.
12332 if Integer_Promotion_Possible
(N
) then
12334 -- All conditions met, go ahead with transformation
12341 Opnd
:= New_Op_Node
(Nkind
(Operand
), Loc
);
12343 R
:= Convert_To
(Standard_Integer
, Right_Opnd
(Operand
));
12344 Set_Right_Opnd
(Opnd
, R
);
12346 if Nkind
(Operand
) in N_Binary_Op
then
12347 L
:= Convert_To
(Standard_Integer
, Left_Opnd
(Operand
));
12348 Set_Left_Opnd
(Opnd
, L
);
12352 Make_Type_Conversion
(Loc
,
12353 Subtype_Mark
=> Relocate_Node
(Subtype_Mark
(N
)),
12354 Expression
=> Opnd
));
12356 Analyze_And_Resolve
(N
, Target_Type
);
12361 -- If the conversion is from Universal_Integer and requires an overflow
12362 -- check, try to do an intermediate conversion to a narrower type first
12363 -- without overflow check, in order to avoid doing the overflow check
12364 -- in Universal_Integer, which can be a very large type.
12366 if Operand_Type
= Universal_Integer
and then Do_Overflow_Check
(N
) then
12368 Lo
, Hi
, Siz
: Uint
;
12373 Determine_Range
(Operand
, OK
, Lo
, Hi
, Assume_Valid
=> True);
12376 Siz
:= Get_Size_For_Range
(Lo
, Hi
);
12378 -- We use the base type instead of the first subtype because
12379 -- overflow checks are done in the base type, so this avoids
12380 -- the need for useless conversions.
12382 if Siz
< System_Max_Integer_Size
then
12383 Typ
:= Etype
(Integer_Type_For
(Siz
, Uns
=> False));
12385 Convert_To_And_Rewrite
(Typ
, Operand
);
12386 Analyze_And_Resolve
12387 (Operand
, Typ
, Suppress
=> Overflow_Check
);
12389 Analyze_And_Resolve
(N
, Target_Type
);
12396 -- Do validity check if validity checking operands
12398 if Validity_Checks_On
and Validity_Check_Operands
then
12399 Ensure_Valid
(Operand
);
12402 -- Special case of converting from non-standard boolean type
12404 if Is_Boolean_Type
(Operand_Type
)
12405 and then (Nonzero_Is_True
(Operand_Type
))
12407 Adjust_Condition
(Operand
);
12408 Set_Etype
(Operand
, Standard_Boolean
);
12409 Operand_Type
:= Standard_Boolean
;
12412 -- Case of converting to an access type
12414 if Is_Access_Type
(Target_Type
) then
12415 -- In terms of accessibility rules, an anonymous access discriminant
12416 -- is not considered separate from its parent object.
12418 if Nkind
(Operand
) = N_Selected_Component
12419 and then Ekind
(Entity
(Selector_Name
(Operand
))) = E_Discriminant
12420 and then Ekind
(Operand_Type
) = E_Anonymous_Access_Type
12422 Operand_Acc
:= Original_Node
(Prefix
(Operand
));
12425 -- If this type conversion was internally generated by the front end
12426 -- to displace the pointer to the object to reference an interface
12427 -- type and the original node was an Unrestricted_Access attribute,
12428 -- then skip applying accessibility checks (because, according to the
12429 -- GNAT Reference Manual, this attribute is similar to 'Access except
12430 -- that all accessibility and aliased view checks are omitted).
12432 if not Comes_From_Source
(N
)
12433 and then Is_Interface
(Designated_Type
(Target_Type
))
12434 and then Nkind
(Original_Node
(N
)) = N_Attribute_Reference
12435 and then Attribute_Name
(Original_Node
(N
)) =
12436 Name_Unrestricted_Access
12440 -- Apply an accessibility check when the conversion operand is an
12441 -- access parameter (or a renaming thereof), unless conversion was
12442 -- expanded from an Unchecked_ or Unrestricted_Access attribute,
12443 -- or for the actual of a class-wide interface parameter. Note that
12444 -- other checks may still need to be applied below (such as tagged
12447 elsif Is_Entity_Name
(Operand_Acc
)
12448 and then Has_Extra_Accessibility
(Entity
(Operand_Acc
))
12449 and then Ekind
(Etype
(Operand_Acc
)) = E_Anonymous_Access_Type
12450 and then (Nkind
(Original_Node
(N
)) /= N_Attribute_Reference
12451 or else Attribute_Name
(Original_Node
(N
)) = Name_Access
)
12452 and then not No_Dynamic_Accessibility_Checks_Enabled
(N
)
12454 if not Comes_From_Source
(N
)
12455 and then Nkind
(Parent
(N
)) in N_Function_Call
12456 | N_Parameter_Association
12457 | N_Procedure_Call_Statement
12458 and then Is_Interface
(Designated_Type
(Target_Type
))
12459 and then Is_Class_Wide_Type
(Designated_Type
(Target_Type
))
12464 Apply_Accessibility_Check
12465 (Operand
, Target_Type
, Insert_Node
=> Operand
);
12468 -- If the level of the operand type is statically deeper than the
12469 -- level of the target type, then force Program_Error. Note that this
12470 -- can only occur for cases where the attribute is within the body of
12471 -- an instantiation, otherwise the conversion will already have been
12472 -- rejected as illegal.
12474 -- Note: warnings are issued by the analyzer for the instance cases,
12475 -- and, since we are late in expansion, a check is performed to
12476 -- verify that neither the target type nor the operand type are
12477 -- internally generated - as this can lead to spurious errors when,
12478 -- for example, the operand type is a result of BIP expansion.
12480 elsif In_Instance_Body
12481 and then Statically_Deeper_Relation_Applies
(Target_Type
)
12482 and then not Is_Internal
(Target_Type
)
12483 and then not Is_Internal
(Operand_Type
)
12485 Type_Access_Level
(Operand_Type
) > Type_Access_Level
(Target_Type
)
12487 Raise_Accessibility_Error
;
12490 -- When the operand is a selected access discriminant the check needs
12491 -- to be made against the level of the object denoted by the prefix
12492 -- of the selected name. Force Program_Error for this case as well
12493 -- (this accessibility violation can only happen if within the body
12494 -- of an instantiation).
12496 elsif In_Instance_Body
12497 and then Ekind
(Operand_Type
) = E_Anonymous_Access_Type
12498 and then Nkind
(Operand
) = N_Selected_Component
12499 and then Ekind
(Entity
(Selector_Name
(Operand
))) = E_Discriminant
12500 and then Static_Accessibility_Level
(Operand
, Zero_On_Dynamic_Level
)
12501 > Type_Access_Level
(Target_Type
)
12503 Raise_Accessibility_Error
;
12508 -- Case of conversions of tagged types and access to tagged types
12510 -- When needed, that is to say when the expression is class-wide, Add
12511 -- runtime a tag check for (strict) downward conversion by using the
12512 -- membership test, generating:
12514 -- [constraint_error when Operand not in Target_Type'Class]
12516 -- or in the access type case
12518 -- [constraint_error
12519 -- when Operand /= null
12520 -- and then Operand.all not in
12521 -- Designated_Type (Target_Type)'Class]
12523 if (Is_Access_Type
(Target_Type
)
12524 and then Is_Tagged_Type
(Designated_Type
(Target_Type
)))
12525 or else Is_Tagged_Type
(Target_Type
)
12527 -- Do not do any expansion in the access type case if the parent is a
12528 -- renaming, since this is an error situation which will be caught by
12529 -- Sem_Ch8, and the expansion can interfere with this error check.
12531 if Is_Access_Type
(Target_Type
) and then Is_Renamed_Object
(N
) then
12535 -- Otherwise, proceed with processing tagged conversion
12537 Tagged_Conversion
: declare
12538 Actual_Op_Typ
: Entity_Id
;
12539 Actual_Targ_Typ
: Entity_Id
;
12540 Root_Op_Typ
: Entity_Id
;
12542 procedure Make_Tag_Check
(Targ_Typ
: Entity_Id
);
12543 -- Create a membership check to test whether Operand is a member
12544 -- of Targ_Typ. If the original Target_Type is an access, include
12545 -- a test for null value. The check is inserted at N.
12547 --------------------
12548 -- Make_Tag_Check --
12549 --------------------
12551 procedure Make_Tag_Check
(Targ_Typ
: Entity_Id
) is
12556 -- [Constraint_Error
12557 -- when Operand /= null
12558 -- and then Operand.all not in Targ_Typ]
12560 if Is_Access_Type
(Target_Type
) then
12562 Make_And_Then
(Loc
,
12565 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Operand
),
12566 Right_Opnd
=> Make_Null
(Loc
)),
12571 Make_Explicit_Dereference
(Loc
,
12572 Prefix
=> Duplicate_Subexpr_No_Checks
(Operand
)),
12573 Right_Opnd
=> New_Occurrence_Of
(Targ_Typ
, Loc
)));
12576 -- [Constraint_Error when Operand not in Targ_Typ]
12581 Left_Opnd
=> Duplicate_Subexpr_No_Checks
(Operand
),
12582 Right_Opnd
=> New_Occurrence_Of
(Targ_Typ
, Loc
));
12586 Make_Raise_Constraint_Error
(Loc
,
12588 Reason
=> CE_Tag_Check_Failed
),
12589 Suppress
=> All_Checks
);
12590 end Make_Tag_Check
;
12592 -- Start of processing for Tagged_Conversion
12595 -- Handle entities from the limited view
12597 if Is_Access_Type
(Operand_Type
) then
12599 Available_View
(Designated_Type
(Operand_Type
));
12601 Actual_Op_Typ
:= Operand_Type
;
12604 if Is_Access_Type
(Target_Type
) then
12606 Available_View
(Designated_Type
(Target_Type
));
12608 Actual_Targ_Typ
:= Target_Type
;
12611 Root_Op_Typ
:= Root_Type
(Actual_Op_Typ
);
12613 -- Ada 2005 (AI-251): Handle interface type conversion
12615 if Is_Interface
(Actual_Op_Typ
)
12617 Is_Interface
(Actual_Targ_Typ
)
12619 Expand_Interface_Conversion
(N
);
12623 -- Create a runtime tag check for a downward CW type conversion
12625 if Is_Class_Wide_Type
(Actual_Op_Typ
)
12626 and then Actual_Op_Typ
/= Actual_Targ_Typ
12627 and then Root_Op_Typ
/= Actual_Targ_Typ
12628 and then Is_Ancestor
12629 (Root_Op_Typ
, Actual_Targ_Typ
, Use_Full_View
=> True)
12630 and then not Tag_Checks_Suppressed
(Actual_Targ_Typ
)
12635 Make_Tag_Check
(Class_Wide_Type
(Actual_Targ_Typ
));
12636 Conv
:= Unchecked_Convert_To
(Target_Type
, Expression
(N
));
12638 Analyze_And_Resolve
(N
, Target_Type
);
12641 end Tagged_Conversion
;
12643 -- Case of other access type conversions
12645 elsif Is_Access_Type
(Target_Type
) then
12646 Apply_Constraint_Check
(Operand
, Target_Type
);
12648 -- Case of conversions from a fixed-point type
12650 -- These conversions require special expansion and processing, found in
12651 -- the Exp_Fixd package. We ignore cases where Conversion_OK is set,
12652 -- since from a semantic point of view, these are simple integer
12653 -- conversions, which do not need further processing except for the
12654 -- generation of range checks, which is performed at the end of this
12657 elsif Is_Fixed_Point_Type
(Operand_Type
)
12658 and then not Conversion_OK
(N
)
12660 -- We should never see universal fixed at this case, since the
12661 -- expansion of the constituent divide or multiply should have
12662 -- eliminated the explicit mention of universal fixed.
12664 pragma Assert
(Operand_Type
/= Universal_Fixed
);
12666 -- Check for special case of the conversion to universal real that
12667 -- occurs as a result of the use of a round attribute. In this case,
12668 -- the real type for the conversion is taken from the target type of
12669 -- the Round attribute and the result must be marked as rounded.
12671 if Target_Type
= Universal_Real
12672 and then Nkind
(Parent
(N
)) = N_Attribute_Reference
12673 and then Attribute_Name
(Parent
(N
)) = Name_Round
12675 Set_Etype
(N
, Etype
(Parent
(N
)));
12676 Target_Type
:= Etype
(N
);
12677 Set_Rounded_Result
(N
);
12680 if Is_Fixed_Point_Type
(Target_Type
) then
12681 Expand_Convert_Fixed_To_Fixed
(N
);
12682 elsif Is_Integer_Type
(Target_Type
) then
12683 Expand_Convert_Fixed_To_Integer
(N
);
12685 pragma Assert
(Is_Floating_Point_Type
(Target_Type
));
12686 Expand_Convert_Fixed_To_Float
(N
);
12689 -- Case of conversions to a fixed-point type
12691 -- These conversions require special expansion and processing, found in
12692 -- the Exp_Fixd package. Again, ignore cases where Conversion_OK is set,
12693 -- since from a semantic point of view, these are simple integer
12694 -- conversions, which do not need further processing.
12696 elsif Is_Fixed_Point_Type
(Target_Type
)
12697 and then not Conversion_OK
(N
)
12699 if Is_Integer_Type
(Operand_Type
) then
12700 Expand_Convert_Integer_To_Fixed
(N
);
12702 pragma Assert
(Is_Floating_Point_Type
(Operand_Type
));
12703 Expand_Convert_Float_To_Fixed
(N
);
12706 -- Case of array conversions
12708 -- Expansion of array conversions, add required length/range checks but
12709 -- only do this if there is no change of representation. For handling of
12710 -- this case, see Handle_Changed_Representation.
12712 elsif Is_Array_Type
(Target_Type
) then
12713 if Is_Constrained
(Target_Type
) then
12714 Apply_Length_Check
(Operand
, Target_Type
);
12716 -- If the object has an unconstrained array subtype with fixed
12717 -- lower bound, then sliding to that bound may be needed.
12719 if Is_Fixed_Lower_Bound_Array_Subtype
(Target_Type
) then
12720 Expand_Sliding_Conversion
(Operand
, Target_Type
);
12723 Apply_Range_Check
(Operand
, Target_Type
);
12726 Handle_Changed_Representation
;
12728 -- Case of conversions of discriminated types
12730 -- Add required discriminant checks if target is constrained. Again this
12731 -- change is skipped if we have a change of representation.
12733 elsif Has_Discriminants
(Target_Type
)
12734 and then Is_Constrained
(Target_Type
)
12736 Apply_Discriminant_Check
(Operand
, Target_Type
);
12737 Handle_Changed_Representation
;
12739 -- Case of all other record conversions. The only processing required
12740 -- is to check for a change of representation requiring the special
12741 -- assignment processing.
12743 elsif Is_Record_Type
(Target_Type
) then
12745 -- Ada 2005 (AI-216): Program_Error is raised when converting from
12746 -- a derived Unchecked_Union type to an unconstrained type that is
12747 -- not Unchecked_Union if the operand lacks inferable discriminants.
12749 if Is_Derived_Type
(Operand_Type
)
12750 and then Is_Unchecked_Union
(Base_Type
(Operand_Type
))
12751 and then not Is_Constrained
(Target_Type
)
12752 and then not Is_Unchecked_Union
(Base_Type
(Target_Type
))
12753 and then not Has_Inferable_Discriminants
(Operand
)
12755 -- To prevent Gigi from generating illegal code, we generate a
12756 -- Program_Error node, but we give it the target type of the
12757 -- conversion (is this requirement documented somewhere ???)
12760 PE
: constant Node_Id
:= Make_Raise_Program_Error
(Loc
,
12761 Reason
=> PE_Unchecked_Union_Restriction
);
12764 Set_Etype
(PE
, Target_Type
);
12769 Handle_Changed_Representation
;
12772 -- Case of conversions of enumeration types
12774 elsif Is_Enumeration_Type
(Target_Type
) then
12776 -- Special processing is required if there is a change of
12777 -- representation (from enumeration representation clauses).
12779 if not Has_Compatible_Representation
(Target_Type
, Operand_Type
)
12780 and then not Conversion_OK
(N
)
12783 -- Convert: x(y) to x'val (ytyp'pos (y))
12786 Make_Attribute_Reference
(Loc
,
12787 Prefix
=> New_Occurrence_Of
(Target_Type
, Loc
),
12788 Attribute_Name
=> Name_Val
,
12789 Expressions
=> New_List
(
12790 Make_Attribute_Reference
(Loc
,
12791 Prefix
=> New_Occurrence_Of
(Operand_Type
, Loc
),
12792 Attribute_Name
=> Name_Pos
,
12793 Expressions
=> New_List
(Operand
)))));
12795 Analyze_And_Resolve
(N
, Target_Type
);
12799 -- At this stage, either the conversion node has been transformed into
12800 -- some other equivalent expression, or left as a conversion that can be
12801 -- handled by Gigi.
12803 -- The only remaining step is to generate a range check if we still have
12804 -- a type conversion at this stage and Do_Range_Check is set. Note that
12805 -- we need to deal with at most 8 out of the 9 possible cases of numeric
12806 -- conversions here, because the float-to-integer case is entirely dealt
12807 -- with by Apply_Float_Conversion_Check.
12809 if Nkind
(N
) = N_Type_Conversion
12810 and then Do_Range_Check
(Expression
(N
))
12812 -- Float-to-float conversions
12814 if Is_Floating_Point_Type
(Target_Type
)
12815 and then Is_Floating_Point_Type
(Etype
(Expression
(N
)))
12817 -- Reset overflow flag, since the range check will include
12818 -- dealing with possible overflow, and generate the check.
12820 Set_Do_Overflow_Check
(N
, False);
12822 Generate_Range_Check
12823 (Expression
(N
), Target_Type
, CE_Range_Check_Failed
);
12825 -- Discrete-to-discrete conversions or fixed-point-to-discrete
12826 -- conversions when Conversion_OK is set.
12828 elsif Is_Discrete_Type
(Target_Type
)
12829 and then (Is_Discrete_Type
(Etype
(Expression
(N
)))
12830 or else (Is_Fixed_Point_Type
(Etype
(Expression
(N
)))
12831 and then Conversion_OK
(N
)))
12833 -- If Address is either a source type or target type,
12834 -- suppress range check to avoid typing anomalies when
12835 -- it is a visible integer type.
12837 if Is_Descendant_Of_Address
(Etype
(Expression
(N
)))
12838 or else Is_Descendant_Of_Address
(Target_Type
)
12840 Set_Do_Range_Check
(Expression
(N
), False);
12842 Discrete_Range_Check
;
12845 -- Conversions to floating- or fixed-point when Conversion_OK is set
12847 elsif Is_Floating_Point_Type
(Target_Type
)
12848 or else (Is_Fixed_Point_Type
(Target_Type
)
12849 and then Conversion_OK
(N
))
12854 pragma Assert
(not Do_Range_Check
(Expression
(N
)));
12857 -- Here at end of processing
12860 -- Apply predicate check if required. Note that we can't just call
12861 -- Apply_Predicate_Check here, because the type looks right after
12862 -- the conversion and it would omit the check. The Comes_From_Source
12863 -- guard is necessary to prevent infinite recursions when we generate
12864 -- internal conversions for the purpose of checking predicates.
12866 -- A view conversion of a tagged object is an object and can appear
12867 -- in an assignment context, in which case no predicate check applies
12868 -- to the now-dead value.
12870 if Nkind
(Parent
(N
)) = N_Assignment_Statement
12871 and then N
= Name
(Parent
(N
))
12875 elsif Predicate_Enabled
(Target_Type
)
12876 and then Target_Type
/= Operand_Type
12877 and then Comes_From_Source
(N
)
12880 New_Expr
: constant Node_Id
:= Duplicate_Subexpr
(N
);
12883 -- Avoid infinite recursion on the subsequent expansion of the
12884 -- copy of the original type conversion. When needed, a range
12885 -- check has already been applied to the expression.
12887 Set_Comes_From_Source
(New_Expr
, False);
12889 Make_Predicate_Check
(Target_Type
, New_Expr
),
12890 Suppress
=> Range_Check
);
12893 end Expand_N_Type_Conversion
;
12895 -----------------------------------
12896 -- Expand_N_Unchecked_Expression --
12897 -----------------------------------
12899 -- Remove the unchecked expression node from the tree. Its job was simply
12900 -- to make sure that its constituent expression was handled with checks
12901 -- off, and now that is done, we can remove it from the tree, and indeed
12902 -- must, since Gigi does not expect to see these nodes.
12904 procedure Expand_N_Unchecked_Expression
(N
: Node_Id
) is
12905 Exp
: constant Node_Id
:= Expression
(N
);
12907 Set_Assignment_OK
(Exp
, Assignment_OK
(N
) or else Assignment_OK
(Exp
));
12909 end Expand_N_Unchecked_Expression
;
12911 ----------------------------------------
12912 -- Expand_N_Unchecked_Type_Conversion --
12913 ----------------------------------------
12915 -- If this cannot be handled by Gigi and we haven't already made a
12916 -- temporary for it, do it now.
12918 procedure Expand_N_Unchecked_Type_Conversion
(N
: Node_Id
) is
12919 Target_Type
: constant Entity_Id
:= Etype
(N
);
12920 Operand
: constant Node_Id
:= Expression
(N
);
12921 Operand_Type
: constant Entity_Id
:= Etype
(Operand
);
12924 -- Nothing at all to do if conversion is to the identical type so remove
12925 -- the conversion completely, it is useless, except that it may carry
12926 -- an Assignment_OK indication which must be propagated to the operand.
12928 if Operand_Type
= Target_Type
then
12929 Expand_N_Unchecked_Expression
(N
);
12933 -- Generate an extra temporary for cases unsupported by the C backend
12935 if Modify_Tree_For_C
then
12937 Source
: constant Node_Id
:= Unqual_Conv
(Expression
(N
));
12938 Source_Typ
: Entity_Id
:= Get_Full_View
(Etype
(Source
));
12941 if Is_Packed_Array
(Source_Typ
) then
12942 Source_Typ
:= Packed_Array_Impl_Type
(Source_Typ
);
12945 if Nkind
(Source
) = N_Function_Call
12946 and then (Is_Composite_Type
(Etype
(Source
))
12947 or else Is_Composite_Type
(Target_Type
))
12949 Force_Evaluation
(Source
);
12954 -- Nothing to do if conversion is safe
12956 if Safe_Unchecked_Type_Conversion
(N
) then
12960 if Assignment_OK
(N
) then
12963 Force_Evaluation
(N
);
12965 end Expand_N_Unchecked_Type_Conversion
;
12967 ----------------------------
12968 -- Expand_Record_Equality --
12969 ----------------------------
12971 -- For non-variant records, Equality is expanded when needed into:
12973 -- and then Lhs.Discr1 = Rhs.Discr1
12975 -- and then Lhs.Discrn = Rhs.Discrn
12976 -- and then Lhs.Cmp1 = Rhs.Cmp1
12978 -- and then Lhs.Cmpn = Rhs.Cmpn
12980 -- The expression is folded by the back end for adjacent fields. This
12981 -- function is called for tagged record in only one occasion: for imple-
12982 -- menting predefined primitive equality (see Predefined_Primitives_Bodies)
12983 -- otherwise the primitive "=" is used directly.
12985 function Expand_Record_Equality
12989 Rhs
: Node_Id
) return Node_Id
12991 Loc
: constant Source_Ptr
:= Sloc
(Nod
);
12996 First_Time
: Boolean := True;
12998 function Element_To_Compare
(C
: Entity_Id
) return Entity_Id
;
12999 -- Return the next discriminant or component to compare, starting with
13000 -- C, skipping inherited components.
13002 ------------------------
13003 -- Element_To_Compare --
13004 ------------------------
13006 function Element_To_Compare
(C
: Entity_Id
) return Entity_Id
is
13007 Comp
: Entity_Id
:= C
;
13010 while Present
(Comp
) loop
13011 -- Skip inherited components
13013 -- Note: for a tagged type, we always generate the "=" primitive
13014 -- for the base type (not on the first subtype), so the test for
13015 -- Comp /= Original_Record_Component (Comp) is True for inherited
13016 -- components only.
13018 if (Is_Tagged_Type
(Typ
)
13019 and then Comp
/= Original_Record_Component
(Comp
))
13023 or else Chars
(Comp
) = Name_uTag
13025 -- Skip interface elements (secondary tags???)
13027 or else Is_Interface
(Etype
(Comp
))
13029 Next_Component_Or_Discriminant
(Comp
);
13036 end Element_To_Compare
;
13038 -- Start of processing for Expand_Record_Equality
13041 -- Generates the following code: (assuming that Typ has one Discr and
13042 -- component C2 is also a record)
13044 -- Lhs.Discr1 = Rhs.Discr1
13045 -- and then Lhs.C1 = Rhs.C1
13046 -- and then Lhs.C2.C1=Rhs.C2.C1 and then ... Lhs.C2.Cn=Rhs.C2.Cn
13048 -- and then Lhs.Cmpn = Rhs.Cmpn
13050 Result
:= New_Occurrence_Of
(Standard_True
, Loc
);
13051 C
:= Element_To_Compare
(First_Component_Or_Discriminant
(Typ
));
13052 while Present
(C
) loop
13063 New_Lhs
:= New_Copy_Tree
(Lhs
);
13064 New_Rhs
:= New_Copy_Tree
(Rhs
);
13068 Expand_Composite_Equality
(Nod
, Etype
(C
),
13070 Make_Selected_Component
(Loc
,
13072 Selector_Name
=> New_Occurrence_Of
(C
, Loc
)),
13074 Make_Selected_Component
(Loc
,
13076 Selector_Name
=> New_Occurrence_Of
(C
, Loc
)));
13078 -- If some (sub)component is an unchecked_union, the whole
13079 -- operation will raise program error.
13081 if Nkind
(Check
) = N_Raise_Program_Error
then
13083 Set_Etype
(Result
, Standard_Boolean
);
13089 -- Generate logical "and" for CodePeer to simplify the
13090 -- generated code and analysis.
13092 elsif CodePeer_Mode
then
13095 Left_Opnd
=> Result
,
13096 Right_Opnd
=> Check
);
13100 Make_And_Then
(Loc
,
13101 Left_Opnd
=> Result
,
13102 Right_Opnd
=> Check
);
13107 First_Time
:= False;
13108 C
:= Element_To_Compare
(Next_Component_Or_Discriminant
(C
));
13112 end Expand_Record_Equality
;
13114 ---------------------------
13115 -- Expand_Set_Membership --
13116 ---------------------------
13118 procedure Expand_Set_Membership
(N
: Node_Id
) is
13119 Lop
: constant Node_Id
:= Left_Opnd
(N
);
13123 function Make_Cond
(Alt
: Node_Id
) return Node_Id
;
13124 -- If the alternative is a subtype mark, create a simple membership
13125 -- test. Otherwise create an equality test for it.
13131 function Make_Cond
(Alt
: Node_Id
) return Node_Id
is
13133 L
: constant Node_Id
:= New_Copy_Tree
(Lop
);
13134 R
: constant Node_Id
:= Relocate_Node
(Alt
);
13137 if (Is_Entity_Name
(Alt
) and then Is_Type
(Entity
(Alt
)))
13138 or else Nkind
(Alt
) = N_Range
13141 Make_In
(Sloc
(Alt
),
13146 Make_Op_Eq
(Sloc
(Alt
),
13150 if Is_Record_Or_Limited_Type
(Etype
(Alt
)) then
13152 -- We reset the Entity in order to use the primitive equality
13153 -- of the type, as per RM 4.5.2 (28.1/4).
13155 Set_Entity
(Cond
, Empty
);
13162 -- Start of processing for Expand_Set_Membership
13165 Remove_Side_Effects
(Lop
);
13167 Alt
:= First
(Alternatives
(N
));
13168 Res
:= Make_Cond
(Alt
);
13171 -- We use left associativity as in the equivalent boolean case. This
13172 -- kind of canonicalization helps the optimizer of the code generator.
13174 while Present
(Alt
) loop
13176 Make_Or_Else
(Sloc
(Alt
),
13178 Right_Opnd
=> Make_Cond
(Alt
));
13183 Analyze_And_Resolve
(N
, Standard_Boolean
);
13184 end Expand_Set_Membership
;
13186 -----------------------------------
13187 -- Expand_Short_Circuit_Operator --
13188 -----------------------------------
13190 -- Deal with special expansion if actions are present for the right operand
13191 -- and deal with optimizing case of arguments being True or False. We also
13192 -- deal with the special case of non-standard boolean values.
13194 procedure Expand_Short_Circuit_Operator
(N
: Node_Id
) is
13195 Loc
: constant Source_Ptr
:= Sloc
(N
);
13196 Typ
: constant Entity_Id
:= Etype
(N
);
13197 Left
: constant Node_Id
:= Left_Opnd
(N
);
13198 Right
: constant Node_Id
:= Right_Opnd
(N
);
13199 LocR
: constant Source_Ptr
:= Sloc
(Right
);
13202 Shortcut_Value
: constant Boolean := Nkind
(N
) = N_Or_Else
;
13203 Shortcut_Ent
: constant Entity_Id
:= Boolean_Literals
(Shortcut_Value
);
13204 -- If Left = Shortcut_Value then Right need not be evaluated
13206 function Make_Test_Expr
(Opnd
: Node_Id
) return Node_Id
;
13207 -- For Opnd a boolean expression, return a Boolean expression equivalent
13208 -- to Opnd /= Shortcut_Value.
13210 function Useful
(Actions
: List_Id
) return Boolean;
13211 -- Return True if Actions is not empty and contains useful nodes to
13214 --------------------
13215 -- Make_Test_Expr --
13216 --------------------
13218 function Make_Test_Expr
(Opnd
: Node_Id
) return Node_Id
is
13220 if Shortcut_Value
then
13221 return Make_Op_Not
(Sloc
(Opnd
), Opnd
);
13225 end Make_Test_Expr
;
13231 function Useful
(Actions
: List_Id
) return Boolean is
13234 if Present
(Actions
) then
13235 L
:= First
(Actions
);
13237 -- For now "useful" means not N_Variable_Reference_Marker.
13238 -- Consider stripping other nodes in the future.
13240 while Present
(L
) loop
13241 if Nkind
(L
) /= N_Variable_Reference_Marker
then
13254 Op_Var
: Entity_Id
;
13255 -- Entity for a temporary variable holding the value of the operator,
13256 -- used for expansion in the case where actions are present.
13258 -- Start of processing for Expand_Short_Circuit_Operator
13261 -- Deal with non-standard booleans
13263 if Is_Boolean_Type
(Typ
) then
13264 Adjust_Condition
(Left
);
13265 Adjust_Condition
(Right
);
13266 Set_Etype
(N
, Standard_Boolean
);
13269 -- Check for cases where left argument is known to be True or False
13271 if Compile_Time_Known_Value
(Left
) then
13273 -- Mark SCO for left condition as compile time known
13275 if Generate_SCO
and then Comes_From_Source
(Left
) then
13276 Set_SCO_Condition
(Left
, Expr_Value_E
(Left
) = Standard_True
);
13279 -- Rewrite True AND THEN Right / False OR ELSE Right to Right.
13280 -- Any actions associated with Right will be executed unconditionally
13281 -- and can thus be inserted into the tree unconditionally.
13283 if Expr_Value_E
(Left
) /= Shortcut_Ent
then
13284 if Present
(Actions
(N
)) then
13285 Insert_Actions
(N
, Actions
(N
));
13288 Rewrite
(N
, Right
);
13290 -- Rewrite False AND THEN Right / True OR ELSE Right to Left.
13291 -- In this case we can forget the actions associated with Right,
13292 -- since they will never be executed.
13295 Kill_Dead_Code
(Right
);
13296 Kill_Dead_Code
(Actions
(N
));
13297 Rewrite
(N
, New_Occurrence_Of
(Shortcut_Ent
, Loc
));
13300 Adjust_Result_Type
(N
, Typ
);
13304 -- If Actions are present for the right operand, we have to do some
13305 -- special processing. We can't just let these actions filter back into
13306 -- code preceding the short circuit (which is what would have happened
13307 -- if we had not trapped them in the short-circuit form), since they
13308 -- must only be executed if the right operand of the short circuit is
13309 -- executed and not otherwise.
13311 if Useful
(Actions
(N
)) then
13312 Actlist
:= Actions
(N
);
13314 -- The old approach is to expand:
13316 -- left AND THEN right
13320 -- C : Boolean := False;
13328 -- and finally rewrite the operator into a reference to C. Similarly
13329 -- for left OR ELSE right, with negated values. Note that this
13330 -- rewrite causes some difficulties for coverage analysis because
13331 -- of the introduction of the new variable C, which obscures the
13332 -- structure of the test.
13334 -- We use this "old approach" if Minimize_Expression_With_Actions
13337 if Minimize_Expression_With_Actions
then
13338 Op_Var
:= Make_Temporary
(Loc
, 'C', Related_Node
=> N
);
13341 Make_Object_Declaration
(Loc
,
13342 Defining_Identifier
=> Op_Var
,
13343 Object_Definition
=>
13344 New_Occurrence_Of
(Standard_Boolean
, Loc
),
13346 New_Occurrence_Of
(Shortcut_Ent
, Loc
)));
13348 Append_To
(Actlist
,
13349 Make_Implicit_If_Statement
(Right
,
13350 Condition
=> Make_Test_Expr
(Right
),
13351 Then_Statements
=> New_List
(
13352 Make_Assignment_Statement
(LocR
,
13353 Name
=> New_Occurrence_Of
(Op_Var
, LocR
),
13356 (Boolean_Literals
(not Shortcut_Value
), LocR
)))));
13359 Make_Implicit_If_Statement
(Left
,
13360 Condition
=> Make_Test_Expr
(Left
),
13361 Then_Statements
=> Actlist
));
13363 Rewrite
(N
, New_Occurrence_Of
(Op_Var
, Loc
));
13364 Analyze_And_Resolve
(N
, Standard_Boolean
);
13366 -- The new approach (the default) is to use an
13367 -- Expression_With_Actions node for the right operand of the
13368 -- short-circuit form. Note that this solves the traceability
13369 -- problems for coverage analysis.
13373 Make_Expression_With_Actions
(LocR
,
13374 Expression
=> Relocate_Node
(Right
),
13375 Actions
=> Actlist
));
13377 Set_Actions
(N
, No_List
);
13378 Analyze_And_Resolve
(Right
, Standard_Boolean
);
13381 Adjust_Result_Type
(N
, Typ
);
13385 -- No actions present, check for cases of right argument True/False
13387 if Compile_Time_Known_Value
(Right
) then
13389 -- Mark SCO for left condition as compile time known
13391 if Generate_SCO
and then Comes_From_Source
(Right
) then
13392 Set_SCO_Condition
(Right
, Expr_Value_E
(Right
) = Standard_True
);
13395 -- Change (Left and then True), (Left or else False) to Left. Note
13396 -- that we know there are no actions associated with the right
13397 -- operand, since we just checked for this case above.
13399 if Expr_Value_E
(Right
) /= Shortcut_Ent
then
13402 -- Change (Left and then False), (Left or else True) to Right,
13403 -- making sure to preserve any side effects associated with the Left
13407 Remove_Side_Effects
(Left
);
13408 Rewrite
(N
, New_Occurrence_Of
(Shortcut_Ent
, Loc
));
13412 Adjust_Result_Type
(N
, Typ
);
13413 end Expand_Short_Circuit_Operator
;
13415 ------------------------------------
13416 -- Fixup_Universal_Fixed_Operation --
13417 -------------------------------------
13419 procedure Fixup_Universal_Fixed_Operation
(N
: Node_Id
) is
13420 Conv
: constant Node_Id
:= Parent
(N
);
13423 -- We must have a type conversion immediately above us
13425 pragma Assert
(Nkind
(Conv
) = N_Type_Conversion
);
13427 -- Normally the type conversion gives our target type. The exception
13428 -- occurs in the case of the Round attribute, where the conversion
13429 -- will be to universal real, and our real type comes from the Round
13430 -- attribute (as well as an indication that we must round the result)
13432 if Etype
(Conv
) = Universal_Real
13433 and then Nkind
(Parent
(Conv
)) = N_Attribute_Reference
13434 and then Attribute_Name
(Parent
(Conv
)) = Name_Round
13436 Set_Etype
(N
, Base_Type
(Etype
(Parent
(Conv
))));
13437 Set_Rounded_Result
(N
);
13439 -- Normal case where type comes from conversion above us
13442 Set_Etype
(N
, Base_Type
(Etype
(Conv
)));
13444 end Fixup_Universal_Fixed_Operation
;
13446 ------------------------
13447 -- Get_Size_For_Range --
13448 ------------------------
13450 function Get_Size_For_Range
(Lo
, Hi
: Uint
) return Uint
is
13452 function Is_OK_For_Range
(Siz
: Uint
) return Boolean;
13453 -- Return True if a signed integer with given size can cover Lo .. Hi
13455 --------------------------
13456 -- Is_OK_For_Range --
13457 --------------------------
13459 function Is_OK_For_Range
(Siz
: Uint
) return Boolean is
13460 B
: constant Uint
:= Uint_2
** (Siz
- 1);
13463 -- Test B = 2 ** (size - 1) (can accommodate -B .. +(B - 1))
13465 return Lo
>= -B
and then Hi
>= -B
and then Lo
< B
and then Hi
< B
;
13466 end Is_OK_For_Range
;
13469 -- This is (almost always) the size of Integer
13471 if Is_OK_For_Range
(Uint_32
) then
13476 elsif Is_OK_For_Range
(Uint_63
) then
13479 -- This is (almost always) the size of Long_Long_Integer
13481 elsif Is_OK_For_Range
(Uint_64
) then
13486 elsif Is_OK_For_Range
(Uint_127
) then
13492 end Get_Size_For_Range
;
13494 -------------------------------
13495 -- Insert_Dereference_Action --
13496 -------------------------------
13498 procedure Insert_Dereference_Action
(N
: Node_Id
) is
13499 function Is_Checked_Storage_Pool
(P
: Entity_Id
) return Boolean;
13500 -- Return true if type of P is derived from Checked_Pool;
13502 -----------------------------
13503 -- Is_Checked_Storage_Pool --
13504 -----------------------------
13506 function Is_Checked_Storage_Pool
(P
: Entity_Id
) return Boolean is
13515 while T
/= Etype
(T
) loop
13516 if Is_RTE
(T
, RE_Checked_Pool
) then
13524 end Is_Checked_Storage_Pool
;
13528 Context
: constant Node_Id
:= Parent
(N
);
13529 Ptr_Typ
: constant Entity_Id
:= Etype
(N
);
13530 Desig_Typ
: constant Entity_Id
:=
13531 Available_View
(Designated_Type
(Ptr_Typ
));
13532 Loc
: constant Source_Ptr
:= Sloc
(N
);
13533 Pool
: constant Entity_Id
:= Associated_Storage_Pool
(Ptr_Typ
);
13539 Size_Bits
: Node_Id
;
13542 -- Start of processing for Insert_Dereference_Action
13545 pragma Assert
(Nkind
(Context
) = N_Explicit_Dereference
);
13547 -- Do not re-expand a dereference which has already been processed by
13550 if Has_Dereference_Action
(Context
) then
13553 -- Do not perform this type of expansion for internally-generated
13556 elsif not Comes_From_Source
(Original_Node
(Context
)) then
13559 -- A dereference action is only applicable to objects which have been
13560 -- allocated on a checked pool.
13562 elsif not Is_Checked_Storage_Pool
(Pool
) then
13566 -- Extract the address of the dereferenced object. Generate:
13568 -- Addr : System.Address := <N>'Pool_Address;
13570 Addr
:= Make_Temporary
(Loc
, 'P');
13573 Make_Object_Declaration
(Loc
,
13574 Defining_Identifier
=> Addr
,
13575 Object_Definition
=>
13576 New_Occurrence_Of
(RTE
(RE_Address
), Loc
),
13578 Make_Attribute_Reference
(Loc
,
13579 Prefix
=> Duplicate_Subexpr_Move_Checks
(N
),
13580 Attribute_Name
=> Name_Pool_Address
)));
13582 -- Calculate the size of the dereferenced object. Generate:
13584 -- Size : Storage_Count := <N>.all'Size / Storage_Unit;
13587 Make_Explicit_Dereference
(Loc
,
13588 Prefix
=> Duplicate_Subexpr_Move_Checks
(N
));
13589 Set_Has_Dereference_Action
(Deref
);
13592 Make_Attribute_Reference
(Loc
,
13594 Attribute_Name
=> Name_Size
);
13596 -- Special case of an unconstrained array: need to add descriptor size
13598 if Is_Array_Type
(Desig_Typ
)
13599 and then not Is_Constrained
(First_Subtype
(Desig_Typ
))
13604 Make_Attribute_Reference
(Loc
,
13606 New_Occurrence_Of
(First_Subtype
(Desig_Typ
), Loc
),
13607 Attribute_Name
=> Name_Descriptor_Size
),
13608 Right_Opnd
=> Size_Bits
);
13611 Size
:= Make_Temporary
(Loc
, 'S');
13613 Make_Object_Declaration
(Loc
,
13614 Defining_Identifier
=> Size
,
13615 Object_Definition
=>
13616 New_Occurrence_Of
(RTE
(RE_Storage_Count
), Loc
),
13618 Make_Op_Divide
(Loc
,
13619 Left_Opnd
=> Size_Bits
,
13620 Right_Opnd
=> Make_Integer_Literal
(Loc
, System_Storage_Unit
))));
13622 -- Calculate the alignment of the dereferenced object. Generate:
13623 -- Alig : constant Storage_Count := <N>.all'Alignment;
13626 Make_Explicit_Dereference
(Loc
,
13627 Prefix
=> Duplicate_Subexpr_Move_Checks
(N
));
13628 Set_Has_Dereference_Action
(Deref
);
13630 Alig
:= Make_Temporary
(Loc
, 'A');
13632 Make_Object_Declaration
(Loc
,
13633 Defining_Identifier
=> Alig
,
13634 Object_Definition
=>
13635 New_Occurrence_Of
(RTE
(RE_Storage_Count
), Loc
),
13637 Make_Attribute_Reference
(Loc
,
13639 Attribute_Name
=> Name_Alignment
)));
13641 -- A dereference of a controlled object requires special processing. The
13642 -- finalization machinery requests additional space from the underlying
13643 -- pool to allocate and hide two pointers. As a result, a checked pool
13644 -- may mark the wrong memory as valid. Since checked pools do not have
13645 -- knowledge of hidden pointers, we have to bring the two pointers back
13646 -- in view in order to restore the original state of the object.
13648 -- The address manipulation is not performed for access types that are
13649 -- subject to pragma No_Heap_Finalization because the two pointers do
13650 -- not exist in the first place.
13652 if No_Heap_Finalization
(Ptr_Typ
) then
13655 elsif Needs_Finalization
(Desig_Typ
) then
13657 -- Adjust the address and size of the dereferenced object. Generate:
13658 -- Adjust_Controlled_Dereference (Addr, Size, Alig);
13661 Make_Procedure_Call_Statement
(Loc
,
13663 New_Occurrence_Of
(RTE
(RE_Adjust_Controlled_Dereference
), Loc
),
13664 Parameter_Associations
=> New_List
(
13665 New_Occurrence_Of
(Addr
, Loc
),
13666 New_Occurrence_Of
(Size
, Loc
),
13667 New_Occurrence_Of
(Alig
, Loc
)));
13669 -- Class-wide types complicate things because we cannot determine
13670 -- statically whether the actual object is truly controlled. We must
13671 -- generate a runtime check to detect this property. Generate:
13673 -- if Needs_Finalization (<N>.all'Tag) then
13677 if Is_Class_Wide_Type
(Desig_Typ
) then
13679 Make_Explicit_Dereference
(Loc
,
13680 Prefix
=> Duplicate_Subexpr_Move_Checks
(N
));
13681 Set_Has_Dereference_Action
(Deref
);
13684 Make_Implicit_If_Statement
(N
,
13686 Make_Function_Call
(Loc
,
13688 New_Occurrence_Of
(RTE
(RE_Needs_Finalization
), Loc
),
13689 Parameter_Associations
=> New_List
(
13690 Make_Attribute_Reference
(Loc
,
13692 Attribute_Name
=> Name_Tag
))),
13693 Then_Statements
=> New_List
(Stmt
));
13696 Insert_Action
(N
, Stmt
);
13700 -- Dereference (Pool, Addr, Size, Alig);
13703 Make_Procedure_Call_Statement
(Loc
,
13706 (Find_Prim_Op
(Etype
(Pool
), Name_Dereference
), Loc
),
13707 Parameter_Associations
=> New_List
(
13708 New_Occurrence_Of
(Pool
, Loc
),
13709 New_Occurrence_Of
(Addr
, Loc
),
13710 New_Occurrence_Of
(Size
, Loc
),
13711 New_Occurrence_Of
(Alig
, Loc
))));
13713 -- Mark the explicit dereference as processed to avoid potential
13714 -- infinite expansion.
13716 Set_Has_Dereference_Action
(Context
);
13719 when RE_Not_Available
=>
13721 end Insert_Dereference_Action
;
13723 --------------------------------
13724 -- Integer_Promotion_Possible --
13725 --------------------------------
13727 function Integer_Promotion_Possible
(N
: Node_Id
) return Boolean is
13728 Operand
: constant Node_Id
:= Expression
(N
);
13729 Operand_Type
: constant Entity_Id
:= Etype
(Operand
);
13730 Root_Operand_Type
: constant Entity_Id
:= Root_Type
(Operand_Type
);
13733 pragma Assert
(Nkind
(N
) = N_Type_Conversion
);
13737 -- We only do the transformation for source constructs. We assume
13738 -- that the expander knows what it is doing when it generates code.
13740 Comes_From_Source
(N
)
13742 -- If the operand type is Short_Integer or Short_Short_Integer,
13743 -- then we will promote to Integer, which is available on all
13744 -- targets, and is sufficient to ensure no intermediate overflow.
13745 -- Furthermore it is likely to be as efficient or more efficient
13746 -- than using the smaller type for the computation so we do this
13747 -- unconditionally.
13750 (Root_Operand_Type
= Base_Type
(Standard_Short_Integer
)
13752 Root_Operand_Type
= Base_Type
(Standard_Short_Short_Integer
))
13754 -- Test for interesting operation, which includes addition,
13755 -- division, exponentiation, multiplication, subtraction, absolute
13756 -- value and unary negation. Unary "+" is omitted since it is a
13757 -- no-op and thus can't overflow.
13759 and then Nkind
(Operand
) in
13760 N_Op_Abs | N_Op_Add | N_Op_Divide | N_Op_Expon |
13761 N_Op_Minus | N_Op_Multiply | N_Op_Subtract
;
13762 end Integer_Promotion_Possible
;
13764 ------------------------------
13765 -- Make_Array_Comparison_Op --
13766 ------------------------------
13768 -- This is a hand-coded expansion of the following generic function:
13771 -- type elem is (<>);
13772 -- type index is (<>);
13773 -- type a is array (index range <>) of elem;
13775 -- function Gnnn (X : a; Y: a) return boolean is
13776 -- J : index := Y'first;
13779 -- if X'length = 0 then
13782 -- elsif Y'length = 0 then
13786 -- for I in X'range loop
13787 -- if X (I) = Y (J) then
13788 -- if J = Y'last then
13791 -- J := index'succ (J);
13795 -- return X (I) > Y (J);
13799 -- return X'length > Y'length;
13803 -- Note that since we are essentially doing this expansion by hand, we
13804 -- do not need to generate an actual or formal generic part, just the
13805 -- instantiated function itself.
13807 function Make_Array_Comparison_Op
13809 Nod
: Node_Id
) return Node_Id
13811 Loc
: constant Source_Ptr
:= Sloc
(Nod
);
13813 X
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uX
);
13814 Y
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uY
);
13815 I
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uI
);
13816 J
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uJ
);
13818 Index
: constant Entity_Id
:= Base_Type
(Etype
(First_Index
(Typ
)));
13820 Loop_Statement
: Node_Id
;
13821 Loop_Body
: Node_Id
;
13823 Inner_If
: Node_Id
;
13824 Final_Expr
: Node_Id
;
13825 Func_Body
: Node_Id
;
13826 Func_Name
: Entity_Id
;
13832 -- if J = Y'last then
13835 -- J := index'succ (J);
13839 Make_Implicit_If_Statement
(Nod
,
13842 Left_Opnd
=> New_Occurrence_Of
(J
, Loc
),
13844 Make_Attribute_Reference
(Loc
,
13845 Prefix
=> New_Occurrence_Of
(Y
, Loc
),
13846 Attribute_Name
=> Name_Last
)),
13848 Then_Statements
=> New_List
(
13849 Make_Exit_Statement
(Loc
)),
13853 Make_Assignment_Statement
(Loc
,
13854 Name
=> New_Occurrence_Of
(J
, Loc
),
13856 Make_Attribute_Reference
(Loc
,
13857 Prefix
=> New_Occurrence_Of
(Index
, Loc
),
13858 Attribute_Name
=> Name_Succ
,
13859 Expressions
=> New_List
(New_Occurrence_Of
(J
, Loc
))))));
13861 -- if X (I) = Y (J) then
13864 -- return X (I) > Y (J);
13868 Make_Implicit_If_Statement
(Nod
,
13872 Make_Indexed_Component
(Loc
,
13873 Prefix
=> New_Occurrence_Of
(X
, Loc
),
13874 Expressions
=> New_List
(New_Occurrence_Of
(I
, Loc
))),
13877 Make_Indexed_Component
(Loc
,
13878 Prefix
=> New_Occurrence_Of
(Y
, Loc
),
13879 Expressions
=> New_List
(New_Occurrence_Of
(J
, Loc
)))),
13881 Then_Statements
=> New_List
(Inner_If
),
13883 Else_Statements
=> New_List
(
13884 Make_Simple_Return_Statement
(Loc
,
13888 Make_Indexed_Component
(Loc
,
13889 Prefix
=> New_Occurrence_Of
(X
, Loc
),
13890 Expressions
=> New_List
(New_Occurrence_Of
(I
, Loc
))),
13893 Make_Indexed_Component
(Loc
,
13894 Prefix
=> New_Occurrence_Of
(Y
, Loc
),
13895 Expressions
=> New_List
(
13896 New_Occurrence_Of
(J
, Loc
)))))));
13898 -- for I in X'range loop
13903 Make_Implicit_Loop_Statement
(Nod
,
13904 Identifier
=> Empty
,
13906 Iteration_Scheme
=>
13907 Make_Iteration_Scheme
(Loc
,
13908 Loop_Parameter_Specification
=>
13909 Make_Loop_Parameter_Specification
(Loc
,
13910 Defining_Identifier
=> I
,
13911 Discrete_Subtype_Definition
=>
13912 Make_Attribute_Reference
(Loc
,
13913 Prefix
=> New_Occurrence_Of
(X
, Loc
),
13914 Attribute_Name
=> Name_Range
))),
13916 Statements
=> New_List
(Loop_Body
));
13918 -- if X'length = 0 then
13920 -- elsif Y'length = 0 then
13923 -- for ... loop ... end loop;
13924 -- return X'length > Y'length;
13928 Make_Attribute_Reference
(Loc
,
13929 Prefix
=> New_Occurrence_Of
(X
, Loc
),
13930 Attribute_Name
=> Name_Length
);
13933 Make_Attribute_Reference
(Loc
,
13934 Prefix
=> New_Occurrence_Of
(Y
, Loc
),
13935 Attribute_Name
=> Name_Length
);
13939 Left_Opnd
=> Length1
,
13940 Right_Opnd
=> Length2
);
13943 Make_Implicit_If_Statement
(Nod
,
13947 Make_Attribute_Reference
(Loc
,
13948 Prefix
=> New_Occurrence_Of
(X
, Loc
),
13949 Attribute_Name
=> Name_Length
),
13951 Make_Integer_Literal
(Loc
, 0)),
13955 Make_Simple_Return_Statement
(Loc
,
13956 Expression
=> New_Occurrence_Of
(Standard_False
, Loc
))),
13958 Elsif_Parts
=> New_List
(
13959 Make_Elsif_Part
(Loc
,
13963 Make_Attribute_Reference
(Loc
,
13964 Prefix
=> New_Occurrence_Of
(Y
, Loc
),
13965 Attribute_Name
=> Name_Length
),
13967 Make_Integer_Literal
(Loc
, 0)),
13971 Make_Simple_Return_Statement
(Loc
,
13972 Expression
=> New_Occurrence_Of
(Standard_True
, Loc
))))),
13974 Else_Statements
=> New_List
(
13976 Make_Simple_Return_Statement
(Loc
,
13977 Expression
=> Final_Expr
)));
13981 Formals
:= New_List
(
13982 Make_Parameter_Specification
(Loc
,
13983 Defining_Identifier
=> X
,
13984 Parameter_Type
=> New_Occurrence_Of
(Typ
, Loc
)),
13986 Make_Parameter_Specification
(Loc
,
13987 Defining_Identifier
=> Y
,
13988 Parameter_Type
=> New_Occurrence_Of
(Typ
, Loc
)));
13990 -- function Gnnn (...) return boolean is
13991 -- J : index := Y'first;
13996 Func_Name
:= Make_Temporary
(Loc
, 'G');
13999 Make_Subprogram_Body
(Loc
,
14001 Make_Function_Specification
(Loc
,
14002 Defining_Unit_Name
=> Func_Name
,
14003 Parameter_Specifications
=> Formals
,
14004 Result_Definition
=> New_Occurrence_Of
(Standard_Boolean
, Loc
)),
14006 Declarations
=> New_List
(
14007 Make_Object_Declaration
(Loc
,
14008 Defining_Identifier
=> J
,
14009 Object_Definition
=> New_Occurrence_Of
(Index
, Loc
),
14011 Make_Attribute_Reference
(Loc
,
14012 Prefix
=> New_Occurrence_Of
(Y
, Loc
),
14013 Attribute_Name
=> Name_First
))),
14015 Handled_Statement_Sequence
=>
14016 Make_Handled_Sequence_Of_Statements
(Loc
,
14017 Statements
=> New_List
(If_Stat
)));
14020 end Make_Array_Comparison_Op
;
14022 ---------------------------
14023 -- Make_Boolean_Array_Op --
14024 ---------------------------
14026 -- For logical operations on boolean arrays, expand in line the following,
14027 -- replacing 'and' with 'or' or 'xor' where needed:
14029 -- function Annn (A : typ; B: typ) return typ is
14032 -- for J in A'range loop
14033 -- C (J) := A (J) op B (J);
14038 -- or in the case of Transform_Function_Array:
14040 -- procedure Annn (A : typ; B: typ; RESULT: out typ) is
14042 -- for J in A'range loop
14043 -- RESULT (J) := A (J) op B (J);
14047 -- Here typ is the boolean array type
14049 function Make_Boolean_Array_Op
14051 N
: Node_Id
) return Node_Id
14053 Loc
: constant Source_Ptr
:= Sloc
(N
);
14055 A
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uA
);
14056 B
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uB
);
14057 J
: constant Entity_Id
:= Make_Defining_Identifier
(Loc
, Name_uJ
);
14067 Func_Name
: Entity_Id
;
14068 Func_Body
: Node_Id
;
14069 Loop_Statement
: Node_Id
;
14072 if Transform_Function_Array
then
14073 C
:= Make_Defining_Identifier
(Loc
, Name_UP_RESULT
);
14075 C
:= Make_Defining_Identifier
(Loc
, Name_uC
);
14079 Make_Indexed_Component
(Loc
,
14080 Prefix
=> New_Occurrence_Of
(A
, Loc
),
14081 Expressions
=> New_List
(New_Occurrence_Of
(J
, Loc
)));
14084 Make_Indexed_Component
(Loc
,
14085 Prefix
=> New_Occurrence_Of
(B
, Loc
),
14086 Expressions
=> New_List
(New_Occurrence_Of
(J
, Loc
)));
14089 Make_Indexed_Component
(Loc
,
14090 Prefix
=> New_Occurrence_Of
(C
, Loc
),
14091 Expressions
=> New_List
(New_Occurrence_Of
(J
, Loc
)));
14093 if Nkind
(N
) = N_Op_And
then
14097 Right_Opnd
=> B_J
);
14099 elsif Nkind
(N
) = N_Op_Or
then
14103 Right_Opnd
=> B_J
);
14109 Right_Opnd
=> B_J
);
14113 Make_Implicit_Loop_Statement
(N
,
14114 Identifier
=> Empty
,
14116 Iteration_Scheme
=>
14117 Make_Iteration_Scheme
(Loc
,
14118 Loop_Parameter_Specification
=>
14119 Make_Loop_Parameter_Specification
(Loc
,
14120 Defining_Identifier
=> J
,
14121 Discrete_Subtype_Definition
=>
14122 Make_Attribute_Reference
(Loc
,
14123 Prefix
=> New_Occurrence_Of
(A
, Loc
),
14124 Attribute_Name
=> Name_Range
))),
14126 Statements
=> New_List
(
14127 Make_Assignment_Statement
(Loc
,
14129 Expression
=> Op
)));
14131 Formals
:= New_List
(
14132 Make_Parameter_Specification
(Loc
,
14133 Defining_Identifier
=> A
,
14134 Parameter_Type
=> New_Occurrence_Of
(Typ
, Loc
)),
14136 Make_Parameter_Specification
(Loc
,
14137 Defining_Identifier
=> B
,
14138 Parameter_Type
=> New_Occurrence_Of
(Typ
, Loc
)));
14140 if Transform_Function_Array
then
14141 Append_To
(Formals
,
14142 Make_Parameter_Specification
(Loc
,
14143 Defining_Identifier
=> C
,
14144 Out_Present
=> True,
14145 Parameter_Type
=> New_Occurrence_Of
(Typ
, Loc
)));
14148 Func_Name
:= Make_Temporary
(Loc
, 'A');
14149 Set_Is_Inlined
(Func_Name
);
14151 if Transform_Function_Array
then
14153 Make_Subprogram_Body
(Loc
,
14155 Make_Procedure_Specification
(Loc
,
14156 Defining_Unit_Name
=> Func_Name
,
14157 Parameter_Specifications
=> Formals
),
14159 Declarations
=> New_List
,
14161 Handled_Statement_Sequence
=>
14162 Make_Handled_Sequence_Of_Statements
(Loc
,
14163 Statements
=> New_List
(Loop_Statement
)));
14167 Make_Subprogram_Body
(Loc
,
14169 Make_Function_Specification
(Loc
,
14170 Defining_Unit_Name
=> Func_Name
,
14171 Parameter_Specifications
=> Formals
,
14172 Result_Definition
=> New_Occurrence_Of
(Typ
, Loc
)),
14174 Declarations
=> New_List
(
14175 Make_Object_Declaration
(Loc
,
14176 Defining_Identifier
=> C
,
14177 Object_Definition
=> New_Occurrence_Of
(Typ
, Loc
))),
14179 Handled_Statement_Sequence
=>
14180 Make_Handled_Sequence_Of_Statements
(Loc
,
14181 Statements
=> New_List
(
14183 Make_Simple_Return_Statement
(Loc
,
14184 Expression
=> New_Occurrence_Of
(C
, Loc
)))));
14188 end Make_Boolean_Array_Op
;
14190 -----------------------------------------
14191 -- Minimized_Eliminated_Overflow_Check --
14192 -----------------------------------------
14194 function Minimized_Eliminated_Overflow_Check
(N
: Node_Id
) return Boolean is
14196 -- The MINIMIZED mode operates in Long_Long_Integer so we cannot use it
14197 -- if the type of the expression is already larger.
14200 Is_Signed_Integer_Type
(Etype
(N
))
14201 and then Overflow_Check_Mode
in Minimized_Or_Eliminated
14202 and then not (Overflow_Check_Mode
= Minimized
14204 Esize
(Etype
(N
)) > Standard_Long_Long_Integer_Size
);
14205 end Minimized_Eliminated_Overflow_Check
;
14207 ----------------------------
14208 -- Narrow_Large_Operation --
14209 ----------------------------
14211 procedure Narrow_Large_Operation
(N
: Node_Id
) is
14212 Kind
: constant Node_Kind
:= Nkind
(N
);
14213 In_Rng
: constant Boolean := Kind
= N_In
;
14214 Binary
: constant Boolean := Kind
in N_Binary_Op
or else In_Rng
;
14215 Compar
: constant Boolean := Kind
in N_Op_Compare
or else In_Rng
;
14216 R
: constant Node_Id
:= Right_Opnd
(N
);
14217 Typ
: constant Entity_Id
:= Etype
(R
);
14218 Tsiz
: constant Uint
:= RM_Size
(Typ
);
14232 -- Start of processing for Narrow_Large_Operation
14235 -- First, determine the range of the left operand, if any
14238 L
:= Left_Opnd
(N
);
14239 Determine_Range
(L
, OK
, Llo
, Lhi
, Assume_Valid
=> True);
14250 -- Second, determine the range of the right operand, which can itself
14251 -- be a range, in which case we take the lower bound of the low bound
14252 -- and the upper bound of the high bound.
14260 (Low_Bound
(R
), OK
, Rlo
, Zhi
, Assume_Valid
=> True);
14266 (High_Bound
(R
), OK
, Zlo
, Rhi
, Assume_Valid
=> True);
14273 Determine_Range
(R
, OK
, Rlo
, Rhi
, Assume_Valid
=> True);
14279 -- Then compute a size suitable for each range
14282 Lsiz
:= Get_Size_For_Range
(Llo
, Lhi
);
14287 Rsiz
:= Get_Size_For_Range
(Rlo
, Rhi
);
14289 -- Now compute the size of the narrower type
14292 -- The type must be able to accommodate the operands
14294 Nsiz
:= UI_Max
(Lsiz
, Rsiz
);
14297 -- The type must be able to accommodate the operand(s) and result.
14299 -- Note that Determine_Range typically does not report the bounds of
14300 -- the value as being larger than those of the base type, which means
14301 -- that it does not report overflow (see also Enable_Overflow_Check).
14303 Determine_Range
(N
, OK
, Nlo
, Nhi
, Assume_Valid
=> True);
14308 -- Therefore, if Nsiz is not lower than the size of the original type
14309 -- here, we cannot be sure that the operation does not overflow.
14311 Nsiz
:= Get_Size_For_Range
(Nlo
, Nhi
);
14312 Nsiz
:= UI_Max
(Nsiz
, Lsiz
);
14313 Nsiz
:= UI_Max
(Nsiz
, Rsiz
);
14316 -- If the size is not lower than the size of the original type, then
14317 -- there is no point in changing the type, except in the case where
14318 -- we can remove a conversion to the original type from an operand.
14321 and then not (Binary
14322 and then Nkind
(L
) = N_Type_Conversion
14323 and then Entity
(Subtype_Mark
(L
)) = Typ
)
14324 and then not (Nkind
(R
) = N_Type_Conversion
14325 and then Entity
(Subtype_Mark
(R
)) = Typ
)
14330 -- Now pick the narrower type according to the size. We use the base
14331 -- type instead of the first subtype because operations are done in
14332 -- the base type, so this avoids the need for useless conversions.
14334 if Nsiz
<= System_Max_Integer_Size
then
14335 Ntyp
:= Etype
(Integer_Type_For
(Nsiz
, Uns
=> False));
14340 -- Finally, rewrite the operation in the narrower type
14342 Nop
:= New_Op_Node
(Kind
, Sloc
(N
));
14345 Set_Left_Opnd
(Nop
, Convert_To
(Ntyp
, L
));
14349 Set_Right_Opnd
(Nop
,
14350 Make_Range
(Sloc
(N
),
14351 Convert_To
(Ntyp
, Low_Bound
(R
)),
14352 Convert_To
(Ntyp
, High_Bound
(R
))));
14354 Set_Right_Opnd
(Nop
, Convert_To
(Ntyp
, R
));
14360 -- Analyze it with the comparison type and checks suppressed since
14361 -- the conversions of the operands cannot overflow.
14363 Analyze_And_Resolve
14364 (N
, Etype
(Original_Node
(N
)), Suppress
=> Overflow_Check
);
14367 -- Analyze it with the narrower type and checks suppressed, but only
14368 -- when we are sure that the operation does not overflow, see above.
14370 if Nsiz
< Tsiz
then
14371 Analyze_And_Resolve
(N
, Ntyp
, Suppress
=> Overflow_Check
);
14373 Analyze_And_Resolve
(N
, Ntyp
);
14376 -- Put back a conversion to the original type
14378 Convert_To_And_Rewrite
(Typ
, N
);
14380 end Narrow_Large_Operation
;
14382 --------------------------------
14383 -- Optimize_Length_Comparison --
14384 --------------------------------
14386 procedure Optimize_Length_Comparison
(N
: Node_Id
) is
14387 Loc
: constant Source_Ptr
:= Sloc
(N
);
14388 Typ
: constant Entity_Id
:= Etype
(N
);
14393 -- First and Last attribute reference nodes, which end up as left and
14394 -- right operands of the optimized result.
14397 -- True for comparison operand of zero
14399 Maybe_Superflat
: Boolean;
14400 -- True if we may be in the dynamic superflat case, i.e. Is_Zero is set
14401 -- to false but the comparison operand can be zero at run time. In this
14402 -- case, we normally cannot do anything because the canonical formula of
14403 -- the length is not valid, but there is one exception: when the operand
14404 -- is itself the length of an array with the same bounds as the array on
14405 -- the LHS, we can entirely optimize away the comparison.
14408 -- Comparison operand, set only if Is_Zero is false
14410 Ent
: array (Pos
range 1 .. 2) of Entity_Id
:= (Empty
, Empty
);
14411 -- Entities whose length is being compared
14413 Index
: array (Pos
range 1 .. 2) of Node_Id
:= (Empty
, Empty
);
14414 -- Integer_Literal nodes for length attribute expressions, or Empty
14415 -- if there is no such expression present.
14417 Op
: Node_Kind
:= Nkind
(N
);
14418 -- Kind of comparison operator, gets flipped if operands backwards
14420 function Convert_To_Long_Long_Integer
(N
: Node_Id
) return Node_Id
;
14421 -- Given a discrete expression, returns a Long_Long_Integer typed
14422 -- expression representing the underlying value of the expression.
14423 -- This is done with an unchecked conversion to Long_Long_Integer.
14424 -- We use unchecked conversion to handle the enumeration type case.
14426 function Is_Entity_Length
(N
: Node_Id
; Num
: Pos
) return Boolean;
14427 -- Tests if N is a length attribute applied to a simple entity. If so,
14428 -- returns True, and sets Ent to the entity, and Index to the integer
14429 -- literal provided as an attribute expression, or to Empty if none.
14430 -- Num is the index designating the relevant slot in Ent and Index.
14431 -- Also returns True if the expression is a generated type conversion
14432 -- whose expression is of the desired form. This latter case arises
14433 -- when Apply_Universal_Integer_Attribute_Check installs a conversion
14434 -- to check for being in range, which is not needed in this context.
14435 -- Returns False if neither condition holds.
14437 function Is_Optimizable
(N
: Node_Id
) return Boolean;
14438 -- Tests N to see if it is an optimizable comparison value (defined as
14439 -- constant zero or one, or something else where the value is known to
14440 -- be nonnegative and in the 32-bit range and where the corresponding
14441 -- Length value is also known to be 32 bits). If result is true, sets
14442 -- Is_Zero, Maybe_Superflat and Comp accordingly.
14444 procedure Rewrite_For_Equal_Lengths
;
14445 -- Rewrite the comparison of two equal lengths into either True or False
14447 ----------------------------------
14448 -- Convert_To_Long_Long_Integer --
14449 ----------------------------------
14451 function Convert_To_Long_Long_Integer
(N
: Node_Id
) return Node_Id
is
14453 return Unchecked_Convert_To
(Standard_Long_Long_Integer
, N
);
14454 end Convert_To_Long_Long_Integer
;
14456 ----------------------
14457 -- Is_Entity_Length --
14458 ----------------------
14460 function Is_Entity_Length
(N
: Node_Id
; Num
: Pos
) return Boolean is
14462 if Nkind
(N
) = N_Attribute_Reference
14463 and then Attribute_Name
(N
) = Name_Length
14464 and then Is_Entity_Name
(Prefix
(N
))
14466 Ent
(Num
) := Entity
(Prefix
(N
));
14468 if Present
(Expressions
(N
)) then
14469 Index
(Num
) := First
(Expressions
(N
));
14471 Index
(Num
) := Empty
;
14476 elsif Nkind
(N
) = N_Type_Conversion
14477 and then not Comes_From_Source
(N
)
14479 return Is_Entity_Length
(Expression
(N
), Num
);
14484 end Is_Entity_Length
;
14486 --------------------
14487 -- Is_Optimizable --
14488 --------------------
14490 function Is_Optimizable
(N
: Node_Id
) return Boolean is
14500 if Compile_Time_Known_Value
(N
) then
14501 Val
:= Expr_Value
(N
);
14503 if Val
= Uint_0
then
14505 Maybe_Superflat
:= False;
14509 elsif Val
= Uint_1
then
14511 Maybe_Superflat
:= False;
14517 -- Here we have to make sure of being within a 32-bit range (take the
14518 -- full unsigned range so the length of 32-bit arrays is accepted).
14520 Determine_Range
(N
, OK
, Lo
, Hi
, Assume_Valid
=> True);
14523 or else Lo
< Uint_0
14524 or else Hi
> Uint_2
** 32
14529 Maybe_Superflat
:= (Lo
= Uint_0
);
14531 -- Tests if N is also a length attribute applied to a simple entity
14533 Dbl
:= Is_Entity_Length
(N
, 2);
14535 -- We can deal with the superflat case only if N is also a length
14537 if Maybe_Superflat
and then not Dbl
then
14541 -- Comparison value was within range, so now we must check the index
14542 -- value to make sure it is also within 32 bits.
14544 for K
in Pos
range 1 .. 2 loop
14545 Indx
:= First_Index
(Etype
(Ent
(K
)));
14547 if Present
(Index
(K
)) then
14548 for J
in 2 .. UI_To_Int
(Intval
(Index
(K
))) loop
14553 Ityp
:= Etype
(Indx
);
14555 if Esize
(Ityp
) > 32 then
14565 end Is_Optimizable
;
14567 -------------------------------
14568 -- Rewrite_For_Equal_Lengths --
14569 -------------------------------
14571 procedure Rewrite_For_Equal_Lengths
is
14580 New_Occurrence_Of
(Standard_True
, Sloc
(N
))));
14588 New_Occurrence_Of
(Standard_False
, Sloc
(N
))));
14591 raise Program_Error
;
14594 Analyze_And_Resolve
(N
, Typ
);
14595 end Rewrite_For_Equal_Lengths
;
14597 -- Start of processing for Optimize_Length_Comparison
14600 -- Nothing to do if not a comparison
14602 if Op
not in N_Op_Compare
then
14606 -- Nothing to do if special -gnatd.P debug flag set.
14608 if Debug_Flag_Dot_PP
then
14612 -- Ent'Length op 0/1
14614 if Is_Entity_Length
(Left_Opnd
(N
), 1)
14615 and then Is_Optimizable
(Right_Opnd
(N
))
14619 -- 0/1 op Ent'Length
14621 elsif Is_Entity_Length
(Right_Opnd
(N
), 1)
14622 and then Is_Optimizable
(Left_Opnd
(N
))
14624 -- Flip comparison to opposite sense
14627 when N_Op_Lt
=> Op
:= N_Op_Gt
;
14628 when N_Op_Le
=> Op
:= N_Op_Ge
;
14629 when N_Op_Gt
=> Op
:= N_Op_Lt
;
14630 when N_Op_Ge
=> Op
:= N_Op_Le
;
14631 when others => null;
14634 -- Else optimization not possible
14640 -- Fall through if we will do the optimization
14642 -- Cases to handle:
14644 -- X'Length = 0 => X'First > X'Last
14645 -- X'Length = 1 => X'First = X'Last
14646 -- X'Length = n => X'First + (n - 1) = X'Last
14648 -- X'Length /= 0 => X'First <= X'Last
14649 -- X'Length /= 1 => X'First /= X'Last
14650 -- X'Length /= n => X'First + (n - 1) /= X'Last
14652 -- X'Length >= 0 => always true, warn
14653 -- X'Length >= 1 => X'First <= X'Last
14654 -- X'Length >= n => X'First + (n - 1) <= X'Last
14656 -- X'Length > 0 => X'First <= X'Last
14657 -- X'Length > 1 => X'First < X'Last
14658 -- X'Length > n => X'First + (n - 1) < X'Last
14660 -- X'Length <= 0 => X'First > X'Last (warn, could be =)
14661 -- X'Length <= 1 => X'First >= X'Last
14662 -- X'Length <= n => X'First + (n - 1) >= X'Last
14664 -- X'Length < 0 => always false (warn)
14665 -- X'Length < 1 => X'First > X'Last
14666 -- X'Length < n => X'First + (n - 1) > X'Last
14668 -- Note: for the cases of n (not constant 0,1), we require that the
14669 -- corresponding index type be integer or shorter (i.e. not 64-bit),
14670 -- and the same for the comparison value. Then we do the comparison
14671 -- using 64-bit arithmetic (actually long long integer), so that we
14672 -- cannot have overflow intefering with the result.
14674 -- First deal with warning cases
14683 Convert_To
(Typ
, New_Occurrence_Of
(Standard_True
, Loc
)));
14684 Analyze_And_Resolve
(N
, Typ
);
14685 Warn_On_Known_Condition
(N
);
14692 Convert_To
(Typ
, New_Occurrence_Of
(Standard_False
, Loc
)));
14693 Analyze_And_Resolve
(N
, Typ
);
14694 Warn_On_Known_Condition
(N
);
14698 if Constant_Condition_Warnings
14699 and then Comes_From_Source
(Original_Node
(N
))
14701 Error_Msg_N
("could replace by ""'=""?c?", N
);
14711 -- Build the First reference we will use
14714 Make_Attribute_Reference
(Loc
,
14715 Prefix
=> New_Occurrence_Of
(Ent
(1), Loc
),
14716 Attribute_Name
=> Name_First
);
14718 if Present
(Index
(1)) then
14719 Set_Expressions
(Left
, New_List
(New_Copy
(Index
(1))));
14722 -- Build the Last reference we will use
14725 Make_Attribute_Reference
(Loc
,
14726 Prefix
=> New_Occurrence_Of
(Ent
(1), Loc
),
14727 Attribute_Name
=> Name_Last
);
14729 if Present
(Index
(1)) then
14730 Set_Expressions
(Right
, New_List
(New_Copy
(Index
(1))));
14733 -- If general value case, then do the addition of (n - 1), and
14734 -- also add the needed conversions to type Long_Long_Integer.
14736 -- If n = Y'Length, we rewrite X'First + (n - 1) op X'Last into:
14738 -- Y'Last + (X'First - Y'First) op X'Last
14740 -- in the hope that X'First - Y'First can be computed statically.
14742 if Present
(Comp
) then
14743 if Present
(Ent
(2)) then
14745 Y_First
: constant Node_Id
:=
14746 Make_Attribute_Reference
(Loc
,
14747 Prefix
=> New_Occurrence_Of
(Ent
(2), Loc
),
14748 Attribute_Name
=> Name_First
);
14749 Y_Last
: constant Node_Id
:=
14750 Make_Attribute_Reference
(Loc
,
14751 Prefix
=> New_Occurrence_Of
(Ent
(2), Loc
),
14752 Attribute_Name
=> Name_Last
);
14753 R
: Compare_Result
;
14756 if Present
(Index
(2)) then
14757 Set_Expressions
(Y_First
, New_List
(New_Copy
(Index
(2))));
14758 Set_Expressions
(Y_Last
, New_List
(New_Copy
(Index
(2))));
14764 -- If X'First = Y'First, simplify the above formula into a
14765 -- direct comparison of Y'Last and X'Last.
14767 R
:= Compile_Time_Compare
(Left
, Y_First
, Assume_Valid
=> True);
14773 R
:= Compile_Time_Compare
14774 (Right
, Y_Last
, Assume_Valid
=> True);
14776 -- If the pairs of attributes are equal, we are done
14779 Rewrite_For_Equal_Lengths
;
14783 -- If the base types are different, convert both operands to
14784 -- Long_Long_Integer, else compare them directly.
14786 if Base_Type
(Etype
(Right
)) /= Base_Type
(Etype
(Y_Last
))
14788 Left
:= Convert_To_Long_Long_Integer
(Y_Last
);
14794 -- Otherwise, use the above formula as-is
14800 Convert_To_Long_Long_Integer
(Y_Last
),
14802 Make_Op_Subtract
(Loc
,
14804 Convert_To_Long_Long_Integer
(Left
),
14806 Convert_To_Long_Long_Integer
(Y_First
)));
14810 -- General value case
14815 Left_Opnd
=> Convert_To_Long_Long_Integer
(Left
),
14817 Make_Op_Subtract
(Loc
,
14818 Left_Opnd
=> Convert_To_Long_Long_Integer
(Comp
),
14819 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1)));
14823 -- We cannot do anything in the superflat case past this point
14825 if Maybe_Superflat
then
14829 -- If general operand, convert Last reference to Long_Long_Integer
14831 if Present
(Comp
) then
14832 Right
:= Convert_To_Long_Long_Integer
(Right
);
14835 -- Check for cases to optimize
14837 -- X'Length = 0 => X'First > X'Last
14838 -- X'Length < 1 => X'First > X'Last
14839 -- X'Length < n => X'First + (n - 1) > X'Last
14841 if (Is_Zero
and then Op
= N_Op_Eq
)
14842 or else (not Is_Zero
and then Op
= N_Op_Lt
)
14847 Right_Opnd
=> Right
);
14849 -- X'Length = 1 => X'First = X'Last
14850 -- X'Length = n => X'First + (n - 1) = X'Last
14852 elsif not Is_Zero
and then Op
= N_Op_Eq
then
14856 Right_Opnd
=> Right
);
14858 -- X'Length /= 0 => X'First <= X'Last
14859 -- X'Length > 0 => X'First <= X'Last
14861 elsif Is_Zero
and (Op
= N_Op_Ne
or else Op
= N_Op_Gt
) then
14865 Right_Opnd
=> Right
);
14867 -- X'Length /= 1 => X'First /= X'Last
14868 -- X'Length /= n => X'First + (n - 1) /= X'Last
14870 elsif not Is_Zero
and then Op
= N_Op_Ne
then
14874 Right_Opnd
=> Right
);
14876 -- X'Length >= 1 => X'First <= X'Last
14877 -- X'Length >= n => X'First + (n - 1) <= X'Last
14879 elsif not Is_Zero
and then Op
= N_Op_Ge
then
14883 Right_Opnd
=> Right
);
14885 -- X'Length > 1 => X'First < X'Last
14886 -- X'Length > n => X'First + (n = 1) < X'Last
14888 elsif not Is_Zero
and then Op
= N_Op_Gt
then
14892 Right_Opnd
=> Right
);
14894 -- X'Length <= 1 => X'First >= X'Last
14895 -- X'Length <= n => X'First + (n - 1) >= X'Last
14897 elsif not Is_Zero
and then Op
= N_Op_Le
then
14901 Right_Opnd
=> Right
);
14903 -- Should not happen at this stage
14906 raise Program_Error
;
14909 -- Rewrite and finish up (we can suppress overflow checks, see above)
14911 Rewrite
(N
, Result
);
14912 Analyze_And_Resolve
(N
, Typ
, Suppress
=> Overflow_Check
);
14913 end Optimize_Length_Comparison
;
14915 --------------------------------
14916 -- Process_If_Case_Statements --
14917 --------------------------------
14919 procedure Process_If_Case_Statements
(N
: Node_Id
; Stmts
: List_Id
) is
14923 Decl
:= First
(Stmts
);
14924 while Present
(Decl
) loop
14925 if Nkind
(Decl
) = N_Object_Declaration
14926 and then Is_Finalizable_Transient
(Decl
, N
)
14928 Process_Transient_In_Expression
(Decl
, N
, Stmts
);
14933 end Process_If_Case_Statements
;
14935 -------------------------------------
14936 -- Process_Transient_In_Expression --
14937 -------------------------------------
14939 procedure Process_Transient_In_Expression
14940 (Obj_Decl
: Node_Id
;
14944 Loc
: constant Source_Ptr
:= Sloc
(Obj_Decl
);
14945 Obj_Id
: constant Entity_Id
:= Defining_Identifier
(Obj_Decl
);
14947 Hook_Context
: constant Node_Id
:= Find_Hook_Context
(Expr
);
14948 -- The node on which to insert the hook as an action. This is usually
14949 -- the innermost enclosing non-transient construct.
14951 Fin_Call
: Node_Id
;
14952 Hook_Assign
: Node_Id
;
14953 Hook_Clear
: Node_Id
;
14954 Hook_Decl
: Node_Id
;
14955 Hook_Insert
: Node_Id
;
14956 Ptr_Decl
: Node_Id
;
14958 Fin_Context
: Node_Id
;
14959 -- The node after which to insert the finalization actions of the
14960 -- transient object.
14963 pragma Assert
(Nkind
(Expr
) in N_Case_Expression
14964 | N_Expression_With_Actions
14965 | N_If_Expression
);
14967 -- When the context is a Boolean evaluation, all three nodes capture the
14968 -- result of their computation in a local temporary:
14971 -- Trans_Id : Ctrl_Typ := ...;
14972 -- Result : constant Boolean := ... Trans_Id ...;
14973 -- <finalize Trans_Id>
14976 -- As a result, the finalization of any transient objects can safely
14977 -- take place after the result capture.
14979 -- ??? could this be extended to elementary types?
14981 if Is_Boolean_Type
(Etype
(Expr
)) then
14982 Fin_Context
:= Last
(Stmts
);
14984 -- Otherwise the immediate context may not be safe enough to carry
14985 -- out transient object finalization due to aliasing and nesting of
14986 -- constructs. Insert calls to [Deep_]Finalize after the innermost
14987 -- enclosing non-transient construct.
14990 Fin_Context
:= Hook_Context
;
14993 -- Mark the transient object as successfully processed to avoid double
14996 Set_Is_Finalized_Transient
(Obj_Id
);
14998 -- Construct all the pieces necessary to hook and finalize a transient
15001 Build_Transient_Object_Statements
15002 (Obj_Decl
=> Obj_Decl
,
15003 Fin_Call
=> Fin_Call
,
15004 Hook_Assign
=> Hook_Assign
,
15005 Hook_Clear
=> Hook_Clear
,
15006 Hook_Decl
=> Hook_Decl
,
15007 Ptr_Decl
=> Ptr_Decl
,
15008 Finalize_Obj
=> False);
15010 -- Add the access type which provides a reference to the transient
15011 -- object. Generate:
15013 -- type Ptr_Typ is access all Desig_Typ;
15015 Insert_Action
(Hook_Context
, Ptr_Decl
);
15017 -- Add the temporary which acts as a hook to the transient object.
15020 -- Hook : Ptr_Id := null;
15022 Insert_Action
(Hook_Context
, Hook_Decl
);
15024 -- When the transient object is initialized by an aggregate, the hook
15025 -- must capture the object after the last aggregate assignment takes
15026 -- place. Only then is the object considered initialized. Generate:
15028 -- Hook := Ptr_Typ (Obj_Id);
15030 -- Hook := Obj_Id'Unrestricted_Access;
15032 if Ekind
(Obj_Id
) in E_Constant | E_Variable
15033 and then Present
(Last_Aggregate_Assignment
(Obj_Id
))
15035 Hook_Insert
:= Last_Aggregate_Assignment
(Obj_Id
);
15037 -- Otherwise the hook seizes the related object immediately
15040 Hook_Insert
:= Obj_Decl
;
15043 Insert_After_And_Analyze
(Hook_Insert
, Hook_Assign
);
15045 -- When the node is part of a return statement, there is no need to
15046 -- insert a finalization call, as the general finalization mechanism
15047 -- (see Build_Finalizer) would take care of the transient object on
15048 -- subprogram exit. Note that it would also be impossible to insert the
15049 -- finalization code after the return statement as this will render it
15052 if Nkind
(Fin_Context
) = N_Simple_Return_Statement
then
15055 -- Finalize the hook after the context has been evaluated. Generate:
15057 -- if Hook /= null then
15058 -- [Deep_]Finalize (Hook.all);
15062 -- Note that the value returned by Find_Hook_Context may be an operator
15063 -- node, which is not a list member. We must locate the proper node in
15064 -- in the tree after which to insert the finalization code.
15067 while not Is_List_Member
(Fin_Context
) loop
15068 Fin_Context
:= Parent
(Fin_Context
);
15071 pragma Assert
(Present
(Fin_Context
));
15073 Insert_Action_After
(Fin_Context
,
15074 Make_Implicit_If_Statement
(Obj_Decl
,
15078 New_Occurrence_Of
(Defining_Entity
(Hook_Decl
), Loc
),
15079 Right_Opnd
=> Make_Null
(Loc
)),
15081 Then_Statements
=> New_List
(
15085 end Process_Transient_In_Expression
;
15087 ------------------------
15088 -- Rewrite_Comparison --
15089 ------------------------
15091 procedure Rewrite_Comparison
(N
: Node_Id
) is
15092 Typ
: constant Entity_Id
:= Etype
(N
);
15094 False_Result
: Boolean;
15095 True_Result
: Boolean;
15098 if Nkind
(N
) = N_Type_Conversion
then
15099 Rewrite_Comparison
(Expression
(N
));
15102 elsif Nkind
(N
) not in N_Op_Compare
then
15106 -- If both operands are static, then the comparison has been already
15107 -- folded in evaluation.
15110 (not Is_Static_Expression
(Left_Opnd
(N
))
15112 not Is_Static_Expression
(Right_Opnd
(N
)));
15114 -- Determine the potential outcome of the comparison assuming that the
15115 -- operands are valid and emit a warning when the comparison evaluates
15116 -- to True or False only in the presence of invalid values.
15118 Warn_On_Constant_Valid_Condition
(N
);
15120 -- Determine the potential outcome of the comparison assuming that the
15121 -- operands are not valid.
15125 Assume_Valid
=> False,
15126 True_Result
=> True_Result
,
15127 False_Result
=> False_Result
);
15129 -- The outcome is a decisive False or True, rewrite the operator into a
15130 -- non-static literal.
15132 if False_Result
or True_Result
then
15135 New_Occurrence_Of
(Boolean_Literals
(True_Result
), Sloc
(N
))));
15137 Analyze_And_Resolve
(N
, Typ
);
15138 Set_Is_Static_Expression
(N
, False);
15139 Warn_On_Known_Condition
(N
);
15141 end Rewrite_Comparison
;
15143 ----------------------------
15144 -- Safe_In_Place_Array_Op --
15145 ----------------------------
15147 function Safe_In_Place_Array_Op
15150 Op2
: Node_Id
) return Boolean
15152 Target
: Entity_Id
;
15154 function Is_Safe_Operand
(Op
: Node_Id
) return Boolean;
15155 -- Operand is safe if it cannot overlap part of the target of the
15156 -- operation. If the operand and the target are identical, the operand
15157 -- is safe. The operand can be empty in the case of negation.
15159 function Is_Unaliased
(N
: Node_Id
) return Boolean;
15160 -- Check that N is a stand-alone entity
15166 function Is_Unaliased
(N
: Node_Id
) return Boolean is
15170 and then No
(Address_Clause
(Entity
(N
)))
15171 and then No
(Renamed_Object
(Entity
(N
)));
15174 ---------------------
15175 -- Is_Safe_Operand --
15176 ---------------------
15178 function Is_Safe_Operand
(Op
: Node_Id
) return Boolean is
15183 elsif Is_Entity_Name
(Op
) then
15184 return Is_Unaliased
(Op
);
15186 elsif Nkind
(Op
) in N_Indexed_Component | N_Selected_Component
then
15187 return Is_Unaliased
(Prefix
(Op
));
15189 elsif Nkind
(Op
) = N_Slice
then
15191 Is_Unaliased
(Prefix
(Op
))
15192 and then Entity
(Prefix
(Op
)) /= Target
;
15194 elsif Nkind
(Op
) = N_Op_Not
then
15195 return Is_Safe_Operand
(Right_Opnd
(Op
));
15200 end Is_Safe_Operand
;
15202 -- Start of processing for Safe_In_Place_Array_Op
15205 -- Skip this processing if the component size is different from system
15206 -- storage unit (since at least for NOT this would cause problems).
15208 if Component_Size
(Etype
(Lhs
)) /= System_Storage_Unit
then
15211 -- Cannot do in place stuff if non-standard Boolean representation
15213 elsif Has_Non_Standard_Rep
(Component_Type
(Etype
(Lhs
))) then
15216 elsif not Is_Unaliased
(Lhs
) then
15220 Target
:= Entity
(Lhs
);
15221 return Is_Safe_Operand
(Op1
) and then Is_Safe_Operand
(Op2
);
15223 end Safe_In_Place_Array_Op
;
15225 -----------------------
15226 -- Tagged_Membership --
15227 -----------------------
15229 -- There are two different cases to consider depending on whether the right
15230 -- operand is a class-wide type or not. If not we just compare the actual
15231 -- tag of the left expr to the target type tag:
15233 -- Left_Expr.Tag = Right_Type'Tag;
15235 -- If it is a class-wide type we use the RT function CW_Membership which is
15236 -- usually implemented by looking in the ancestor tables contained in the
15237 -- dispatch table pointed by Left_Expr.Tag for Typ'Tag
15239 -- In both cases if Left_Expr is an access type, we first check whether it
15242 -- Ada 2005 (AI-251): If it is a class-wide interface type we use the RT
15243 -- function IW_Membership which is usually implemented by looking in the
15244 -- table of abstract interface types plus the ancestor table contained in
15245 -- the dispatch table pointed by Left_Expr.Tag for Typ'Tag
15247 procedure Tagged_Membership
15249 SCIL_Node
: out Node_Id
;
15250 Result
: out Node_Id
)
15252 Left
: constant Node_Id
:= Left_Opnd
(N
);
15253 Right
: constant Node_Id
:= Right_Opnd
(N
);
15254 Loc
: constant Source_Ptr
:= Sloc
(N
);
15256 -- Handle entities from the limited view
15258 Orig_Right_Type
: constant Entity_Id
:= Available_View
(Etype
(Right
));
15260 Full_R_Typ
: Entity_Id
;
15261 Left_Type
: Entity_Id
:= Available_View
(Etype
(Left
));
15262 Right_Type
: Entity_Id
:= Orig_Right_Type
;
15266 SCIL_Node
:= Empty
;
15268 -- We have to examine the corresponding record type when dealing with
15269 -- protected types instead of the original, unexpanded, type.
15271 if Ekind
(Right_Type
) = E_Protected_Type
then
15272 Right_Type
:= Corresponding_Record_Type
(Right_Type
);
15275 if Ekind
(Left_Type
) = E_Protected_Type
then
15276 Left_Type
:= Corresponding_Record_Type
(Left_Type
);
15279 -- In the case where the type is an access type, the test is applied
15280 -- using the designated types (needed in Ada 2012 for implicit anonymous
15281 -- access conversions, for AI05-0149).
15283 if Is_Access_Type
(Right_Type
) then
15284 Left_Type
:= Designated_Type
(Left_Type
);
15285 Right_Type
:= Designated_Type
(Right_Type
);
15288 if Is_Class_Wide_Type
(Left_Type
) then
15289 Left_Type
:= Root_Type
(Left_Type
);
15292 if Is_Class_Wide_Type
(Right_Type
) then
15293 Full_R_Typ
:= Underlying_Type
(Root_Type
(Right_Type
));
15295 Full_R_Typ
:= Underlying_Type
(Right_Type
);
15299 Make_Selected_Component
(Loc
,
15300 Prefix
=> Relocate_Node
(Left
),
15302 New_Occurrence_Of
(First_Tag_Component
(Left_Type
), Loc
));
15304 if Is_Class_Wide_Type
(Right_Type
) then
15306 -- No need to issue a run-time check if we statically know that the
15307 -- result of this membership test is always true. For example,
15308 -- considering the following declarations:
15310 -- type Iface is interface;
15311 -- type T is tagged null record;
15312 -- type DT is new T and Iface with null record;
15317 -- These membership tests are always true:
15320 -- Obj2 in T'Class;
15321 -- Obj2 in Iface'Class;
15323 -- We do not need to handle cases where the membership is illegal.
15326 -- Obj1 in DT'Class; -- Compile time error
15327 -- Obj1 in Iface'Class; -- Compile time error
15329 if not Is_Interface
(Left_Type
)
15330 and then not Is_Class_Wide_Type
(Left_Type
)
15331 and then (Is_Ancestor
(Etype
(Right_Type
), Left_Type
,
15332 Use_Full_View
=> True)
15333 or else (Is_Interface
(Etype
(Right_Type
))
15334 and then Interface_Present_In_Ancestor
15336 Iface
=> Etype
(Right_Type
))))
15338 Result
:= New_Occurrence_Of
(Standard_True
, Loc
);
15342 -- Ada 2005 (AI-251): Class-wide applied to interfaces
15344 if Is_Interface
(Etype
(Class_Wide_Type
(Right_Type
)))
15346 -- Support to: "Iface_CW_Typ in Typ'Class"
15348 or else Is_Interface
(Left_Type
)
15350 -- Issue error if IW_Membership operation not available in a
15351 -- configurable run-time setting.
15353 if not RTE_Available
(RE_IW_Membership
) then
15355 ("dynamic membership test on interface types", N
);
15361 Make_Function_Call
(Loc
,
15362 Name
=> New_Occurrence_Of
(RTE
(RE_IW_Membership
), Loc
),
15363 Parameter_Associations
=> New_List
(
15364 Make_Attribute_Reference
(Loc
,
15366 Attribute_Name
=> Name_Address
),
15367 New_Occurrence_Of
(
15368 Node
(First_Elmt
(Access_Disp_Table
(Full_R_Typ
))),
15371 -- Ada 95: Normal case
15374 -- Issue error if CW_Membership operation not available in a
15375 -- configurable run-time setting.
15377 if not RTE_Available
(RE_CW_Membership
) then
15379 ("dynamic membership test on tagged types", N
);
15385 Make_Function_Call
(Loc
,
15386 Name
=> New_Occurrence_Of
(RTE
(RE_CW_Membership
), Loc
),
15387 Parameter_Associations
=> New_List
(
15389 New_Occurrence_Of
(
15390 Node
(First_Elmt
(Access_Disp_Table
(Full_R_Typ
))),
15393 -- Generate the SCIL node for this class-wide membership test.
15395 if Generate_SCIL
then
15396 SCIL_Node
:= Make_SCIL_Membership_Test
(Sloc
(N
));
15397 Set_SCIL_Entity
(SCIL_Node
, Etype
(Right_Type
));
15398 Set_SCIL_Tag_Value
(SCIL_Node
, Obj_Tag
);
15402 -- Right_Type is not a class-wide type
15405 -- No need to check the tag of the object if Right_Typ is abstract
15407 if Is_Abstract_Type
(Right_Type
) then
15408 Result
:= New_Occurrence_Of
(Standard_False
, Loc
);
15413 Left_Opnd
=> Obj_Tag
,
15416 (Node
(First_Elmt
(Access_Disp_Table
(Full_R_Typ
))), Loc
));
15420 -- if Left is an access object then generate test of the form:
15421 -- * if Right_Type excludes null: Left /= null and then ...
15422 -- * if Right_Type includes null: Left = null or else ...
15424 if Is_Access_Type
(Orig_Right_Type
) then
15425 if Can_Never_Be_Null
(Orig_Right_Type
) then
15426 Result
:= Make_And_Then
(Loc
,
15430 Right_Opnd
=> Make_Null
(Loc
)),
15431 Right_Opnd
=> Result
);
15434 Result
:= Make_Or_Else
(Loc
,
15438 Right_Opnd
=> Make_Null
(Loc
)),
15439 Right_Opnd
=> Result
);
15442 end Tagged_Membership
;
15444 ------------------------------
15445 -- Unary_Op_Validity_Checks --
15446 ------------------------------
15448 procedure Unary_Op_Validity_Checks
(N
: Node_Id
) is
15450 if Validity_Checks_On
and Validity_Check_Operands
then
15451 Ensure_Valid
(Right_Opnd
(N
));
15453 end Unary_Op_Validity_Checks
;