| ------------------------------------------------------------------------------ |
| -- -- |
| -- GNAT COMPILER COMPONENTS -- |
| -- -- |
| -- E X P _ U T I L -- |
| -- -- |
| -- B o d y -- |
| -- -- |
| -- Copyright (C) 1992-2015, Free Software Foundation, Inc. -- |
| -- -- |
| -- GNAT is free software; you can redistribute it and/or modify it under -- |
| -- terms of the GNU General Public License as published by the Free Soft- -- |
| -- ware Foundation; either version 3, or (at your option) any later ver- -- |
| -- sion. GNAT is distributed in the hope that it will be useful, but WITH- -- |
| -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY -- |
| -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License -- |
| -- for more details. You should have received a copy of the GNU General -- |
| -- Public License distributed with GNAT; see file COPYING3. If not, go to -- |
| -- http://www.gnu.org/licenses for a complete copy of the license. -- |
| -- -- |
| -- GNAT was originally developed by the GNAT team at New York University. -- |
| -- Extensive contributions were provided by Ada Core Technologies Inc. -- |
| -- -- |
| ------------------------------------------------------------------------------ |
| |
| with Aspects; use Aspects; |
| with Atree; use Atree; |
| with Casing; use Casing; |
| 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 Inline; use Inline; |
| with Itypes; use Itypes; |
| with Lib; use Lib; |
| 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_Eval; use Sem_Eval; |
| with Sem_Res; use Sem_Res; |
| with Sem_Type; use Sem_Type; |
| with Sem_Util; use Sem_Util; |
| with Snames; use Snames; |
| with Stand; use Stand; |
| with Stringt; use Stringt; |
| with Targparm; use Targparm; |
| with Tbuild; use Tbuild; |
| with Ttypes; use Ttypes; |
| with Urealp; use Urealp; |
| with Validsw; use Validsw; |
| |
| package body Exp_Util is |
| |
| ----------------------- |
| -- Local Subprograms -- |
| ----------------------- |
| |
| function Build_Task_Array_Image |
| (Loc : Source_Ptr; |
| Id_Ref : Node_Id; |
| A_Type : Entity_Id; |
| Dyn : Boolean := False) return Node_Id; |
| -- Build function to generate the image string for a task that is an array |
| -- component, concatenating the images of each index. To avoid storage |
| -- leaks, the string is built with successive slice assignments. The flag |
| -- Dyn indicates whether this is called for the initialization procedure of |
| -- an array of tasks, or for the name of a dynamically created task that is |
| -- assigned to an indexed component. |
| |
| function Build_Task_Image_Function |
| (Loc : Source_Ptr; |
| Decls : List_Id; |
| Stats : List_Id; |
| Res : Entity_Id) return Node_Id; |
| -- Common processing for Task_Array_Image and Task_Record_Image. Build |
| -- function body that computes image. |
| |
| procedure Build_Task_Image_Prefix |
| (Loc : Source_Ptr; |
| Len : out Entity_Id; |
| Res : out Entity_Id; |
| Pos : out Entity_Id; |
| Prefix : Entity_Id; |
| Sum : Node_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. |
| |
| function Build_Task_Record_Image |
| (Loc : Source_Ptr; |
| Id_Ref : Node_Id; |
| Dyn : Boolean := False) return Node_Id; |
| -- Build function to generate the image string for a task that is a record |
| -- component. Concatenate name of variable with that of selector. The flag |
| -- Dyn indicates whether this is called for the initialization procedure of |
| -- record with task components, or for a dynamically created task that is |
| -- assigned to a selected component. |
| |
| procedure Evaluate_Slice_Bounds (Slice : Node_Id); |
| -- Force evaluation of bounds of a slice, which may be given by a range |
| -- or by a subtype indication with or without a constraint. |
| |
| function Make_CW_Equivalent_Type |
| (T : Entity_Id; |
| E : Node_Id) return Entity_Id; |
| -- T is a class-wide type entity, E is the initial expression node that |
| -- constrains T in case such as: " X: T := E" or "new T'(E)". This function |
| -- returns the entity of the Equivalent type and inserts on the fly the |
| -- necessary declaration such as: |
| -- |
| -- type anon is record |
| -- _parent : Root_Type (T); constrained with E discriminants (if any) |
| -- Extension : String (1 .. expr to match size of E); |
| -- end record; |
| -- |
| -- This record is compatible with any object of the class of T thanks to |
| -- the first field and has the same size as E thanks to the second. |
| |
| function Make_Literal_Range |
| (Loc : Source_Ptr; |
| 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) |
| -- 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; |
| N : Node_Id) return Entity_Id; |
| -- Create an implicit subtype of CW_Typ attached to node N |
| |
| function Requires_Cleanup_Actions |
| (L : List_Id; |
| Lib_Level : Boolean; |
| Nested_Constructs : Boolean) return Boolean; |
| -- Given a list L, determine whether it contains one of the following: |
| -- |
| -- 1) controlled objects |
| -- 2) library-level tagged types |
| -- |
| -- Lib_Level is True when the list comes from a construct at the library |
| -- level, and False otherwise. Nested_Constructs is True when any nested |
| -- packages declared in L must be processed, and False otherwise. |
| |
| ------------------------------------- |
| -- Activate_Atomic_Synchronization -- |
| ------------------------------------- |
| |
| procedure Activate_Atomic_Synchronization (N : Node_Id) is |
| Msg_Node : Node_Id; |
| |
| begin |
| case Nkind (Parent (N)) is |
| |
| -- Check for cases of appearing in the prefix of a construct where |
| -- we don't need atomic synchronization for this kind of usage. |
| |
| when |
| -- Nothing to do if we are the prefix of an attribute, since we |
| -- do not want an atomic sync operation for things like 'Size. |
| |
| N_Attribute_Reference | |
| |
| -- The N_Reference node is like an attribute |
| |
| N_Reference | |
| |
| -- Nothing to do for a reference to a component (or components) |
| -- of a composite object. Only reads and updates of the object |
| -- as a whole require atomic synchronization (RM C.6 (15)). |
| |
| N_Indexed_Component | |
| N_Selected_Component | |
| N_Slice => |
| |
| -- For all the above cases, nothing to do if we are the prefix |
| |
| if Prefix (Parent (N)) = N then |
| return; |
| end if; |
| |
| when others => null; |
| end case; |
| |
| -- Go ahead and set the flag |
| |
| Set_Atomic_Sync_Required (N); |
| |
| -- Generate info message if requested |
| |
| if Warn_On_Atomic_Synchronization then |
| case Nkind (N) is |
| when N_Identifier => |
| Msg_Node := N; |
| |
| when N_Selected_Component | N_Expanded_Name => |
| Msg_Node := Selector_Name (N); |
| |
| when N_Explicit_Dereference | N_Indexed_Component => |
| Msg_Node := Empty; |
| |
| when others => |
| pragma Assert (False); |
| return; |
| end case; |
| |
| if Present (Msg_Node) then |
| Error_Msg_N |
| ("info: atomic synchronization set for &?N?", Msg_Node); |
| else |
| Error_Msg_N |
| ("info: atomic synchronization set?N?", N); |
| end if; |
| end if; |
| end Activate_Atomic_Synchronization; |
| |
| ---------------------- |
| -- Adjust_Condition -- |
| ---------------------- |
| |
| procedure Adjust_Condition (N : Node_Id) is |
| begin |
| if No (N) then |
| return; |
| end if; |
| |
| declare |
| Loc : constant Source_Ptr := Sloc (N); |
| T : constant Entity_Id := Etype (N); |
| Ti : Entity_Id; |
| |
| begin |
| -- Defend against a call where the argument has no type, or has a |
| -- type that is not Boolean. This can occur because of prior errors. |
| |
| if No (T) or else not Is_Boolean_Type (T) then |
| return; |
| end if; |
| |
| -- Apply validity checking if needed |
| |
| if Validity_Checks_On and Validity_Check_Tests then |
| Ensure_Valid (N); |
| end if; |
| |
| -- Immediate return if standard boolean, the most common case, |
| -- where nothing needs to be done. |
| |
| if Base_Type (T) = Standard_Boolean then |
| return; |
| end if; |
| |
| -- Case of zero/non-zero semantics or non-standard enumeration |
| -- representation. In each case, we rewrite the node as: |
| |
| -- ityp!(N) /= False'Enum_Rep |
| |
| -- where ityp is an integer type with large enough size to hold any |
| -- value of type T. |
| |
| if Nonzero_Is_True (T) or else Has_Non_Standard_Rep (T) then |
| if Esize (T) <= Esize (Standard_Integer) then |
| Ti := Standard_Integer; |
| else |
| Ti := Standard_Long_Long_Integer; |
| end if; |
| |
| Rewrite (N, |
| Make_Op_Ne (Loc, |
| Left_Opnd => Unchecked_Convert_To (Ti, N), |
| Right_Opnd => |
| Make_Attribute_Reference (Loc, |
| Attribute_Name => Name_Enum_Rep, |
| Prefix => |
| New_Occurrence_Of (First_Literal (T), Loc)))); |
| Analyze_And_Resolve (N, Standard_Boolean); |
| |
| else |
| Rewrite (N, Convert_To (Standard_Boolean, N)); |
| Analyze_And_Resolve (N, Standard_Boolean); |
| end if; |
| end; |
| end Adjust_Condition; |
| |
| ------------------------ |
| -- Adjust_Result_Type -- |
| ------------------------ |
| |
| procedure Adjust_Result_Type (N : Node_Id; T : Entity_Id) is |
| begin |
| -- Ignore call if current type is not Standard.Boolean |
| |
| if Etype (N) /= Standard_Boolean then |
| return; |
| end if; |
| |
| -- If result is already of correct type, nothing to do. Note that |
| -- this will get the most common case where everything has a type |
| -- of Standard.Boolean. |
| |
| if Base_Type (T) = Standard_Boolean then |
| return; |
| |
| else |
| declare |
| KP : constant Node_Kind := Nkind (Parent (N)); |
| |
| begin |
| -- If result is to be used as a Condition in the syntax, no need |
| -- to convert it back, since if it was changed to Standard.Boolean |
| -- using Adjust_Condition, that is just fine for this usage. |
| |
| if KP in N_Raise_xxx_Error or else KP in N_Has_Condition then |
| return; |
| |
| -- If result is an operand of another logical operation, no need |
| -- 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 in N_Short_Circuit |
| or else KP = N_Op_Not |
| then |
| return; |
| |
| -- Otherwise we perform a conversion from the current type, which |
| -- must be Standard.Boolean, to the desired type. |
| |
| else |
| Set_Analyzed (N); |
| Rewrite (N, Convert_To (T, N)); |
| Analyze_And_Resolve (N, T); |
| end if; |
| end; |
| end if; |
| end Adjust_Result_Type; |
| |
| -------------------------- |
| -- Append_Freeze_Action -- |
| -------------------------- |
| |
| procedure Append_Freeze_Action (T : Entity_Id; N : Node_Id) is |
| Fnode : Node_Id; |
| |
| begin |
| Ensure_Freeze_Node (T); |
| Fnode := Freeze_Node (T); |
| |
| if No (Actions (Fnode)) then |
| Set_Actions (Fnode, New_List (N)); |
| else |
| Append (N, Actions (Fnode)); |
| end if; |
| |
| end Append_Freeze_Action; |
| |
| --------------------------- |
| -- Append_Freeze_Actions -- |
| --------------------------- |
| |
| procedure Append_Freeze_Actions (T : Entity_Id; L : List_Id) is |
| Fnode : Node_Id; |
| |
| begin |
| if No (L) then |
| return; |
| end if; |
| |
| Ensure_Freeze_Node (T); |
| Fnode := Freeze_Node (T); |
| |
| if No (Actions (Fnode)) then |
| Set_Actions (Fnode, L); |
| else |
| Append_List (L, Actions (Fnode)); |
| end if; |
| end Append_Freeze_Actions; |
| |
| ------------------------------------ |
| -- Build_Allocate_Deallocate_Proc -- |
| ------------------------------------ |
| |
| procedure Build_Allocate_Deallocate_Proc |
| (N : Node_Id; |
| Is_Allocate : Boolean) |
| is |
| Desig_Typ : Entity_Id; |
| Expr : Node_Id; |
| Pool_Id : Entity_Id; |
| Proc_To_Call : Node_Id := Empty; |
| Ptr_Typ : Entity_Id; |
| |
| function Find_Object (E : Node_Id) return Node_Id; |
| -- Given an arbitrary expression of an allocator, try to find an object |
| -- reference in it, otherwise return the original expression. |
| |
| function Is_Allocate_Deallocate_Proc (Subp : Entity_Id) return Boolean; |
| -- Determine whether subprogram Subp denotes a custom allocate or |
| -- deallocate. |
| |
| ----------------- |
| -- Find_Object -- |
| ----------------- |
| |
| function Find_Object (E : Node_Id) return Node_Id is |
| Expr : Node_Id; |
| |
| begin |
| pragma Assert (Is_Allocate); |
| |
| Expr := E; |
| loop |
| if Nkind (Expr) = N_Explicit_Dereference then |
| Expr := Prefix (Expr); |
| |
| elsif Nkind (Expr) = N_Qualified_Expression then |
| Expr := Expression (Expr); |
| |
| elsif Nkind (Expr) = N_Unchecked_Type_Conversion then |
| |
| -- When interface class-wide types are involved in allocation, |
| -- the expander introduces several levels of address arithmetic |
| -- to perform dispatch table displacement. In this scenario the |
| -- object appears as: |
| |
| -- Tag_Ptr (Base_Address (<object>'Address)) |
| |
| -- Detect this case and utilize the whole expression as the |
| -- "object" since it now points to the proper dispatch table. |
| |
| if Is_RTE (Etype (Expr), RE_Tag_Ptr) then |
| exit; |
| |
| -- Continue to strip the object |
| |
| else |
| Expr := Expression (Expr); |
| end if; |
| |
| else |
| exit; |
| end if; |
| end loop; |
| |
| return Expr; |
| end Find_Object; |
| |
| --------------------------------- |
| -- Is_Allocate_Deallocate_Proc -- |
| --------------------------------- |
| |
| function Is_Allocate_Deallocate_Proc (Subp : Entity_Id) return Boolean is |
| begin |
| -- Look for a subprogram body with only one statement which is a |
| -- call to Allocate_Any_Controlled / Deallocate_Any_Controlled. |
| |
| if Ekind (Subp) = E_Procedure |
| and then Nkind (Parent (Parent (Subp))) = N_Subprogram_Body |
| then |
| declare |
| HSS : constant Node_Id := |
| Handled_Statement_Sequence (Parent (Parent (Subp))); |
| Proc : Entity_Id; |
| |
| begin |
| if Present (Statements (HSS)) |
| and then Nkind (First (Statements (HSS))) = |
| N_Procedure_Call_Statement |
| then |
| Proc := Entity (Name (First (Statements (HSS)))); |
| |
| return |
| Is_RTE (Proc, RE_Allocate_Any_Controlled) |
| or else Is_RTE (Proc, RE_Deallocate_Any_Controlled); |
| end if; |
| end; |
| end if; |
| |
| return False; |
| end Is_Allocate_Deallocate_Proc; |
| |
| -- Start of processing for Build_Allocate_Deallocate_Proc |
| |
| begin |
| -- Obtain the attributes of the allocation / deallocation |
| |
| if Nkind (N) = N_Free_Statement then |
| Expr := Expression (N); |
| Ptr_Typ := Base_Type (Etype (Expr)); |
| Proc_To_Call := Procedure_To_Call (N); |
| |
| else |
| if Nkind (N) = N_Object_Declaration then |
| Expr := Expression (N); |
| else |
| Expr := N; |
| end if; |
| |
| -- In certain cases an allocator with a qualified expression may |
| -- be relocated and used as the initialization expression of a |
| -- temporary: |
| |
| -- before: |
| -- Obj : Ptr_Typ := new Desig_Typ'(...); |
| |
| -- after: |
| -- Tmp : Ptr_Typ := new Desig_Typ'(...); |
| -- Obj : Ptr_Typ := Tmp; |
| |
| -- Since the allocator is always marked as analyzed to avoid infinite |
| -- expansion, it will never be processed by this routine given that |
| -- the designated type needs finalization actions. Detect this case |
| -- and complete the expansion of the allocator. |
| |
| if Nkind (Expr) = N_Identifier |
| and then Nkind (Parent (Entity (Expr))) = N_Object_Declaration |
| and then Nkind (Expression (Parent (Entity (Expr)))) = N_Allocator |
| then |
| Build_Allocate_Deallocate_Proc (Parent (Entity (Expr)), True); |
| return; |
| end if; |
| |
| -- The allocator may have been rewritten into something else in which |
| -- case the expansion performed by this routine does not apply. |
| |
| if Nkind (Expr) /= N_Allocator then |
| return; |
| end if; |
| |
| Ptr_Typ := Base_Type (Etype (Expr)); |
| Proc_To_Call := Procedure_To_Call (Expr); |
| end if; |
| |
| Pool_Id := Associated_Storage_Pool (Ptr_Typ); |
| Desig_Typ := Available_View (Designated_Type (Ptr_Typ)); |
| |
| -- Handle concurrent types |
| |
| if Is_Concurrent_Type (Desig_Typ) |
| and then Present (Corresponding_Record_Type (Desig_Typ)) |
| then |
| Desig_Typ := Corresponding_Record_Type (Desig_Typ); |
| end if; |
| |
| -- Do not process allocations / deallocations without a pool |
| |
| if No (Pool_Id) then |
| return; |
| |
| -- Do not process allocations on / deallocations from the secondary |
| -- stack. |
| |
| elsif Is_RTE (Pool_Id, RE_SS_Pool) then |
| return; |
| |
| -- Do not replicate the machinery if the allocator / free has already |
| -- been expanded and has a custom Allocate / Deallocate. |
| |
| elsif Present (Proc_To_Call) |
| and then Is_Allocate_Deallocate_Proc (Proc_To_Call) |
| then |
| return; |
| end if; |
| |
| if Needs_Finalization (Desig_Typ) then |
| |
| -- Certain run-time configurations and targets do not provide support |
| -- for controlled types. |
| |
| if Restriction_Active (No_Finalization) then |
| return; |
| |
| -- Do nothing if the access type may never allocate / deallocate |
| -- objects. |
| |
| elsif No_Pool_Assigned (Ptr_Typ) then |
| return; |
| |
| -- Access-to-controlled types are not supported on .NET/JVM since |
| -- these targets cannot support pools and address arithmetic. |
| |
| elsif VM_Target /= No_VM then |
| return; |
| end if; |
| |
| -- The allocation / deallocation of a controlled object must be |
| -- chained on / detached from a finalization master. |
| |
| pragma Assert (Present (Finalization_Master (Ptr_Typ))); |
| |
| -- The only other kind of allocation / deallocation supported by this |
| -- routine is on / from a subpool. |
| |
| elsif Nkind (Expr) = N_Allocator |
| and then No (Subpool_Handle_Name (Expr)) |
| then |
| return; |
| end if; |
| |
| declare |
| Loc : constant Source_Ptr := Sloc (N); |
| Addr_Id : constant Entity_Id := Make_Temporary (Loc, 'A'); |
| Alig_Id : constant Entity_Id := Make_Temporary (Loc, 'L'); |
| Proc_Id : constant Entity_Id := Make_Temporary (Loc, 'P'); |
| Size_Id : constant Entity_Id := Make_Temporary (Loc, 'S'); |
| |
| Actuals : List_Id; |
| Fin_Addr_Id : Entity_Id; |
| Fin_Mas_Act : Node_Id; |
| Fin_Mas_Id : Entity_Id; |
| Proc_To_Call : Entity_Id; |
| Subpool : Node_Id := Empty; |
| |
| begin |
| -- Step 1: Construct all the actuals for the call to library routine |
| -- Allocate_Any_Controlled / Deallocate_Any_Controlled. |
| |
| -- a) Storage pool |
| |
| Actuals := New_List (New_Occurrence_Of (Pool_Id, Loc)); |
| |
| if Is_Allocate then |
| |
| -- b) Subpool |
| |
| if Nkind (Expr) = N_Allocator then |
| Subpool := Subpool_Handle_Name (Expr); |
| end if; |
| |
| -- If a subpool is present it can be an arbitrary name, so make |
| -- the actual by copying the tree. |
| |
| if Present (Subpool) then |
| Append_To (Actuals, New_Copy_Tree (Subpool, New_Sloc => Loc)); |
| else |
| Append_To (Actuals, Make_Null (Loc)); |
| end if; |
| |
| -- c) Finalization master |
| |
| if Needs_Finalization (Desig_Typ) then |
| Fin_Mas_Id := Finalization_Master (Ptr_Typ); |
| Fin_Mas_Act := New_Occurrence_Of (Fin_Mas_Id, Loc); |
| |
| -- Handle the case where the master is actually a pointer to a |
| -- master. This case arises in build-in-place functions. |
| |
| if Is_Access_Type (Etype (Fin_Mas_Id)) then |
| Append_To (Actuals, Fin_Mas_Act); |
| else |
| Append_To (Actuals, |
| Make_Attribute_Reference (Loc, |
| Prefix => Fin_Mas_Act, |
| Attribute_Name => Name_Unrestricted_Access)); |
| end if; |
| else |
| Append_To (Actuals, Make_Null (Loc)); |
| end if; |
| |
| -- d) Finalize_Address |
| |
| -- Primitive Finalize_Address is never generated in CodePeer mode |
| -- since it contains an Unchecked_Conversion. |
| |
| if Needs_Finalization (Desig_Typ) and then not CodePeer_Mode then |
| Fin_Addr_Id := Finalize_Address (Desig_Typ); |
| pragma Assert (Present (Fin_Addr_Id)); |
| |
| Append_To (Actuals, |
| Make_Attribute_Reference (Loc, |
| Prefix => New_Occurrence_Of (Fin_Addr_Id, Loc), |
| Attribute_Name => Name_Unrestricted_Access)); |
| else |
| Append_To (Actuals, Make_Null (Loc)); |
| end if; |
| end if; |
| |
| -- e) Address |
| -- f) Storage_Size |
| -- g) Alignment |
| |
| Append_To (Actuals, New_Occurrence_Of (Addr_Id, Loc)); |
| Append_To (Actuals, New_Occurrence_Of (Size_Id, Loc)); |
| |
| if Is_Allocate or else not Is_Class_Wide_Type (Desig_Typ) then |
| Append_To (Actuals, New_Occurrence_Of (Alig_Id, Loc)); |
| |
| -- For deallocation of class-wide types we obtain the value of |
| -- alignment from the Type Specific Record of the deallocated object. |
| -- This is needed because the frontend expansion of class-wide types |
| -- into equivalent types confuses the backend. |
| |
| else |
| -- Generate: |
| -- Obj.all'Alignment |
| |
| -- ... because 'Alignment applied to class-wide types is expanded |
| -- into the code that reads the value of alignment from the TSD |
| -- (see Expand_N_Attribute_Reference) |
| |
| Append_To (Actuals, |
| Unchecked_Convert_To (RTE (RE_Storage_Offset), |
| Make_Attribute_Reference (Loc, |
| Prefix => |
| Make_Explicit_Dereference (Loc, Relocate_Node (Expr)), |
| Attribute_Name => Name_Alignment))); |
| end if; |
| |
| -- h) Is_Controlled |
| |
| if Needs_Finalization (Desig_Typ) then |
| declare |
| Flag_Id : constant Entity_Id := Make_Temporary (Loc, 'F'); |
| Flag_Expr : Node_Id; |
| Param : Node_Id; |
| Temp : Node_Id; |
| |
| begin |
| if Is_Allocate then |
| Temp := Find_Object (Expression (Expr)); |
| else |
| Temp := Expr; |
| end if; |
| |
| -- Processing for allocations where the expression is a subtype |
| -- indication. |
| |
| if Is_Allocate |
| and then Is_Entity_Name (Temp) |
| and then Is_Type (Entity (Temp)) |
| then |
| Flag_Expr := |
| New_Occurrence_Of |
| (Boolean_Literals |
| (Needs_Finalization (Entity (Temp))), Loc); |
| |
| -- The allocation / deallocation of a class-wide object relies |
| -- on a runtime check to determine whether the object is truly |
| -- controlled or not. Depending on this check, the finalization |
| -- machinery will request or reclaim extra storage reserved for |
| -- a list header. |
| |
| elsif Is_Class_Wide_Type (Desig_Typ) then |
| |
| -- Detect a special case where interface class-wide types |
| -- are involved as the object appears as: |
| |
| -- Tag_Ptr (Base_Address (<object>'Address)) |
| |
| -- The expression already yields the proper tag, generate: |
| |
| -- Temp.all |
| |
| if Is_RTE (Etype (Temp), RE_Tag_Ptr) then |
| Param := |
| Make_Explicit_Dereference (Loc, |
| Prefix => Relocate_Node (Temp)); |
| |
| -- In the default case, obtain the tag of the object about |
| -- to be allocated / deallocated. Generate: |
| |
| -- Temp'Tag |
| |
| else |
| Param := |
| Make_Attribute_Reference (Loc, |
| Prefix => Relocate_Node (Temp), |
| Attribute_Name => Name_Tag); |
| end if; |
| |
| -- Generate: |
| -- Needs_Finalization (<Param>) |
| |
| Flag_Expr := |
| Make_Function_Call (Loc, |
| Name => |
| New_Occurrence_Of (RTE (RE_Needs_Finalization), Loc), |
| Parameter_Associations => New_List (Param)); |
| |
| -- Processing for generic actuals |
| |
| elsif Is_Generic_Actual_Type (Desig_Typ) then |
| Flag_Expr := |
| New_Occurrence_Of (Boolean_Literals |
| (Needs_Finalization (Base_Type (Desig_Typ))), Loc); |
| |
| -- The object does not require any specialized checks, it is |
| -- known to be controlled. |
| |
| else |
| Flag_Expr := New_Occurrence_Of (Standard_True, Loc); |
| end if; |
| |
| -- Create the temporary which represents the finalization state |
| -- of the expression. Generate: |
| -- |
| -- F : constant Boolean := <Flag_Expr>; |
| |
| Insert_Action (N, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Flag_Id, |
| Constant_Present => True, |
| Object_Definition => |
| New_Occurrence_Of (Standard_Boolean, Loc), |
| Expression => Flag_Expr)); |
| |
| Append_To (Actuals, New_Occurrence_Of (Flag_Id, Loc)); |
| end; |
| |
| -- The object is not controlled |
| |
| else |
| Append_To (Actuals, New_Occurrence_Of (Standard_False, Loc)); |
| end if; |
| |
| -- i) On_Subpool |
| |
| if Is_Allocate then |
| Append_To (Actuals, |
| New_Occurrence_Of (Boolean_Literals (Present (Subpool)), Loc)); |
| end if; |
| |
| -- Step 2: Build a wrapper Allocate / Deallocate which internally |
| -- calls Allocate_Any_Controlled / Deallocate_Any_Controlled. |
| |
| -- Select the proper routine to call |
| |
| if Is_Allocate then |
| Proc_To_Call := RTE (RE_Allocate_Any_Controlled); |
| else |
| Proc_To_Call := RTE (RE_Deallocate_Any_Controlled); |
| end if; |
| |
| -- Create a custom Allocate / Deallocate routine which has identical |
| -- profile to that of System.Storage_Pools. |
| |
| Insert_Action (N, |
| Make_Subprogram_Body (Loc, |
| Specification => |
| |
| -- procedure Pnn |
| |
| Make_Procedure_Specification (Loc, |
| Defining_Unit_Name => Proc_Id, |
| Parameter_Specifications => New_List ( |
| |
| -- P : Root_Storage_Pool |
| |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => Make_Temporary (Loc, 'P'), |
| Parameter_Type => |
| New_Occurrence_Of (RTE (RE_Root_Storage_Pool), Loc)), |
| |
| -- A : [out] Address |
| |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => Addr_Id, |
| Out_Present => Is_Allocate, |
| Parameter_Type => |
| New_Occurrence_Of (RTE (RE_Address), Loc)), |
| |
| -- S : Storage_Count |
| |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => Size_Id, |
| Parameter_Type => |
| New_Occurrence_Of (RTE (RE_Storage_Count), Loc)), |
| |
| -- L : Storage_Count |
| |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => Alig_Id, |
| Parameter_Type => |
| New_Occurrence_Of (RTE (RE_Storage_Count), Loc)))), |
| |
| Declarations => No_List, |
| |
| Handled_Statement_Sequence => |
| Make_Handled_Sequence_Of_Statements (Loc, |
| Statements => New_List ( |
| Make_Procedure_Call_Statement (Loc, |
| Name => New_Occurrence_Of (Proc_To_Call, Loc), |
| Parameter_Associations => Actuals))))); |
| |
| -- The newly generated Allocate / Deallocate becomes the default |
| -- procedure to call when the back end processes the allocation / |
| -- deallocation. |
| |
| if Is_Allocate then |
| Set_Procedure_To_Call (Expr, Proc_Id); |
| else |
| Set_Procedure_To_Call (N, Proc_Id); |
| end if; |
| end; |
| end Build_Allocate_Deallocate_Proc; |
| |
| ------------------------ |
| -- Build_Runtime_Call -- |
| ------------------------ |
| |
| function Build_Runtime_Call (Loc : Source_Ptr; RE : RE_Id) return Node_Id is |
| begin |
| -- If entity is not available, we can skip making the call (this avoids |
| -- junk duplicated error messages in a number of cases). |
| |
| if not RTE_Available (RE) then |
| return Make_Null_Statement (Loc); |
| else |
| return |
| Make_Procedure_Call_Statement (Loc, |
| Name => New_Occurrence_Of (RTE (RE), Loc)); |
| end if; |
| end Build_Runtime_Call; |
| |
| ------------------------ |
| -- Build_SS_Mark_Call -- |
| ------------------------ |
| |
| function Build_SS_Mark_Call |
| (Loc : Source_Ptr; |
| Mark : Entity_Id) return Node_Id |
| is |
| begin |
| -- Generate: |
| -- Mark : constant Mark_Id := SS_Mark; |
| |
| return |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Mark, |
| Constant_Present => True, |
| Object_Definition => |
| New_Occurrence_Of (RTE (RE_Mark_Id), Loc), |
| Expression => |
| Make_Function_Call (Loc, |
| Name => New_Occurrence_Of (RTE (RE_SS_Mark), Loc))); |
| end Build_SS_Mark_Call; |
| |
| --------------------------- |
| -- Build_SS_Release_Call -- |
| --------------------------- |
| |
| function Build_SS_Release_Call |
| (Loc : Source_Ptr; |
| Mark : Entity_Id) return Node_Id |
| is |
| begin |
| -- Generate: |
| -- SS_Release (Mark); |
| |
| return |
| Make_Procedure_Call_Statement (Loc, |
| Name => |
| New_Occurrence_Of (RTE (RE_SS_Release), Loc), |
| Parameter_Associations => New_List ( |
| New_Occurrence_Of (Mark, Loc))); |
| end Build_SS_Release_Call; |
| |
| ---------------------------- |
| -- Build_Task_Array_Image -- |
| ---------------------------- |
| |
| -- This function generates the body for a function that constructs the |
| -- image string for a task that is an array component. The function is |
| -- local to the init proc for the array type, and is called for each one |
| -- of the components. The constructed image has the form of an indexed |
| -- component, whose prefix is the outer variable of the array type. |
| -- The n-dimensional array type has known indexes Index, Index2... |
| |
| -- Id_Ref is an indexed component form created by the enclosing init proc. |
| -- Its successive indexes 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: |
| |
| -- function F return String is |
| -- Pref : string renames Task_Name; |
| -- T1 : String := Index1'Image (Val1); |
| -- ... |
| -- Tn : String := indexn'image (Valn); |
| -- Len : Integer := T1'Length + ... + Tn'Length + n + 1; |
| -- -- Len includes commas and the end parentheses. |
| -- Res : String (1..Len); |
| -- Pos : Integer := Pref'Length; |
| -- |
| -- begin |
| -- Res (1 .. Pos) := Pref; |
| -- Pos := Pos + 1; |
| -- Res (Pos) := '('; |
| -- Pos := Pos + 1; |
| -- Res (Pos .. Pos + T1'Length - 1) := T1; |
| -- Pos := Pos + T1'Length; |
| -- Res (Pos) := '.'; |
| -- Pos := Pos + 1; |
| -- ... |
| -- Res (Pos .. Pos + Tn'Length - 1) := Tn; |
| -- Res (Len) := ')'; |
| -- |
| -- return Res; |
| -- end F; |
| -- |
| -- Needless to say, multidimensional arrays of tasks are rare enough that |
| -- the bulkiness of this code is not really a concern. |
| |
| function Build_Task_Array_Image |
| (Loc : Source_Ptr; |
| Id_Ref : Node_Id; |
| A_Type : Entity_Id; |
| Dyn : Boolean := False) return Node_Id |
| is |
| Dims : constant Nat := Number_Dimensions (A_Type); |
| -- Number of dimensions for array of tasks |
| |
| Temps : array (1 .. Dims) of Entity_Id; |
| -- Array of temporaries to hold string for each index |
| |
| Indx : Node_Id; |
| -- Index expression |
| |
| Len : Entity_Id; |
| -- Total length of generated name |
| |
| Pos : Entity_Id; |
| -- Running index for substring assignments |
| |
| Pref : constant Entity_Id := Make_Temporary (Loc, 'P'); |
| -- Name of enclosing variable, prefix of resulting name |
| |
| Res : Entity_Id; |
| -- String to hold result |
| |
| Val : Node_Id; |
| -- Value of successive indexes |
| |
| Sum : Node_Id; |
| -- Expression to compute total size of string |
| |
| T : Entity_Id; |
| -- Entity for name at one index position |
| |
| Decls : constant List_Id := New_List; |
| Stats : constant List_Id := New_List; |
| |
| begin |
| -- For a dynamic task, the name comes from the target variable. For a |
| -- static one it is a formal of the enclosing init proc. |
| |
| if Dyn then |
| Get_Name_String (Chars (Entity (Prefix (Id_Ref)))); |
| Append_To (Decls, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Pref, |
| Object_Definition => New_Occurrence_Of (Standard_String, Loc), |
| Expression => |
| Make_String_Literal (Loc, |
| Strval => String_From_Name_Buffer))); |
| |
| else |
| Append_To (Decls, |
| Make_Object_Renaming_Declaration (Loc, |
| Defining_Identifier => Pref, |
| Subtype_Mark => New_Occurrence_Of (Standard_String, Loc), |
| Name => Make_Identifier (Loc, Name_uTask_Name))); |
| end if; |
| |
| Indx := First_Index (A_Type); |
| Val := First (Expressions (Id_Ref)); |
| |
| for J in 1 .. Dims loop |
| T := Make_Temporary (Loc, 'T'); |
| Temps (J) := T; |
| |
| Append_To (Decls, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => T, |
| Object_Definition => New_Occurrence_Of (Standard_String, Loc), |
| Expression => |
| Make_Attribute_Reference (Loc, |
| Attribute_Name => Name_Image, |
| Prefix => New_Occurrence_Of (Etype (Indx), Loc), |
| Expressions => New_List (New_Copy_Tree (Val))))); |
| |
| Next_Index (Indx); |
| Next (Val); |
| end loop; |
| |
| Sum := Make_Integer_Literal (Loc, Dims + 1); |
| |
| Sum := |
| Make_Op_Add (Loc, |
| Left_Opnd => Sum, |
| Right_Opnd => |
| Make_Attribute_Reference (Loc, |
| Attribute_Name => Name_Length, |
| Prefix => New_Occurrence_Of (Pref, Loc), |
| Expressions => New_List (Make_Integer_Literal (Loc, 1)))); |
| |
| for J in 1 .. Dims loop |
| Sum := |
| Make_Op_Add (Loc, |
| Left_Opnd => Sum, |
| Right_Opnd => |
| Make_Attribute_Reference (Loc, |
| Attribute_Name => Name_Length, |
| Prefix => |
| New_Occurrence_Of (Temps (J), Loc), |
| Expressions => New_List (Make_Integer_Literal (Loc, 1)))); |
| end loop; |
| |
| Build_Task_Image_Prefix (Loc, Len, Res, Pos, Pref, Sum, Decls, Stats); |
| |
| Set_Character_Literal_Name (Char_Code (Character'Pos ('('))); |
| |
| Append_To (Stats, |
| Make_Assignment_Statement (Loc, |
| Name => |
| Make_Indexed_Component (Loc, |
| Prefix => New_Occurrence_Of (Res, Loc), |
| Expressions => New_List (New_Occurrence_Of (Pos, Loc))), |
| Expression => |
| Make_Character_Literal (Loc, |
| Chars => Name_Find, |
| Char_Literal_Value => UI_From_Int (Character'Pos ('('))))); |
| |
| Append_To (Stats, |
| Make_Assignment_Statement (Loc, |
| Name => New_Occurrence_Of (Pos, Loc), |
| Expression => |
| Make_Op_Add (Loc, |
| Left_Opnd => New_Occurrence_Of (Pos, Loc), |
| Right_Opnd => Make_Integer_Literal (Loc, 1)))); |
| |
| for J in 1 .. Dims loop |
| |
| Append_To (Stats, |
| Make_Assignment_Statement (Loc, |
| Name => |
| Make_Slice (Loc, |
| Prefix => New_Occurrence_Of (Res, Loc), |
| Discrete_Range => |
| Make_Range (Loc, |
| Low_Bound => New_Occurrence_Of (Pos, Loc), |
| High_Bound => |
| Make_Op_Subtract (Loc, |
| Left_Opnd => |
| Make_Op_Add (Loc, |
| Left_Opnd => New_Occurrence_Of (Pos, Loc), |
| Right_Opnd => |
| Make_Attribute_Reference (Loc, |
| Attribute_Name => Name_Length, |
| Prefix => |
| New_Occurrence_Of (Temps (J), Loc), |
| Expressions => |
| New_List (Make_Integer_Literal (Loc, 1)))), |
| Right_Opnd => Make_Integer_Literal (Loc, 1)))), |
| |
| Expression => New_Occurrence_Of (Temps (J), Loc))); |
| |
| if J < Dims then |
| Append_To (Stats, |
| Make_Assignment_Statement (Loc, |
| Name => New_Occurrence_Of (Pos, Loc), |
| Expression => |
| Make_Op_Add (Loc, |
| Left_Opnd => New_Occurrence_Of (Pos, Loc), |
| Right_Opnd => |
| Make_Attribute_Reference (Loc, |
| Attribute_Name => Name_Length, |
| Prefix => New_Occurrence_Of (Temps (J), Loc), |
| Expressions => |
| New_List (Make_Integer_Literal (Loc, 1)))))); |
| |
| Set_Character_Literal_Name (Char_Code (Character'Pos (','))); |
| |
| Append_To (Stats, |
| Make_Assignment_Statement (Loc, |
| Name => Make_Indexed_Component (Loc, |
| Prefix => New_Occurrence_Of (Res, Loc), |
| Expressions => New_List (New_Occurrence_Of (Pos, Loc))), |
| Expression => |
| Make_Character_Literal (Loc, |
| Chars => Name_Find, |
| Char_Literal_Value => UI_From_Int (Character'Pos (','))))); |
| |
| Append_To (Stats, |
| Make_Assignment_Statement (Loc, |
| Name => New_Occurrence_Of (Pos, Loc), |
| Expression => |
| Make_Op_Add (Loc, |
| Left_Opnd => New_Occurrence_Of (Pos, Loc), |
| Right_Opnd => Make_Integer_Literal (Loc, 1)))); |
| end if; |
| end loop; |
| |
| Set_Character_Literal_Name (Char_Code (Character'Pos (')'))); |
| |
| Append_To (Stats, |
| Make_Assignment_Statement (Loc, |
| Name => |
| Make_Indexed_Component (Loc, |
| Prefix => New_Occurrence_Of (Res, Loc), |
| Expressions => New_List (New_Occurrence_Of (Len, Loc))), |
| Expression => |
| Make_Character_Literal (Loc, |
| Chars => Name_Find, |
| Char_Literal_Value => UI_From_Int (Character'Pos (')'))))); |
| return Build_Task_Image_Function (Loc, Decls, Stats, Res); |
| end Build_Task_Array_Image; |
| |
| ---------------------------- |
| -- Build_Task_Image_Decls -- |
| ---------------------------- |
| |
| function Build_Task_Image_Decls |
| (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; |
| Decl : Node_Id; |
| Expr : Node_Id := Empty; |
| Fun : Node_Id := Empty; |
| Is_Dyn : constant Boolean := |
| Nkind (Parent (Id_Ref)) = N_Assignment_Statement |
| and then |
| Nkind (Expression (Parent (Id_Ref))) = N_Allocator; |
| |
| begin |
| -- If Discard_Names or No_Implicit_Heap_Allocations are in effect, |
| -- generate a dummy declaration only. |
| |
| if Restriction_Active (No_Implicit_Heap_Allocations) |
| or else Global_Discard_Names |
| then |
| T_Id := Make_Temporary (Loc, 'J'); |
| Name_Len := 0; |
| |
| return |
| New_List ( |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => T_Id, |
| Object_Definition => New_Occurrence_Of (Standard_String, Loc), |
| Expression => |
| Make_String_Literal (Loc, |
| Strval => String_From_Name_Buffer))); |
| |
| else |
| if Nkind (Id_Ref) = N_Identifier |
| or else Nkind (Id_Ref) = N_Defining_Identifier |
| then |
| -- For a simple variable, the image of the task is built from |
| -- the name of the variable. To avoid possible conflict with the |
| -- anonymous type created for a single protected object, add a |
| -- numeric suffix. |
| |
| T_Id := |
| Make_Defining_Identifier (Loc, |
| New_External_Name (Chars (Id_Ref), 'T', 1)); |
| |
| Get_Name_String (Chars (Id_Ref)); |
| |
| Expr := |
| Make_String_Literal (Loc, |
| Strval => String_From_Name_Buffer); |
| |
| elsif Nkind (Id_Ref) = N_Selected_Component then |
| T_Id := |
| Make_Defining_Identifier (Loc, |
| New_External_Name (Chars (Selector_Name (Id_Ref)), 'T')); |
| Fun := Build_Task_Record_Image (Loc, Id_Ref, Is_Dyn); |
| |
| elsif Nkind (Id_Ref) = N_Indexed_Component then |
| T_Id := |
| Make_Defining_Identifier (Loc, |
| New_External_Name (Chars (A_Type), 'N')); |
| |
| Fun := Build_Task_Array_Image (Loc, Id_Ref, A_Type, Is_Dyn); |
| end if; |
| end if; |
| |
| if Present (Fun) then |
| 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, |
| Defining_Identifier => T_Id, |
| Object_Definition => New_Occurrence_Of (Standard_String, Loc), |
| Constant_Present => True, |
| Expression => Expr); |
| |
| Append (Decl, Decls); |
| return Decls; |
| end Build_Task_Image_Decls; |
| |
| ------------------------------- |
| -- Build_Task_Image_Function -- |
| ------------------------------- |
| |
| function Build_Task_Image_Function |
| (Loc : Source_Ptr; |
| Decls : List_Id; |
| Stats : List_Id; |
| Res : Entity_Id) return Node_Id |
| is |
| Spec : Node_Id; |
| |
| begin |
| Append_To (Stats, |
| Make_Simple_Return_Statement (Loc, |
| Expression => New_Occurrence_Of (Res, Loc))); |
| |
| Spec := Make_Function_Specification (Loc, |
| Defining_Unit_Name => Make_Temporary (Loc, 'F'), |
| Result_Definition => New_Occurrence_Of (Standard_String, Loc)); |
| |
| -- Calls to 'Image use the secondary stack, which must be cleaned up |
| -- after the task name is built. |
| |
| return Make_Subprogram_Body (Loc, |
| Specification => Spec, |
| Declarations => Decls, |
| Handled_Statement_Sequence => |
| Make_Handled_Sequence_Of_Statements (Loc, Statements => Stats)); |
| end Build_Task_Image_Function; |
| |
| ----------------------------- |
| -- Build_Task_Image_Prefix -- |
| ----------------------------- |
| |
| procedure Build_Task_Image_Prefix |
| (Loc : Source_Ptr; |
| Len : out Entity_Id; |
| Res : out Entity_Id; |
| Pos : out Entity_Id; |
| Prefix : Entity_Id; |
| Sum : Node_Id; |
| Decls : List_Id; |
| Stats : List_Id) |
| is |
| begin |
| Len := Make_Temporary (Loc, 'L', Sum); |
| |
| Append_To (Decls, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Len, |
| Object_Definition => New_Occurrence_Of (Standard_Integer, Loc), |
| Expression => Sum)); |
| |
| Res := Make_Temporary (Loc, 'R'); |
| |
| Append_To (Decls, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Res, |
| Object_Definition => |
| Make_Subtype_Indication (Loc, |
| Subtype_Mark => New_Occurrence_Of (Standard_String, Loc), |
| Constraint => |
| Make_Index_Or_Discriminant_Constraint (Loc, |
| Constraints => |
| New_List ( |
| Make_Range (Loc, |
| Low_Bound => Make_Integer_Literal (Loc, 1), |
| High_Bound => New_Occurrence_Of (Len, Loc))))))); |
| |
| -- Indicate that the result is an internal temporary, so it does not |
| -- receive a bogus initialization when declaration is expanded. This |
| -- is both efficient, and prevents anomalies in the handling of |
| -- dynamic objects on the secondary stack. |
| |
| Set_Is_Internal (Res); |
| Pos := Make_Temporary (Loc, 'P'); |
| |
| Append_To (Decls, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Pos, |
| Object_Definition => New_Occurrence_Of (Standard_Integer, Loc))); |
| |
| -- Pos := Prefix'Length; |
| |
| Append_To (Stats, |
| Make_Assignment_Statement (Loc, |
| Name => New_Occurrence_Of (Pos, Loc), |
| Expression => |
| Make_Attribute_Reference (Loc, |
| Attribute_Name => Name_Length, |
| Prefix => New_Occurrence_Of (Prefix, Loc), |
| Expressions => New_List (Make_Integer_Literal (Loc, 1))))); |
| |
| -- Res (1 .. Pos) := Prefix; |
| |
| Append_To (Stats, |
| Make_Assignment_Statement (Loc, |
| Name => |
| Make_Slice (Loc, |
| Prefix => New_Occurrence_Of (Res, Loc), |
| Discrete_Range => |
| Make_Range (Loc, |
| Low_Bound => Make_Integer_Literal (Loc, 1), |
| High_Bound => New_Occurrence_Of (Pos, Loc))), |
| |
| Expression => New_Occurrence_Of (Prefix, Loc))); |
| |
| Append_To (Stats, |
| Make_Assignment_Statement (Loc, |
| Name => New_Occurrence_Of (Pos, Loc), |
| Expression => |
| Make_Op_Add (Loc, |
| Left_Opnd => New_Occurrence_Of (Pos, Loc), |
| Right_Opnd => Make_Integer_Literal (Loc, 1)))); |
| end Build_Task_Image_Prefix; |
| |
| ----------------------------- |
| -- Build_Task_Record_Image -- |
| ----------------------------- |
| |
| function Build_Task_Record_Image |
| (Loc : Source_Ptr; |
| Id_Ref : Node_Id; |
| Dyn : Boolean := False) return Node_Id |
| is |
| Len : Entity_Id; |
| -- Total length of generated name |
| |
| Pos : Entity_Id; |
| -- Index into result |
| |
| Res : Entity_Id; |
| -- String to hold result |
| |
| Pref : constant Entity_Id := Make_Temporary (Loc, 'P'); |
| -- Name of enclosing variable, prefix of resulting name |
| |
| Sum : Node_Id; |
| -- Expression to compute total size of string |
| |
| Sel : Entity_Id; |
| -- Entity for selector name |
| |
| Decls : constant List_Id := New_List; |
| Stats : constant List_Id := New_List; |
| |
| begin |
| -- For a dynamic task, the name comes from the target variable. For a |
| -- static one it is a formal of the enclosing init proc. |
| |
| if Dyn then |
| Get_Name_String (Chars (Entity (Prefix (Id_Ref)))); |
| Append_To (Decls, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Pref, |
| Object_Definition => New_Occurrence_Of (Standard_String, Loc), |
| Expression => |
| Make_String_Literal (Loc, |
| Strval => String_From_Name_Buffer))); |
| |
| else |
| Append_To (Decls, |
| Make_Object_Renaming_Declaration (Loc, |
| Defining_Identifier => Pref, |
| Subtype_Mark => New_Occurrence_Of (Standard_String, Loc), |
| Name => Make_Identifier (Loc, Name_uTask_Name))); |
| end if; |
| |
| Sel := Make_Temporary (Loc, 'S'); |
| |
| Get_Name_String (Chars (Selector_Name (Id_Ref))); |
| |
| Append_To (Decls, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Sel, |
| Object_Definition => New_Occurrence_Of (Standard_String, Loc), |
| Expression => |
| Make_String_Literal (Loc, |
| Strval => String_From_Name_Buffer))); |
| |
| Sum := Make_Integer_Literal (Loc, Nat (Name_Len + 1)); |
| |
| Sum := |
| Make_Op_Add (Loc, |
| Left_Opnd => Sum, |
| Right_Opnd => |
| Make_Attribute_Reference (Loc, |
| Attribute_Name => Name_Length, |
| Prefix => |
| New_Occurrence_Of (Pref, Loc), |
| Expressions => New_List (Make_Integer_Literal (Loc, 1)))); |
| |
| Build_Task_Image_Prefix (Loc, Len, Res, Pos, Pref, Sum, Decls, Stats); |
| |
| Set_Character_Literal_Name (Char_Code (Character'Pos ('.'))); |
| |
| -- Res (Pos) := '.'; |
| |
| Append_To (Stats, |
| Make_Assignment_Statement (Loc, |
| Name => Make_Indexed_Component (Loc, |
| Prefix => New_Occurrence_Of (Res, Loc), |
| Expressions => New_List (New_Occurrence_Of (Pos, Loc))), |
| Expression => |
| Make_Character_Literal (Loc, |
| Chars => Name_Find, |
| Char_Literal_Value => |
| UI_From_Int (Character'Pos ('.'))))); |
| |
| Append_To (Stats, |
| Make_Assignment_Statement (Loc, |
| Name => New_Occurrence_Of (Pos, Loc), |
| Expression => |
| Make_Op_Add (Loc, |
| Left_Opnd => New_Occurrence_Of (Pos, Loc), |
| Right_Opnd => Make_Integer_Literal (Loc, 1)))); |
| |
| -- Res (Pos .. Len) := Selector; |
| |
| Append_To (Stats, |
| Make_Assignment_Statement (Loc, |
| Name => Make_Slice (Loc, |
| Prefix => New_Occurrence_Of (Res, Loc), |
| Discrete_Range => |
| Make_Range (Loc, |
| Low_Bound => New_Occurrence_Of (Pos, Loc), |
| High_Bound => New_Occurrence_Of (Len, Loc))), |
| Expression => New_Occurrence_Of (Sel, Loc))); |
| |
| return Build_Task_Image_Function (Loc, Decls, Stats, Res); |
| end Build_Task_Record_Image; |
| |
| ----------------------------- |
| -- Check_Float_Op_Overflow -- |
| ----------------------------- |
| |
| procedure Check_Float_Op_Overflow (N : Node_Id) is |
| begin |
| -- Return if no check needed |
| |
| if not Is_Floating_Point_Type (Etype (N)) |
| or else not (Do_Overflow_Check (N) and then Check_Float_Overflow) |
| |
| -- In CodePeer_Mode, rely on the overflow check flag being set instead |
| -- and do not expand the code for float overflow checking. |
| |
| or else CodePeer_Mode |
| then |
| return; |
| end if; |
| |
| -- Otherwise we replace the expression by |
| |
| -- do Tnn : constant ftype := expression; |
| -- constraint_error when not Tnn'Valid; |
| -- in Tnn; |
| |
| declare |
| Loc : constant Source_Ptr := Sloc (N); |
| Tnn : constant Entity_Id := Make_Temporary (Loc, 'T', N); |
| Typ : constant Entity_Id := Etype (N); |
| |
| begin |
| -- Turn off the Do_Overflow_Check flag, since we are doing that work |
| -- right here. We also set the node as analyzed to prevent infinite |
| -- recursion from repeating the operation in the expansion. |
| |
| Set_Do_Overflow_Check (N, False); |
| Set_Analyzed (N, True); |
| |
| -- Do the rewrite to include the check |
| |
| Rewrite (N, |
| Make_Expression_With_Actions (Loc, |
| Actions => New_List ( |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Tnn, |
| Object_Definition => New_Occurrence_Of (Typ, Loc), |
| Constant_Present => True, |
| Expression => Relocate_Node (N)), |
| Make_Raise_Constraint_Error (Loc, |
| Condition => |
| Make_Op_Not (Loc, |
| Right_Opnd => |
| Make_Attribute_Reference (Loc, |
| Prefix => New_Occurrence_Of (Tnn, Loc), |
| Attribute_Name => Name_Valid)), |
| Reason => CE_Overflow_Check_Failed)), |
| Expression => New_Occurrence_Of (Tnn, Loc))); |
| |
| Analyze_And_Resolve (N, Typ); |
| end; |
| end Check_Float_Op_Overflow; |
| |
| ---------------------------------- |
| -- Component_May_Be_Bit_Aligned -- |
| ---------------------------------- |
| |
| function Component_May_Be_Bit_Aligned (Comp : Entity_Id) return Boolean is |
| UT : Entity_Id; |
| |
| 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 (Comp) or else No (Component_Clause (Comp)) then |
| return False; |
| end if; |
| |
| UT := Underlying_Type (Etype (Comp)); |
| |
| -- It is only array and record types that cause trouble |
| |
| 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 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 (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. |
| |
| elsif Normalized_First_Bit (Comp) /= Uint_0 |
| or else Esize (Comp) mod System_Storage_Unit /= Uint_0 |
| then |
| return True; |
| |
| -- If we are large and byte aligned, then OK at this level |
| |
| else |
| return False; |
| end if; |
| end Component_May_Be_Bit_Aligned; |
| |
| ---------------------------------------- |
| -- Containing_Package_With_Ext_Axioms -- |
| ---------------------------------------- |
| |
| function Containing_Package_With_Ext_Axioms |
| (E : Entity_Id) return Entity_Id |
| is |
| Decl : Node_Id; |
| |
| begin |
| if Ekind (E) = E_Package then |
| if Nkind (Parent (E)) = N_Defining_Program_Unit_Name then |
| Decl := Parent (Parent (E)); |
| else |
| Decl := Parent (E); |
| end if; |
| end if; |
| |
| -- E is the package or generic package which is externally axiomatized |
| |
| if Ekind_In (E, E_Package, E_Generic_Package) |
| and then Has_Annotate_Pragma_For_External_Axiomatization (E) |
| then |
| return E; |
| end if; |
| |
| -- If E's scope is axiomatized, E is axiomatized. |
| |
| declare |
| First_Ax_Parent_Scope : Entity_Id := Empty; |
| |
| begin |
| if Present (Scope (E)) then |
| First_Ax_Parent_Scope := |
| Containing_Package_With_Ext_Axioms (Scope (E)); |
| end if; |
| |
| if Present (First_Ax_Parent_Scope) then |
| return First_Ax_Parent_Scope; |
| end if; |
| |
| -- otherwise, if E is a package instance, it is axiomatized if the |
| -- corresponding generic package is axiomatized. |
| |
| if Ekind (E) = E_Package |
| and then Present (Generic_Parent (Decl)) |
| then |
| return |
| Containing_Package_With_Ext_Axioms (Generic_Parent (Decl)); |
| else |
| return Empty; |
| end if; |
| end; |
| end Containing_Package_With_Ext_Axioms; |
| |
| ------------------------------- |
| -- Convert_To_Actual_Subtype -- |
| ------------------------------- |
| |
| procedure Convert_To_Actual_Subtype (Exp : Entity_Id) is |
| Act_ST : Entity_Id; |
| |
| begin |
| Act_ST := Get_Actual_Subtype (Exp); |
| |
| if Act_ST = Etype (Exp) then |
| return; |
| else |
| Rewrite (Exp, Convert_To (Act_ST, Relocate_Node (Exp))); |
| Analyze_And_Resolve (Exp, Act_ST); |
| end if; |
| end Convert_To_Actual_Subtype; |
| |
| ----------------------------------- |
| -- 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) |
| |
| -- 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))) |
| |
| -- Protected types with interrupt handlers (when not using a |
| -- restricted profile) are also considered equivalent to |
| -- protected types with entries. The types which are used |
| -- (Static_Interrupt_Protection and Dynamic_Interrupt_Protection) |
| -- are derived from Protection_Entries. |
| |
| or else (Has_Attach_Handler (Typ) and then not Restricted_Profile) |
| or else Has_Interrupt_Handler (Typ) |
| then |
| if Abort_Allowed |
| or else Restriction_Active (No_Entry_Queue) = False |
| or else Restriction_Active (No_Select_Statements) = 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; |
| |
| ----------------------------------- |
| -- Current_Sem_Unit_Declarations -- |
| ----------------------------------- |
| |
| function Current_Sem_Unit_Declarations return List_Id is |
| U : Node_Id := Unit (Cunit (Current_Sem_Unit)); |
| Decls : List_Id; |
| |
| begin |
| -- If the current unit is a package body, locate the visible |
| -- declarations of the package spec. |
| |
| if Nkind (U) = N_Package_Body then |
| U := Unit (Library_Unit (Cunit (Current_Sem_Unit))); |
| end if; |
| |
| if Nkind (U) = N_Package_Declaration then |
| U := Specification (U); |
| Decls := Visible_Declarations (U); |
| |
| if No (Decls) then |
| Decls := New_List; |
| Set_Visible_Declarations (U, Decls); |
| end if; |
| |
| else |
| Decls := Declarations (U); |
| |
| if No (Decls) then |
| Decls := New_List; |
| Set_Declarations (U, Decls); |
| end if; |
| end if; |
| |
| return Decls; |
| end Current_Sem_Unit_Declarations; |
| |
| ----------------------- |
| -- Duplicate_Subexpr -- |
| ----------------------- |
| |
| function Duplicate_Subexpr |
| (Exp : Node_Id; |
| Name_Req : Boolean := False; |
| Renaming_Req : Boolean := False) return Node_Id |
| is |
| begin |
| Remove_Side_Effects (Exp, Name_Req, Renaming_Req); |
| return New_Copy_Tree (Exp); |
| end Duplicate_Subexpr; |
| |
| --------------------------------- |
| -- Duplicate_Subexpr_No_Checks -- |
| --------------------------------- |
| |
| function Duplicate_Subexpr_No_Checks |
| (Exp : Node_Id; |
| Name_Req : Boolean := False; |
| Renaming_Req : Boolean := False; |
| Related_Id : Entity_Id := Empty; |
| Is_Low_Bound : Boolean := False; |
| Is_High_Bound : Boolean := False) return Node_Id |
| is |
| New_Exp : Node_Id; |
| |
| begin |
| Remove_Side_Effects |
| (Exp => Exp, |
| Name_Req => Name_Req, |
| Renaming_Req => Renaming_Req, |
| Related_Id => Related_Id, |
| Is_Low_Bound => Is_Low_Bound, |
| Is_High_Bound => Is_High_Bound); |
| |
| New_Exp := New_Copy_Tree (Exp); |
| Remove_Checks (New_Exp); |
| return New_Exp; |
| end Duplicate_Subexpr_No_Checks; |
| |
| ----------------------------------- |
| -- Duplicate_Subexpr_Move_Checks -- |
| ----------------------------------- |
| |
| function Duplicate_Subexpr_Move_Checks |
| (Exp : Node_Id; |
| Name_Req : Boolean := False; |
| Renaming_Req : Boolean := False) return Node_Id |
| is |
| New_Exp : Node_Id; |
| |
| begin |
| Remove_Side_Effects (Exp, Name_Req, Renaming_Req); |
| New_Exp := New_Copy_Tree (Exp); |
| Remove_Checks (Exp); |
| return New_Exp; |
| end Duplicate_Subexpr_Move_Checks; |
| |
| -------------------- |
| -- Ensure_Defined -- |
| -------------------- |
| |
| procedure Ensure_Defined (Typ : Entity_Id; N : Node_Id) is |
| IR : Node_Id; |
| |
| begin |
| -- 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); |
| 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; |
| |
| ------------------- |
| -- Evaluate_Name -- |
| ------------------- |
| |
| procedure Evaluate_Name (Nam : Node_Id) is |
| K : constant Node_Kind := Nkind (Nam); |
| |
| begin |
| -- For an explicit dereference, we simply force the evaluation of the |
| -- name expression. The dereference provides a value that is the address |
| -- for the renamed object, and it is precisely this value that we want |
| -- to preserve. |
| |
| if K = N_Explicit_Dereference then |
| Force_Evaluation (Prefix (Nam)); |
| |
| -- For a selected component, we simply evaluate the prefix |
| |
| elsif K = N_Selected_Component then |
| Evaluate_Name (Prefix (Nam)); |
| |
| -- For an indexed component, or an attribute reference, we evaluate the |
| -- prefix, which is itself a name, recursively, and then force the |
| -- evaluation of all the subscripts (or attribute expressions). |
| |
| elsif Nkind_In (K, N_Indexed_Component, N_Attribute_Reference) then |
| Evaluate_Name (Prefix (Nam)); |
| |
| declare |
| E : Node_Id; |
| |
| begin |
| E := First (Expressions (Nam)); |
| while Present (E) loop |
| Force_Evaluation (E); |
| |
| if Original_Node (E) /= E then |
| Set_Do_Range_Check (E, Do_Range_Check (Original_Node (E))); |
| end if; |
| |
| Next (E); |
| end loop; |
| end; |
| |
| -- For a slice, we evaluate the prefix, as for the indexed component |
| -- case and then, if there is a range present, either directly or as the |
| -- constraint of a discrete subtype indication, we evaluate the two |
| -- bounds of this range. |
| |
| elsif K = N_Slice then |
| Evaluate_Name (Prefix (Nam)); |
| Evaluate_Slice_Bounds (Nam); |
| |
| -- For a type conversion, the expression of the conversion must be the |
| -- name of an object, and we simply need to evaluate this name. |
| |
| elsif K = N_Type_Conversion then |
| Evaluate_Name (Expression (Nam)); |
| |
| -- For a function call, we evaluate the call |
| |
| elsif K = N_Function_Call then |
| Force_Evaluation (Nam); |
| |
| -- The remaining cases are direct name, operator symbol and character |
| -- literal. In all these cases, we do nothing, since we want to |
| -- reevaluate each time the renamed object is used. |
| |
| else |
| return; |
| end if; |
| end Evaluate_Name; |
| |
| --------------------------- |
| -- Evaluate_Slice_Bounds -- |
| --------------------------- |
| |
| procedure Evaluate_Slice_Bounds (Slice : Node_Id) is |
| DR : constant Node_Id := Discrete_Range (Slice); |
| Constr : Node_Id; |
| Rexpr : Node_Id; |
| |
| begin |
| if Nkind (DR) = N_Range then |
| Force_Evaluation (Low_Bound (DR)); |
| Force_Evaluation (High_Bound (DR)); |
| |
| elsif Nkind (DR) = N_Subtype_Indication then |
| Constr := Constraint (DR); |
| |
| if Nkind (Constr) = N_Range_Constraint then |
| Rexpr := Range_Expression (Constr); |
| |
| Force_Evaluation (Low_Bound (Rexpr)); |
| Force_Evaluation (High_Bound (Rexpr)); |
| end if; |
| end if; |
| end Evaluate_Slice_Bounds; |
| |
| --------------------- |
| -- Evolve_And_Then -- |
| --------------------- |
| |
| procedure Evolve_And_Then (Cond : in out Node_Id; Cond1 : Node_Id) is |
| begin |
| if No (Cond) then |
| Cond := Cond1; |
| else |
| Cond := |
| Make_And_Then (Sloc (Cond1), |
| Left_Opnd => Cond, |
| Right_Opnd => Cond1); |
| end if; |
| end Evolve_And_Then; |
| |
| -------------------- |
| -- Evolve_Or_Else -- |
| -------------------- |
| |
| procedure Evolve_Or_Else (Cond : in out Node_Id; Cond1 : Node_Id) is |
| begin |
| if No (Cond) then |
| Cond := Cond1; |
| else |
| Cond := |
| Make_Or_Else (Sloc (Cond1), |
| Left_Opnd => Cond, |
| Right_Opnd => Cond1); |
| end if; |
| end Evolve_Or_Else; |
| |
| ----------------------------------------- |
| -- Expand_Static_Predicates_In_Choices -- |
| ----------------------------------------- |
| |
| procedure Expand_Static_Predicates_In_Choices (N : Node_Id) is |
| pragma Assert (Nkind_In (N, N_Case_Statement_Alternative, N_Variant)); |
| |
| Choices : constant List_Id := Discrete_Choices (N); |
| |
| Choice : Node_Id; |
| Next_C : Node_Id; |
| P : Node_Id; |
| C : Node_Id; |
| |
| begin |
| Choice := First (Choices); |
| while Present (Choice) loop |
| Next_C := Next (Choice); |
| |
| -- Check for name of subtype with static predicate |
| |
| if Is_Entity_Name (Choice) |
| and then Is_Type (Entity (Choice)) |
| and then Has_Predicates (Entity (Choice)) |
| then |
| -- Loop through entries in predicate list, converting to choices |
| -- and inserting in the list before the current choice. Note that |
| -- if the list is empty, corresponding to a False predicate, then |
| -- no choices are inserted. |
| |
| P := First (Static_Discrete_Predicate (Entity (Choice))); |
| while Present (P) loop |
| |
| -- If low bound and high bounds are equal, copy simple choice |
| |
| if Expr_Value (Low_Bound (P)) = Expr_Value (High_Bound (P)) then |
| C := New_Copy (Low_Bound (P)); |
| |
| -- Otherwise copy a range |
| |
| else |
| C := New_Copy (P); |
| end if; |
| |
| -- Change Sloc to referencing choice (rather than the Sloc of |
| -- the predicate declaration element itself). |
| |
| Set_Sloc (C, Sloc (Choice)); |
| Insert_Before (Choice, C); |
| Next (P); |
| end loop; |
| |
| -- Delete the predicated entry |
| |
| Remove (Choice); |
| end if; |
| |
| -- Move to next choice to check |
| |
| Choice := Next_C; |
| end loop; |
| end Expand_Static_Predicates_In_Choices; |
| |
| ------------------------------ |
| -- Expand_Subtype_From_Expr -- |
| ------------------------------ |
| |
| -- This function is applicable for both static and dynamic allocation of |
| -- 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 evaluation. In the static allocation case, the general |
| -- scheme is: |
| |
| -- Val : T := Expr; |
| |
| -- is transformed into |
| |
| -- Val : Constrained_Subtype_of_T := Maybe_Modified_Expr; |
| -- |
| -- Here are the main cases : |
| -- |
| -- <if Expr is a Slice> |
| -- Val : T ([Index_Subtype (Expr)]) := Expr; |
| -- |
| -- <elsif Expr is a String Literal> |
| -- Val : T (T'First .. T'First + Length (string literal) - 1) := Expr; |
| -- |
| -- <elsif Expr is Constrained> |
| -- subtype T is Type_Of_Expr |
| -- Val : T := Expr; |
| -- |
| -- <elsif Expr is an entity_name> |
| -- Val : T (constraints taken from Expr) := Expr; |
| -- |
| -- <else> |
| -- type Axxx is access all T; |
| -- Rval : Axxx := Expr'ref; |
| -- Val : T (constraints taken from Rval) := Rval.all; |
| |
| -- ??? note: when the Expression is allocated in the secondary stack |
| -- we could use it directly instead of copying it by declaring |
| -- Val : T (...) renames Rval.all |
| |
| procedure Expand_Subtype_From_Expr |
| (N : Node_Id; |
| Unc_Type : Entity_Id; |
| Subtype_Indic : Node_Id; |
| Exp : Node_Id) |
| is |
| Loc : constant Source_Ptr := Sloc (N); |
| Exp_Typ : constant Entity_Id := Etype (Exp); |
| T : Entity_Id; |
| |
| begin |
| -- In general we cannot build the subtype if expansion is disabled, |
| -- because internal entities may not have been defined. However, to |
| -- avoid some cascaded errors, we try to continue when the expression is |
| -- an array (or string), because it is safe to compute the bounds. It is |
| -- in fact required to do so even in a generic context, because there |
| -- may be constants that depend on the bounds of a string literal, both |
| -- standard string types and more generally arrays of characters. |
| |
| -- In GNATprove mode, these extra subtypes are not needed |
| |
| if GNATprove_Mode then |
| return; |
| end if; |
| |
| if not Expander_Active |
| and then (No (Etype (Exp)) or else not Is_String_Type (Etype (Exp))) |
| then |
| return; |
| end if; |
| |
| if Nkind (Exp) = N_Slice then |
| declare |
| Slice_Type : constant Entity_Id := Etype (First_Index (Exp_Typ)); |
| |
| begin |
| Rewrite (Subtype_Indic, |
| Make_Subtype_Indication (Loc, |
| Subtype_Mark => New_Occurrence_Of (Unc_Type, Loc), |
| Constraint => |
| Make_Index_Or_Discriminant_Constraint (Loc, |
| Constraints => New_List |
| (New_Occurrence_Of (Slice_Type, Loc))))); |
| |
| -- 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. |
| |
| Evaluate_Slice_Bounds (Exp); |
| end; |
| |
| elsif Ekind (Exp_Typ) = E_String_Literal_Subtype then |
| Rewrite (Subtype_Indic, |
| Make_Subtype_Indication (Loc, |
| Subtype_Mark => New_Occurrence_Of (Unc_Type, Loc), |
| Constraint => |
| Make_Index_Or_Discriminant_Constraint (Loc, |
| Constraints => New_List ( |
| Make_Literal_Range (Loc, |
| Literal_Typ => Exp_Typ))))); |
| |
| -- If the type of the expression is an internally generated type it |
| -- may not be necessary to create a new subtype. However there are two |
| -- exceptions: references to the current instances, and aliased array |
| -- object declarations for which the backend needs to create a template. |
| |
| elsif Is_Constrained (Exp_Typ) |
| and then not Is_Class_Wide_Type (Unc_Type) |
| and then |
| (Nkind (N) /= N_Object_Declaration |
| or else not Is_Entity_Name (Expression (N)) |
| or else not Comes_From_Source (Entity (Expression (N))) |
| or else not Is_Array_Type (Exp_Typ) |
| or else not Aliased_Present (N)) |
| then |
| if Is_Itype (Exp_Typ) then |
| |
| -- Within an initialization procedure, a selected component |
| -- denotes a component of the enclosing record, and it appears as |
| -- an actual in a call to its own initialization procedure. If |
| -- this component depends on the outer discriminant, we must |
| -- generate the proper actual subtype for it. |
| |
| if Nkind (Exp) = N_Selected_Component |
| and then Within_Init_Proc |
| then |
| declare |
| Decl : constant Node_Id := |
| Build_Actual_Subtype_Of_Component (Exp_Typ, Exp); |
| begin |
| if Present (Decl) then |
| Insert_Action (N, Decl); |
| T := Defining_Identifier (Decl); |
| else |
| T := Exp_Typ; |
| end if; |
| end; |
| |
| -- No need to generate a new subtype |
| |
| else |
| T := Exp_Typ; |
| end if; |
| |
| else |
| T := Make_Temporary (Loc, 'T'); |
| |
| Insert_Action (N, |
| Make_Subtype_Declaration (Loc, |
| Defining_Identifier => T, |
| Subtype_Indication => New_Occurrence_Of (Exp_Typ, Loc))); |
| |
| -- This type is marked as an itype even though it has an explicit |
| -- declaration since otherwise Is_Generic_Actual_Type can get |
| -- set, resulting in the generation of spurious errors. (See |
| -- sem_ch8.Analyze_Package_Renaming and sem_type.covers) |
| |
| Set_Is_Itype (T); |
| Set_Associated_Node_For_Itype (T, Exp); |
| end if; |
| |
| Rewrite (Subtype_Indic, New_Occurrence_Of (T, Loc)); |
| |
| -- 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_Unchecked_Union (Underlying_Type (Unc_Type))) |
| then |
| null; |
| |
| -- 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 |
| -- Nothing to be done if no underlying record view available |
| |
| if No (Underlying_Record_View (Unc_Type)) then |
| null; |
| |
| -- Otherwise use the Underlying_Record_View to create the proper |
| -- constrained subtype for an object of a derived type with unknown |
| -- discriminants. |
| |
| else |
| Remove_Side_Effects (Exp); |
| Rewrite (Subtype_Indic, |
| Make_Subtype_From_Expr (Exp, Underlying_Record_View (Unc_Type))); |
| end if; |
| |
| -- 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. The same is |
| -- presumably true for class-wide types in general, so this test |
| -- is broadened to include all class-wide renamings, which also |
| -- avoids cases of unbounded recursion in Remove_Side_Effects. |
| -- (Is this really correct, or are there some cases of class-wide |
| -- renamings that require action in this procedure???) |
| |
| elsif Present (N) |
| and then Nkind (N) = N_Object_Renaming_Declaration |
| and then Is_Class_Wide_Type (Unc_Type) |
| then |
| null; |
| |
| -- In Ada 95 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. |
| |
| -- In Ada 2005 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. |
| |
| -- If the type is class-wide, the expression is dynamically tagged and |
| -- we do not create an actual subtype either. Ditto for an interface. |
| -- For now this applies only if the type is immutably limited, and the |
| -- function being called is build-in-place. This will have to be revised |
| -- when build-in-place functions are generalized to other types. |
| |
| elsif Is_Limited_View (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; |
| |
| -- 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. |
| |
| elsif Is_Build_In_Place_Function_Call (Exp) then |
| null; |
| |
| else |
| Remove_Side_Effects (Exp); |
| Rewrite (Subtype_Indic, |
| Make_Subtype_From_Expr (Exp, Unc_Type)); |
| end if; |
| end Expand_Subtype_From_Expr; |
| |
| ---------------------- |
| -- Finalize_Address -- |
| ---------------------- |
| |
| function Finalize_Address (Typ : Entity_Id) return Entity_Id is |
| Utyp : Entity_Id := Typ; |
| |
| begin |
| -- Handle protected class-wide or task class-wide types |
| |
| if Is_Class_Wide_Type (Utyp) then |
| if Is_Concurrent_Type (Root_Type (Utyp)) then |
| Utyp := Root_Type (Utyp); |
| |
| elsif Is_Private_Type (Root_Type (Utyp)) |
| and then Present (Full_View (Root_Type (Utyp))) |
| and then Is_Concurrent_Type (Full_View (Root_Type (Utyp))) |
| then |
| Utyp := Full_View (Root_Type (Utyp)); |
| end if; |
| end if; |
| |
| -- Handle private types |
| |
| if Is_Private_Type (Utyp) and then Present (Full_View (Utyp)) then |
| Utyp := Full_View (Utyp); |
| end if; |
| |
| -- Handle protected and task types |
| |
| if Is_Concurrent_Type (Utyp) |
| and then Present (Corresponding_Record_Type (Utyp)) |
| then |
| Utyp := Corresponding_Record_Type (Utyp); |
| end if; |
| |
| Utyp := Underlying_Type (Base_Type (Utyp)); |
| |
| -- Deal with untagged derivation of private views. If the parent is |
| -- now known to be protected, the finalization routine is the one |
| -- defined on the corresponding record of the ancestor (corresponding |
| -- records do not automatically inherit operations, but maybe they |
| -- should???) |
| |
| if Is_Untagged_Derivation (Typ) then |
| if Is_Protected_Type (Typ) then |
| Utyp := Corresponding_Record_Type (Root_Type (Base_Type (Typ))); |
| |
| else |
| Utyp := Underlying_Type (Root_Type (Base_Type (Typ))); |
| |
| if Is_Protected_Type (Utyp) then |
| Utyp := Corresponding_Record_Type (Utyp); |
| end if; |
| end if; |
| end if; |
| |
| -- If the underlying_type is a subtype, we are dealing with the |
| -- completion of a private type. We need to access the base type and |
| -- generate a conversion to it. |
| |
| if Utyp /= Base_Type (Utyp) then |
| pragma Assert (Is_Private_Type (Typ)); |
| |
| Utyp := Base_Type (Utyp); |
| end if; |
| |
| -- When dealing with an internally built full view for a type with |
| -- unknown discriminants, use the original record type. |
| |
| if Is_Underlying_Record_View (Utyp) then |
| Utyp := Etype (Utyp); |
| end if; |
| |
| return TSS (Utyp, TSS_Finalize_Address); |
| end Finalize_Address; |
| |
| ------------------------ |
| -- Find_Interface_ADT -- |
| ------------------------ |
| |
| function Find_Interface_ADT |
| (T : Entity_Id; |
| Iface : Entity_Id) return Elmt_Id |
| is |
| ADT : Elmt_Id; |
| Typ : Entity_Id := T; |
| |
| begin |
| pragma Assert (Is_Interface (Iface)); |
| |
| -- Handle private types |
| |
| if Has_Private_Declaration (Typ) and then Present (Full_View (Typ)) then |
| Typ := Full_View (Typ); |
| end if; |
| |
| -- Handle access types |
| |
| if Is_Access_Type (Typ) then |
| Typ := Designated_Type (Typ); |
| end if; |
| |
| -- Handle task and protected types implementing interfaces |
| |
| if Is_Concurrent_Type (Typ) then |
| Typ := Corresponding_Record_Type (Typ); |
| end if; |
| |
| pragma Assert |
| (not Is_Class_Wide_Type (Typ) |
| and then Ekind (Typ) /= E_Incomplete_Type); |
| |
| if Is_Ancestor (Iface, Typ, Use_Full_View => True) 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)), |
| Use_Full_View => True) |
| loop |
| Next_Elmt (ADT); |
| end loop; |
| |
| pragma Assert (Present (Related_Type (Node (ADT)))); |
| return ADT; |
| end if; |
| end Find_Interface_ADT; |
| |
| ------------------------ |
| -- Find_Interface_Tag -- |
| ------------------------ |
| |
| function Find_Interface_Tag |
| (T : Entity_Id; |
| Iface : Entity_Id) return Entity_Id |
| is |
| AI_Tag : Entity_Id; |
| Found : Boolean := False; |
| Typ : Entity_Id := T; |
| |
| procedure Find_Tag (Typ : Entity_Id); |
| -- Internal subprogram used to recursively climb to the ancestors |
| |
| -------------- |
| -- Find_Tag -- |
| -------------- |
| |
| procedure Find_Tag (Typ : Entity_Id) is |
| AI_Elmt : Elmt_Id; |
| AI : Node_Id; |
| |
| begin |
| -- This routine does not handle the case in which the interface is an |
| -- ancestor of Typ. That case is handled by the enclosing subprogram. |
| |
| pragma Assert (Typ /= Iface); |
| |
| -- Climb to the root type handling private types |
| |
| if Present (Full_View (Etype (Typ))) then |
| if Full_View (Etype (Typ)) /= Typ then |
| Find_Tag (Full_View (Etype (Typ))); |
| end if; |
| |
| elsif Etype (Typ) /= Typ then |
| Find_Tag (Etype (Typ)); |
| end if; |
| |
| -- Traverse the list of interfaces implemented by the type |
| |
| if not Found |
| and then Present (Interfaces (Typ)) |
| and then not (Is_Empty_Elmt_List (Interfaces (Typ))) |
| then |
| -- Skip the tag associated with the primary table |
| |
| pragma Assert (Etype (First_Tag_Component (Typ)) = RTE (RE_Tag)); |
| AI_Tag := Next_Tag_Component (First_Tag_Component (Typ)); |
| pragma Assert (Present (AI_Tag)); |
| |
| AI_Elmt := First_Elmt (Interfaces (Typ)); |
| while Present (AI_Elmt) loop |
| AI := Node (AI_Elmt); |
| |
| if AI = Iface |
| or else Is_Ancestor (Iface, AI, Use_Full_View => True) |
| then |
| Found := True; |
| return; |
| end if; |
| |
| AI_Tag := Next_Tag_Component (AI_Tag); |
| Next_Elmt (AI_Elmt); |
| end loop; |
| end if; |
| end Find_Tag; |
| |
| -- Start of processing for Find_Interface_Tag |
| |
| begin |
| pragma Assert (Is_Interface (Iface)); |
| |
| -- Handle access types |
| |
| if Is_Access_Type (Typ) then |
| Typ := 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) and then Present (Full_View (Typ)) then |
| Typ := Full_View (Typ); |
| end if; |
| |
| -- Handle entities from the limited view |
| |
| 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 |
| |
| if Is_Concurrent_Type (Typ) then |
| Typ := Corresponding_Record_Type (Typ); |
| end if; |
| |
| -- If the interface is an ancestor of the type, then it shared the |
| -- primary dispatch table. |
| |
| if Is_Ancestor (Iface, Typ, Use_Full_View => True) then |
| pragma Assert (Etype (First_Tag_Component (Typ)) = RTE (RE_Tag)); |
| return First_Tag_Component (Typ); |
| |
| -- Otherwise we need to search for its associated tag component |
| |
| else |
| Find_Tag (Typ); |
| pragma Assert (Found); |
| return AI_Tag; |
| end if; |
| end Find_Interface_Tag; |
| |
| ------------------ |
| -- Find_Prim_Op -- |
| ------------------ |
| |
| 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 |
| Typ := Root_Type (Typ); |
| end if; |
| |
| Typ := Underlying_Type (Typ); |
| |
| -- Loop through primitive operations |
| |
| Prim := First_Elmt (Primitive_Operations (Typ)); |
| 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_Formal (Op)) = Etype (Last_Formal (Op))); |
| |
| Next_Elmt (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 |
| is |
| Inher_Op : Entity_Id := Empty; |
| Own_Op : Entity_Id := Empty; |
| Prim_Elmt : Elmt_Id; |
| Prim_Id : Entity_Id; |
| Typ : Entity_Id := T; |
| |
| begin |
| if Is_Class_Wide_Type (Typ) then |
| Typ := Root_Type (Typ); |
| end if; |
| |
| Typ := Underlying_Type (Typ); |
| |
| -- This search is based on the assertion that the dispatching version |
| -- of the TSS routine always precedes the real primitive. |
| |
| Prim_Elmt := First_Elmt (Primitive_Operations (Typ)); |
| while Present (Prim_Elmt) loop |
| Prim_Id := Node (Prim_Elmt); |
| |
| if Is_TSS (Prim_Id, Name) then |
| if Present (Alias (Prim_Id)) then |
| Inher_Op := Prim_Id; |
| else |
| Own_Op := Prim_Id; |
| end if; |
| end if; |
| |
| Next_Elmt (Prim_Elmt); |
| end loop; |
| |
| if Present (Own_Op) then |
| return Own_Op; |
| elsif Present (Inher_Op) then |
| return Inher_Op; |
| else |
| raise Program_Error; |
| end if; |
| 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_In (S, E_Entry, E_Entry_Family, E_Function, 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; |
| |
| -------------------------- |
| -- Find_Protection_Type -- |
| -------------------------- |
| |
| function Find_Protection_Type (Conc_Typ : Entity_Id) return Entity_Id is |
| Comp : Entity_Id; |
| Typ : Entity_Id := Conc_Typ; |
| |
| begin |
| if Is_Concurrent_Type (Typ) then |
| Typ := Corresponding_Record_Type (Typ); |
| end if; |
| |
| -- Since restriction violations are not considered serious errors, the |
| -- expander remains active, but may leave the corresponding record type |
| -- malformed. In such cases, component _object is not available so do |
| -- not look for it. |
| |
| if not Analyzed (Typ) then |
| return Empty; |
| end if; |
| |
| Comp := First_Component (Typ); |
| while Present (Comp) loop |
| if Chars (Comp) = Name_uObject then |
| return Base_Type (Etype (Comp)); |
| end if; |
| |
| Next_Component (Comp); |
| end loop; |
| |
| -- The corresponding record of a protected type should always have an |
| -- _object field. |
| |
| raise Program_Error; |
| end Find_Protection_Type; |
| |
| ----------------------- |
| -- Find_Hook_Context -- |
| ----------------------- |
| |
| function Find_Hook_Context (N : Node_Id) return Node_Id is |
| Par : Node_Id; |
| Top : Node_Id; |
| |
| Wrapped_Node : Node_Id; |
| -- Note: if we are in a transient scope, we want to reuse it as |
| -- the context for actions insertion, if possible. But if N is itself |
| -- part of the stored actions for the current transient scope, |
| -- then we need to insert at the appropriate (inner) location in |
| -- the not as an action on Node_To_Be_Wrapped. |
| |
| In_Cond_Expr : constant Boolean := Within_Case_Or_If_Expression (N); |
| |
| begin |
| -- When the node is inside a case/if expression, the lifetime of any |
| -- temporary controlled object is extended. Find a suitable insertion |
| -- node by locating the topmost case or if expressions. |
| |
| if In_Cond_Expr then |
| Par := N; |
| Top := N; |
| while Present (Par) loop |
| if Nkind_In (Original_Node (Par), N_Case_Expression, |
| N_If_Expression) |
| then |
| Top := Par; |
| |
| -- Prevent the search from going too far |
| |
| elsif Is_Body_Or_Package_Declaration (Par) then |
| exit; |
| end if; |
| |
| Par := Parent (Par); |
| end loop; |
| |
| -- The topmost case or if expression is now recovered, but it may |
| -- still not be the correct place to add generated code. Climb to |
| -- find a parent that is part of a declarative or statement list, |
| -- and is not a list of actuals in a call. |
| |
| Par := Top; |
| while Present (Par) loop |
| if Is_List_Member (Par) |
| and then not Nkind_In (Par, N_Component_Association, |
| N_Discriminant_Association, |
| N_Parameter_Association, |
| N_Pragma_Argument_Association) |
| and then not Nkind_In |
| (Parent (Par), N_Function_Call, |
| N_Procedure_Call_Statement, |
| N_Entry_Call_Statement) |
| |
| then |
| return Par; |
| |
| -- Prevent the search from going too far |
| |
| elsif Is_Body_Or_Package_Declaration (Par) then |
| exit; |
| end if; |
| |
| Par := Parent (Par); |
| end loop; |
| |
| return Par; |
| |
| else |
| Par := N; |
| while Present (Par) loop |
| |
| -- Keep climbing past various operators |
| |
| if Nkind (Parent (Par)) in N_Op |
| or else Nkind_In (Parent (Par), N_And_Then, N_Or_Else) |
| then |
| Par := Parent (Par); |
| else |
| exit; |
| end if; |
| end loop; |
| |
| Top := Par; |
| |
| -- The node may be located in a pragma in which case return the |
| -- pragma itself: |
| |
| -- pragma Precondition (... and then Ctrl_Func_Call ...); |
| |
| -- Similar case occurs when the node is related to an object |
| -- declaration or assignment: |
| |
| -- Obj [: Some_Typ] := ... and then Ctrl_Func_Call ...; |
| |
| -- Another case to consider is when the node is part of a return |
| -- statement: |
| |
| -- return ... and then Ctrl_Func_Call ...; |
| |
| -- Another case is when the node acts as a formal in a procedure |
| -- call statement: |
| |
| -- Proc (... and then Ctrl_Func_Call ...); |
| |
| if Scope_Is_Transient then |
| Wrapped_Node := Node_To_Be_Wrapped; |
| else |
| Wrapped_Node := Empty; |
| end if; |
| |
| while Present (Par) loop |
| if Par = Wrapped_Node |
| or else Nkind_In (Par, N_Assignment_Statement, |
| N_Object_Declaration, |
| N_Pragma, |
| N_Procedure_Call_Statement, |
| N_Simple_Return_Statement) |
| then |
| return Par; |
| |
| -- Prevent the search from going too far |
| |
| elsif Is_Body_Or_Package_Declaration (Par) then |
| exit; |
| end if; |
| |
| Par := Parent (Par); |
| end loop; |
| |
| -- Return the topmost short circuit operator |
| |
| return Top; |
| end if; |
| end Find_Hook_Context; |
| |
| ------------------------------ |
| -- Following_Address_Clause -- |
| ------------------------------ |
| |
| function Following_Address_Clause (D : Node_Id) return Node_Id is |
| Id : constant Entity_Id := Defining_Identifier (D); |
| Result : Node_Id; |
| Par : Node_Id; |
| |
| function Check_Decls (D : Node_Id) return Node_Id; |
| -- This internal function differs from the main function in that it |
| -- gets called to deal with a following package private part, and |
| -- it checks declarations starting with D (the main function checks |
| -- declarations following D). If D is Empty, then Empty is returned. |
| |
| ----------------- |
| -- Check_Decls -- |
| ----------------- |
| |
| function Check_Decls (D : Node_Id) return Node_Id is |
| Decl : Node_Id; |
| |
| begin |
| Decl := D; |
| while Present (Decl) loop |
| if Nkind (Decl) = N_At_Clause |
| and then Chars (Identifier (Decl)) = Chars (Id) |
| then |
| return Decl; |
| |
| elsif Nkind (Decl) = N_Attribute_Definition_Clause |
| and then Chars (Decl) = Name_Address |
| and then Chars (Name (Decl)) = Chars (Id) |
| then |
| return Decl; |
| end if; |
| |
| Next (Decl); |
| end loop; |
| |
| -- Otherwise not found, return Empty |
| |
| return Empty; |
| end Check_Decls; |
| |
| -- Start of processing for Following_Address_Clause |
| |
| begin |
| -- If parser detected no address clause for the identifier in question, |
| -- then the answer is a quick NO, without the need for a search. |
| |
| if not Get_Name_Table_Boolean1 (Chars (Id)) then |
| return Empty; |
| end if; |
| |
| -- Otherwise search current declarative unit |
| |
| Result := Check_Decls (Next (D)); |
| |
| if Present (Result) then |
| return Result; |
| end if; |
| |
| -- Check for possible package private part following |
| |
| Par := Parent (D); |
| |
| if Nkind (Par) = N_Package_Specification |
| and then Visible_Declarations (Par) = List_Containing (D) |
| and then Present (Private_Declarations (Par)) |
| then |
| -- Private part present, check declarations there |
| |
| return Check_Decls (First (Private_Declarations (Par))); |
| |
| else |
| -- No private part, clause not found, return Empty |
| |
| return Empty; |
| end if; |
| end Following_Address_Clause; |
| |
| ---------------------- |
| -- Force_Evaluation -- |
| ---------------------- |
| |
| procedure Force_Evaluation |
| (Exp : Node_Id; |
| Name_Req : Boolean := False; |
| Related_Id : Entity_Id := Empty; |
| Is_Low_Bound : Boolean := False; |
| Is_High_Bound : Boolean := False) |
| is |
| begin |
| Remove_Side_Effects |
| (Exp => Exp, |
| Name_Req => Name_Req, |
| Variable_Ref => True, |
| Renaming_Req => False, |
| Related_Id => Related_Id, |
| Is_Low_Bound => Is_Low_Bound, |
| Is_High_Bound => Is_High_Bound); |
| end Force_Evaluation; |
| |
| --------------------------------- |
| -- Fully_Qualified_Name_String -- |
| --------------------------------- |
| |
| function Fully_Qualified_Name_String |
| (E : Entity_Id; |
| Append_NUL : Boolean := True) return String_Id |
| is |
| procedure Internal_Full_Qualified_Name (E : Entity_Id); |
| -- Compute recursively the qualified name without NUL at the end, adding |
| -- it to the currently started string being generated |
| |
| ---------------------------------- |
| -- Internal_Full_Qualified_Name -- |
| ---------------------------------- |
| |
| procedure Internal_Full_Qualified_Name (E : Entity_Id) is |
| Ent : Entity_Id; |
| |
| begin |
| -- Deal properly with child units |
| |
| if Nkind (E) = N_Defining_Program_Unit_Name then |
| Ent := Defining_Identifier (E); |
| else |
| Ent := E; |
| end if; |
| |
| -- Compute qualification recursively (only "Standard" has no scope) |
| |
| if Present (Scope (Scope (Ent))) then |
| Internal_Full_Qualified_Name (Scope (Ent)); |
| Store_String_Char (Get_Char_Code ('.')); |
| end if; |
| |
| -- Every entity should have a name except some expanded blocks |
| -- don't bother about those. |
| |
| if Chars (Ent) = No_Name then |
| return; |
| end if; |
| |
| -- Generates the entity name in upper case |
| |
| Get_Decoded_Name_String (Chars (Ent)); |
| Set_All_Upper_Case; |
| Store_String_Chars (Name_Buffer (1 .. Name_Len)); |
| return; |
| end Internal_Full_Qualified_Name; |
| |
| -- Start of processing for Full_Qualified_Name |
| |
| begin |
| Start_String; |
| Internal_Full_Qualified_Name (E); |
| |
| if Append_NUL then |
| Store_String_Char (Get_Char_Code (ASCII.NUL)); |
| end if; |
| |
| return End_String; |
| end Fully_Qualified_Name_String; |
| |
| ------------------------ |
| -- Generate_Poll_Call -- |
| ------------------------ |
| |
| procedure Generate_Poll_Call (N : Node_Id) is |
| begin |
| -- No poll call if polling not active |
| |
| if not Polling_Required then |
| return; |
| |
| -- Otherwise generate require poll call |
| |
| else |
| Insert_Before_And_Analyze (N, |
| Make_Procedure_Call_Statement (Sloc (N), |
| Name => New_Occurrence_Of (RTE (RE_Poll), Sloc (N)))); |
| end if; |
| end Generate_Poll_Call; |
| |
| --------------------------------- |
| -- 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); |
| 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; |
| Prev_Cond : Node_Id; |
| Sens : Boolean; |
| |
| begin |
| Cond := N; |
| Sens := S; |
| |
| loop |
| Prev_Cond := Cond; |
| |
| -- Deal with NOT operators, inverting sense |
| |
| while Nkind (Cond) = N_Op_Not loop |
| Cond := Right_Opnd (Cond); |
| Sens := not Sens; |
| end loop; |
| |
| -- Deal with conversions, qualifications, and expressions with |
| -- actions. |
| |
| while Nkind_In (Cond, |
| N_Type_Conversion, |
| N_Qualified_Expression, |
| N_Expression_With_Actions) |
| loop |
| Cond := Expression (Cond); |
| end loop; |
| |
| exit when Cond = Prev_Cond; |
| end loop; |
| |
| -- Deal with AND THEN and AND cases |
| |
| if Nkind_In (Cond, N_And_Then, 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). |
| |
| if Sens = False then |
| Op := N_Empty; |
| Val := Empty; |
| return; |
| end if; |
| |
| -- Recursively process AND and AND THEN branches |
| |
| Process_Current_Value_Condition (Left_Opnd (Cond), True); |
| |
| if Op /= N_Empty then |
| return; |
| end if; |
| |
| Process_Current_Value_Condition (Right_Opnd (Cond), True); |
| return; |
| |
| -- Case of relational operator |
| |
| elsif Nkind (Cond) in N_Op_Compare then |
| Op := Nkind (Cond); |
| |
| -- Invert sense of test if inverted test |
| |
| 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_Entity_Name (Left_Opnd (Cond)) |
| and then Ent = Entity (Left_Opnd (Cond)) |
| and then Compile_Time_Known_Value (Right_Opnd (Cond)) |
| then |
| Val := Right_Opnd (Cond); |
| |
| -- Case of value op entity |
| |
| 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); |
| |
| -- We are effectively swapping operands |
| |
| 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; |
| |
| else |
| Op := N_Empty; |
| end if; |
| |
| return; |
| |
| elsif Nkind_In (Cond, |
| N_Type_Conversion, |
| N_Qualified_Expression, |
| N_Expression_With_Actions) |
| then |
| Cond := Expression (Cond); |
| |
| -- Case of Boolean variable reference, return as though the |
| -- reference had said var = True. |
| |
| 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; |
| |
| -- Start of processing for Get_Current_Value_Condition |
| |
| begin |
| Op := N_Empty; |
| Val := Empty; |
| |
| -- Immediate return, nothing doing, if this is not an object |
| |
| if Ekind (Ent) not in Object_Kind then |
| return; |
| end if; |
| |
| -- Otherwise examine current value |
| |
| declare |
| CV : constant Node_Id := Current_Value (Ent); |
| Sens : Boolean; |
| Stm : Node_Id; |
| |
| begin |
| -- If statement. Condition is known true in THEN section, known False |
| -- in any ELSIF or ELSE part, and unknown outside the IF statement. |
| |
| if Nkind (CV) = N_If_Statement then |
| |
| -- 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; |
| |
| -- 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. |
| |
| declare |
| N : Node_Id; |
| |
| begin |
| N := Parent (Var); |
| while Parent (N) /= CV 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 now we can tell if we are within |
| -- the THEN statements. |
| |
| if Is_List_Member (N) |
| and then List_Containing (N) = Then_Statements (CV) |
| then |
| Sens := True; |
| |
| -- 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. |
| |
| elsif not Comes_From_Source (N) then |
| return; |
| |
| -- 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 |
| |
| -- if the Elsif_Part had condition_actions, the elsif has been |
| -- rewritten as a nested if, and the original elsif_part is |
| -- detached from the tree, so there is no way to obtain useful |
| -- information on the current value of the variable. |
| -- Can this be improved ??? |
| |
| if No (Parent (CV)) then |
| return; |
| end if; |
| |
| 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; |
| |
| --------------------- |
| -- Get_Stream_Size -- |
| --------------------- |
| |
| function Get_Stream_Size (E : Entity_Id) return Uint is |
| begin |
| -- If we have a Stream_Size clause for this type use it |
| |
| if Has_Stream_Size_Clause (E) then |
| return Static_Integer (Expression (Stream_Size_Clause (E))); |
| |
| -- Otherwise the Stream_Size if the size of the type |
| |
| else |
| return Esize (E); |
| end if; |
| end Get_Stream_Size; |
| |
| --------------------------- |
| -- Has_Access_Constraint -- |
| --------------------------- |
| |
| function Has_Access_Constraint (E : Entity_Id) return Boolean is |
| Disc : Entity_Id; |
| T : constant Entity_Id := Etype (E); |
| |
| begin |
| if Has_Per_Object_Constraint (E) and then Has_Discriminants (T) then |
| Disc := First_Discriminant (T); |
| while Present (Disc) loop |
| if Is_Access_Type (Etype (Disc)) then |
| return True; |
| end if; |
| |
| Next_Discriminant (Disc); |
| end loop; |
| |
| return False; |
| else |
| return False; |
| end if; |
| end Has_Access_Constraint; |
| |
| ----------------------------------------------------- |
| -- Has_Annotate_Pragma_For_External_Axiomatization -- |
| ----------------------------------------------------- |
| |
| function Has_Annotate_Pragma_For_External_Axiomatization |
| (E : Entity_Id) return Boolean |
| is |
| function Is_Annotate_Pragma_For_External_Axiomatization |
| (N : Node_Id) return Boolean; |
| -- Returns whether N is |
| -- pragma Annotate (GNATprove, External_Axiomatization); |
| |
| ---------------------------------------------------- |
| -- Is_Annotate_Pragma_For_External_Axiomatization -- |
| ---------------------------------------------------- |
| |
| -- The general form of pragma Annotate is |
| |
| -- pragma Annotate (IDENTIFIER [, IDENTIFIER {, ARG}]); |
| -- ARG ::= NAME | EXPRESSION |
| |
| -- The first two arguments are by convention intended to refer to an |
| -- external tool and a tool-specific function. These arguments are |
| -- not analyzed. |
| |
| -- The following is used to annotate a package specification which |
| -- GNATprove should treat specially, because the axiomatization of |
| -- this unit is given by the user instead of being automatically |
| -- generated. |
| |
| -- pragma Annotate (GNATprove, External_Axiomatization); |
| |
| function Is_Annotate_Pragma_For_External_Axiomatization |
| (N : Node_Id) return Boolean |
| is |
| Name_GNATprove : constant String := |
| "gnatprove"; |
| Name_External_Axiomatization : constant String := |
| "external_axiomatization"; |
| -- Special names |
| |
| begin |
| if Nkind (N) = N_Pragma |
| and then Get_Pragma_Id (Pragma_Name (N)) = Pragma_Annotate |
| and then List_Length (Pragma_Argument_Associations (N)) = 2 |
| then |
| declare |
| Arg1 : constant Node_Id := |
| First (Pragma_Argument_Associations (N)); |
| Arg2 : constant Node_Id := Next (Arg1); |
| Nam1 : Name_Id; |
| Nam2 : Name_Id; |
| |
| begin |
| -- Fill in Name_Buffer with Name_GNATprove first, and then with |
| -- Name_External_Axiomatization so that Name_Find returns the |
| -- corresponding name. This takes care of all possible casings. |
| |
| Name_Len := 0; |
| Add_Str_To_Name_Buffer (Name_GNATprove); |
| Nam1 := Name_Find; |
| |
| Name_Len := 0; |
| Add_Str_To_Name_Buffer (Name_External_Axiomatization); |
| Nam2 := Name_Find; |
| |
| return Chars (Get_Pragma_Arg (Arg1)) = Nam1 |
| and then |
| Chars (Get_Pragma_Arg (Arg2)) = Nam2; |
| end; |
| |
| else |
| return False; |
| end if; |
| end Is_Annotate_Pragma_For_External_Axiomatization; |
| |
| -- Local variables |
| |
| Decl : Node_Id; |
| Vis_Decls : List_Id; |
| N : Node_Id; |
| |
| -- Start of processing for Has_Annotate_Pragma_For_External_Axiomatization |
| |
| begin |
| if Nkind (Parent (E)) = N_Defining_Program_Unit_Name then |
| Decl := Parent (Parent (E)); |
| else |
| Decl := Parent (E); |
| end if; |
| |
| Vis_Decls := Visible_Declarations (Decl); |
| |
| N := First (Vis_Decls); |
| while Present (N) loop |
| |
| -- Skip declarations generated by the frontend. Skip all pragmas |
| -- that are not the desired Annotate pragma. Stop the search on |
| -- the first non-pragma source declaration. |
| |
| if Comes_From_Source (N) then |
| if Nkind (N) = N_Pragma then |
| if Is_Annotate_Pragma_For_External_Axiomatization (N) then |
| return True; |
| end if; |
| else |
| return False; |
| end if; |
| end if; |
| |
| Next (N); |
| end loop; |
| |
| return False; |
| end Has_Annotate_Pragma_For_External_Axiomatization; |
| |
| -------------------- |
| -- Homonym_Number -- |
| -------------------- |
| |
| function Homonym_Number (Subp : Entity_Id) return Nat is |
| Count : Nat; |
| Hom : Entity_Id; |
| |
| begin |
| Count := 1; |
| Hom := Homonym (Subp); |
| while Present (Hom) loop |
| if Scope (Hom) = Scope (Subp) then |
| Count := Count + 1; |
| end if; |
| |
| Hom := Homonym (Hom); |
| end loop; |
| |
| return Count; |
| end Homonym_Number; |
| |
| ----------------------------------- |
| -- In_Library_Level_Package_Body -- |
| ----------------------------------- |
| |
| function In_Library_Level_Package_Body (Id : Entity_Id) return Boolean is |
| begin |
| -- First determine whether the entity appears at the library level, then |
| -- look at the containing unit. |
| |
| if Is_Library_Level_Entity (Id) then |
| declare |
| Container : constant Node_Id := Cunit (Get_Source_Unit (Id)); |
| |
| begin |
| return Nkind (Unit (Container)) = N_Package_Body; |
| end; |
| end if; |
| |
| return False; |
| end In_Library_Level_Package_Body; |
| |
| ------------------------------ |
| -- In_Unconditional_Context -- |
| ------------------------------ |
| |
| function In_Unconditional_Context (Node : Node_Id) return Boolean is |
| P : Node_Id; |
| |
| begin |
| P := Node; |
| while Present (P) loop |
| case Nkind (P) is |
| when N_Subprogram_Body => |
| return True; |
| |
| when N_If_Statement => |
| return False; |
| |
| when N_Loop_Statement => |
| return False; |
| |
| when N_Case_Statement => |
| return False; |
| |
| when others => |
| P := Parent (P); |
| end case; |
| end loop; |
| |
| return False; |
| end In_Unconditional_Context; |
| |
| ------------------- |
| -- Insert_Action -- |
| ------------------- |
| |
| procedure Insert_Action (Assoc_Node : Node_Id; Ins_Action : Node_Id) is |
| begin |
| if Present (Ins_Action) then |
| Insert_Actions (Assoc_Node, New_List (Ins_Action)); |
| end if; |
| end Insert_Action; |
| |
| -- Version with check(s) suppressed |
| |
| procedure Insert_Action |
| (Assoc_Node : Node_Id; Ins_Action : Node_Id; Suppress : Check_Id) |
| is |
| begin |
| Insert_Actions (Assoc_Node, New_List (Ins_Action), Suppress); |
| end Insert_Action; |
| |
| ------------------------- |
| -- Insert_Action_After -- |
| ------------------------- |
| |
| procedure Insert_Action_After |
| (Assoc_Node : Node_Id; |
| Ins_Action : Node_Id) |
| is |
| begin |
| Insert_Actions_After (Assoc_Node, New_List (Ins_Action)); |
| end Insert_Action_After; |
| |
| -------------------- |
| -- Insert_Actions -- |
| -------------------- |
| |
| procedure Insert_Actions (Assoc_Node : Node_Id; Ins_Actions : List_Id) is |
| N : Node_Id; |
| P : Node_Id; |
| |
| Wrapped_Node : Node_Id := Empty; |
| |
| begin |
| if No (Ins_Actions) or else Is_Empty_List (Ins_Actions) then |
| return; |
| end if; |
| |
| -- 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_Spec_Expression then |
| return; |
| end if; |
| |
| -- If the action derives from stuff inside a record, then the actions |
| -- are attached to the current scope, to be inserted and analyzed on |
| -- exit from the scope. The reason for this is that we may also be |
| -- generating freeze actions at the same time, and they must eventually |
| -- be elaborated in the correct order. |
| |
| if Is_Record_Type (Current_Scope) |
| and then not Is_Frozen (Current_Scope) |
| then |
| if No (Scope_Stack.Table |
| (Scope_Stack.Last).Pending_Freeze_Actions) |
| then |
| Scope_Stack.Table (Scope_Stack.Last).Pending_Freeze_Actions := |
| Ins_Actions; |
| else |
| Append_List |
| (Ins_Actions, |
| Scope_Stack.Table (Scope_Stack.Last).Pending_Freeze_Actions); |
| end if; |
| |
| return; |
| end if; |
| |
| -- We now intend to climb up the tree to find the right point to |
| -- insert the actions. We start at Assoc_Node, unless this node is a |
| -- subexpression in which case we start with its parent. We do this for |
| -- two reasons. First it speeds things up. Second, if Assoc_Node is |
| -- itself one of the special nodes like N_And_Then, then we assume that |
| -- an initial request to insert actions for such a node does not expect |
| -- the actions to get deposited in the node for later handling when the |
| -- node is expanded, since clearly the node is being dealt with by the |
| -- caller. Note that in the subexpression case, N is always the child we |
| -- came from. |
| |
| -- N_Raise_xxx_Error is an annoying special case, it is a statement if |
| -- it has type Standard_Void_Type, and a subexpression otherwise. |
| -- otherwise. Procedure calls, and similarly procedure attribute |
| -- references, are also statements. |
| |
| if Nkind (Assoc_Node) in N_Subexpr |
| and then (Nkind (Assoc_Node) not in N_Raise_xxx_Error |
| or else Etype (Assoc_Node) /= Standard_Void_Type) |
| and then Nkind (Assoc_Node) /= N_Procedure_Call_Statement |
| and then (Nkind (Assoc_Node) /= N_Attribute_Reference |
| or else not Is_Procedure_Attribute_Name |
| (Attribute_Name (Assoc_Node))) |
| then |
| N := Assoc_Node; |
| P := Parent (Assoc_Node); |
| |
| -- Non-subexpression case. Note that N is initially Empty in this case |
| -- (N is only guaranteed Non-Empty in the subexpr case). |
| |
| else |
| N := Empty; |
| P := Assoc_Node; |
| end if; |
| |
| -- Capture root of the transient scope |
| |
| if Scope_Is_Transient then |
| Wrapped_Node := Node_To_Be_Wrapped; |
| end if; |
| |
| loop |
| pragma Assert (Present (P)); |
| |
| -- Make sure that inserted actions stay in the transient scope |
| |
| if Present (Wrapped_Node) and then N = Wrapped_Node then |
| Store_Before_Actions_In_Scope (Ins_Actions); |
| return; |
| end if; |
| |
| case Nkind (P) is |
| |
| -- Case of right operand of AND THEN or OR ELSE. Put the actions |
| -- in the Actions field of the right operand. They will be moved |
| -- out further when the AND THEN or OR ELSE operator is expanded. |
| -- Nothing special needs to be done for the left operand since |
| -- in that case the actions are executed unconditionally. |
| |
| 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 P has already been expanded, we can't park new actions |
| -- on it, so we need to expand them immediately, introducing |
| -- an Expression_With_Actions. N can't be an expression |
| -- with actions, or else then the actions would have been |
| -- inserted at an inner level. |
| |
| if Analyzed (P) then |
| pragma Assert (Nkind (N) /= N_Expression_With_Actions); |
| Rewrite (N, |
| Make_Expression_With_Actions (Sloc (N), |
| Actions => Ins_Actions, |
| Expression => Relocate_Node (N))); |
| Analyze_And_Resolve (N); |
| |
| elsif Present (Actions (P)) then |
| Insert_List_After_And_Analyze |
| (Last (Actions (P)), Ins_Actions); |
| else |
| Set_Actions (P, Ins_Actions); |
| Analyze_List (Actions (P)); |
| end if; |
| |
| Kill_Current_Values; |
| |
| return; |
| end if; |
| |
| -- Then or Else dependent expression of an if expression. Add |
| -- actions to Then_Actions or Else_Actions field as appropriate. |
| -- The actions will be moved further out when the if is expanded. |
| |
| when N_If_Expression => |
| declare |
| ThenX : constant Node_Id := Next (First (Expressions (P))); |
| ElseX : constant Node_Id := Next (ThenX); |
| |
| begin |
| -- If the enclosing expression is already analyzed, as |
| -- is the case for nested elaboration checks, insert the |
| -- conditional further out. |
| |
| if Analyzed (P) then |
| null; |
| |
| -- Actions belong to the then expression, temporarily place |
| -- them as Then_Actions of the if expression. They will be |
| -- moved to the proper place later when the if expression |
| -- is expanded. |
| |
| elsif N = ThenX then |
| if Present (Then_Actions (P)) then |
| Insert_List_After_And_Analyze |
| (Last (Then_Actions (P)), Ins_Actions); |
| else |
| Set_Then_Actions (P, Ins_Actions); |
| Analyze_List (Then_Actions (P)); |
| end if; |
| |
| return; |
| |
| -- Actions belong to the else expression, temporarily place |
| -- them as Else_Actions of the if expression. They will be |
| -- moved to the proper place later when the if expression |
| -- is expanded. |
| |
| elsif N = ElseX then |
| if Present (Else_Actions (P)) then |
| Insert_List_After_And_Analyze |
| (Last (Else_Actions (P)), Ins_Actions); |
| else |
| Set_Else_Actions (P, Ins_Actions); |
| Analyze_List (Else_Actions (P)); |
| end if; |
| |
| return; |
| |
| -- Actions belong to the condition. In this case they are |
| -- unconditionally executed, and so we can continue the |
| -- search for the proper insert point. |
| |
| else |
| null; |
| end if; |
| end; |
| |
| -- Alternative of case expression, we place the action in the |
| -- Actions field of the case expression alternative, this will |
| -- be handled when the case expression is expanded. |
| |
| when N_Case_Expression_Alternative => |
| if Present (Actions (P)) then |
| Insert_List_After_And_Analyze |
| (Last (Actions (P)), Ins_Actions); |
| else |
| Set_Actions (P, Ins_Actions); |
| Analyze_List (Actions (P)); |
| end if; |
| |
| return; |
| |
| -- Case of appearing within an Expressions_With_Actions node. When |
| -- the new actions come from the expression of the expression with |
| -- actions, they must be added to the existing actions. The other |
| -- alternative is when the new actions are related to one of the |
| -- existing actions of the expression with actions, and should |
| -- never reach here: if actions are inserted on a statement |
| -- within the Actions of an expression with actions, or on some |
| -- sub-expression of such a statement, then the outermost proper |
| -- insertion point is right before the statement, and we should |
| -- never climb up as far as the N_Expression_With_Actions itself. |
| |
| when N_Expression_With_Actions => |
| if N = Expression (P) then |
| if Is_Empty_List (Actions (P)) then |
| Append_List_To (Actions (P), Ins_Actions); |
| Analyze_List (Actions (P)); |
| else |
| Insert_List_After_And_Analyze |
| (Last (Actions (P)), Ins_Actions); |
| end if; |
| |
| return; |
| |
| else |
| raise Program_Error; |
| end if; |
| |
| -- Case of appearing in the condition of a while expression or |
| -- elsif. We insert the actions into the Condition_Actions field. |
| -- They will be moved further out when the while loop or elsif |
| -- is analyzed. |
| |
| when N_Iteration_Scheme | |
| N_Elsif_Part |
| => |
| if N = Condition (P) then |
| if Present (Condition_Actions (P)) then |
| Insert_List_After_And_Analyze |
| (Last (Condition_Actions (P)), Ins_Actions); |
| else |
| Set_Condition_Actions (P, Ins_Actions); |
| |
| -- Set the parent of the insert actions explicitly. This |
| -- is not a syntactic field, but we need the parent field |
| -- set, in particular so that freeze can understand that |
| -- it is dealing with condition actions, and properly |
| -- insert the freezing actions. |
| |
| Set_Parent (Ins_Actions, P); |
| Analyze_List (Condition_Actions (P)); |
| end if; |
| |
| return; |
| end if; |
| |
| -- Statements, declarations, pragmas, representation clauses |
| |
| when |
| -- Statements |
| |
| N_Procedure_Call_Statement | |
| N_Statement_Other_Than_Procedure_Call | |
| |
| -- Pragmas |
| |
| N_Pragma | |
| |
| -- Representation_Clause |
| |
| N_At_Clause | |
| N_Attribute_Definition_Clause | |
| N_Enumeration_Representation_Clause | |
| N_Record_Representation_Clause | |
| |
| -- Declarations |
| |
| N_Abstract_Subprogram_Declaration | |
| N_Entry_Body | |
| N_Exception_Declaration | |
| N_Exception_Renaming_Declaration | |
| N_Expression_Function | |
| N_Formal_Abstract_Subprogram_Declaration | |
| N_Formal_Concrete_Subprogram_Declaration | |
| N_Formal_Object_Declaration | |
| N_Formal_Type_Declaration | |
| N_Full_Type_Declaration | |
| N_Function_Instantiation | |
| N_Generic_Function_Renaming_Declaration | |
| N_Generic_Package_Declaration | |
| N_Generic_Package_Renaming_Declaration | |
| N_Generic_Procedure_Renaming_Declaration | |
| N_Generic_Subprogram_Declaration | |
| N_Implicit_Label_Declaration | |
| N_Incomplete_Type_Declaration | |
| N_Number_Declaration | |
| N_Object_Declaration | |
| N_Object_Renaming_Declaration | |
| N_Package_Body | |
| N_Package_Body_Stub | |
| N_Package_Declaration | |
| N_Package_Instantiation | |
| N_Package_Renaming_Declaration | |
| 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 | |
| N_Subprogram_Body | |
| N_Subprogram_Body_Stub | |
| N_Subprogram_Declaration | |
| N_Subprogram_Renaming_Declaration | |
| N_Subtype_Declaration | |
| N_Task_Body | |
| N_Task_Body_Stub | |
| N_Task_Type_Declaration | |
| |
| -- Use clauses can appear in lists of declarations |
| |
| N_Use_Package_Clause | |
| N_Use_Type_Clause | |
| |
| -- Freeze entity behaves like a declaration or statement |
| |
| N_Freeze_Entity | |
| N_Freeze_Generic_Entity |
| => |
| -- Do not insert here if the item is not a list member (this |
| -- happens for example with a triggering statement, and the |
| -- proper approach is to insert before the entire select). |
| |
| if not Is_List_Member (P) then |
| 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 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; |
| |
| -- Do not insert if the parent of P is either an N_Variant node |
| -- or an N_Record_Definition node, meaning in either case that |
| -- P is a member of a component list, and that therefore the |
| -- actions should be inserted outside the complete record |
| -- declaration. |
| |
| elsif Nkind_In (Parent (P), N_Variant, N_Record_Definition) then |
| null; |
| |
| -- Do not insert freeze nodes within the loop generated for |
| -- an aggregate, because they may be elaborated too late for |
| -- subsequent use in the back end: within a package spec the |
| -- loop is part of the elaboration procedure and is only |
| -- elaborated during the second pass. |
| |
| -- If the loop comes from source, or the entity is local to the |
| -- loop itself it must remain within. |
| |
| elsif Nkind (Parent (P)) = N_Loop_Statement |
| and then not Comes_From_Source (Parent (P)) |
| and then Nkind (First (Ins_Actions)) = N_Freeze_Entity |
| and then |
| Scope (Entity (First (Ins_Actions))) /= Current_Scope |
| then |
| null; |
| |
| -- Otherwise we can go ahead and do the insertion |
| |
| elsif P = Wrapped_Node then |
| Store_Before_Actions_In_Scope (Ins_Actions); |
| return; |
| |
| else |
| Insert_List_Before_And_Analyze (P, Ins_Actions); |
| return; |
| end if; |
| |
| -- A special case, N_Raise_xxx_Error can act either as a statement |
| -- or a subexpression. We tell the difference by looking at the |
| -- Etype. It is set to Standard_Void_Type in the statement case. |
| |
| when |
| N_Raise_xxx_Error => |
| if Etype (P) = Standard_Void_Type then |
| if P = Wrapped_Node then |
| Store_Before_Actions_In_Scope (Ins_Actions); |
| else |
| Insert_List_Before_And_Analyze (P, Ins_Actions); |
| end if; |
| |
| return; |
| |
| -- In the subexpression case, keep climbing |
| |
| else |
| null; |
| end if; |
| |
| -- If a component association appears within a loop created for |
| -- an array aggregate, attach the actions to the association so |
| -- they can be subsequently inserted within the loop. For other |
| -- component associations insert outside of the aggregate. For |
| -- an association that will generate a loop, its Loop_Actions |
| -- attribute is already initialized (see exp_aggr.adb). |
| |
| -- The list of loop_actions can in turn generate additional ones, |
| -- that are inserted before the associated node. If the associated |
| -- node is outside the aggregate, the new actions are collected |
| -- at the end of the loop actions, to respect the order in which |
| -- they are to be elaborated. |
| |
| when |
| N_Component_Association => |
| if Nkind (Parent (P)) = N_Aggregate |
| and then Present (Loop_Actions (P)) |
| then |
| if Is_Empty_List (Loop_Actions (P)) then |
| Set_Loop_Actions (P, Ins_Actions); |
| Analyze_List (Ins_Actions); |
| |
| else |
| declare |
| Decl : Node_Id; |
| |
| begin |
| -- Check whether these actions were generated by a |
| -- declaration that is part of the loop_ actions |
| -- for the component_association. |
| |
| Decl := Assoc_Node; |
| while Present (Decl) loop |
| exit when Parent (Decl) = P |
| and then Is_List_Member (Decl) |
| and then |
| List_Containing (Decl) = Loop_Actions (P); |
| Decl := Parent (Decl); |
| end loop; |
| |
| if Present (Decl) then |
| Insert_List_Before_And_Analyze |
| (Decl, Ins_Actions); |
| else |
| Insert_List_After_And_Analyze |
| (Last (Loop_Actions (P)), Ins_Actions); |
| end if; |
| end; |
| end if; |
| |
| return; |
| |
| else |
| null; |
| end if; |
| |
| -- Another special case, an attribute denoting a procedure call |
| |
| when |
| N_Attribute_Reference => |
| if Is_Procedure_Attribute_Name (Attribute_Name (P)) then |
| if P = Wrapped_Node then |
| Store_Before_Actions_In_Scope (Ins_Actions); |
| else |
| Insert_List_Before_And_Analyze (P, Ins_Actions); |
| end if; |
| |
| return; |
| |
| -- In the subexpression case, keep climbing |
| |
| else |
| null; |
| end if; |
| |
| -- A contract node should not belong to the tree |
| |
| when N_Contract => |
| raise Program_Error; |
| |
| -- For all other node types, keep climbing tree |
| |
| when |
| N_Abortable_Part | |
| N_Accept_Alternative | |
| N_Access_Definition | |
| N_Access_Function_Definition | |
| N_Access_Procedure_Definition | |
| N_Access_To_Object_Definition | |
| N_Aggregate | |
| N_Allocator | |
| N_Aspect_Specification | |
| N_Case_Expression | |
| N_Case_Statement_Alternative | |
| N_Character_Literal | |
| N_Compilation_Unit | |
| N_Compilation_Unit_Aux | |
| N_Component_Clause | |
| N_Component_Declaration | |
| N_Component_Definition | |
| N_Component_List | |
| N_Constrained_Array_Definition | |
| N_Decimal_Fixed_Point_Definition | |
| N_Defining_Character_Literal | |
| N_Defining_Identifier | |
| N_Defining_Operator_Symbol | |
| N_Defining_Program_Unit_Name | |
| N_Delay_Alternative | |
| N_Delta_Constraint | |
| N_Derived_Type_Definition | |
| N_Designator | |
| N_Digits_Constraint | |
| N_Discriminant_Association | |
| N_Discriminant_Specification | |
| N_Empty | |
| N_Entry_Body_Formal_Part | |
| N_Entry_Call_Alternative | |
| N_Entry_Declaration | |
| N_Entry_Index_Specification | |
| N_Enumeration_Type_Definition | |
| N_Error | |
| N_Exception_Handler | |
| N_Expanded_Name | |
| N_Explicit_Dereference | |
| N_Extension_Aggregate | |
| N_Floating_Point_Definition | |
| N_Formal_Decimal_Fixed_Point_Definition | |
| N_Formal_Derived_Type_Definition | |
| N_Formal_Discrete_Type_Definition | |
| N_Formal_Floating_Point_Definition | |
| N_Formal_Modular_Type_Definition | |
| N_Formal_Ordinary_Fixed_Point_Definition | |
| N_Formal_Package_Declaration | |
| N_Formal_Private_Type_Definition | |
| N_Formal_Incomplete_Type_Definition | |
| N_Formal_Signed_Integer_Type_Definition | |
| N_Function_Call | |
| N_Function_Specification | |
| N_Generic_Association | |
| N_Handled_Sequence_Of_Statements | |
| N_Identifier | |
| N_In | |
| N_Index_Or_Discriminant_Constraint | |
| N_Indexed_Component | |
| N_Integer_Literal | |
| N_Iterator_Specification | |
| N_Itype_Reference | |
| N_Label | |
| N_Loop_Parameter_Specification | |
| N_Mod_Clause | |
| N_Modular_Type_Definition | |
| N_Not_In | |
| N_Null | |
| N_Op_Abs | |
| N_Op_Add | |
| N_Op_And | |
| N_Op_Concat | |
| N_Op_Divide | |
| N_Op_Eq | |
| N_Op_Expon | |
| N_Op_Ge | |
| N_Op_Gt | |
| N_Op_Le | |
| N_Op_Lt | |
| N_Op_Minus | |
| N_Op_Mod | |
| N_Op_Multiply | |
| N_Op_Ne | |
| N_Op_Not | |
| N_Op_Or | |
| N_Op_Plus | |
| N_Op_Rem | |
| N_Op_Rotate_Left | |
| N_Op_Rotate_Right | |
| N_Op_Shift_Left | |
| N_Op_Shift_Right | |
| N_Op_Shift_Right_Arithmetic | |
| N_Op_Subtract | |
| N_Op_Xor | |
|