X-Git-Url: http://git.sourceforge.jp/view?a=blobdiff_plain;f=gcc%2Fada%2Fexp_util.adb;h=c450b677faf240f597e92c068e63d3568c03ec59;hb=20d2f5309ee374943308566fa4f174cd3312853b;hp=c6924e97cb68085686d67e675734e26f9dace5a2;hpb=76a1c25b5ba521501bd8e2ce30573c34cc0da1fb;p=pf3gnuchains%2Fgcc-fork.git diff --git a/gcc/ada/exp_util.adb b/gcc/ada/exp_util.adb index c6924e97cb6..c450b677faf 100644 --- a/gcc/ada/exp_util.adb +++ b/gcc/ada/exp_util.adb @@ -6,18 +6,17 @@ -- -- -- B o d y -- -- -- --- Copyright (C) 1992-2005, Free Software Foundation, Inc. -- +-- Copyright (C) 1992-2009, 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 2, or (at your option) any later ver- -- +-- 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 COPYING. If not, write -- --- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, -- --- Boston, MA 02110-1301, USA. -- +-- 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. -- @@ -26,23 +25,25 @@ with Atree; use Atree; with Checks; use Checks; +with Debug; use Debug; with Einfo; use Einfo; with Elists; use Elists; with Errout; use Errout; with Exp_Aggr; use Exp_Aggr; +with Exp_Ch6; use Exp_Ch6; with Exp_Ch7; use Exp_Ch7; -with Hostparm; use Hostparm; with Inline; use Inline; with Itypes; use Itypes; with Lib; use Lib; -with Namet; use Namet; with Nlists; use Nlists; with Nmake; use Nmake; with Opt; use Opt; with Restrict; use Restrict; with Rident; use Rident; with Sem; use Sem; +with Sem_Aux; use Sem_Aux; with Sem_Ch8; use Sem_Ch8; +with Sem_SCIL; use Sem_SCIL; with Sem_Eval; use Sem_Eval; with Sem_Res; use Sem_Res; with Sem_Type; use Sem_Type; @@ -90,8 +91,8 @@ package body Exp_Util is Pos : out Entity_Id; Prefix : Entity_Id; Sum : Node_Id; - Decls : in out List_Id; - Stats : in out List_Id); + Decls : List_Id; + Stats : List_Id); -- Common processing for Task_Array_Image and Task_Record_Image. -- Create local variables and assign prefix of name to result string. @@ -126,8 +127,20 @@ package body Exp_Util is Literal_Typ : Entity_Id) return Node_Id; -- Produce a Range node whose bounds are: -- Low_Bound (Literal_Type) .. - -- Low_Bound (Literal_Type) + Length (Literal_Typ) - 1 + -- Low_Bound (Literal_Type) + (Length (Literal_Typ) - 1) -- this is used for expanding declarations like X : String := "sdfgdfg"; + -- + -- If the index type of the target array is not integer, we generate: + -- Low_Bound (Literal_Type) .. + -- Literal_Type'Val + -- (Literal_Type'Pos (Low_Bound (Literal_Type)) + -- + (Length (Literal_Typ) -1)) + + function Make_Non_Empty_Check + (Loc : Source_Ptr; + N : Node_Id) return Node_Id; + -- Produce a boolean expression checking that the unidimensional array + -- node N is not empty. function New_Class_Wide_Subtype (CW_Typ : Entity_Id; @@ -243,9 +256,8 @@ package body Exp_Util is -- to reset its type, since Standard.Boolean is just fine, and -- such operations always do Adjust_Condition on their operands. - elsif KP in N_Op_Boolean - or else KP = N_And_Then - or else KP = N_Or_Else + elsif KP in N_Op_Boolean + or else KP in N_Short_Circuit or else KP = N_Op_Not then return; @@ -267,13 +279,13 @@ package body Exp_Util is -------------------------- procedure Append_Freeze_Action (T : Entity_Id; N : Node_Id) is - Fnode : Node_Id := Freeze_Node (T); + Fnode : Node_Id; begin Ensure_Freeze_Node (T); Fnode := Freeze_Node (T); - if not Present (Actions (Fnode)) then + if No (Actions (Fnode)) then Set_Actions (Fnode, New_List); end if; @@ -331,7 +343,7 @@ package body Exp_Util is -- component, whose prefix is the outer variable of the array type. -- The n-dimensional array type has known indices Index, Index2... -- Id_Ref is an indexed component form created by the enclosing init proc. - -- Its successive indices are Val1, Val2,.. which are the loop variables + -- Its successive indices are Val1, Val2, ... which are the loop variables -- in the loops that call the individual task init proc on each component. -- The generated function has the following structure: @@ -401,8 +413,8 @@ package body Exp_Util is T : Entity_Id; -- Entity for name at one index position - Decls : List_Id := New_List; - Stats : List_Id := New_List; + Decls : constant List_Id := New_List; + Stats : constant List_Id := New_List; begin Pref := Make_Defining_Identifier (Loc, New_Internal_Name ('P')); @@ -579,9 +591,10 @@ package body Exp_Util is ---------------------------- function Build_Task_Image_Decls - (Loc : Source_Ptr; - Id_Ref : Node_Id; - A_Type : Entity_Id) return List_Id + (Loc : Source_Ptr; + Id_Ref : Node_Id; + A_Type : Entity_Id; + In_Init_Proc : Boolean := False) return List_Id is Decls : constant List_Id := New_List; T_Id : Entity_Id := Empty; @@ -650,6 +663,10 @@ package body Exp_Util is Append (Fun, Decls); Expr := Make_Function_Call (Loc, Name => New_Occurrence_Of (Defining_Entity (Fun), Loc)); + + if not In_Init_Proc and then VM_Target = No_VM then + Set_Uses_Sec_Stack (Defining_Entity (Fun)); + end if; end if; Decl := Make_Object_Declaration (Loc, @@ -676,7 +693,7 @@ package body Exp_Util is begin Append_To (Stats, - Make_Return_Statement (Loc, + Make_Simple_Return_Statement (Loc, Expression => New_Occurrence_Of (Res, Loc))); Spec := Make_Function_Specification (Loc, @@ -687,8 +704,6 @@ package body Exp_Util is -- Calls to 'Image use the secondary stack, which must be cleaned -- up after the task name is built. - Set_Uses_Sec_Stack (Defining_Unit_Name (Spec)); - return Make_Subprogram_Body (Loc, Specification => Spec, Declarations => Decls, @@ -707,8 +722,8 @@ package body Exp_Util is Pos : out Entity_Id; Prefix : Entity_Id; Sum : Node_Id; - Decls : in out List_Id; - Stats : in out List_Id) + Decls : List_Id; + Stats : List_Id) is begin Len := Make_Defining_Identifier (Loc, New_Internal_Name ('L')); @@ -803,8 +818,8 @@ package body Exp_Util is Sel : Entity_Id; -- Entity for selector name - Decls : List_Id := New_List; - Stats : List_Id := New_List; + Decls : constant List_Id := New_List; + Stats : constant List_Id := New_List; begin Pref := Make_Defining_Identifier (Loc, New_Internal_Name ('P')); @@ -899,10 +914,12 @@ package body Exp_Util is ---------------------------------- function Component_May_Be_Bit_Aligned (Comp : Entity_Id) return Boolean is + UT : constant Entity_Id := Underlying_Type (Etype (Comp)); + begin - -- If no component clause, then everything is fine, since the - -- back end never bit-misaligns by default, even if there is - -- a pragma Packed for the record. + -- If no component clause, then everything is fine, since the back end + -- never bit-misaligns by default, even if there is a pragma Packed for + -- the record. if No (Component_Clause (Comp)) then return False; @@ -910,23 +927,23 @@ package body Exp_Util is -- It is only array and record types that cause trouble - if not Is_Record_Type (Etype (Comp)) - and then not Is_Array_Type (Etype (Comp)) + if not Is_Record_Type (UT) + and then not Is_Array_Type (UT) then return False; - -- If we know that we have a small (64 bits or less) record - -- or bit-packed array, then everything is fine, since the - -- back end can handle these cases correctly. + -- If we know that we have a small (64 bits or less) record or small + -- bit-packed array, then everything is fine, since the back end can + -- handle these cases correctly. elsif Esize (Comp) <= 64 - and then (Is_Record_Type (Etype (Comp)) - or else Is_Bit_Packed_Array (Etype (Comp))) + and then (Is_Record_Type (UT) + or else Is_Bit_Packed_Array (UT)) then return False; - -- Otherwise if the component is not byte aligned, we - -- know we have the nasty unaligned case. + -- Otherwise if the component is not byte aligned, we know we have the + -- nasty unaligned case. elsif Normalized_First_Bit (Comp) /= Uint_0 or else Esize (Comp) mod System_Storage_Unit /= Uint_0 @@ -940,6 +957,50 @@ package body Exp_Util is end if; end Component_May_Be_Bit_Aligned; + ----------------------------------- + -- Corresponding_Runtime_Package -- + ----------------------------------- + + function Corresponding_Runtime_Package (Typ : Entity_Id) return RTU_Id is + Pkg_Id : RTU_Id := RTU_Null; + + begin + pragma Assert (Is_Concurrent_Type (Typ)); + + if Ekind (Typ) in Protected_Kind then + if Has_Entries (Typ) + or else Has_Interrupt_Handler (Typ) + or else (Has_Attach_Handler (Typ) + and then not Restricted_Profile) + + -- A protected type without entries that covers an interface and + -- overrides the abstract routines with protected procedures is + -- considered equivalent to a protected type with entries in the + -- context of dispatching select statements. It is sufficient to + -- check for the presence of an interface list in the declaration + -- node to recognize this case. + + or else Present (Interface_List (Parent (Typ))) + then + if Abort_Allowed + or else Restriction_Active (No_Entry_Queue) = False + or else Number_Entries (Typ) > 1 + or else (Has_Attach_Handler (Typ) + and then not Restricted_Profile) + then + Pkg_Id := System_Tasking_Protected_Objects_Entries; + else + Pkg_Id := System_Tasking_Protected_Objects_Single_Entry; + end if; + + else + Pkg_Id := System_Tasking_Protected_Objects; + end if; + end if; + + return Pkg_Id; + end Corresponding_Runtime_Package; + ------------------------------- -- Convert_To_Actual_Subtype -- ------------------------------- @@ -1050,39 +1111,33 @@ package body Exp_Util is procedure Ensure_Defined (Typ : Entity_Id; N : Node_Id) is IR : Node_Id; - P : Node_Id; begin - if Is_Itype (Typ) then + -- An itype reference must only be created if this is a local + -- itype, so that gigi can elaborate it on the proper objstack. + + if Is_Itype (Typ) + and then Scope (Typ) = Current_Scope + then IR := Make_Itype_Reference (Sloc (N)); Set_Itype (IR, Typ); - - if not In_Open_Scopes (Scope (Typ)) - and then Is_Subprogram (Current_Scope) - and then Scope (Current_Scope) /= Standard_Standard - then - -- Insert node in front of subprogram, to avoid scope anomalies - -- in gigi. - - P := Parent (N); - while Present (P) - and then Nkind (P) /= N_Subprogram_Body - loop - P := Parent (P); - end loop; - - if Present (P) then - Insert_Action (P, IR); - else - Insert_Action (N, IR); - end if; - - else - Insert_Action (N, IR); - end if; + Insert_Action (N, IR); end if; end Ensure_Defined; + -------------------- + -- Entry_Names_OK -- + -------------------- + + function Entry_Names_OK return Boolean is + begin + return + not Restricted_Profile + and then not Global_Discard_Names + and then not Restriction_Active (No_Implicit_Heap_Allocations) + and then not Restriction_Active (No_Local_Allocators); + end Entry_Names_OK; + --------------------- -- Evolve_And_Then -- --------------------- @@ -1123,8 +1178,8 @@ package body Exp_Util is -- objects which are constrained by an initial expression. Basically it -- transforms an unconstrained subtype indication into a constrained one. -- The expression may also be transformed in certain cases in order to - -- avoid multiple evaulation. In the static allocation case, the general - -- scheme is : + -- avoid multiple evaluation. In the static allocation case, the general + -- scheme is: -- Val : T := Expr; @@ -1194,7 +1249,7 @@ package body Exp_Util is Constraints => New_List (New_Reference_To (Slice_Type, Loc))))); - -- This subtype indication may be used later for contraint checks + -- This subtype indication may be used later for constraint checks -- we better make sure that if a variable was used as a bound of -- of the original slice, its value is frozen. @@ -1265,178 +1320,156 @@ package body Exp_Util is Rewrite (Subtype_Indic, New_Reference_To (T, Loc)); - -- nothing needs to be done for private types with unknown discriminants - -- if the underlying type is not an unconstrained composite type. + -- Nothing needs to be done for private types with unknown discriminants + -- if the underlying type is not an unconstrained composite type or it + -- is an unchecked union. elsif Is_Private_Type (Unc_Type) and then Has_Unknown_Discriminants (Unc_Type) and then (not Is_Composite_Type (Underlying_Type (Unc_Type)) - or else Is_Constrained (Underlying_Type (Unc_Type))) + or else Is_Constrained (Underlying_Type (Unc_Type)) + or else Is_Unchecked_Union (Underlying_Type (Unc_Type))) then null; - -- Nothing to be done for derived types with unknown discriminants if - -- the parent type also has unknown discriminants. + -- Case of derived type with unknown discriminants where the parent type + -- also has unknown discriminants. elsif Is_Record_Type (Unc_Type) and then not Is_Class_Wide_Type (Unc_Type) and then Has_Unknown_Discriminants (Unc_Type) and then Has_Unknown_Discriminants (Underlying_Type (Unc_Type)) then - null; - - -- Nothing to be done if the type of the expression is limited, because - -- in this case the expression cannot be copied, and its use can only - -- be by reference and there is no need for the actual subtype. + -- Nothing to be done if no underlying record view available - elsif Is_Limited_Type (Exp_Typ) then - null; + if No (Underlying_Record_View (Unc_Type)) then + null; - else - Remove_Side_Effects (Exp); - Rewrite (Subtype_Indic, - Make_Subtype_From_Expr (Exp, Unc_Type)); - end if; - end Expand_Subtype_From_Expr; + -- Otherwise use the Underlying_Record_View to create the proper + -- constrained subtype for an object of a derived type with unknown + -- discriminants. - -------------------------------- - -- Find_Implemented_Interface -- - -------------------------------- + else + Remove_Side_Effects (Exp); + Rewrite (Subtype_Indic, + Make_Subtype_From_Expr (Exp, Underlying_Record_View (Unc_Type))); + end if; - -- Given the following code (XXX denotes irrelevant value): + -- Renamings of class-wide interface types require no equivalent + -- constrained type declarations because we only need to reference + -- the tag component associated with the interface. - -- type Limd_Iface is limited interface; - -- type Prot_Iface is protected interface; - -- type Sync_Iface is synchronized interface; + elsif Present (N) + and then Nkind (N) = N_Object_Renaming_Declaration + and then Is_Interface (Unc_Type) + then + pragma Assert (Is_Class_Wide_Type (Unc_Type)); + null; - -- type Parent_Subtype is new Limd_Iface and Sync_Iface with ... - -- type Child_Subtype is new Parent_Subtype and Prot_Iface with ... + -- In Ada95, nothing to be done if the type of the expression is + -- limited, because in this case the expression cannot be copied, + -- and its use can only be by reference. - -- The following calls will return the following values: + -- In Ada2005, the context can be an object declaration whose expression + -- is a function that returns in place. If the nominal subtype has + -- unknown discriminants, the call still provides constraints on the + -- object, and we have to create an actual subtype from it. - -- Find_Implemented_Interface - -- (Child_Subtype, Synchronized_Interface, False) -> Empty + -- If the type is class-wide, the expression is dynamically tagged and + -- we do not create an actual subtype either. Ditto for an interface. - -- Find_Implemented_Interface - -- (Child_Subtype, Synchronized_Interface, True) -> Sync_Iface + elsif Is_Limited_Type (Exp_Typ) + and then + (Is_Class_Wide_Type (Exp_Typ) + or else Is_Interface (Exp_Typ) + or else not Has_Unknown_Discriminants (Exp_Typ) + or else not Is_Composite_Type (Unc_Type)) + then + null; - -- Find_Implemented_Interface - -- (Child_Subtype, Any_Synchronized_Interface, XXX) -> Prot_Iface + -- For limited objects initialized with build in place function calls, + -- nothing to be done; otherwise we prematurely introduce an N_Reference + -- node in the expression initializing the object, which breaks the + -- circuitry that detects and adds the additional arguments to the + -- called function. - -- Find_Implemented_Interface - -- (Child_Subtype, Any_Limited_Interface, XXX) -> Prot_Iface + elsif Is_Build_In_Place_Function_Call (Exp) then + null; - function Find_Implemented_Interface - (Typ : Entity_Id; - Kind : Interface_Kind; - Check_Parent : Boolean := False) return Entity_Id - is - Iface_Elmt : Elmt_Id; + else + Remove_Side_Effects (Exp); + Rewrite (Subtype_Indic, + Make_Subtype_From_Expr (Exp, Unc_Type)); + end if; + end Expand_Subtype_From_Expr; - function Interface_In_Kind - (I : Entity_Id; - Kind : Interface_Kind) return Boolean; - -- Determine whether an interface falls into a specified kind + -------------------- + -- Find_Init_Call -- + -------------------- - ----------------------- - -- Interface_In_Kind -- - ----------------------- + function Find_Init_Call + (Var : Entity_Id; + Rep_Clause : Node_Id) return Node_Id + is + Typ : constant Entity_Id := Etype (Var); - function Interface_In_Kind - (I : Entity_Id; - Kind : Interface_Kind) return Boolean is - begin - if Is_Limited_Interface (I) - and then (Kind = Any_Interface - or else Kind = Any_Limited_Interface - or else Kind = Limited_Interface) - then - return True; + Init_Proc : Entity_Id; + -- Initialization procedure for Typ - elsif Is_Protected_Interface (I) - and then (Kind = Any_Interface - or else Kind = Any_Limited_Interface - or else Kind = Any_Synchronized_Interface - or else Kind = Protected_Interface) - then - return True; + function Find_Init_Call_In_List (From : Node_Id) return Node_Id; + -- Look for init call for Var starting at From and scanning the + -- enclosing list until Rep_Clause or the end of the list is reached. - elsif Is_Synchronized_Interface (I) - and then (Kind = Any_Interface - or else Kind = Any_Limited_Interface - or else Kind = Synchronized_Interface) - then - return True; + ---------------------------- + -- Find_Init_Call_In_List -- + ---------------------------- - elsif Is_Task_Interface (I) - and then (Kind = Any_Interface - or else Kind = Any_Limited_Interface - or else Kind = Any_Synchronized_Interface - or else Kind = Task_Interface) - then - return True; + function Find_Init_Call_In_List (From : Node_Id) return Node_Id is + Init_Call : Node_Id; + begin + Init_Call := From; - -- Regular interface. This should be the last kind to check since - -- all of the previous cases have their Is_Interface flags set. + while Present (Init_Call) and then Init_Call /= Rep_Clause loop + if Nkind (Init_Call) = N_Procedure_Call_Statement + and then Is_Entity_Name (Name (Init_Call)) + and then Entity (Name (Init_Call)) = Init_Proc + then + return Init_Call; + end if; + Next (Init_Call); + end loop; - elsif Is_Interface (I) - and then (Kind = Any_Interface - or else Kind = Iface) - then - return True; + return Empty; + end Find_Init_Call_In_List; - else - return False; - end if; - end Interface_In_Kind; + Init_Call : Node_Id; - -- Start of processing for Find_Implemented_Interface + -- Start of processing for Find_Init_Call begin - if not Is_Tagged_Type (Typ) then - return Empty; - end if; + if not Has_Non_Null_Base_Init_Proc (Typ) then + -- No init proc for the type, so obviously no call to be found - -- Implementations of the form: - -- Typ is new Interface ... - - if Is_Interface (Etype (Typ)) - and then Interface_In_Kind (Etype (Typ), Kind) - then - return Etype (Typ); + return Empty; end if; - -- Implementations of the form: - -- Typ is new Typ_Parent and Interface ... + Init_Proc := Base_Init_Proc (Typ); - if Present (Abstract_Interfaces (Typ)) then - Iface_Elmt := First_Elmt (Abstract_Interfaces (Typ)); - while Present (Iface_Elmt) loop - if Interface_In_Kind (Node (Iface_Elmt), Kind) then - return Node (Iface_Elmt); - end if; + -- First scan the list containing the declaration of Var - Iface_Elmt := Next_Elmt (Iface_Elmt); - end loop; - end if; + Init_Call := Find_Init_Call_In_List (From => Next (Parent (Var))); - -- Typ is a derived type and may implement a limited interface - -- through its parent subtype. Check the parent subtype as well - -- as any interfaces explicitly implemented at this level. + -- If not found, also look on Var's freeze actions list, if any, since + -- the init call may have been moved there (case of an address clause + -- applying to Var). - if Check_Parent - and then Ekind (Typ) = E_Record_Type - and then Present (Parent_Subtype (Typ)) - then - return Find_Implemented_Interface ( - Parent_Subtype (Typ), Kind, Check_Parent); + if No (Init_Call) and then Present (Freeze_Node (Var)) then + Init_Call := Find_Init_Call_In_List + (First (Actions (Freeze_Node (Var)))); end if; - -- Typ does not implement a limited interface either at this level or - -- in any of its parent subtypes. - - return Empty; - end Find_Implemented_Interface; + return Init_Call; + end Find_Init_Call; ------------------------ -- Find_Interface_ADT -- @@ -1444,62 +1477,14 @@ package body Exp_Util is function Find_Interface_ADT (T : Entity_Id; - Iface : Entity_Id) return Entity_Id + Iface : Entity_Id) return Elmt_Id is - ADT : Elmt_Id; - Found : Boolean := False; - Typ : Entity_Id := T; - - procedure Find_Secondary_Table (Typ : Entity_Id); - -- Internal subprogram used to recursively climb to the ancestors - - -------------------------- - -- Find_Secondary_Table -- - -------------------------- - - procedure Find_Secondary_Table (Typ : Entity_Id) is - AI_Elmt : Elmt_Id; - AI : Node_Id; - - begin - -- Climb to the ancestor (if any) handling private types - - if Present (Full_View (Etype (Typ))) then - if Full_View (Etype (Typ)) /= Typ then - Find_Secondary_Table (Full_View (Etype (Typ))); - end if; - - elsif Etype (Typ) /= Typ then - Find_Secondary_Table (Etype (Typ)); - end if; - - -- If we already found it there is nothing else to do - - if Found then - return; - end if; - - if Present (Abstract_Interfaces (Typ)) - and then not Is_Empty_Elmt_List (Abstract_Interfaces (Typ)) - then - AI_Elmt := First_Elmt (Abstract_Interfaces (Typ)); - while Present (AI_Elmt) loop - AI := Node (AI_Elmt); - - if AI = Iface or else Is_Ancestor (Iface, AI) then - Found := True; - return; - end if; - - Next_Elmt (ADT); - Next_Elmt (AI_Elmt); - end loop; - end if; - end Find_Secondary_Table; - - -- Start of processing for Find_Interface_Tag + ADT : Elmt_Id; + Typ : Entity_Id := T; begin + pragma Assert (Is_Interface (Iface)); + -- Handle private types if Has_Private_Declaration (Typ) @@ -1516,17 +1501,31 @@ package body Exp_Util is -- Handle task and protected types implementing interfaces - if Ekind (Typ) = E_Protected_Type - or else Ekind (Typ) = E_Task_Type - then + if Is_Concurrent_Type (Typ) then Typ := Corresponding_Record_Type (Typ); end if; - ADT := Next_Elmt (First_Elmt (Access_Disp_Table (Typ))); - pragma Assert (Present (Node (ADT))); - Find_Secondary_Table (Typ); - pragma Assert (Found); - return Node (ADT); + pragma Assert + (not Is_Class_Wide_Type (Typ) + and then Ekind (Typ) /= E_Incomplete_Type); + + if Is_Ancestor (Iface, Typ) then + return First_Elmt (Access_Disp_Table (Typ)); + + else + ADT := + Next_Elmt (Next_Elmt (First_Elmt (Access_Disp_Table (Typ)))); + while Present (ADT) + and then Present (Related_Type (Node (ADT))) + and then Related_Type (Node (ADT)) /= Iface + and then not Is_Ancestor (Iface, Related_Type (Node (ADT))) + loop + Next_Elmt (ADT); + end loop; + + pragma Assert (Present (Related_Type (Node (ADT)))); + return ADT; + end if; end Find_Interface_ADT; ------------------------ @@ -1534,34 +1533,29 @@ package body Exp_Util is ------------------------ function Find_Interface_Tag - (T : Entity_Id; - Iface : Entity_Id) return Entity_Id + (T : Entity_Id; + Iface : Entity_Id) return Entity_Id is AI_Tag : Entity_Id; - Found : Boolean := False; + Found : Boolean := False; Typ : Entity_Id := T; - procedure Find_Tag (Typ : in Entity_Id); + procedure Find_Tag (Typ : Entity_Id); -- Internal subprogram used to recursively climb to the ancestors - ----------------- - -- Find_AI_Tag -- - ----------------- + -------------- + -- Find_Tag -- + -------------- - procedure Find_Tag (Typ : in Entity_Id) is + procedure Find_Tag (Typ : Entity_Id) is AI_Elmt : Elmt_Id; AI : Node_Id; begin - -- Check if the interface is an immediate ancestor of the type and - -- therefore shares the main tag. + -- This routine does not handle the case in which the interface is an + -- ancestor of Typ. That case is handled by the enclosing subprogram. - if Typ = Iface then - pragma Assert (Etype (First_Tag_Component (Typ)) = RTE (RE_Tag)); - AI_Tag := First_Tag_Component (Typ); - Found := True; - return; - end if; + pragma Assert (Typ /= Iface); -- Climb to the root type handling private types @@ -1577,8 +1571,8 @@ package body Exp_Util is -- Traverse the list of interfaces implemented by the type if not Found - and then Present (Abstract_Interfaces (Typ)) - and then not (Is_Empty_Elmt_List (Abstract_Interfaces (Typ))) + and then Present (Interfaces (Typ)) + and then not (Is_Empty_Elmt_List (Interfaces (Typ))) then -- Skip the tag associated with the primary table @@ -1586,7 +1580,7 @@ package body Exp_Util is AI_Tag := Next_Tag_Component (First_Tag_Component (Typ)); pragma Assert (Present (AI_Tag)); - AI_Elmt := First_Elmt (Abstract_Interfaces (Typ)); + AI_Elmt := First_Elmt (Interfaces (Typ)); while Present (AI_Elmt) loop AI := Node (AI_Elmt); @@ -1606,6 +1600,18 @@ package body Exp_Util is begin pragma Assert (Is_Interface (Iface)); + -- Handle access types + + if Is_Access_Type (Typ) then + Typ := Directly_Designated_Type (Typ); + end if; + + -- Handle class-wide types + + if Is_Class_Wide_Type (Typ) then + Typ := Root_Type (Typ); + end if; + -- Handle private types if Has_Private_Declaration (Typ) @@ -1614,10 +1620,11 @@ package body Exp_Util is Typ := Full_View (Typ); end if; - -- Handle access types + -- Handle entities from the limited view - if Is_Access_Type (Typ) then - Typ := Directly_Designated_Type (Typ); + if Ekind (Typ) = E_Incomplete_Type then + pragma Assert (Present (Non_Limited_View (Typ))); + Typ := Non_Limited_View (Typ); end if; -- Handle task and protected types implementing interfaces @@ -1626,20 +1633,20 @@ package body Exp_Util is Typ := Corresponding_Record_Type (Typ); end if; - if Is_Class_Wide_Type (Typ) then - Typ := Etype (Typ); - end if; + -- If the interface is an ancestor of the type, then it shared the + -- primary dispatch table. - -- Handle entities from the limited view + if Is_Ancestor (Iface, Typ) then + pragma Assert (Etype (First_Tag_Component (Typ)) = RTE (RE_Tag)); + return First_Tag_Component (Typ); - if Ekind (Typ) = E_Incomplete_Type then - pragma Assert (Present (Non_Limited_View (Typ))); - Typ := Non_Limited_View (Typ); - end if; + -- Otherwise we need to search for its associated tag component - Find_Tag (Typ); - pragma Assert (Found); - return AI_Tag; + else + Find_Tag (Typ); + pragma Assert (Found); + return AI_Tag; + end if; end Find_Interface_Tag; ------------------ @@ -1649,6 +1656,7 @@ package body Exp_Util is function Find_Prim_Op (T : Entity_Id; Name : Name_Id) return Entity_Id is Prim : Elmt_Id; Typ : Entity_Id := T; + Op : Entity_Id; begin if Is_Class_Wide_Type (Typ) then @@ -1657,15 +1665,38 @@ package body Exp_Util is Typ := Underlying_Type (Typ); + -- Loop through primitive operations + Prim := First_Elmt (Primitive_Operations (Typ)); - while Chars (Node (Prim)) /= Name loop + while Present (Prim) loop + Op := Node (Prim); + + -- We can retrieve primitive operations by name if it is an internal + -- name. For equality we must check that both of its operands have + -- the same type, to avoid confusion with user-defined equalities + -- than may have a non-symmetric signature. + + exit when Chars (Op) = Name + and then + (Name /= Name_Op_Eq + or else Etype (First_Entity (Op)) = Etype (Last_Entity (Op))); + Next_Elmt (Prim); - pragma Assert (Present (Prim)); + + -- Raise Program_Error if no primitive found + + if No (Prim) then + raise Program_Error; + end if; end loop; return Node (Prim); end Find_Prim_Op; + ------------------ + -- Find_Prim_Op -- + ------------------ + function Find_Prim_Op (T : Entity_Id; Name : TSS_Name_Type) return Entity_Id @@ -1683,12 +1714,45 @@ package body Exp_Util is Prim := First_Elmt (Primitive_Operations (Typ)); while not Is_TSS (Node (Prim), Name) loop Next_Elmt (Prim); - pragma Assert (Present (Prim)); + + -- Raise program error if no primitive found + + if No (Prim) then + raise Program_Error; + end if; end loop; return Node (Prim); end Find_Prim_Op; + ---------------------------- + -- Find_Protection_Object -- + ---------------------------- + + function Find_Protection_Object (Scop : Entity_Id) return Entity_Id is + S : Entity_Id; + + begin + S := Scop; + while Present (S) loop + if (Ekind (S) = E_Entry + or else Ekind (S) = E_Entry_Family + or else Ekind (S) = E_Function + or else Ekind (S) = E_Procedure) + and then Present (Protection_Object (S)) + then + return Protection_Object (S); + end if; + + S := Scope (S); + end loop; + + -- If we do not find a Protection object in the scope chain, then + -- something has gone wrong, most likely the object was never created. + + raise Program_Error; + end Find_Protection_Object; + ---------------------- -- Force_Evaluation -- ---------------------- @@ -1722,173 +1786,363 @@ package body Exp_Util is -- Get_Current_Value_Condition -- --------------------------------- + -- Note: the implementation of this procedure is very closely tied to the + -- implementation of Set_Current_Value_Condition. In the Get procedure, we + -- interpret Current_Value fields set by the Set procedure, so the two + -- procedures need to be closely coordinated. + procedure Get_Current_Value_Condition (Var : Node_Id; Op : out Node_Kind; Val : out Node_Id) is - Loc : constant Source_Ptr := Sloc (Var); - CV : constant Node_Id := Current_Value (Entity (Var)); - Sens : Boolean; - Stm : Node_Id; - Cond : Node_Id; + Loc : constant Source_Ptr := Sloc (Var); + Ent : constant Entity_Id := Entity (Var); + + procedure Process_Current_Value_Condition + (N : Node_Id; + S : Boolean); + -- N is an expression which holds either True (S = True) or False (S = + -- False) in the condition. This procedure digs out the expression and + -- if it refers to Ent, sets Op and Val appropriately. + + ------------------------------------- + -- Process_Current_Value_Condition -- + ------------------------------------- + + procedure Process_Current_Value_Condition + (N : Node_Id; + S : Boolean) + is + Cond : Node_Id; + Sens : Boolean; - begin - Op := N_Empty; - Val := Empty; + begin + Cond := N; + Sens := S; - -- If statement. Condition is known true in THEN section, known False - -- in any ELSIF or ELSE part, and unknown outside the IF statement. + -- Deal with NOT operators, inverting sense - if Nkind (CV) = N_If_Statement then + while Nkind (Cond) = N_Op_Not loop + Cond := Right_Opnd (Cond); + Sens := not Sens; + end loop; - -- Before start of IF statement + -- Deal with AND THEN and AND cases - if Loc < Sloc (CV) then - return; + if Nkind (Cond) = N_And_Then + or else Nkind (Cond) = N_Op_And + then + -- Don't ever try to invert a condition that is of the form + -- of an AND or AND THEN (since we are not doing sufficiently + -- general processing to allow this). - -- After end of IF statement + if Sens = False then + Op := N_Empty; + Val := Empty; + return; + end if; - elsif Loc >= Sloc (CV) + Text_Ptr (UI_To_Int (End_Span (CV))) then - return; - end if; + -- Recursively process AND and AND THEN branches - -- At this stage we know that we are within the IF statement, but - -- unfortunately, the tree does not record the SLOC of the ELSE so - -- we cannot use a simple SLOC comparison to distinguish between - -- the then/else statements, so we have to climb the tree. + Process_Current_Value_Condition (Left_Opnd (Cond), True); - declare - N : Node_Id; + if Op /= N_Empty then + return; + end if; - begin - N := Parent (Var); - while Parent (N) /= CV loop - N := Parent (N); + Process_Current_Value_Condition (Right_Opnd (Cond), True); + return; - -- If we fall off the top of the tree, then that's odd, but - -- perhaps it could occur in some error situation, and the - -- safest response is simply to assume that the outcome of the - -- condition is unknown. No point in bombing during an attempt - -- to optimize things. + -- Case of relational operator - if No (N) then - return; - end if; - end loop; + elsif Nkind (Cond) in N_Op_Compare then + Op := Nkind (Cond); + + -- Invert sense of test if inverted test - -- Now we have N pointing to a node whose parent is the IF - -- statement in question, so now we can tell if we are within - -- the THEN statements. + if Sens = False then + case Op is + when N_Op_Eq => Op := N_Op_Ne; + when N_Op_Ne => Op := N_Op_Eq; + when N_Op_Lt => Op := N_Op_Ge; + when N_Op_Gt => Op := N_Op_Le; + when N_Op_Le => Op := N_Op_Gt; + when N_Op_Ge => Op := N_Op_Lt; + when others => raise Program_Error; + end case; + end if; + + -- Case of entity op value - if Is_List_Member (N) - and then List_Containing (N) = Then_Statements (CV) + if Is_Entity_Name (Left_Opnd (Cond)) + and then Ent = Entity (Left_Opnd (Cond)) + and then Compile_Time_Known_Value (Right_Opnd (Cond)) then - Sens := True; + Val := Right_Opnd (Cond); - -- Otherwise we must be in ELSIF or ELSE part + -- Case of value op entity - else - Sens := False; - end if; - end; + elsif Is_Entity_Name (Right_Opnd (Cond)) + and then Ent = Entity (Right_Opnd (Cond)) + and then Compile_Time_Known_Value (Left_Opnd (Cond)) + then + Val := Left_Opnd (Cond); - -- ELSIF part. Condition is known true within the referenced ELSIF, - -- known False in any subsequent ELSIF or ELSE part, and unknown before - -- the ELSE part or after the IF statement. + -- We are effectively swapping operands - elsif Nkind (CV) = N_Elsif_Part then - Stm := Parent (CV); + case Op is + when N_Op_Eq => null; + when N_Op_Ne => null; + when N_Op_Lt => Op := N_Op_Gt; + when N_Op_Gt => Op := N_Op_Lt; + when N_Op_Le => Op := N_Op_Ge; + when N_Op_Ge => Op := N_Op_Le; + when others => raise Program_Error; + end case; - -- Before start of ELSIF part + else + Op := N_Empty; + end if; - if Loc < Sloc (CV) then return; - -- After end of IF statement + -- Case of Boolean variable reference, return as though the + -- reference had said var = True. - elsif Loc >= Sloc (Stm) + - Text_Ptr (UI_To_Int (End_Span (Stm))) - then - return; + else + if Is_Entity_Name (Cond) + and then Ent = Entity (Cond) + then + Val := New_Occurrence_Of (Standard_True, Sloc (Cond)); + + if Sens = False then + Op := N_Op_Ne; + else + Op := N_Op_Eq; + end if; + end if; end if; + end Process_Current_Value_Condition; - -- Again we lack the SLOC of the ELSE, so we need to climb the tree - -- to see if we are within the ELSIF part in question. + -- Start of processing for Get_Current_Value_Condition - declare - N : Node_Id; + begin + Op := N_Empty; + Val := Empty; - begin - N := Parent (Var); - while Parent (N) /= Stm loop - N := Parent (N); + -- Immediate return, nothing doing, if this is not an object - -- If we fall off the top of the tree, then that's odd, but - -- perhaps it could occur in some error situation, and the - -- safest response is simply to assume that the outcome of the - -- condition is unknown. No point in bombing during an attempt - -- to optimize things. + if Ekind (Ent) not in Object_Kind then + return; + end if; - if No (N) then - return; - end if; - end loop; + -- Otherwise examine current value - -- Now we have N pointing to a node whose parent is the IF - -- statement in question, so see if is the ELSIF part we want. - -- the THEN statements. + declare + CV : constant Node_Id := Current_Value (Ent); + Sens : Boolean; + Stm : Node_Id; - if N = CV then - Sens := True; + begin + -- If statement. Condition is known true in THEN section, known False + -- in any ELSIF or ELSE part, and unknown outside the IF statement. - -- Otherwise we must be in susbequent ELSIF or ELSE part + if Nkind (CV) = N_If_Statement then - else - Sens := False; + -- Before start of IF statement + + if Loc < Sloc (CV) then + return; + + -- After end of IF statement + + elsif Loc >= Sloc (CV) + Text_Ptr (UI_To_Int (End_Span (CV))) then + return; end if; - end; - -- All other cases of Current_Value settings + -- At this stage we know that we are within the IF statement, but + -- unfortunately, the tree does not record the SLOC of the ELSE so + -- we cannot use a simple SLOC comparison to distinguish between + -- the then/else statements, so we have to climb the tree. - else - return; - end if; + declare + N : Node_Id; - -- If we fall through here, then we have a reportable condition, Sens is - -- True if the condition is true and False if it needs inverting. + begin + N := Parent (Var); + while Parent (N) /= CV loop + N := Parent (N); - -- Deal with NOT operators, inverting sense + -- If we fall off the top of the tree, then that's odd, but + -- perhaps it could occur in some error situation, and the + -- safest response is simply to assume that the outcome of + -- the condition is unknown. No point in bombing during an + -- attempt to optimize things. - Cond := Condition (CV); - while Nkind (Cond) = N_Op_Not loop - Cond := Right_Opnd (Cond); - Sens := not Sens; - end loop; + if No (N) then + return; + end if; + end loop; - -- Now we must have a relational operator + -- Now we have N pointing to a node whose parent is the IF + -- statement in question, so now we can tell if we are within + -- the THEN statements. - pragma Assert (Entity (Var) = Entity (Left_Opnd (Cond))); - Val := Right_Opnd (Cond); - Op := Nkind (Cond); + if Is_List_Member (N) + and then List_Containing (N) = Then_Statements (CV) + then + Sens := True; - if Sens = False then - case Op is - when N_Op_Eq => Op := N_Op_Ne; - when N_Op_Ne => Op := N_Op_Eq; - when N_Op_Lt => Op := N_Op_Ge; - when N_Op_Gt => Op := N_Op_Le; - when N_Op_Le => Op := N_Op_Gt; - when N_Op_Ge => Op := N_Op_Lt; + -- If the variable reference does not come from source, we + -- cannot reliably tell whether it appears in the else part. + -- In particular, if it appears in generated code for a node + -- that requires finalization, it may be attached to a list + -- that has not been yet inserted into the code. For now, + -- treat it as unknown. - -- No other entry should be possible + elsif not Comes_From_Source (N) then + return; - when others => - raise Program_Error; - end case; - end if; + -- Otherwise we must be in ELSIF or ELSE part + + else + Sens := False; + end if; + end; + + -- ELSIF part. Condition is known true within the referenced + -- ELSIF, known False in any subsequent ELSIF or ELSE part, and + -- unknown before the ELSE part or after the IF statement. + + elsif Nkind (CV) = N_Elsif_Part then + Stm := Parent (CV); + + -- Before start of ELSIF part + + if Loc < Sloc (CV) then + return; + + -- After end of IF statement + + elsif Loc >= Sloc (Stm) + + Text_Ptr (UI_To_Int (End_Span (Stm))) + then + return; + end if; + + -- Again we lack the SLOC of the ELSE, so we need to climb the + -- tree to see if we are within the ELSIF part in question. + + declare + N : Node_Id; + + begin + N := Parent (Var); + while Parent (N) /= Stm loop + N := Parent (N); + + -- If we fall off the top of the tree, then that's odd, but + -- perhaps it could occur in some error situation, and the + -- safest response is simply to assume that the outcome of + -- the condition is unknown. No point in bombing during an + -- attempt to optimize things. + + if No (N) then + return; + end if; + end loop; + + -- Now we have N pointing to a node whose parent is the IF + -- statement in question, so see if is the ELSIF part we want. + -- the THEN statements. + + if N = CV then + Sens := True; + + -- Otherwise we must be in subsequent ELSIF or ELSE part + + else + Sens := False; + end if; + end; + + -- Iteration scheme of while loop. The condition is known to be + -- true within the body of the loop. + + elsif Nkind (CV) = N_Iteration_Scheme then + declare + Loop_Stmt : constant Node_Id := Parent (CV); + + begin + -- Before start of body of loop + + if Loc < Sloc (Loop_Stmt) then + return; + + -- After end of LOOP statement + + elsif Loc >= Sloc (End_Label (Loop_Stmt)) then + return; + + -- We are within the body of the loop + + else + Sens := True; + end if; + end; + + -- All other cases of Current_Value settings + + else + return; + end if; + + -- If we fall through here, then we have a reportable condition, Sens + -- is True if the condition is true and False if it needs inverting. + + Process_Current_Value_Condition (Condition (CV), Sens); + end; end Get_Current_Value_Condition; + --------------------------------- + -- Has_Controlled_Coextensions -- + --------------------------------- + + function Has_Controlled_Coextensions (Typ : Entity_Id) return Boolean is + D_Typ : Entity_Id; + Discr : Entity_Id; + + begin + -- Only consider record types + + if Ekind (Typ) /= E_Record_Type + and then Ekind (Typ) /= E_Record_Subtype + then + return False; + end if; + + if Has_Discriminants (Typ) then + Discr := First_Discriminant (Typ); + while Present (Discr) loop + D_Typ := Etype (Discr); + + if Ekind (D_Typ) = E_Anonymous_Access_Type + and then + (Is_Controlled (Directly_Designated_Type (D_Typ)) + or else + Is_Concurrent_Type (Directly_Designated_Type (D_Typ))) + then + return True; + end if; + + Next_Discriminant (Discr); + end loop; + end if; + + return False; + end Has_Controlled_Coextensions; + -------------------- -- Homonym_Number -- -------------------- @@ -1911,18 +2165,6 @@ package body Exp_Util is return Count; end Homonym_Number; - -------------------------- - -- Implements_Interface -- - -------------------------- - - function Implements_Interface - (Typ : Entity_Id; - Kind : Interface_Kind; - Check_Parent : Boolean := False) return Boolean is - begin - return Find_Implemented_Interface (Typ, Kind, Check_Parent) /= Empty; - end Implements_Interface; - ------------------------------ -- In_Unconditional_Context -- ------------------------------ @@ -1989,13 +2231,14 @@ package body Exp_Util is return; end if; - -- Ignore insert of actions from inside default expression in the - -- special preliminary analyze mode. Any insertions at this point - -- have no relevance, since we are only doing the analyze to freeze - -- the types of any static expressions. See section "Handling of - -- Default Expressions" in the spec of package Sem for further details. + -- Ignore insert of actions from inside default expression (or other + -- similar "spec expression") in the special spec-expression analyze + -- mode. Any insertions at this point have no relevance, since we are + -- only doing the analyze to freeze the types of any static expressions. + -- See section "Handling of Default Expressions" in the spec of package + -- Sem for further details. - if In_Default_Expression then + if In_Spec_Expression then return; end if; @@ -2059,7 +2302,7 @@ package body Exp_Util is -- Capture root of the transient scope if Scope_Is_Transient then - Wrapped_Node := Node_To_Be_Wrapped; + Wrapped_Node := Node_To_Be_Wrapped; end if; loop @@ -2073,16 +2316,33 @@ package body Exp_Util is -- Nothing special needs to be done for the left operand since -- in that case the actions are executed unconditionally. - when N_And_Then | N_Or_Else => + when N_Short_Circuit => if N = Right_Opnd (P) then + + -- We are now going to either append the actions to the + -- actions field of the short-circuit operation. We will + -- also analyze the actions now. + + -- This analysis is really too early, the proper thing would + -- be to just park them there now, and only analyze them if + -- we find we really need them, and to it at the proper + -- final insertion point. However attempting to this proved + -- tricky, so for now we just kill current values before and + -- after the analyze call to make sure we avoid peculiar + -- optimizations from this out of order insertion. + + Kill_Current_Values; + if Present (Actions (P)) then Insert_List_After_And_Analyze - (Last (Actions (P)), Ins_Actions); + (Last (Actions (P)), Ins_Actions); else Set_Actions (P, Ins_Actions); Analyze_List (Actions (P)); end if; + Kill_Current_Values; + return; end if; @@ -2214,6 +2474,7 @@ package body Exp_Util is N_Private_Extension_Declaration | N_Private_Type_Declaration | N_Procedure_Instantiation | + N_Protected_Body | N_Protected_Body_Stub | N_Protected_Type_Declaration | N_Single_Task_Declaration | @@ -2238,8 +2499,9 @@ package body Exp_Util is null; -- Do not insert if parent of P is an N_Component_Association - -- node (i.e. we are in the context of an N_Aggregate node. - -- In this case we want to insert before the entire aggregate. + -- node (i.e. we are in the context of an N_Aggregate or + -- N_Extension_Aggregate node. In this case we want to insert + -- before the entire aggregate. elsif Nkind (Parent (P)) = N_Component_Association then null; @@ -2273,7 +2535,7 @@ package body Exp_Util is -- Otherwise we can go ahead and do the insertion - elsif P = Wrapped_Node then + elsif P = Wrapped_Node then Store_Before_Actions_In_Scope (Ins_Actions); return; @@ -2480,10 +2742,15 @@ package body Exp_Util is N_Package_Specification | N_Parameter_Association | N_Parameter_Specification | + N_Pop_Constraint_Error_Label | + N_Pop_Program_Error_Label | + N_Pop_Storage_Error_Label | N_Pragma_Argument_Association | N_Procedure_Specification | - N_Protected_Body | N_Protected_Definition | + N_Push_Constraint_Error_Label | + N_Push_Program_Error_Label | + N_Push_Storage_Error_Label | N_Qualified_Expression | N_Range | N_Range_Constraint | @@ -2491,6 +2758,11 @@ package body Exp_Util is N_Real_Range_Specification | N_Record_Definition | N_Reference | + N_SCIL_Dispatch_Table_Object_Init | + N_SCIL_Dispatch_Table_Tag_Init | + N_SCIL_Dispatching_Call | + N_SCIL_Membership_Test | + N_SCIL_Tag_Init | N_Selected_Component | N_Signed_Integer_Type_Definition | N_Single_Protected_Declaration | @@ -2513,8 +2785,7 @@ package body Exp_Util is N_Variant | N_Variant_Part | N_Validate_Unchecked_Conversion | - N_With_Clause | - N_With_Type_Clause + N_With_Clause => null; @@ -2535,7 +2806,7 @@ package body Exp_Util is -- This is the proper body corresponding to a stub. Insertion -- must be done at the point of the stub, which is in the decla- - -- tive part of the parent unit. + -- rative part of the parent unit. P := Corresponding_Stub (Parent (N)); @@ -2543,13 +2814,14 @@ package body Exp_Util is P := Parent (N); end if; end loop; - end Insert_Actions; -- Version with check(s) suppressed procedure Insert_Actions - (Assoc_Node : Node_Id; Ins_Actions : List_Id; Suppress : Check_Id) + (Assoc_Node : Node_Id; + Ins_Actions : List_Id; + Suppress : Check_Id) is begin if Suppress = All_Checks then @@ -2598,7 +2870,8 @@ package body Exp_Util is Aux : constant Node_Id := Aux_Decls_Node (Cunit (Main_Unit)); begin - New_Scope (Cunit_Entity (Main_Unit)); + Push_Scope (Cunit_Entity (Main_Unit)); + -- ??? should this be Current_Sem_Unit instead of Main_Unit? if No (Actions (Aux)) then Set_Actions (Aux, New_List (N)); @@ -2619,7 +2892,8 @@ package body Exp_Util is begin if Is_Non_Empty_List (L) then - New_Scope (Cunit_Entity (Main_Unit)); + Push_Scope (Cunit_Entity (Main_Unit)); + -- ??? should this be Current_Sem_Unit instead of Main_Unit? if No (Actions (Aux)) then Set_Actions (Aux, L); @@ -2674,52 +2948,52 @@ package body Exp_Util is return True; end Is_All_Null_Statements; - ----------------------------------------- - -- Is_Predefined_Dispatching_Operation -- - ----------------------------------------- + --------------------------------- + -- Is_Fully_Repped_Tagged_Type -- + --------------------------------- - function Is_Predefined_Dispatching_Operation - (Subp : Entity_Id) return Boolean - is - TSS_Name : TSS_Name_Type; - E : Entity_Id := Subp; - begin - pragma Assert (Is_Dispatching_Operation (Subp)); + function Is_Fully_Repped_Tagged_Type (T : Entity_Id) return Boolean is + U : constant Entity_Id := Underlying_Type (T); + Comp : Entity_Id; - -- Handle overriden subprograms + begin + if No (U) or else not Is_Tagged_Type (U) then + return False; + elsif Has_Discriminants (U) then + return False; + elsif not Has_Specified_Layout (U) then + return False; + end if; - while Present (Alias (E)) loop - E := Alias (E); - end loop; + -- Here we have a tagged type, see if it has any unlayed out fields + -- other than a possible tag and parent fields. If so, we return False. - Get_Name_String (Chars (E)); - - if Name_Len > TSS_Name_Type'Last then - TSS_Name := TSS_Name_Type (Name_Buffer (Name_Len - TSS_Name'Length + 1 - .. Name_Len)); - if Chars (E) = Name_uSize - or else Chars (E) = Name_uAlignment - or else TSS_Name = TSS_Stream_Read - or else TSS_Name = TSS_Stream_Write - or else TSS_Name = TSS_Stream_Input - or else TSS_Name = TSS_Stream_Output - or else Chars (E) = Name_Op_Eq - or else Chars (E) = Name_uAssign - or else TSS_Name = TSS_Deep_Adjust - or else TSS_Name = TSS_Deep_Finalize - or else (Ada_Version >= Ada_05 - and then (Chars (E) = Name_uDisp_Asynchronous_Select - or else Chars (E) = Name_uDisp_Conditional_Select - or else Chars (E) = Name_uDisp_Get_Prim_Op_Kind - or else Chars (E) = Name_uDisp_Get_Task_Id - or else Chars (E) = Name_uDisp_Timed_Select)) + Comp := First_Component (U); + while Present (Comp) loop + if not Is_Tag (Comp) + and then Chars (Comp) /= Name_uParent + and then No (Component_Clause (Comp)) then - return True; + return False; + else + Next_Component (Comp); end if; - end if; + end loop; - return False; - end Is_Predefined_Dispatching_Operation; + -- All components are layed out + + return True; + end Is_Fully_Repped_Tagged_Type; + + ---------------------------------- + -- Is_Library_Level_Tagged_Type -- + ---------------------------------- + + function Is_Library_Level_Tagged_Type (Typ : Entity_Id) return Boolean is + begin + return Is_Tagged_Type (Typ) + and then Is_Library_Level_Entity (Typ); + end Is_Library_Level_Tagged_Type; ---------------------------------- -- Is_Possibly_Unaligned_Object -- @@ -2869,14 +3143,7 @@ package body Exp_Util is function Is_Possibly_Unaligned_Slice (N : Node_Id) return Boolean is begin - -- ??? GCC3 will eventually handle strings with arbitrary alignments, - -- but for now the following check must be disabled. - - -- if get_gcc_version >= 3 then - -- return False; - -- end if; - - -- For renaming case, go to renamed object + -- Go to renamed object if Is_Entity_Name (N) and then Is_Object (Entity (N)) @@ -3050,14 +3317,16 @@ package body Exp_Util is function Is_Ref_To_Bit_Packed_Slice (N : Node_Id) return Boolean is begin - if Is_Entity_Name (N) + if Nkind (N) = N_Type_Conversion then + return Is_Ref_To_Bit_Packed_Slice (Expression (N)); + + elsif Is_Entity_Name (N) and then Is_Object (Entity (N)) and then Present (Renamed_Object (Entity (N))) then return Is_Ref_To_Bit_Packed_Slice (Renamed_Object (Entity (N))); - end if; - if Nkind (N) = N_Slice + elsif Nkind (N) = N_Slice and then Is_Bit_Packed_Array (Etype (Prefix (N))) then return True; @@ -3080,16 +3349,11 @@ package body Exp_Util is function Is_Renamed_Object (N : Node_Id) return Boolean is Pnod : constant Node_Id := Parent (N); Kind : constant Node_Kind := Nkind (Pnod); - begin if Kind = N_Object_Renaming_Declaration then return True; - - elsif Kind = N_Indexed_Component - or else Kind = N_Selected_Component - then + elsif Nkind_In (Kind, N_Indexed_Component, N_Selected_Component) then return Is_Renamed_Object (Pnod); - else return False; end if; @@ -3107,26 +3371,96 @@ package body Exp_Util is and then not Is_Tagged_Type (Full_View (T)) and then Is_Derived_Type (Full_View (T)) and then Etype (Full_View (T)) /= T); - end Is_Untagged_Derivation; + --------------------------- + -- Is_Volatile_Reference -- + --------------------------- + + function Is_Volatile_Reference (N : Node_Id) return Boolean is + begin + if Nkind (N) in N_Has_Etype + and then Present (Etype (N)) + and then Treat_As_Volatile (Etype (N)) + then + return True; + + elsif Is_Entity_Name (N) then + return Treat_As_Volatile (Entity (N)); + + elsif Nkind (N) = N_Slice then + return Is_Volatile_Reference (Prefix (N)); + + elsif Nkind_In (N, N_Indexed_Component, N_Selected_Component) then + if (Is_Entity_Name (Prefix (N)) + and then Has_Volatile_Components (Entity (Prefix (N)))) + or else (Present (Etype (Prefix (N))) + and then Has_Volatile_Components (Etype (Prefix (N)))) + then + return True; + else + return Is_Volatile_Reference (Prefix (N)); + end if; + + else + return False; + end if; + end Is_Volatile_Reference; + -------------------- -- Kill_Dead_Code -- -------------------- - procedure Kill_Dead_Code (N : Node_Id) is + procedure Kill_Dead_Code (N : Node_Id; Warn : Boolean := False) is + W : Boolean := Warn; + -- Set False if warnings suppressed + begin if Present (N) then Remove_Warning_Messages (N); + -- Generate warning if appropriate + + if W then + + -- We suppress the warning if this code is under control of an + -- if statement, whose condition is a simple identifier, and + -- either we are in an instance, or warnings off is set for this + -- identifier. The reason for killing it in the instance case is + -- that it is common and reasonable for code to be deleted in + -- instances for various reasons. + + if Nkind (Parent (N)) = N_If_Statement then + declare + C : constant Node_Id := Condition (Parent (N)); + begin + if Nkind (C) = N_Identifier + and then + (In_Instance + or else (Present (Entity (C)) + and then Has_Warnings_Off (Entity (C)))) + then + W := False; + end if; + end; + end if; + + -- Generate warning if not suppressed + + if W then + Error_Msg_F + ("?this code can never be executed and has been deleted!", N); + end if; + end if; + -- Recurse into block statements and bodies to process declarations - -- and statements + -- and statements. if Nkind (N) = N_Block_Statement or else Nkind (N) = N_Subprogram_Body or else Nkind (N) = N_Package_Body then - Kill_Dead_Code (Declarations (N)); + Kill_Dead_Code (Declarations (N), False); Kill_Dead_Code (Statements (Handled_Statement_Sequence (N))); if Nkind (N) = N_Subprogram_Body then @@ -3137,6 +3471,10 @@ package body Exp_Util is Kill_Dead_Code (Visible_Declarations (Specification (N))); Kill_Dead_Code (Private_Declarations (Specification (N))); + -- ??? After this point, Delete_Tree has been called on all + -- declarations in Specification (N), so references to + -- entities therein look suspicious. + declare E : Entity_Id := First_Entity (Defining_Entity (N)); begin @@ -3179,22 +3517,22 @@ package body Exp_Util is elsif Nkind (N) in N_Generic_Instantiation then Remove_Dead_Instance (N); end if; - - Delete_Tree (N); end if; end Kill_Dead_Code; -- Case where argument is a list of nodes to be killed - procedure Kill_Dead_Code (L : List_Id) is + procedure Kill_Dead_Code (L : List_Id; Warn : Boolean := False) is N : Node_Id; - + W : Boolean; begin + W := Warn; if Is_Non_Empty_List (L) then - loop - N := Remove_Head (L); - exit when No (N); - Kill_Dead_Code (N); + N := First (L); + while Present (N) loop + Kill_Dead_Code (N, W); + W := False; + Next (N); end loop; end if; end Kill_Dead_Code; @@ -3227,27 +3565,38 @@ package body Exp_Util is function Known_Non_Null (N : Node_Id) return Boolean is begin - pragma Assert (Is_Access_Type (Underlying_Type (Etype (N)))); + -- Checks for case where N is an entity reference + + if Is_Entity_Name (N) and then Present (Entity (N)) then + declare + E : constant Entity_Id := Entity (N); + Op : Node_Kind; + Val : Node_Id; - -- Case of entity for which Is_Known_Non_Null is True + begin + -- First check if we are in decisive conditional - if Is_Entity_Name (N) and then Is_Known_Non_Null (Entity (N)) then + Get_Current_Value_Condition (N, Op, Val); - -- If the entity is aliased or volatile, then we decide that - -- we don't know it is really non-null even if the sequential - -- flow indicates that it is, since such variables can be - -- changed without us noticing. + if Known_Null (Val) then + if Op = N_Op_Eq then + return False; + elsif Op = N_Op_Ne then + return True; + end if; + end if; - if Is_Aliased (Entity (N)) - or else Treat_As_Volatile (Entity (N)) - then - return False; + -- If OK to do replacement, test Is_Known_Non_Null flag - -- For all other cases, the flag is decisive + if OK_To_Do_Constant_Replacement (E) then + return Is_Known_Non_Null (E); - else - return True; - end if; + -- Otherwise if not safe to do replacement, then say so + + else + return False; + end if; + end; -- True if access attribute @@ -3270,38 +3619,90 @@ package body Exp_Util is elsif Nkind (N) = N_Type_Conversion then return Known_Non_Null (Expression (N)); - -- One more case is when Current_Value references a condition - -- that ensures a non-null value. + -- Above are all cases where the value could be determined to be + -- non-null. In all other cases, we don't know, so return False. - elsif Is_Entity_Name (N) then + else + return False; + end if; + end Known_Non_Null; + + ---------------- + -- Known_Null -- + ---------------- + + function Known_Null (N : Node_Id) return Boolean is + begin + -- Checks for case where N is an entity reference + + if Is_Entity_Name (N) and then Present (Entity (N)) then declare + E : constant Entity_Id := Entity (N); Op : Node_Kind; Val : Node_Id; begin + -- Constant null value is for sure null + + if Ekind (E) = E_Constant + and then Known_Null (Constant_Value (E)) + then + return True; + end if; + + -- First check if we are in decisive conditional + Get_Current_Value_Condition (N, Op, Val); - return Op = N_Op_Ne and then Nkind (Val) = N_Null; + + if Known_Null (Val) then + if Op = N_Op_Eq then + return True; + elsif Op = N_Op_Ne then + return False; + end if; + end if; + + -- If OK to do replacement, test Is_Known_Null flag + + if OK_To_Do_Constant_Replacement (E) then + return Is_Known_Null (E); + + -- Otherwise if not safe to do replacement, then say so + + else + return False; + end if; end; - -- Above are all cases where the value could be determined to be - -- non-null. In all other cases, we don't know, so return False. + -- True if explicit reference to null + + elsif Nkind (N) = N_Null then + return True; + + -- For a conversion, true if expression is known null + + elsif Nkind (N) = N_Type_Conversion then + return Known_Null (Expression (N)); + + -- Above are all cases where the value could be determined to be null. + -- In all other cases, we don't know, so return False. else return False; end if; - end Known_Non_Null; + end Known_Null; ----------------------------- -- Make_CW_Equivalent_Type -- ----------------------------- - -- Create a record type used as an equivalent of any member - -- of the class which takes its size from exp. + -- Create a record type used as an equivalent of any member of the class + -- which takes its size from exp. -- Generate the following code: -- type Equiv_T is record - -- _parent : T (List of discriminant constaints taken from Exp); + -- _parent : T (List of discriminant constraints taken from Exp); -- Ext__50 : Storage_Array (1 .. (Exp'size - Typ'object_size)/8); -- end Equiv_T; -- @@ -3315,6 +3716,7 @@ package body Exp_Util is Loc : constant Source_Ptr := Sloc (E); Root_Typ : constant Entity_Id := Root_Type (T); List_Def : constant List_Id := Empty_List; + Comp_List : constant List_Id := New_List; Equiv_Type : Entity_Id; Range_Type : Entity_Id; Str_Type : Entity_Id; @@ -3337,22 +3739,36 @@ package body Exp_Util is Make_Subtype_From_Expr (E, Root_Typ))); end if; - -- subtype rg__xx is Storage_Offset range - -- (Expr'size - typ'size) / Storage_Unit + -- Generate the range subtype declaration Range_Type := Make_Defining_Identifier (Loc, New_Internal_Name ('G')); - Sizexpr := - Make_Op_Subtract (Loc, - Left_Opnd => - Make_Attribute_Reference (Loc, - Prefix => - OK_Convert_To (T, Duplicate_Subexpr_No_Checks (E)), - Attribute_Name => Name_Size), - Right_Opnd => - Make_Attribute_Reference (Loc, - Prefix => New_Reference_To (Constr_Root, Loc), - Attribute_Name => Name_Object_Size)); + if not Is_Interface (Root_Typ) then + + -- subtype rg__xx is + -- Storage_Offset range 1 .. (Expr'size - typ'size) / Storage_Unit + + Sizexpr := + Make_Op_Subtract (Loc, + Left_Opnd => + Make_Attribute_Reference (Loc, + Prefix => + OK_Convert_To (T, Duplicate_Subexpr_No_Checks (E)), + Attribute_Name => Name_Size), + Right_Opnd => + Make_Attribute_Reference (Loc, + Prefix => New_Reference_To (Constr_Root, Loc), + Attribute_Name => Name_Object_Size)); + else + -- subtype rg__xx is + -- Storage_Offset range 1 .. Expr'size / Storage_Unit + + Sizexpr := + Make_Attribute_Reference (Loc, + Prefix => + OK_Convert_To (T, Duplicate_Subexpr_No_Checks (E)), + Attribute_Name => Name_Size); + end if; Set_Paren_Count (Sizexpr, 1); @@ -3387,57 +3803,57 @@ package body Exp_Util is New_List (New_Reference_To (Range_Type, Loc)))))); -- type Equiv_T is record - -- _parent : Tnn; + -- [ _parent : Tnn; ] -- E : Str_Type; -- end Equiv_T; Equiv_Type := Make_Defining_Identifier (Loc, New_Internal_Name ('T')); + Set_Ekind (Equiv_Type, E_Record_Type); + Set_Parent_Subtype (Equiv_Type, Constr_Root); - -- When the target requires front-end layout, it's necessary to allow - -- the equivalent type to be frozen so that layout can occur (when the - -- associated class-wide subtype is frozen, the equivalent type will - -- be frozen, see freeze.adb). For other targets, Gigi wants to have - -- the equivalent type marked as frozen and deals with this type itself. - -- In the Gigi case this will also avoid the generation of an init - -- procedure for the type. - - if not Frontend_Layout_On_Target then - Set_Is_Frozen (Equiv_Type); + -- Set Is_Class_Wide_Equivalent_Type very early to trigger the special + -- treatment for this type. In particular, even though _parent's type + -- is a controlled type or contains controlled components, we do not + -- want to set Has_Controlled_Component on it to avoid making it gain + -- an unwanted _controller component. + + Set_Is_Class_Wide_Equivalent_Type (Equiv_Type); + + if not Is_Interface (Root_Typ) then + Append_To (Comp_List, + Make_Component_Declaration (Loc, + Defining_Identifier => + Make_Defining_Identifier (Loc, Name_uParent), + Component_Definition => + Make_Component_Definition (Loc, + Aliased_Present => False, + Subtype_Indication => New_Reference_To (Constr_Root, Loc)))); end if; - Set_Ekind (Equiv_Type, E_Record_Type); - Set_Parent_Subtype (Equiv_Type, Constr_Root); + Append_To (Comp_List, + Make_Component_Declaration (Loc, + Defining_Identifier => + Make_Defining_Identifier (Loc, + Chars => New_Internal_Name ('C')), + Component_Definition => + Make_Component_Definition (Loc, + Aliased_Present => False, + Subtype_Indication => New_Reference_To (Str_Type, Loc)))); Append_To (List_Def, Make_Full_Type_Declaration (Loc, Defining_Identifier => Equiv_Type, - Type_Definition => Make_Record_Definition (Loc, - Component_List => Make_Component_List (Loc, - Component_Items => New_List ( - Make_Component_Declaration (Loc, - Defining_Identifier => - Make_Defining_Identifier (Loc, Name_uParent), - Component_Definition => - Make_Component_Definition (Loc, - Aliased_Present => False, - Subtype_Indication => - New_Reference_To (Constr_Root, Loc))), - - Make_Component_Declaration (Loc, - Defining_Identifier => - Make_Defining_Identifier (Loc, - Chars => New_Internal_Name ('C')), - Component_Definition => - Make_Component_Definition (Loc, - Aliased_Present => False, - Subtype_Indication => - New_Reference_To (Str_Type, Loc)))), - - Variant_Part => Empty)))); - - Insert_Actions (E, List_Def); + Component_List => + Make_Component_List (Loc, + Component_Items => Comp_List, + Variant_Part => Empty)))); + + -- Suppress all checks during the analysis of the expanded code + -- to avoid the generation of spurious warnings under ZFP run-time. + + Insert_Actions (E, List_Def, Suppress => All_Checks); return Equiv_Type; end Make_CW_Equivalent_Type; @@ -3449,33 +3865,73 @@ package body Exp_Util is (Loc : Source_Ptr; Literal_Typ : Entity_Id) return Node_Id is - Lo : constant Node_Id := - New_Copy_Tree (String_Literal_Low_Bound (Literal_Typ)); + Lo : constant Node_Id := + New_Copy_Tree (String_Literal_Low_Bound (Literal_Typ)); + Index : constant Entity_Id := Etype (Lo); + + Hi : Node_Id; + Length_Expr : constant Node_Id := + Make_Op_Subtract (Loc, + Left_Opnd => + Make_Integer_Literal (Loc, + Intval => String_Literal_Length (Literal_Typ)), + Right_Opnd => + Make_Integer_Literal (Loc, 1)); begin Set_Analyzed (Lo, False); + if Is_Integer_Type (Index) then + Hi := + Make_Op_Add (Loc, + Left_Opnd => New_Copy_Tree (Lo), + Right_Opnd => Length_Expr); + else + Hi := + Make_Attribute_Reference (Loc, + Attribute_Name => Name_Val, + Prefix => New_Occurrence_Of (Index, Loc), + Expressions => New_List ( + Make_Op_Add (Loc, + Left_Opnd => + Make_Attribute_Reference (Loc, + Attribute_Name => Name_Pos, + Prefix => New_Occurrence_Of (Index, Loc), + Expressions => New_List (New_Copy_Tree (Lo))), + Right_Opnd => Length_Expr))); + end if; + return Make_Range (Loc, - Low_Bound => Lo, - - High_Bound => - Make_Op_Subtract (Loc, - Left_Opnd => - Make_Op_Add (Loc, - Left_Opnd => New_Copy_Tree (Lo), - Right_Opnd => - Make_Integer_Literal (Loc, - String_Literal_Length (Literal_Typ))), - Right_Opnd => Make_Integer_Literal (Loc, 1))); + Low_Bound => Lo, + High_Bound => Hi); end Make_Literal_Range; + -------------------------- + -- Make_Non_Empty_Check -- + -------------------------- + + function Make_Non_Empty_Check + (Loc : Source_Ptr; + N : Node_Id) return Node_Id + is + begin + return + Make_Op_Ne (Loc, + Left_Opnd => + Make_Attribute_Reference (Loc, + Attribute_Name => Name_Length, + Prefix => Duplicate_Subexpr_No_Checks (N, Name_Req => True)), + Right_Opnd => + Make_Integer_Literal (Loc, 0)); + end Make_Non_Empty_Check; + ---------------------------- -- Make_Subtype_From_Expr -- ---------------------------- - -- 1. If Expr is an uncontrained array expression, creates - -- Unc_Type(Expr'first(1)..Expr'Last(1),..., Expr'first(n)..Expr'last(n)) + -- 1. If Expr is an unconstrained array expression, creates + -- Unc_Type(Expr'first(1)..Expr'last(1),..., Expr'first(n)..Expr'last(n)) -- 2. If Expr is a unconstrained discriminated type expression, creates -- Unc_Type(Expr.Discr1, ... , Expr.Discr_n) @@ -3500,7 +3956,8 @@ package body Exp_Util is and then Has_Unknown_Discriminants (Unc_Typ) then -- Prepare the subtype completion, Go to base type to - -- find underlying type. + -- find underlying type, because the type may be a generic + -- actual or an explicit subtype. Utyp := Underlying_Type (Base_Type (Unc_Typ)); Full_Subtyp := Make_Defining_Identifier (Loc, @@ -3521,7 +3978,7 @@ package body Exp_Util is -- Define the dummy private subtype Set_Ekind (Priv_Subtyp, Subtype_Kind (Ekind (Unc_Typ))); - Set_Etype (Priv_Subtyp, Unc_Typ); + Set_Etype (Priv_Subtyp, Base_Type (Unc_Typ)); Set_Scope (Priv_Subtyp, Full_Subtyp); Set_Is_Constrained (Priv_Subtyp); Set_Is_Tagged_Type (Priv_Subtyp, Is_Tagged_Type (Unc_Typ)); @@ -3564,28 +4021,23 @@ package body Exp_Util is EQ_Typ : Entity_Id := Empty; begin - -- A class-wide equivalent type is not needed when Java_VM - -- because the JVM back end handles the class-wide object + -- A class-wide equivalent type is not needed when VM_Target + -- because the VM back-ends handle the class-wide object -- initialization itself (and doesn't need or want the -- additional intermediate type to handle the assignment). - if Expander_Active and then not Java_VM then + if Expander_Active and then Tagged_Type_Expansion then EQ_Typ := Make_CW_Equivalent_Type (Unc_Typ, E); end if; CW_Subtype := New_Class_Wide_Subtype (Unc_Typ, E); Set_Equivalent_Type (CW_Subtype, EQ_Typ); - - if Present (EQ_Typ) then - Set_Is_Class_Wide_Equivalent_Type (EQ_Typ); - end if; - Set_Cloned_Subtype (CW_Subtype, Base_Type (Unc_Typ)); return New_Occurrence_Of (CW_Subtype, Loc); end; - -- Indefinite record type with discriminants. + -- Indefinite record type with discriminants else D := First_Discriminant (Unc_Typ); @@ -3650,6 +4102,7 @@ package body Exp_Util is begin Copy_Node (CW_Typ, Res); + Set_Comes_From_Source (Res, False); Set_Sloc (Res, Sloc (N)); Set_Is_Itype (Res); Set_Associated_Node_For_Itype (Res, N); @@ -3660,21 +4113,162 @@ package body Exp_Util is Set_Ekind (Res, E_Class_Wide_Subtype); Set_Next_Entity (Res, Empty); Set_Etype (Res, Base_Type (CW_Typ)); + Set_Is_Frozen (Res, False); + Set_Freeze_Node (Res, Empty); + return (Res); + end New_Class_Wide_Subtype; - -- For targets where front-end layout is required, reset the Is_Frozen - -- status of the subtype to False (it can be implicitly set to true - -- from the copy of the class-wide type). For other targets, Gigi - -- doesn't want the class-wide subtype to go through the freezing - -- process (though it's unclear why that causes problems and it would - -- be nice to allow freezing to occur normally for all targets ???). + -------------------------------- + -- Non_Limited_Designated_Type -- + --------------------------------- - if Frontend_Layout_On_Target then - Set_Is_Frozen (Res, False); + function Non_Limited_Designated_Type (T : Entity_Id) return Entity_Id is + Desig : constant Entity_Id := Designated_Type (T); + begin + if Ekind (Desig) = E_Incomplete_Type + and then Present (Non_Limited_View (Desig)) + then + return Non_Limited_View (Desig); + else + return Desig; end if; + end Non_Limited_Designated_Type; - Set_Freeze_Node (Res, Empty); - return (Res); - end New_Class_Wide_Subtype; + ----------------------------------- + -- OK_To_Do_Constant_Replacement -- + ----------------------------------- + + function OK_To_Do_Constant_Replacement (E : Entity_Id) return Boolean is + ES : constant Entity_Id := Scope (E); + CS : Entity_Id; + + begin + -- Do not replace statically allocated objects, because they may be + -- modified outside the current scope. + + if Is_Statically_Allocated (E) then + return False; + + -- Do not replace aliased or volatile objects, since we don't know what + -- else might change the value. + + elsif Is_Aliased (E) or else Treat_As_Volatile (E) then + return False; + + -- Debug flag -gnatdM disconnects this optimization + + elsif Debug_Flag_MM then + return False; + + -- Otherwise check scopes + + else + CS := Current_Scope; + + loop + -- If we are in right scope, replacement is safe + + if CS = ES then + return True; + + -- Packages do not affect the determination of safety + + elsif Ekind (CS) = E_Package then + exit when CS = Standard_Standard; + CS := Scope (CS); + + -- Blocks do not affect the determination of safety + + elsif Ekind (CS) = E_Block then + CS := Scope (CS); + + -- Loops do not affect the determination of safety. Note that we + -- kill all current values on entry to a loop, so we are just + -- talking about processing within a loop here. + + elsif Ekind (CS) = E_Loop then + CS := Scope (CS); + + -- Otherwise, the reference is dubious, and we cannot be sure that + -- it is safe to do the replacement. + + else + exit; + end if; + end loop; + + return False; + end if; + end OK_To_Do_Constant_Replacement; + + ------------------------------------ + -- Possible_Bit_Aligned_Component -- + ------------------------------------ + + function Possible_Bit_Aligned_Component (N : Node_Id) return Boolean is + begin + case Nkind (N) is + + -- Case of indexed component + + when N_Indexed_Component => + declare + P : constant Node_Id := Prefix (N); + Ptyp : constant Entity_Id := Etype (P); + + begin + -- If we know the component size and it is less than 64, then + -- we are definitely OK. The back end always does assignment of + -- misaligned small objects correctly. + + if Known_Static_Component_Size (Ptyp) + and then Component_Size (Ptyp) <= 64 + then + return False; + + -- Otherwise, we need to test the prefix, to see if we are + -- indexing from a possibly unaligned component. + + else + return Possible_Bit_Aligned_Component (P); + end if; + end; + + -- Case of selected component + + when N_Selected_Component => + declare + P : constant Node_Id := Prefix (N); + Comp : constant Entity_Id := Entity (Selector_Name (N)); + + begin + -- If there is no component clause, then we are in the clear + -- since the back end will never misalign a large component + -- unless it is forced to do so. In the clear means we need + -- only the recursive test on the prefix. + + if Component_May_Be_Bit_Aligned (Comp) then + return True; + else + return Possible_Bit_Aligned_Component (P); + end if; + end; + + -- For a slice, test the prefix, if that is possibly misaligned, + -- then for sure the slice is! + + when N_Slice => + return Possible_Bit_Aligned_Component (Prefix (N)); + + -- If we have none of the above, it means that we have fallen off the + -- top testing prefixes recursively, and we now have a stand alone + -- object, where we don't have a problem. + + when others => + return False; + + end case; + end Possible_Bit_Aligned_Component; ------------------------- -- Remove_Side_Effects -- @@ -3685,7 +4279,7 @@ package body Exp_Util is Name_Req : Boolean := False; Variable_Ref : Boolean := False) is - Loc : constant Source_Ptr := Sloc (Exp); + Loc : constant Source_Ptr := Sloc (Exp); Exp_Type : constant Entity_Id := Etype (Exp); Svg_Suppress : constant Suppress_Array := Scope_Suppress; Def_Id : Entity_Id; @@ -3696,31 +4290,30 @@ package body Exp_Util is E : Node_Id; function Side_Effect_Free (N : Node_Id) return Boolean; - -- Determines if the tree N represents an expression that is known - -- not to have side effects, and for which no processing is required. + -- Determines if the tree N represents an expression that is known not + -- to have side effects, and for which no processing is required. function Side_Effect_Free (L : List_Id) return Boolean; -- Determines if all elements of the list L are side effect free function Safe_Prefixed_Reference (N : Node_Id) return Boolean; - -- The argument N is a construct where the Prefix is dereferenced - -- if it is a an access type and the result is a variable. The call - -- returns True if the construct is side effect free (not considering - -- side effects in other than the prefix which are to be tested by the - -- caller). + -- The argument N is a construct where the Prefix is dereferenced if it + -- is an access type and the result is a variable. The call returns True + -- if the construct is side effect free (not considering side effects in + -- other than the prefix which are to be tested by the caller). function Within_In_Parameter (N : Node_Id) return Boolean; - -- Determines if N is a subcomponent of a composite in-parameter. - -- If so, N is not side-effect free when the actual is global and - -- modifiable indirectly from within a subprogram, because it may - -- be passed by reference. The front-end must be conservative here - -- and assume that this may happen with any array or record type. - -- On the other hand, we cannot create temporaries for all expressions - -- for which this condition is true, for various reasons that might - -- require clearing up ??? For example, descriminant references that - -- appear out of place, or spurious type errors with class-wide - -- expressions. As a result, we limit the transformation to loop - -- bounds, which is so far the only case that requires it. + -- Determines if N is a subcomponent of a composite in-parameter. If so, + -- N is not side-effect free when the actual is global and modifiable + -- indirectly from within a subprogram, because it may be passed by + -- reference. The front-end must be conservative here and assume that + -- this may happen with any array or record type. On the other hand, we + -- cannot create temporaries for all expressions for which this + -- condition is true, for various reasons that might require clearing up + -- ??? For example, discriminant references that appear out of place, or + -- spurious type errors with class-wide expressions. As a result, we + -- limit the transformation to loop bounds, which is so far the only + -- case that requires it. ----------------------------- -- Safe_Prefixed_Reference -- @@ -3785,7 +4378,7 @@ package body Exp_Util is -- hand, if we do not consider them to be side effect free, then -- we get some awkward expansions in -gnato mode, resulting in -- code insertions at a point where we do not have a clear model - -- for performing the insertions. See 4908-002/comment for details. + -- for performing the insertions. -- Special handling for entity names @@ -3809,14 +4402,13 @@ package body Exp_Util is return False; -- Variables are considered to be a side effect if Variable_Ref - -- is set or if we have a volatile variable and Name_Req is off. + -- is set or if we have a volatile reference and Name_Req is off. -- If Name_Req is True then we can't help returning a name which -- effectively allows multiple references in any case. elsif Is_Variable (N) then return not Variable_Ref - and then (not Treat_As_Volatile (Entity (N)) - or else Name_Req); + and then (not Is_Volatile_Reference (N) or else Name_Req); -- Any other entity (e.g. a subtype name) is definitely side -- effect free. @@ -3829,6 +4421,17 @@ package body Exp_Util is elsif Compile_Time_Known_Value (N) then return True; + + -- A variable renaming is not side-effect free, because the + -- renaming will function like a macro in the front-end in + -- some cases, and an assignment can modify the component + -- designated by N, so we need to create a temporary for it. + + elsif Is_Entity_Name (Original_Node (N)) + and then Is_Renaming_Of_Object (Entity (Original_Node (N))) + and then Ekind (Entity (Original_Node (N))) /= E_Constant + then + return False; end if; -- For other than entity names and compile time known values, @@ -3844,6 +4447,7 @@ package body Exp_Util is when N_Attribute_Reference => return Side_Effect_Free (Expressions (N)) + and then Attribute_Name (N) /= Name_Input and then (Is_Entity_Name (Prefix (N)) or else Side_Effect_Free (Prefix (N))); @@ -3851,13 +4455,10 @@ package body Exp_Util is -- are side effect free. For this purpose binary operators -- include membership tests and short circuit forms - when N_Binary_Op | - N_In | - N_Not_In | - N_And_Then | - N_Or_Else => + when N_Binary_Op | N_Membership_Test | N_Short_Circuit => return Side_Effect_Free (Left_Opnd (N)) - and then Side_Effect_Free (Right_Opnd (N)); + and then + Side_Effect_Free (Right_Opnd (N)); -- An explicit dereference is side effect free only if it is -- a side effect free prefixed reference. @@ -3895,10 +4496,23 @@ package body Exp_Util is return Side_Effect_Free (Expression (N)); -- A selected component is side effect free only if it is a - -- side effect free prefixed reference. + -- side effect free prefixed reference. If it designates a + -- component with a rep. clause it must be treated has having + -- a potential side effect, because it may be modified through + -- a renaming, and a subsequent use of the renaming as a macro + -- will yield the wrong value. This complex interaction between + -- renaming and removing side effects is a reminder that the + -- latter has become a headache to maintain, and that it should + -- be removed in favor of the gcc mechanism to capture values ??? when N_Selected_Component => - return Safe_Prefixed_Reference (N); + if Nkind (Parent (N)) = N_Explicit_Dereference + and then Has_Non_Standard_Rep (Designated_Type (Etype (N))) + then + return False; + else + return Safe_Prefixed_Reference (N); + end if; -- A range is side effect free if the bounds are side effect free @@ -3913,8 +4527,8 @@ package body Exp_Util is return Side_Effect_Free (Discrete_Range (N)) and then Safe_Prefixed_Reference (N); - -- A type conversion is side effect free if the expression - -- to be converted is side effect free. + -- A type conversion is side effect free if the expression to be + -- converted is side effect free. when N_Type_Conversion => return Side_Effect_Free (Expression (N)); @@ -3990,8 +4604,7 @@ package body Exp_Util is return False; elsif Is_Entity_Name (N) then - return - Ekind (Entity (N)) = E_In_Parameter; + return Ekind (Entity (N)) = E_In_Parameter; elsif Nkind (N) = N_Indexed_Component or else Nkind (N) = N_Selected_Component @@ -4017,20 +4630,19 @@ package body Exp_Util is Scope_Suppress := (others => True); - -- If it is a scalar type and we need to capture the value, just - -- make a copy. Likewise for a function call. And if we have a - -- volatile variable and Nam_Req is not set (see comments above - -- for Side_Effect_Free). + -- If it is a scalar type and we need to capture the value, just make + -- a copy. Likewise for a function call, an attribute reference or an + -- operator. And if we have a volatile reference and Name_Req is not + -- set (see comments above for Side_Effect_Free). if Is_Elementary_Type (Exp_Type) and then (Variable_Ref or else Nkind (Exp) = N_Function_Call - or else (not Name_Req - and then Is_Entity_Name (Exp) - and then Treat_As_Volatile (Entity (Exp)))) + or else Nkind (Exp) = N_Attribute_Reference + or else Nkind (Exp) in N_Op + or else (not Name_Req and then Is_Volatile_Reference (Exp))) then - - Def_Id := Make_Defining_Identifier (Loc, New_Internal_Name ('R')); + Def_Id := Make_Temporary (Loc, 'R', Exp); Set_Etype (Def_Id, Exp_Type); Res := New_Reference_To (Def_Id, Loc); @@ -4041,6 +4653,15 @@ package body Exp_Util is Constant_Present => True, Expression => Relocate_Node (Exp)); + -- Check if the previous node relocation requires readjustment of + -- some SCIL Dispatching node. + + if Generate_SCIL + and then Nkind (Exp) = N_Function_Call + then + Adjust_SCIL_Node (Exp, Expression (E)); + end if; + Set_Assignment_OK (E); Insert_Action (Exp, E); @@ -4048,8 +4669,7 @@ package body Exp_Util is -- the pointer, and then do an explicit dereference on the result. elsif Nkind (Exp) = N_Explicit_Dereference then - Def_Id := - Make_Defining_Identifier (Loc, New_Internal_Name ('R')); + Def_Id := Make_Temporary (Loc, 'R', Exp); Res := Make_Explicit_Dereference (Loc, New_Reference_To (Def_Id, Loc)); @@ -4073,18 +4693,11 @@ package body Exp_Util is -- If this is a type conversion, leave the type conversion and remove -- the side effects in the expression. This is important in several - -- circumstances: for change of representations, and also when this - -- is a view conversion to a smaller object, where gigi can end up - -- creating its own temporary of the wrong size. - - -- ??? this transformation is inhibited for elementary types that are - -- not involved in a change of representation because it causes - -- regressions that are not fully understood yet. + -- circumstances: for change of representations, and also when this is + -- a view conversion to a smaller object, where gigi can end up creating + -- its own temporary of the wrong size. - elsif Nkind (Exp) = N_Type_Conversion - and then (not Is_Elementary_Type (Underlying_Type (Exp_Type)) - or else Nkind (Parent (Exp)) = N_Assignment_Statement) - then + elsif Nkind (Exp) = N_Type_Conversion then Remove_Side_Effects (Expression (Exp), Name_Req, Variable_Ref); Scope_Suppress := Svg_Suppress; return; @@ -4095,12 +4708,12 @@ package body Exp_Util is elsif Nkind (Exp) = N_Unchecked_Type_Conversion and then not Safe_Unchecked_Type_Conversion (Exp) then - if Controlled_Type (Etype (Exp)) then + if CW_Or_Has_Controlled_Part (Exp_Type) then -- Use a renaming to capture the expression, rather than create -- a controlled temporary. - Def_Id := Make_Defining_Identifier (Loc, New_Internal_Name ('R')); + Def_Id := Make_Temporary (Loc, 'R', Exp); Res := New_Reference_To (Def_Id, Loc); Insert_Action (Exp, @@ -4110,7 +4723,7 @@ package body Exp_Util is Name => Relocate_Node (Exp))); else - Def_Id := Make_Defining_Identifier (Loc, New_Internal_Name ('R')); + Def_Id := Make_Temporary (Loc, 'R', Exp); Set_Etype (Def_Id, Exp_Type); Res := New_Reference_To (Def_Id, Loc); @@ -4126,20 +4739,18 @@ package body Exp_Util is end if; -- For expressions that denote objects, we can use a renaming scheme. - -- We skip using this if we have a volatile variable and we do not - -- have Nam_Req set true (see comments above for Side_Effect_Free). + -- We skip using this if we have a volatile reference and we do not + -- have Name_Req set true (see comments above for Side_Effect_Free). elsif Is_Object_Reference (Exp) and then Nkind (Exp) /= N_Function_Call - and then (Name_Req - or else not Is_Entity_Name (Exp) - or else not Treat_As_Volatile (Entity (Exp))) + and then (Name_Req or else not Is_Volatile_Reference (Exp)) then - Def_Id := Make_Defining_Identifier (Loc, New_Internal_Name ('R')); + Def_Id := Make_Temporary (Loc, 'R', Exp); if Nkind (Exp) = N_Selected_Component and then Nkind (Prefix (Exp)) = N_Function_Call - and then Is_Array_Type (Etype (Exp)) + and then Is_Array_Type (Exp_Type) then -- Avoid generating a variable-sized temporary, by generating -- the renaming declaration just for the function call. The @@ -4166,18 +4777,68 @@ package body Exp_Util is Defining_Identifier => Def_Id, Subtype_Mark => New_Reference_To (Exp_Type, Loc), Name => Relocate_Node (Exp))); - end if; - -- The temporary must be elaborated by gigi, and is of course - -- not to be replaced in-line by the expression it renames, - -- which would defeat the purpose of removing the side-effect. - - Set_Is_Renaming_Of_Object (Def_Id, False); + -- If this is a packed reference, or a selected component with a + -- non-standard representation, a reference to the temporary will + -- be replaced by a copy of the original expression (see + -- Exp_Ch2.Expand_Renaming). Otherwise the temporary must be + -- elaborated by gigi, and is of course not to be replaced in-line + -- by the expression it renames, which would defeat the purpose of + -- removing the side-effect. + + if (Nkind (Exp) = N_Selected_Component + or else Nkind (Exp) = N_Indexed_Component) + and then Has_Non_Standard_Rep (Etype (Prefix (Exp))) + then + null; + else + Set_Is_Renaming_Of_Object (Def_Id, False); + end if; -- Otherwise we generate a reference to the value else + -- Special processing for function calls that return a limited type. + -- We need to build a declaration that will enable build-in-place + -- expansion of the call. This is not done if the context is already + -- an object declaration, to prevent infinite recursion. + + -- This is relevant only in Ada 2005 mode. In Ada 95 programs we have + -- to accommodate functions returning limited objects by reference. + + if Nkind (Exp) = N_Function_Call + and then Is_Inherently_Limited_Type (Etype (Exp)) + and then Nkind (Parent (Exp)) /= N_Object_Declaration + and then Ada_Version >= Ada_05 + then + declare + Obj : constant Entity_Id := Make_Temporary (Loc, 'F', Exp); + Decl : Node_Id; + + begin + Decl := + Make_Object_Declaration (Loc, + Defining_Identifier => Obj, + Object_Definition => New_Occurrence_Of (Exp_Type, Loc), + Expression => Relocate_Node (Exp)); + + -- Check if the previous node relocation requires readjustment + -- of some SCIL Dispatching node. + + if Generate_SCIL + and then Nkind (Exp) = N_Function_Call + then + Adjust_SCIL_Node (Exp, Expression (Decl)); + end if; + + Insert_Action (Exp, Decl); + Set_Etype (Obj, Exp_Type); + Rewrite (Exp, New_Occurrence_Of (Obj, Loc)); + return; + end; + end if; + Ref_Type := Make_Defining_Identifier (Loc, New_Internal_Name ('A')); Ptr_Typ_Decl := @@ -4192,7 +4853,7 @@ package body Exp_Util is E := Exp; Insert_Action (Exp, Ptr_Typ_Decl); - Def_Id := Make_Defining_Identifier (Loc, New_Internal_Name ('R')); + Def_Id := Make_Temporary (Loc, 'R', Exp); Set_Etype (Def_Id, Exp_Type); Res := @@ -4230,6 +4891,15 @@ package body Exp_Util is Defining_Identifier => Def_Id, Object_Definition => New_Reference_To (Ref_Type, Loc), Expression => New_Exp)); + + -- Check if the previous node relocation requires readjustment + -- of some SCIL Dispatching node. + + if Generate_SCIL + and then Nkind (Exp) = N_Function_Call + then + Adjust_SCIL_Node (Exp, Prefix (New_Exp)); + end if; end if; -- Preserve the Assignment_OK flag in all copies, since at least @@ -4365,6 +5035,14 @@ package body Exp_Util is then return True; + -- If the expression has an access type (object or subprogram) we + -- assume that the conversion is safe, because the size of the target + -- is safe, even if it is a record (which might be treated as having + -- unknown size at this point). + + elsif Is_Access_Type (Ityp) then + return True; + -- If the size of output type is known at compile time, there is -- never a problem. Note that unconstrained records are considered -- to be of known size, but we can't consider them that way here, @@ -4443,9 +5121,113 @@ package body Exp_Util is else return False; end if; - end Safe_Unchecked_Type_Conversion; + --------------------------------- + -- Set_Current_Value_Condition -- + --------------------------------- + + -- Note: the implementation of this procedure is very closely tied to the + -- implementation of Get_Current_Value_Condition. Here we set required + -- Current_Value fields, and in Get_Current_Value_Condition, we interpret + -- them, so they must have a consistent view. + + procedure Set_Current_Value_Condition (Cnode : Node_Id) is + + procedure Set_Entity_Current_Value (N : Node_Id); + -- If N is an entity reference, where the entity is of an appropriate + -- kind, then set the current value of this entity to Cnode, unless + -- there is already a definite value set there. + + procedure Set_Expression_Current_Value (N : Node_Id); + -- If N is of an appropriate form, sets an appropriate entry in current + -- value fields of relevant entities. Multiple entities can be affected + -- in the case of an AND or AND THEN. + + ------------------------------ + -- Set_Entity_Current_Value -- + ------------------------------ + + procedure Set_Entity_Current_Value (N : Node_Id) is + begin + if Is_Entity_Name (N) then + declare + Ent : constant Entity_Id := Entity (N); + + begin + -- Don't capture if not safe to do so + + if not Safe_To_Capture_Value (N, Ent, Cond => True) then + return; + end if; + + -- Here we have a case where the Current_Value field may + -- need to be set. We set it if it is not already set to a + -- compile time expression value. + + -- Note that this represents a decision that one condition + -- blots out another previous one. That's certainly right + -- if they occur at the same level. If the second one is + -- nested, then the decision is neither right nor wrong (it + -- would be equally OK to leave the outer one in place, or + -- take the new inner one. Really we should record both, but + -- our data structures are not that elaborate. + + if Nkind (Current_Value (Ent)) not in N_Subexpr then + Set_Current_Value (Ent, Cnode); + end if; + end; + end if; + end Set_Entity_Current_Value; + + ---------------------------------- + -- Set_Expression_Current_Value -- + ---------------------------------- + + procedure Set_Expression_Current_Value (N : Node_Id) is + Cond : Node_Id; + + begin + Cond := N; + + -- Loop to deal with (ignore for now) any NOT operators present. The + -- presence of NOT operators will be handled properly when we call + -- Get_Current_Value_Condition. + + while Nkind (Cond) = N_Op_Not loop + Cond := Right_Opnd (Cond); + end loop; + + -- For an AND or AND THEN, recursively process operands + + if Nkind (Cond) = N_Op_And or else Nkind (Cond) = N_And_Then then + Set_Expression_Current_Value (Left_Opnd (Cond)); + Set_Expression_Current_Value (Right_Opnd (Cond)); + return; + end if; + + -- Check possible relational operator + + if Nkind (Cond) in N_Op_Compare then + if Compile_Time_Known_Value (Right_Opnd (Cond)) then + Set_Entity_Current_Value (Left_Opnd (Cond)); + elsif Compile_Time_Known_Value (Left_Opnd (Cond)) then + Set_Entity_Current_Value (Right_Opnd (Cond)); + end if; + + -- Check possible boolean variable reference + + else + Set_Entity_Current_Value (Cond); + end if; + end Set_Expression_Current_Value; + + -- Start of processing for Set_Current_Value_Condition + + begin + Set_Expression_Current_Value (Condition (Cnode)); + end Set_Current_Value_Condition; + -------------------------- -- Set_Elaboration_Flag -- -------------------------- @@ -4481,15 +5263,148 @@ package body Exp_Util is Analyze (Asn); - -- Kill current value indication. This is necessary because - -- the tests of this flag are inserted out of sequence and must - -- not pick up bogus indications of the wrong constant value. + -- Kill current value indication. This is necessary because the + -- tests of this flag are inserted out of sequence and must not + -- pick up bogus indications of the wrong constant value. Set_Current_Value (Ent, Empty); end if; end if; end Set_Elaboration_Flag; + ---------------------------- + -- Set_Renamed_Subprogram -- + ---------------------------- + + procedure Set_Renamed_Subprogram (N : Node_Id; E : Entity_Id) is + begin + -- If input node is an identifier, we can just reset it + + if Nkind (N) = N_Identifier then + Set_Chars (N, Chars (E)); + Set_Entity (N, E); + + -- Otherwise we have to do a rewrite, preserving Comes_From_Source + + else + declare + CS : constant Boolean := Comes_From_Source (N); + begin + Rewrite (N, Make_Identifier (Sloc (N), Chars => Chars (E))); + Set_Entity (N, E); + Set_Comes_From_Source (N, CS); + Set_Analyzed (N, True); + end; + end if; + end Set_Renamed_Subprogram; + + ---------------------------------- + -- Silly_Boolean_Array_Not_Test -- + ---------------------------------- + + -- This procedure implements an odd and silly test. We explicitly check + -- for the case where the 'First of the component type is equal to the + -- 'Last of this component type, and if this is the case, we make sure + -- that constraint error is raised. The reason is that the NOT is bound + -- to cause CE in this case, and we will not otherwise catch it. + + -- No such check is required for AND and OR, since for both these cases + -- False op False = False, and True op True = True. For the XOR case, + -- see Silly_Boolean_Array_Xor_Test. + + -- Believe it or not, this was reported as a bug. Note that nearly + -- always, the test will evaluate statically to False, so the code will + -- be statically removed, and no extra overhead caused. + + procedure Silly_Boolean_Array_Not_Test (N : Node_Id; T : Entity_Id) is + Loc : constant Source_Ptr := Sloc (N); + CT : constant Entity_Id := Component_Type (T); + + begin + -- The check we install is + + -- constraint_error when + -- component_type'first = component_type'last + -- and then array_type'Length /= 0) + + -- We need the last guard because we don't want to raise CE for empty + -- arrays since no out of range values result. (Empty arrays with a + -- component type of True .. True -- very useful -- even the ACATS + -- does not test that marginal case!) + + Insert_Action (N, + Make_Raise_Constraint_Error (Loc, + Condition => + Make_And_Then (Loc, + Left_Opnd => + Make_Op_Eq (Loc, + Left_Opnd => + Make_Attribute_Reference (Loc, + Prefix => New_Occurrence_Of (CT, Loc), + Attribute_Name => Name_First), + + Right_Opnd => + Make_Attribute_Reference (Loc, + Prefix => New_Occurrence_Of (CT, Loc), + Attribute_Name => Name_Last)), + + Right_Opnd => Make_Non_Empty_Check (Loc, Right_Opnd (N))), + Reason => CE_Range_Check_Failed)); + end Silly_Boolean_Array_Not_Test; + + ---------------------------------- + -- Silly_Boolean_Array_Xor_Test -- + ---------------------------------- + + -- This procedure implements an odd and silly test. We explicitly check + -- for the XOR case where the component type is True .. True, since this + -- will raise constraint error. A special check is required since CE + -- will not be generated otherwise (cf Expand_Packed_Not). + + -- No such check is required for AND and OR, since for both these cases + -- False op False = False, and True op True = True, and no check is + -- required for the case of False .. False, since False xor False = False. + -- See also Silly_Boolean_Array_Not_Test + + procedure Silly_Boolean_Array_Xor_Test (N : Node_Id; T : Entity_Id) is + Loc : constant Source_Ptr := Sloc (N); + CT : constant Entity_Id := Component_Type (T); + + begin + -- The check we install is + + -- constraint_error when + -- Boolean (component_type'First) + -- and then Boolean (component_type'Last) + -- and then array_type'Length /= 0) + + -- We need the last guard because we don't want to raise CE for empty + -- arrays since no out of range values result (Empty arrays with a + -- component type of True .. True -- very useful -- even the ACATS + -- does not test that marginal case!). + + Insert_Action (N, + Make_Raise_Constraint_Error (Loc, + Condition => + Make_And_Then (Loc, + Left_Opnd => + Make_And_Then (Loc, + Left_Opnd => + Convert_To (Standard_Boolean, + Make_Attribute_Reference (Loc, + Prefix => New_Occurrence_Of (CT, Loc), + Attribute_Name => Name_First)), + + Right_Opnd => + Convert_To (Standard_Boolean, + Make_Attribute_Reference (Loc, + Prefix => New_Occurrence_Of (CT, Loc), + Attribute_Name => Name_Last))), + + Right_Opnd => Make_Non_Empty_Check (Loc, Right_Opnd (N))), + Reason => CE_Range_Check_Failed)); + end Silly_Boolean_Array_Xor_Test; + -------------------------- -- Target_Has_Fixed_Ops -- -------------------------- @@ -4500,7 +5415,7 @@ package body Exp_Util is Long_Integer_Sized_Small : Ureal; -- Set to 2.0 ** -(Long_Integer'Size - 1) the first time that this - -- functoin is called (we don't want to compute it more than once) + -- function is called (we don't want to compute it more than once) First_Time_For_THFO : Boolean := True; -- Set to False after first call (if Fractional_Fixed_Ops_On_Target) @@ -4593,20 +5508,15 @@ package body Exp_Util is E : Entity_Id; begin - E := First_Entity (Typ); + E := First_Component_Or_Discriminant (Typ); while Present (E) loop - if Ekind (E) = E_Component - or else Ekind (E) = E_Discriminant + if Component_May_Be_Bit_Aligned (E) + or else Type_May_Have_Bit_Aligned_Components (Etype (E)) then - if Component_May_Be_Bit_Aligned (E) - or else - Type_May_Have_Bit_Aligned_Components (Etype (E)) - then - return True; - end if; + return True; end if; - Next_Entity (E); + Next_Component_Or_Discriminant (E); end loop; return False;