| ------------------------------------------------------------------------------ |
| -- -- |
| -- GNAT COMPILER COMPONENTS -- |
| -- -- |
| -- E X P _ C H 9 -- |
| -- -- |
| -- 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 Atree; use Atree; |
| with Checks; use Checks; |
| with Einfo; use Einfo; |
| with Elists; use Elists; |
| with Errout; use Errout; |
| with Exp_Ch3; use Exp_Ch3; |
| with Exp_Ch6; use Exp_Ch6; |
| with Exp_Ch11; use Exp_Ch11; |
| with Exp_Dbug; use Exp_Dbug; |
| with Exp_Disp; use Exp_Disp; |
| with Exp_Sel; use Exp_Sel; |
| with Exp_Smem; use Exp_Smem; |
| with Exp_Tss; use Exp_Tss; |
| with Exp_Util; use Exp_Util; |
| with Freeze; use Freeze; |
| with Hostparm; |
| with Itypes; use Itypes; |
| with Namet; use Namet; |
| with Nlists; use Nlists; |
| with Nmake; use Nmake; |
| with Opt; use Opt; |
| with Restrict; use Restrict; |
| with Rident; use Rident; |
| with Rtsfind; use Rtsfind; |
| with Sem; use Sem; |
| with Sem_Aux; use Sem_Aux; |
| with Sem_Ch6; use Sem_Ch6; |
| with Sem_Ch8; use Sem_Ch8; |
| with Sem_Ch9; use Sem_Ch9; |
| with Sem_Ch11; use Sem_Ch11; |
| with Sem_Elab; use Sem_Elab; |
| with Sem_Eval; use Sem_Eval; |
| with Sem_Res; use Sem_Res; |
| with Sem_Util; use Sem_Util; |
| with Sinfo; use Sinfo; |
| with Snames; use Snames; |
| with Stand; use Stand; |
| with Stringt; use Stringt; |
| with Targparm; use Targparm; |
| with Tbuild; use Tbuild; |
| with Uintp; use Uintp; |
| |
| package body Exp_Ch9 is |
| |
| -- The following constant establishes the upper bound for the index of |
| -- an entry family. It is used to limit the allocated size of protected |
| -- types with defaulted discriminant of an integer type, when the bound |
| -- of some entry family depends on a discriminant. The limitation to entry |
| -- families of 128K should be reasonable in all cases, and is a documented |
| -- implementation restriction. |
| |
| Entry_Family_Bound : constant Int := 2**16; |
| |
| ----------------------- |
| -- Local Subprograms -- |
| ----------------------- |
| |
| function Actual_Index_Expression |
| (Sloc : Source_Ptr; |
| Ent : Entity_Id; |
| Index : Node_Id; |
| Tsk : Entity_Id) return Node_Id; |
| -- Compute the index position for an entry call. Tsk is the target task. If |
| -- the bounds of some entry family depend on discriminants, the expression |
| -- computed by this function uses the discriminants of the target task. |
| |
| procedure Add_Object_Pointer |
| (Loc : Source_Ptr; |
| Conc_Typ : Entity_Id; |
| Decls : List_Id); |
| -- Prepend an object pointer declaration to the declaration list Decls. |
| -- This object pointer is initialized to a type conversion of the System. |
| -- Address pointer passed to entry barrier functions and entry body |
| -- procedures. |
| |
| procedure Add_Formal_Renamings |
| (Spec : Node_Id; |
| Decls : List_Id; |
| Ent : Entity_Id; |
| Loc : Source_Ptr); |
| -- Create renaming declarations for the formals, inside the procedure that |
| -- implements an entry body. The renamings make the original names of the |
| -- formals accessible to gdb, and serve no other purpose. |
| -- Spec is the specification of the procedure being built. |
| -- Decls is the list of declarations to be enhanced. |
| -- Ent is the entity for the original entry body. |
| |
| function Build_Accept_Body (Astat : Node_Id) return Node_Id; |
| -- Transform accept statement into a block with added exception handler. |
| -- Used both for simple accept statements and for accept alternatives in |
| -- select statements. Astat is the accept statement. |
| |
| function Build_Barrier_Function |
| (N : Node_Id; |
| Ent : Entity_Id; |
| Pid : Node_Id) return Node_Id; |
| -- Build the function body returning the value of the barrier expression |
| -- for the specified entry body. |
| |
| function Build_Barrier_Function_Specification |
| (Loc : Source_Ptr; |
| Def_Id : Entity_Id) return Node_Id; |
| -- Build a specification for a function implementing the protected entry |
| -- barrier of the specified entry body. |
| |
| function Build_Corresponding_Record |
| (N : Node_Id; |
| Ctyp : Node_Id; |
| Loc : Source_Ptr) return Node_Id; |
| -- Common to tasks and protected types. Copy discriminant specifications, |
| -- build record declaration. N is the type declaration, Ctyp is the |
| -- concurrent entity (task type or protected type). |
| |
| function Build_Dispatching_Tag_Check |
| (K : Entity_Id; |
| N : Node_Id) return Node_Id; |
| -- Utility to create the tree to check whether the dispatching call in |
| -- a timed entry call, a conditional entry call, or an asynchronous |
| -- transfer of control is a call to a primitive of a non-synchronized type. |
| -- K is the temporary that holds the tagged kind of the target object, and |
| -- N is the enclosing construct. |
| |
| function Build_Entry_Count_Expression |
| (Concurrent_Type : Node_Id; |
| Component_List : List_Id; |
| Loc : Source_Ptr) return Node_Id; |
| -- Compute number of entries for concurrent object. This is a count of |
| -- simple entries, followed by an expression that computes the length |
| -- of the range of each entry family. A single array with that size is |
| -- allocated for each concurrent object of the type. |
| |
| function Build_Find_Body_Index (Typ : Entity_Id) return Node_Id; |
| -- Build the function that translates the entry index in the call |
| -- (which depends on the size of entry families) into an index into the |
| -- Entry_Bodies_Array, to determine the body and barrier function used |
| -- in a protected entry call. A pointer to this function appears in every |
| -- protected object. |
| |
| function Build_Find_Body_Index_Spec (Typ : Entity_Id) return Node_Id; |
| -- Build subprogram declaration for previous one |
| |
| function Build_Lock_Free_Protected_Subprogram_Body |
| (N : Node_Id; |
| Prot_Typ : Node_Id; |
| Unprot_Spec : Node_Id) return Node_Id; |
| -- N denotes a subprogram body of protected type Prot_Typ. Unprot_Spec is |
| -- the subprogram specification of the unprotected version of N. Transform |
| -- N such that it invokes the unprotected version of the body. |
| |
| function Build_Lock_Free_Unprotected_Subprogram_Body |
| (N : Node_Id; |
| Prot_Typ : Node_Id) return Node_Id; |
| -- N denotes a subprogram body of protected type Prot_Typ. Build a version |
| -- of N where the original statements of N are synchronized through atomic |
| -- actions such as compare and exchange. Prior to invoking this routine, it |
| -- has been established that N can be implemented in a lock-free fashion. |
| |
| function Build_Parameter_Block |
| (Loc : Source_Ptr; |
| Actuals : List_Id; |
| Formals : List_Id; |
| Decls : List_Id) return Entity_Id; |
| -- Generate an access type for each actual parameter in the list Actuals. |
| -- Create an encapsulating record that contains all the actuals and return |
| -- its type. Generate: |
| -- type Ann1 is access all <actual1-type> |
| -- ... |
| -- type AnnN is access all <actualN-type> |
| -- type Pnn is record |
| -- <formal1> : Ann1; |
| -- ... |
| -- <formalN> : AnnN; |
| -- end record; |
| |
| procedure Build_PPC_Wrapper (E : Entity_Id; Decl : Node_Id); |
| -- Build body of wrapper procedure for an entry or entry family that has |
| -- pre/postconditions. The body gathers the PPC's and expands them in the |
| -- usual way, and performs the entry call itself. This way preconditions |
| -- are evaluated before the call is queued. E is the entry in question, |
| -- and Decl is the enclosing synchronized type declaration at whose freeze |
| -- point the generated body is analyzed. |
| |
| function Build_Protected_Entry |
| (N : Node_Id; |
| Ent : Entity_Id; |
| Pid : Node_Id) return Node_Id; |
| -- Build the procedure implementing the statement sequence of the specified |
| -- entry body. |
| |
| function Build_Protected_Entry_Specification |
| (Loc : Source_Ptr; |
| Def_Id : Entity_Id; |
| Ent_Id : Entity_Id) return Node_Id; |
| -- Build a specification for the procedure implementing the statements of |
| -- the specified entry body. Add attributes associating it with the entry |
| -- defining identifier Ent_Id. |
| |
| function Build_Protected_Spec |
| (N : Node_Id; |
| Obj_Type : Entity_Id; |
| Ident : Entity_Id; |
| Unprotected : Boolean := False) return List_Id; |
| -- Utility shared by Build_Protected_Sub_Spec and Expand_Access_Protected_ |
| -- Subprogram_Type. Builds signature of protected subprogram, adding the |
| -- formal that corresponds to the object itself. For an access to protected |
| -- subprogram, there is no object type to specify, so the parameter has |
| -- type Address and mode In. An indirect call through such a pointer will |
| -- convert the address to a reference to the actual object. The object is |
| -- a limited record and therefore a by_reference type. |
| |
| function Build_Protected_Subprogram_Body |
| (N : Node_Id; |
| Pid : Node_Id; |
| N_Op_Spec : Node_Id) return Node_Id; |
| -- This function is used to construct the protected version of a protected |
| -- subprogram. Its statement sequence first defers abort, then locks the |
| -- associated protected object, and then enters a block that contains a |
| -- call to the unprotected version of the subprogram (for details, see |
| -- Build_Unprotected_Subprogram_Body). This block statement requires a |
| -- cleanup handler that unlocks the object in all cases. For details, |
| -- see Exp_Ch7.Expand_Cleanup_Actions. |
| |
| function Build_Renamed_Formal_Declaration |
| (New_F : Entity_Id; |
| Formal : Entity_Id; |
| Comp : Entity_Id; |
| Renamed_Formal : Node_Id) return Node_Id; |
| -- Create a renaming declaration for a formal, within a protected entry |
| -- body or an accept body. The renamed object is a component of the |
| -- parameter block that is a parameter in the entry call. |
| -- |
| -- In Ada 2012, if the formal is an incomplete tagged type, the renaming |
| -- does not dereference the corresponding component to prevent an illegal |
| -- use of the incomplete type (AI05-0151). |
| |
| function Build_Selected_Name |
| (Prefix : Entity_Id; |
| Selector : Entity_Id; |
| Append_Char : Character := ' ') return Name_Id; |
| -- Build a name in the form of Prefix__Selector, with an optional character |
| -- appended. This is used for internal subprograms generated for operations |
| -- of protected types, including barrier functions. For the subprograms |
| -- generated for entry bodies and entry barriers, the generated name |
| -- includes a sequence number that makes names unique in the presence of |
| -- entry overloading. This is necessary because entry body procedures and |
| -- barrier functions all have the same signature. |
| |
| procedure Build_Simple_Entry_Call |
| (N : Node_Id; |
| Concval : Node_Id; |
| Ename : Node_Id; |
| Index : Node_Id); |
| -- Some comments here would be useful ??? |
| |
| function Build_Task_Proc_Specification (T : Entity_Id) return Node_Id; |
| -- This routine constructs a specification for the procedure that we will |
| -- build for the task body for task type T. The spec has the form: |
| -- |
| -- procedure tnameB (_Task : access tnameV); |
| -- |
| -- where name is the character name taken from the task type entity that |
| -- is passed as the argument to the procedure, and tnameV is the task |
| -- value type that is associated with the task type. |
| |
| function Build_Unprotected_Subprogram_Body |
| (N : Node_Id; |
| Pid : Node_Id) return Node_Id; |
| -- This routine constructs the unprotected version of a protected |
| -- subprogram body, which is contains all of the code in the original, |
| -- unexpanded body. This is the version of the protected subprogram that is |
| -- called from all protected operations on the same object, including the |
| -- protected version of the same subprogram. |
| |
| procedure Build_Wrapper_Bodies |
| (Loc : Source_Ptr; |
| Typ : Entity_Id; |
| N : Node_Id); |
| -- Ada 2005 (AI-345): Typ is either a concurrent type or the corresponding |
| -- record of a concurrent type. N is the insertion node where all bodies |
| -- will be placed. This routine builds the bodies of the subprograms which |
| -- serve as an indirection mechanism to overriding primitives of concurrent |
| -- types, entries and protected procedures. Any new body is analyzed. |
| |
| procedure Build_Wrapper_Specs |
| (Loc : Source_Ptr; |
| Typ : Entity_Id; |
| N : in out Node_Id); |
| -- Ada 2005 (AI-345): Typ is either a concurrent type or the corresponding |
| -- record of a concurrent type. N is the insertion node where all specs |
| -- will be placed. This routine builds the specs of the subprograms which |
| -- serve as an indirection mechanism to overriding primitives of concurrent |
| -- types, entries and protected procedures. Any new spec is analyzed. |
| |
| procedure Collect_Entry_Families |
| (Loc : Source_Ptr; |
| Cdecls : List_Id; |
| Current_Node : in out Node_Id; |
| Conctyp : Entity_Id); |
| -- For each entry family in a concurrent type, create an anonymous array |
| -- type of the right size, and add a component to the corresponding_record. |
| |
| function Concurrent_Object |
| (Spec_Id : Entity_Id; |
| Conc_Typ : Entity_Id) return Entity_Id; |
| -- Given a subprogram entity Spec_Id and concurrent type Conc_Typ, return |
| -- the entity associated with the concurrent object in the Protected_Body_ |
| -- Subprogram or the Task_Body_Procedure of Spec_Id. The returned entity |
| -- denotes formal parameter _O, _object or _task. |
| |
| function Copy_Result_Type (Res : Node_Id) return Node_Id; |
| -- Copy the result type of a function specification, when building the |
| -- internal operation corresponding to a protected function, or when |
| -- expanding an access to protected function. If the result is an anonymous |
| -- access to subprogram itself, we need to create a new signature with the |
| -- same parameter names and the same resolved types, but with new entities |
| -- for the formals. |
| |
| procedure Debug_Private_Data_Declarations (Decls : List_Id); |
| -- Decls is a list which may contain the declarations created by Install_ |
| -- Private_Data_Declarations. All generated entities are marked as needing |
| -- debug info and debug nodes are manually generation where necessary. This |
| -- step of the expansion must to be done after private data has been moved |
| -- to its final resting scope to ensure proper visibility of debug objects. |
| |
| procedure Ensure_Statement_Present (Loc : Source_Ptr; Alt : Node_Id); |
| -- If control flow optimizations are suppressed, and Alt is an accept, |
| -- delay, or entry call alternative with no trailing statements, insert |
| -- a null trailing statement with the given Loc (which is the sloc of |
| -- the accept, delay, or entry call statement). There might not be any |
| -- generated code for the accept, delay, or entry call itself (the effect |
| -- of these statements is part of the general processsing done for the |
| -- enclosing selective accept, timed entry call, or asynchronous select), |
| -- and the null statement is there to carry the sloc of that statement to |
| -- the back-end for trace-based coverage analysis purposes. |
| |
| procedure Extract_Dispatching_Call |
| (N : Node_Id; |
| Call_Ent : out Entity_Id; |
| Object : out Entity_Id; |
| Actuals : out List_Id; |
| Formals : out List_Id); |
| -- Given a dispatching call, extract the entity of the name of the call, |
| -- its actual dispatching object, its actual parameters and the formal |
| -- parameters of the overridden interface-level version. If the type of |
| -- the dispatching object is an access type then an explicit dereference |
| -- is returned in Object. |
| |
| procedure Extract_Entry |
| (N : Node_Id; |
| Concval : out Node_Id; |
| Ename : out Node_Id; |
| Index : out Node_Id); |
| -- Given an entry call, returns the associated concurrent object, the entry |
| -- name, and the entry family index. |
| |
| function Family_Offset |
| (Loc : Source_Ptr; |
| Hi : Node_Id; |
| Lo : Node_Id; |
| Ttyp : Entity_Id; |
| Cap : Boolean) return Node_Id; |
| -- Compute (Hi - Lo) for two entry family indexes. Hi is the index in an |
| -- accept statement, or the upper bound in the discrete subtype of an entry |
| -- declaration. Lo is the corresponding lower bound. Ttyp is the concurrent |
| -- type of the entry. If Cap is true, the result is capped according to |
| -- Entry_Family_Bound. |
| |
| function Family_Size |
| (Loc : Source_Ptr; |
| Hi : Node_Id; |
| Lo : Node_Id; |
| Ttyp : Entity_Id; |
| Cap : Boolean) return Node_Id; |
| -- Compute (Hi - Lo) + 1 Max 0, to determine the number of entries in a |
| -- family, and handle properly the superflat case. This is equivalent to |
| -- the use of 'Length on the index type, but must use Family_Offset to |
| -- handle properly the case of bounds that depend on discriminants. If |
| -- Cap is true, the result is capped according to Entry_Family_Bound. |
| |
| procedure Find_Enclosing_Context |
| (N : Node_Id; |
| Context : out Node_Id; |
| Context_Id : out Entity_Id; |
| Context_Decls : out List_Id); |
| -- Subsidiary routine to procedures Build_Activation_Chain_Entity and |
| -- Build_Master_Entity. Given an arbitrary node in the tree, find the |
| -- nearest enclosing body, block, package or return statement and return |
| -- its constituents. Context is the enclosing construct, Context_Id is |
| -- the scope of Context_Id and Context_Decls is the declarative list of |
| -- Context. |
| |
| function Index_Object (Spec_Id : Entity_Id) return Entity_Id; |
| -- Given a subprogram identifier, return the entity which is associated |
| -- with the protection entry index in the Protected_Body_Subprogram or |
| -- the Task_Body_Procedure of Spec_Id. The returned entity denotes formal |
| -- parameter _E. |
| |
| function Is_Exception_Safe (Subprogram : Node_Id) return Boolean; |
| -- Tell whether a given subprogram cannot raise an exception |
| |
| function Is_Potentially_Large_Family |
| (Base_Index : Entity_Id; |
| Conctyp : Entity_Id; |
| Lo : Node_Id; |
| Hi : Node_Id) return Boolean; |
| |
| function Is_Private_Primitive_Subprogram (Id : Entity_Id) return Boolean; |
| -- Determine whether Id is a function or a procedure and is marked as a |
| -- private primitive. |
| |
| function Null_Statements (Stats : List_Id) return Boolean; |
| -- Used to check DO-END sequence. Checks for equivalent of DO NULL; END. |
| -- Allows labels, and pragma Warnings/Unreferenced in the sequence as well |
| -- to still count as null. Returns True for a null sequence. The argument |
| -- is the list of statements from the DO-END sequence. |
| |
| function Parameter_Block_Pack |
| (Loc : Source_Ptr; |
| Blk_Typ : Entity_Id; |
| Actuals : List_Id; |
| Formals : List_Id; |
| Decls : List_Id; |
| Stmts : List_Id) return Entity_Id; |
| -- Set the components of the generated parameter block with the values |
| -- of the actual parameters. Generate aliased temporaries to capture the |
| -- values for types that are passed by copy. Otherwise generate a reference |
| -- to the actual's value. Return the address of the aggregate block. |
| -- Generate: |
| -- Jnn1 : alias <formal-type1>; |
| -- Jnn1 := <actual1>; |
| -- ... |
| -- P : Blk_Typ := ( |
| -- Jnn1'unchecked_access; |
| -- <actual2>'reference; |
| -- ...); |
| |
| function Parameter_Block_Unpack |
| (Loc : Source_Ptr; |
| P : Entity_Id; |
| Actuals : List_Id; |
| Formals : List_Id) return List_Id; |
| -- Retrieve the values of the components from the parameter block and |
| -- assign then to the original actual parameters. Generate: |
| -- <actual1> := P.<formal1>; |
| -- ... |
| -- <actualN> := P.<formalN>; |
| |
| function Trivial_Accept_OK return Boolean; |
| -- If there is no DO-END block for an accept, or if the DO-END block has |
| -- only null statements, then it is possible to do the Rendezvous with much |
| -- less overhead using the Accept_Trivial routine in the run-time library. |
| -- However, this is not always a valid optimization. Whether it is valid or |
| -- not depends on the Task_Dispatching_Policy. The issue is whether a full |
| -- rescheduling action is required or not. In FIFO_Within_Priorities, such |
| -- a rescheduling is required, so this optimization is not allowed. This |
| -- function returns True if the optimization is permitted. |
| |
| ----------------------------- |
| -- Actual_Index_Expression -- |
| ----------------------------- |
| |
| function Actual_Index_Expression |
| (Sloc : Source_Ptr; |
| Ent : Entity_Id; |
| Index : Node_Id; |
| Tsk : Entity_Id) return Node_Id |
| is |
| Ttyp : constant Entity_Id := Etype (Tsk); |
| Expr : Node_Id; |
| Num : Node_Id; |
| Lo : Node_Id; |
| Hi : Node_Id; |
| Prev : Entity_Id; |
| S : Node_Id; |
| |
| function Actual_Family_Offset (Hi, Lo : Node_Id) return Node_Id; |
| -- Compute difference between bounds of entry family |
| |
| -------------------------- |
| -- Actual_Family_Offset -- |
| -------------------------- |
| |
| function Actual_Family_Offset (Hi, Lo : Node_Id) return Node_Id is |
| |
| function Actual_Discriminant_Ref (Bound : Node_Id) return Node_Id; |
| -- Replace a reference to a discriminant with a selected component |
| -- denoting the discriminant of the target task. |
| |
| ----------------------------- |
| -- Actual_Discriminant_Ref -- |
| ----------------------------- |
| |
| function Actual_Discriminant_Ref (Bound : Node_Id) return Node_Id is |
| Typ : constant Entity_Id := Etype (Bound); |
| B : Node_Id; |
| |
| begin |
| if not Is_Entity_Name (Bound) |
| or else Ekind (Entity (Bound)) /= E_Discriminant |
| then |
| if Nkind (Bound) = N_Attribute_Reference then |
| return Bound; |
| else |
| B := New_Copy_Tree (Bound); |
| end if; |
| |
| else |
| B := |
| Make_Selected_Component (Sloc, |
| Prefix => New_Copy_Tree (Tsk), |
| Selector_Name => New_Occurrence_Of (Entity (Bound), Sloc)); |
| |
| Analyze_And_Resolve (B, Typ); |
| end if; |
| |
| return |
| Make_Attribute_Reference (Sloc, |
| Attribute_Name => Name_Pos, |
| Prefix => New_Occurrence_Of (Etype (Bound), Sloc), |
| Expressions => New_List (B)); |
| end Actual_Discriminant_Ref; |
| |
| -- Start of processing for Actual_Family_Offset |
| |
| begin |
| return |
| Make_Op_Subtract (Sloc, |
| Left_Opnd => Actual_Discriminant_Ref (Hi), |
| Right_Opnd => Actual_Discriminant_Ref (Lo)); |
| end Actual_Family_Offset; |
| |
| -- Start of processing for Actual_Index_Expression |
| |
| begin |
| -- The queues of entries and entry families appear in textual order in |
| -- the associated record. The entry index is computed as the sum of the |
| -- number of queues for all entries that precede the designated one, to |
| -- which is added the index expression, if this expression denotes a |
| -- member of a family. |
| |
| -- The following is a place holder for the count of simple entries |
| |
| Num := Make_Integer_Literal (Sloc, 1); |
| |
| -- We construct an expression which is a series of addition operations. |
| -- See comments in Entry_Index_Expression, which is identical in |
| -- structure. |
| |
| if Present (Index) then |
| S := Etype (Discrete_Subtype_Definition (Declaration_Node (Ent))); |
| |
| Expr := |
| Make_Op_Add (Sloc, |
| Left_Opnd => Num, |
| Right_Opnd => |
| Actual_Family_Offset ( |
| Make_Attribute_Reference (Sloc, |
| Attribute_Name => Name_Pos, |
| Prefix => New_Occurrence_Of (Base_Type (S), Sloc), |
| Expressions => New_List (Relocate_Node (Index))), |
| Type_Low_Bound (S))); |
| else |
| Expr := Num; |
| end if; |
| |
| -- Now add lengths of preceding entries and entry families |
| |
| Prev := First_Entity (Ttyp); |
| while Chars (Prev) /= Chars (Ent) |
| or else (Ekind (Prev) /= Ekind (Ent)) |
| or else not Sem_Ch6.Type_Conformant (Ent, Prev) |
| loop |
| if Ekind (Prev) = E_Entry then |
| Set_Intval (Num, Intval (Num) + 1); |
| |
| elsif Ekind (Prev) = E_Entry_Family then |
| S := |
| Etype (Discrete_Subtype_Definition (Declaration_Node (Prev))); |
| |
| -- The need for the following full view retrieval stems from this |
| -- complex case of nested generics and tasking: |
| |
| -- generic |
| -- type Formal_Index is range <>; |
| -- ... |
| -- package Outer is |
| -- type Index is private; |
| -- generic |
| -- ... |
| -- package Inner is |
| -- procedure P; |
| -- end Inner; |
| -- private |
| -- type Index is new Formal_Index range 1 .. 10; |
| -- end Outer; |
| |
| -- package body Outer is |
| -- task type T is |
| -- entry Fam (Index); -- (2) |
| -- entry E; |
| -- end T; |
| -- package body Inner is -- (3) |
| -- procedure P is |
| -- begin |
| -- T.E; -- (1) |
| -- end P; |
| -- end Inner; |
| -- ... |
| |
| -- We are currently building the index expression for the entry |
| -- call "T.E" (1). Part of the expansion must mention the range |
| -- of the discrete type "Index" (2) of entry family "Fam". |
| |
| -- However only the private view of type "Index" is available to |
| -- the inner generic (3) because there was no prior mention of |
| -- the type inside "Inner". This visibility requirement is |
| -- implicit and cannot be detected during the construction of |
| -- the generic trees and needs special handling. |
| |
| if In_Instance_Body |
| and then Is_Private_Type (S) |
| and then Present (Full_View (S)) |
| then |
| S := Full_View (S); |
| end if; |
| |
| Lo := Type_Low_Bound (S); |
| Hi := Type_High_Bound (S); |
| |
| Expr := |
| Make_Op_Add (Sloc, |
| Left_Opnd => Expr, |
| Right_Opnd => |
| Make_Op_Add (Sloc, |
| Left_Opnd => Actual_Family_Offset (Hi, Lo), |
| Right_Opnd => Make_Integer_Literal (Sloc, 1))); |
| |
| -- Other components are anonymous types to be ignored |
| |
| else |
| null; |
| end if; |
| |
| Next_Entity (Prev); |
| end loop; |
| |
| return Expr; |
| end Actual_Index_Expression; |
| |
| -------------------------- |
| -- Add_Formal_Renamings -- |
| -------------------------- |
| |
| procedure Add_Formal_Renamings |
| (Spec : Node_Id; |
| Decls : List_Id; |
| Ent : Entity_Id; |
| Loc : Source_Ptr) |
| is |
| Ptr : constant Entity_Id := |
| Defining_Identifier |
| (Next (First (Parameter_Specifications (Spec)))); |
| -- The name of the formal that holds the address of the parameter block |
| -- for the call. |
| |
| Comp : Entity_Id; |
| Decl : Node_Id; |
| Formal : Entity_Id; |
| New_F : Entity_Id; |
| Renamed_Formal : Node_Id; |
| |
| begin |
| Formal := First_Formal (Ent); |
| while Present (Formal) loop |
| Comp := Entry_Component (Formal); |
| New_F := |
| Make_Defining_Identifier (Sloc (Formal), |
| Chars => Chars (Formal)); |
| Set_Etype (New_F, Etype (Formal)); |
| Set_Scope (New_F, Ent); |
| |
| -- Now we set debug info needed on New_F even though it does not come |
| -- from source, so that the debugger will get the right information |
| -- for these generated names. |
| |
| Set_Debug_Info_Needed (New_F); |
| |
| if Ekind (Formal) = E_In_Parameter then |
| Set_Ekind (New_F, E_Constant); |
| else |
| Set_Ekind (New_F, E_Variable); |
| Set_Extra_Constrained (New_F, Extra_Constrained (Formal)); |
| end if; |
| |
| Set_Actual_Subtype (New_F, Actual_Subtype (Formal)); |
| |
| Renamed_Formal := |
| Make_Selected_Component (Loc, |
| Prefix => |
| Unchecked_Convert_To (Entry_Parameters_Type (Ent), |
| Make_Identifier (Loc, Chars (Ptr))), |
| Selector_Name => New_Occurrence_Of (Comp, Loc)); |
| |
| Decl := |
| Build_Renamed_Formal_Declaration |
| (New_F, Formal, Comp, Renamed_Formal); |
| |
| Append (Decl, Decls); |
| Set_Renamed_Object (Formal, New_F); |
| Next_Formal (Formal); |
| end loop; |
| end Add_Formal_Renamings; |
| |
| ------------------------ |
| -- Add_Object_Pointer -- |
| ------------------------ |
| |
| procedure Add_Object_Pointer |
| (Loc : Source_Ptr; |
| Conc_Typ : Entity_Id; |
| Decls : List_Id) |
| is |
| Rec_Typ : constant Entity_Id := Corresponding_Record_Type (Conc_Typ); |
| Decl : Node_Id; |
| Obj_Ptr : Node_Id; |
| |
| begin |
| -- Create the renaming declaration for the Protection object of a |
| -- protected type. _Object is used by Complete_Entry_Body. |
| -- ??? An attempt to make this a renaming was unsuccessful. |
| |
| -- Build the entity for the access type |
| |
| Obj_Ptr := |
| Make_Defining_Identifier (Loc, |
| New_External_Name (Chars (Rec_Typ), 'P')); |
| |
| -- Generate: |
| -- _object : poVP := poVP!O; |
| |
| Decl := |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Make_Defining_Identifier (Loc, Name_uObject), |
| Object_Definition => New_Occurrence_Of (Obj_Ptr, Loc), |
| Expression => |
| Unchecked_Convert_To (Obj_Ptr, Make_Identifier (Loc, Name_uO))); |
| Set_Debug_Info_Needed (Defining_Identifier (Decl)); |
| Prepend_To (Decls, Decl); |
| |
| -- Generate: |
| -- type poVP is access poV; |
| |
| Decl := |
| Make_Full_Type_Declaration (Loc, |
| Defining_Identifier => |
| Obj_Ptr, |
| Type_Definition => |
| Make_Access_To_Object_Definition (Loc, |
| Subtype_Indication => |
| New_Occurrence_Of (Rec_Typ, Loc))); |
| Set_Debug_Info_Needed (Defining_Identifier (Decl)); |
| Prepend_To (Decls, Decl); |
| end Add_Object_Pointer; |
| |
| ----------------------- |
| -- Build_Accept_Body -- |
| ----------------------- |
| |
| function Build_Accept_Body (Astat : Node_Id) return Node_Id is |
| Loc : constant Source_Ptr := Sloc (Astat); |
| Stats : constant Node_Id := Handled_Statement_Sequence (Astat); |
| New_S : Node_Id; |
| Hand : Node_Id; |
| Call : Node_Id; |
| Ohandle : Node_Id; |
| |
| begin |
| -- At the end of the statement sequence, Complete_Rendezvous is called. |
| -- A label skipping the Complete_Rendezvous, and all other accept |
| -- processing, has already been added for the expansion of requeue |
| -- statements. The Sloc is copied from the last statement since it |
| -- is really part of this last statement. |
| |
| Call := |
| Build_Runtime_Call |
| (Sloc (Last (Statements (Stats))), RE_Complete_Rendezvous); |
| Insert_Before (Last (Statements (Stats)), Call); |
| Analyze (Call); |
| |
| -- If exception handlers are present, then append Complete_Rendezvous |
| -- calls to the handlers, and construct the required outer block. As |
| -- above, the Sloc is copied from the last statement in the sequence. |
| |
| if Present (Exception_Handlers (Stats)) then |
| Hand := First (Exception_Handlers (Stats)); |
| while Present (Hand) loop |
| Call := |
| Build_Runtime_Call |
| (Sloc (Last (Statements (Hand))), RE_Complete_Rendezvous); |
| Append (Call, Statements (Hand)); |
| Analyze (Call); |
| Next (Hand); |
| end loop; |
| |
| New_S := |
| Make_Handled_Sequence_Of_Statements (Loc, |
| Statements => New_List ( |
| Make_Block_Statement (Loc, |
| Handled_Statement_Sequence => Stats))); |
| |
| else |
| New_S := Stats; |
| end if; |
| |
| -- At this stage we know that the new statement sequence does |
| -- not have an exception handler part, so we supply one to call |
| -- Exceptional_Complete_Rendezvous. This handler is |
| |
| -- when all others => |
| -- Exceptional_Complete_Rendezvous (Get_GNAT_Exception); |
| |
| -- We handle Abort_Signal to make sure that we properly catch the abort |
| -- case and wake up the caller. |
| |
| Ohandle := Make_Others_Choice (Loc); |
| Set_All_Others (Ohandle); |
| |
| Set_Exception_Handlers (New_S, |
| New_List ( |
| Make_Implicit_Exception_Handler (Loc, |
| Exception_Choices => New_List (Ohandle), |
| |
| Statements => New_List ( |
| Make_Procedure_Call_Statement (Sloc (Stats), |
| Name => New_Occurrence_Of ( |
| RTE (RE_Exceptional_Complete_Rendezvous), Sloc (Stats)), |
| Parameter_Associations => New_List ( |
| Make_Function_Call (Sloc (Stats), |
| Name => |
| New_Occurrence_Of |
| (RTE (RE_Get_GNAT_Exception), Sloc (Stats))))))))); |
| |
| Set_Parent (New_S, Astat); -- temp parent for Analyze call |
| Analyze_Exception_Handlers (Exception_Handlers (New_S)); |
| Expand_Exception_Handlers (New_S); |
| |
| -- Exceptional_Complete_Rendezvous must be called with abort still |
| -- deferred, which is the case for a "when all others" handler. |
| |
| return New_S; |
| end Build_Accept_Body; |
| |
| ----------------------------------- |
| -- Build_Activation_Chain_Entity -- |
| ----------------------------------- |
| |
| procedure Build_Activation_Chain_Entity (N : Node_Id) is |
| function Has_Activation_Chain (Stmt : Node_Id) return Boolean; |
| -- Determine whether an extended return statement has activation chain |
| |
| -------------------------- |
| -- Has_Activation_Chain -- |
| -------------------------- |
| |
| function Has_Activation_Chain (Stmt : Node_Id) return Boolean is |
| Decl : Node_Id; |
| |
| begin |
| Decl := First (Return_Object_Declarations (Stmt)); |
| while Present (Decl) loop |
| if Nkind (Decl) = N_Object_Declaration |
| and then Chars (Defining_Identifier (Decl)) = Name_uChain |
| then |
| return True; |
| end if; |
| |
| Next (Decl); |
| end loop; |
| |
| return False; |
| end Has_Activation_Chain; |
| |
| -- Local variables |
| |
| Context : Node_Id; |
| Context_Id : Entity_Id; |
| Decls : List_Id; |
| |
| -- Start of processing for Build_Activation_Chain_Entity |
| |
| begin |
| -- Activation chain is never used for sequential elaboration policy, see |
| -- comment for Create_Restricted_Task_Sequential in s-tarest.ads). |
| |
| if Partition_Elaboration_Policy = 'S' then |
| return; |
| end if; |
| |
| Find_Enclosing_Context (N, Context, Context_Id, Decls); |
| |
| -- If activation chain entity has not been declared already, create one |
| |
| if Nkind (Context) = N_Extended_Return_Statement |
| or else No (Activation_Chain_Entity (Context)) |
| then |
| -- Since extended return statements do not store the entity of the |
| -- chain, examine the return object declarations to avoid creating |
| -- a duplicate. |
| |
| if Nkind (Context) = N_Extended_Return_Statement |
| and then Has_Activation_Chain (Context) |
| then |
| return; |
| end if; |
| |
| declare |
| Loc : constant Source_Ptr := Sloc (Context); |
| Chain : Entity_Id; |
| Decl : Node_Id; |
| |
| begin |
| Chain := Make_Defining_Identifier (Sloc (N), Name_uChain); |
| |
| -- Note: An extended return statement is not really a task |
| -- activator, but it does have an activation chain on which to |
| -- store the tasks temporarily. On successful return, the tasks |
| -- on this chain are moved to the chain passed in by the caller. |
| -- We do not build an Activation_Chain_Entity for an extended |
| -- return statement, because we do not want to build a call to |
| -- Activate_Tasks. Task activation is the responsibility of the |
| -- caller. |
| |
| if Nkind (Context) /= N_Extended_Return_Statement then |
| Set_Activation_Chain_Entity (Context, Chain); |
| end if; |
| |
| Decl := |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Chain, |
| Aliased_Present => True, |
| Object_Definition => |
| New_Occurrence_Of (RTE (RE_Activation_Chain), Loc)); |
| |
| Prepend_To (Decls, Decl); |
| |
| -- Ensure that _chain appears in the proper scope of the context |
| |
| if Context_Id /= Current_Scope then |
| Push_Scope (Context_Id); |
| Analyze (Decl); |
| Pop_Scope; |
| else |
| Analyze (Decl); |
| end if; |
| end; |
| end if; |
| end Build_Activation_Chain_Entity; |
| |
| ---------------------------- |
| -- Build_Barrier_Function -- |
| ---------------------------- |
| |
| function Build_Barrier_Function |
| (N : Node_Id; |
| Ent : Entity_Id; |
| Pid : Node_Id) return Node_Id |
| is |
| Ent_Formals : constant Node_Id := Entry_Body_Formal_Part (N); |
| Cond : constant Node_Id := Condition (Ent_Formals); |
| Loc : constant Source_Ptr := Sloc (Cond); |
| Func_Id : constant Entity_Id := Barrier_Function (Ent); |
| Op_Decls : constant List_Id := New_List; |
| Stmt : Node_Id; |
| Func_Body : Node_Id; |
| |
| begin |
| -- Add a declaration for the Protection object, renaming declarations |
| -- for the discriminals and privals and finally a declaration for the |
| -- entry family index (if applicable). |
| |
| Install_Private_Data_Declarations (Sloc (N), |
| Spec_Id => Func_Id, |
| Conc_Typ => Pid, |
| Body_Nod => N, |
| Decls => Op_Decls, |
| Barrier => True, |
| Family => Ekind (Ent) = E_Entry_Family); |
| |
| -- If compiling with -fpreserve-control-flow, make sure we insert an |
| -- IF statement so that the back-end knows to generate a conditional |
| -- branch instruction, even if the condition is just the name of a |
| -- boolean object. Note that Expand_N_If_Statement knows to preserve |
| -- such redundant IF statements under -fpreserve-control-flow |
| -- (whether coming from this routine, or directly from source). |
| |
| if Opt.Suppress_Control_Flow_Optimizations then |
| Stmt := Make_Implicit_If_Statement (Cond, |
| Condition => Cond, |
| Then_Statements => New_List ( |
| Make_Simple_Return_Statement (Loc, |
| New_Occurrence_Of (Standard_True, Loc))), |
| Else_Statements => New_List ( |
| Make_Simple_Return_Statement (Loc, |
| New_Occurrence_Of (Standard_False, Loc)))); |
| |
| else |
| Stmt := Make_Simple_Return_Statement (Loc, Cond); |
| end if; |
| |
| -- Note: the condition in the barrier function needs to be properly |
| -- processed for the C/Fortran boolean possibility, but this happens |
| -- automatically since the return statement does this normalization. |
| |
| Func_Body := |
| Make_Subprogram_Body (Loc, |
| Specification => |
| Build_Barrier_Function_Specification (Loc, |
| Make_Defining_Identifier (Loc, Chars (Func_Id))), |
| Declarations => Op_Decls, |
| Handled_Statement_Sequence => |
| Make_Handled_Sequence_Of_Statements (Loc, |
| Statements => New_List (Stmt))); |
| Set_Is_Entry_Barrier_Function (Func_Body); |
| |
| return Func_Body; |
| end Build_Barrier_Function; |
| |
| ------------------------------------------ |
| -- Build_Barrier_Function_Specification -- |
| ------------------------------------------ |
| |
| function Build_Barrier_Function_Specification |
| (Loc : Source_Ptr; |
| Def_Id : Entity_Id) return Node_Id |
| is |
| begin |
| Set_Debug_Info_Needed (Def_Id); |
| |
| return Make_Function_Specification (Loc, |
| Defining_Unit_Name => Def_Id, |
| Parameter_Specifications => New_List ( |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => |
| Make_Defining_Identifier (Loc, Name_uO), |
| Parameter_Type => |
| New_Occurrence_Of (RTE (RE_Address), Loc)), |
| |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => |
| Make_Defining_Identifier (Loc, Name_uE), |
| Parameter_Type => |
| New_Occurrence_Of (RTE (RE_Protected_Entry_Index), Loc))), |
| |
| Result_Definition => New_Occurrence_Of (Standard_Boolean, Loc)); |
| end Build_Barrier_Function_Specification; |
| |
| -------------------------- |
| -- Build_Call_With_Task -- |
| -------------------------- |
| |
| function Build_Call_With_Task |
| (N : Node_Id; |
| E : Entity_Id) return Node_Id |
| is |
| Loc : constant Source_Ptr := Sloc (N); |
| begin |
| return |
| Make_Function_Call (Loc, |
| Name => New_Occurrence_Of (E, Loc), |
| Parameter_Associations => New_List (Concurrent_Ref (N))); |
| end Build_Call_With_Task; |
| |
| ----------------------------- |
| -- Build_Class_Wide_Master -- |
| ----------------------------- |
| |
| procedure Build_Class_Wide_Master (Typ : Entity_Id) is |
| Loc : constant Source_Ptr := Sloc (Typ); |
| Master_Id : Entity_Id; |
| Master_Scope : Entity_Id; |
| Name_Id : Node_Id; |
| Related_Node : Node_Id; |
| Ren_Decl : Node_Id; |
| |
| begin |
| -- Nothing to do if there is no task hierarchy |
| |
| if Restriction_Active (No_Task_Hierarchy) then |
| return; |
| end if; |
| |
| -- Find the declaration that created the access type, which is either a |
| -- type declaration, or an object declaration with an access definition, |
| -- in which case the type is anonymous. |
| |
| if Is_Itype (Typ) then |
| Related_Node := Associated_Node_For_Itype (Typ); |
| else |
| Related_Node := Parent (Typ); |
| end if; |
| |
| Master_Scope := Find_Master_Scope (Typ); |
| |
| -- Nothing to do if the master scope already contains a _master entity. |
| -- The only exception to this is the following scenario: |
| |
| -- Source_Scope |
| -- Transient_Scope_1 |
| -- _master |
| |
| -- Transient_Scope_2 |
| -- use of master |
| |
| -- In this case the source scope is marked as having the master entity |
| -- even though the actual declaration appears inside an inner scope. If |
| -- the second transient scope requires a _master, it cannot use the one |
| -- already declared because the entity is not visible. |
| |
| Name_Id := Make_Identifier (Loc, Name_uMaster); |
| |
| if not Has_Master_Entity (Master_Scope) |
| or else No (Current_Entity_In_Scope (Name_Id)) |
| then |
| declare |
| Master_Decl : Node_Id; |
| begin |
| Set_Has_Master_Entity (Master_Scope); |
| |
| -- Generate: |
| -- _master : constant Integer := Current_Master.all; |
| |
| Master_Decl := |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => |
| Make_Defining_Identifier (Loc, Name_uMaster), |
| Constant_Present => True, |
| Object_Definition => |
| New_Occurrence_Of (Standard_Integer, Loc), |
| Expression => |
| Make_Explicit_Dereference (Loc, |
| New_Occurrence_Of (RTE (RE_Current_Master), Loc))); |
| |
| Insert_Action (Find_Hook_Context (Related_Node), Master_Decl); |
| Analyze (Master_Decl); |
| |
| -- Mark the containing scope as a task master. Masters associated |
| -- with return statements are already marked at this stage (see |
| -- Analyze_Subprogram_Body). |
| |
| if Ekind (Current_Scope) /= E_Return_Statement then |
| declare |
| Par : Node_Id := Related_Node; |
| |
| begin |
| while Nkind (Par) /= N_Compilation_Unit loop |
| Par := Parent (Par); |
| |
| -- If we fall off the top, we are at the outer level, |
| -- and the environment task is our effective master, |
| -- so nothing to mark. |
| |
| if Nkind_In (Par, N_Block_Statement, |
| N_Subprogram_Body, |
| N_Task_Body) |
| then |
| Set_Is_Task_Master (Par); |
| exit; |
| end if; |
| end loop; |
| end; |
| end if; |
| end; |
| end if; |
| |
| Master_Id := |
| Make_Defining_Identifier (Loc, New_External_Name (Chars (Typ), 'M')); |
| |
| -- Generate: |
| -- typeMnn renames _master; |
| |
| Ren_Decl := |
| Make_Object_Renaming_Declaration (Loc, |
| Defining_Identifier => Master_Id, |
| Subtype_Mark => New_Occurrence_Of (Standard_Integer, Loc), |
| Name => Name_Id); |
| |
| Insert_Action (Related_Node, Ren_Decl); |
| |
| Set_Master_Id (Typ, Master_Id); |
| end Build_Class_Wide_Master; |
| |
| -------------------------------- |
| -- Build_Corresponding_Record -- |
| -------------------------------- |
| |
| function Build_Corresponding_Record |
| (N : Node_Id; |
| Ctyp : Entity_Id; |
| Loc : Source_Ptr) return Node_Id |
| is |
| Rec_Ent : constant Entity_Id := |
| Make_Defining_Identifier |
| (Loc, New_External_Name (Chars (Ctyp), 'V')); |
| Disc : Entity_Id; |
| Dlist : List_Id; |
| New_Disc : Entity_Id; |
| Cdecls : List_Id; |
| |
| begin |
| Set_Corresponding_Record_Type (Ctyp, Rec_Ent); |
| Set_Ekind (Rec_Ent, E_Record_Type); |
| Set_Has_Delayed_Freeze (Rec_Ent, Has_Delayed_Freeze (Ctyp)); |
| Set_Is_Concurrent_Record_Type (Rec_Ent, True); |
| Set_Corresponding_Concurrent_Type (Rec_Ent, Ctyp); |
| Set_Stored_Constraint (Rec_Ent, No_Elist); |
| Cdecls := New_List; |
| |
| -- Propagate type invariants to the corresponding record type |
| |
| Set_Has_Invariants (Rec_Ent, Has_Invariants (Ctyp)); |
| Set_Has_Inheritable_Invariants (Rec_Ent, |
| Has_Inheritable_Invariants (Ctyp)); |
| |
| -- Use discriminals to create list of discriminants for record, and |
| -- create new discriminals for use in default expressions, etc. It is |
| -- worth noting that a task discriminant gives rise to 5 entities; |
| |
| -- a) The original discriminant. |
| -- b) The discriminal for use in the task. |
| -- c) The discriminant of the corresponding record. |
| -- d) The discriminal for the init proc of the corresponding record. |
| -- e) The local variable that renames the discriminant in the procedure |
| -- for the task body. |
| |
| -- In fact the discriminals b) are used in the renaming declarations |
| -- for e). See details in einfo (Handling of Discriminants). |
| |
| if Present (Discriminant_Specifications (N)) then |
| Dlist := New_List; |
| Disc := First_Discriminant (Ctyp); |
| |
| while Present (Disc) loop |
| New_Disc := CR_Discriminant (Disc); |
| |
| Append_To (Dlist, |
| Make_Discriminant_Specification (Loc, |
| Defining_Identifier => New_Disc, |
| Discriminant_Type => |
| New_Occurrence_Of (Etype (Disc), Loc), |
| Expression => |
| New_Copy (Discriminant_Default_Value (Disc)))); |
| |
| Next_Discriminant (Disc); |
| end loop; |
| |
| else |
| Dlist := No_List; |
| end if; |
| |
| -- Now we can construct the record type declaration. Note that this |
| -- record is "limited tagged". It is "limited" to reflect the underlying |
| -- limitedness of the task or protected object that it represents, and |
| -- ensuring for example that it is properly passed by reference. It is |
| -- "tagged" to give support to dispatching calls through interfaces. We |
| -- propagate here the list of interfaces covered by the concurrent type |
| -- (Ada 2005: AI-345). |
| |
| return |
| Make_Full_Type_Declaration (Loc, |
| Defining_Identifier => Rec_Ent, |
| Discriminant_Specifications => Dlist, |
| Type_Definition => |
| Make_Record_Definition (Loc, |
| Component_List => |
| Make_Component_List (Loc, Component_Items => Cdecls), |
| Tagged_Present => |
| Ada_Version >= Ada_2005 and then Is_Tagged_Type (Ctyp), |
| Interface_List => Interface_List (N), |
| Limited_Present => True)); |
| end Build_Corresponding_Record; |
| |
| --------------------------------- |
| -- Build_Dispatching_Tag_Check -- |
| --------------------------------- |
| |
| function Build_Dispatching_Tag_Check |
| (K : Entity_Id; |
| N : Node_Id) return Node_Id |
| is |
| Loc : constant Source_Ptr := Sloc (N); |
| |
| begin |
| return |
| Make_Op_Or (Loc, |
| Make_Op_Eq (Loc, |
| Left_Opnd => |
| New_Occurrence_Of (K, Loc), |
| Right_Opnd => |
| New_Occurrence_Of (RTE (RE_TK_Limited_Tagged), Loc)), |
| |
| Make_Op_Eq (Loc, |
| Left_Opnd => |
| New_Occurrence_Of (K, Loc), |
| Right_Opnd => |
| New_Occurrence_Of (RTE (RE_TK_Tagged), Loc))); |
| end Build_Dispatching_Tag_Check; |
| |
| ---------------------------------- |
| -- Build_Entry_Count_Expression -- |
| ---------------------------------- |
| |
| function Build_Entry_Count_Expression |
| (Concurrent_Type : Node_Id; |
| Component_List : List_Id; |
| Loc : Source_Ptr) return Node_Id |
| is |
| Eindx : Nat; |
| Ent : Entity_Id; |
| Ecount : Node_Id; |
| Comp : Node_Id; |
| Lo : Node_Id; |
| Hi : Node_Id; |
| Typ : Entity_Id; |
| Large : Boolean; |
| |
| begin |
| -- Count number of non-family entries |
| |
| Eindx := 0; |
| Ent := First_Entity (Concurrent_Type); |
| while Present (Ent) loop |
| if Ekind (Ent) = E_Entry then |
| Eindx := Eindx + 1; |
| end if; |
| |
| Next_Entity (Ent); |
| end loop; |
| |
| Ecount := Make_Integer_Literal (Loc, Eindx); |
| |
| -- Loop through entry families building the addition nodes |
| |
| Ent := First_Entity (Concurrent_Type); |
| Comp := First (Component_List); |
| while Present (Ent) loop |
| if Ekind (Ent) = E_Entry_Family then |
| while Chars (Ent) /= Chars (Defining_Identifier (Comp)) loop |
| Next (Comp); |
| end loop; |
| |
| Typ := Etype (Discrete_Subtype_Definition (Parent (Ent))); |
| Hi := Type_High_Bound (Typ); |
| Lo := Type_Low_Bound (Typ); |
| Large := Is_Potentially_Large_Family |
| (Base_Type (Typ), Concurrent_Type, Lo, Hi); |
| Ecount := |
| Make_Op_Add (Loc, |
| Left_Opnd => Ecount, |
| Right_Opnd => |
| Family_Size (Loc, Hi, Lo, Concurrent_Type, Large)); |
| end if; |
| |
| Next_Entity (Ent); |
| end loop; |
| |
| return Ecount; |
| end Build_Entry_Count_Expression; |
| |
| ----------------------- |
| -- Build_Entry_Names -- |
| ----------------------- |
| |
| procedure Build_Entry_Names |
| (Obj_Ref : Node_Id; |
| Obj_Typ : Entity_Id; |
| Stmts : List_Id) |
| is |
| Loc : constant Source_Ptr := Sloc (Obj_Ref); |
| Data : Entity_Id := Empty; |
| Index : Entity_Id := Empty; |
| Typ : Entity_Id := Obj_Typ; |
| |
| procedure Build_Entry_Name (Comp_Id : Entity_Id); |
| -- Given an entry [family], create a static string which denotes the |
| -- name of Comp_Id and assign it to the underlying data structure which |
| -- contains the entry names of a concurrent object. |
| |
| function Object_Reference return Node_Id; |
| -- Return a reference to field _object or _task_id depending on the |
| -- concurrent object being processed. |
| |
| ---------------------- |
| -- Build_Entry_Name -- |
| ---------------------- |
| |
| procedure Build_Entry_Name (Comp_Id : Entity_Id) is |
| function Build_Range (Def : Node_Id) return Node_Id; |
| -- Given a discrete subtype definition of an entry family, generate a |
| -- range node which covers the range of Def's type. |
| |
| procedure Create_Index_And_Data; |
| -- Generate the declarations of variables Index and Data. Subsequent |
| -- calls do nothing. |
| |
| function Increment_Index return Node_Id; |
| -- Increment the index used in the assignment of string names to the |
| -- Data array. |
| |
| function Name_Declaration (Def_Id : Entity_Id) return Node_Id; |
| -- Given the name of a temporary variable, create the following |
| -- declaration for it: |
| -- |
| -- Def_Id : aliased constant String := <String_Name_From_Buffer>; |
| |
| function Set_Entry_Name (Def_Id : Entity_Id) return Node_Id; |
| -- Given the name of a temporary variable, place it in the array of |
| -- string names. Generate: |
| -- |
| -- Data (Index) := Def_Id'Unchecked_Access; |
| |
| ----------------- |
| -- Build_Range -- |
| ----------------- |
| |
| function Build_Range (Def : Node_Id) return Node_Id is |
| High : Node_Id := Type_High_Bound (Etype (Def)); |
| Low : Node_Id := Type_Low_Bound (Etype (Def)); |
| |
| begin |
| -- If a bound references a discriminant, generate an identifier |
| -- with the same name. Resolution will map it to the formals of |
| -- the init proc. |
| |
| if Is_Entity_Name (Low) |
| and then Ekind (Entity (Low)) = E_Discriminant |
| then |
| Low := |
| Make_Selected_Component (Loc, |
| Prefix => New_Copy_Tree (Obj_Ref), |
| Selector_Name => Make_Identifier (Loc, Chars (Low))); |
| else |
| Low := New_Copy_Tree (Low); |
| end if; |
| |
| if Is_Entity_Name (High) |
| and then Ekind (Entity (High)) = E_Discriminant |
| then |
| High := |
| Make_Selected_Component (Loc, |
| Prefix => New_Copy_Tree (Obj_Ref), |
| Selector_Name => Make_Identifier (Loc, Chars (High))); |
| else |
| High := New_Copy_Tree (High); |
| end if; |
| |
| return |
| Make_Range (Loc, |
| Low_Bound => Low, |
| High_Bound => High); |
| end Build_Range; |
| |
| --------------------------- |
| -- Create_Index_And_Data -- |
| --------------------------- |
| |
| procedure Create_Index_And_Data is |
| begin |
| if No (Index) and then No (Data) then |
| declare |
| Count : RE_Id; |
| Data_Typ : RE_Id; |
| Size : Entity_Id; |
| |
| begin |
| if Is_Protected_Type (Typ) then |
| Count := RO_PE_Number_Of_Entries; |
| Data_Typ := RE_Protected_Entry_Names_Array; |
| else |
| Count := RO_ST_Number_Of_Entries; |
| Data_Typ := RE_Task_Entry_Names_Array; |
| end if; |
| |
| -- Step 1: Generate the declaration of the index variable: |
| |
| -- Index : Entry_Index := 1; |
| |
| Index := Make_Temporary (Loc, 'I'); |
| |
| Append_To (Stmts, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Index, |
| Object_Definition => |
| New_Occurrence_Of (RTE (RE_Entry_Index), Loc), |
| Expression => Make_Integer_Literal (Loc, 1))); |
| |
| -- Step 2: Generate the declaration of an array to house all |
| -- names: |
| |
| -- Size : constant Entry_Index := <Count> (Obj_Ref); |
| -- Data : aliased <Data_Typ> := (1 .. Size => null); |
| |
| Size := Make_Temporary (Loc, 'S'); |
| |
| Append_To (Stmts, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Size, |
| Constant_Present => True, |
| Object_Definition => |
| New_Occurrence_Of (RTE (RE_Entry_Index), Loc), |
| Expression => |
| Make_Function_Call (Loc, |
| Name => |
| New_Occurrence_Of (RTE (Count), Loc), |
| Parameter_Associations => |
| New_List (Object_Reference)))); |
| |
| Data := Make_Temporary (Loc, 'A'); |
| |
| Append_To (Stmts, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Data, |
| Aliased_Present => True, |
| Object_Definition => |
| New_Occurrence_Of (RTE (Data_Typ), Loc), |
| Expression => |
| Make_Aggregate (Loc, |
| Component_Associations => New_List ( |
| Make_Component_Association (Loc, |
| Choices => New_List ( |
| Make_Range (Loc, |
| Low_Bound => |
| Make_Integer_Literal (Loc, 1), |
| High_Bound => |
| New_Occurrence_Of (Size, Loc))), |
| Expression => Make_Null (Loc)))))); |
| end; |
| end if; |
| end Create_Index_And_Data; |
| |
| --------------------- |
| -- Increment_Index -- |
| --------------------- |
| |
| function Increment_Index return Node_Id is |
| begin |
| return |
| Make_Assignment_Statement (Loc, |
| Name => New_Occurrence_Of (Index, Loc), |
| Expression => |
| Make_Op_Add (Loc, |
| Left_Opnd => New_Occurrence_Of (Index, Loc), |
| Right_Opnd => Make_Integer_Literal (Loc, 1))); |
| end Increment_Index; |
| |
| ---------------------- |
| -- Name_Declaration -- |
| ---------------------- |
| |
| function Name_Declaration (Def_Id : Entity_Id) return Node_Id is |
| begin |
| return |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Def_Id, |
| Aliased_Present => True, |
| Constant_Present => True, |
| Object_Definition => |
| New_Occurrence_Of (Standard_String, Loc), |
| Expression => |
| Make_String_Literal (Loc, String_From_Name_Buffer)); |
| end Name_Declaration; |
| |
| -------------------- |
| -- Set_Entry_Name -- |
| -------------------- |
| |
| function Set_Entry_Name (Def_Id : Entity_Id) return Node_Id is |
| begin |
| return |
| Make_Assignment_Statement (Loc, |
| Name => |
| Make_Indexed_Component (Loc, |
| Prefix => New_Occurrence_Of (Data, Loc), |
| Expressions => New_List (New_Occurrence_Of (Index, Loc))), |
| |
| Expression => |
| Make_Attribute_Reference (Loc, |
| Prefix => New_Occurrence_Of (Def_Id, Loc), |
| Attribute_Name => Name_Unchecked_Access)); |
| end Set_Entry_Name; |
| |
| -- Local variables |
| |
| Temp_Id : Entity_Id; |
| Subt_Def : Node_Id; |
| |
| -- Start of processing for Build_Entry_Name |
| |
| begin |
| if Ekind (Comp_Id) = E_Entry_Family then |
| Subt_Def := Discrete_Subtype_Definition (Parent (Comp_Id)); |
| |
| Create_Index_And_Data; |
| |
| -- Step 1: Create the string name of the entry family. |
| -- Generate: |
| -- Temp : aliased constant String := "name ()"; |
| |
| Temp_Id := Make_Temporary (Loc, 'S'); |
| Get_Name_String (Chars (Comp_Id)); |
| Add_Char_To_Name_Buffer (' '); |
| Add_Char_To_Name_Buffer ('('); |
| Add_Char_To_Name_Buffer (')'); |
| |
| Append_To (Stmts, Name_Declaration (Temp_Id)); |
| |
| -- Generate: |
| -- for Member in Family_Low .. Family_High loop |
| -- Set_Entry_Name (...); |
| -- Index := Index + 1; |
| -- end loop; |
| |
| Append_To (Stmts, |
| Make_Loop_Statement (Loc, |
| Iteration_Scheme => |
| Make_Iteration_Scheme (Loc, |
| Loop_Parameter_Specification => |
| Make_Loop_Parameter_Specification (Loc, |
| Defining_Identifier => |
| Make_Temporary (Loc, 'L'), |
| Discrete_Subtype_Definition => |
| Build_Range (Subt_Def))), |
| |
| Statements => New_List ( |
| Set_Entry_Name (Temp_Id), |
| Increment_Index), |
| End_Label => Empty)); |
| |
| -- Entry |
| |
| else |
| Create_Index_And_Data; |
| |
| -- Step 1: Create the string name of the entry. Generate: |
| -- Temp : aliased constant String := "name"; |
| |
| Temp_Id := Make_Temporary (Loc, 'S'); |
| Get_Name_String (Chars (Comp_Id)); |
| |
| Append_To (Stmts, Name_Declaration (Temp_Id)); |
| |
| -- Step 2: Associate the string name with the underlying data |
| -- structure. |
| |
| Append_To (Stmts, Set_Entry_Name (Temp_Id)); |
| Append_To (Stmts, Increment_Index); |
| end if; |
| end Build_Entry_Name; |
| |
| ---------------------- |
| -- Object_Reference -- |
| ---------------------- |
| |
| function Object_Reference return Node_Id is |
| Conc_Typ : constant Entity_Id := Corresponding_Record_Type (Typ); |
| Field : Name_Id; |
| Ref : Node_Id; |
| |
| begin |
| if Is_Protected_Type (Typ) then |
| Field := Name_uObject; |
| else |
| Field := Name_uTask_Id; |
| end if; |
| |
| Ref := |
| Make_Selected_Component (Loc, |
| Prefix => |
| Unchecked_Convert_To (Conc_Typ, New_Copy_Tree (Obj_Ref)), |
| Selector_Name => Make_Identifier (Loc, Field)); |
| |
| if Is_Protected_Type (Typ) then |
| Ref := |
| Make_Attribute_Reference (Loc, |
| Prefix => Ref, |
| Attribute_Name => Name_Unchecked_Access); |
| end if; |
| |
| return Ref; |
| end Object_Reference; |
| |
| -- Local variables |
| |
| Comp : Node_Id; |
| Proc : RE_Id; |
| |
| -- Start of processing for Build_Entry_Names |
| |
| begin |
| -- Retrieve the original concurrent type |
| |
| if Is_Concurrent_Record_Type (Typ) then |
| Typ := Corresponding_Concurrent_Type (Typ); |
| end if; |
| |
| pragma Assert (Is_Concurrent_Type (Typ)); |
| |
| -- Nothing to do if the type has no entries |
| |
| if not Has_Entries (Typ) then |
| return; |
| end if; |
| |
| -- Avoid generating entry names for a protected type with only one entry |
| |
| if Is_Protected_Type (Typ) |
| and then Find_Protection_Type (Base_Type (Typ)) /= |
| RTE (RE_Protection_Entries) |
| then |
| return; |
| end if; |
| |
| -- Step 1: Populate the array with statically generated strings denoting |
| -- entries and entry family names. |
| |
| Comp := First_Entity (Typ); |
| while Present (Comp) loop |
| if Comes_From_Source (Comp) |
| and then Ekind_In (Comp, E_Entry, E_Entry_Family) |
| then |
| Build_Entry_Name (Comp); |
| end if; |
| |
| Next_Entity (Comp); |
| end loop; |
| |
| -- Step 2: Associate the array with the related concurrent object: |
| |
| -- Set_Entry_Names (Obj_Ref, <Data>'Unchecked_Access); |
| |
| if Present (Data) then |
| if Is_Protected_Type (Typ) then |
| Proc := RO_PE_Set_Entry_Names; |
| else |
| Proc := RO_ST_Set_Entry_Names; |
| end if; |
| |
| Append_To (Stmts, |
| Make_Procedure_Call_Statement (Loc, |
| Name => New_Occurrence_Of (RTE (Proc), Loc), |
| Parameter_Associations => New_List ( |
| Object_Reference, |
| Make_Attribute_Reference (Loc, |
| Prefix => New_Occurrence_Of (Data, Loc), |
| Attribute_Name => Name_Unchecked_Access)))); |
| end if; |
| end Build_Entry_Names; |
| |
| --------------------------- |
| -- Build_Parameter_Block -- |
| --------------------------- |
| |
| function Build_Parameter_Block |
| (Loc : Source_Ptr; |
| Actuals : List_Id; |
| Formals : List_Id; |
| Decls : List_Id) return Entity_Id |
| is |
| Actual : Entity_Id; |
| Comp_Nam : Node_Id; |
| Comps : List_Id; |
| Formal : Entity_Id; |
| Has_Comp : Boolean := False; |
| Rec_Nam : Node_Id; |
| |
| begin |
| Actual := First (Actuals); |
| Comps := New_List; |
| Formal := Defining_Identifier (First (Formals)); |
| |
| while Present (Actual) loop |
| if not Is_Controlling_Actual (Actual) then |
| |
| -- Generate: |
| -- type Ann is access all <actual-type> |
| |
| Comp_Nam := Make_Temporary (Loc, 'A'); |
| |
| Append_To (Decls, |
| Make_Full_Type_Declaration (Loc, |
| Defining_Identifier => Comp_Nam, |
| Type_Definition => |
| Make_Access_To_Object_Definition (Loc, |
| All_Present => True, |
| Constant_Present => Ekind (Formal) = E_In_Parameter, |
| Subtype_Indication => |
| New_Occurrence_Of (Etype (Actual), Loc)))); |
| |
| -- Generate: |
| -- Param : Ann; |
| |
| Append_To (Comps, |
| Make_Component_Declaration (Loc, |
| Defining_Identifier => |
| Make_Defining_Identifier (Loc, Chars (Formal)), |
| Component_Definition => |
| Make_Component_Definition (Loc, |
| Aliased_Present => |
| False, |
| Subtype_Indication => |
| New_Occurrence_Of (Comp_Nam, Loc)))); |
| |
| Has_Comp := True; |
| end if; |
| |
| Next_Actual (Actual); |
| Next_Formal_With_Extras (Formal); |
| end loop; |
| |
| Rec_Nam := Make_Temporary (Loc, 'P'); |
| |
| if Has_Comp then |
| |
| -- Generate: |
| -- type Pnn is record |
| -- Param1 : Ann1; |
| -- ... |
| -- ParamN : AnnN; |
| |
| -- where Pnn is a parameter wrapping record, Param1 .. ParamN are |
| -- the original parameter names and Ann1 .. AnnN are the access to |
| -- actual types. |
| |
| Append_To (Decls, |
| Make_Full_Type_Declaration (Loc, |
| Defining_Identifier => |
| Rec_Nam, |
| Type_Definition => |
| Make_Record_Definition (Loc, |
| Component_List => |
| Make_Component_List (Loc, Comps)))); |
| else |
| -- Generate: |
| -- type Pnn is null record; |
| |
| Append_To (Decls, |
| Make_Full_Type_Declaration (Loc, |
| Defining_Identifier => |
| Rec_Nam, |
| Type_Definition => |
| Make_Record_Definition (Loc, |
| Null_Present => True, |
| Component_List => Empty))); |
| end if; |
| |
| return Rec_Nam; |
| end Build_Parameter_Block; |
| |
| -------------------------------------- |
| -- Build_Renamed_Formal_Declaration -- |
| -------------------------------------- |
| |
| function Build_Renamed_Formal_Declaration |
| (New_F : Entity_Id; |
| Formal : Entity_Id; |
| Comp : Entity_Id; |
| Renamed_Formal : Node_Id) return Node_Id |
| is |
| Loc : constant Source_Ptr := Sloc (New_F); |
| Decl : Node_Id; |
| |
| begin |
| -- If the formal is a tagged incomplete type, it is already passed |
| -- by reference, so it is sufficient to rename the pointer component |
| -- that corresponds to the actual. Otherwise we need to dereference |
| -- the pointer component to obtain the actual. |
| |
| if Is_Incomplete_Type (Etype (Formal)) |
| and then Is_Tagged_Type (Etype (Formal)) |
| then |
| Decl := |
| Make_Object_Renaming_Declaration (Loc, |
| Defining_Identifier => New_F, |
| Subtype_Mark => New_Occurrence_Of (Etype (Comp), Loc), |
| Name => Renamed_Formal); |
| |
| else |
| Decl := |
| Make_Object_Renaming_Declaration (Loc, |
| Defining_Identifier => New_F, |
| Subtype_Mark => New_Occurrence_Of (Etype (Formal), Loc), |
| Name => |
| Make_Explicit_Dereference (Loc, Renamed_Formal)); |
| end if; |
| |
| return Decl; |
| end Build_Renamed_Formal_Declaration; |
| |
| ----------------------- |
| -- Build_PPC_Wrapper -- |
| ----------------------- |
| |
| procedure Build_PPC_Wrapper (E : Entity_Id; Decl : Node_Id) is |
| Items : constant Node_Id := Contract (E); |
| Loc : constant Source_Ptr := Sloc (E); |
| Synch_Type : constant Entity_Id := Scope (E); |
| Actuals : List_Id; |
| Decls : List_Id; |
| Entry_Call : Node_Id; |
| Entry_Name : Node_Id; |
| Params : List_Id; |
| Prag : Node_Id; |
| Synch_Id : Entity_Id; |
| Wrapper_Id : Entity_Id; |
| |
| begin |
| -- Only build the wrapper if entry has pre/postconditions |
| -- Should this be done unconditionally instead ??? |
| |
| if Present (Items) then |
| Prag := Pre_Post_Conditions (Items); |
| |
| if No (Prag) then |
| return; |
| end if; |
| |
| -- Transfer ppc pragmas to the declarations of the wrapper |
| |
| Decls := New_List; |
| |
| while Present (Prag) loop |
| if Nam_In (Pragma_Name (Prag), Name_Precondition, |
| Name_Postcondition) |
| then |
| Append (Relocate_Node (Prag), Decls); |
| Set_Analyzed (Last (Decls), False); |
| end if; |
| |
| Prag := Next_Pragma (Prag); |
| end loop; |
| else |
| return; |
| end if; |
| |
| Actuals := New_List; |
| Synch_Id := |
| Make_Defining_Identifier (Loc, |
| Chars => New_External_Name (Chars (Scope (E)), 'A')); |
| |
| -- First formal is synchronized object |
| |
| Params := New_List ( |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => Synch_Id, |
| Out_Present => True, |
| In_Present => True, |
| Parameter_Type => New_Occurrence_Of (Scope (E), Loc))); |
| |
| Entry_Name := |
| Make_Selected_Component (Loc, |
| Prefix => New_Occurrence_Of (Synch_Id, Loc), |
| Selector_Name => New_Occurrence_Of (E, Loc)); |
| |
| -- If entity is entry family, second formal is the corresponding index, |
| -- and entry name is an indexed component. |
| |
| if Ekind (E) = E_Entry_Family then |
| declare |
| Index : constant Entity_Id := |
| Make_Defining_Identifier (Loc, Name_I); |
| begin |
| Append_To (Params, |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => Index, |
| Parameter_Type => |
| New_Occurrence_Of (Entry_Index_Type (E), Loc))); |
| |
| Entry_Name := |
| Make_Indexed_Component (Loc, |
| Prefix => Entry_Name, |
| Expressions => New_List (New_Occurrence_Of (Index, Loc))); |
| end; |
| end if; |
| |
| Entry_Call := |
| Make_Procedure_Call_Statement (Loc, |
| Name => Entry_Name, |
| Parameter_Associations => Actuals); |
| |
| -- Now add formals that match those of the entry, and build actuals for |
| -- the nested entry call. |
| |
| declare |
| Form : Entity_Id; |
| New_Form : Entity_Id; |
| Parm_Spec : Node_Id; |
| |
| begin |
| Form := First_Formal (E); |
| while Present (Form) loop |
| New_Form := Make_Defining_Identifier (Loc, Chars (Form)); |
| Parm_Spec := |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => New_Form, |
| Out_Present => Out_Present (Parent (Form)), |
| In_Present => In_Present (Parent (Form)), |
| Parameter_Type => New_Occurrence_Of (Etype (Form), Loc)); |
| |
| Append (Parm_Spec, Params); |
| Append (New_Occurrence_Of (New_Form, Loc), Actuals); |
| Next_Formal (Form); |
| end loop; |
| end; |
| |
| -- Add renaming declarations for the discriminants of the enclosing |
| -- type, which may be visible in the preconditions. |
| |
| if Has_Discriminants (Synch_Type) then |
| declare |
| D : Entity_Id; |
| Decl : Node_Id; |
| |
| begin |
| D := First_Discriminant (Synch_Type); |
| while Present (D) loop |
| Decl := |
| Make_Object_Renaming_Declaration (Loc, |
| Defining_Identifier => |
| Make_Defining_Identifier (Loc, Chars (D)), |
| Subtype_Mark => New_Occurrence_Of (Etype (D), Loc), |
| Name => |
| Make_Selected_Component (Loc, |
| Prefix => New_Occurrence_Of (Synch_Id, Loc), |
| Selector_Name => Make_Identifier (Loc, Chars (D)))); |
| Prepend (Decl, Decls); |
| Next_Discriminant (D); |
| end loop; |
| end; |
| end if; |
| |
| Wrapper_Id := |
| Make_Defining_Identifier (Loc, New_External_Name (Chars (E), 'E')); |
| Set_PPC_Wrapper (E, Wrapper_Id); |
| |
| -- The wrapper body is analyzed when the enclosing type is frozen |
| |
| Append_Freeze_Action (Defining_Entity (Decl), |
| Make_Subprogram_Body (Loc, |
| Specification => |
| Make_Procedure_Specification (Loc, |
| Defining_Unit_Name => Wrapper_Id, |
| Parameter_Specifications => Params), |
| Declarations => Decls, |
| Handled_Statement_Sequence => |
| Make_Handled_Sequence_Of_Statements (Loc, |
| Statements => New_List (Entry_Call)))); |
| end Build_PPC_Wrapper; |
| |
| -------------------------- |
| -- Build_Wrapper_Bodies -- |
| -------------------------- |
| |
| procedure Build_Wrapper_Bodies |
| (Loc : Source_Ptr; |
| Typ : Entity_Id; |
| N : Node_Id) |
| is |
| Rec_Typ : Entity_Id; |
| |
| function Build_Wrapper_Body |
| (Loc : Source_Ptr; |
| Subp_Id : Entity_Id; |
| Obj_Typ : Entity_Id; |
| Formals : List_Id) return Node_Id; |
| -- Ada 2005 (AI-345): Build the body that wraps a primitive operation |
| -- associated with a protected or task type. Subp_Id is the subprogram |
| -- name which will be wrapped. Obj_Typ is the type of the new formal |
| -- parameter which handles dispatching and object notation. Formals are |
| -- the original formals of Subp_Id which will be explicitly replicated. |
| |
| ------------------------ |
| -- Build_Wrapper_Body -- |
| ------------------------ |
| |
| function Build_Wrapper_Body |
| (Loc : Source_Ptr; |
| Subp_Id : Entity_Id; |
| Obj_Typ : Entity_Id; |
| Formals : List_Id) return Node_Id |
| is |
| Body_Spec : Node_Id; |
| |
| begin |
| Body_Spec := Build_Wrapper_Spec (Subp_Id, Obj_Typ, Formals); |
| |
| -- The subprogram is not overriding or is not a primitive declared |
| -- between two views. |
| |
| if No (Body_Spec) then |
| return Empty; |
| end if; |
| |
| declare |
| Actuals : List_Id := No_List; |
| Conv_Id : Node_Id; |
| First_Form : Node_Id; |
| Formal : Node_Id; |
| Nam : Node_Id; |
| |
| begin |
| -- Map formals to actuals. Use the list built for the wrapper |
| -- spec, skipping the object notation parameter. |
| |
| First_Form := First (Parameter_Specifications (Body_Spec)); |
| |
| Formal := First_Form; |
| Next (Formal); |
| |
| if Present (Formal) then |
| Actuals := New_List; |
| while Present (Formal) loop |
| Append_To (Actuals, |
| Make_Identifier (Loc, |
| Chars => Chars (Defining_Identifier (Formal)))); |
| Next (Formal); |
| end loop; |
| end if; |
| |
| -- Special processing for primitives declared between a private |
| -- type and its completion: the wrapper needs a properly typed |
| -- parameter if the wrapped operation has a controlling first |
| -- parameter. Note that this might not be the case for a function |
| -- with a controlling result. |
| |
| if Is_Private_Primitive_Subprogram (Subp_Id) then |
| if No (Actuals) then |
| Actuals := New_List; |
| end if; |
| |
| if Is_Controlling_Formal (First_Formal (Subp_Id)) then |
| Prepend_To (Actuals, |
| Unchecked_Convert_To |
| (Corresponding_Concurrent_Type (Obj_Typ), |
| Make_Identifier (Loc, Name_uO))); |
| |
| else |
| Prepend_To (Actuals, |
| Make_Identifier (Loc, |
| Chars => Chars (Defining_Identifier (First_Form)))); |
| end if; |
| |
| Nam := New_Occurrence_Of (Subp_Id, Loc); |
| else |
| -- An access-to-variable object parameter requires an explicit |
| -- dereference in the unchecked conversion. This case occurs |
| -- when a protected entry wrapper must override an interface |
| -- level procedure with interface access as first parameter. |
| |
| -- O.all.Subp_Id (Formal_1, ..., Formal_N) |
| |
| if Nkind (Parameter_Type (First_Form)) = |
| N_Access_Definition |
| then |
| Conv_Id := |
| Make_Explicit_Dereference (Loc, |
| Prefix => Make_Identifier (Loc, Name_uO)); |
| else |
| Conv_Id := Make_Identifier (Loc, Name_uO); |
| end if; |
| |
| Nam := |
| Make_Selected_Component (Loc, |
| Prefix => |
| Unchecked_Convert_To |
| (Corresponding_Concurrent_Type (Obj_Typ), Conv_Id), |
| Selector_Name => New_Occurrence_Of (Subp_Id, Loc)); |
| end if; |
| |
| -- Create the subprogram body. For a function, the call to the |
| -- actual subprogram has to be converted to the corresponding |
| -- record if it is a controlling result. |
| |
| if Ekind (Subp_Id) = E_Function then |
| declare |
| Res : Node_Id; |
| |
| begin |
| Res := |
| Make_Function_Call (Loc, |
| Name => Nam, |
| Parameter_Associations => Actuals); |
| |
| if Has_Controlling_Result (Subp_Id) then |
| Res := |
| Unchecked_Convert_To |
| (Corresponding_Record_Type (Etype (Subp_Id)), Res); |
| end if; |
| |
| return |
| Make_Subprogram_Body (Loc, |
| Specification => Body_Spec, |
| Declarations => Empty_List, |
| Handled_Statement_Sequence => |
| Make_Handled_Sequence_Of_Statements (Loc, |
| Statements => New_List ( |
| Make_Simple_Return_Statement (Loc, Res)))); |
| end; |
| |
| else |
| return |
| Make_Subprogram_Body (Loc, |
| Specification => Body_Spec, |
| Declarations => Empty_List, |
| Handled_Statement_Sequence => |
| Make_Handled_Sequence_Of_Statements (Loc, |
| Statements => New_List ( |
| Make_Procedure_Call_Statement (Loc, |
| Name => Nam, |
| Parameter_Associations => Actuals)))); |
| end if; |
| end; |
| end Build_Wrapper_Body; |
| |
| -- Start of processing for Build_Wrapper_Bodies |
| |
| begin |
| if Is_Concurrent_Type (Typ) then |
| Rec_Typ := Corresponding_Record_Type (Typ); |
| else |
| Rec_Typ := Typ; |
| end if; |
| |
| -- Generate wrapper bodies for a concurrent type which implements an |
| -- interface. |
| |
| if Present (Interfaces (Rec_Typ)) then |
| declare |
| Insert_Nod : Node_Id; |
| Prim : Entity_Id; |
| Prim_Elmt : Elmt_Id; |
| Prim_Decl : Node_Id; |
| Subp : Entity_Id; |
| Wrap_Body : Node_Id; |
| Wrap_Id : Entity_Id; |
| |
| begin |
| Insert_Nod := N; |
| |
| -- Examine all primitive operations of the corresponding record |
| -- type, looking for wrapper specs. Generate bodies in order to |
| -- complete them. |
| |
| Prim_Elmt := First_Elmt (Primitive_Operations (Rec_Typ)); |
| while Present (Prim_Elmt) loop |
| Prim := Node (Prim_Elmt); |
| |
| if (Ekind (Prim) = E_Function |
| or else Ekind (Prim) = E_Procedure) |
| and then Is_Primitive_Wrapper (Prim) |
| then |
| Subp := Wrapped_Entity (Prim); |
| Prim_Decl := Parent (Parent (Prim)); |
| |
| Wrap_Body := |
| Build_Wrapper_Body (Loc, |
| Subp_Id => Subp, |
| Obj_Typ => Rec_Typ, |
| Formals => Parameter_Specifications (Parent (Subp))); |
| Wrap_Id := Defining_Unit_Name (Specification (Wrap_Body)); |
| |
| Set_Corresponding_Spec (Wrap_Body, Prim); |
| Set_Corresponding_Body (Prim_Decl, Wrap_Id); |
| |
| Insert_After (Insert_Nod, Wrap_Body); |
| Insert_Nod := Wrap_Body; |
| |
| Analyze (Wrap_Body); |
| end if; |
| |
| Next_Elmt (Prim_Elmt); |
| end loop; |
| end; |
| end if; |
| end Build_Wrapper_Bodies; |
| |
| ------------------------ |
| -- Build_Wrapper_Spec -- |
| ------------------------ |
| |
| function Build_Wrapper_Spec |
| (Subp_Id : Entity_Id; |
| Obj_Typ : Entity_Id; |
| Formals : List_Id) return Node_Id |
| is |
| Loc : constant Source_Ptr := Sloc (Subp_Id); |
| First_Param : Node_Id; |
| Iface : Entity_Id; |
| Iface_Elmt : Elmt_Id; |
| Iface_Op : Entity_Id; |
| Iface_Op_Elmt : Elmt_Id; |
| |
| function Overriding_Possible |
| (Iface_Op : Entity_Id; |
| Wrapper : Entity_Id) return Boolean; |
| -- Determine whether a primitive operation can be overridden by Wrapper. |
| -- Iface_Op is the candidate primitive operation of an interface type, |
| -- Wrapper is the generated entry wrapper. |
| |
| function Replicate_Formals |
| (Loc : Source_Ptr; |
| Formals : List_Id) return List_Id; |
| -- An explicit parameter replication is required due to the Is_Entry_ |
| -- Formal flag being set for all the formals of an entry. The explicit |
| -- replication removes the flag that would otherwise cause a different |
| -- path of analysis. |
| |
| ------------------------- |
| -- Overriding_Possible -- |
| ------------------------- |
| |
| function Overriding_Possible |
| (Iface_Op : Entity_Id; |
| Wrapper : Entity_Id) return Boolean |
| is |
| Iface_Op_Spec : constant Node_Id := Parent (Iface_Op); |
| Wrapper_Spec : constant Node_Id := Parent (Wrapper); |
| |
| function Type_Conformant_Parameters |
| (Iface_Op_Params : List_Id; |
| Wrapper_Params : List_Id) return Boolean; |
| -- Determine whether the parameters of the generated entry wrapper |
| -- and those of a primitive operation are type conformant. During |
| -- this check, the first parameter of the primitive operation is |
| -- skipped if it is a controlling argument: protected functions |
| -- may have a controlling result. |
| |
| -------------------------------- |
| -- Type_Conformant_Parameters -- |
| -------------------------------- |
| |
| function Type_Conformant_Parameters |
| (Iface_Op_Params : List_Id; |
| Wrapper_Params : List_Id) return Boolean |
| is |
| Iface_Op_Param : Node_Id; |
| Iface_Op_Typ : Entity_Id; |
| Wrapper_Param : Node_Id; |
| Wrapper_Typ : Entity_Id; |
| |
| begin |
| -- Skip the first (controlling) parameter of primitive operation |
| |
| Iface_Op_Param := First (Iface_Op_Params); |
| |
| if Present (First_Formal (Iface_Op)) |
| and then Is_Controlling_Formal (First_Formal (Iface_Op)) |
| then |
| Iface_Op_Param := Next (Iface_Op_Param); |
| end if; |
| |
| Wrapper_Param := First (Wrapper_Params); |
| while Present (Iface_Op_Param) |
| and then Present (Wrapper_Param) |
| loop |
| Iface_Op_Typ := Find_Parameter_Type (Iface_Op_Param); |
| Wrapper_Typ := Find_Parameter_Type (Wrapper_Param); |
| |
| -- The two parameters must be mode conformant |
| |
| if not Conforming_Types |
| (Iface_Op_Typ, Wrapper_Typ, Mode_Conformant) |
| then |
| return False; |
| end if; |
| |
| Next (Iface_Op_Param); |
| Next (Wrapper_Param); |
| end loop; |
| |
| -- One of the lists is longer than the other |
| |
| if Present (Iface_Op_Param) or else Present (Wrapper_Param) then |
| return False; |
| end if; |
| |
| return True; |
| end Type_Conformant_Parameters; |
| |
| -- Start of processing for Overriding_Possible |
| |
| begin |
| if Chars (Iface_Op) /= Chars (Wrapper) then |
| return False; |
| end if; |
| |
| -- If an inherited subprogram is implemented by a protected procedure |
| -- or an entry, then the first parameter of the inherited subprogram |
| -- must be of mode OUT or IN OUT, or access-to-variable parameter. |
| |
| if Ekind (Iface_Op) = E_Procedure |
| and then Present (Parameter_Specifications (Iface_Op_Spec)) |
| then |
| declare |
| Obj_Param : constant Node_Id := |
| First (Parameter_Specifications (Iface_Op_Spec)); |
| begin |
| if not Out_Present (Obj_Param) |
| and then Nkind (Parameter_Type (Obj_Param)) /= |
| N_Access_Definition |
| then |
| return False; |
| end if; |
| end; |
| end if; |
| |
| return |
| Type_Conformant_Parameters ( |
| Parameter_Specifications (Iface_Op_Spec), |
| Parameter_Specifications (Wrapper_Spec)); |
| end Overriding_Possible; |
| |
| ----------------------- |
| -- Replicate_Formals -- |
| ----------------------- |
| |
| function Replicate_Formals |
| (Loc : Source_Ptr; |
| Formals : List_Id) return List_Id |
| is |
| New_Formals : constant List_Id := New_List; |
| Formal : Node_Id; |
| Param_Type : Node_Id; |
| |
| begin |
| Formal := First (Formals); |
| |
| -- Skip the object parameter when dealing with primitives declared |
| -- between two views. |
| |
| if Is_Private_Primitive_Subprogram (Subp_Id) |
| and then not Has_Controlling_Result (Subp_Id) |
| then |
| Formal := Next (Formal); |
| end if; |
| |
| while Present (Formal) loop |
| |
| -- Create an explicit copy of the entry parameter |
| |
| -- When creating the wrapper subprogram for a primitive operation |
| -- of a protected interface we must construct an equivalent |
| -- signature to that of the overriding operation. For regular |
| -- parameters we can just use the type of the formal, but for |
| -- access to subprogram parameters we need to reanalyze the |
| -- parameter type to create local entities for the signature of |
| -- the subprogram type. Using the entities of the overriding |
| -- subprogram will result in out-of-scope errors in the back-end. |
| |
| if Nkind (Parameter_Type (Formal)) = N_Access_Definition then |
| Param_Type := Copy_Separate_Tree (Parameter_Type (Formal)); |
| else |
| Param_Type := |
| New_Occurrence_Of (Etype (Parameter_Type (Formal)), Loc); |
| end if; |
| |
| Append_To (New_Formals, |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => |
| Make_Defining_Identifier (Loc, |
| Chars => Chars |
| (Defining_Identifier (Formal))), |
| In_Present => In_Present (Formal), |
| Out_Present => Out_Present (Formal), |
| Null_Exclusion_Present => Null_Exclusion_Present (Formal), |
| Parameter_Type => Param_Type)); |
| |
| Next (Formal); |
| end loop; |
| |
| return New_Formals; |
| end Replicate_Formals; |
| |
| -- Start of processing for Build_Wrapper_Spec |
| |
| begin |
| -- No point in building wrappers for untagged concurrent types |
| |
| pragma Assert (Is_Tagged_Type (Obj_Typ)); |
| |
| -- An entry or a protected procedure can override a routine where the |
| -- controlling formal is either IN OUT, OUT or is of access-to-variable |
| -- type. Since the wrapper must have the exact same signature as that of |
| -- the overridden subprogram, we try to find the overriding candidate |
| -- and use its controlling formal. |
| |
| First_Param := Empty; |
| |
| -- Check every implemented interface |
| |
| if Present (Interfaces (Obj_Typ)) then |
| Iface_Elmt := First_Elmt (Interfaces (Obj_Typ)); |
| Search : while Present (Iface_Elmt) loop |
| Iface := Node (Iface_Elmt); |
| |
| -- Check every interface primitive |
| |
| if Present (Primitive_Operations (Iface)) then |
| Iface_Op_Elmt := First_Elmt (Primitive_Operations (Iface)); |
| while Present (Iface_Op_Elmt) loop |
| Iface_Op := Node (Iface_Op_Elmt); |
| |
| -- Ignore predefined primitives |
| |
| if not Is_Predefined_Dispatching_Operation (Iface_Op) then |
| Iface_Op := Ultimate_Alias (Iface_Op); |
| |
| -- The current primitive operation can be overridden by |
| -- the generated entry wrapper. |
| |
| if Overriding_Possible (Iface_Op, Subp_Id) then |
| First_Param := |
| First (Parameter_Specifications (Parent (Iface_Op))); |
| |
| exit Search; |
| end if; |
| end if; |
| |
| Next_Elmt (Iface_Op_Elmt); |
| end loop; |
| end if; |
| |
| Next_Elmt (Iface_Elmt); |
| end loop Search; |
| end if; |
| |
| -- Ada 2012 (AI05-0090-1): If no interface primitive is covered by |
| -- this subprogram and this is not a primitive declared between two |
| -- views then force the generation of a wrapper. As an optimization, |
| -- previous versions of the frontend avoid generating the wrapper; |
| -- however, the wrapper facilitates locating and reporting an error |
| -- when a duplicate declaration is found later. See example in |
| -- AI05-0090-1. |
| |
| if No (First_Param) |
| and then not Is_Private_Primitive_Subprogram (Subp_Id) |
| then |
| if Is_Task_Type |
| (Corresponding_Concurrent_Type (Obj_Typ)) |
| then |
| First_Param := |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => Make_Defining_Identifier (Loc, Name_uO), |
| In_Present => True, |
| Out_Present => False, |
| Parameter_Type => New_Occurrence_Of (Obj_Typ, Loc)); |
| |
| -- For entries and procedures of protected types the mode of |
| -- the controlling argument must be in-out. |
| |
| else |
| First_Param := |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => |
| Make_Defining_Identifier (Loc, |
| Chars => Name_uO), |
| In_Present => True, |
| Out_Present => (Ekind (Subp_Id) /= E_Function), |
| Parameter_Type => New_Occurrence_Of (Obj_Typ, Loc)); |
| end if; |
| end if; |
| |
| declare |
| Wrapper_Id : constant Entity_Id := |
| Make_Defining_Identifier (Loc, Chars (Subp_Id)); |
| New_Formals : List_Id; |
| Obj_Param : Node_Id; |
| Obj_Param_Typ : Entity_Id; |
| |
| begin |
| -- Minimum decoration is needed to catch the entity in |
| -- Sem_Ch6.Override_Dispatching_Operation. |
| |
| if Ekind (Subp_Id) = E_Function then |
| Set_Ekind (Wrapper_Id, E_Function); |
| else |
| Set_Ekind (Wrapper_Id, E_Procedure); |
| end if; |
| |
| Set_Is_Primitive_Wrapper (Wrapper_Id); |
| Set_Wrapped_Entity (Wrapper_Id, Subp_Id); |
| Set_Is_Private_Primitive (Wrapper_Id, |
| Is_Private_Primitive_Subprogram (Subp_Id)); |
| |
| -- Process the formals |
| |
| New_Formals := Replicate_Formals (Loc, Formals); |
| |
| -- A function with a controlling result and no first controlling |
| -- formal needs no additional parameter. |
| |
| if Has_Controlling_Result (Subp_Id) |
| and then |
| (No (First_Formal (Subp_Id)) |
| or else not Is_Controlling_Formal (First_Formal (Subp_Id))) |
| then |
| null; |
| |
| -- Routine Subp_Id has been found to override an interface primitive. |
| -- If the interface operation has an access parameter, create a copy |
| -- of it, with the same null exclusion indicator if present. |
| |
| elsif Present (First_Param) then |
| if Nkind (Parameter_Type (First_Param)) = N_Access_Definition then |
| Obj_Param_Typ := |
| Make_Access_Definition (Loc, |
| Subtype_Mark => |
| New_Occurrence_Of (Obj_Typ, Loc), |
| Null_Exclusion_Present => |
| Null_Exclusion_Present (Parameter_Type (First_Param)), |
| Constant_Present => |
| Constant_Present (Parameter_Type (First_Param))); |
| else |
| Obj_Param_Typ := New_Occurrence_Of (Obj_Typ, Loc); |
| end if; |
| |
| Obj_Param := |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => |
| Make_Defining_Identifier (Loc, |
| Chars => Name_uO), |
| In_Present => In_Present (First_Param), |
| Out_Present => Out_Present (First_Param), |
| Parameter_Type => Obj_Param_Typ); |
| |
| Prepend_To (New_Formals, Obj_Param); |
| |
| -- If we are dealing with a primitive declared between two views, |
| -- implemented by a synchronized operation, we need to create |
| -- a default parameter. The mode of the parameter must match that |
| -- of the primitive operation. |
| |
| else |
| pragma Assert (Is_Private_Primitive_Subprogram (Subp_Id)); |
| Obj_Param := |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => |
| Make_Defining_Identifier (Loc, Name_uO), |
| In_Present => In_Present (Parent (First_Entity (Subp_Id))), |
| Out_Present => Ekind (Subp_Id) /= E_Function, |
| Parameter_Type => New_Occurrence_Of (Obj_Typ, Loc)); |
| Prepend_To (New_Formals, Obj_Param); |
| end if; |
| |
| -- Build the final spec. If it is a function with a controlling |
| -- result, it is a primitive operation of the corresponding |
| -- record type, so mark the spec accordingly. |
| |
| if Ekind (Subp_Id) = E_Function then |
| declare |
| Res_Def : Node_Id; |
| |
| begin |
| if Has_Controlling_Result (Subp_Id) then |
| Res_Def := |
| New_Occurrence_Of |
| (Corresponding_Record_Type (Etype (Subp_Id)), Loc); |
| else |
| Res_Def := New_Copy (Result_Definition (Parent (Subp_Id))); |
| end if; |
| |
| return |
| Make_Function_Specification (Loc, |
| Defining_Unit_Name => Wrapper_Id, |
| Parameter_Specifications => New_Formals, |
| Result_Definition => Res_Def); |
| end; |
| else |
| return |
| Make_Procedure_Specification (Loc, |
| Defining_Unit_Name => Wrapper_Id, |
| Parameter_Specifications => New_Formals); |
| end if; |
| end; |
| end Build_Wrapper_Spec; |
| |
| ------------------------- |
| -- Build_Wrapper_Specs -- |
| ------------------------- |
| |
| procedure Build_Wrapper_Specs |
| (Loc : Source_Ptr; |
| Typ : Entity_Id; |
| N : in out Node_Id) |
| is |
| Def : Node_Id; |
| Rec_Typ : Entity_Id; |
| procedure Scan_Declarations (L : List_Id); |
| -- Common processing for visible and private declarations |
| -- of a protected type. |
| |
| procedure Scan_Declarations (L : List_Id) is |
| Decl : Node_Id; |
| Wrap_Decl : Node_Id; |
| Wrap_Spec : Node_Id; |
| |
| begin |
| if No (L) then |
| return; |
| end if; |
| |
| Decl := First (L); |
| while Present (Decl) loop |
| Wrap_Spec := Empty; |
| |
| if Nkind (Decl) = N_Entry_Declaration |
| and then Ekind (Defining_Identifier (Decl)) = E_Entry |
| then |
| Wrap_Spec := |
| Build_Wrapper_Spec |
| (Subp_Id => Defining_Identifier (Decl), |
| Obj_Typ => Rec_Typ, |
| Formals => Parameter_Specifications (Decl)); |
| |
| elsif Nkind (Decl) = N_Subprogram_Declaration then |
| Wrap_Spec := |
| Build_Wrapper_Spec |
| (Subp_Id => Defining_Unit_Name (Specification (Decl)), |
| Obj_Typ => Rec_Typ, |
| Formals => |
| Parameter_Specifications (Specification (Decl))); |
| end if; |
| |
| if Present (Wrap_Spec) then |
| Wrap_Decl := |
| Make_Subprogram_Declaration (Loc, |
| Specification => Wrap_Spec); |
| |
| Insert_After (N, Wrap_Decl); |
| N := Wrap_Decl; |
| |
| Analyze (Wrap_Decl); |
| end if; |
| |
| Next (Decl); |
| end loop; |
| end Scan_Declarations; |
| |
| -- start of processing for Build_Wrapper_Specs |
| |
| begin |
| if Is_Protected_Type (Typ) then |
| Def := Protected_Definition (Parent (Typ)); |
| else pragma Assert (Is_Task_Type (Typ)); |
| Def := Task_Definition (Parent (Typ)); |
| end if; |
| |
| Rec_Typ := Corresponding_Record_Type (Typ); |
| |
| -- Generate wrapper specs for a concurrent type which implements an |
| -- interface. Operations in both the visible and private parts may |
| -- implement progenitor operations. |
| |
| if Present (Interfaces (Rec_Typ)) and then Present (Def) then |
| Scan_Declarations (Visible_Declarations (Def)); |
| Scan_Declarations (Private_Declarations (Def)); |
| end if; |
| end Build_Wrapper_Specs; |
| |
| --------------------------- |
| -- Build_Find_Body_Index -- |
| --------------------------- |
| |
| function Build_Find_Body_Index (Typ : Entity_Id) return Node_Id is |
| Loc : constant Source_Ptr := Sloc (Typ); |
| Ent : Entity_Id; |
| E_Typ : Entity_Id; |
| Has_F : Boolean := False; |
| Index : Nat; |
| If_St : Node_Id := Empty; |
| Lo : Node_Id; |
| Hi : Node_Id; |
| Decls : List_Id := New_List; |
| Ret : Node_Id; |
| Spec : Node_Id; |
| Siz : Node_Id := Empty; |
| |
| procedure Add_If_Clause (Expr : Node_Id); |
| -- Add test for range of current entry |
| |
| function Convert_Discriminant_Ref (Bound : Node_Id) return Node_Id; |
| -- If a bound of an entry is given by a discriminant, retrieve the |
| -- actual value of the discriminant from the enclosing object. |
| |
| ------------------- |
| -- Add_If_Clause -- |
| ------------------- |
| |
| procedure Add_If_Clause (Expr : Node_Id) is |
| Cond : Node_Id; |
| Stats : constant List_Id := |
| New_List ( |
| Make_Simple_Return_Statement (Loc, |
| Expression => Make_Integer_Literal (Loc, Index + 1))); |
| |
| begin |
| -- Index for current entry body |
| |
| Index := Index + 1; |
| |
| -- Compute total length of entry queues so far |
| |
| if No (Siz) then |
| Siz := Expr; |
| else |
| Siz := |
| Make_Op_Add (Loc, |
| Left_Opnd => Siz, |
| Right_Opnd => Expr); |
| end if; |
| |
| Cond := |
| Make_Op_Le (Loc, |
| Left_Opnd => Make_Identifier (Loc, Name_uE), |
| Right_Opnd => Siz); |
| |
| -- Map entry queue indexes in the range of the current family |
| -- into the current index, that designates the entry body. |
| |
| if No (If_St) then |
| If_St := |
| Make_Implicit_If_Statement (Typ, |
| Condition => Cond, |
| Then_Statements => Stats, |
| Elsif_Parts => New_List); |
| Ret := If_St; |
| |
| else |
| Append_To (Elsif_Parts (If_St), |
| Make_Elsif_Part (Loc, |
| Condition => Cond, |
| Then_Statements => Stats)); |
| end if; |
| end Add_If_Clause; |
| |
| ------------------------------ |
| -- Convert_Discriminant_Ref -- |
| ------------------------------ |
| |
| function Convert_Discriminant_Ref (Bound : Node_Id) return Node_Id is |
| B : Node_Id; |
| |
| begin |
| if Is_Entity_Name (Bound) |
| and then Ekind (Entity (Bound)) = E_Discriminant |
| then |
| B := |
| Make_Selected_Component (Loc, |
| Prefix => |
| Unchecked_Convert_To (Corresponding_Record_Type (Typ), |
| Make_Explicit_Dereference (Loc, |
| Make_Identifier (Loc, Name_uObject))), |
| Selector_Name => Make_Identifier (Loc, Chars (Bound))); |
| Set_Etype (B, Etype (Entity (Bound))); |
| else |
| B := New_Copy_Tree (Bound); |
| end if; |
| |
| return B; |
| end Convert_Discriminant_Ref; |
| |
| -- Start of processing for Build_Find_Body_Index |
| |
| begin |
| Spec := Build_Find_Body_Index_Spec (Typ); |
| |
| Ent := First_Entity (Typ); |
| while Present (Ent) loop |
| if Ekind (Ent) = E_Entry_Family then |
| Has_F := True; |
| exit; |
| end if; |
| |
| Next_Entity (Ent); |
| end loop; |
| |
| if not Has_F then |
| |
| -- If the protected type has no entry families, there is a one-one |
| -- correspondence between entry queue and entry body. |
| |
| Ret := |
| Make_Simple_Return_Statement (Loc, |
| Expression => Make_Identifier (Loc, Name_uE)); |
| |
| else |
| -- Suppose entries e1, e2, ... have size l1, l2, ... we generate |
| -- the following: |
| |
| -- if E <= l1 then return 1; |
| -- elsif E <= l1 + l2 then return 2; |
| -- ... |
| |
| Index := 0; |
| Siz := Empty; |
| Ent := First_Entity (Typ); |
| |
| Add_Object_Pointer (Loc, Typ, Decls); |
| |
| while Present (Ent) loop |
| if Ekind (Ent) = E_Entry then |
| Add_If_Clause (Make_Integer_Literal (Loc, 1)); |
| |
| elsif Ekind (Ent) = E_Entry_Family then |
| E_Typ := Etype (Discrete_Subtype_Definition (Parent (Ent))); |
| Hi := Convert_Discriminant_Ref (Type_High_Bound (E_Typ)); |
| Lo := Convert_Discriminant_Ref (Type_Low_Bound (E_Typ)); |
| Add_If_Clause (Family_Size (Loc, Hi, Lo, Typ, False)); |
| end if; |
| |
| Next_Entity (Ent); |
| end loop; |
| |
| if Index = 1 then |
| Decls := New_List; |
| Ret := |
| Make_Simple_Return_Statement (Loc, |
| Expression => Make_Integer_Literal (Loc, 1)); |
| |
| elsif Nkind (Ret) = N_If_Statement then |
| |
| -- Ranges are in increasing order, so last one doesn't need guard |
| |
| declare |
| Nod : constant Node_Id := Last (Elsif_Parts (Ret)); |
| begin |
| Remove (Nod); |
| Set_Else_Statements (Ret, Then_Statements (Nod)); |
| end; |
| end if; |
| end if; |
| |
| return |
| Make_Subprogram_Body (Loc, |
| Specification => Spec, |
| Declarations => Decls, |
| Handled_Statement_Sequence => |
| Make_Handled_Sequence_Of_Statements (Loc, |
| Statements => New_List (Ret))); |
| end Build_Find_Body_Index; |
| |
| -------------------------------- |
| -- Build_Find_Body_Index_Spec -- |
| -------------------------------- |
| |
| function Build_Find_Body_Index_Spec (Typ : Entity_Id) return Node_Id is |
| Loc : constant Source_Ptr := Sloc (Typ); |
| Id : constant Entity_Id := |
| Make_Defining_Identifier (Loc, |
| Chars => New_External_Name (Chars (Typ), 'F')); |
| Parm1 : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uO); |
| Parm2 : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uE); |
| |
| begin |
| return |
| Make_Function_Specification (Loc, |
| Defining_Unit_Name => Id, |
| Parameter_Specifications => New_List ( |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => Parm1, |
| Parameter_Type => |
| New_Occurrence_Of (RTE (RE_Address), Loc)), |
| |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => Parm2, |
| Parameter_Type => |
| New_Occurrence_Of (RTE (RE_Protected_Entry_Index), Loc))), |
| |
| Result_Definition => New_Occurrence_Of ( |
| RTE (RE_Protected_Entry_Index), Loc)); |
| end Build_Find_Body_Index_Spec; |
| |
| ----------------------------------------------- |
| -- Build_Lock_Free_Protected_Subprogram_Body -- |
| ----------------------------------------------- |
| |
| function Build_Lock_Free_Protected_Subprogram_Body |
| (N : Node_Id; |
| Prot_Typ : Node_Id; |
| Unprot_Spec : Node_Id) return Node_Id |
| is |
| Actuals : constant List_Id := New_List; |
| Loc : constant Source_Ptr := Sloc (N); |
| Spec : constant Node_Id := Specification (N); |
| Unprot_Id : constant Entity_Id := Defining_Unit_Name (Unprot_Spec); |
| Formal : Node_Id; |
| Prot_Spec : Node_Id; |
| Stmt : Node_Id; |
| |
| begin |
| -- Create the protected version of the body |
| |
| Prot_Spec := |
| Build_Protected_Sub_Specification (N, Prot_Typ, Protected_Mode); |
| |
| -- Build the actual parameters which appear in the call to the |
| -- unprotected version of the body. |
| |
| Formal := First (Parameter_Specifications (Prot_Spec)); |
| while Present (Formal) loop |
| Append_To (Actuals, |
| Make_Identifier (Loc, Chars (Defining_Identifier (Formal)))); |
| |
| Next (Formal); |
| end loop; |
| |
| -- Function case, generate: |
| -- return <Unprot_Func_Call>; |
| |
| if Nkind (Spec) = N_Function_Specification then |
| Stmt := |
| Make_Simple_Return_Statement (Loc, |
| Expression => |
| Make_Function_Call (Loc, |
| Name => |
| Make_Identifier (Loc, Chars (Unprot_Id)), |
| Parameter_Associations => Actuals)); |
| |
| -- Procedure case, call the unprotected version |
| |
| else |
| Stmt := |
| Make_Procedure_Call_Statement (Loc, |
| Name => |
| Make_Identifier (Loc, Chars (Unprot_Id)), |
| Parameter_Associations => Actuals); |
| end if; |
| |
| return |
| Make_Subprogram_Body (Loc, |
| Declarations => Empty_List, |
| Specification => Prot_Spec, |
| Handled_Statement_Sequence => |
| Make_Handled_Sequence_Of_Statements (Loc, |
| Statements => New_List (Stmt))); |
| end Build_Lock_Free_Protected_Subprogram_Body; |
| |
| ------------------------------------------------- |
| -- Build_Lock_Free_Unprotected_Subprogram_Body -- |
| ------------------------------------------------- |
| |
| -- Procedures which meet the lock-free implementation requirements and |
| -- reference a unique scalar component Comp are expanded in the following |
| -- manner: |
| |
| -- procedure P (...) is |
| -- Expected_Comp : constant Comp_Type := |
| -- Comp_Type |
| -- (System.Atomic_Primitives.Lock_Free_Read_N |
| -- (_Object.Comp'Address)); |
| -- begin |
| -- loop |
| -- declare |
| -- <original declarations before the object renaming declaration |
| -- of Comp> |
| -- |
| -- Desired_Comp : Comp_Type := Expected_Comp; |
| -- Comp : Comp_Type renames Desired_Comp; |
| -- |
| -- <original delarations after the object renaming declaration |
| -- of Comp> |
| -- |
| -- begin |
| -- <original statements> |
| -- exit when System.Atomic_Primitives.Lock_Free_Try_Write_N |
| -- (_Object.Comp'Address, |
| -- Interfaces.Unsigned_N (Expected_Comp), |
| -- Interfaces.Unsigned_N (Desired_Comp)); |
| -- end; |
| -- end loop; |
| -- end P; |
| |
| -- Each return and raise statement of P is transformed into an atomic |
| -- status check: |
| |
| -- if System.Atomic_Primitives.Lock_Free_Try_Write_N |
| -- (_Object.Comp'Address, |
| -- Interfaces.Unsigned_N (Expected_Comp), |
| -- Interfaces.Unsigned_N (Desired_Comp)); |
| -- then |
| -- <original statement> |
| -- else |
| -- goto L0; |
| -- end if; |
| |
| -- Functions which meet the lock-free implementation requirements and |
| -- reference a unique scalar component Comp are expanded in the following |
| -- manner: |
| |
| -- function F (...) return ... is |
| -- <original declarations before the object renaming declaration |
| -- of Comp> |
| -- |
| -- Expected_Comp : constant Comp_Type := |
| -- Comp_Type |
| -- (System.Atomic_Primitives.Lock_Free_Read_N |
| -- (_Object.Comp'Address)); |
| -- Comp : Comp_Type renames Expected_Comp; |
| -- |
| -- <original delarations after the object renaming declaration of |
| -- Comp> |
| -- |
| -- begin |
| -- <original statements> |
| -- end F; |
| |
| function Build_Lock_Free_Unprotected_Subprogram_Body |
| (N : Node_Id; |
| Prot_Typ : Node_Id) return Node_Id |
| is |
| function Referenced_Component (N : Node_Id) return Entity_Id; |
| -- Subprograms which meet the lock-free implementation criteria are |
| -- allowed to reference only one unique component. Return the prival |
| -- of the said component. |
| |
| -------------------------- |
| -- Referenced_Component -- |
| -------------------------- |
| |
| function Referenced_Component (N : Node_Id) return Entity_Id is |
| Comp : Entity_Id; |
| Decl : Node_Id; |
| Source_Comp : Entity_Id := Empty; |
| |
| begin |
| -- Find the unique source component which N references in its |
| -- statements. |
| |
| for Index in 1 .. Lock_Free_Subprogram_Table.Last loop |
| declare |
| Element : Lock_Free_Subprogram renames |
| Lock_Free_Subprogram_Table.Table (Index); |
| begin |
| if Element.Sub_Body = N then |
| Source_Comp := Element.Comp_Id; |
| exit; |
| end if; |
| end; |
| end loop; |
| |
| if No (Source_Comp) then |
| return Empty; |
| end if; |
| |
| -- Find the prival which corresponds to the source component within |
| -- the declarations of N. |
| |
| Decl := First (Declarations (N)); |
| while Present (Decl) loop |
| |
| -- Privals appear as object renamings |
| |
| if Nkind (Decl) = N_Object_Renaming_Declaration then |
| Comp := Defining_Identifier (Decl); |
| |
| if Present (Prival_Link (Comp)) |
| and then Prival_Link (Comp) = Source_Comp |
| then |
| return Comp; |
| end if; |
| end if; |
| |
| Next (Decl); |
| end loop; |
| |
| return Empty; |
| end Referenced_Component; |
| |
| -- Local variables |
| |
| Comp : constant Entity_Id := Referenced_Component (N); |
| Loc : constant Source_Ptr := Sloc (N); |
| Hand_Stmt_Seq : Node_Id := Handled_Statement_Sequence (N); |
| Decls : List_Id := Declarations (N); |
| |
| -- Start of processing for Build_Lock_Free_Unprotected_Subprogram_Body |
| |
| begin |
| -- Add renamings for the protection object, discriminals, privals and |
| -- the entry index constant for use by debugger. |
| |
| Debug_Private_Data_Declarations (Decls); |
| |
| -- Perform the lock-free expansion when the subprogram references a |
| -- protected component. |
| |
| if Present (Comp) then |
| Protected_Component_Ref : declare |
| Comp_Decl : constant Node_Id := Parent (Comp); |
| Comp_Sel_Nam : constant Node_Id := Name (Comp_Decl); |
| Comp_Type : constant Entity_Id := Etype (Comp); |
| |
| Is_Procedure : constant Boolean := |
| Ekind (Corresponding_Spec (N)) = E_Procedure; |
| -- Indicates if N is a protected procedure body |
| |
| Block_Decls : List_Id; |
| Try_Write : Entity_Id; |
| Desired_Comp : Entity_Id; |
| Decl : Node_Id; |
| Label : Node_Id; |
| Label_Id : Entity_Id := Empty; |
| Read : Entity_Id; |
| Expected_Comp : Entity_Id; |
| Stmt : Node_Id; |
| Stmts : List_Id := |
| New_Copy_List (Statements (Hand_Stmt_Seq)); |
| Typ_Size : Int; |
| Unsigned : Entity_Id; |
| |
| function Process_Node (N : Node_Id) return Traverse_Result; |
| -- Transform a single node if it is a return statement, a raise |
| -- statement or a reference to Comp. |
| |
| procedure Process_Stmts (Stmts : List_Id); |
| -- Given a statement sequence Stmts, wrap any return or raise |
| -- statements in the following manner: |
| -- |
| -- if System.Atomic_Primitives.Lock_Free_Try_Write_N |
| -- (_Object.Comp'Address, |
| -- Interfaces.Unsigned_N (Expected_Comp), |
| -- Interfaces.Unsigned_N (Desired_Comp)) |
| -- then |
| -- <Stmt>; |
| -- else |
| -- goto L0; |
| -- end if; |
| |
| ------------------ |
| -- Process_Node -- |
| ------------------ |
| |
| function Process_Node (N : Node_Id) return Traverse_Result is |
| |
| procedure Wrap_Statement (Stmt : Node_Id); |
| -- Wrap an arbitrary statement inside an if statement where the |
| -- condition does an atomic check on the state of the object. |
| |
| -------------------- |
| -- Wrap_Statement -- |
| -------------------- |
| |
| procedure Wrap_Statement (Stmt : Node_Id) is |
| begin |
| -- The first time through, create the declaration of a label |
| -- which is used to skip the remainder of source statements |
| -- if the state of the object has changed. |
| |
| if No (Label_Id) then |
| Label_Id := |
| Make_Identifier (Loc, New_External_Name ('L', 0)); |
| Set_Entity (Label_Id, |
| Make_Defining_Identifier (Loc, Chars (Label_Id))); |
| end if; |
| |
| -- Generate: |
| -- if System.Atomic_Primitives.Lock_Free_Try_Write_N |
| -- (_Object.Comp'Address, |
| -- Interfaces.Unsigned_N (Expected_Comp), |
| -- Interfaces.Unsigned_N (Desired_Comp)) |
| -- then |
| -- <Stmt>; |
| -- else |
| -- goto L0; |
| -- end if; |
| |
| Rewrite (Stmt, |
| Make_Implicit_If_Statement (N, |
| Condition => |
| Make_Function_Call (Loc, |
| Name => |
| New_Occurrence_Of (Try_Write, Loc), |
| Parameter_Associations => New_List ( |
| Make_Attribute_Reference (Loc, |
| Prefix => Relocate_Node (Comp_Sel_Nam), |
| Attribute_Name => Name_Address), |
| |
| Unchecked_Convert_To (Unsigned, |
| New_Occurrence_Of (Expected_Comp, Loc)), |
| |
| Unchecked_Convert_To (Unsigned, |
| New_Occurrence_Of (Desired_Comp, Loc)))), |
| |
| Then_Statements => New_List (Relocate_Node (Stmt)), |
| |
| Else_Statements => New_List ( |
| Make_Goto_Statement (Loc, |
| Name => |
| New_Occurrence_Of (Entity (Label_Id), Loc))))); |
| end Wrap_Statement; |
| |
| -- Start of processing for Process_Node |
| |
| begin |
| -- Wrap each return and raise statement that appear inside a |
| -- procedure. Skip the last return statement which is added by |
| -- default since it is transformed into an exit statement. |
| |
| if Is_Procedure |
| and then ((Nkind (N) = N_Simple_Return_Statement |
| and then N /= Last (Stmts)) |
| or else Nkind (N) = N_Extended_Return_Statement |
| or else (Nkind_In (N, N_Raise_Constraint_Error, |
| N_Raise_Program_Error, |
| N_Raise_Statement, |
| N_Raise_Storage_Error) |
| and then Comes_From_Source (N))) |
| then |
| Wrap_Statement (N); |
| return Skip; |
| end if; |
| |
| -- Force reanalysis |
| |
| Set_Analyzed (N, False); |
| |
| return OK; |
| end Process_Node; |
| |
| procedure Process_Nodes is new Traverse_Proc (Process_Node); |
| |
| ------------------- |
| -- Process_Stmts -- |
| ------------------- |
| |
| procedure Process_Stmts (Stmts : List_Id) is |
| Stmt : Node_Id; |
| begin |
| Stmt := First (Stmts); |
| while Present (Stmt) loop |
| Process_Nodes (Stmt); |
| Next (Stmt); |
| end loop; |
| end Process_Stmts; |
| |
| -- Start of processing for Protected_Component_Ref |
| |
| begin |
| -- Get the type size |
| |
| if Known_Static_Esize (Comp_Type) then |
| Typ_Size := UI_To_Int (Esize (Comp_Type)); |
| |
| -- If the Esize (Object_Size) is unknown at compile time, look at |
| -- the RM_Size (Value_Size) since it may have been set by an |
| -- explicit representation clause. |
| |
| elsif Known_Static_RM_Size (Comp_Type) then |
| Typ_Size := UI_To_Int (RM_Size (Comp_Type)); |
| |
| -- Should not happen since this has already been checked in |
| -- Allows_Lock_Free_Implementation (see Sem_Ch9). |
| |
| else |
| raise Program_Error; |
| end if; |
| |
| -- Retrieve all relevant atomic routines and types |
| |
| case Typ_Size is |
| when 8 => |
| Try_Write := RTE (RE_Lock_Free_Try_Write_8); |
| Read := RTE (RE_Lock_Free_Read_8); |
| Unsigned := RTE (RE_Uint8); |
| |
| when 16 => |
| Try_Write := RTE (RE_Lock_Free_Try_Write_16); |
| Read := RTE (RE_Lock_Free_Read_16); |
| Unsigned := RTE (RE_Uint16); |
| |
| when 32 => |
| Try_Write := RTE (RE_Lock_Free_Try_Write_32); |
| Read := RTE (RE_Lock_Free_Read_32); |
| Unsigned := RTE (RE_Uint32); |
| |
| when 64 => |
| Try_Write := RTE (RE_Lock_Free_Try_Write_64); |
| Read := RTE (RE_Lock_Free_Read_64); |
| Unsigned := RTE (RE_Uint64); |
| |
| when others => |
| raise Program_Error; |
| end case; |
| |
| -- Generate: |
| -- Expected_Comp : constant Comp_Type := |
| -- Comp_Type |
| -- (System.Atomic_Primitives.Lock_Free_Read_N |
| -- (_Object.Comp'Address)); |
| |
| Expected_Comp := |
| Make_Defining_Identifier (Loc, |
| New_External_Name (Chars (Comp), Suffix => "_saved")); |
| |
| Decl := |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Expected_Comp, |
| Object_Definition => New_Occurrence_Of (Comp_Type, Loc), |
| Constant_Present => True, |
| Expression => |
| Unchecked_Convert_To (Comp_Type, |
| Make_Function_Call (Loc, |
| Name => New_Occurrence_Of (Read, Loc), |
| Parameter_Associations => New_List ( |
| Make_Attribute_Reference (Loc, |
| Prefix => Relocate_Node (Comp_Sel_Nam), |
| Attribute_Name => Name_Address))))); |
| |
| -- Protected procedures |
| |
| if Is_Procedure then |
| -- Move the original declarations inside the generated block |
| |
| Block_Decls := Decls; |
| |
| -- Reset the declarations list of the protected procedure to |
| -- contain only Decl. |
| |
| Decls := New_List (Decl); |
| |
| -- Generate: |
| -- Desired_Comp : Comp_Type := Expected_Comp; |
| |
| Desired_Comp := |
| Make_Defining_Identifier (Loc, |
| New_External_Name (Chars (Comp), Suffix => "_current")); |
| |
| -- Insert the declarations of Expected_Comp and Desired_Comp in |
| -- the block declarations right before the renaming of the |
| -- protected component. |
| |
| Insert_Before (Comp_Decl, |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => Desired_Comp, |
| Object_Definition => New_Occurrence_Of (Comp_Type, Loc), |
| Expression => |
| New_Occurrence_Of (Expected_Comp, Loc))); |
| |
| -- Protected function |
| |
| else |
| Desired_Comp := Expected_Comp; |
| |
| -- Insert the declaration of Expected_Comp in the function |
| -- declarations right before the renaming of the protected |
| -- component. |
| |
| Insert_Before (Comp_Decl, Decl); |
| end if; |
| |
| -- Rewrite the protected component renaming declaration to be a |
| -- renaming of Desired_Comp. |
| |
| -- Generate: |
| -- Comp : Comp_Type renames Desired_Comp; |
| |
| Rewrite (Comp_Decl, |
| Make_Object_Renaming_Declaration (Loc, |
| Defining_Identifier => |
| Defining_Identifier (Comp_Decl), |
| Subtype_Mark => |
| New_Occurrence_Of (Comp_Type, Loc), |
| Name => |
| New_Occurrence_Of (Desired_Comp, Loc))); |
| |
| -- Wrap any return or raise statements in Stmts in same the manner |
| -- described in Process_Stmts. |
| |
| Process_Stmts (Stmts); |
| |
| -- Generate: |
| -- exit when System.Atomic_Primitives.Lock_Free_Try_Write_N |
| -- (_Object.Comp'Address, |
| -- Interfaces.Unsigned_N (Expected_Comp), |
| -- Interfaces.Unsigned_N (Desired_Comp)) |
| |
| if Is_Procedure then |
| Stmt := |
| Make_Exit_Statement (Loc, |
| Condition => |
| Make_Function_Call (Loc, |
| Name => |
| New_Occurrence_Of (Try_Write, Loc), |
| Parameter_Associations => New_List ( |
| Make_Attribute_Reference (Loc, |
| Prefix => Relocate_Node (Comp_Sel_Nam), |
| Attribute_Name => Name_Address), |
| |
| Unchecked_Convert_To (Unsigned, |
| New_Occurrence_Of (Expected_Comp, Loc)), |
| |
| Unchecked_Convert_To (Unsigned, |
| New_Occurrence_Of (Desired_Comp, Loc))))); |
| |
| -- Small optimization: transform the default return statement |
| -- of a procedure into the atomic exit statement. |
| |
| if Nkind (Last (Stmts)) = N_Simple_Return_Statement then |
| Rewrite (Last (Stmts), Stmt); |
| else |
| Append_To (Stmts, Stmt); |
| end if; |
| end if; |
| |
| -- Create the declaration of the label used to skip the rest of |
| -- the source statements when the object state changes. |
| |
| if Present (Label_Id) then |
| Label := Make_Label (Loc, Label_Id); |
| Append_To (Decls, |
| Make_Implicit_Label_Declaration (Loc, |
| Defining_Identifier => Entity (Label_Id), |
| Label_Construct => Label)); |
| Append_To (Stmts, Label); |
| end if; |
| |
| -- Generate: |
| -- loop |
| -- declare |
| -- <Decls> |
| -- begin |
| -- <Stmts> |
| -- end; |
| -- end loop; |
| |
| if Is_Procedure then |
| Stmts := |
| New_List ( |
| Make_Loop_Statement (Loc, |
| Statements => New_List ( |
| Make_Block_Statement (Loc, |
| Declarations => Block_Decls, |
| Handled_Statement_Sequence => |
| Make_Handled_Sequence_Of_Statements (Loc, |
| Statements => Stmts))), |
| End_Label => Empty)); |
| end if; |
| |
| Hand_Stmt_Seq := |
| Make_Handled_Sequence_Of_Statements (Loc, Statements => Stmts); |
| end Protected_Component_Ref; |
| end if; |
| |
| -- Make an unprotected version of the subprogram for use within the same |
| -- object, with new name and extra parameter representing the object. |
| |
| return |
| Make_Subprogram_Body (Loc, |
| Specification => |
| Build_Protected_Sub_Specification (N, Prot_Typ, Unprotected_Mode), |
| Declarations => Decls, |
| Handled_Statement_Sequence => Hand_Stmt_Seq); |
| end Build_Lock_Free_Unprotected_Subprogram_Body; |
| |
| ------------------------- |
| -- Build_Master_Entity -- |
| ------------------------- |
| |
| procedure Build_Master_Entity (Obj_Or_Typ : Entity_Id) is |
| Loc : constant Source_Ptr := Sloc (Obj_Or_Typ); |
| Context : Node_Id; |
| Context_Id : Entity_Id; |
| Decl : Node_Id; |
| Decls : List_Id; |
| Par : Node_Id; |
| |
| begin |
| if Is_Itype (Obj_Or_Typ) then |
| Par := Associated_Node_For_Itype (Obj_Or_Typ); |
| else |
| Par := Parent (Obj_Or_Typ); |
| end if; |
| |
| -- When creating a master for a record component which is either a task |
| -- or access-to-task, the enclosing record is the master scope and the |
| -- proper insertion point is the component list. |
| |
| if Is_Record_Type (Current_Scope) then |
| Context := Par; |
| Context_Id := Current_Scope; |
| Decls := List_Containing (Context); |
| |
| -- Default case for object declarations and access types. Note that the |
| -- context is updated to the nearest enclosing body, block, package or |
| -- return statement. |
| |
| else |
| Find_Enclosing_Context (Par, Context, Context_Id, Decls); |
| end if; |
| |
| -- Do not create a master if one already exists or there is no task |
| -- hierarchy. |
| |
| if Has_Master_Entity (Context_Id) |
| or else Restriction_Active (No_Task_Hierarchy) |
| then |
| return; |
| end if; |
| |
| -- Create a master, generate: |
| -- _Master : constant Master_Id := Current_Master.all; |
| |
| Decl := |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => |
| Make_Defining_Identifier (Loc, Name_uMaster), |
| Constant_Present => True, |
| Object_Definition => New_Occurrence_Of (RTE (RE_Master_Id), Loc), |
| Expression => |
| Make_Explicit_Dereference (Loc, |
| New_Occurrence_Of (RTE (RE_Current_Master), Loc))); |
| |
| -- The master is inserted at the start of the declarative list of the |
| -- context. |
| |
| Prepend_To (Decls, Decl); |
| |
| -- In certain cases where transient scopes are involved, the immediate |
| -- scope is not always the proper master scope. Ensure that the master |
| -- declaration and entity appear in the same context. |
| |
| if Context_Id /= Current_Scope then |
| Push_Scope (Context_Id); |
| Analyze (Decl); |
| Pop_Scope; |
| else |
| Analyze (Decl); |
| end if; |
| |
| -- Mark the enclosing scope and its associated construct as being task |
| -- masters. |
| |
| Set_Has_Master_Entity (Context_Id); |
| |
| while Present (Context) |
| and then Nkind (Context) /= N_Compilation_Unit |
| loop |
| if Nkind_In (Context, N_Block_Statement, |
| N_Subprogram_Body, |
| N_Task_Body) |
| then |
| Set_Is_Task_Master (Context); |
| exit; |
| |
| elsif Nkind (Parent (Context)) = N_Subunit then |
| Context := Corresponding_Stub (Parent (Context)); |
| end if; |
| |
| Context := Parent (Context); |
| end loop; |
| end Build_Master_Entity; |
| |
| --------------------------- |
| -- Build_Master_Renaming -- |
| --------------------------- |
| |
| procedure Build_Master_Renaming |
| (Ptr_Typ : Entity_Id; |
| Ins_Nod : Node_Id := Empty) |
| is |
| Loc : constant Source_Ptr := Sloc (Ptr_Typ); |
| Context : Node_Id; |
| Master_Decl : Node_Id; |
| Master_Id : Entity_Id; |
| |
| begin |
| -- Nothing to do if there is no task hierarchy |
| |
| if Restriction_Active (No_Task_Hierarchy) then |
| return; |
| end if; |
| |
| -- Determine the proper context to insert the master renaming |
| |
| if Present (Ins_Nod) then |
| Context := Ins_Nod; |
| elsif Is_Itype (Ptr_Typ) then |
| Context := Associated_Node_For_Itype (Ptr_Typ); |
| else |
| Context := Parent (Ptr_Typ); |
| end if; |
| |
| -- Generate: |
| -- <Ptr_Typ>M : Master_Id renames _Master; |
| |
| Master_Id := |
| Make_Defining_Identifier (Loc, |
| New_External_Name (Chars (Ptr_Typ), 'M')); |
| |
| Master_Decl := |
| Make_Object_Renaming_Declaration (Loc, |
| Defining_Identifier => Master_Id, |
| Subtype_Mark => New_Occurrence_Of (RTE (RE_Master_Id), Loc), |
| Name => Make_Identifier (Loc, Name_uMaster)); |
| |
| Insert_Action (Context, Master_Decl); |
| |
| -- The renamed master now services the access type |
| |
| Set_Master_Id (Ptr_Typ, Master_Id); |
| end Build_Master_Renaming; |
| |
| ----------------------------------------- |
| -- Build_Private_Protected_Declaration -- |
| ----------------------------------------- |
| |
| function Build_Private_Protected_Declaration |
| (N : Node_Id) return Entity_Id |
| is |
| Loc : constant Source_Ptr := Sloc (N); |
| Body_Id : constant Entity_Id := Defining_Entity (N); |
| Decl : Node_Id; |
| Plist : List_Id; |
| Formal : Entity_Id; |
| New_Spec : Node_Id; |
| Spec_Id : Entity_Id; |
| |
| begin |
| Formal := First_Formal (Body_Id); |
| |
| -- The protected operation always has at least one formal, namely the |
| -- object itself, but it is only placed in the parameter list if |
| -- expansion is enabled. |
| |
| if Present (Formal) or else Expander_Active then |
| Plist := Copy_Parameter_List (Body_Id); |
| else |
| Plist := No_List; |
| end if; |
| |
| if Nkind (Specification (N)) = N_Procedure_Specification then |
| New_Spec := |
| Make_Procedure_Specification (Loc, |
| Defining_Unit_Name => |
| Make_Defining_Identifier (Sloc (Body_Id), |
| Chars => Chars (Body_Id)), |
| Parameter_Specifications => |
| Plist); |
| else |
| New_Spec := |
| Make_Function_Specification (Loc, |
| Defining_Unit_Name => |
| Make_Defining_Identifier (Sloc (Body_Id), |
| Chars => Chars (Body_Id)), |
| Parameter_Specifications => Plist, |
| Result_Definition => |
| New_Occurrence_Of (Etype (Body_Id), Loc)); |
| end if; |
| |
| Decl := Make_Subprogram_Declaration (Loc, Specification => New_Spec); |
| Insert_Before (N, Decl); |
| Spec_Id := Defining_Unit_Name (New_Spec); |
| |
| -- Indicate that the entity comes from source, to ensure that cross- |
| -- reference information is properly generated. The body itself is |
| -- rewritten during expansion, and the body entity will not appear in |
| -- calls to the operation. |
| |
| Set_Comes_From_Source (Spec_Id, True); |
| Analyze (Decl); |
| Set_Has_Completion (Spec_Id); |
| Set_Convention (Spec_Id, Convention_Protected); |
| return Spec_Id; |
| end Build_Private_Protected_Declaration; |
| |
| --------------------------- |
| -- Build_Protected_Entry -- |
| --------------------------- |
| |
| function Build_Protected_Entry |
| (N : Node_Id; |
| Ent : Entity_Id; |
| Pid : Node_Id) return Node_Id |
| is |
| Loc : constant Source_Ptr := Sloc (N); |
| |
| Decls : constant List_Id := Declarations (N); |
| End_Lab : constant Node_Id := |
| End_Label (Handled_Statement_Sequence (N)); |
| End_Loc : constant Source_Ptr := |
| Sloc (Last (Statements (Handled_Statement_Sequence (N)))); |
| -- Used for the generated call to Complete_Entry_Body |
| |
| Han_Loc : Source_Ptr; |
| -- Used for the exception handler, inserted at end of the body |
| |
| Op_Decls : constant List_Id := New_List; |
| Complete : Node_Id; |
| Edef : Entity_Id; |
| Espec : Node_Id; |
| Ohandle : Node_Id; |
| Op_Stats : List_Id; |
| |
| begin |
| -- Set the source location on the exception handler only when debugging |
| -- the expanded code (see Make_Implicit_Exception_Handler). |
| |
| if Debug_Generated_Code then |
| Han_Loc := End_Loc; |
| |
| -- Otherwise the inserted code should not be visible to the debugger |
| |
| else |
| Han_Loc := No_Location; |
| end if; |
| |
| Edef := |
| Make_Defining_Identifier (Loc, |
| Chars => Chars (Protected_Body_Subprogram (Ent))); |
| Espec := |
| Build_Protected_Entry_Specification (Loc, Edef, Empty); |
| |
| -- Add the following declarations: |
| |
| -- type poVP is access poV; |
| -- _object : poVP := poVP (_O); |
| |
| -- where _O is the formal parameter associated with the concurrent |
| -- object. These declarations are needed for Complete_Entry_Body. |
| |
| Add_Object_Pointer (Loc, Pid, Op_Decls); |
| |
| -- Add renamings for all formals, the Protection object, discriminals, |
| -- privals and the entry index constant for use by debugger. |
| |
| Add_Formal_Renamings (Espec, Op_Decls, Ent, Loc); |
| Debug_Private_Data_Declarations (Decls); |
| |
| -- Put the declarations and the statements from the entry |
| |
| Op_Stats := |
| New_List ( |
| Make_Block_Statement (Loc, |
| Declarations => Decls, |
| Handled_Statement_Sequence => |
| Handled_Statement_Sequence (N))); |
| |
| case Corresponding_Runtime_Package (Pid) is |
| when System_Tasking_Protected_Objects_Entries => |
| Append_To (Op_Stats, |
| Make_Procedure_Call_Statement (End_Loc, |
| Name => |
| New_Occurrence_Of (RTE (RE_Complete_Entry_Body), Loc), |
| Parameter_Associations => New_List ( |
| Make_Attribute_Reference (End_Loc, |
| Prefix => |
| Make_Selected_Component (End_Loc, |
| Prefix => |
| Make_Identifier (End_Loc, Name_uObject), |
| Selector_Name => |
| Make_Identifier (End_Loc, Name_uObject)), |
| Attribute_Name => Name_Unchecked_Access)))); |
| |
| when System_Tasking_Protected_Objects_Single_Entry => |
| |
| -- Historically, a call to Complete_Single_Entry_Body was |
| -- inserted, but it was a null procedure. |
| |
| null; |
| |
| when others => |
| raise Program_Error; |
| end case; |
| |
| -- When exceptions can not be propagated, we never need to call |
| -- Exception_Complete_Entry_Body |
| |
| if No_Exception_Handlers_Set then |
| return |
| Make_Subprogram_Body (Loc, |
| Specification => Espec, |
| Declarations => Op_Decls, |
| Handled_Statement_Sequence => |
| Make_Handled_Sequence_Of_Statements (Loc, |
| Statements => Op_Stats, |
| End_Label => End_Lab)); |
| |
| else |
| Ohandle := Make_Others_Choice (Loc); |
| Set_All_Others (Ohandle); |
| |
| case Corresponding_Runtime_Package (Pid) is |
| when System_Tasking_Protected_Objects_Entries => |
| Complete := |
| New_Occurrence_Of |
| (RTE (RE_Exceptional_Complete_Entry_Body), Loc); |
| |
| when System_Tasking_Protected_Objects_Single_Entry => |
| Complete := |
| New_Occurrence_Of |
| (RTE (RE_Exceptional_Complete_Single_Entry_Body), Loc); |
| |
| when others => |
| raise Program_Error; |
| end case; |
| |
| -- Establish link between subprogram body entity and source entry |
| |
| Set_Corresponding_Protected_Entry (Edef, Ent); |
| |
| -- Create body of entry procedure. The renaming declarations are |
| -- placed ahead of the block that contains the actual entry body. |
| |
| return |
| Make_Subprogram_Body (Loc, |
| Specification => Espec, |
| Declarations => Op_Decls, |
| Handled_Statement_Sequence => |
| Make_Handled_Sequence_Of_Statements (Loc, |
| Statements => Op_Stats, |
| End_Label => End_Lab, |
| Exception_Handlers => New_List ( |
| Make_Implicit_Exception_Handler (Han_Loc, |
| Exception_Choices => New_List (Ohandle), |
| |
| Statements => New_List ( |
| Make_Procedure_Call_Statement (Han_Loc, |
| Name => Complete, |
| Parameter_Associations => New_List ( |
| Make_Attribute_Reference (Han_Loc, |
| Prefix => |
| Make_Selected_Component (Han_Loc, |
| Prefix => |
| Make_Identifier (Han_Loc, Name_uObject), |
| Selector_Name => |
| Make_Identifier (Han_Loc, Name_uObject)), |
| Attribute_Name => Name_Unchecked_Access), |
| |
| Make_Function_Call (Han_Loc, |
| Name => New_Occurrence_Of ( |
| RTE (RE_Get_GNAT_Exception), Loc))))))))); |
| end if; |
| end Build_Protected_Entry; |
| |
| ----------------------------------------- |
| -- Build_Protected_Entry_Specification -- |
| ----------------------------------------- |
| |
| function Build_Protected_Entry_Specification |
| (Loc : Source_Ptr; |
| Def_Id : Entity_Id; |
| Ent_Id : Entity_Id) return Node_Id |
| is |
| P : constant Entity_Id := Make_Defining_Identifier (Loc, Name_uP); |
| |
| begin |
| Set_Debug_Info_Needed (Def_Id); |
| |
| if Present (Ent_Id) then |
| Append_Elmt (P, Accept_Address (Ent_Id)); |
| end if; |
| |
| return |
| Make_Procedure_Specification (Loc, |
| Defining_Unit_Name => Def_Id, |
| Parameter_Specifications => New_List ( |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => |
| Make_Defining_Identifier (Loc, Name_uO), |
| Parameter_Type => |
| New_Occurrence_Of (RTE (RE_Address), Loc)), |
| |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => P, |
| Parameter_Type => |
| New_Occurrence_Of (RTE (RE_Address), Loc)), |
| |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => |
| Make_Defining_Identifier (Loc, Name_uE), |
| Parameter_Type => |
| New_Occurrence_Of (RTE (RE_Protected_Entry_Index), Loc)))); |
| end Build_Protected_Entry_Specification; |
| |
| -------------------------- |
| -- Build_Protected_Spec -- |
| -------------------------- |
| |
| function Build_Protected_Spec |
| (N : Node_Id; |
| Obj_Type : Entity_Id; |
| Ident : Entity_Id; |
| Unprotected : Boolean := False) return List_Id |
| is |
| Loc : constant Source_Ptr := Sloc (N); |
| Decl : Node_Id; |
| Formal : Entity_Id; |
| New_Plist : List_Id; |
| New_Param : Node_Id; |
| |
| begin |
| New_Plist := New_List; |
| |
| Formal := First_Formal (Ident); |
| while Present (Formal) loop |
| New_Param := |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => |
| Make_Defining_Identifier (Sloc (Formal), Chars (Formal)), |
| Aliased_Present => Aliased_Present (Parent (Formal)), |
| In_Present => In_Present (Parent (Formal)), |
| Out_Present => Out_Present (Parent (Formal)), |
| Parameter_Type => New_Occurrence_Of (Etype (Formal), Loc)); |
| |
| if Unprotected then |
| Set_Protected_Formal (Formal, Defining_Identifier (New_Param)); |
| end if; |
| |
| Append (New_Param, New_Plist); |
| Next_Formal (Formal); |
| end loop; |
| |
| -- If the subprogram is a procedure and the context is not an access |
| -- to protected subprogram, the parameter is in-out. Otherwise it is |
| -- an in parameter. |
| |
| Decl := |
| Make_Parameter_Specification (Loc, |
| Defining_Identifier => |
| Make_Defining_Identifier (Loc, Name_uObject), |
| In_Present => True, |
| Out_Present => |
| (Etype (Ident) = Standard_Void_Type |
| and then not Is_RTE (Obj_Type, RE_Address)), |
| Parameter_Type => |
| New_Occurrence_Of (Obj_Type, Loc)); |
| Set_Debug_Info_Needed (Defining_Identifier (Decl)); |
| Prepend_To (New_Plist, Decl); |
| |
| return New_Plist; |
| end Build_Protected_Spec; |
| |
| --------------------------------------- |
| -- Build_Protected_Sub_Specification -- |
| --------------------------------------- |
| |
| function Build_Protected_Sub_Specification |
| (N : Node_Id; |
| Prot_Typ : Entity_Id; |
| Mode : Subprogram_Protection_Mode) return Node_Id |
| is |
| Loc : constant Source_Ptr := Sloc (N); |
| Decl : Node_Id; |
| Def_Id : Entity_Id; |
| New_Id : Entity_Id; |
| New_Plist : List_Id; |
| New_Spec : Node_Id; |
| |
| Append_Chr : constant array (Subprogram_Protection_Mode) of Character := |
| (Dispatching_Mode => ' ', |
| Protected_Mode => 'P', |
| Unprotected_Mode => 'N'); |
| |
| begin |
| if Ekind (Defining_Unit_Name (Specification (N))) = |
| E_Subprogram_Body |
| then |
| Decl := Unit_Declaration_Node (Corresponding_Spec (N)); |
| else |
| Decl := N; |
| end if; |
| |
| Def_Id := Defining_Unit_Name (Specification (Decl)); |
| |
| New_Plist := |
| Build_Protected_Spec |
| (Decl, Corresponding_Record_Type (Prot_Typ), Def_Id, |
| Mode = Unprotected_Mode); |
| New_Id := |
| Make_Defining_Identifier (Loc, |
| Chars => Build_Selected_Name (Prot_Typ, Def_Id, Append_Chr (Mode))); |
| |
| -- The unprotected operation carries the user code, and debugging |
| -- information must be generated for it, even though this spec does |
| -- not come from source. It is also convenient to allow gdb to step |
| -- into the protected operation, even though it only contains lock/ |
| -- unlock calls. |
| |
| Set_Debug_Info_Needed (New_Id); |
| |
| -- If a pragma Eliminate applies to the source entity, the internal |
| -- subprograms will be eliminated as well. |
| |
| Set_Is_Eliminated (New_Id, Is_Eliminated (Def_Id)); |
| |
| if Nkind (Specification (Decl)) = N_Procedure_Specification then |
| New_Spec := |
| Make_Procedure_Specification (Loc, |
| Defining_Unit_Name => New_Id, |
| Parameter_Specifications => New_Plist); |
| |
| -- Create a new specification for the anonymous subprogram type |
| |
| else |
| New_Spec := |
| Make_Function_Specification (Loc, |
| Defining_Unit_Name => New_Id, |
| Parameter_Specifications => New_Plist, |
| Result_Definition => |
| Copy_Result_Type (Result_Definition (Specification (Decl)))); |
| |
| Set_Return_Present (Defining_Unit_Name (New_Spec)); |
| end if; |
| |
| return New_Spec; |
| end Build_Protected_Sub_Specification; |
| |
| ------------------------------------- |
| -- Build_Protected_Subprogram_Body -- |
| ------------------------------------- |
| |
| function Build_Protected_Subprogram_Body |
| (N : Node_Id; |
| Pid : Node_Id; |
| N_Op_Spec : Node_Id) return Node_Id |
| is |
| Loc : constant Source_Ptr := Sloc (N); |
| Op_Spec : Node_Id; |
| P_Op_Spec : Node_Id; |
| Uactuals : List_Id; |
| Pformal : Node_Id; |
| Unprot_Call : Node_Id; |
| Sub_Body : Node_Id; |
| Lock_Name : Node_Id; |
| Lock_Stmt : Node_Id; |
| R : Node_Id; |
| Return_Stmt : Node_Id := Empty; -- init to avoid gcc 3 warning |
| Pre_Stmts : List_Id := No_List; -- init to avoid gcc 3 warning |
| Stmts : List_Id; |
| Object_Parm : Node_Id; |
| Exc_Safe : Boolean; |
| Lock_Kind : RE_Id; |
| |
| begin |
| Op_Spec := Specification (N); |
| Exc_Safe := Is_Exception_Safe (N); |
| |
| P_Op_Spec := |
| Build_Protected_Sub_Specification (N, Pid, Protected_Mode); |
| |
| -- Build a list of the formal parameters of the protected version of |
| -- the subprogram to use as the actual parameters of the unprotected |
| -- version. |
| |
| Uactuals := New_List; |
| Pformal := First (Parameter_Specifications (P_Op_Spec)); |
| while Present (Pformal) loop |
| Append_To (Uactuals, |
| Make_Identifier (Loc, Chars (Defining_Identifier (Pformal)))); |
| Next (Pformal); |
| end loop; |
| |
| -- Make a call to the unprotected version of the subprogram built above |
| -- for use by the protected version built below. |
| |
| if Nkind (Op_Spec) = N_Function_Specification then |
| if Exc_Safe then |
| R := Make_Temporary (Loc, 'R'); |
| Unprot_Call := |
| Make_Object_Declaration (Loc, |
| Defining_Identifier => R, |
| Constant_Present => True, |
| Object_Definition => New_Copy (Result_Definition (N_Op_Spec)), |
| Expression => |
| Make_Function_Call (Loc, |
| Name => Make_Identifier (Loc, |
| Chars => Chars (Defining_Unit_Name (N_Op_Spec))), |
| Parameter_Associations => Uactuals)); |
| |
| Return_Stmt := |
| Make_Simple_Return_Statement (Loc, |
| Expression => New_Occurrence_Of (R, Loc)); |
| |
| else |
| Unprot_Call := Make_Simple_Return_Statement (Loc, |
| Expression => Make_Function_Call (Loc, |
| Name => |
| Make_Identifier (Loc, |
| Chars => Chars (Defining_Unit_Name (N_Op_Spec))), |
| Parameter_Associations => Uactuals)); |
| end if; |
| |
| Lock_Kind := RE_Lock_Read_Only; |
| |
| else |
| Unprot_Call := |
| Make_Procedure_Call_Statement (Loc, |
| Name => |
| Make_Identifier (Loc, Chars (Defining_Unit_Name (N_Op_Spec))), |
| Parameter_Associations => Uactuals); |
| |
| Lock_Kind := RE_Lock; |
| end if; |
| |
| -- Wrap call in block that will be covered by an at_end handler |
| |
| if not Exc_Safe then |
| Unprot_Call := Make_Block_Statement (Loc, |
| Handled_Statement_Sequence => |
| Make_Handled_Sequence_Of_Statements (Loc, |
| Statements => New_List (Unprot_Call))); |
| end if; |
| |
| -- Make the protected subprogram body. This locks the protected |
| -- object and calls the unprotected version of the subprogram. |
| |
| case Corresponding_Runtime_Package (Pid) is |
| when System_Tasking_Protected_Objects_Entries => |
| Lock_Name := New_Occurrence_Of (RTE (RE_Lock_Entries), Loc); |
| |
| when System_Tasking_Protected_Objects_Single_Entry => |
| Lock_Name := New_Occurrence_Of (RTE (RE_Lock_Entry), Loc); |
| |
| when System_Tasking_Protected_Objects => |
| Lock_Name := New_Occurrence_Of (RTE (Lock_Kind), Loc); |
| |
| when others => |
| raise Program_Error; |
| end case; |
| |
| Object_Parm := |
| Make_Attribute_Reference (Loc, |
| Prefix => |
| Make_Selected_Component (Loc, |
| Prefix => Make_Identifier (Loc, Name_uObject), |
| Selector_Name => Make_Identifier (Loc, Name_uObject)), |
| Attribute_Name => Name_Unchecked_Access); |
| |
| Lock_Stmt := Make_Procedure_Call_Statement (Loc, |
| Name => Lock_Name, |
| Parameter_Associations => New_List (Object_Parm)); |
| |
| if Abort_Allowed then |
| Stmts := New_List ( |
| Make_Procedure_Call_Statement (Loc, |
| Name => New_Occurrence_Of (RTE (RE_Abort_Defer), Loc), |
| Parameter_Associations => Empty_List), |
| Lock_Stmt); |
| |
| else |
| Stmts := New_List (Lock_Stmt); |
| end if; |
| |
| if not Exc_Safe then |
| |