| ------------------------------------------------------------------------------ |
| -- -- |
| -- GNAT COMPILER COMPONENTS -- |
| -- -- |
| -- E X P _ C H 4 -- |
| -- -- |
| -- B o d y -- |
| -- -- |
| -- Copyright (C) 1992-2022, Free Software Foundation, Inc. -- |
| -- -- |
| -- GNAT is free software; you can redistribute it and/or modify it under -- |
| -- terms of the GNU General Public License as published by the Free Soft- -- |
| -- ware Foundation; either version 3, or (at your option) any later ver- -- |
| -- sion. GNAT is distributed in the hope that it will be useful, but WITH- -- |
| -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY -- |
| -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License -- |
| -- for more details. You should have received a copy of the GNU General -- |
| -- Public License distributed with GNAT; see file COPYING3. If not, go to -- |
| -- http://www.gnu.org/licenses for a complete copy of the license. -- |
| -- -- |
| -- GNAT was originally developed by the GNAT team at New York University. -- |
| -- Extensive contributions were provided by Ada Core Technologies Inc. -- |
| -- -- |
| ------------------------------------------------------------------------------ |
| |
| with Aspects; use Aspects; |
| with Atree; use Atree; |
| with Checks; use Checks; |
| with Debug; use Debug; |
| with Einfo; use Einfo; |
| with Einfo.Entities; use Einfo.Entities; |
| with Einfo.Utils; use Einfo.Utils; |
| with Elists; use Elists; |
| with Errout; use Errout; |
| with Exp_Aggr; use Exp_Aggr; |
| with Exp_Atag; use Exp_Atag; |
| with Exp_Ch3; use Exp_Ch3; |
| with Exp_Ch6; use Exp_Ch6; |
| with Exp_Ch7; use Exp_Ch7; |
| with Exp_Ch9; use Exp_Ch9; |
| with Exp_Disp; use Exp_Disp; |
| with Exp_Fixd; use Exp_Fixd; |
| with Exp_Intr; use Exp_Intr; |
| with Exp_Pakd; use Exp_Pakd; |
| with Exp_Tss; use Exp_Tss; |
| with Exp_Util; use Exp_Util; |
| with Freeze; use Freeze; |
| with Inline; use Inline; |
| with Namet; use Namet; |
| with Nlists; use Nlists; |
| with Nmake; use Nmake; |
| with Opt; use Opt; |
| with Par_SCO; use Par_SCO; |
| with Restrict; use Restrict; |
| with Rident; use Rident; |
| with Rtsfind; use Rtsfind; |
| with Sem; use Sem; |
| with Sem_Aux; use Sem_Aux; |
| with Sem_Cat; use Sem_Cat; |
| with Sem_Ch3; use Sem_Ch3; |
| with Sem_Ch13; use Sem_Ch13; |
| with Sem_Eval; use Sem_Eval; |
| with Sem_Res; use Sem_Res; |
| with Sem_Type; use Sem_Type; |
| with Sem_Util; use Sem_Util; |
| with Sem_Warn; use Sem_Warn; |
| with Sinfo; use Sinfo; |
| with Sinfo.Nodes; use Sinfo.Nodes; |
| with Sinfo.Utils; use Sinfo.Utils; |
| with Snames; use Snames; |
| with Stand; use Stand; |
| with SCIL_LL; use SCIL_LL; |
| with Targparm; use Targparm; |
| with Tbuild; use Tbuild; |
| with Ttypes; use Ttypes; |
| with Uintp; use Uintp; |
| with Urealp; use Urealp; |
| with Validsw; use Validsw; |
| with Warnsw; use Warnsw; |
| |
| package body Exp_Ch4 is |
| |
| ----------------------- |
| -- Local Subprograms -- |
| ----------------------- |
| |
| procedure Binary_Op_Validity_Checks (N : Node_Id); |
| pragma Inline (Binary_Op_Validity_Checks); |
| -- Performs validity checks for a binary operator |
| |
| procedure Build_Boolean_Array_Proc_Call |
| (N : Node_Id; |
| Op1 : Node_Id; |
| Op2 : Node_Id); |
| -- If a boolean array assignment can be done in place, build call to |
| -- corresponding library procedure. |
| |
| procedure Displace_Allocator_Pointer (N : Node_Id); |
| -- Ada 2005 (AI-251): Subsidiary procedure to Expand_N_Allocator and |
| -- Expand_Allocator_Expression. Allocating class-wide interface objects |
| -- this routine displaces the pointer to the allocated object to reference |
| -- the component referencing the corresponding secondary dispatch table. |
| |
| procedure Expand_Allocator_Expression (N : Node_Id); |
| -- Subsidiary to Expand_N_Allocator, for the case when the expression |
| -- is a qualified expression. |
| |
| procedure Expand_Array_Comparison (N : Node_Id); |
| -- This routine handles expansion of the comparison operators (N_Op_Lt, |
| -- N_Op_Le, N_Op_Gt, N_Op_Ge) when operating on an array type. The basic |
| -- code for these operators is similar, differing only in the details of |
| -- the actual comparison call that is made. Special processing (call a |
| -- run-time routine) |
| |
| function Expand_Array_Equality |
| (Nod : Node_Id; |
| Lhs : Node_Id; |
| Rhs : Node_Id; |
| Bodies : List_Id; |
| Typ : Entity_Id) return Node_Id; |
| -- Expand an array equality into a call to a function implementing this |
| -- equality, and a call to it. Loc is the location for the generated nodes. |
| -- Lhs and Rhs are the array expressions to be compared. Bodies is a list |
| -- on which to attach bodies of local functions that are created in the |
| -- process. It is the responsibility of the caller to insert those bodies |
| -- at the right place. Nod provides the Sloc value for the generated code. |
| -- Normally the types used for the generated equality routine are taken |
| -- from Lhs and Rhs. However, in some situations of generated code, the |
| -- Etype fields of Lhs and Rhs are not set yet. In such cases, Typ supplies |
| -- the type to be used for the formal parameters. |
| |
| procedure Expand_Boolean_Operator (N : Node_Id); |
| -- Common expansion processing for Boolean operators (And, Or, Xor) for the |
| -- case of array type arguments. |
| |
| procedure Expand_Nonbinary_Modular_Op (N : Node_Id); |
| -- When generating C code, convert nonbinary modular arithmetic operations |
| -- into code that relies on the front-end expansion of operator Mod. No |
| -- expansion is performed if N is not a nonbinary modular operand. |
| |
| procedure Expand_Short_Circuit_Operator (N : Node_Id); |
| -- Common expansion processing for short-circuit boolean operators |
| |
| procedure Expand_Compare_Minimize_Eliminate_Overflow (N : Node_Id); |
| -- Deal with comparison in MINIMIZED/ELIMINATED overflow mode. This is |
| -- where we allow comparison of "out of range" values. |
| |
| function Expand_Composite_Equality |
| (Nod : Node_Id; |
| Typ : Entity_Id; |
| Lhs : Node_Id; |
| Rhs : Node_Id) return Node_Id; |
| -- Local recursive function used to expand equality for nested composite |
| -- types. Used by Expand_Record/Array_Equality. Nod provides the Sloc value |
| -- for generated code. Lhs and Rhs are the left and right sides for the |
| -- comparison, and Typ is the type of the objects to compare. |
| |
| procedure Expand_Concatenate (Cnode : Node_Id; Opnds : List_Id); |
| -- Routine to expand concatenation of a sequence of two or more operands |
| -- (in the list Operands) and replace node Cnode with the result of the |
| -- concatenation. The operands can be of any appropriate type, and can |
| -- include both arrays and singleton elements. |
| |
| procedure Expand_Membership_Minimize_Eliminate_Overflow (N : Node_Id); |
| -- N is an N_In membership test mode, with the overflow check mode set to |
| -- MINIMIZED or ELIMINATED, and the type of the left operand is a signed |
| -- integer type. This is a case where top level processing is required to |
| -- handle overflow checks in subtrees. |
| |
| procedure Fixup_Universal_Fixed_Operation (N : Node_Id); |
| -- N is a N_Op_Divide or N_Op_Multiply node whose result is universal |
| -- fixed. We do not have such a type at runtime, so the purpose of this |
| -- routine is to find the real type by looking up the tree. We also |
| -- determine if the operation must be rounded. |
| |
| function Get_Size_For_Range (Lo, Hi : Uint) return Uint; |
| -- Return the size of a small signed integer type covering Lo .. Hi, the |
| -- main goal being to return a size lower than that of standard types. |
| |
| procedure Insert_Dereference_Action (N : Node_Id); |
| -- N is an expression whose type is an access. When the type of the |
| -- associated storage pool is derived from Checked_Pool, generate a |
| -- call to the 'Dereference' primitive operation. |
| |
| function Make_Array_Comparison_Op |
| (Typ : Entity_Id; |
| Nod : Node_Id) return Node_Id; |
| -- Comparisons between arrays are expanded in line. This function produces |
| -- the body of the implementation of (a > b), where a and b are one- |
| -- dimensional arrays of some discrete type. The original node is then |
| -- expanded into the appropriate call to this function. Nod provides the |
| -- Sloc value for the generated code. |
| |
| function Make_Boolean_Array_Op |
| (Typ : Entity_Id; |
| N : Node_Id) return Node_Id; |
| -- Boolean operations on boolean arrays are expanded in line. This function |
| -- produce the body for the node N, which is (a and b), (a or b), or (a xor |
| -- b). It is used only the normal case and not the packed case. The type |
| -- involved, Typ, is the Boolean array type, and the logical operations in |
| -- the body are simple boolean operations. Note that Typ is always a |
| -- constrained type (the caller has ensured this by using |
| -- Convert_To_Actual_Subtype if necessary). |
| |
| function Minimized_Eliminated_Overflow_Check (N : Node_Id) return Boolean; |
| -- For signed arithmetic operations when the current overflow mode is |
| -- MINIMIZED or ELIMINATED, we must call Apply_Arithmetic_Overflow_Checks |
| -- as the first thing we do. We then return. We count on the recursive |
| -- apparatus for overflow checks to call us back with an equivalent |
| -- operation that is in CHECKED mode, avoiding a recursive entry into this |
| -- routine, and that is when we will proceed with the expansion of the |
| -- operator (e.g. converting X+0 to X, or X**2 to X*X). We cannot do |
| -- these optimizations without first making this check, since there may be |
| -- operands further down the tree that are relying on the recursive calls |
| -- triggered by the top level nodes to properly process overflow checking |
| -- and remaining expansion on these nodes. Note that this call back may be |
| -- skipped if the operation is done in Bignum mode but that's fine, since |
| -- the Bignum call takes care of everything. |
| |
| procedure Narrow_Large_Operation (N : Node_Id); |
| -- Try to compute the result of a large operation in a narrower type than |
| -- its nominal type. This is mainly aimed at getting rid of operations done |
| -- in Universal_Integer that can be generated for attributes. |
| |
| procedure Optimize_Length_Comparison (N : Node_Id); |
| -- Given an expression, if it is of the form X'Length op N (or the other |
| -- way round), where N is known at compile time to be 0 or 1, or something |
| -- else where the value is known to be nonnegative and in the 32-bit range, |
| -- and X is a simple entity, and op is a comparison operator, optimizes it |
| -- into a comparison of X'First and X'Last. |
| |
| procedure Process_If_Case_Statements (N : Node_Id; Stmts : List_Id); |
| -- Inspect and process statement list Stmt of if or case expression N for |
| -- transient objects. If such objects are found, the routine generates code |
| -- to clean them up when the context of the expression is evaluated. |
| |
| procedure Process_Transient_In_Expression |
| (Obj_Decl : Node_Id; |
| Expr : Node_Id; |
| Stmts : List_Id); |
| -- Subsidiary routine to the expansion of expression_with_actions, if and |
| -- case expressions. Generate all necessary code to finalize a transient |
| -- object when the enclosing context is elaborated or evaluated. Obj_Decl |
| -- denotes the declaration of the transient object, which is usually the |
| -- result of a controlled function call. Expr denotes the expression with |
| -- actions, if expression, or case expression node. Stmts denotes the |
| -- statement list which contains Decl, either at the top level or within a |
| -- nested construct. |
| |
| procedure Rewrite_Comparison (N : Node_Id); |
| -- If N is the node for a comparison whose outcome can be determined at |
| -- compile time, then the node N can be rewritten with True or False. If |
| -- the outcome cannot be determined at compile time, the call has no |
| -- effect. If N is a type conversion, then this processing is applied to |
| -- its expression. If N is neither comparison nor a type conversion, the |
| -- call has no effect. |
| |
| procedure Tagged_Membership |
| (N : Node_Id; |
| SCIL_Node : out Node_Id; |
| Result : out Node_Id); |
| -- Construct the expression corresponding to the tagged membership test. |
| -- Deals with a second operand being (or not) a class-wide type. |
| |
| function Safe_In_Place_Array_Op |
| (Lhs : Node_Id; |
| Op1 : Node_Id; |
| Op2 : Node_Id) return Boolean; |
| -- In the context of an assignment, where the right-hand side is a boolean |
| -- operation on arrays, check whether operation can be performed in place. |
| |
| procedure Unary_Op_Validity_Checks (N : Node_Id); |
| pragma Inline (Unary_Op_Validity_Checks); |
| -- Performs validity checks for a unary operator |
| |
| ------------------------------- |
| -- Binary_Op_Validity_Checks -- |
| ------------------------------- |
| |
| procedure Binary_Op_Validity_Checks (N : Node_Id) is |
| begin |
| if Validity_Checks_On and Validity_Check_Operands then |
| Ensure_Valid (Left_Opnd (N)); |
| Ensure_Valid (Right_Opnd (N)); |
| end if; |
| end Binary_Op_Validity_Checks; |
| |
| ------------------------------------ |
| -- Build_Boolean_Array_Proc_Call -- |
| ------------------------------------ |
| |
| procedure Build_Boolean_Array_Proc_Call |
| (N : Node_Id; |
| Op1 : Node_Id; |
| Op2 : Node_Id) |
| is |
| Loc : constant Source_Ptr := Sloc (N); |
| Kind : constant Node_Kind := Nkind (Expression (N)); |
| Target : constant Node_Id := |
| Make_Attribute_Reference (Loc, |
| Prefix => Name (N), |
| Attribute_Name => Name_Address); |
| |
| Arg1 : Node_Id := Op1; |
| Arg2 : Node_Id := Op2; |
| Call_Node : Node_Id; |
| Proc_Name : Entity_Id; |
| |
| begin |
| if Kind = N_Op_Not then |
| if Nkind (Op1) in N_Binary_Op then |
| |
| -- Use negated version of the binary operators |
| |
| if Nkind (Op1) = N_Op_And then |
| Proc_Name := RTE (RE_Vector_Nand); |
| |
| elsif Nkind (Op1) = N_Op_Or then |
| Proc_Name := RTE (RE_Vector_Nor); |
| |
| else pragma Assert (Nkind (Op1) = N_Op_Xor); |
| Proc_Name := RTE (RE_Vector_Xor); |
| end if; |
| |
| Call_Node := |
| Make_Procedure_Call_Statement (Loc, |
| Name => New_Occurrence_Of (Proc_Name, Loc), |
| |
| Parameter_Associations => New_List ( |
| Target, |
| Make_Attribute_Reference (Loc, |
| Prefix => Left_Opnd (Op1), |
| Attribute_Name => Name_Address), |
| |
| Make_Attribute_Reference (Loc, |
| Prefix => Right_Opnd (Op1), |
| Attribute_Name => Name_Address), |
| |
| Make_Attribute_Reference (Loc, |
| Prefix => Left_Opnd (Op1), |
| Attribute_Name => Name_Length))); |
| |
| else |
| Proc_Name := RTE (RE_Vector_Not); |
| |
| Call_Node := |
| Make_Procedure_Call_Statement (Loc, |
| Name => New_Occurrence_Of (Proc_Name, Loc), |
| Parameter_Associations => New_List ( |
| Target, |
| |
| Make_Attribute_Reference (Loc, |
| Prefix => Op1, |
| Attribute_Name => Name_Address), |
| |
| Make_Attribute_Reference (Loc, |
| Prefix => Op1, |
| Attribute_Name => Name_Length))); |
| end if; |
| |
| else |
| -- We use the following equivalences: |
| |
| -- (not X) or (not Y) = not (X and Y) = Nand (X, Y) |
| -- (not X) and (not Y) = not (X or Y) = Nor (X, Y) |
| -- (not X) xor (not Y) = X xor Y |
| -- X xor (not Y) = not (X xor Y) = Nxor (X, Y) |
| |
| if Nkind (Op1) = N_Op_Not then |
| Arg1 := Right_Opnd (Op1); |
| Arg2 := Right_Opnd (Op2); |
| |
| if Kind = N_Op_And then |
| Proc_Name := RTE (RE_Vector_Nor); |
| elsif Kind = N_Op_Or then |
| Proc_Name := RTE (RE_Vector_Nand); |
| else |
| Proc_Name := RTE (RE_Vector_Xor); |
| end if; |
| |
| else |
| if Kind = N_Op_And then |
| Proc_Name := RTE (RE_Vector_And); |
| elsif Kind = N_Op_Or then |
| Proc_Name := RTE (RE_Vector_Or); |
| elsif Nkind (Op2) = N_Op_Not then |
| Proc_Name := RTE (RE_Vector_Nxor); |
| Arg2 := Right_Opnd (Op2); |
| else |
| Proc_Name := RTE (RE_Vector_Xor); |
| end if; |
| end if; |
| |
| Call_Node := |
| Make_Procedure_Call_Statement (Loc, |
| Name => New_Occurrence_Of (Proc_Name, Loc), |
| Parameter_Associations => New_List ( |
| Target, |
| Make_Attribute_Reference (Loc, |
| Prefix => Arg1, |
| Attribute_Name => Name_Address), |
| Make_Attribute_Reference (Loc, |
| Prefix => Arg2, |
| Attribute_Name => Name_Address), |
| Make_Attribute_Reference (Loc, |
| Prefix => Arg1, |
| Attribute_Name => Name_Length))); |
| end if; |
| |
| Rewrite (N, Call_Node); |
| Analyze (N); |
| |
| exception |
| when RE_Not_Available => |
| return; |
| end Build_Boolean_Array_Proc_Call; |
| |
| ----------------------- |
| -- Build_Eq_Call -- |
| ----------------------- |
| |
| function Build_Eq_Call |
| (Typ : Entity_Id; |
| Loc : Source_Ptr; |
| Lhs : Node_Id; |
| Rhs : Node_Id) return Node_Id |
| is |
| Prim : Node_Id; |
| Prim_E : Elmt_Id; |
| |
| begin |
| Prim_E := First_Elmt (Collect_Primitive_Operations (Typ)); |
| while Present (Prim_E) loop |
| Prim := Node (Prim_E); |
| |
| -- Locate primitive equality with the right signature |
| |
| if Chars (Prim) = Name_Op_Eq |
| and then Etype (First_Formal (Prim)) = |
| Etype (Next_Formal (First_Formal (Prim))) |
| and then Etype (Prim) = Standard_Boolean |
| then |
| if Is_Abstract_Subprogram (Prim) then |
| return |
| Make_Raise_Program_Error (Loc, |
| Reason => PE_Explicit_Raise); |
| |
| else |
| return |
| Make_Function_Call (Loc, |
| Name => New_Occurrence_Of (Prim, Loc), |
| Parameter_Associations => New_List (Lhs, Rhs)); |
| end if; |
| end if; |
| |
| Next_Elmt (Prim_E); |
| end loop; |
| |
| -- If not found, predefined operation will be used |
| |
| return Empty; |
| end Build_Eq_Call; |
| |
| -------------------------------- |
| -- Displace_Allocator_Pointer -- |
| -------------------------------- |
| |
| procedure Displace_Allocator_Pointer (N : Node_Id) is |
| Loc : constant Source_Ptr := Sloc (N); |
| Orig_Node : constant Node_Id := Original_Node (N); |
| Dtyp : Entity_Id; |
| Etyp : Entity_Id; |
| PtrT : Entity_Id; |
| |
| begin |
| -- Do nothing in case of VM targets: the virtual machine will handle |
| -- interfaces directly. |
| |
| if not Tagged_Type_Expansion then |
| return; |
| end if; |
| |
| pragma Assert (Nkind (N) = N_Identifier |
| and then Nkind (Orig_Node) = N_Allocator); |
| |
| PtrT := Etype (Orig_Node); |
| Dtyp := Available_View (Designated_Type (PtrT)); |
| Etyp := Etype (Expression (Orig_Node)); |
| |
| if Is_Class_Wide_Type (Dtyp) and then Is_Interface (Dtyp) then |
| |
| -- If the type of the allocator expression is not an interface type |
| -- we can generate code to reference the record component containing |
| -- the pointer to the secondary dispatch table. |
| |
| if not Is_Interface (Etyp) then |
| declare |
| Saved_Typ : constant Entity_Id := Etype (Orig_Node); |
| |
| begin |
| -- 1) Get access to the allocated object |
| |
| Rewrite (N, |
| Make_Explicit_Dereference (Loc, Relocate_Node (N))); |
| Set_Etype (N, Etyp); |
| Set_Analyzed (N); |
| |
| -- 2) Add the conversion to displace the pointer to reference |
| -- the secondary dispatch table. |
| |
| Rewrite (N, Convert_To (Dtyp, Relocate_Node (N))); |
| Analyze_And_Resolve (N, Dtyp); |
| |
| -- 3) The 'access to the secondary dispatch table will be used |
| -- as the value returned by the allocator. |
| |
| Rewrite (N, |
| Make_Attribute_Reference (Loc, |
| Prefix => Relocate_Node (N), |
| Attribute_Name => Name_Access)); |
| Set_Etype (N, Saved_Typ); |
| Set_Analyzed (N); |
| end; |
| |
| -- If the type of the allocator expression is an interface type we |
| -- generate a run-time call to displace "this" to reference the |
| -- component containing the pointer to the secondary dispatch table |
| -- or else raise Constraint_Error if the actual object does not |
| -- implement the target interface. This case corresponds to the |
| -- following example: |
| |
| -- function Op (Obj : Iface_1'Class) return access Iface_2'Class is |
| -- begin |
| -- return new Iface_2'Class'(Obj); |
| -- end Op; |
| |
| else |
| Rewrite (N, |
| Unchecked_Convert_To (PtrT, |
| Make_Function_Call (Loc, |
| Name => New_Occurrence_Of (RTE (RE_Displace), Loc), |
| Parameter_Associations => New_List ( |
| Unchecked_Convert_To (RTE (RE_Address), |
| Relocate_Node (N)), |
| |
| New_Occurrence_Of |
| (Elists.Node |
| (First_Elmt |
| (Access_Disp_Table (Etype (Base_Type (Dtyp))))), |
| Loc))))); |
| Analyze_And_Resolve (N, PtrT); |
| end if; |
| end if; |
| end Displace_Allocator_Pointer; |
| |
| --------------------------------- |
| -- Expand_Allocator_Expression -- |
| --------------------------------- |
| |
| procedure Expand_Allocator_Expression (N : Node_Id) is |
| Loc : constant Source_Ptr := Sloc (N); |
| Exp : constant Node_Id := Expression (Expression (N)); |
| PtrT : constant Entity_Id := Etype (N); |
| DesigT : constant Entity_Id := Designated_Type (PtrT); |
| |
| procedure Apply_Accessibility_Check |
| (Ref : Node_Id; |
| Built_In_Place : Boolean := False); |
| -- Ada 2005 (AI-344): For an allocator with a class-wide designated |
| -- type, generate an accessibility check to verify that the level of the |
| -- type of the created object is not deeper than the level of the access |
| -- type. If the type of the qualified expression is class-wide, then |
| -- always generate the check (except in the case where it is known to be |
| -- unnecessary, see comment below). Otherwise, only generate the check |
| -- if the level of the qualified expression type is statically deeper |
| -- than the access type. |
| -- |
| -- Although the static accessibility will generally have been performed |
| -- as a legality check, it won't have been done in cases where the |
| -- allocator appears in generic body, so a run-time check is needed in |
| -- general. One special case is when the access type is declared in the |
| -- same scope as the class-wide allocator, in which case the check can |
| -- never fail, so it need not be generated. |
| -- |
| -- As an open issue, there seem to be cases where the static level |
| -- associated with the class-wide object's underlying type is not |
| -- sufficient to perform the proper accessibility check, such as for |
| -- allocators in nested subprograms or accept statements initialized by |
| -- class-wide formals when the actual originates outside at a deeper |
| -- static level. The nested subprogram case might require passing |
| -- accessibility levels along with class-wide parameters, and the task |
| -- case seems to be an actual gap in the language rules that needs to |
| -- be fixed by the ARG. ??? |
| |
| ------------------------------- |
| -- Apply_Accessibility_Check -- |
| ------------------------------- |
| |
| procedure Apply_Accessibility_Check |
| (Ref : Node_Id; |
| Built_In_Place : Boolean := False) |
| is |
| Pool_Id : constant Entity_Id := Associated_Storage_Pool (PtrT); |
| Cond : Node_Id; |
| Fin_Call : Node_Id; |
| Free_Stmt : Node_Id; |
| Obj_Ref : Node_Id; |
| Stmts : List_Id; |
| |
| begin |
| if Ada_Version >= Ada_2005 |
| and then Is_Class_Wide_Type (DesigT) |
| and then Tagged_Type_Expansion |
| and then not Scope_Suppress.Suppress (Accessibility_Check) |
| and then not No_Dynamic_Accessibility_Checks_Enabled (Ref) |
| and then |
| (Type_Access_Level (Etype (Exp)) > Type_Access_Level (PtrT) |
| or else |
| (Is_Class_Wide_Type (Etype (Exp)) |
| and then Scope (PtrT) /= Current_Scope)) |
| then |
| -- If the allocator was built in place, Ref is already a reference |
| -- to the access object initialized to the result of the allocator |
| -- (see Exp_Ch6.Make_Build_In_Place_Call_In_Allocator). We call |
| -- Remove_Side_Effects for cases where the build-in-place call may |
| -- still be the prefix of the reference (to avoid generating |
| -- duplicate calls). Otherwise, it is the entity associated with |
| -- the object containing the address of the allocated object. |
| |
| if Built_In_Place then |
| Remove_Side_Effects (Ref); |
| Obj_Ref := New_Copy_Tree (Ref); |
| else |
| Obj_Ref := New_Occurrence_Of (Ref, Loc); |
| end if; |
| |
| -- For access to interface types we must generate code to displace |
| -- the pointer to the base of the object since the subsequent code |
| -- references components located in the TSD of the object (which |
| -- is associated with the primary dispatch table --see a-tags.ads) |
| -- and also generates code invoking Free, which requires also a |
| -- reference to the base of the unallocated object. |
| |
| if Is_Interface (DesigT) and then Tagged_Type_Expansion then |
| Obj_Ref := |
| Unchecked_Convert_To (Etype (Obj_Ref), |
| Make_Function_Call (Loc, |
| Name => |
| New_Occurrence_Of (RTE (RE_Base_Address), Loc), |
| Parameter_Associations => New_List ( |
| Unchecked_Convert_To (RTE (RE_Address), |
| New_Copy_Tree (Obj_Ref))))); |
| end if; |
| |
| -- Step 1: Create the object clean up code |
| |
| Stmts := New_List; |
| |
| -- Deallocate the object if the accessibility check fails. This |
| -- is done only on targets or profiles that support deallocation. |
| |
| -- Free (Obj_Ref); |
| |
| if RTE_Available (RE_Free) then |
| Free_Stmt := Make_Free_Statement (Loc, New_Copy_Tree (Obj_Ref)); |
| Set_Storage_Pool (Free_Stmt, Pool_Id); |
| |
| Append_To (Stmts, Free_Stmt); |
| |
| -- The target or profile cannot deallocate objects |
| |
| else |
| Free_Stmt := Empty; |
| end if; |
| |
| -- Finalize the object if applicable. Generate: |
| |
| -- [Deep_]Finalize (Obj_Ref.all); |
| |
| if Needs_Finalization (DesigT) |
| and then not No_Heap_Finalization (PtrT) |
| then |
| Fin_Call := |
| Make_Final_Call |
| (Obj_Ref => |
| Make_Explicit_Dereference (Loc, New_Copy (Obj_Ref)), |
| Typ => DesigT); |
| |
| -- Guard against a missing [Deep_]Finalize when the designated |
| -- type was not properly frozen. |
| |
| if No (Fin_Call) then |
| Fin_Call := Make_Null_Statement (Loc); |
| end if; |
| |
| -- When the target or profile supports deallocation, wrap the |
| -- finalization call in a block to ensure proper deallocation |
| -- even if finalization fails. Generate: |
| |
| -- begin |
| -- <Fin_Call> |
| -- exception |
| -- when others => |
| -- <Free_Stmt> |
| -- raise; |
| -- end; |
| |
| if Present (Free_Stmt) then |
| Fin_Call := |
| Make_Block_Statement (Loc, |
| Handled_Statement_Sequence => |
| Make_Handled_Sequence_Of_Statements (Loc, |
| Statements => New_List (Fin_Call), |
| |
| Exception_Handlers => New_List ( |
| Make_Exception_Handler (Loc, |
| Exception_Choices => New_List ( |
| Make_Others_Choice (Loc)), |
| Statements => New_List ( |
| New_Copy_Tree (Free_Stmt), |
| Make_Raise_Statement (Loc)))))); |
| end if; |
| |
| Prepend_To (Stmts, Fin_Call); |
| end if; |
| |
| -- Signal the accessibility failure through a Program_Error |
| |
| Append_To (Stmts, |
| Make_Raise_Program_Error (Loc, |
| Reason => PE_Accessibility_Check_Failed)); |
| |
| -- Step 2: Create the accessibility comparison |
| |
| -- Generate: |
| -- Ref'Tag |
| |
| Obj_Ref := |
| Make_Attribute_Reference (Loc, |
| Prefix => Obj_Ref, |
| Attribute_Name => Name_Tag); |
| |
| -- For tagged types, determine the accessibility level by looking |
| -- at the type specific data of the dispatch table. Generate: |
| |
| -- Type_Specific_Data (Address (Ref'Tag)).Access_Level |
| |
| if Tagged_Type_Expansion then |
| Cond := Build_Get_Access_Level (Loc, Obj_Ref); |
| |
| -- Use a runtime call to determine the accessibility level when |
| -- compiling on virtual machine targets. Generate: |
| |
| -- Get_Access_Level (Ref'Tag) |
| |
| else |
| Cond := |
| Make_Function_Call (Loc, |
| Name => |
| New_Occurrence_Of (RTE (RE_Get_Access_Level), Loc), |
| Parameter_Associations => New_List (Obj_Ref)); |
| end if; |
| |
| Cond := |
| Make_Op_Gt (Loc, |
| Left_Opnd => Cond, |
| Right_Opnd => Accessibility_Level (N, Dynamic_Level)); |
| |
| -- Due to the complexity and side effects of the check, utilize an |
| -- if statement instead of the regular Program_Error circuitry. |
| |
| Insert_Action (N, |
| Make_Implicit_If_Statement (N, |
| Condition => Cond, |
| Then_Statements => Stmts)); |
| end if; |
| end Apply_Accessibility_Check; |
| |
| -- Local variables |
| |
| Indic : constant Node_Id := Subtype_Mark (Expression (N)); |
| T : constant Entity_Id := Entity (Indic); |
| Adj_Call : Node_Id; |
| Aggr_In_Place : Boolean; |
| Node : Node_Id; |
| Tag_Assign : Node_Id; |
| Temp : Entity_Id; |
| Temp_Decl : Node_Id; |
| |
| TagT : Entity_Id := Empty; |
| -- Type used as source for tag assignment |
| |
| TagR : Node_Id := Empty; |
| -- Target reference for tag assignment |
| |
| -- Start of processing for Expand_Allocator_Expression |
| |
| begin |
| -- Handle call to C++ constructor |
| |
| if Is_CPP_Constructor_Call (Exp) then |
| Make_CPP_Constructor_Call_In_Allocator |
| (Allocator => N, |
| Function_Call => Exp); |
| return; |
| end if; |
| |
| -- If we have: |
| -- type A is access T1; |
| -- X : A := new T2'(...); |
| -- T1 and T2 can be different subtypes, and we might need to check |
| -- both constraints. First check against the type of the qualified |
| -- expression. |
| |
| Apply_Constraint_Check (Exp, T, No_Sliding => True); |
| |
| Apply_Predicate_Check (Exp, T); |
| |
| -- Check that any anonymous access discriminants are suitable |
| -- for use in an allocator. |
| |
| -- Note: This check is performed here instead of during analysis so that |
| -- we can check against the fully resolved etype of Exp. |
| |
| if Is_Entity_Name (Exp) |
| and then Has_Anonymous_Access_Discriminant (Etype (Exp)) |
| and then Static_Accessibility_Level (Exp, Object_Decl_Level) |
| > Static_Accessibility_Level (N, Object_Decl_Level) |
| then |
| -- A dynamic check and a warning are generated when we are within |
| -- an instance. |
| |
| if In_Instance then |
| Insert_Action (N, |
| Make_Raise_Program_Error (Loc, |
| Reason => PE_Accessibility_Check_Failed)); |
| |
| Error_Msg_N ("anonymous access discriminant is too deep for use" |
| & " in allocator<<", N); |
| Error_Msg_N ("\Program_Error [<<", N); |
| |
| -- Otherwise, make the error static |
| |
| else |
| Error_Msg_N ("anonymous access discriminant is too deep for use" |
| & " in allocator", N); |
| end if; |
| end if; |
| |
| if Do_Range_Check (Exp) then |
| Generate_Range_Check (Exp, T, CE_Range_Check_Failed); |
| end if; |
| |
| -- A check is also needed in cases where the designated subtype is |
| -- constrained and differs from the subtype given in the qualified |
| -- expression. Note that the check on the qualified expression does |
| -- not allow sliding, but this check does (a relaxation from Ada 83). |
| |
| if Is_Constrained (DesigT) |
| and then not Subtypes_Statically_Match (T, DesigT) |
| then |
| Apply_Constraint_Check (Exp, DesigT, No_Sliding => False); |
| |
| Apply_Predicate_Check (Exp, DesigT); |
| |
| if Do_Range_Check (Exp) then |
| Generate_Range_Check (Exp, DesigT, CE_Range_Check_Failed); |
| end if; |
| end if; |
| |
| if Nkind (Exp) = N_Raise_Constraint_Error then |
| Rewrite (N, New_Copy (Exp)); |
| Set_Etype (N, PtrT); |
| return; |
| end if; |
| |
| Aggr_In_Place := Is_Delayed_Aggregate (Exp); |
| |
| -- Case of tagged type or type requiring finalization |
| |
| if Is_Tagged_Type (T) or else Needs_Finalization (T) then |
| |
| -- Ada 2005 (AI-318-02): If the initialization expression is a call |
| -- to a build-in-place function, then access to the allocated object |
| -- must be passed to the function. |
| |
| if Is_Build_In_Place_Function_Call (Exp) then |
| Make_Build_In_Place_Call_In_Allocator (N, Exp); |
| Apply_Accessibility_Check (N, Built_In_Place => True); |
| return; |
| |
| -- Ada 2005 (AI-318-02): Specialization of the previous case for |
| -- expressions containing a build-in-place function call whose |
| -- returned object covers interface types, and Expr has calls to |
| -- Ada.Tags.Displace to displace the pointer to the returned build- |
| -- in-place object to reference the secondary dispatch table of a |
| -- covered interface type. |
| |
| elsif Present (Unqual_BIP_Iface_Function_Call (Exp)) then |
| Make_Build_In_Place_Iface_Call_In_Allocator (N, Exp); |
| Apply_Accessibility_Check (N, Built_In_Place => True); |
| return; |
| end if; |
| |
| -- Actions inserted before: |
| -- Temp : constant ptr_T := new T'(Expression); |
| -- Temp._tag = T'tag; -- when not class-wide |
| -- [Deep_]Adjust (Temp.all); |
| |
| -- We analyze by hand the new internal allocator to avoid any |
| -- recursion and inappropriate call to Initialize. |
| |
| -- We don't want to remove side effects when the expression must be |
| -- built in place. In the case of a build-in-place function call, |
| -- that could lead to a duplication of the call, which was already |
| -- substituted for the allocator. |
| |
| if not Aggr_In_Place then |
| Remove_Side_Effects (Exp); |
| end if; |
| |
| Temp := Make_Temporary (Loc, 'P', N); |
| |
| -- For a class wide allocation generate the following code: |
| |
| -- type Equiv_Record is record ... end record; |
| -- implicit subtype CW is <Class_Wide_Subytpe>; |
| -- temp : PtrT := new CW'(CW!(expr)); |
| |
| if Is_Class_Wide_Type (T) then |
| Expand_Subtype_From_Expr (Empty, T, Indic, Exp); |
| |
| -- Ada 2005 (AI-251): If the expression is a class-wide interface |
| -- object we generate code to move up "this" to reference the |
| -- base of the object before allocating the new object. |
| |
| -- Note that Exp'Address is recursively expanded into a call |
| -- to Base_Address (Exp.Tag) |
| |
| if Is_Class_Wide_Type (Etype (Exp)) |
| and then Is_Interface (Etype (Exp)) |
| and then Tagged_Type_Expansion |
| then |
| Set_Expression |
| (Expression (N), |
| Unchecked_Convert_To (Entity (Indic), |
| Make_Explicit_Dereference (Loc, |
| Unchecked_Convert_To (RTE (RE_Tag_Ptr), |
| Make_Attribute_Reference (Loc, |
| Prefix => Exp, |
| Attribute_Name => Name_Address))))); |
| else |
| Set_Expression |
| (Expression (N), |
| Unchecked_Convert_To (Entity (Indic), Exp)); |
| end if; |
| |
| Analyze_And_Resolve (Expression (N), Entity (Indic)); |
| end if; |
| |
| -- Processing for allocators returning non-interface types |
| |
| if not Is_Interface (Directly_Designated_Type (PtrT)) then |
| if Aggr_In_Place then |
| Temp_Decl := |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Temp, |
| Object_Definition => New_Occurrence_Of (PtrT, Loc), |
| Expression => |
| Make_Allocator (Loc, |
| Expression => |
| New_Occurrence_Of (Etype (Exp), Loc))); |
| |
| -- Copy the Comes_From_Source flag for the allocator we just |
| -- built, since logically this allocator is a replacement of |
| -- the original allocator node. This is for proper handling of |
| -- restriction No_Implicit_Heap_Allocations. |
| |
| Preserve_Comes_From_Source |
| (Expression (Temp_Decl), N); |
| |
| Set_No_Initialization (Expression (Temp_Decl)); |
| Insert_Action (N, Temp_Decl); |
| |
| Build_Allocate_Deallocate_Proc (Temp_Decl, True); |
| Convert_Aggr_In_Allocator (N, Temp_Decl, Exp); |
| |
| else |
| Node := Relocate_Node (N); |
| Set_Analyzed (Node); |
| |
| Temp_Decl := |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Temp, |
| Constant_Present => True, |
| Object_Definition => New_Occurrence_Of (PtrT, Loc), |
| Expression => Node); |
| |
| Insert_Action (N, Temp_Decl); |
| Build_Allocate_Deallocate_Proc (Temp_Decl, True); |
| end if; |
| |
| -- Ada 2005 (AI-251): Handle allocators whose designated type is an |
| -- interface type. In this case we use the type of the qualified |
| -- expression to allocate the object. |
| |
| else |
| declare |
| Def_Id : constant Entity_Id := Make_Temporary (Loc, 'T'); |
| New_Decl : Node_Id; |
| |
| begin |
| New_Decl := |
| Make_Full_Type_Declaration (Loc, |
| Defining_Identifier => Def_Id, |
| Type_Definition => |
| Make_Access_To_Object_Definition (Loc, |
| All_Present => True, |
| Null_Exclusion_Present => False, |
| Constant_Present => |
| Is_Access_Constant (Etype (N)), |
| Subtype_Indication => |
| New_Occurrence_Of (Etype (Exp), Loc))); |
| |
| Insert_Action (N, New_Decl); |
| |
| -- Inherit the allocation-related attributes from the original |
| -- access type. |
| |
| Set_Finalization_Master |
| (Def_Id, Finalization_Master (PtrT)); |
| |
| Set_Associated_Storage_Pool |
| (Def_Id, Associated_Storage_Pool (PtrT)); |
| |
| -- Declare the object using the previous type declaration |
| |
| if Aggr_In_Place then |
| Temp_Decl := |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Temp, |
| Object_Definition => New_Occurrence_Of (Def_Id, Loc), |
| Expression => |
| Make_Allocator (Loc, |
| New_Occurrence_Of (Etype (Exp), Loc))); |
| |
| -- Copy the Comes_From_Source flag for the allocator we just |
| -- built, since logically this allocator is a replacement of |
| -- the original allocator node. This is for proper handling |
| -- of restriction No_Implicit_Heap_Allocations. |
| |
| Set_Comes_From_Source |
| (Expression (Temp_Decl), Comes_From_Source (N)); |
| |
| Set_No_Initialization (Expression (Temp_Decl)); |
| Insert_Action (N, Temp_Decl); |
| |
| Build_Allocate_Deallocate_Proc (Temp_Decl, True); |
| Convert_Aggr_In_Allocator (N, Temp_Decl, Exp); |
| |
| else |
| Node := Relocate_Node (N); |
| Set_Analyzed (Node); |
| |
| Temp_Decl := |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Temp, |
| Constant_Present => True, |
| Object_Definition => New_Occurrence_Of (Def_Id, Loc), |
| Expression => Node); |
| |
| Insert_Action (N, Temp_Decl); |
| Build_Allocate_Deallocate_Proc (Temp_Decl, True); |
| end if; |
| |
| -- Generate an additional object containing the address of the |
| -- returned object. The type of this second object declaration |
| -- is the correct type required for the common processing that |
| -- is still performed by this subprogram. The displacement of |
| -- this pointer to reference the component associated with the |
| -- interface type will be done at the end of common processing. |
| |
| New_Decl := |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Make_Temporary (Loc, 'P'), |
| Object_Definition => New_Occurrence_Of (PtrT, Loc), |
| Expression => |
| Unchecked_Convert_To (PtrT, |
| New_Occurrence_Of (Temp, Loc))); |
| |
| Insert_Action (N, New_Decl); |
| |
| Temp_Decl := New_Decl; |
| Temp := Defining_Identifier (New_Decl); |
| end; |
| end if; |
| |
| -- Generate the tag assignment |
| |
| -- Suppress the tag assignment for VM targets because VM tags are |
| -- represented implicitly in objects. |
| |
| if not Tagged_Type_Expansion then |
| null; |
| |
| -- Ada 2005 (AI-251): Suppress the tag assignment with class-wide |
| -- interface objects because in this case the tag does not change. |
| |
| elsif Is_Interface (Directly_Designated_Type (Etype (N))) then |
| pragma Assert (Is_Class_Wide_Type |
| (Directly_Designated_Type (Etype (N)))); |
| null; |
| |
| elsif Is_Tagged_Type (T) and then not Is_Class_Wide_Type (T) then |
| TagT := T; |
| TagR := |
| Make_Explicit_Dereference (Loc, |
| Prefix => New_Occurrence_Of (Temp, Loc)); |
| |
| elsif Is_Private_Type (T) |
| and then Is_Tagged_Type (Underlying_Type (T)) |
| then |
| TagT := Underlying_Type (T); |
| TagR := |
| Unchecked_Convert_To (Underlying_Type (T), |
| Make_Explicit_Dereference (Loc, |
| Prefix => New_Occurrence_Of (Temp, Loc))); |
| end if; |
| |
| if Present (TagT) then |
| declare |
| Full_T : constant Entity_Id := Underlying_Type (TagT); |
| |
| begin |
| Tag_Assign := |
| Make_Assignment_Statement (Loc, |
| Name => |
| Make_Selected_Component (Loc, |
| Prefix => TagR, |
| Selector_Name => |
| New_Occurrence_Of |
| (First_Tag_Component (Full_T), Loc)), |
| |
| Expression => |
| Unchecked_Convert_To (RTE (RE_Tag), |
| New_Occurrence_Of |
| (Elists.Node |
| (First_Elmt (Access_Disp_Table (Full_T))), Loc))); |
| end; |
| |
| -- The previous assignment has to be done in any case |
| |
| Set_Assignment_OK (Name (Tag_Assign)); |
| Insert_Action (N, Tag_Assign); |
| end if; |
| |
| -- Generate an Adjust call if the object will be moved. In Ada 2005, |
| -- the object may be inherently limited, in which case there is no |
| -- Adjust procedure, and the object is built in place. In Ada 95, the |
| -- object can be limited but not inherently limited if this allocator |
| -- came from a return statement (we're allocating the result on the |
| -- secondary stack). In that case, the object will be moved, so we do |
| -- want to Adjust. However, if it's a nonlimited build-in-place |
| -- function call, Adjust is not wanted. |
| -- |
| -- Needs_Finalization (DesigT) can differ from Needs_Finalization (T) |
| -- if one of the two types is class-wide, and the other is not. |
| |
| if Needs_Finalization (DesigT) |
| and then Needs_Finalization (T) |
| and then not Aggr_In_Place |
| and then not Is_Limited_View (T) |
| and then not Alloc_For_BIP_Return (N) |
| and then not Is_Build_In_Place_Function_Call (Expression (N)) |
| then |
| -- An unchecked conversion is needed in the classwide case because |
| -- the designated type can be an ancestor of the subtype mark of |
| -- the allocator. |
| |
| Adj_Call := |
| Make_Adjust_Call |
| (Obj_Ref => |
| Unchecked_Convert_To (T, |
| Make_Explicit_Dereference (Loc, |
| Prefix => New_Occurrence_Of (Temp, Loc))), |
| Typ => T); |
| |
| if Present (Adj_Call) then |
| Insert_Action (N, Adj_Call); |
| end if; |
| end if; |
| |
| -- Note: the accessibility check must be inserted after the call to |
| -- [Deep_]Adjust to ensure proper completion of the assignment. |
| |
| Apply_Accessibility_Check (Temp); |
| |
| Rewrite (N, New_Occurrence_Of (Temp, Loc)); |
| Analyze_And_Resolve (N, PtrT); |
| |
| -- Ada 2005 (AI-251): Displace the pointer to reference the record |
| -- component containing the secondary dispatch table of the interface |
| -- type. |
| |
| if Is_Interface (Directly_Designated_Type (PtrT)) then |
| Displace_Allocator_Pointer (N); |
| end if; |
| |
| -- Always force the generation of a temporary for aggregates when |
| -- generating C code, to simplify the work in the code generator. |
| |
| elsif Aggr_In_Place |
| or else (Modify_Tree_For_C and then Nkind (Exp) = N_Aggregate) |
| then |
| Temp := Make_Temporary (Loc, 'P', N); |
| Temp_Decl := |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Temp, |
| Object_Definition => New_Occurrence_Of (PtrT, Loc), |
| Expression => |
| Make_Allocator (Loc, |
| Expression => New_Occurrence_Of (Etype (Exp), Loc))); |
| |
| -- Copy the Comes_From_Source flag for the allocator we just built, |
| -- since logically this allocator is a replacement of the original |
| -- allocator node. This is for proper handling of restriction |
| -- No_Implicit_Heap_Allocations. |
| |
| Set_Comes_From_Source |
| (Expression (Temp_Decl), Comes_From_Source (N)); |
| |
| Set_No_Initialization (Expression (Temp_Decl)); |
| Insert_Action (N, Temp_Decl); |
| |
| Build_Allocate_Deallocate_Proc (Temp_Decl, True); |
| Convert_Aggr_In_Allocator (N, Temp_Decl, Exp); |
| |
| Rewrite (N, New_Occurrence_Of (Temp, Loc)); |
| Analyze_And_Resolve (N, PtrT); |
| |
| elsif Is_Access_Type (T) and then Can_Never_Be_Null (T) then |
| Install_Null_Excluding_Check (Exp); |
| |
| elsif Is_Access_Type (DesigT) |
| and then Nkind (Exp) = N_Allocator |
| and then Nkind (Expression (Exp)) /= N_Qualified_Expression |
| then |
| -- Apply constraint to designated subtype indication |
| |
| Apply_Constraint_Check |
| (Expression (Exp), Designated_Type (DesigT), No_Sliding => True); |
| |
| if Nkind (Expression (Exp)) = N_Raise_Constraint_Error then |
| |
| -- Propagate constraint_error to enclosing allocator |
| |
| Rewrite (Exp, New_Copy (Expression (Exp))); |
| end if; |
| |
| else |
| Build_Allocate_Deallocate_Proc (N, True); |
| |
| -- For an access to unconstrained packed array, GIGI needs to see an |
| -- expression with a constrained subtype in order to compute the |
| -- proper size for the allocator. |
| |
| if Is_Packed_Array (T) |
| and then not Is_Constrained (T) |
| then |
| declare |
| ConstrT : constant Entity_Id := Make_Temporary (Loc, 'A'); |
| Internal_Exp : constant Node_Id := Relocate_Node (Exp); |
| begin |
| Insert_Action (Exp, |
| Make_Subtype_Declaration (Loc, |
| Defining_Identifier => ConstrT, |
| Subtype_Indication => |
| Make_Subtype_From_Expr (Internal_Exp, T))); |
| Freeze_Itype (ConstrT, Exp); |
| Rewrite (Exp, OK_Convert_To (ConstrT, Internal_Exp)); |
| end; |
| end if; |
| |
| -- Ada 2005 (AI-318-02): If the initialization expression is a call |
| -- to a build-in-place function, then access to the allocated object |
| -- must be passed to the function. |
| |
| if Is_Build_In_Place_Function_Call (Exp) then |
| Make_Build_In_Place_Call_In_Allocator (N, Exp); |
| end if; |
| end if; |
| |
| exception |
| when RE_Not_Available => |
| return; |
| end Expand_Allocator_Expression; |
| |
| ----------------------------- |
| -- Expand_Array_Comparison -- |
| ----------------------------- |
| |
| -- Expansion is only required in the case of array types. For the unpacked |
| -- case, an appropriate runtime routine is called. For packed cases, and |
| -- also in some other cases where a runtime routine cannot be called, the |
| -- form of the expansion is: |
| |
| -- [body for greater_nn; boolean_expression] |
| |
| -- The body is built by Make_Array_Comparison_Op, and the form of the |
| -- Boolean expression depends on the operator involved. |
| |
| procedure Expand_Array_Comparison (N : Node_Id) is |
| Loc : constant Source_Ptr := Sloc (N); |
| Op1 : Node_Id := Left_Opnd (N); |
| Op2 : Node_Id := Right_Opnd (N); |
| Typ1 : constant Entity_Id := Base_Type (Etype (Op1)); |
| Ctyp : constant Entity_Id := Component_Type (Typ1); |
| |
| Expr : Node_Id; |
| Func_Body : Node_Id; |
| Func_Name : Entity_Id; |
| |
| Comp : RE_Id; |
| |
| Byte_Addressable : constant Boolean := System_Storage_Unit = Byte'Size; |
| -- True for byte addressable target |
| |
| function Length_Less_Than_4 (Opnd : Node_Id) return Boolean; |
| -- Returns True if the length of the given operand is known to be less |
| -- than 4. Returns False if this length is known to be four or greater |
| -- or is not known at compile time. |
| |
| ------------------------ |
| -- Length_Less_Than_4 -- |
| ------------------------ |
| |
| function Length_Less_Than_4 (Opnd : Node_Id) return Boolean is |
| Otyp : constant Entity_Id := Etype (Opnd); |
| |
| begin |
| if Ekind (Otyp) = E_String_Literal_Subtype then |
| return String_Literal_Length (Otyp) < 4; |
| |
| else |
| declare |
| Ityp : constant Entity_Id := Etype (First_Index (Otyp)); |
| Lo : constant Node_Id := Type_Low_Bound (Ityp); |
| Hi : constant Node_Id := Type_High_Bound (Ityp); |
| Lov : Uint; |
| Hiv : Uint; |
| |
| begin |
| if Compile_Time_Known_Value (Lo) then |
| Lov := Expr_Value (Lo); |
| else |
| return False; |
| end if; |
| |
| if Compile_Time_Known_Value (Hi) then |
| Hiv := Expr_Value (Hi); |
| else |
| return False; |
| end if; |
| |
| return Hiv < Lov + 3; |
| end; |
| end if; |
| end Length_Less_Than_4; |
| |
| -- Start of processing for Expand_Array_Comparison |
| |
| begin |
| -- Deal first with unpacked case, where we can call a runtime routine |
| -- except that we avoid this for targets for which are not addressable |
| -- by bytes. |
| |
| if not Is_Bit_Packed_Array (Typ1) and then Byte_Addressable then |
| -- The call we generate is: |
| |
| -- Compare_Array_xn[_Unaligned] |
| -- (left'address, right'address, left'length, right'length) <op> 0 |
| |
| -- x = U for unsigned, S for signed |
| -- n = 8,16,32,64,128 for component size |
| -- Add _Unaligned if length < 4 and component size is 8. |
| -- <op> is the standard comparison operator |
| |
| if Component_Size (Typ1) = 8 then |
| if Length_Less_Than_4 (Op1) |
| or else |
| Length_Less_Than_4 (Op2) |
| then |
| if Is_Unsigned_Type (Ctyp) then |
| Comp := RE_Compare_Array_U8_Unaligned; |
| else |
| Comp := RE_Compare_Array_S8_Unaligned; |
| end if; |
| |
| else |
| if Is_Unsigned_Type (Ctyp) then |
| Comp := RE_Compare_Array_U8; |
| else |
| Comp := RE_Compare_Array_S8; |
| end if; |
| end if; |
| |
| elsif Component_Size (Typ1) = 16 then |
| if Is_Unsigned_Type (Ctyp) then |
| Comp := RE_Compare_Array_U16; |
| else |
| Comp := RE_Compare_Array_S16; |
| end if; |
| |
| elsif Component_Size (Typ1) = 32 then |
| if Is_Unsigned_Type (Ctyp) then |
| Comp := RE_Compare_Array_U32; |
| else |
| Comp := RE_Compare_Array_S32; |
| end if; |
| |
| elsif Component_Size (Typ1) = 64 then |
| if Is_Unsigned_Type (Ctyp) then |
| Comp := RE_Compare_Array_U64; |
| else |
| Comp := RE_Compare_Array_S64; |
| end if; |
| |
| else pragma Assert (Component_Size (Typ1) = 128); |
| if Is_Unsigned_Type (Ctyp) then |
| Comp := RE_Compare_Array_U128; |
| else |
| Comp := RE_Compare_Array_S128; |
| end if; |
| end if; |
| |
| if RTE_Available (Comp) then |
| |
| -- Expand to a call only if the runtime function is available, |
| -- otherwise fall back to inline code. |
| |
| Remove_Side_Effects (Op1, Name_Req => True); |
| Remove_Side_Effects (Op2, Name_Req => True); |
| |
| Rewrite (Op1, |
| Make_Function_Call (Sloc (Op1), |
| Name => New_Occurrence_Of (RTE (Comp), Loc), |
| |
| Parameter_Associations => New_List ( |
| Make_Attribute_Reference (Loc, |
| Prefix => Relocate_Node (Op1), |
| Attribute_Name => Name_Address), |
| |
| Make_Attribute_Reference (Loc, |
| Prefix => Relocate_Node (Op2), |
| Attribute_Name => Name_Address), |
| |
| Make_Attribute_Reference (Loc, |
| Prefix => Relocate_Node (Op1), |
| Attribute_Name => Name_Length), |
| |
| Make_Attribute_Reference (Loc, |
| Prefix => Relocate_Node (Op2), |
| Attribute_Name => Name_Length)))); |
| |
| Rewrite (Op2, |
| Make_Integer_Literal (Sloc (Op2), |
| Intval => Uint_0)); |
| |
| Analyze_And_Resolve (Op1, Standard_Integer); |
| Analyze_And_Resolve (Op2, Standard_Integer); |
| return; |
| end if; |
| end if; |
| |
| -- Cases where we cannot make runtime call |
| |
| -- For (a <= b) we convert to not (a > b) |
| |
| if Chars (N) = Name_Op_Le then |
| Rewrite (N, |
| Make_Op_Not (Loc, |
| Right_Opnd => |
| Make_Op_Gt (Loc, |
| Left_Opnd => Op1, |
| Right_Opnd => Op2))); |
| Analyze_And_Resolve (N, Standard_Boolean); |
| return; |
| |
| -- For < the Boolean expression is |
| -- greater__nn (op2, op1) |
| |
| elsif Chars (N) = Name_Op_Lt then |
| Func_Body := Make_Array_Comparison_Op (Typ1, N); |
| |
| -- Switch operands |
| |
| Op1 := Right_Opnd (N); |
| Op2 := Left_Opnd (N); |
| |
| -- For (a >= b) we convert to not (a < b) |
| |
| elsif Chars (N) = Name_Op_Ge then |
| Rewrite (N, |
| Make_Op_Not (Loc, |
| Right_Opnd => |
| Make_Op_Lt (Loc, |
| Left_Opnd => Op1, |
| Right_Opnd => Op2))); |
| Analyze_And_Resolve (N, Standard_Boolean); |
| return; |
| |
| -- For > the Boolean expression is |
| -- greater__nn (op1, op2) |
| |
| else |
| pragma Assert (Chars (N) = Name_Op_Gt); |
| Func_Body := Make_Array_Comparison_Op (Typ1, N); |
| end if; |
| |
| Func_Name := Defining_Unit_Name (Specification (Func_Body)); |
| Expr := |
| Make_Function_Call (Loc, |
| Name => New_Occurrence_Of (Func_Name, Loc), |
| Parameter_Associations => New_List (Op1, Op2)); |
| |
| Insert_Action (N, Func_Body); |
| Rewrite (N, Expr); |
| Analyze_And_Resolve (N, Standard_Boolean); |
| end Expand_Array_Comparison; |
| |
| --------------------------- |
| -- Expand_Array_Equality -- |
| --------------------------- |
| |
| -- Expand an equality function for multi-dimensional arrays. Here is an |
| -- example of such a function for Nb_Dimension = 2 |
| |
| -- function Enn (A : atyp; B : btyp) return boolean is |
| -- begin |
| -- if (A'length (1) = 0 or else A'length (2) = 0) |
| -- and then |
| -- (B'length (1) = 0 or else B'length (2) = 0) |
| -- then |
| -- return true; -- RM 4.5.2(22) |
| -- end if; |
| |
| -- if A'length (1) /= B'length (1) |
| -- or else |
| -- A'length (2) /= B'length (2) |
| -- then |
| -- return false; -- RM 4.5.2(23) |
| -- end if; |
| |
| -- declare |
| -- A1 : Index_T1 := A'first (1); |
| -- B1 : Index_T1 := B'first (1); |
| -- begin |
| -- loop |
| -- declare |
| -- A2 : Index_T2 := A'first (2); |
| -- B2 : Index_T2 := B'first (2); |
| -- begin |
| -- loop |
| -- if A (A1, A2) /= B (B1, B2) then |
| -- return False; |
| -- end if; |
| |
| -- exit when A2 = A'last (2); |
| -- A2 := Index_T2'succ (A2); |
| -- B2 := Index_T2'succ (B2); |
| -- end loop; |
| -- end; |
| |
| -- exit when A1 = A'last (1); |
| -- A1 := Index_T1'succ (A1); |
| -- B1 := Index_T1'succ (B1); |
| -- end loop; |
| -- end; |
| |
| -- return true; |
| -- end Enn; |
| |
| -- Note on the formal types used (atyp and btyp). If either of the arrays |
| -- is of a private type, we use the underlying type, and do an unchecked |
| -- conversion of the actual. If either of the arrays has a bound depending |
| -- on a discriminant, then we use the base type since otherwise we have an |
| -- escaped discriminant in the function. |
| |
| -- If both arrays are constrained and have the same bounds, we can generate |
| -- a loop with an explicit iteration scheme using a 'Range attribute over |
| -- the first array. |
| |
| function Expand_Array_Equality |
| (Nod : Node_Id; |
| Lhs : Node_Id; |
| Rhs : Node_Id; |
| Bodies : List_Id; |
| Typ : Entity_Id) return Node_Id |
| is |
| Loc : constant Source_Ptr := Sloc (Nod); |
| Decls : constant List_Id := New_List; |
| Index_List1 : constant List_Id := New_List; |
| Index_List2 : constant List_Id := New_List; |
| |
| First_Idx : Node_Id; |
| Formals : List_Id; |
| Func_Name : Entity_Id; |
| Func_Body : Node_Id; |
| |
| A : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uA); |
| B : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uB); |
| |
| Ltyp : Entity_Id; |
| Rtyp : Entity_Id; |
| -- The parameter types to be used for the formals |
| |
| New_Lhs : Node_Id; |
| New_Rhs : Node_Id; |
| -- The LHS and RHS converted to the parameter types |
| |
| function Arr_Attr |
| (Arr : Entity_Id; |
| Nam : Name_Id; |
| Dim : Pos) return Node_Id; |
| -- This builds the attribute reference Arr'Nam (Dim) |
| |
| function Component_Equality (Typ : Entity_Id) return Node_Id; |
| -- Create one statement to compare corresponding components, designated |
| -- by a full set of indexes. |
| |
| function Get_Arg_Type (N : Node_Id) return Entity_Id; |
| -- Given one of the arguments, computes the appropriate type to be used |
| -- for that argument in the corresponding function formal |
| |
| function Handle_One_Dimension |
| (N : Pos; |
| Index : Node_Id) return Node_Id; |
| -- This procedure returns the following code |
| -- |
| -- declare |
| -- An : Index_T := A'First (N); |
| -- Bn : Index_T := B'First (N); |
| -- begin |
| -- loop |
| -- xxx |
| -- exit when An = A'Last (N); |
| -- An := Index_T'Succ (An) |
| -- Bn := Index_T'Succ (Bn) |
| -- end loop; |
| -- end; |
| -- |
| -- If both indexes are constrained and identical, the procedure |
| -- returns a simpler loop: |
| -- |
| -- for An in A'Range (N) loop |
| -- xxx |
| -- end loop |
| -- |
| -- N is the dimension for which we are generating a loop. Index is the |
| -- N'th index node, whose Etype is Index_Type_n in the above code. The |
| -- xxx statement is either the loop or declare for the next dimension |
| -- or if this is the last dimension the comparison of corresponding |
| -- components of the arrays. |
| -- |
| -- The actual way the code works is to return the comparison of |
| -- corresponding components for the N+1 call. That's neater. |
| |
| function Test_Empty_Arrays return Node_Id; |
| -- This function constructs the test for both arrays being empty |
| -- (A'length (1) = 0 or else A'length (2) = 0 or else ...) |
| -- and then |
| -- (B'length (1) = 0 or else B'length (2) = 0 or else ...) |
| |
| function Test_Lengths_Correspond return Node_Id; |
| -- This function constructs the test for arrays having different lengths |
| -- in at least one index position, in which case the resulting code is: |
| |
| -- A'length (1) /= B'length (1) |
| -- or else |
| -- A'length (2) /= B'length (2) |
| -- or else |
| -- ... |
| |
| -------------- |
| -- Arr_Attr -- |
| -------------- |
| |
| function Arr_Attr |
| (Arr : Entity_Id; |
| Nam : Name_Id; |
| Dim : Pos) return Node_Id |
| is |
| begin |
| return |
| Make_Attribute_Reference (Loc, |
| Attribute_Name => Nam, |
| Prefix => New_Occurrence_Of (Arr, Loc), |
| Expressions => New_List (Make_Integer_Literal (Loc, Dim))); |
| end Arr_Attr; |
| |
| ------------------------ |
| -- Component_Equality -- |
| ------------------------ |
| |
| function Component_Equality (Typ : Entity_Id) return Node_Id is |
| Test : Node_Id; |
| L, R : Node_Id; |
| |
| begin |
| -- if a(i1...) /= b(j1...) then return false; end if; |
| |
| L := |
| Make_Indexed_Component (Loc, |
| Prefix => Make_Identifier (Loc, Chars (A)), |
| Expressions => Index_List1); |
| |
| R := |
| Make_Indexed_Component (Loc, |
| Prefix => Make_Identifier (Loc, Chars (B)), |
| Expressions => Index_List2); |
| |
| Test := Expand_Composite_Equality (Nod, Component_Type (Typ), L, R); |
| |
| -- If some (sub)component is an unchecked_union, the whole operation |
| -- will raise program error. |
| |
| if Nkind (Test) = N_Raise_Program_Error then |
| |
| -- This node is going to be inserted at a location where a |
| -- statement is expected: clear its Etype so analysis will set |
| -- it to the expected Standard_Void_Type. |
| |
| Set_Etype (Test, Empty); |
| return Test; |
| |
| else |
| return |
| Make_Implicit_If_Statement (Nod, |
| Condition => Make_Op_Not (Loc, Right_Opnd => Test), |
| Then_Statements => New_List ( |
| Make_Simple_Return_Statement (Loc, |
| Expression => New_Occurrence_Of (Standard_False, Loc)))); |
| end if; |
| end Component_Equality; |
| |
| ------------------ |
| -- Get_Arg_Type -- |
| ------------------ |
| |
| function Get_Arg_Type (N : Node_Id) return Entity_Id is |
| T : Entity_Id; |
| X : Node_Id; |
| |
| begin |
| T := Etype (N); |
| |
| if No (T) then |
| return Typ; |
| |
| else |
| T := Underlying_Type (T); |
| |
| X := First_Index (T); |
| while Present (X) loop |
| if Denotes_Discriminant (Type_Low_Bound (Etype (X))) |
| or else |
| Denotes_Discriminant (Type_High_Bound (Etype (X))) |
| then |
| T := Base_Type (T); |
| exit; |
| end if; |
| |
| Next_Index (X); |
| end loop; |
| |
| return T; |
| end if; |
| end Get_Arg_Type; |
| |
| -------------------------- |
| -- Handle_One_Dimension -- |
| --------------------------- |
| |
| function Handle_One_Dimension |
| (N : Pos; |
| Index : Node_Id) return Node_Id |
| is |
| Need_Separate_Indexes : constant Boolean := |
| Ltyp /= Rtyp or else not Is_Constrained (Ltyp); |
| -- If the index types are identical, and we are working with |
| -- constrained types, then we can use the same index for both |
| -- of the arrays. |
| |
| An : constant Entity_Id := Make_Temporary (Loc, 'A'); |
| |
| Bn : Entity_Id; |
| Index_T : Entity_Id; |
| Stm_List : List_Id; |
| Loop_Stm : Node_Id; |
| |
| begin |
| if N > Number_Dimensions (Ltyp) then |
| return Component_Equality (Ltyp); |
| end if; |
| |
| -- Case where we generate a loop |
| |
| Index_T := Base_Type (Etype (Index)); |
| |
| if Need_Separate_Indexes then |
| Bn := Make_Temporary (Loc, 'B'); |
| else |
| Bn := An; |
| end if; |
| |
| Append (New_Occurrence_Of (An, Loc), Index_List1); |
| Append (New_Occurrence_Of (Bn, Loc), Index_List2); |
| |
| Stm_List := New_List ( |
| Handle_One_Dimension (N + 1, Next_Index (Index))); |
| |
| if Need_Separate_Indexes then |
| |
| -- Generate guard for loop, followed by increments of indexes |
| |
| Append_To (Stm_List, |
| Make_Exit_Statement (Loc, |
| Condition => |
| Make_Op_Eq (Loc, |
| Left_Opnd => New_Occurrence_Of (An, Loc), |
| Right_Opnd => Arr_Attr (A, Name_Last, N)))); |
| |
| Append_To (Stm_List, |
| Make_Assignment_Statement (Loc, |
| Name => New_Occurrence_Of (An, Loc), |
| Expression => |
| Make_Attribute_Reference (Loc, |
| Prefix => New_Occurrence_Of (Index_T, Loc), |
| Attribute_Name => Name_Succ, |
| Expressions => New_List ( |
| New_Occurrence_Of (An, Loc))))); |
| |
| Append_To (Stm_List, |
| Make_Assignment_Statement (Loc, |
| Name => New_Occurrence_Of (Bn, Loc), |
| Expression => |
| Make_Attribute_Reference (Loc, |
| Prefix => New_Occurrence_Of (Index_T, Loc), |
| Attribute_Name => Name_Succ, |
| Expressions => New_List ( |
| New_Occurrence_Of (Bn, Loc))))); |
| end if; |
| |
| -- If separate indexes, we need a declare block for An and Bn, and a |
| -- loop without an iteration scheme. |
| |
| if Need_Separate_Indexes then |
| Loop_Stm := |
| Make_Implicit_Loop_Statement (Nod, Statements => Stm_List); |
| |
| return |
| Make_Block_Statement (Loc, |
| Declarations => New_List ( |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => An, |
| Object_Definition => New_Occurrence_Of (Index_T, Loc), |
| Expression => Arr_Attr (A, Name_First, N)), |
| |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Bn, |
| Object_Definition => New_Occurrence_Of (Index_T, Loc), |
| Expression => Arr_Attr (B, Name_First, N))), |
| |
| Handled_Statement_Sequence => |
| Make_Handled_Sequence_Of_Statements (Loc, |
| Statements => New_List (Loop_Stm))); |
| |
| -- If no separate indexes, return loop statement with explicit |
| -- iteration scheme on its own. |
| |
| else |
| Loop_Stm := |
| Make_Implicit_Loop_Statement (Nod, |
| Statements => Stm_List, |
| Iteration_Scheme => |
| Make_Iteration_Scheme (Loc, |
| Loop_Parameter_Specification => |
| Make_Loop_Parameter_Specification (Loc, |
| Defining_Identifier => An, |
| Discrete_Subtype_Definition => |
| Arr_Attr (A, Name_Range, N)))); |
| return Loop_Stm; |
| end if; |
| end Handle_One_Dimension; |
| |
| ----------------------- |
| -- Test_Empty_Arrays -- |
| ----------------------- |
| |
| function Test_Empty_Arrays return Node_Id is |
| Alist : Node_Id := Empty; |
| Blist : Node_Id := Empty; |
| |
| begin |
| for J in 1 .. Number_Dimensions (Ltyp) loop |
| Evolve_Or_Else (Alist, |
| Make_Op_Eq (Loc, |
| Left_Opnd => Arr_Attr (A, Name_Length, J), |
| Right_Opnd => Make_Integer_Literal (Loc, Uint_0))); |
| |
| Evolve_Or_Else (Blist, |
| Make_Op_Eq (Loc, |
| Left_Opnd => Arr_Attr (B, Name_Length, J), |
| Right_Opnd => Make_Integer_Literal (Loc, Uint_0))); |
| end loop; |
| |
| return |
| Make_And_Then (Loc, |
| Left_Opnd => Alist, |
| Right_Opnd => Blist); |
| end Test_Empty_Arrays; |
| |
| ----------------------------- |
| -- Test_Lengths_Correspond -- |
| ----------------------------- |
| |
| function Test_Lengths_Correspond return Node_Id is |
| Result : Node_Id := Empty; |
| |
| begin |
| for J in 1 .. Number_Dimensions (Ltyp) loop |
| Evolve_Or_Else (Result, |
| Make_Op_Ne (Loc, |
| Left_Opnd => Arr_Attr (A, Name_Length, J), |
| Right_Opnd => Arr_Attr (B, Name_Length, J))); |
| end loop; |
| |
| return Result; |
| end Test_Lengths_Correspond; |
| |
| -- Start of processing for Expand_Array_Equality |
| |
| begin |
| Ltyp := Get_Arg_Type (Lhs); |
| Rtyp := Get_Arg_Type (Rhs); |
| |
| -- For now, if the argument types are not the same, go to the base type, |
| -- since the code assumes that the formals have the same type. This is |
| -- fixable in future ??? |
| |
| if Ltyp /= Rtyp then |
| Ltyp := Base_Type (Ltyp); |
| Rtyp := Base_Type (Rtyp); |
| pragma Assert (Ltyp = Rtyp); |
| end if; |
| |
| -- If the array type is distinct from the type of the arguments, it |
| -- is the full view of a private type. Apply an unchecked conversion |
| -- to ensure that analysis of the code below succeeds. |
| |
| if No (Etype (Lhs)) |
| or else Base_Type (Etype (Lhs)) /= Base_Type (Ltyp) |
| then |
| New_Lhs := OK_Convert_To (Ltyp, Lhs); |
| else |
| New_Lhs := Lhs; |
| end if; |
| |
| if No (Etype (Rhs)) |
| or else Base_Type (Etype (Rhs)) /= Base_Type (Rtyp) |
| then |
| New_Rhs := OK_Convert_To (Rtyp, Rhs); |
| else |
| New_Rhs := Rhs; |
| end if; |
| |
| First_Idx := First_Index (Ltyp); |
| |
| -- If optimization is enabled and the array boils down to a couple of |
| -- consecutive elements, generate a simple conjunction of comparisons |
| -- which should be easier to optimize by the code generator. |
| |
| if Optimization_Level > 0 |
| and then Ltyp = Rtyp |
| and then Is_Constrained (Ltyp) |
| and then Number_Dimensions (Ltyp) = 1 |
| and then Compile_Time_Known_Bounds (Ltyp) |
| and then Expr_Value (Type_High_Bound (Etype (First_Idx))) = |
| Expr_Value (Type_Low_Bound (Etype (First_Idx))) + 1 |
| then |
| declare |
| Ctyp : constant Entity_Id := Component_Type (Ltyp); |
| Low_B : constant Node_Id := |
| Type_Low_Bound (Etype (First_Idx)); |
| High_B : constant Node_Id := |
| Type_High_Bound (Etype (First_Idx)); |
| L, R : Node_Id; |
| TestL, TestH : Node_Id; |
| |
| begin |
| L := |
| Make_Indexed_Component (Loc, |
| Prefix => New_Copy_Tree (New_Lhs), |
| Expressions => New_List (New_Copy_Tree (Low_B))); |
| |
| R := |
| Make_Indexed_Component (Loc, |
| Prefix => New_Copy_Tree (New_Rhs), |
| Expressions => New_List (New_Copy_Tree (Low_B))); |
| |
| TestL := Expand_Composite_Equality (Nod, Ctyp, L, R); |
| |
| L := |
| Make_Indexed_Component (Loc, |
| Prefix => New_Lhs, |
| Expressions => New_List (New_Copy_Tree (High_B))); |
| |
| R := |
| Make_Indexed_Component (Loc, |
| Prefix => New_Rhs, |
| Expressions => New_List (New_Copy_Tree (High_B))); |
| |
| TestH := Expand_Composite_Equality (Nod, Ctyp, L, R); |
| |
| return |
| Make_And_Then (Loc, Left_Opnd => TestL, Right_Opnd => TestH); |
| end; |
| end if; |
| |
| -- Build list of formals for function |
| |
| Formals := New_List ( |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => A, |
| Parameter_Type => New_Occurrence_Of (Ltyp, Loc)), |
| |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => B, |
| Parameter_Type => New_Occurrence_Of (Rtyp, Loc))); |
| |
| Func_Name := Make_Temporary (Loc, 'E'); |
| |
| -- Build statement sequence for function |
| |
| Func_Body := |
| Make_Subprogram_Body (Loc, |
| Specification => |
| Make_Function_Specification (Loc, |
| Defining_Unit_Name => Func_Name, |
| Parameter_Specifications => Formals, |
| Result_Definition => New_Occurrence_Of (Standard_Boolean, Loc)), |
| |
| Declarations => Decls, |
| |
| Handled_Statement_Sequence => |
| Make_Handled_Sequence_Of_Statements (Loc, |
| Statements => New_List ( |
| |
| Make_Implicit_If_Statement (Nod, |
| Condition => Test_Empty_Arrays, |
| Then_Statements => New_List ( |
| Make_Simple_Return_Statement (Loc, |
| Expression => |
| New_Occurrence_Of (Standard_True, Loc)))), |
| |
| Make_Implicit_If_Statement (Nod, |
| Condition => Test_Lengths_Correspond, |
| Then_Statements => New_List ( |
| Make_Simple_Return_Statement (Loc, |
| Expression => New_Occurrence_Of (Standard_False, Loc)))), |
| |
| Handle_One_Dimension (1, First_Idx), |
| |
| Make_Simple_Return_Statement (Loc, |
| Expression => New_Occurrence_Of (Standard_True, Loc))))); |
| |
| Set_Has_Completion (Func_Name, True); |
| Set_Is_Inlined (Func_Name); |
| |
| Append_To (Bodies, Func_Body); |
| |
| return |
| Make_Function_Call (Loc, |
| Name => New_Occurrence_Of (Func_Name, Loc), |
| Parameter_Associations => New_List (New_Lhs, New_Rhs)); |
| end Expand_Array_Equality; |
| |
| ----------------------------- |
| -- Expand_Boolean_Operator -- |
| ----------------------------- |
| |
| -- Note that we first get the actual subtypes of the operands, since we |
| -- always want to deal with types that have bounds. |
| |
| procedure Expand_Boolean_Operator (N : Node_Id) is |
| Typ : constant Entity_Id := Etype (N); |
| |
| begin |
| -- Special case of bit packed array where both operands are known to be |
| -- properly aligned. In this case we use an efficient run time routine |
| -- to carry out the operation (see System.Bit_Ops). |
| |
| if Is_Bit_Packed_Array (Typ) |
| and then not Is_Possibly_Unaligned_Object (Left_Opnd (N)) |
| and then not Is_Possibly_Unaligned_Object (Right_Opnd (N)) |
| then |
| Expand_Packed_Boolean_Operator (N); |
| return; |
| end if; |
| |
| -- For the normal non-packed case, the general expansion is to build |
| -- function for carrying out the comparison (use Make_Boolean_Array_Op) |
| -- and then inserting it into the tree. The original operator node is |
| -- then rewritten as a call to this function. We also use this in the |
| -- packed case if either operand is a possibly unaligned object. |
| |
| declare |
| Loc : constant Source_Ptr := Sloc (N); |
| L : constant Node_Id := Relocate_Node (Left_Opnd (N)); |
| R : Node_Id := Relocate_Node (Right_Opnd (N)); |
| Func_Body : Node_Id; |
| Func_Name : Entity_Id; |
| |
| begin |
| Convert_To_Actual_Subtype (L); |
| Convert_To_Actual_Subtype (R); |
| Ensure_Defined (Etype (L), N); |
| Ensure_Defined (Etype (R), N); |
| Apply_Length_Check (R, Etype (L)); |
| |
| if Nkind (N) = N_Op_Xor then |
| R := Duplicate_Subexpr (R); |
| Silly_Boolean_Array_Xor_Test (N, R, Etype (L)); |
| end if; |
| |
| if Nkind (Parent (N)) = N_Assignment_Statement |
| and then Safe_In_Place_Array_Op (Name (Parent (N)), L, R) |
| then |
| Build_Boolean_Array_Proc_Call (Parent (N), L, R); |
| |
| elsif Nkind (Parent (N)) = N_Op_Not |
| and then Nkind (N) = N_Op_And |
| and then Nkind (Parent (Parent (N))) = N_Assignment_Statement |
| and then Safe_In_Place_Array_Op (Name (Parent (Parent (N))), L, R) |
| then |
| return; |
| else |
| Func_Body := Make_Boolean_Array_Op (Etype (L), N); |
| Func_Name := Defining_Unit_Name (Specification (Func_Body)); |
| Insert_Action (N, Func_Body); |
| |
| -- Now rewrite the expression with a call |
| |
| if Transform_Function_Array then |
| declare |
| Temp_Id : constant Entity_Id := Make_Temporary (Loc, 'T'); |
| Call : Node_Id; |
| Decl : Node_Id; |
| |
| begin |
| -- Generate: |
| -- Temp : ...; |
| |
| Decl := |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Temp_Id, |
| Object_Definition => |
| New_Occurrence_Of (Etype (L), Loc)); |
| |
| -- Generate: |
| -- Proc_Call (L, R, Temp); |
| |
| Call := |
| Make_Procedure_Call_Statement (Loc, |
| Name => New_Occurrence_Of (Func_Name, Loc), |
| Parameter_Associations => |
| New_List ( |
| L, |
| Make_Type_Conversion |
| (Loc, New_Occurrence_Of (Etype (L), Loc), R), |
| New_Occurrence_Of (Temp_Id, Loc))); |
| |
| Insert_Actions (Parent (N), New_List (Decl, Call)); |
| Rewrite (N, New_Occurrence_Of (Temp_Id, Loc)); |
| end; |
| else |
| Rewrite (N, |
| Make_Function_Call (Loc, |
| Name => New_Occurrence_Of (Func_Name, Loc), |
| Parameter_Associations => |
| New_List ( |
| L, |
| Make_Type_Conversion |
| (Loc, New_Occurrence_Of (Etype (L), Loc), R)))); |
| end if; |
| |
| Analyze_And_Resolve (N, Typ); |
| end if; |
| end; |
| end Expand_Boolean_Operator; |
| |
| ------------------------------------------------ |
| -- Expand_Compare_Minimize_Eliminate_Overflow -- |
| ------------------------------------------------ |
| |
| procedure Expand_Compare_Minimize_Eliminate_Overflow (N : Node_Id) is |
| Loc : constant Source_Ptr := Sloc (N); |
| |
| Result_Type : constant Entity_Id := Etype (N); |
| -- Capture result type (could be a derived boolean type) |
| |
| Llo, Lhi : Uint; |
| Rlo, Rhi : Uint; |
| |
| LLIB : constant Entity_Id := Base_Type (Standard_Long_Long_Integer); |
| -- Entity for Long_Long_Integer'Base |
| |
| procedure Set_True; |
| procedure Set_False; |
| -- These procedures rewrite N with an occurrence of Standard_True or |
| -- Standard_False, and then makes a call to Warn_On_Known_Condition. |
| |
| --------------- |
| -- Set_False -- |
| --------------- |
| |
| procedure Set_False is |
| begin |
| Rewrite (N, New_Occurrence_Of (Standard_False, Loc)); |
| Warn_On_Known_Condition (N); |
| end Set_False; |
| |
| -------------- |
| -- Set_True -- |
| -------------- |
| |
| procedure Set_True is |
| begin |
| Rewrite (N, New_Occurrence_Of (Standard_True, Loc)); |
| Warn_On_Known_Condition (N); |
| end Set_True; |
| |
| -- Start of processing for Expand_Compare_Minimize_Eliminate_Overflow |
| |
| begin |
| -- OK, this is the case we are interested in. First step is to process |
| -- our operands using the Minimize_Eliminate circuitry which applies |
| -- this processing to the two operand subtrees. |
| |
| Minimize_Eliminate_Overflows |
| (Left_Opnd (N), Llo, Lhi, Top_Level => False); |
| Minimize_Eliminate_Overflows |
| (Right_Opnd (N), Rlo, Rhi, Top_Level => False); |
| |
| -- See if the range information decides the result of the comparison. |
| -- We can only do this if we in fact have full range information (which |
| -- won't be the case if either operand is bignum at this stage). |
| |
| if Present (Llo) and then Present (Rlo) then |
| case N_Op_Compare (Nkind (N)) is |
| when N_Op_Eq => |
| if Llo = Lhi and then Rlo = Rhi and then Llo = Rlo then |
| Set_True; |
| elsif Llo > Rhi or else Lhi < Rlo then |
| Set_False; |
| end if; |
| |
| when N_Op_Ge => |
| if Llo >= Rhi then |
| Set_True; |
| elsif Lhi < Rlo then |
| Set_False; |
| end if; |
| |
| when N_Op_Gt => |
| if Llo > Rhi then |
| Set_True; |
| elsif Lhi <= Rlo then |
| Set_False; |
| end if; |
| |
| when N_Op_Le => |
| if Llo > Rhi then |
| Set_False; |
| elsif Lhi <= Rlo then |
| Set_True; |
| end if; |
| |
| when N_Op_Lt => |
| if Llo >= Rhi then |
| Set_False; |
| elsif Lhi < Rlo then |
| Set_True; |
| end if; |
| |
| when N_Op_Ne => |
| if Llo = Lhi and then Rlo = Rhi and then Llo = Rlo then |
| Set_False; |
| elsif Llo > Rhi or else Lhi < Rlo then |
| Set_True; |
| end if; |
| end case; |
| |
| -- All done if we did the rewrite |
| |
| if Nkind (N) not in N_Op_Compare then |
| return; |
| end if; |
| end if; |
| |
| -- Otherwise, time to do the comparison |
| |
| declare |
| Ltype : constant Entity_Id := Etype (Left_Opnd (N)); |
| Rtype : constant Entity_Id := Etype (Right_Opnd (N)); |
| |
| begin |
| -- If the two operands have the same signed integer type we are |
| -- all set, nothing more to do. This is the case where either |
| -- both operands were unchanged, or we rewrote both of them to |
| -- be Long_Long_Integer. |
| |
| -- Note: Entity for the comparison may be wrong, but it's not worth |
| -- the effort to change it, since the back end does not use it. |
| |
| if Is_Signed_Integer_Type (Ltype) |
| and then Base_Type (Ltype) = Base_Type (Rtype) |
| then |
| return; |
| |
| -- Here if bignums are involved (can only happen in ELIMINATED mode) |
| |
| elsif Is_RTE (Ltype, RE_Bignum) or else Is_RTE (Rtype, RE_Bignum) then |
| declare |
| Left : Node_Id := Left_Opnd (N); |
| Right : Node_Id := Right_Opnd (N); |
| -- Bignum references for left and right operands |
| |
| begin |
| if not Is_RTE (Ltype, RE_Bignum) then |
| Left := Convert_To_Bignum (Left); |
| elsif not Is_RTE (Rtype, RE_Bignum) then |
| Right := Convert_To_Bignum (Right); |
| end if; |
| |
| -- We rewrite our node with: |
| |
| -- do |
| -- Bnn : Result_Type; |
| -- declare |
| -- M : Mark_Id := SS_Mark; |
| -- begin |
| -- Bnn := Big_xx (Left, Right); (xx = EQ, NT etc) |
| -- SS_Release (M); |
| -- end; |
| -- in |
| -- Bnn |
| -- end |
| |
| declare |
| Blk : constant Node_Id := Make_Bignum_Block (Loc); |
| Bnn : constant Entity_Id := Make_Temporary (Loc, 'B', N); |
| Ent : RE_Id; |
| |
| begin |
| case N_Op_Compare (Nkind (N)) is |
| when N_Op_Eq => Ent := RE_Big_EQ; |
| when N_Op_Ge => Ent := RE_Big_GE; |
| when N_Op_Gt => Ent := RE_Big_GT; |
| when N_Op_Le => Ent := RE_Big_LE; |
| when N_Op_Lt => Ent := RE_Big_LT; |
| when N_Op_Ne => Ent := RE_Big_NE; |
| end case; |
| |
| -- Insert assignment to Bnn into the bignum block |
| |
| Insert_Before |
| (First (Statements (Handled_Statement_Sequence (Blk))), |
| Make_Assignment_Statement (Loc, |
| Name => New_Occurrence_Of (Bnn, Loc), |
| Expression => |
| Make_Function_Call (Loc, |
| Name => |
| New_Occurrence_Of (RTE (Ent), Loc), |
| Parameter_Associations => New_List (Left, Right)))); |
| |
| -- Now do the rewrite with expression actions |
| |
| Rewrite (N, |
| Make_Expression_With_Actions (Loc, |
| Actions => New_List ( |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Bnn, |
| Object_Definition => |
| New_Occurrence_Of (Result_Type, Loc)), |
| Blk), |
| Expression => New_Occurrence_Of (Bnn, Loc))); |
| Analyze_And_Resolve (N, Result_Type); |
| end; |
| end; |
| |
| -- No bignums involved, but types are different, so we must have |
| -- rewritten one of the operands as a Long_Long_Integer but not |
| -- the other one. |
| |
| -- If left operand is Long_Long_Integer, convert right operand |
| -- and we are done (with a comparison of two Long_Long_Integers). |
| |
| elsif Ltype = LLIB then |
| Convert_To_And_Rewrite (LLIB, Right_Opnd (N)); |
| Analyze_And_Resolve (Right_Opnd (N), LLIB, Suppress => All_Checks); |
| return; |
| |
| -- If right operand is Long_Long_Integer, convert left operand |
| -- and we are done (with a comparison of two Long_Long_Integers). |
| |
| -- This is the only remaining possibility |
| |
| else pragma Assert (Rtype = LLIB); |
| Convert_To_And_Rewrite (LLIB, Left_Opnd (N)); |
| Analyze_And_Resolve (Left_Opnd (N), LLIB, Suppress => All_Checks); |
| return; |
| end if; |
| end; |
| end Expand_Compare_Minimize_Eliminate_Overflow; |
| |
| ------------------------------- |
| -- Expand_Composite_Equality -- |
| ------------------------------- |
| |
| -- This function is only called for comparing internal fields of composite |
| -- types when these fields are themselves composites. This is a special |
| -- case because it is not possible to respect normal Ada visibility rules. |
| |
| function Expand_Composite_Equality |
| (Nod : Node_Id; |
| Typ : Entity_Id; |
| Lhs : Node_Id; |
| Rhs : Node_Id) return Node_Id |
| is |
| Loc : constant Source_Ptr := Sloc (Nod); |
| Full_Type : Entity_Id; |
| Eq_Op : Entity_Id; |
| |
| begin |
| if Is_Private_Type (Typ) then |
| Full_Type := Underlying_Type (Typ); |
| else |
| Full_Type := Typ; |
| end if; |
| |
| -- If the private type has no completion the context may be the |
| -- expansion of a composite equality for a composite type with some |
| -- still incomplete components. The expression will not be analyzed |
| -- until the enclosing type is completed, at which point this will be |
| -- properly expanded, unless there is a bona fide completion error. |
| |
| if No (Full_Type) then |
| return Make_Op_Eq (Loc, Left_Opnd => Lhs, Right_Opnd => Rhs); |
| end if; |
| |
| Full_Type := Base_Type (Full_Type); |
| |
| -- When the base type itself is private, use the full view to expand |
| -- the composite equality. |
| |
| if Is_Private_Type (Full_Type) then |
| Full_Type := Underlying_Type (Full_Type); |
| end if; |
| |
| -- Case of tagged record types |
| |
| if Is_Tagged_Type (Full_Type) then |
| Eq_Op := Find_Primitive_Eq (Typ); |
| pragma Assert (Present (Eq_Op)); |
| |
| return |
| Make_Function_Call (Loc, |
| Name => New_Occurrence_Of (Eq_Op, Loc), |
| Parameter_Associations => |
| New_List |
| (Unchecked_Convert_To (Etype (First_Formal (Eq_Op)), Lhs), |
| Unchecked_Convert_To (Etype (First_Formal (Eq_Op)), Rhs))); |
| |
| -- Case of untagged record types |
| |
| elsif Is_Record_Type (Full_Type) then |
| Eq_Op := TSS (Full_Type, TSS_Composite_Equality); |
| |
| if Present (Eq_Op) then |
| if Etype (First_Formal (Eq_Op)) /= Full_Type then |
| |
| -- Inherited equality from parent type. Convert the actuals to |
| -- match signature of operation. |
| |
| declare |
| T : constant Entity_Id := Etype (First_Formal (Eq_Op)); |
| |
| begin |
| return |
| Make_Function_Call (Loc, |
| Name => New_Occurrence_Of (Eq_Op, Loc), |
| Parameter_Associations => New_List ( |
| OK_Convert_To (T, Lhs), |
| OK_Convert_To (T, Rhs))); |
| end; |
| |
| else |
| -- Comparison between Unchecked_Union components |
| |
| if Is_Unchecked_Union (Full_Type) then |
| declare |
| Lhs_Type : Node_Id := Full_Type; |
| Rhs_Type : Node_Id := Full_Type; |
| Lhs_Discr_Val : Node_Id; |
| Rhs_Discr_Val : Node_Id; |
| |
| begin |
| -- Lhs subtype |
| |
| if Nkind (Lhs) = N_Selected_Component then |
| Lhs_Type := Etype (Entity (Selector_Name (Lhs))); |
| end if; |
| |
| -- Rhs subtype |
| |
| if Nkind (Rhs) = N_Selected_Component then |
| Rhs_Type := Etype (Entity (Selector_Name (Rhs))); |
| end if; |
| |
| -- Lhs of the composite equality |
| |
| if Is_Constrained (Lhs_Type) then |
| |
| -- Since the enclosing record type can never be an |
| -- Unchecked_Union (this code is executed for records |
| -- that do not have variants), we may reference its |
| -- discriminant(s). |
| |
| if Nkind (Lhs) = N_Selected_Component |
| and then Has_Per_Object_Constraint |
| (Entity (Selector_Name (Lhs))) |
| then |
| Lhs_Discr_Val := |
| Make_Selected_Component (Loc, |
| Prefix => Prefix (Lhs), |
| Selector_Name => |
| New_Copy |
| (Get_Discriminant_Value |
| (First_Discriminant (Lhs_Type), |
| Lhs_Type, |
| Stored_Constraint (Lhs_Type)))); |
| |
| else |
| Lhs_Discr_Val := |
| New_Copy |
| (Get_Discriminant_Value |
| (First_Discriminant (Lhs_Type), |
| Lhs_Type, |
| Stored_Constraint (Lhs_Type))); |
| |
| end if; |
| else |
| -- It is not possible to infer the discriminant since |
| -- the subtype is not constrained. |
| |
| return |
| Make_Raise_Program_Error (Loc, |
| Reason => PE_Unchecked_Union_Restriction); |
| end if; |
| |
| -- Rhs of the composite equality |
| |
| if Is_Constrained (Rhs_Type) then |
| if Nkind (Rhs) = N_Selected_Component |
| and then Has_Per_Object_Constraint |
| (Entity (Selector_Name (Rhs))) |
| then |
| Rhs_Discr_Val := |
| Make_Selected_Component (Loc, |
| Prefix => Prefix (Rhs), |
| Selector_Name => |
| New_Copy |
| (Get_Discriminant_Value |
| (First_Discriminant (Rhs_Type), |
| Rhs_Type, |
| Stored_Constraint (Rhs_Type)))); |
| |
| else |
| Rhs_Discr_Val := |
| New_Copy |
| (Get_Discriminant_Value |
| (First_Discriminant (Rhs_Type), |
| Rhs_Type, |
| Stored_Constraint (Rhs_Type))); |
| |
| end if; |
| else |
| return |
| Make_Raise_Program_Error (Loc, |
| Reason => PE_Unchecked_Union_Restriction); |
| end if; |
| |
| -- Call the TSS equality function with the inferred |
| -- discriminant values. |
| |
| return |
| Make_Function_Call (Loc, |
| Name => New_Occurrence_Of (Eq_Op, Loc), |
| Parameter_Associations => New_List ( |
| Lhs, |
| Rhs, |
| Lhs_Discr_Val, |
| Rhs_Discr_Val)); |
| end; |
| |
| -- All cases other than comparing Unchecked_Union types |
| |
| else |
| declare |
| T : constant Entity_Id := Etype (First_Formal (Eq_Op)); |
| begin |
| return |
| Make_Function_Call (Loc, |
| Name => |
| New_Occurrence_Of (Eq_Op, Loc), |
| Parameter_Associations => New_List ( |
| OK_Convert_To (T, Lhs), |
| OK_Convert_To (T, Rhs))); |
| end; |
| end if; |
| end if; |
| |
| -- Equality composes in Ada 2012 for untagged record types. It also |
| -- composes for bounded strings, because they are part of the |
| -- predefined environment. We could make it compose for bounded |
| -- strings by making them tagged, or by making sure all subcomponents |
| -- are set to the same value, even when not used. Instead, we have |
| -- this special case in the compiler, because it's more efficient. |
| |
| elsif Ada_Version >= Ada_2012 or else Is_Bounded_String (Typ) then |
| |
| -- If no TSS has been created for the type, check whether there is |
| -- a primitive equality declared for it. |
| |
| declare |
| Op : constant Node_Id := Build_Eq_Call (Typ, Loc, Lhs, Rhs); |
| |
| begin |
| -- Use user-defined primitive if it exists, otherwise use |
| -- predefined equality. |
| |
| if Present (Op) then |
| return Op; |
| else |
| return Make_Op_Eq (Loc, Lhs, Rhs); |
| end if; |
| end; |
| |
| else |
| return Expand_Record_Equality (Nod, Full_Type, Lhs, Rhs); |
| end if; |
| |
| -- Case of non-record types (always use predefined equality) |
| |
| else |
| return Make_Op_Eq (Loc, Left_Opnd => Lhs, Right_Opnd => Rhs); |
| end if; |
| end Expand_Composite_Equality; |
| |
| ------------------------ |
| -- Expand_Concatenate -- |
| ------------------------ |
| |
| procedure Expand_Concatenate (Cnode : Node_Id; Opnds : List_Id) is |
| Loc : constant Source_Ptr := Sloc (Cnode); |
| |
| Atyp : constant Entity_Id := Base_Type (Etype (Cnode)); |
| -- Result type of concatenation |
| |
| Ctyp : constant Entity_Id := Base_Type (Component_Type (Etype (Cnode))); |
| -- Component type. Elements of this component type can appear as one |
| -- of the operands of concatenation as well as arrays. |
| |
| Istyp : constant Entity_Id := Etype (First_Index (Atyp)); |
| -- Index subtype |
| |
| Ityp : constant Entity_Id := Base_Type (Istyp); |
| -- Index type. This is the base type of the index subtype, and is used |
| -- for all computed bounds (which may be out of range of Istyp in the |
| -- case of null ranges). |
| |
| Artyp : Entity_Id; |
| -- This is the type we use to do arithmetic to compute the bounds and |
| -- lengths of operands. The choice of this type is a little subtle and |
| -- is discussed in a separate section at the start of the body code. |
| |
| Result_May_Be_Null : Boolean := True; |
| -- Reset to False if at least one operand is encountered which is known |
| -- at compile time to be non-null. Used for handling the special case |
| -- of setting the high bound to the last operand high bound for a null |
| -- result, thus ensuring a proper high bound in the super-flat case. |
| |
| N : constant Nat := List_Length (Opnds); |
| -- Number of concatenation operands including possibly null operands |
| |
| NN : Nat := 0; |
| -- Number of operands excluding any known to be null, except that the |
| -- last operand is always retained, in case it provides the bounds for |
| -- a null result. |
| |
| Opnd : Node_Id := Empty; |
| -- Current operand being processed in the loop through operands. After |
| -- this loop is complete, always contains the last operand (which is not |
| -- the same as Operands (NN), since null operands are skipped). |
| |
| -- Arrays describing the operands, only the first NN entries of each |
| -- array are set (NN < N when we exclude known null operands). |
| |
| Is_Fixed_Length : array (1 .. N) of Boolean; |
| -- True if length of corresponding operand known at compile time |
| |
| Operands : array (1 .. N) of Node_Id; |
| -- Set to the corresponding entry in the Opnds list (but note that null |
| -- operands are excluded, so not all entries in the list are stored). |
| |
| Fixed_Length : array (1 .. N) of Uint; |
| -- Set to length of operand. Entries in this array are set only if the |
| -- corresponding entry in Is_Fixed_Length is True. |
| |
| Opnd_Low_Bound : array (1 .. N) of Node_Id; |
| -- Set to lower bound of operand. Either an integer literal in the case |
| -- where the bound is known at compile time, else actual lower bound. |
| -- The operand low bound is of type Ityp. |
| |
| Var_Length : array (1 .. N) of Entity_Id; |
| -- Set to an entity of type Natural that contains the length of an |
| -- operand whose length is not known at compile time. Entries in this |
| -- array are set only if the corresponding entry in Is_Fixed_Length |
| -- is False. The entity is of type Artyp. |
| |
| Aggr_Length : array (0 .. N) of Node_Id; |
| -- The J'th entry in an expression node that represents the total length |
| -- of operands 1 through J. It is either an integer literal node, or a |
| -- reference to a constant entity with the right value, so it is fine |
| -- to just do a Copy_Node to get an appropriate copy. The extra zeroth |
| -- entry always is set to zero. The length is of type Artyp. |
| |
| Low_Bound : Node_Id := Empty; |
| -- A tree node representing the low bound of the result (of type Ityp). |
| -- This is either an integer literal node, or an identifier reference to |
| -- a constant entity initialized to the appropriate value. |
| |
| Last_Opnd_Low_Bound : Node_Id := Empty; |
| -- A tree node representing the low bound of the last operand. This |
| -- need only be set if the result could be null. It is used for the |
| -- special case of setting the right low bound for a null result. |
| -- This is of type Ityp. |
| |
| Last_Opnd_High_Bound : Node_Id := Empty; |
| -- A tree node representing the high bound of the last operand. This |
| -- need only be set if the result could be null. It is used for the |
| -- special case of setting the right high bound for a null result. |
| -- This is of type Ityp. |
| |
| High_Bound : Node_Id := Empty; |
| -- A tree node representing the high bound of the result (of type Ityp) |
| |
| Result : Node_Id := Empty; |
| -- Result of the concatenation (of type Ityp) |
| |
| Actions : constant List_Id := New_List; |
| -- Collect actions to be inserted |
| |
| Known_Non_Null_Operand_Seen : Boolean; |
| -- Set True during generation of the assignments of operands into |
| -- result once an operand known to be non-null has been seen. |
| |
| function Library_Level_Target return Boolean; |
| -- Return True if the concatenation is within the expression of the |
| -- declaration of a library-level object. |
| |
| function Make_Artyp_Literal (Val : Nat) return Node_Id; |
| -- This function makes an N_Integer_Literal node that is returned in |
| -- analyzed form with the type set to Artyp. Importantly this literal |
| -- is not flagged as static, so that if we do computations with it that |
| -- result in statically detected out of range conditions, we will not |
| -- generate error messages but instead warning messages. |
| |
| function To_Artyp (X : Node_Id) return Node_Id; |
| -- Given a node of type Ityp, returns the corresponding value of type |
| -- Artyp. For non-enumeration types, this is a plain integer conversion. |
| -- For enum types, the Pos of the value is returned. |
| |
| function To_Ityp (X : Node_Id) return Node_Id; |
| -- The inverse function (uses Val in the case of enumeration types) |
| |
| -------------------------- |
| -- Library_Level_Target -- |
| -------------------------- |
| |
| function Library_Level_Target return Boolean is |
| P : Node_Id := Parent (Cnode); |
| |
| begin |
| while Present (P) loop |
| if Nkind (P) = N_Object_Declaration then |
| return Is_Library_Level_Entity (Defining_Identifier (P)); |
| |
| -- Prevent the search from going too far |
| |
| elsif Is_Body_Or_Package_Declaration (P) then |
| return False; |
| end if; |
| |
| P := Parent (P); |
| end loop; |
| |
| return False; |
| end Library_Level_Target; |
| |
| ------------------------ |
| -- Make_Artyp_Literal -- |
| ------------------------ |
| |
| function Make_Artyp_Literal (Val : Nat) return Node_Id is |
| Result : constant Node_Id := Make_Integer_Literal (Loc, Val); |
| begin |
| Set_Etype (Result, Artyp); |
| Set_Analyzed (Result, True); |
| Set_Is_Static_Expression (Result, False); |
| return Result; |
| end Make_Artyp_Literal; |
| |
| -------------- |
| -- To_Artyp -- |
| -------------- |
| |
| function To_Artyp (X : Node_Id) return Node_Id is |
| begin |
| if Ityp = Base_Type (Artyp) then |
| return X; |
| |
| elsif Is_Enumeration_Type (Ityp) then |
| return |
| Make_Attribute_Reference (Loc, |
| Prefix => New_Occurrence_Of (Ityp, Loc), |
| Attribute_Name => Name_Pos, |
| Expressions => New_List (X)); |
| |
| else |
| return Convert_To (Artyp, X); |
| end if; |
| end To_Artyp; |
| |
| ------------- |
| -- To_Ityp -- |
| ------------- |
| |
| function To_Ityp (X : Node_Id) return Node_Id is |
| begin |
| if Is_Enumeration_Type (Ityp) then |
| return |
| Make_Attribute_Reference (Loc, |
| Prefix => New_Occurrence_Of (Ityp, Loc), |
| Attribute_Name => Name_Val, |
| Expressions => New_List (X)); |
| |
| -- Case where we will do a type conversion |
| |
| else |
| if Ityp = Base_Type (Artyp) then |
| return X; |
| else |
| return Convert_To (Ityp, X); |
| end if; |
| end if; |
| end To_Ityp; |
| |
| -- Local Declarations |
| |
| Opnd_Typ : Entity_Id; |
| Subtyp_Ind : Entity_Id; |
| Ent : Entity_Id; |
| Len : Uint; |
| J : Nat; |
| Clen : Node_Id; |
| Set : Boolean; |
| |
| -- Start of processing for Expand_Concatenate |
| |
| begin |
| -- Choose an appropriate computational type |
| |
| -- We will be doing calculations of lengths and bounds in this routine |
| -- and computing one from the other in some cases, e.g. getting the high |
| -- bound by adding the length-1 to the low bound. |
| |
| -- We can't just use the index type, or even its base type for this |
| -- purpose for two reasons. First it might be an enumeration type which |
| -- is not suitable for computations of any kind, and second it may |
| -- simply not have enough range. For example if the index type is |
| -- -128..+127 then lengths can be up to 256, which is out of range of |
| -- the type. |
| |
| -- For enumeration types, we can simply use Standard_Integer, this is |
| -- sufficient since the actual number of enumeration literals cannot |
| -- possibly exceed the range of integer (remember we will be doing the |
| -- arithmetic with POS values, not representation values). |
| |
| if Is_Enumeration_Type (Ityp) then |
| Artyp := Standard_Integer; |
| |
| -- For modular types, we use a 32-bit modular type for types whose size |
| -- is in the range 1-31 bits. For 32-bit unsigned types, we use the |
| -- identity type, and for larger unsigned types we use a 64-bit type. |
| |
| elsif Is_Modular_Integer_Type (Ityp) then |
| if RM_Size (Ityp) < Standard_Integer_Size then |
| Artyp := Standard_Unsigned; |
| elsif RM_Size (Ityp) = Standard_Integer_Size then |
| Artyp := Ityp; |
| else |
| Artyp := Standard_Long_Long_Unsigned; |
| end if; |
| |
| -- Similar treatment for signed types |
| |
| else |
| if RM_Size (Ityp) < Standard_Integer_Size then |
| Artyp := Standard_Integer; |
| elsif RM_Size (Ityp) = Standard_Integer_Size then |
| Artyp := Ityp; |
| else |
| Artyp := Standard_Long_Long_Integer; |
| end if; |
| end if; |
| |
| -- Supply dummy entry at start of length array |
| |
| Aggr_Length (0) := Make_Artyp_Literal (0); |
| |
| -- Go through operands setting up the above arrays |
| |
| J := 1; |
| while J <= N loop |
| Opnd := Remove_Head (Opnds); |
| Opnd_Typ := Etype (Opnd); |
| |
| -- The parent got messed up when we put the operands in a list, |
| -- so now put back the proper parent for the saved operand, that |
| -- is to say the concatenation node, to make sure that each operand |
| -- is seen as a subexpression, e.g. if actions must be inserted. |
| |
| Set_Parent (Opnd, Cnode); |
| |
| -- Set will be True when we have setup one entry in the array |
| |
| Set := False; |
| |
| -- Singleton element (or character literal) case |
| |
| if Base_Type (Opnd_Typ) = Ctyp then |
| NN := NN + 1; |
| Operands (NN) := Opnd; |
| Is_Fixed_Length (NN) := True; |
| Fixed_Length (NN) := Uint_1; |
| Result_May_Be_Null := False; |
| |
| -- Set low bound of operand (no need to set Last_Opnd_High_Bound |
| -- since we know that the result cannot be null). |
| |
| Opnd_Low_Bound (NN) := |
| Make_Attribute_Reference (Loc, |
| Prefix => New_Occurrence_Of (Istyp, Loc), |
| Attribute_Name => Name_First); |
| |
| Set := True; |
| |
| -- String literal case (can only occur for strings of course) |
| |
| elsif Nkind (Opnd) = N_String_Literal then |
| Len := String_Literal_Length (Opnd_Typ); |
| |
| if Len /= 0 then |
| Result_May_Be_Null := False; |
| end if; |
| |
| -- Capture last operand low and high bound if result could be null |
| |
| if J = N and then Result_May_Be_Null then |
| Last_Opnd_Low_Bound := |
| New_Copy_Tree (String_Literal_Low_Bound (Opnd_Typ)); |
| |
| Last_Opnd_High_Bound := |
| Make_Op_Subtract (Loc, |
| Left_Opnd => |
| New_Copy_Tree (String_Literal_Low_Bound (Opnd_Typ)), |
| Right_Opnd => Make_Integer_Literal (Loc, 1)); |
| end if; |
| |
| -- Skip null string literal |
| |
| if J < N and then Len = 0 then |
| goto Continue; |
| end if; |
| |
| NN := NN + 1; |
| Operands (NN) := Opnd; |
| Is_Fixed_Length (NN) := True; |
| |
| -- Set length and bounds |
| |
| Fixed_Length (NN) := Len; |
| |
| Opnd_Low_Bound (NN) := |
| New_Copy_Tree (String_Literal_Low_Bound (Opnd_Typ)); |
| |
| Set := True; |
| |
| -- All other cases |
| |
| else |
| -- Check constrained case with known bounds |
| |
| if Is_Constrained (Opnd_Typ) then |
| declare |
| Index : constant Node_Id := First_Index (Opnd_Typ); |
| Indx_Typ : constant Entity_Id := Etype (Index); |
| Lo : constant Node_Id := Type_Low_Bound (Indx_Typ); |
| Hi : constant Node_Id := Type_High_Bound (Indx_Typ); |
| |
| begin |
| -- Fixed length constrained array type with known at compile |
| -- time bounds is last case of fixed length operand. |
| |
| if Compile_Time_Known_Value (Lo) |
| and then |
| Compile_Time_Known_Value (Hi) |
| then |
| declare |
| Loval : constant Uint := Expr_Value (Lo); |
| Hival : constant Uint := Expr_Value (Hi); |
| Len : constant Uint := |
| UI_Max (Hival - Loval + 1, Uint_0); |
| |
| begin |
| if Len > 0 then |
| Result_May_Be_Null := False; |
| end if; |
| |
| -- Capture last operand bounds if result could be null |
| |
| if J = N and then Result_May_Be_Null then |
| Last_Opnd_Low_Bound := |
| Convert_To (Ityp, |
| Make_Integer_Literal (Loc, Expr_Value (Lo))); |
| |
| Last_Opnd_High_Bound := |
| Convert_To (Ityp, |
| Make_Integer_Literal (Loc, Expr_Value (Hi))); |
| end if; |
| |
| -- Exclude null length case unless last operand |
| |
| if J < N and then Len = 0 then |
| goto Continue; |
| end if; |
| |
| NN := NN + 1; |
| Operands (NN) := Opnd; |
| Is_Fixed_Length (NN) := True; |
| Fixed_Length (NN) := Len; |
| |
| Opnd_Low_Bound (NN) := |
| To_Ityp |
| (Make_Integer_Literal (Loc, Expr_Value (Lo))); |
| Set := True; |
| end; |
| end if; |
| end; |
| end if; |
| |
| -- All cases where the length is not known at compile time, or the |
| -- special case of an operand which is known to be null but has a |
| -- lower bound other than 1 or is other than a string type. |
| |
| if not Set then |
| NN := NN + 1; |
| |
| -- Capture operand bounds |
| |
| Opnd_Low_Bound (NN) := |
| Make_Attribute_Reference (Loc, |
| Prefix => |
| Duplicate_Subexpr (Opnd, Name_Req => True), |
| Attribute_Name => Name_First); |
| |
| -- Capture last operand bounds if result could be null |
| |
| if J = N and Result_May_Be_Null then |
| Last_Opnd_Low_Bound := |
| Convert_To (Ityp, |
| Make_Attribute_Reference (Loc, |
| Prefix => |
| Duplicate_Subexpr (Opnd, Name_Req => True), |
| Attribute_Name => Name_First)); |
| |
| Last_Opnd_High_Bound := |
| Convert_To (Ityp, |
| Make_Attribute_Reference (Loc, |
| Prefix => |
| Duplicate_Subexpr (Opnd, Name_Req => True), |
| Attribute_Name => Name_Last)); |
| end if; |
| |
| -- Capture length of operand in entity |
| |
| Operands (NN) := Opnd; |
| Is_Fixed_Length (NN) := False; |
| |
| Var_Length (NN) := Make_Temporary (Loc, 'L'); |
| |
| Append_To (Actions, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Var_Length (NN), |
| Constant_Present => True, |
| Object_Definition => New_Occurrence_Of (Artyp, Loc), |
| Expression => |
| Make_Attribute_Reference (Loc, |
| Prefix => |
| Duplicate_Subexpr (Opnd, Name_Req => True), |
| Attribute_Name => Name_Length))); |
| end if; |
| end if; |
| |
| -- Set next entry in aggregate length array |
| |
| -- For first entry, make either integer literal for fixed length |
| -- or a reference to the saved length for variable length. |
| |
| if NN = 1 then |
| if Is_Fixed_Length (1) then |
| Aggr_Length (1) := Make_Integer_Literal (Loc, Fixed_Length (1)); |
| else |
| Aggr_Length (1) := New_Occurrence_Of (Var_Length (1), Loc); |
| end if; |
| |
| -- If entry is fixed length and only fixed lengths so far, make |
| -- appropriate new integer literal adding new length. |
| |
| elsif Is_Fixed_Length (NN) |
| and then Nkind (Aggr_Length (NN - 1)) = N_Integer_Literal |
| then |
| Aggr_Length (NN) := |
| Make_Integer_Literal (Loc, |
| Intval => Fixed_Length (NN) + Intval (Aggr_Length (NN - 1))); |
| |
| -- All other cases, construct an addition node for the length and |
| -- create an entity initialized to this length. |
| |
| else |
| Ent := Make_Temporary (Loc, 'L'); |
| |
| if Is_Fixed_Length (NN) then |
| Clen := Make_Integer_Literal (Loc, Fixed_Length (NN)); |
| else |
| Clen := New_Occurrence_Of (Var_Length (NN), Loc); |
| end if; |
| |
| Append_To (Actions, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Ent, |
| Constant_Present => True, |
| Object_Definition => New_Occurrence_Of (Artyp, Loc), |
| Expression => |
| Make_Op_Add (Loc, |
| Left_Opnd => New_Copy_Tree (Aggr_Length (NN - 1)), |
| Right_Opnd => Clen))); |
| |
| Aggr_Length (NN) := Make_Identifier (Loc, Chars => Chars (Ent)); |
| end if; |
| |
| <<Continue>> |
| J := J + 1; |
| end loop; |
| |
| -- If we have only skipped null operands, return the last operand |
| |
| if NN = 0 then |
| Result := Opnd; |
| goto Done; |
| end if; |
| |
| -- If we have only one non-null operand, return it and we are done. |
| -- There is one case in which this cannot be done, and that is when |
| -- the sole operand is of the element type, in which case it must be |
| -- converted to an array, and the easiest way of doing that is to go |
| -- through the normal general circuit. |
| |
| if NN = 1 and then Base_Type (Etype (Operands (1))) /= Ctyp then |
| Result := Operands (1); |
| goto Done; |
| end if; |
| |
| -- Cases where we have a real concatenation |
| |
| -- Next step is to find the low bound for the result array that we |
| -- will allocate. The rules for this are in (RM 4.5.6(5-7)). |
| |
| -- If the ultimate ancestor of the index subtype is a constrained array |
| -- definition, then the lower bound is that of the index subtype as |
| -- specified by (RM 4.5.3(6)). |
| |
| -- The right test here is to go to the root type, and then the ultimate |
| -- ancestor is the first subtype of this root type. |
| |
| if Is_Constrained (First_Subtype (Root_Type (Atyp))) then |
| Low_Bound := |
| Make_Attribute_Reference (Loc, |
| Prefix => |
| New_Occurrence_Of (First_Subtype (Root_Type (Atyp)), Loc), |
| Attribute_Name => Name_First); |
| |
| -- If the first operand in the list has known length we know that |
| -- the lower bound of the result is the lower bound of this operand. |
| |
| elsif Is_Fixed_Length (1) then |
| Low_Bound := Opnd_Low_Bound (1); |
| |
| -- OK, we don't know the lower bound, we have to build a horrible |
| -- if expression node of the form |
| |
| -- if Cond1'Length /= 0 then |
| -- Opnd1 low bound |
| -- else |
| -- if Opnd2'Length /= 0 then |
| -- Opnd2 low bound |
| -- else |
| -- ... |
| |
| -- The nesting ends either when we hit an operand whose length is known |
| -- at compile time, or on reaching the last operand, whose low bound we |
| -- take unconditionally whether or not it is null. It's easiest to do |
| -- this with a recursive procedure: |
| |
| else |
| declare |
| function Get_Known_Bound (J : Nat) return Node_Id; |
| -- Returns the lower bound determined by operands J .. NN |
| |
| --------------------- |
| -- Get_Known_Bound -- |
| --------------------- |
| |
| function Get_Known_Bound (J : Nat) return Node_Id is |
| begin |
| if Is_Fixed_Length (J) or else J = NN then |
| return New_Copy_Tree (Opnd_Low_Bound (J)); |
| |
| else |
| return |
| Make_If_Expression (Loc, |
| Expressions => New_List ( |
| |
| Make_Op_Ne (Loc, |
| Left_Opnd => |
| New_Occurrence_Of (Var_Length (J), Loc), |
| Right_Opnd => |
| Make_Integer_Literal (Loc, 0)), |
| |
| New_Copy_Tree (Opnd_Low_Bound (J)), |
| Get_Known_Bound (J + 1))); |
| end if; |
| end Get_Known_Bound; |
| |
| begin |
| Ent := Make_Temporary (Loc, 'L'); |
| |
| Append_To (Actions, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Ent, |
| Constant_Present => True, |
| Object_Definition => New_Occurrence_Of (Ityp, Loc), |
| Expression => Get_Known_Bound (1))); |
| |
| Low_Bound := New_Occurrence_Of (Ent, Loc); |
| end; |
| end if; |
| |
| pragma Assert (Present (Low_Bound)); |
| |
| -- Now we can safely compute the upper bound, normally |
| -- Low_Bound + Length - 1. |
| |
| High_Bound := |
| To_Ityp |
| (Make_Op_Add (Loc, |
| Left_Opnd => To_Artyp (New_Copy_Tree (Low_Bound)), |
| Right_Opnd => |
| Make_Op_Subtract (Loc, |
| Left_Opnd => New_Copy_Tree (Aggr_Length (NN)), |
| Right_Opnd => Make_Artyp_Literal (1)))); |
| |
| -- Note that calculation of the high bound may cause overflow in some |
| -- very weird cases, so in the general case we need an overflow check on |
| -- the high bound. We can avoid this for the common case of string types |
| -- and other types whose index is Positive, since we chose a wider range |
| -- for the arithmetic type. If checks are suppressed we do not set the |
| -- flag, and possibly superfluous warnings will be omitted. |
| |
| if Istyp /= Standard_Positive |
| and then not Overflow_Checks_Suppressed (Istyp) |
| then |
| Activate_Overflow_Check (High_Bound); |
| end if; |
| |
| -- Handle the exceptional case where the result is null, in which case |
| -- case the bounds come from the last operand (so that we get the proper |
| -- bounds if the last operand is super-flat). |
| |
| if Result_May_Be_Null then |
| Low_Bound := |
| Make_If_Expression (Loc, |
| Expressions => New_List ( |
| Make_Op_Eq (Loc, |
| Left_Opnd => New_Copy_Tree (Aggr_Length (NN)), |
| Right_Opnd => Make_Artyp_Literal (0)), |
| Last_Opnd_Low_Bound, |
| Low_Bound)); |
| |
| High_Bound := |
| Make_If_Expression (Loc, |
| Expressions => New_List ( |
| Make_Op_Eq (Loc, |
| Left_Opnd => New_Copy_Tree (Aggr_Length (NN)), |
| Right_Opnd => Make_Artyp_Literal (0)), |
| Last_Opnd_High_Bound, |
| High_Bound)); |
| end if; |
| |
| -- Here is where we insert the saved up actions |
| |
| Insert_Actions (Cnode, Actions, Suppress => All_Checks); |
| |
| -- Now we construct an array object with appropriate bounds. We mark |
| -- the target as internal to prevent useless initialization when |
| -- Initialize_Scalars is enabled. Also since this is the actual result |
| -- entity, we make sure we have debug information for the result. |
| |
| Subtyp_Ind := |
| Make_Subtype_Indication (Loc, |
| Subtype_Mark => New_Occurrence_Of (Atyp, Loc), |
| Constraint => |
| Make_Index_Or_Discriminant_Constraint (Loc, |
| Constraints => New_List ( |
| Make_Range (Loc, |
| Low_Bound => Low_Bound, |
| High_Bound => High_Bound)))); |
| |
| Ent := Make_Temporary (Loc, 'S'); |
| Set_Is_Internal (Ent); |
| Set_Debug_Info_Needed (Ent); |
| |
| -- If we are concatenating strings and the current scope already uses |
| -- the secondary stack, allocate the resulting string also on the |
| -- secondary stack to avoid putting too much pressure on the primary |
| -- stack. |
| -- Don't do this if -gnatd.h is set, as this will break the wrapping of |
| -- Cnode in an Expression_With_Actions, see Expand_N_Op_Concat. |
| |
| if Atyp = Standard_String |
| and then Uses_Sec_Stack (Current_Scope) |
| and then RTE_Available (RE_SS_Pool) |
| and then not Debug_Flag_Dot_H |
| then |
| -- Generate: |
| -- subtype Axx is ...; |
| -- type Ayy is access Axx; |
| -- Rxx : Ayy := new <subtype> [storage_pool = ss_pool]; |
| -- Sxx : <subtype> renames Rxx.all; |
| |
| declare |
| Alloc : Node_Id; |
| ConstrT : constant Entity_Id := Make_Temporary (Loc, 'A'); |
| Acc_Typ : constant Entity_Id := Make_Temporary (Loc, 'A'); |
| Temp : Entity_Id; |
| |
| begin |
| Insert_Action (Cnode, |
| Make_Subtype_Declaration (Loc, |
| Defining_Identifier => ConstrT, |
| Subtype_Indication => Subtyp_Ind), |
| Suppress => All_Checks); |
| Freeze_Itype (ConstrT, Cnode); |
| |
| Insert_Action (Cnode, |
| Make_Full_Type_Declaration (Loc, |
| Defining_Identifier => Acc_Typ, |
| Type_Definition => |
| Make_Access_To_Object_Definition (Loc, |
| Subtype_Indication => New_Occurrence_Of (ConstrT, Loc))), |
| Suppress => All_Checks); |
| Alloc := |
| Make_Allocator (Loc, |
| Expression => New_Occurrence_Of (ConstrT, Loc)); |
| |
| -- Allocate on the secondary stack. This is currently done |
| -- only for type String, which normally doesn't have default |
| -- initialization, but we need to Set_No_Initialization in case |
| -- of Initialize_Scalars or Normalize_Scalars; otherwise, the |
| -- allocator will get transformed and will not use the secondary |
| -- stack. |
| |
| Set_Storage_Pool (Alloc, RTE (RE_SS_Pool)); |
| Set_Procedure_To_Call (Alloc, RTE (RE_SS_Allocate)); |
| Set_No_Initialization (Alloc); |
| |
| Temp := Make_Temporary (Loc, 'R', Alloc); |
| Insert_Action (Cnode, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Temp, |
| Object_Definition => New_Occurrence_Of (Acc_Typ, Loc), |
| Expression => Alloc), |
| Suppress => All_Checks); |
| |
| Insert_Action (Cnode, |
| Make_Object_Renaming_Declaration (Loc, |
| Defining_Identifier => Ent, |
| Subtype_Mark => New_Occurrence_Of (ConstrT, Loc), |
| Name => |
| Make_Explicit_Dereference (Loc, |
| Prefix => New_Occurrence_Of (Temp, Loc))), |
| Suppress => All_Checks); |
| end; |
| else |
| -- If the bound is statically known to be out of range, we do not |
| -- want to abort, we want a warning and a runtime constraint error. |
| -- Note that we have arranged that the result will not be treated as |
| -- a static constant, so we won't get an illegality during this |
| -- insertion. |
| -- We also enable checks (in particular range checks) in case the |
| -- bounds of Subtyp_Ind are out of range. |
| |
| Insert_Action (Cnode, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Ent, |
| Object_Definition => Subtyp_Ind)); |
| end if; |
| |
| -- If the result of the concatenation appears as the initializing |
| -- expression of an object declaration, we can just rename the |
| -- result, rather than copying it. |
| |
| Set_OK_To_Rename (Ent); |
| |
| -- Catch the static out of range case now |
| |
| if Raises_Constraint_Error (High_Bound) then |
| -- Kill warning generated for the declaration of the static out of |
| -- range high bound, and instead generate a Constraint_Error with |
| -- an appropriate specific message. |
| |
| Kill_Dead_Code (Declaration_Node (Entity (High_Bound))); |
| Apply_Compile_Time_Constraint_Error |
| (N => Cnode, |
| Msg => "concatenation result upper bound out of range??", |
| Reason => CE_Range_Check_Failed); |
| return; |
| end if; |
| |
| -- Now we will generate the assignments to do the actual concatenation |
| |
| -- There is one case in which we will not do this, namely when all the |
| -- following conditions are met: |
| |
| -- The result type is Standard.String |
| |
| -- There are nine or fewer retained (non-null) operands |
| |
| -- The optimization level is -O0 or the debug flag gnatd.C is set, |
| -- and the debug flag gnatd.c is not set. |
| |
| -- The corresponding System.Concat_n.Str_Concat_n routine is |
| -- available in the run time. |
| |
| -- If all these conditions are met then we generate a call to the |
| -- relevant concatenation routine. The purpose of this is to avoid |
| -- undesirable code bloat at -O0. |
| |
| -- If the concatenation is within the declaration of a library-level |
| -- object, we call the built-in concatenation routines to prevent code |
| -- bloat, regardless of the optimization level. This is space efficient |
| -- and prevents linking problems when units are compiled with different |
| -- optimization levels. |
| |
| if Atyp = Standard_String |
| and then NN in 2 .. 9 |
| and then (((Optimization_Level = 0 or else Debug_Flag_Dot_CC) |
| and then not Debug_Flag_Dot_C) |
| or else Library_Level_Target) |
| then |
| declare |
| RR : constant array (Nat range 2 .. 9) of RE_Id := |
| (RE_Str_Concat_2, |
| RE_Str_Concat_3, |
| RE_Str_Concat_4, |
| RE_Str_Concat_5, |
| RE_Str_Concat_6, |
| RE_Str_Concat_7, |
| RE_Str_Concat_8, |
| RE_Str_Concat_9); |
| |
| begin |
| if RTE_Available (RR (NN)) then |
| declare |
| Opnds : constant List_Id := |
| New_List (New_Occurrence_Of (Ent, Loc)); |
| |
| begin |
| for J in 1 .. NN loop |
| if Is_List_Member (Operands (J)) then |
| Remove (Operands (J)); |
| end if; |
| |
| if Base_Type (Etype (Operands (J))) = Ctyp then |
| Append_To (Opnds, |
| Make_Aggregate (Loc, |
| Component_Associations => New_List ( |
| Make_Component_Association (Loc, |
| Choices => New_List ( |
| Make_Integer_Literal (Loc, 1)), |
| Expression => Operands (J))))); |
| |
| else |
| Append_To (Opnds, Operands (J)); |
| end if; |
| end loop; |
| |
| Insert_Action (Cnode, |
| Make_Procedure_Call_Statement (Loc, |
| Name => New_Occurrence_Of (RTE (RR (NN)), Loc), |
| Parameter_Associations => Opnds)); |
| |
| Result := New_Occurrence_Of (Ent, Loc); |
| goto Done; |
| end; |
| end if; |
| end; |
| end if; |
| |
| -- Not special case so generate the assignments |
| |
| Known_Non_Null_Operand_Seen := False; |
| |
| for J in 1 .. NN loop |
| declare |
| Lo : constant Node_Id := |
| Make_Op_Add (Loc, |
| Left_Opnd => To_Artyp (New_Copy_Tree (Low_Bound)), |
| Right_Opnd => Aggr_Length (J - 1)); |
| |
| Hi : constant Node_Id := |
| Make_Op_Add (Loc, |
| Left_Opnd => To_Artyp (New_Copy_Tree (Low_Bound)), |
| Right_Opnd => |
| Make_Op_Subtract (Loc, |
| Left_Opnd => Aggr_Length (J), |
| Right_Opnd => Make_Artyp_Literal (1))); |
| |
| begin |
| -- Singleton case, simple assignment |
| |
| if Base_Type (Etype (Operands (J))) = Ctyp then |
| Known_Non_Null_Operand_Seen := True; |
| Insert_Action (Cnode, |
| Make_Assignment_Statement (Loc, |
| Name => |
| Make_Indexed_Component (Loc, |
| Prefix => New_Occurrence_Of (Ent, Loc), |
| Expressions => New_List (To_Ityp (Lo))), |
| Expression => Operands (J)), |
| Suppress => All_Checks); |
| |
| -- Array case, slice assignment, skipped when argument is fixed |
| -- length and known to be null. |
| |
| elsif (not Is_Fixed_Length (J)) or else (Fixed_Length (J) > 0) then |
| declare |
| Assign : Node_Id := |
| Make_Assignment_Statement (Loc, |
| Name => |
| Make_Slice (Loc, |
| Prefix => |
| New_Occurrence_Of (Ent, Loc), |
| Discrete_Range => |
| Make_Range (Loc, |
| Low_Bound => To_Ityp (Lo), |
| High_Bound => To_Ityp (Hi))), |
| Expression => Operands (J)); |
| begin |
| if Is_Fixed_Length (J) then |
| Known_Non_Null_Operand_Seen := True; |
| |
| elsif not Known_Non_Null_Operand_Seen then |
| |
| -- Here if operand length is not statically known and no |
| -- operand known to be non-null has been processed yet. |
| -- If operand length is 0, we do not need to perform the |
| -- assignment, and we must avoid the evaluation of the |
| -- high bound of the slice, since it may underflow if the |
| -- low bound is Ityp'First. |
| |
| Assign := |
| Make_Implicit_If_Statement (Cnode, |
| Condition => |
| Make_Op_Ne (Loc, |
| Left_Opnd => |
| New_Occurrence_Of (Var_Length (J), Loc), |
| Right_Opnd => Make_Integer_Literal (Loc, 0)), |
| Then_Statements => New_List (Assign)); |
| end if; |
| |
| Insert_Action (Cnode, Assign, Suppress => All_Checks); |
| end; |
| end if; |
| end; |
| end loop; |
| |
| -- Finally we build the result, which is a reference to the array object |
| |
| Result := New_Occurrence_Of (Ent, Loc); |
| |
| <<Done>> |
| pragma Assert (Present (Result)); |
| Rewrite (Cnode, Result); |
| Analyze_And_Resolve (Cnode, Atyp); |
| end Expand_Concatenate; |
| |
| --------------------------------------------------- |
| -- Expand_Membership_Minimize_Eliminate_Overflow -- |
| --------------------------------------------------- |
| |
| procedure Expand_Membership_Minimize_Eliminate_Overflow (N : Node_Id) is |
| pragma Assert (Nkind (N) = N_In); |
| -- Despite the name, this routine applies only to N_In, not to |
| -- N_Not_In. The latter is always rewritten as not (X in Y). |
| |
| Result_Type : constant Entity_Id := Etype (N); |
| -- Capture result type, may be a derived boolean type |
| |
| Loc : constant Source_Ptr := Sloc (N); |
| Lop : constant Node_Id := Left_Opnd (N); |
| Rop : constant Node_Id := Right_Opnd (N); |
| |
| -- Note: there are many referencs to Etype (Lop) and Etype (Rop). It |
| -- is thus tempting to capture these values, but due to the rewrites |
| -- that occur as a result of overflow checking, these values change |
| -- as we go along, and it is safe just to always use Etype explicitly. |
| |
| Restype : constant Entity_Id := Etype (N); |
| -- Save result type |
| |
| Lo, Hi : Uint; |
| -- Bounds in Minimize calls, not used currently |
| |
| LLIB : constant Entity_Id := Base_Type (Standard_Long_Long_Integer); |
| -- Entity for Long_Long_Integer'Base |
| |
| begin |
| Minimize_Eliminate_Overflows (Lop, Lo, Hi, Top_Level => False); |
| |
| -- If right operand is a subtype name, and the subtype name has no |
| -- predicate, then we can just replace the right operand with an |
| -- explicit range T'First .. T'Last, and use the explicit range code. |
| |
| if Nkind (Rop) /= N_Range |
| and then No (Predicate_Function (Etype (Rop))) |
| then |
| declare |
| Rtyp : constant Entity_Id := Etype (Rop); |
| begin |
| Rewrite (Rop, |
| Make_Range (Loc, |
| Low_Bound => |
| Make_Attribute_Reference (Loc, |
| Attribute_Name => Name_First, |
| Prefix => New_Occurrence_Of (Rtyp, Loc)), |
| High_Bound => |
| Make_Attribute_Reference (Loc, |
| Attribute_Name => Name_Last, |
| Prefix => New_Occurrence_Of (Rtyp, Loc)))); |
| Analyze_And_Resolve (Rop, Rtyp, Suppress => All_Checks); |
| end; |
| end if; |
| |
| -- Here for the explicit range case. Note that the bounds of the range |
| -- have not been processed for minimized or eliminated checks. |
| |
| if Nkind (Rop) = N_Range then |
| Minimize_Eliminate_Overflows |
| (Low_Bound (Rop), Lo, Hi, Top_Level => False); |
| Minimize_Eliminate_Overflows |
| (High_Bound (Rop), Lo, Hi, Top_Level => False); |
| |
| -- We have A in B .. C, treated as A >= B and then A <= C |
| |
| -- Bignum case |
| |
| if Is_RTE (Etype (Lop), RE_Bignum) |
| or else Is_RTE (Etype (Low_Bound (Rop)), RE_Bignum) |
| or else Is_RTE (Etype (High_Bound (Rop)), RE_Bignum) |
| then |
| declare |
| Blk : constant Node_Id := Make_Bignum_Block (Loc); |
| Bnn : constant Entity_Id := Make_Temporary (Loc, 'B', N); |
| L : constant Entity_Id := |
| Make_Defining_Identifier (Loc, Name_uL); |
| Lopnd : constant Node_Id := Convert_To_Bignum (Lop); |
| Lbound : constant Node_Id := |
| Convert_To_Bignum (Low_Bound (Rop)); |
| Hbound : constant Node_Id := |
| Convert_To_Bignum (High_Bound (Rop)); |
| |
| -- Now we rewrite the membership test node to look like |
| |
| -- do |
| -- Bnn : Result_Type; |
| -- declare |
| -- M : Mark_Id := SS_Mark; |
| -- L : Bignum := Lopnd; |
| -- begin |
| -- Bnn := Big_GE (L, Lbound) and then Big_LE (L, Hbound) |
| -- SS_Release (M); |
| -- end; |
| -- in |
| -- Bnn |
| -- end |
| |
| begin |
| -- Insert declaration of L into declarations of bignum block |
| |
| Insert_After |
| (Last (Declarations (Blk)), |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => L, |
| Object_Definition => |
| New_Occurrence_Of (RTE (RE_Bignum), Loc), |
| Expression => Lopnd)); |
| |
| -- Insert assignment to Bnn into expressions of bignum block |
| |
| Insert_Before |
| (First (Statements (Handled_Statement_Sequence (Blk))), |
| Make_Assignment_Statement (Loc, |
| Name => New_Occurrence_Of (Bnn, Loc), |
| Expression => |
| Make_And_Then (Loc, |
| Left_Opnd => |
| Make_Function_Call (Loc, |
| Name => |
| New_Occurrence_Of (RTE (RE_Big_GE), Loc), |
| Parameter_Associations => New_List ( |
| New_Occurrence_Of (L, Loc), |
| Lbound)), |
| |
| Right_Opnd => |
| Make_Function_Call (Loc, |
| Name => |
| New_Occurrence_Of (RTE (RE_Big_LE), Loc), |
| Parameter_Associations => New_List ( |
| New_Occurrence_Of (L, Loc), |
| Hbound))))); |
| |
| -- Now rewrite the node |
| |
| Rewrite (N, |
| Make_Expression_With_Actions (Loc, |
| Actions => New_List ( |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Bnn, |
| Object_Definition => |
| New_Occurrence_Of (Result_Type, Loc)), |
| Blk), |
| Expression => New_Occurrence_Of (Bnn, Loc))); |
| Analyze_And_Resolve (N, Result_Type); |
| return; |
| end; |
| |
| -- Here if no bignums around |
| |
| else |
| -- Case where types are all the same |
| |
| if Base_Type (Etype (Lop)) = Base_Type (Etype (Low_Bound (Rop))) |
| and then |
| Base_Type (Etype (Lop)) = Base_Type (Etype (High_Bound (Rop))) |
| then |
| null; |
| |
| -- If types are not all the same, it means that we have rewritten |
| -- at least one of them to be of type Long_Long_Integer, and we |
| -- will convert the other operands to Long_Long_Integer. |
| |
| else |
| Convert_To_And_Rewrite (LLIB, Lop); |
| Set_Analyzed (Lop, False); |
| Analyze_And_Resolve (Lop, LLIB); |
| |
| -- For the right operand, avoid unnecessary recursion into |
| -- this routine, we know that overflow is not possible. |
| |
| Convert_To_And_Rewrite (LLIB, Low_Bound (Rop)); |
| Convert_To_And_Rewrite (LLIB, High_Bound (Rop)); |
| Set_Analyzed (Rop, False); |
| Analyze_And_Resolve (Rop, LLIB, Suppress => Overflow_Check); |
| end if; |
| |
| -- Now the three operands are of the same signed integer type, |
| -- so we can use the normal expansion routine for membership, |
| -- setting the flag to prevent recursion into this procedure. |
| |
| Set_No_Minimize_Eliminate (N); |
| Expand_N_In (N); |
| end if; |
| |
| -- Right operand is a subtype name and the subtype has a predicate. We |
| -- have to make sure the predicate is checked, and for that we need to |
| -- use the standard N_In circuitry with appropriate types. |
| |
| else |
| pragma Assert (Present (Predicate_Function (Etype (Rop)))); |
| |
| -- If types are "right", just call Expand_N_In preventing recursion |
| |
| if Base_Type (Etype (Lop)) = Base_Type (Etype (Rop)) then |
| Set_No_Minimize_Eliminate (N); |
| Expand_N_In (N); |
| |
| -- Bignum case |
| |
| elsif Is_RTE (Etype (Lop), RE_Bignum) then |
| |
| -- For X in T, we want to rewrite our node as |
| |
| -- do |
| -- Bnn : Result_Type; |
| |
| -- declare |
| -- M : Mark_Id := SS_Mark; |
| -- Lnn : Long_Long_Integer'Base |
| -- Nnn : Bignum; |
| |
| -- begin |
| -- Nnn := X; |
| |
| -- if not Bignum_In_LLI_Range (Nnn) then |
| -- Bnn := False; |
| -- else |
| -- Lnn := From_Bignum (Nnn); |
| -- Bnn := |
| -- Lnn in LLIB (T'Base'First) .. LLIB (T'Base'Last) |
| -- and then T'Base (Lnn) in T; |
| -- end if; |
| |
| -- SS_Release (M); |
| -- end |
| -- in |
| -- Bnn |
| -- end |
| |
| -- A bit gruesome, but there doesn't seem to be a simpler way |
| |
| declare |
| Blk : constant Node_Id := Make_Bignum_Block (Loc); |
| Bnn : constant Entity_Id := Make_Temporary (Loc, 'B', N); |
| Lnn : constant Entity_Id := Make_Temporary (Loc, 'L', N); |
| Nnn : constant Entity_Id := Make_Temporary (Loc, 'N', N); |
| T : constant Entity_Id := Etype (Rop); |
| TB : constant Entity_Id := Base_Type (T); |
| Nin : Node_Id; |
| |
| begin |
| -- Mark the last membership operation to prevent recursion |
| |
| Nin := |
| Make_In (Loc, |
| Left_Opnd => Convert_To (TB, New_Occurrence_Of (Lnn, Loc)), |
| Right_Opnd => New_Occurrence_Of (T, Loc)); |
| Set_No_Minimize_Eliminate (Nin); |
| |
| -- Now decorate the block |
| |
| Insert_After |
| (Last (Declarations (Blk)), |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Lnn, |
| Object_Definition => New_Occurrence_Of (LLIB, Loc))); |
| |
| Insert_After |
| (Last (Declarations (Blk)), |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Nnn, |
| Object_Definition => |
| New_Occurrence_Of (RTE (RE_Bignum), Loc))); |
| |
| Insert_List_Before |
| (First (Statements (Handled_Statement_Sequence (Blk))), |
| New_List ( |
| Make_Assignment_Statement (Loc, |
| Name => New_Occurrence_Of (Nnn, Loc), |
| Expression => Relocate_Node (Lop)), |
| |
| Make_Implicit_If_Statement (N, |
| Condition => |
| Make_Op_Not (Loc, |
| Right_Opnd => |
| Make_Function_Call (Loc, |
| Name => |
| New_Occurrence_Of |
| (RTE (RE_Bignum_In_LLI_Range), Loc), |
| Parameter_Associations => New_List ( |
| New_Occurrence_Of (Nnn, Loc)))), |
| |
| Then_Statements => New_List ( |
| Make_Assignment_Statement (Loc, |
| Name => New_Occurrence_Of (Bnn, Loc), |
| Expression => |
| New_Occurrence_Of (Standard_False, Loc))), |
| |
| Else_Statements => New_List ( |
| Make_Assignment_Statement (Loc, |
| Name => New_Occurrence_Of (Lnn, Loc), |
| Expression => |
| Make_Function_Call (Loc, |
| Name => |
| New_Occurrence_Of (RTE (RE_From_Bignum), Loc), |
| Parameter_Associations => New_List ( |
| New_Occurrence_Of (Nnn, Loc)))), |
| |
| Make_Assignment_Statement (Loc, |
| Name => New_Occurrence_Of (Bnn, Loc), |
| Expression => |
| Make_And_Then (Loc, |
| Left_Opnd => |
| Make_In (Loc, |
| Left_Opnd => New_Occurrence_Of (Lnn, Loc), |
| Right_Opnd => |
| Make_Range (Loc, |
| Low_Bound => |
| Convert_To (LLIB, |
| Make_Attribute_Reference (Loc, |
| Attribute_Name => Name_First, |
| Prefix => |
| New_Occurrence_Of (TB, Loc))), |
| |
| High_Bound => |
| Convert_To (LLIB, |
| Make_Attribute_Reference (Loc, |
| Attribute_Name => Name_Last, |
| Prefix => |
| New_Occurrence_Of (TB, Loc))))), |
| |
| Right_Opnd => Nin)))))); |
| |
| -- Now we can do the rewrite |
| |
| Rewrite (N, |
| Make_Expression_With_Actions (Loc, |
| Actions => New_List ( |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Bnn, |
| Object_Definition => |
| New_Occurrence_Of (Result_Type, Loc)), |
| Blk), |
| Expression => New_Occurrence_Of (Bnn, Loc))); |
| Analyze_And_Resolve (N, Result_Type); |
| return; |
| end; |
| |
| -- Not bignum case, but types don't match (this means we rewrote the |
| -- left operand to be Long_Long_Integer). |
| |
| else |
| pragma Assert (Base_Type (Etype (Lop)) = LLIB); |
| |
| -- We rewrite the membership test as (where T is the type with |
| -- the predicate, i.e. the type of the right operand) |
| |
| -- Lop in LLIB (T'Base'First) .. LLIB (T'Base'Last) |
| -- and then T'Base (Lop) in T |
| |
| declare |
| T : constant Entity_Id := Etype (Rop); |
| TB : constant Entity_Id := Base_Type (T); |
| Nin : Node_Id; |
| |
| begin |
| -- The last membership test is marked to prevent recursion |
| |
| Nin := |
| Make_In (Loc, |
| Left_Opnd => Convert_To (TB, Duplicate_Subexpr (Lop)), |
| Right_Opnd => New_Occurrence_Of (T, Loc)); |
| Set_No_Minimize_Eliminate (Nin); |
| |
| -- Now do the rewrite |
| |
| Rewrite (N, |
| Make_And_Then (Loc, |
| Left_Opnd => |
| Make_In (Loc, |
| Left_Opnd => Lop, |
| Right_Opnd => |
| Make_Range (Loc, |
| Low_Bound => |
| Convert_To (LLIB, |
| Make_Attribute_Reference (Loc, |
| Attribute_Name => Name_First, |
| Prefix => |
| New_Occurrence_Of (TB, Loc))), |
| High_Bound => |
| Convert_To (LLIB, |
| Make_Attribute_Reference (Loc, |
| Attribute_Name => Name_Last, |
| Prefix => |
| New_Occurrence_Of (TB, Loc))))), |
| Right_Opnd => Nin)); |
| Set_Analyzed (N, False); |
| Analyze_And_Resolve (N, Restype); |
| end; |
| end if; |
| end if; |
| end Expand_Membership_Minimize_Eliminate_Overflow; |
| |
| --------------------------------- |
| -- Expand_Nonbinary_Modular_Op -- |
| --------------------------------- |
| |
| procedure Expand_Nonbinary_Modular_Op (N : Node_Id) is |
| Loc : constant Source_Ptr := Sloc (N); |
| Typ : constant Entity_Id := Etype (N); |
| |
| procedure Expand_Modular_Addition; |
| -- Expand the modular addition, handling the special case of adding a |
| -- constant. |
| |
| procedure Expand_Modular_Op; |
| -- Compute the general rule: (lhs OP rhs) mod Modulus |
| |
| procedure Expand_Modular_Subtraction; |
| -- Expand the modular addition, handling the special case of subtracting |
| -- a constant. |
| |
| ----------------------------- |
| -- Expand_Modular_Addition -- |
| ----------------------------- |
| |
| procedure Expand_Modular_Addition is |
| begin |
| -- If this is not the addition of a constant then compute it using |
| -- the general rule: (lhs + rhs) mod Modulus |
| |
| if Nkind (Right_Opnd (N)) /= N_Integer_Literal then |
| Expand_Modular_Op; |
| |
| -- If this is an addition of a constant, convert it to a subtraction |
| -- plus a conditional expression since we can compute it faster than |
| -- computing the modulus. |
| |
| -- modMinusRhs = Modulus - rhs |
| -- if lhs < modMinusRhs then lhs + rhs |
| -- else lhs - modMinusRhs |
| |
| else |
| declare |
| Mod_Minus_Right : constant Uint := |
| Modulus (Typ) - Intval (Right_Opnd (N)); |
| |
| Exprs : constant List_Id := New_List; |
| Cond_Expr : constant Node_Id := New_Op_Node (N_Op_Lt, Loc); |
| Then_Expr : constant Node_Id := New_Op_Node (N_Op_Add, Loc); |
| Else_Expr : constant Node_Id := New_Op_Node (N_Op_Subtract, |
| Loc); |
| begin |
| -- To prevent spurious visibility issues, convert all |
| -- operands to Standard.Unsigned. |
| |
| Set_Left_Opnd (Cond_Expr, |
| Unchecked_Convert_To (Standard_Unsigned, |
| New_Copy_Tree (Left_Opnd (N)))); |
| Set_Right_Opnd (Cond_Expr, |
| Make_Integer_Literal (Loc, Mod_Minus_Right)); |
| Append_To (Exprs, Cond_Expr); |
| |
| Set_Left_Opnd (Then_Expr, |
| Unchecked_Convert_To (Standard_Unsigned, |
| New_Copy_Tree (Left_Opnd (N)))); |
| Set_Right_Opnd (Then_Expr, |
| Make_Integer_Literal (Loc, Intval (Right_Opnd (N)))); |
| Append_To (Exprs, Then_Expr); |
| |
| Set_Left_Opnd (Else_Expr, |
| Unchecked_Convert_To (Standard_Unsigned, |
| New_Copy_Tree (Left_Opnd (N)))); |
| Set_Right_Opnd (Else_Expr, |
| Make_Integer_Literal (Loc, Mod_Minus_Right)); |
| Append_To (Exprs, Else_Expr); |
| |
| Rewrite (N, |
| Unchecked_Convert_To (Typ, |
| Make_If_Expression (Loc, Expressions => Exprs))); |
| end; |
| end if; |
| end Expand_Modular_Addition; |
| |
| ----------------------- |
| -- Expand_Modular_Op -- |
| ----------------------- |
| |
| procedure Expand_Modular_Op is |
| Op_Expr : constant Node_Id := New_Op_Node (Nkind (N), Loc); |
| Mod_Expr : constant Node_Id := New_Op_Node (N_Op_Mod, Loc); |
| |
| Target_Type : Entity_Id; |
| |
| begin |
| -- Convert nonbinary modular type operands into integer values. Thus |
| -- we avoid never-ending loops expanding them, and we also ensure |
| -- the back end never receives nonbinary modular type expressions. |
| |
| if Nkind (N) in N_Op_And | N_Op_Or | N_Op_Xor then |
| Set_Left_Opnd (Op_Expr, |
| Unchecked_Convert_To (Standard_Unsigned, |
| New_Copy_Tree (Left_Opnd (N)))); |
| Set_Right_Opnd (Op_Expr, |
| Unchecked_Convert_To (Standard_Unsigned, |
| New_Copy_Tree (Right_Opnd (N)))); |
| Set_Left_Opnd (Mod_Expr, |
| Unchecked_Convert_To (Standard_Integer, Op_Expr)); |
| |
| else |
| -- If the modulus of the type is larger than Integer'Last use a |
| -- larger type for the operands, to prevent spurious constraint |
| -- errors on large legal literals of the type. |
| |
| if Modulus (Etype (N)) > Int (Integer'Last) then |
| Target_Type := Standard_Long_Long_Integer; |
| else |
| Target_Type := Standard_Integer; |
| end if; |
| |
| Set_Left_Opnd (Op_Expr, |
| Unchecked_Convert_To (Target_Type, |
| New_Copy_Tree (Left_Opnd (N)))); |
| Set_Right_Opnd (Op_Expr, |
| Unchecked_Convert_To (Target_Type, |
| New_Copy_Tree (Right_Opnd (N)))); |
| |
| -- Link this node to the tree to analyze it |
| |
| -- If the parent node is an expression with actions we link it to |
| -- N since otherwise Force_Evaluation cannot identify if this node |
| -- comes from the Expression and rejects generating the temporary. |
| |
| if Nkind (Parent (N)) = N_Expression_With_Actions then |
| Set_Parent (Op_Expr, N); |
| |
| -- Common case |
| |
| else |
| Set_Parent (Op_Expr, Parent (N)); |
| end if; |
| |
| Analyze (Op_Expr); |
| |
| -- Force generating a temporary because in the expansion of this |
| -- expression we may generate code that performs this computation |
| -- several times. |
| |
| Force_Evaluation (Op_Expr, Mode => Strict); |
| |
| Set_Left_Opnd (Mod_Expr, Op_Expr); |
| end if; |
| |
| Set_Right_Opnd (Mod_Expr, |
| Make_Integer_Literal (Loc, Modulus (Typ))); |
| |
| Rewrite (N, |
| Unchecked_Convert_To (Typ, Mod_Expr)); |
| end Expand_Modular_Op; |
| |
| -------------------------------- |
| -- Expand_Modular_Subtraction -- |
| -------------------------------- |
| |
| procedure Expand_Modular_Subtraction is |
| begin |
| -- If this is not the addition of a constant then compute it using |
| -- the general rule: (lhs + rhs) mod Modulus |
| |
| if Nkind (Right_Opnd (N)) /= N_Integer_Literal then |
| Expand_Modular_Op; |
| |
| -- If this is an addition of a constant, convert it to a subtraction |
| -- plus a conditional expression since we can compute it faster than |
| -- computing the modulus. |
| |
| -- modMinusRhs = Modulus - rhs |
| -- if lhs < rhs then lhs + modMinusRhs |
| -- else lhs - rhs |
| |
| else |
| declare |
| Mod_Minus_Right : constant Uint := |
| Modulus (Typ) - Intval (Right_Opnd (N)); |
| |
| Exprs : constant List_Id := New_List; |
| Cond_Expr : constant Node_Id := New_Op_Node (N_Op_Lt, Loc); |
| Then_Expr : constant Node_Id := New_Op_Node (N_Op_Add, Loc); |
| Else_Expr : constant Node_Id := New_Op_Node (N_Op_Subtract, |
| Loc); |
| begin |
| Set_Left_Opnd (Cond_Expr, |
| Unchecked_Convert_To (Standard_Unsigned, |
| New_Copy_Tree (Left_Opnd (N)))); |
| Set_Right_Opnd (Cond_Expr, |
| Make_Integer_Literal (Loc, Intval (Right_Opnd (N)))); |
| Append_To (Exprs, Cond_Expr); |
| |
| Set_Left_Opnd (Then_Expr, |
| Unchecked_Convert_To (Standard_Unsigned, |
| New_Copy_Tree (Left_Opnd (N)))); |
| Set_Right_Opnd (Then_Expr, |
| Make_Integer_Literal (Loc, Mod_Minus_Right)); |
| Append_To (Exprs, Then_Expr); |
| |
| Set_Left_Opnd (Else_Expr, |
| Unchecked_Convert_To (Standard_Unsigned, |
| New_Copy_Tree (Left_Opnd (N)))); |
| Set_Right_Opnd (Else_Expr, |
| Unchecked_Convert_To (Standard_Unsigned, |
| New_Copy_Tree (Right_Opnd (N)))); |
| Append_To (Exprs, Else_Expr); |
| |
| Rewrite (N, |
| Unchecked_Convert_To (Typ, |
| |