X-Git-Url: http://git.sourceforge.jp/view?a=blobdiff_plain;f=gcc%2Fada%2Fsem_ch12.adb;h=d3eb0f8962f306733d7e829f89463b346d82d2dd;hb=0c1fe26b5f780a30fd26e3e3075764f99322dbbf;hp=59e3bec5dfa56f168619fbb7621e85b2b4b5cd2b;hpb=856029ac2930d7624ee6dfcafa84fa38c062a636;p=pf3gnuchains%2Fgcc-fork.git diff --git a/gcc/ada/sem_ch12.adb b/gcc/ada/sem_ch12.adb index 59e3bec5dfa..d3eb0f8962f 100644 --- a/gcc/ada/sem_ch12.adb +++ b/gcc/ada/sem_ch12.adb @@ -6,7 +6,7 @@ -- -- -- B o d y -- -- -- --- Copyright (C) 1992-2004, Free Software Foundation, Inc. -- +-- Copyright (C) 1992-2007, 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- -- @@ -16,8 +16,8 @@ -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License -- -- for more details. You should have received a copy of the GNU General -- -- Public License distributed with GNAT; see file COPYING. If not, write -- --- to the Free Software Foundation, 59 Temple Place - Suite 330, Boston, -- --- MA 02111-1307, USA. -- +-- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, -- +-- Boston, MA 02110-1301, USA. -- -- -- -- GNAT was originally developed by the GNAT team at New York University. -- -- Extensive contributions were provided by Ada Core Technologies Inc. -- @@ -33,11 +33,11 @@ with Fname; use Fname; with Fname.UF; use Fname.UF; with Freeze; use Freeze; with Hostparm; -with Inline; use Inline; with Lib; use Lib; with Lib.Load; use Lib.Load; with Lib.Xref; use Lib.Xref; with Nlists; use Nlists; +with Namet; use Namet; with Nmake; use Nmake; with Opt; use Opt; with Rident; use Rident; @@ -51,6 +51,7 @@ with Sem_Ch7; use Sem_Ch7; with Sem_Ch8; use Sem_Ch8; with Sem_Ch10; use Sem_Ch10; with Sem_Ch13; use Sem_Ch13; +with Sem_Disp; use Sem_Disp; with Sem_Elab; use Sem_Elab; with Sem_Elim; use Sem_Elim; with Sem_Eval; use Sem_Eval; @@ -77,13 +78,13 @@ package body Sem_Ch12 is ---------------------------------------------------------- -- Implementation of Generic Analysis and Instantiation -- - ----------------------------------------------------------- + ---------------------------------------------------------- - -- GNAT implements generics by macro expansion. No attempt is made to - -- share generic instantiations (for now). Analysis of a generic definition - -- does not perform any expansion action, but the expander must be called - -- on the tree for each instantiation, because the expansion may of course - -- depend on the generic actuals. All of this is best achieved as follows: + -- GNAT implements generics by macro expansion. No attempt is made to share + -- generic instantiations (for now). Analysis of a generic definition does + -- not perform any expansion action, but the expander must be called on the + -- tree for each instantiation, because the expansion may of course depend + -- on the generic actuals. All of this is best achieved as follows: -- -- a) Semantic analysis of a generic unit is performed on a copy of the -- tree for the generic unit. All tree modifications that follow analysis @@ -92,7 +93,7 @@ package body Sem_Ch12 is -- the generic, and propagate them to each instance (recall that name -- resolution is done on the generic declaration: generics are not really -- macros!). This is summarized in the following diagram: - -- + -- .-----------. .----------. -- | semantic |<--------------| generic | -- | copy | | unit | @@ -107,13 +108,13 @@ package body Sem_Ch12 is -- |__| | | -- |__| instance | -- |__________| - -- + -- b) Each instantiation copies the original tree, and inserts into it a -- series of declarations that describe the mapping between generic formals -- and actuals. For example, a generic In OUT parameter is an object -- renaming of the corresponing actual, etc. Generic IN parameters are -- constant declarations. - -- + -- c) In order to give the right visibility for these renamings, we use -- a different scheme for package and subprogram instantiations. For -- packages, the list of renamings is inserted into the package @@ -153,16 +154,16 @@ package body Sem_Ch12 is -- Visibility within nested generic units requires special handling. -- Consider the following scheme: - -- + -- type Global is ... -- outside of generic unit. -- generic ... -- package Outer is -- ... -- type Semi_Global is ... -- global to inner. - -- + -- generic ... -- 1 -- procedure inner (X1 : Global; X2 : Semi_Global); - -- + -- procedure in2 is new inner (...); -- 4 -- end Outer; @@ -220,31 +221,78 @@ package body Sem_Ch12 is -- Detection of Instantiation Circularities -- ---------------------------------------------- - -- If we have a chain of instantiations that is circular, this is a - -- static error which must be detected at compile time. The detection - -- of these circularities is carried out at the point that we insert - -- a generic instance spec or body. If there is a circularity, then - -- the analysis of the offending spec or body will eventually result - -- in trying to load the same unit again, and we detect this problem - -- as we analyze the package instantiation for the second time. + -- If we have a chain of instantiations that is circular, this is static + -- error which must be detected at compile time. The detection of these + -- circularities is carried out at the point that we insert a generic + -- instance spec or body. If there is a circularity, then the analysis of + -- the offending spec or body will eventually result in trying to load the + -- same unit again, and we detect this problem as we analyze the package + -- instantiation for the second time. - -- At least in some cases after we have detected the circularity, we - -- get into trouble if we try to keep going. The following flag is - -- set if a circularity is detected, and used to abandon compilation - -- after the messages have been posted. + -- At least in some cases after we have detected the circularity, we get + -- into trouble if we try to keep going. The following flag is set if a + -- circularity is detected, and used to abandon compilation after the + -- messages have been posted. Circularity_Detected : Boolean := False; -- This should really be reset on encountering a new main unit, but in -- practice we are not using multiple main units so it is not critical. + ------------------------------------------------- + -- Formal packages and partial parametrization -- + ------------------------------------------------- + + -- When compiling a generic, a formal package is a local instantiation. If + -- declared with a box, its generic formals are visible in the enclosing + -- generic. If declared with a partial list of actuals, those actuals that + -- are defaulted (covered by an Others clause, or given an explicit box + -- initialization) are also visible in the enclosing generic, while those + -- that have a corresponding actual are not. + + -- In our source model of instantiation, the same visibility must be + -- present in the spec and body of an instance: the names of the formals + -- that are defaulted must be made visible within the instance, and made + -- invisible (hidden) after the instantiation is complete, so that they + -- are not accessible outside of the instance. + + -- In a generic, a formal package is treated like a special instantiation. + -- Our Ada95 compiler handled formals with and without box in different + -- ways. With partial parametrization, we use a single model for both. + -- We create a package declaration that consists of the specification of + -- the generic package, and a set of declarations that map the actuals + -- into local renamings, just as we do for bona fide instantiations. For + -- defaulted parameters and formals with a box, we copy directly the + -- declarations of the formal into this local package. The result is a + -- a package whose visible declarations may include generic formals. This + -- package is only used for type checking and visibility analysis, and + -- never reaches the back-end, so it can freely violate the placement + -- rules for generic formal declarations. + + -- The list of declarations (renamings and copies of formals) is built + -- by Analyze_Associations, just as for regular instantiations. + + -- At the point of instantiation, conformance checking must be applied only + -- to those parameters that were specified in the formal. We perform this + -- checking by creating another internal instantiation, this one including + -- only the renamings and the formals (the rest of the package spec is not + -- relevant to conformance checking). We can then traverse two lists: the + -- list of actuals in the instance that corresponds to the formal package, + -- and the list of actuals produced for this bogus instantiation. We apply + -- the conformance rules to those actuals that are not defaulted (i.e. + -- which still appear as generic formals. + + -- When we compile an instance body we must make the right parameters + -- visible again. The predicate Is_Generic_Formal indicates which of the + -- formals should have its Is_Hidden flag reset. + ----------------------- -- Local subprograms -- ----------------------- procedure Abandon_Instantiation (N : Node_Id); pragma No_Return (Abandon_Instantiation); - -- Posts an error message "instantiation abandoned" at the indicated - -- node and then raises the exception Instantiation_Error to do it. + -- Posts an error message "instantiation abandoned" at the indicated node + -- and then raises the exception Instantiation_Error to do it. procedure Analyze_Formal_Array_Type (T : in out Entity_Id; @@ -254,14 +302,28 @@ package body Sem_Ch12 is -- in-out, because in the case of an anonymous type the entity is -- actually created in the procedure. - -- The following procedures treat other kinds of formal parameters. + -- The following procedures treat other kinds of formal parameters + + procedure Analyze_Formal_Derived_Interface_Type + (N : Node_Id; + T : Entity_Id; + Def : Node_Id); procedure Analyze_Formal_Derived_Type (N : Node_Id; T : Entity_Id; Def : Node_Id); - -- All the following need comments??? + procedure Analyze_Formal_Interface_Type + (N : Node_Id; + T : Entity_Id; + Def : Node_Id); + + -- The following subprograms create abbreviated declarations for formal + -- scalar types. We introduce an anonymous base of the proper class for + -- each of them, and define the formals as constrained first subtypes of + -- their bases. The bounds are expressions that are non-static in the + -- generic. procedure Analyze_Formal_Decimal_Fixed_Point_Type (T : Entity_Id; Def : Node_Id); @@ -276,12 +338,12 @@ package body Sem_Ch12 is (N : Node_Id; T : Entity_Id; Def : Node_Id); - -- This needs comments??? + -- Creates a new private type, which does not require completion procedure Analyze_Generic_Formal_Part (N : Node_Id); procedure Analyze_Generic_Access_Type (T : Entity_Id; Def : Node_Id); - -- This needs comments ??? + -- Create a new access type with the given designated type function Analyze_Associations (I_Node : Node_Id; @@ -311,8 +373,12 @@ package body Sem_Ch12 is -- nodes or subprogram body and declaration nodes depending on the case). -- On return, the node N has been rewritten with the actual body. + procedure Check_Access_Definition (N : Node_Id); + -- Subsidiary routine to null exclusion processing. Perform an assertion + -- check on Ada version and the presence of an access definition in N. + procedure Check_Formal_Packages (P_Id : Entity_Id); - -- Apply the following to all formal packages in generic associations. + -- Apply the following to all formal packages in generic associations procedure Check_Formal_Package_Instance (Formal_Pack : Entity_Id; @@ -335,16 +401,6 @@ package body Sem_Ch12 is -- instance, we need to make an explicit test that it is not hidden by -- a child instance of the same name and parent. - procedure Check_Private_View (N : Node_Id); - -- Check whether the type of a generic entity has a different view between - -- the point of generic analysis and the point of instantiation. If the - -- view has changed, then at the point of instantiation we restore the - -- correct view to perform semantic analysis of the instance, and reset - -- the current view after instantiation. The processing is driven by the - -- current private status of the type of the node, and Has_Private_View, - -- a flag that is set at the point of generic compilation. If view and - -- flag are inconsistent then the type is updated appropriately. - procedure Check_Generic_Actuals (Instance : Entity_Id; Is_Formal_Box : Boolean); @@ -383,13 +439,14 @@ package body Sem_Ch12 is -- When validating the actual types of a child instance, check whether -- the formal is a formal type of the parent unit, and retrieve the current -- actual for it. Typ is the entity in the analyzed formal type declaration - -- (component or index type of an array type) and Gen_Scope is the scope of - -- the analyzed formal array type. - - function Get_Package_Instantiation_Node (A : Entity_Id) return Node_Id; - -- Given the entity of a unit that is an instantiation, retrieve the - -- original instance node. This is used when loading the instantiations - -- of the ancestors of a child generic that is being instantiated. + -- (component or index type of an array type, or designated type of an + -- access formal) and Gen_Scope is the scope of the analyzed formal array + -- or access type. The desired actual may be a formal of a parent, or may + -- be declared in a formal package of a parent. In both cases it is a + -- generic actual type because it appears within a visible instance. + -- Ambiguities may still arise if two homonyms are declared in two formal + -- packages, and the prefix of the formal type may be needed to resolve + -- the ambiguity in the instance ??? function In_Same_Declarative_Part (F_Node : Node_Id; @@ -400,12 +457,26 @@ package body Sem_Ch12 is -- of the instance can be placed after the freeze node of the parent, -- which it itself an instance. + function In_Main_Context (E : Entity_Id) return Boolean; + -- Check whether an instantiation is in the context of the main unit. + -- Used to determine whether its body should be elaborated to allow + -- front-end inlining. + + function Is_Generic_Formal (E : Entity_Id) return Boolean; + -- Utility to determine whether a given entity is declared by means of + -- of a formal parameter declaration. Used to set properly the visiblity + -- of generic formals of a generic package declared with a box or with + -- partial parametrization. + procedure Set_Instance_Env (Gen_Unit : Entity_Id; Act_Unit : Entity_Id); -- Save current instance on saved environment, to be used to determine -- the global status of entities in nested instances. Part of Save_Env. - -- called after verifying that the generic unit is legal for the instance. + -- called after verifying that the generic unit is legal for the instance, + -- The procedure also examines whether the generic unit is a predefined + -- unit, in order to set configuration switches accordingly. As a result + -- the procedure must be called after analyzing and freezing the actuals. procedure Set_Instance_Of (A : Entity_Id; B : Entity_Id); -- Associate analyzed generic parameter with corresponding @@ -461,15 +532,23 @@ package body Sem_Ch12 is -- Save_Env because data-structures for visibility handling must be -- initialized before call to Check_Generic_Child_Unit. + procedure Install_Formal_Packages (Par : Entity_Id); + -- If any of the formals of the parent are formal packages with box, + -- their formal parts are visible in the parent and thus in the child + -- unit as well. Analogous to what is done in Check_Generic_Actuals + -- for the unit itself. This procedure is also used in an instance, to + -- make visible the proper entities of the actual for a formal package + -- declared with a box. + procedure Install_Parent (P : Entity_Id; In_Body : Boolean := False); -- When compiling an instance of a child unit the parent (which is -- itself an instance) is an enclosing scope that must be made -- immediately visible. This procedure is also used to install the non- - -- generic parent of a generic child unit when compiling its body, so that - -- full views of types in the parent are made visible. + -- generic parent of a generic child unit when compiling its body, so + -- that full views of types in the parent are made visible. procedure Remove_Parent (In_Body : Boolean := False); - -- Reverse effect after instantiation of child is complete. + -- Reverse effect after instantiation of child is complete procedure Inline_Instance_Body (N : Node_Id; @@ -480,8 +559,11 @@ package body Sem_Ch12 is -- that successive instantiations succeed. -- The functions Instantiate_XXX perform various legality checks and build - -- the declarations for instantiated generic parameters. - -- Need to describe what the parameters are ??? + -- the declarations for instantiated generic parameters. In all of these + -- Formal is the entity in the generic unit, Actual is the entity of + -- expression in the generic associations, and Analyzed_Formal is the + -- formal in the generic copy, which contains the semantic information to + -- be used to validate the actual. function Instantiate_Object (Formal : Node_Id; @@ -492,7 +574,7 @@ package body Sem_Ch12 is (Formal : Node_Id; Actual : Node_Id; Analyzed_Formal : Node_Id; - Actual_Decls : List_Id) return Node_Id; + Actual_Decls : List_Id) return List_Id; function Instantiate_Formal_Subprogram (Formal : Node_Id; @@ -518,6 +600,15 @@ package body Sem_Ch12 is -- apply these rules is to repeat the instantiation of the formal package -- in the context of the enclosing instance, and compare the generic -- associations of this instantiation with those of the actual package. + -- This internal instantiation only needs to contain the renamings of the + -- formals: the visible and private declarations themselves need not be + -- created. + + -- In Ada2005, the formal package may be only partially parametrized. In + -- that case the visibility step must make visible those actuals whose + -- corresponding formals were given with a box. A final complication + -- involves inherited operations from formal derived types, which must be + -- visible if the type is. function Is_In_Main_Unit (N : Node_Id) return Boolean; -- Test if given node is in the main unit @@ -670,12 +761,25 @@ package body Sem_Ch12 is -- that the visibility data structures be properly initialized. Once the -- generic is unit is validated, Set_Instance_Env completes Save_Env. + Parent_Unit_Visible : Boolean := False; + -- Parent_Unit_Visible is used when the generic is a child unit, and + -- indicates whether the ultimate parent of the generic is visible in the + -- instantiation environment. It is used to reset the visibility of the + -- parent at the end of the instantiation (see Remove_Parent). + + Instance_Parent_Unit : Entity_Id := Empty; + -- This records the ultimate parent unit of an instance of a generic + -- child unit and is used in conjunction with Parent_Unit_Visible to + -- indicate the unit to which the Parent_Unit_Visible flag corresponds. + type Instance_Env is record - Ada_Version : Ada_Version_Type; - Instantiated_Parent : Assoc; - Exchanged_Views : Elist_Id; - Hidden_Entities : Elist_Id; - Current_Sem_Unit : Unit_Number_Type; + Instantiated_Parent : Assoc; + Exchanged_Views : Elist_Id; + Hidden_Entities : Elist_Id; + Current_Sem_Unit : Unit_Number_Type; + Parent_Unit_Visible : Boolean := False; + Instance_Parent_Unit : Entity_Id := Empty; + Switches : Config_Switches_Type; end record; package Instance_Envs is new Table.Table ( @@ -741,7 +845,7 @@ package body Sem_Ch12 is procedure Abandon_Instantiation (N : Node_Id) is begin - Error_Msg_N ("instantiation abandoned!", N); + Error_Msg_N ("\instantiation abandoned!", N); raise Instantiation_Error; end Abandon_Instantiation; @@ -756,7 +860,7 @@ package body Sem_Ch12 is is Actual_Types : constant Elist_Id := New_Elmt_List; Assoc : constant List_Id := New_List; - Defaults : constant Elist_Id := New_Elmt_List; + Default_Actuals : constant Elist_Id := New_Elmt_List; Gen_Unit : constant Entity_Id := Defining_Entity (Parent (F_Copy)); Actuals : List_Id; Actual : Node_Id; @@ -767,11 +871,26 @@ package body Sem_Ch12 is Match : Node_Id; Named : Node_Id; First_Named : Node_Id := Empty; + + Default_Formals : constant List_Id := New_List; + -- If an Other_Choice is present, some of the formals may be defaulted. + -- To simplify the treatement of visibility in an instance, we introduce + -- individual defaults for each such formal. These defaults are + -- appended to the list of associations and replace the Others_Choice. + Found_Assoc : Node_Id; + -- Association for the current formal being match. Empty if there are + -- no remaining actuals, or if there is no named association with the + -- name of the formal. + Is_Named_Assoc : Boolean; Num_Matched : Int := 0; Num_Actuals : Int := 0; + Others_Present : Boolean := False; + -- In Ada 2005, indicates partial parametrization of of a formal + -- package. As usual an others association must be last in the list. + function Matching_Actual (F : Entity_Id; A_F : Entity_Id) return Node_Id; @@ -781,6 +900,21 @@ package body Sem_Ch12 is -- A_F is the corresponding entity in the analyzed generic,which is -- placed on the selector name for ASIS use. + -- In Ada 2005, a named association may be given with a box, in which + -- case Matching_Actual sets Found_Assoc to the generic association, + -- but return Empty for the actual itself. In this case the code below + -- creates a corresponding declaration for the formal. + + function Partial_Parametrization return Boolean; + -- Ada 2005: if no match is found for a given formal, check if the + -- association for it includes a box, or whether the associations + -- include an Others clause. + + procedure Process_Default (F : Entity_Id); + -- Add a copy of the declaration of generic formal F to the list of + -- associations, and add an explicit box association for F if there + -- is none yet, and the default comes from an Others_Choice. + procedure Set_Analyzed_Formal; -- Find the node in the generic copy that corresponds to a given formal. -- The semantic information on this node is used to perform legality @@ -798,22 +932,25 @@ package body Sem_Ch12 is (F : Entity_Id; A_F : Entity_Id) return Node_Id is - Found : Node_Id; Prev : Node_Id; + Act : Node_Id; begin Is_Named_Assoc := False; -- End of list of purely positional parameters - if No (Actual) then - Found := Empty; + if No (Actual) + or else Nkind (Actual) = N_Others_Choice + then + Found_Assoc := Empty; + Act := Empty; -- Case of positional parameter corresponding to current formal elsif No (Selector_Name (Actual)) then - Found := Explicit_Generic_Actual_Parameter (Actual); Found_Assoc := Actual; + Act := Explicit_Generic_Actual_Parameter (Actual); Num_Matched := Num_Matched + 1; Next (Actual); @@ -822,16 +959,17 @@ package body Sem_Ch12 is else Is_Named_Assoc := True; - Found := Empty; - Prev := Empty; + Found_Assoc := Empty; + Act := Empty; + Prev := Empty; while Present (Actual) loop if Chars (Selector_Name (Actual)) = Chars (F) then - Found := Explicit_Generic_Actual_Parameter (Actual); Set_Entity (Selector_Name (Actual), A_F); Set_Etype (Selector_Name (Actual), Etype (A_F)); Generate_Reference (A_F, Selector_Name (Actual)); Found_Assoc := Actual; + Act := Explicit_Generic_Actual_Parameter (Actual); Num_Matched := Num_Matched + 1; exit; end if; @@ -858,9 +996,60 @@ package body Sem_Ch12 is Actual := First_Named; end if; - return Found; + return Act; end Matching_Actual; + ----------------------------- + -- Partial_Parametrization -- + ----------------------------- + + function Partial_Parametrization return Boolean is + begin + return Others_Present + or else (Present (Found_Assoc) and then Box_Present (Found_Assoc)); + end Partial_Parametrization; + + --------------------- + -- Process_Default -- + --------------------- + + procedure Process_Default (F : Entity_Id) is + Loc : constant Source_Ptr := Sloc (I_Node); + Decl : Node_Id; + Default : Node_Id; + Id : Entity_Id; + + begin + -- Append copy of formal declaration to associations, and create + -- new defining identifier for it. + + Decl := New_Copy_Tree (F); + + if Nkind (F) = N_Formal_Concrete_Subprogram_Declaration then + Id := + Make_Defining_Identifier (Sloc (Defining_Entity (F)), + Chars => Chars (Defining_Entity (F))); + Set_Defining_Unit_Name (Specification (Decl), Id); + + else + Id := + Make_Defining_Identifier (Sloc (Defining_Entity (F)), + Chars => Chars (Defining_Identifier (F))); + Set_Defining_Identifier (Decl, Id); + end if; + + Append (Decl, Assoc); + + if No (Found_Assoc) then + Default := + Make_Generic_Association (Loc, + Selector_Name => New_Occurrence_Of (Id, Loc), + Explicit_Generic_Actual_Parameter => Empty); + Set_Box_Present (Default); + Append (Default, Default_Formals); + end if; + end Process_Default; + ------------------------- -- Set_Analyzed_Formal -- ------------------------- @@ -874,7 +1063,7 @@ package body Sem_Ch12 is case Nkind (Formal) is when N_Formal_Subprogram_Declaration => - exit when Kind = N_Formal_Subprogram_Declaration + exit when Kind in N_Formal_Subprogram_Declaration and then Chars (Defining_Unit_Name (Specification (Formal))) = @@ -885,7 +1074,9 @@ package body Sem_Ch12 is exit when Kind = N_Formal_Package_Declaration or else - Kind = N_Generic_Package_Declaration; + Kind = N_Generic_Package_Declaration + or else + Kind = N_Package_Declaration; when N_Use_Package_Clause | N_Use_Type_Clause => exit; @@ -895,7 +1086,7 @@ package body Sem_Ch12 is -- unrecognized pragmas. exit when - Kind /= N_Formal_Subprogram_Declaration + Kind not in N_Formal_Subprogram_Declaration and then Kind /= N_Subprogram_Declaration and then Kind /= N_Freeze_Entity and then Kind /= N_Null_Statement @@ -906,21 +1097,59 @@ package body Sem_Ch12 is Next (Analyzed_Formal); end loop; - end Set_Analyzed_Formal; -- Start of processing for Analyze_Associations begin - -- If named associations are present, save the first named association - -- (it may of course be Empty) to facilitate subsequent name search. - Actuals := Generic_Associations (I_Node); if Present (Actuals) then - First_Named := First (Actuals); + -- check for an Others choice, indicating a partial parametrization + -- for a formal package. + + Actual := First (Actuals); + while Present (Actual) loop + if Nkind (Actual) = N_Others_Choice then + Others_Present := True; + if Present (Next (Actual)) then + Error_Msg_N ("others must be last association", Actual); + end if; + + -- This subprogram is used both for formal packages and for + -- instantiations. For the latter, associations must all be + -- explicit. + + if Nkind (I_Node) /= N_Formal_Package_Declaration + and then Comes_From_Source (I_Node) + then + Error_Msg_N + ("others association not allowed in an instance", + Actual); + end if; + + -- In any case, nothing to do after the others association + + exit; + + elsif Box_Present (Actual) + and then Comes_From_Source (I_Node) + and then Nkind (I_Node) /= N_Formal_Package_Declaration + then + Error_Msg_N + ("box association not allowed in an instance", Actual); + end if; + + Next (Actual); + end loop; + + -- If named associations are present, save first named association + -- (it may of course be Empty) to facilitate subsequent name search. + + First_Named := First (Actuals); while Present (First_Named) + and then Nkind (First_Named) /= N_Others_Choice and then No (Selector_Name (First_Named)) loop Num_Actuals := Num_Actuals + 1; @@ -930,7 +1159,9 @@ package body Sem_Ch12 is Named := First_Named; while Present (Named) loop - if No (Selector_Name (Named)) then + if Nkind (Named) /= N_Others_Choice + and then No (Selector_Name (Named)) + then Error_Msg_N ("invalid positional actual after named one", Named); Abandon_Instantiation (Named); end if; @@ -939,7 +1170,9 @@ package body Sem_Ch12 is -- introduced for a default subprogram that turns out to be local -- to the outer instantiation. - if Present (Explicit_Generic_Actual_Parameter (Named)) then + if Nkind (Named) /= N_Others_Choice + and then Present (Explicit_Generic_Actual_Parameter (Named)) + then Num_Actuals := Num_Actuals + 1; end if; @@ -970,9 +1203,13 @@ package body Sem_Ch12 is Defining_Identifier (Formal), Defining_Identifier (Analyzed_Formal)); - Append_List - (Instantiate_Object (Formal, Match, Analyzed_Formal), - Assoc); + if No (Match) and then Partial_Parametrization then + Process_Default (Formal); + else + Append_List + (Instantiate_Object (Formal, Match, Analyzed_Formal), + Assoc); + end if; when N_Formal_Type_Declaration => Match := @@ -981,21 +1218,28 @@ package body Sem_Ch12 is Defining_Identifier (Analyzed_Formal)); if No (Match) then - Error_Msg_Sloc := Sloc (Gen_Unit); - Error_Msg_NE - ("missing actual&", - Instantiation_Node, Defining_Identifier (Formal)); - Error_Msg_NE ("\in instantiation of & declared#", - Instantiation_Node, Gen_Unit); - Abandon_Instantiation (Instantiation_Node); + if Partial_Parametrization then + Process_Default (Formal); + + else + Error_Msg_Sloc := Sloc (Gen_Unit); + Error_Msg_NE + ("missing actual&", + Instantiation_Node, + Defining_Identifier (Formal)); + Error_Msg_NE ("\in instantiation of & declared#", + Instantiation_Node, Gen_Unit); + Abandon_Instantiation (Instantiation_Node); + end if; else Analyze (Match); - Append_To (Assoc, - Instantiate_Type - (Formal, Match, Analyzed_Formal, Assoc)); + Append_List + (Instantiate_Type + (Formal, Match, Analyzed_Formal, Assoc), + Assoc); - -- an instantiation is a freeze point for the actuals, + -- An instantiation is a freeze point for the actuals, -- unless this is a rewritten formal package. if Nkind (I_Node) /= N_Formal_Package_Declaration then @@ -1033,7 +1277,7 @@ package body Sem_Ch12 is then Temp_Formal := First (Formals); while Present (Temp_Formal) loop - if Nkind (Temp_Formal) = + if Nkind (Temp_Formal) in N_Formal_Subprogram_Declaration and then Temp_Formal /= Formal and then @@ -1051,16 +1295,29 @@ package body Sem_Ch12 is end loop; end if; - Append_To (Assoc, - Instantiate_Formal_Subprogram - (Formal, Match, Analyzed_Formal)); + -- If there is no corresponding actual, this may be case of + -- partial parametrization, or else the formal has a default + -- or a box. + + if No (Match) + and then Partial_Parametrization + then + Process_Default (Formal); + else + Append_To (Assoc, + Instantiate_Formal_Subprogram + (Formal, Match, Analyzed_Formal)); + end if; + + -- If this is a nested generic, preserve default for later + -- instantiations. if No (Match) and then Box_Present (Formal) then Append_Elmt (Defining_Unit_Name (Specification (Last (Assoc))), - Defaults); + Default_Actuals); end if; when N_Formal_Package_Declaration => @@ -1070,14 +1327,19 @@ package body Sem_Ch12 is Defining_Identifier (Original_Node (Analyzed_Formal))); if No (Match) then - Error_Msg_Sloc := Sloc (Gen_Unit); - Error_Msg_NE - ("missing actual&", - Instantiation_Node, Defining_Identifier (Formal)); - Error_Msg_NE ("\in instantiation of & declared#", - Instantiation_Node, Gen_Unit); + if Partial_Parametrization then + Process_Default (Formal); - Abandon_Instantiation (Instantiation_Node); + else + Error_Msg_Sloc := Sloc (Gen_Unit); + Error_Msg_NE + ("missing actual&", + Instantiation_Node, Defining_Identifier (Formal)); + Error_Msg_NE ("\in instantiation of & declared#", + Instantiation_Node, Gen_Unit); + + Abandon_Instantiation (Instantiation_Node); + end if; else Analyze (Match); @@ -1087,15 +1349,21 @@ package body Sem_Ch12 is Assoc); end if; - -- For use type and use package appearing in the context - -- clause, we have already copied them, so we can just - -- move them where they belong (we mustn't recopy them - -- since this would mess up the Sloc values). + -- For use type and use package appearing in the generic part, + -- we have already copied them, so we can just move them where + -- they belong (we mustn't recopy them since this would mess up + -- the Sloc values). when N_Use_Package_Clause | N_Use_Type_Clause => - Remove (Formal); - Append (Formal, Assoc); + if Nkind (Original_Node (I_Node)) = + N_Formal_Package_Declaration + then + Append (New_Copy_Tree (Formal), Assoc); + else + Remove (Formal); + Append (Formal, Assoc); + end if; when others => raise Program_Error; @@ -1147,7 +1415,7 @@ package body Sem_Ch12 is New_D : Node_Id; begin - Elmt := First_Elmt (Defaults); + Elmt := First_Elmt (Default_Actuals); while Present (Elmt) loop if No (Actuals) then Actuals := New_List; @@ -1166,6 +1434,14 @@ package body Sem_Ch12 is end loop; end; + -- If this is a formal package. normalize the parameter list by adding + -- explicit box asssociations for the formals that are covered by an + -- Others_Choice. + + if not Is_Empty_List (Default_Formals) then + Append_List (Default_Formals, Formals); + end if; + return Assoc; end Analyze_Associations; @@ -1180,8 +1456,8 @@ package body Sem_Ch12 is DSS : Node_Id; begin - -- Treated like a non-generic array declaration, with - -- additional semantic checks. + -- Treated like a non-generic array declaration, with additional + -- semantic checks. Enter_Name (T); @@ -1207,14 +1483,19 @@ package body Sem_Ch12 is then Error_Msg_N ("premature usage of incomplete type", Def); + -- Check that range constraint is not allowed on the component type + -- of a generic formal array type (AARM 12.5.3(3)) + elsif Is_Internal (Component_Type (T)) + and then Present (Subtype_Indication (Component_Definition (Def))) and then Nkind (Original_Node (Subtype_Indication (Component_Definition (Def)))) - /= N_Attribute_Reference + = N_Subtype_Indication then Error_Msg_N - ("only a subtype mark is allowed in a formal", - Subtype_Indication (Component_Definition (Def))); + ("in a formal, a subtype indication can only be " + & "a subtype mark ('R'M 12.5.3(3))", + Subtype_Indication (Component_Definition (Def))); end if; end Analyze_Formal_Array_Type; @@ -1223,8 +1504,8 @@ package body Sem_Ch12 is -- Analyze_Formal_Decimal_Fixed_Point_Type -- --------------------------------------------- - -- As for other generic types, we create a valid type representation - -- with legal but arbitrary attributes, whose values are never considered + -- As for other generic types, we create a valid type representation with + -- legal but arbitrary attributes, whose values are never considered -- static. For all scalar types we introduce an anonymous base type, with -- the same attributes. We choose the corresponding integer type to be -- Standard_Integer. @@ -1269,10 +1550,37 @@ package body Sem_Ch12 is Set_Delta_Value (T, Delta_Val); Set_Small_Value (T, Delta_Val); Set_Scalar_Range (T, Scalar_Range (Base)); + Set_Is_Constrained (T); Check_Restriction (No_Fixed_Point, Def); end Analyze_Formal_Decimal_Fixed_Point_Type; + ------------------------------------------- + -- Analyze_Formal_Derived_Interface_Type -- + ------------------------------------------- + + procedure Analyze_Formal_Derived_Interface_Type + (N : Node_Id; + T : Entity_Id; + Def : Node_Id) + is + Loc : constant Source_Ptr := Sloc (Def); + New_N : Node_Id; + + begin + -- Rewrite as a type declaration of a derived type. This ensures that + -- the interface list and primitive operations are properly captured. + + New_N := + Make_Full_Type_Declaration (Loc, + Defining_Identifier => T, + Type_Definition => Def); + + Rewrite (N, New_N); + Analyze (N); + Set_Is_Generic_Type (T); + end Analyze_Formal_Derived_Interface_Type; + --------------------------------- -- Analyze_Formal_Derived_Type -- --------------------------------- @@ -1295,9 +1603,12 @@ package body Sem_Ch12 is Defining_Identifier => T, Discriminant_Specifications => Discriminant_Specifications (N), Unknown_Discriminants_Present => Unk_Disc, - Subtype_Indication => Subtype_Mark (Def)); + Subtype_Indication => Subtype_Mark (Def), + Interface_List => Interface_List (Def)); - Set_Abstract_Present (New_N, Abstract_Present (Def)); + Set_Abstract_Present (New_N, Abstract_Present (Def)); + Set_Limited_Present (New_N, Limited_Present (Def)); + Set_Synchronized_Present (New_N, Synchronized_Present (Def)); else New_N := @@ -1311,6 +1622,8 @@ package body Sem_Ch12 is Set_Abstract_Present (Type_Definition (New_N), Abstract_Present (Def)); + Set_Limited_Present + (Type_Definition (New_N), Limited_Present (Def)); end if; Rewrite (N, New_N); @@ -1326,8 +1639,8 @@ package body Sem_Ch12 is end if; end if; - -- If the parent type has a known size, so does the formal, which - -- makes legal representation clauses that involve the formal. + -- If the parent type has a known size, so does the formal, which makes + -- legal representation clauses that involve the formal. Set_Size_Known_At_Compile_Time (T, Size_Known_At_Compile_Time (Entity (Subtype_Mark (Def)))); @@ -1338,25 +1651,30 @@ package body Sem_Ch12 is -- Analyze_Formal_Discrete_Type -- ---------------------------------- - -- The operations defined for a discrete types are those of an - -- enumeration type. The size is set to an arbitrary value, for use - -- in analyzing the generic unit. + -- The operations defined for a discrete types are those of an enumeration + -- type. The size is set to an arbitrary value, for use in analyzing the + -- generic unit. procedure Analyze_Formal_Discrete_Type (T : Entity_Id; Def : Node_Id) is Loc : constant Source_Ptr := Sloc (Def); Lo : Node_Id; Hi : Node_Id; + Base : constant Entity_Id := + New_Internal_Entity + (E_Floating_Point_Type, Current_Scope, Sloc (Def), 'G'); begin - Enter_Name (T); - Set_Ekind (T, E_Enumeration_Type); - Set_Etype (T, T); - Init_Size (T, 8); - Init_Alignment (T); + Enter_Name (T); + Set_Ekind (T, E_Enumeration_Subtype); + Set_Etype (T, Base); + Init_Size (T, 8); + Init_Alignment (T); + Set_Is_Generic_Type (T); + Set_Is_Constrained (T); -- For semantic analysis, the bounds of the type must be set to some - -- non-static value. The simplest is to create attribute nodes for - -- those bounds, that refer to the type itself. These bounds are never + -- non-static value. The simplest is to create attribute nodes for those + -- bounds, that refer to the type itself. These bounds are never -- analyzed but serve as place-holders. Lo := @@ -1376,6 +1694,13 @@ package body Sem_Ch12 is Low_Bound => Lo, High_Bound => Hi)); + Set_Ekind (Base, E_Enumeration_Type); + Set_Etype (Base, Base); + Init_Size (Base, 8); + Init_Alignment (Base); + Set_Is_Generic_Type (Base); + Set_Scalar_Range (Base, Scalar_Range (T)); + Set_Parent (Base, Parent (Def)); end Analyze_Formal_Discrete_Type; ---------------------------------- @@ -1394,12 +1719,13 @@ package body Sem_Ch12 is -- the generic itself. Enter_Name (T); - Set_Ekind (T, E_Floating_Point_Subtype); - Set_Etype (T, Base); - Set_Size_Info (T, (Standard_Float)); - Set_RM_Size (T, RM_Size (Standard_Float)); - Set_Digits_Value (T, Digits_Value (Standard_Float)); - Set_Scalar_Range (T, Scalar_Range (Standard_Float)); + Set_Ekind (T, E_Floating_Point_Subtype); + Set_Etype (T, Base); + Set_Size_Info (T, (Standard_Float)); + Set_RM_Size (T, RM_Size (Standard_Float)); + Set_Digits_Value (T, Digits_Value (Standard_Float)); + Set_Scalar_Range (T, Scalar_Range (Standard_Float)); + Set_Is_Constrained (T); Set_Is_Generic_Type (Base); Set_Etype (Base, Base); @@ -1412,14 +1738,37 @@ package body Sem_Ch12 is Check_Restriction (No_Floating_Point, Def); end Analyze_Formal_Floating_Type; + ----------------------------------- + -- Analyze_Formal_Interface_Type;-- + ----------------------------------- + + procedure Analyze_Formal_Interface_Type + (N : Node_Id; + T : Entity_Id; + Def : Node_Id) + is + Loc : constant Source_Ptr := Sloc (N); + New_N : Node_Id; + + begin + New_N := + Make_Full_Type_Declaration (Loc, + Defining_Identifier => T, + Type_Definition => Def); + + Rewrite (N, New_N); + Analyze (N); + Set_Is_Generic_Type (T); + end Analyze_Formal_Interface_Type; + --------------------------------- -- Analyze_Formal_Modular_Type -- --------------------------------- procedure Analyze_Formal_Modular_Type (T : Entity_Id; Def : Node_Id) is begin - -- Apart from their entity kind, generic modular types are treated - -- like signed integer types, and have the same attributes. + -- Apart from their entity kind, generic modular types are treated like + -- signed integer types, and have the same attributes. Analyze_Formal_Signed_Integer_Type (T, Def); Set_Ekind (T, E_Modular_Integer_Subtype); @@ -1432,7 +1781,7 @@ package body Sem_Ch12 is --------------------------------------- procedure Analyze_Formal_Object_Declaration (N : Node_Id) is - E : constant Node_Id := Expression (N); + E : constant Node_Id := Default_Expression (N); Id : constant Node_Id := Defining_Identifier (N); K : Entity_Kind; T : Node_Id; @@ -1453,11 +1802,33 @@ package body Sem_Ch12 is K := E_Generic_In_Parameter; end if; - Find_Type (Subtype_Mark (N)); - T := Entity (Subtype_Mark (N)); + if Present (Subtype_Mark (N)) then + Find_Type (Subtype_Mark (N)); + T := Entity (Subtype_Mark (N)); + + -- Ada 2005 (AI-423): Formal object with an access definition + + else + Check_Access_Definition (N); + T := Access_Definition + (Related_Nod => N, + N => Access_Definition (N)); + end if; if Ekind (T) = E_Incomplete_Type then - Error_Msg_N ("premature usage of incomplete type", Subtype_Mark (N)); + declare + Error_Node : Node_Id; + + begin + if Present (Subtype_Mark (N)) then + Error_Node := Subtype_Mark (N); + else + Check_Access_Definition (N); + Error_Node := Access_Definition (N); + end if; + + Error_Msg_N ("premature usage of incomplete type", Error_Node); + end; end if; if K = E_Generic_In_Parameter then @@ -1470,24 +1841,30 @@ package body Sem_Ch12 is Explain_Limited_Type (T, N); end if; - if Is_Abstract (T) then + if Is_Abstract_Type (T) then Error_Msg_N ("generic formal of mode IN must not be of abstract type", N); end if; if Present (E) then Analyze_Per_Use_Expression (E, T); + + if Is_Limited_Type (T) and then not OK_For_Limited_Init (E) then + Error_Msg_N + ("initialization not allowed for limited types", E); + Explain_Limited_Type (T, E); + end if; end if; Set_Ekind (Id, K); Set_Etype (Id, T); - -- Case of generic IN OUT parameter. + -- Case of generic IN OUT parameter else - -- If the formal has an unconstrained type, construct its - -- actual subtype, as is done for subprogram formals. In this - -- fashion, all its uses can refer to specific bounds. + -- If the formal has an unconstrained type, construct its actual + -- subtype, as is done for subprogram formals. In this fashion, all + -- its uses can refer to specific bounds. Set_Ekind (Id, K); Set_Etype (Id, T); @@ -1504,8 +1881,7 @@ package body Sem_Ch12 is Decl : Node_Id; begin - -- Make sure that the actual subtype doesn't generate - -- bogus freezing. + -- Make sure the actual subtype doesn't generate bogus freezing Set_Must_Not_Freeze (Non_Freezing_Ref); Decl := Build_Actual_Subtype (T, Non_Freezing_Ref); @@ -1537,9 +1913,8 @@ package body Sem_Ch12 is New_Internal_Entity (E_Ordinary_Fixed_Point_Type, Current_Scope, Sloc (Def), 'G'); begin - -- The semantic attributes are set for completeness only, their - -- values will never be used, because all properties of the type - -- are non-static. + -- The semantic attributes are set for completeness only, their values + -- will never be used, since all properties of the type are non-static. Enter_Name (T); Set_Ekind (T, E_Ordinary_Fixed_Point_Subtype); @@ -1552,6 +1927,7 @@ package body Sem_Ch12 is Make_Range (Loc, Low_Bound => Make_Real_Literal (Loc, Ureal_1), High_Bound => Make_Real_Literal (Loc, Ureal_1))); + Set_Is_Constrained (T); Set_Is_Generic_Type (Base); Set_Etype (Base, Base); @@ -1581,6 +1957,110 @@ package body Sem_Ch12 is Renaming : Node_Id; Parent_Instance : Entity_Id; Renaming_In_Par : Entity_Id; + No_Associations : Boolean := False; + + function Build_Local_Package return Node_Id; + -- The formal package is rewritten so that its parameters are replaced + -- with corresponding declarations. For parameters with bona fide + -- associations these declarations are created by Analyze_Associations + -- as for aa regular instantiation. For boxed parameters, we preserve + -- the formal declarations and analyze them, in order to introduce + -- entities of the right kind in the environment of the formal. + + ------------------------- + -- Build_Local_Package -- + ------------------------- + + function Build_Local_Package return Node_Id is + Decls : List_Id; + Pack_Decl : Node_Id; + + begin + -- Within the formal, the name of the generic package is a renaming + -- of the formal (as for a regular instantiation). + + Pack_Decl := + Make_Package_Declaration (Loc, + Specification => + Copy_Generic_Node + (Specification (Original_Node (Gen_Decl)), + Empty, Instantiating => True)); + + Renaming := Make_Package_Renaming_Declaration (Loc, + Defining_Unit_Name => + Make_Defining_Identifier (Loc, Chars (Gen_Unit)), + Name => New_Occurrence_Of (Formal, Loc)); + + if Nkind (Gen_Id) = N_Identifier + and then Chars (Gen_Id) = Chars (Pack_Id) + then + Error_Msg_NE + ("& is hidden within declaration of instance", Gen_Id, Gen_Unit); + end if; + + -- If the formal is declared with a box, or with an others choice, + -- create corresponding declarations for all entities in the formal + -- part, so that names with the proper types are available in the + -- specification of the formal package. + + if No_Associations then + declare + Formal_Decl : Node_Id; + + begin + -- TBA : for a formal package, need to recurse ??? + + Decls := New_List; + Formal_Decl := + First + (Generic_Formal_Declarations (Original_Node (Gen_Decl))); + while Present (Formal_Decl) loop + Append_To + (Decls, Copy_Generic_Node (Formal_Decl, Empty, True)); + Next (Formal_Decl); + end loop; + end; + + -- If generic associations are present, use Analyze_Associations to + -- create the proper renaming declarations. + + else + declare + Act_Tree : constant Node_Id := + Copy_Generic_Node + (Original_Node (Gen_Decl), Empty, + Instantiating => True); + + begin + Generic_Renamings.Set_Last (0); + Generic_Renamings_HTable.Reset; + Instantiation_Node := N; + + Decls := + Analyze_Associations + (Original_Node (N), + Generic_Formal_Declarations (Act_Tree), + Generic_Formal_Declarations (Gen_Decl)); + end; + end if; + + Append (Renaming, To => Decls); + + -- Add generated declarations ahead of local declarations in + -- the package. + + if No (Visible_Declarations (Specification (Pack_Decl))) then + Set_Visible_Declarations (Specification (Pack_Decl), Decls); + else + Insert_List_Before + (First (Visible_Declarations (Specification (Pack_Decl))), + Decls); + end if; + + return Pack_Decl; + end Build_Local_Package; + + -- Start of processing for Analyze_Formal_Package begin Text_IO_Kludge (Gen_Id); @@ -1589,6 +2069,12 @@ package body Sem_Ch12 is Check_Generic_Child_Unit (Gen_Id, Parent_Installed); Gen_Unit := Entity (Gen_Id); + -- Check for a formal package that is a package renaming + + if Present (Renamed_Object (Gen_Unit)) then + Gen_Unit := Renamed_Object (Gen_Unit); + end if; + if Ekind (Gen_Unit) /= E_Generic_Package then Error_Msg_N ("expect generic package name", Gen_Id); Restore_Env; @@ -1623,111 +2109,128 @@ package body Sem_Ch12 is end if; end if; - -- Check for a formal package that is a package renaming. + if Box_Present (N) + or else No (Generic_Associations (N)) + or else Nkind (First (Generic_Associations (N))) = N_Others_Choice + then + No_Associations := True; + end if; + + -- If there are no generic associations, the generic parameters appear + -- as local entities and are instantiated like them. We copy the generic + -- package declaration as if it were an instantiation, and analyze it + -- like a regular package, except that we treat the formals as + -- additional visible components. - if Present (Renamed_Object (Gen_Unit)) then - Gen_Unit := Renamed_Object (Gen_Unit); + Gen_Decl := Unit_Declaration_Node (Gen_Unit); + + if In_Extended_Main_Source_Unit (N) then + Set_Is_Instantiated (Gen_Unit); + Generate_Reference (Gen_Unit, N); end if; - -- The formal package is treated like a regular instance, but only - -- the specification needs to be instantiated, to make entities visible. + Formal := New_Copy (Pack_Id); + Create_Instantiation_Source (N, Gen_Unit, False, S_Adjustment); - if not Box_Present (N) then - Hidden_Entities := New_Elmt_List; - Analyze_Package_Instantiation (N); + -- Make local generic without formals. The formals will be replaced with + -- internal declarations. - if Parent_Installed then - Remove_Parent; - end if; + New_N := Build_Local_Package; + Rewrite (N, New_N); + Set_Defining_Unit_Name (Specification (New_N), Formal); + Set_Generic_Parent (Specification (N), Gen_Unit); + Set_Instance_Env (Gen_Unit, Formal); + Set_Is_Generic_Instance (Formal); - else - -- If there are no generic associations, the generic parameters - -- appear as local entities and are instantiated like them. We copy - -- the generic package declaration as if it were an instantiation, - -- and analyze it like a regular package, except that we treat the - -- formals as additional visible components. + Enter_Name (Formal); + Set_Ekind (Formal, E_Package); + Set_Etype (Formal, Standard_Void_Type); + Set_Inner_Instances (Formal, New_Elmt_List); + Push_Scope (Formal); - Gen_Decl := Unit_Declaration_Node (Gen_Unit); + if Is_Child_Unit (Gen_Unit) + and then Parent_Installed + then + -- Similarly, we have to make the name of the formal visible in the + -- parent instance, to resolve properly fully qualified names that + -- may appear in the generic unit. The parent instance has been + -- placed on the scope stack ahead of the current scope. + + Parent_Instance := Scope_Stack.Table (Scope_Stack.Last - 1).Entity; + + Renaming_In_Par := + Make_Defining_Identifier (Loc, Chars (Gen_Unit)); + Set_Ekind (Renaming_In_Par, E_Package); + Set_Etype (Renaming_In_Par, Standard_Void_Type); + Set_Scope (Renaming_In_Par, Parent_Instance); + Set_Parent (Renaming_In_Par, Parent (Formal)); + Set_Renamed_Object (Renaming_In_Par, Formal); + Append_Entity (Renaming_In_Par, Parent_Instance); + end if; - if In_Extended_Main_Source_Unit (N) then - Set_Is_Instantiated (Gen_Unit); - Generate_Reference (Gen_Unit, N); - end if; + Analyze (Specification (N)); - Formal := New_Copy (Pack_Id); - New_N := - Copy_Generic_Node - (Original_Node (Gen_Decl), Empty, Instantiating => True); - Rewrite (N, New_N); - Set_Defining_Unit_Name (Specification (New_N), Formal); - Set_Instance_Env (Gen_Unit, Formal); + -- The formals for which associations are provided are not visible + -- outside of the formal package. The others are still declared by a + -- formal parameter declaration. - Enter_Name (Formal); - Set_Ekind (Formal, E_Generic_Package); - Set_Etype (Formal, Standard_Void_Type); - Set_Inner_Instances (Formal, New_Elmt_List); - New_Scope (Formal); + if not No_Associations then + declare + E : Entity_Id; - -- Within the formal, the name of the generic package is a renaming - -- of the formal (as for a regular instantiation). + begin + E := First_Entity (Formal); + while Present (E) loop + exit when Ekind (E) = E_Package + and then Renamed_Entity (E) = Formal; - Renaming := Make_Package_Renaming_Declaration (Loc, - Defining_Unit_Name => - Make_Defining_Identifier (Loc, Chars (Gen_Unit)), - Name => New_Reference_To (Formal, Loc)); + if not Is_Generic_Formal (E) then + Set_Is_Hidden (E); + end if; - if Present (Visible_Declarations (Specification (N))) then - Prepend (Renaming, To => Visible_Declarations (Specification (N))); - elsif Present (Private_Declarations (Specification (N))) then - Prepend (Renaming, To => Private_Declarations (Specification (N))); - end if; + Next_Entity (E); + end loop; + end; + end if; - if Is_Child_Unit (Gen_Unit) - and then Parent_Installed - then - -- Similarly, we have to make the name of the formal visible in - -- the parent instance, to resolve properly fully qualified names - -- that may appear in the generic unit. The parent instance has - -- been placed on the scope stack ahead of the current scope. + End_Package_Scope (Formal); - Parent_Instance := Scope_Stack.Table (Scope_Stack.Last - 1).Entity; + if Parent_Installed then + Remove_Parent; + end if; - Renaming_In_Par := - Make_Defining_Identifier (Loc, Chars (Gen_Unit)); - Set_Ekind (Renaming_In_Par, E_Package); - Set_Etype (Renaming_In_Par, Standard_Void_Type); - Set_Scope (Renaming_In_Par, Parent_Instance); - Set_Parent (Renaming_In_Par, Parent (Formal)); - Set_Renamed_Object (Renaming_In_Par, Formal); - Append_Entity (Renaming_In_Par, Parent_Instance); - end if; + Restore_Env; - Analyze_Generic_Formal_Part (N); - Analyze (Specification (N)); - End_Package_Scope (Formal); + -- Inside the generic unit, the formal package is a regular package, but + -- no body is needed for it. Note that after instantiation, the defining + -- unit name we need is in the new tree and not in the original (see + -- Package_Instantiation). A generic formal package is an instance, and + -- can be used as an actual for an inner instance. - if Parent_Installed then - Remove_Parent; - end if; + Set_Has_Completion (Formal, True); - Restore_Env; + -- Add semantic information to the original defining identifier. + -- for ASIS use. - -- Inside the generic unit, the formal package is a regular - -- package, but no body is needed for it. Note that after - -- instantiation, the defining_unit_name we need is in the - -- new tree and not in the original. (see Package_Instantiation). - -- A generic formal package is an instance, and can be used as - -- an actual for an inner instance. Mark its generic parent. - - Set_Ekind (Formal, E_Package); - Set_Generic_Parent (Specification (N), Gen_Unit); - Set_Has_Completion (Formal, True); - - Set_Ekind (Pack_Id, E_Package); - Set_Etype (Pack_Id, Standard_Void_Type); - Set_Scope (Pack_Id, Scope (Formal)); - Set_Has_Completion (Pack_Id, True); - end if; + Set_Ekind (Pack_Id, E_Package); + Set_Etype (Pack_Id, Standard_Void_Type); + Set_Scope (Pack_Id, Scope (Formal)); + Set_Has_Completion (Pack_Id, True); + + -- If there are errors in the parameter list, Analyze_Associations + -- raises Instantiation_Error. Patch the declaration to prevent + -- further exception propagation. + + exception + when Instantiation_Error => + + Enter_Name (Formal); + Set_Ekind (Formal, E_Variable); + Set_Etype (Formal, Any_Type); + + if Parent_Installed then + Remove_Parent; + end if; end Analyze_Formal_Package; --------------------------------- @@ -1742,7 +2245,7 @@ package body Sem_Ch12 is begin New_Private_Type (N, T, Def); - -- Set the size to an arbitrary but legal value. + -- Set the size to an arbitrary but legal value Set_Size_Info (T, Standard_Integer); Set_RM_Size (T, RM_Size (Standard_Integer)); @@ -1763,11 +2266,12 @@ package body Sem_Ch12 is begin Enter_Name (T); - Set_Ekind (T, E_Signed_Integer_Subtype); - Set_Etype (T, Base); - Set_Size_Info (T, Standard_Integer); - Set_RM_Size (T, RM_Size (Standard_Integer)); - Set_Scalar_Range (T, Scalar_Range (Standard_Integer)); + Set_Ekind (T, E_Signed_Integer_Subtype); + Set_Etype (T, Base); + Set_Size_Info (T, Standard_Integer); + Set_RM_Size (T, RM_Size (Standard_Integer)); + Set_Scalar_Range (T, Scalar_Range (Standard_Integer)); + Set_Is_Constrained (T); Set_Is_Generic_Type (Base); Set_Size_Info (Base, Standard_Integer); @@ -1801,6 +2305,23 @@ package body Sem_Ch12 is Set_Is_Formal_Subprogram (Nam); Set_Has_Completion (Nam); + if Nkind (N) = N_Formal_Abstract_Subprogram_Declaration then + Set_Is_Abstract_Subprogram (Nam); + Set_Is_Dispatching_Operation (Nam); + + declare + Ctrl_Type : constant Entity_Id := Find_Dispatching_Type (Nam); + begin + if No (Ctrl_Type) then + Error_Msg_N + ("abstract formal subprogram must have a controlling type", + N); + else + Check_Controlling_Formals (Ctrl_Type, Nam); + end if; + end; + end if; + -- Default name is resolved at the point of instantiation if Box_Present (N) then @@ -1945,7 +2466,7 @@ package body Sem_Ch12 is Defining_Identifier (First (Discriminant_Specifications (N)))); end if; - -- Enter the new name, and branch to specific routine. + -- Enter the new name, and branch to specific routine case Nkind (Def) is when N_Formal_Private_Type_Definition => @@ -1980,6 +2501,15 @@ package body Sem_Ch12 is N_Access_Procedure_Definition => Analyze_Generic_Access_Type (T, Def); + -- Ada 2005: a interface declaration is encoded as an abstract + -- record declaration or a abstract type derivation. + + when N_Record_Definition => + Analyze_Formal_Interface_Type (N, T, Def); + + when N_Derived_Type_Definition => + Analyze_Formal_Derived_Interface_Type (N, T, Def); + when N_Error => null; @@ -2035,9 +2565,9 @@ package body Sem_Ch12 is Gen_Parm_Decl : Node_Id; begin - -- The generic formals are processed in the scope of the generic - -- unit, where they are immediately visible. The scope is installed - -- by the caller. + -- The generic formals are processed in the scope of the generic unit, + -- where they are immediately visible. The scope is installed by the + -- caller. Gen_Parm_Decl := First (Generic_Formal_Declarations (N)); @@ -2095,9 +2625,9 @@ package body Sem_Ch12 is Set_Visible_Declarations (Specification (N), New_List (Renaming)); end if; - -- Create copy of generic unit, and save for instantiation. - -- If the unit is a child unit, do not copy the specifications - -- for the parent, which are not part of the generic tree. + -- Create copy of generic unit, and save for instantiation. If the unit + -- is a child unit, do not copy the specifications for the parent, which + -- are not part of the generic tree. Save_Parent := Parent_Spec (N); Set_Parent_Spec (N, Empty); @@ -2108,28 +2638,28 @@ package body Sem_Ch12 is Id := Defining_Entity (N); Generate_Definition (Id); - -- Expansion is not applied to generic units. + -- Expansion is not applied to generic units Start_Generic; Enter_Name (Id); Set_Ekind (Id, E_Generic_Package); Set_Etype (Id, Standard_Void_Type); - New_Scope (Id); + Push_Scope (Id); Enter_Generic_Scope (Id); Set_Inner_Instances (Id, New_Elmt_List); Set_Categorization_From_Pragmas (N); Set_Is_Pure (Id, Is_Pure (Current_Scope)); - -- Link the declaration of the generic homonym in the generic copy - -- to the package it renames, so that it is always resolved properly. + -- Link the declaration of the generic homonym in the generic copy to + -- the package it renames, so that it is always resolved properly. Set_Generic_Homonym (Id, Defining_Unit_Name (Renaming)); Set_Entity (Associated_Node (Name (Renaming)), Id); - -- For a library unit, we have reconstructed the entity for the - -- unit, and must reset it in the library tables. + -- For a library unit, we have reconstructed the entity for the unit, + -- and must reset it in the library tables. if Nkind (Parent (N)) = N_Compilation_Unit then Set_Cunit_Entity (Current_Sem_Unit, Id); @@ -2137,8 +2667,8 @@ package body Sem_Ch12 is Analyze_Generic_Formal_Part (N); - -- After processing the generic formals, analysis proceeds - -- as for a non-generic package. + -- After processing the generic formals, analysis proceeds as for a + -- non-generic package. Analyze (Specification (N)); @@ -2176,12 +2706,13 @@ package body Sem_Ch12 is Id : Entity_Id; Formals : List_Id; New_N : Node_Id; + Result_Type : Entity_Id; Save_Parent : Node_Id; begin - -- Create copy of generic unit,and save for instantiation. - -- If the unit is a child unit, do not copy the specifications - -- for the parent, which are not part of the generic tree. + -- Create copy of generic unit,and save for instantiation. If the unit + -- is a child unit, do not copy the specifications for the parent, which + -- are not part of the generic tree. Save_Parent := Parent_Spec (N); Set_Parent_Spec (N, Empty); @@ -2204,7 +2735,7 @@ package body Sem_Ch12 is Enter_Name (Id); Set_Scope_Depth_Value (Id, Scope_Depth (Current_Scope) + 1); - New_Scope (Id); + Push_Scope (Id); Enter_Generic_Scope (Id); Set_Inner_Instances (Id, New_Elmt_List); Set_Is_Pure (Id, Is_Pure (Current_Scope)); @@ -2219,17 +2750,23 @@ package body Sem_Ch12 is if Nkind (Spec) = N_Function_Specification then Set_Ekind (Id, E_Generic_Function); - Find_Type (Subtype_Mark (Spec)); - Set_Etype (Id, Entity (Subtype_Mark (Spec))); + + if Nkind (Result_Definition (Spec)) = N_Access_Definition then + Result_Type := Access_Definition (Spec, Result_Definition (Spec)); + Set_Etype (Id, Result_Type); + else + Find_Type (Result_Definition (Spec)); + Set_Etype (Id, Entity (Result_Definition (Spec))); + end if; + else Set_Ekind (Id, E_Generic_Procedure); Set_Etype (Id, Standard_Void_Type); end if; - -- For a library unit, we have reconstructed the entity for the - -- unit, and must reset it in the library tables. We also need - -- to make sure that Body_Required is set properly in the original - -- compilation unit node. + -- For a library unit, we have reconstructed the entity for the unit, + -- and must reset it in the library tables. We also make sure that + -- Body_Required is set properly in the original compilation unit node. if Nkind (Parent (N)) = N_Compilation_Unit then Set_Cunit_Entity (Current_Sem_Unit, Id); @@ -2251,10 +2788,6 @@ package body Sem_Ch12 is -- Analyze_Package_Instantiation -- ----------------------------------- - -- Note: this procedure is also used for formal package declarations, - -- in which case the argument N is an N_Formal_Package_Declaration - -- node. This should really be noted in the spec! ??? - procedure Analyze_Package_Instantiation (N : Node_Id) is Loc : constant Source_Ptr := Sloc (N); Gen_Id : constant Node_Id := Name (N); @@ -2271,6 +2804,7 @@ package body Sem_Ch12 is Is_Actual_Pack : constant Boolean := Is_Internal (Defining_Entity (N)); + Env_Installed : Boolean := False; Parent_Installed : Boolean := False; Renaming_List : List_Id; Unit_Renaming : Node_Id; @@ -2334,7 +2868,7 @@ package body Sem_Ch12 is Text_IO_Kludge (Name (N)); - -- Make node global for error reporting. + -- Make node global for error reporting Instantiation_Node := N; @@ -2364,6 +2898,7 @@ package body Sem_Ch12 is Pre_Analyze_Actuals (N); Init_Env; + Env_Installed := True; Check_Generic_Child_Unit (Gen_Id, Parent_Installed); Gen_Unit := Entity (Gen_Id); @@ -2416,7 +2951,7 @@ package body Sem_Ch12 is Set_Entity (Gen_Id, Gen_Unit); - -- If generic is a renaming, get original generic unit. + -- If generic is a renaming, get original generic unit if Present (Renamed_Object (Gen_Unit)) and then Ekind (Renamed_Object (Gen_Unit)) = E_Generic_Package @@ -2424,7 +2959,7 @@ package body Sem_Ch12 is Gen_Unit := Renamed_Object (Gen_Unit); end if; - -- Verify that there are no circular instantiations. + -- Verify that there are no circular instantiations if In_Open_Scopes (Gen_Unit) then Error_Msg_NE ("instantiation of & within itself", N, Gen_Unit); @@ -2440,21 +2975,20 @@ package body Sem_Ch12 is return; else - Set_Instance_Env (Gen_Unit, Act_Decl_Id); Gen_Decl := Unit_Declaration_Node (Gen_Unit); - -- Initialize renamings map, for error checking, and the list - -- that holds private entities whose views have changed between - -- generic definition and instantiation. If this is the instance - -- created to validate an actual package, the instantiation - -- environment is that of the enclosing instance. + -- Initialize renamings map, for error checking, and the list that + -- holds private entities whose views have changed between generic + -- definition and instantiation. If this is the instance created to + -- validate an actual package, the instantiation environment is that + -- of the enclosing instance. Generic_Renamings.Set_Last (0); Generic_Renamings_HTable.Reset; Create_Instantiation_Source (N, Gen_Unit, False, S_Adjustment); - -- Copy original generic tree, to produce text for instantiation. + -- Copy original generic tree, to produce text for instantiation Act_Tree := Copy_Generic_Node @@ -2476,14 +3010,15 @@ package body Sem_Ch12 is Generic_Formal_Declarations (Act_Tree), Generic_Formal_Declarations (Gen_Decl)); + Set_Instance_Env (Gen_Unit, Act_Decl_Id); Set_Defining_Unit_Name (Act_Spec, Act_Decl_Name); Set_Is_Generic_Instance (Act_Decl_Id); Set_Generic_Parent (Act_Spec, Gen_Unit); - -- References to the generic in its own declaration or its body - -- are references to the instance. Add a renaming declaration for - -- the generic unit itself. This declaration, as well as the renaming + -- References to the generic in its own declaration or its body are + -- references to the instance. Add a renaming declaration for the + -- generic unit itself. This declaration, as well as the renaming -- declarations for the generic formals, must remain private to the -- unit: the formals, because this is the language semantics, and -- the unit because its use is an artifact of the implementation. @@ -2510,10 +3045,10 @@ package body Sem_Ch12 is Make_Package_Declaration (Loc, Specification => Act_Spec); - -- Save the instantiation node, for subsequent instantiation - -- of the body, if there is one and we are generating code for - -- the current unit. Mark the unit as having a body, to avoid - -- a premature error message. + -- Save the instantiation node, for subsequent instantiation of the + -- body, if there is one and we are generating code for the current + -- unit. Mark the unit as having a body, to avoid a premature error + -- message. -- We instantiate the body if we are generating code, if we are -- generating cross-reference information, or if we are building @@ -2521,10 +3056,10 @@ package body Sem_Ch12 is declare Enclosing_Body_Present : Boolean := False; - -- If the generic unit is not a compilation unit, then a body - -- may be present in its parent even if none is required. We - -- create a tentative pending instantiation for the body, which - -- will be discarded if none is actually present. + -- If the generic unit is not a compilation unit, then a body may + -- be present in its parent even if none is required. We create a + -- tentative pending instantiation for the body, which will be + -- discarded if none is actually present. Scop : Entity_Id; @@ -2555,20 +3090,56 @@ package body Sem_Ch12 is -- If front-end inlining is enabled, and this is a unit for which -- code will be generated, we instantiate the body at once. + -- This is done if the instance is not the main unit, and if the -- generic is not a child unit of another generic, to avoid scope -- problems and the reinstallation of parent instances. - if Front_End_Inlining - and then Expander_Active + if Expander_Active and then (not Is_Child_Unit (Gen_Unit) or else not Is_Generic_Unit (Scope (Gen_Unit))) - and then Is_In_Main_Unit (N) - and then Nkind (Parent (N)) /= N_Compilation_Unit and then Might_Inline_Subp and then not Is_Actual_Pack then - Inline_Now := True; + if Front_End_Inlining + and then (Is_In_Main_Unit (N) + or else In_Main_Context (Current_Scope)) + and then Nkind (Parent (N)) /= N_Compilation_Unit + then + Inline_Now := True; + + -- In configurable_run_time mode we force the inlining of + -- predefined subprogram marked Inline_Always, to minimize + -- the use of the run-time library. + + elsif Is_Predefined_File_Name + (Unit_File_Name (Get_Source_Unit (Gen_Decl))) + and then Configurable_Run_Time_Mode + and then Nkind (Parent (N)) /= N_Compilation_Unit + then + Inline_Now := True; + end if; + + -- If the current scope is itself an instance within a child + -- unit,there will be duplications in the scope stack, and the + -- unstacking mechanism in Inline_Instance_Body will fail. + -- This loses some rare cases of optimization, and might be + -- improved some day, if we can find a proper abstraction for + -- "the complete compilation context" that can be saved and + -- restored ??? + + if Is_Generic_Instance (Current_Scope) then + declare + Curr_Unit : constant Entity_Id := + Cunit_Entity (Current_Sem_Unit); + begin + if Curr_Unit /= Current_Scope + and then Is_Child_Unit (Curr_Unit) + then + Inline_Now := False; + end if; + end; + end if; end if; Needs_Body := @@ -2579,13 +3150,12 @@ package body Sem_Ch12 is or else Might_Inline_Subp) and then not Is_Actual_Pack and then not Inline_Now - and then (Operating_Mode = Generate_Code or else (Operating_Mode = Check_Semantics and then ASIS_Mode)); - -- If front_end_inlining is enabled, do not instantiate a - -- body if within a generic context. + -- If front_end_inlining is enabled, do not instantiate body if + -- within a generic context. if (Front_End_Inlining and then not Expander_Active) @@ -2595,12 +3165,11 @@ package body Sem_Ch12 is end if; -- If the current context is generic, and the package being - -- instantiated is declared within a formal package, there - -- is no body to instantiate until the enclosing generic is - -- instantiated, and there is an actual for the formal - -- package. If the formal package has parameters, we build a - -- regular package instance for it, that preceeds the original - -- formal package declaration. + -- instantiated is declared within a formal package, there is no + -- body to instantiate until the enclosing generic is instantiated + -- and there is an actual for the formal package. If the formal + -- package has parameters, we build regular package instance for + -- it, that preceeds the original formal package declaration. if In_Open_Scopes (Scope (Scope (Gen_Unit))) then declare @@ -2621,9 +3190,9 @@ package body Sem_Ch12 is end if; end; - -- If we are generating the calling stubs from the instantiation - -- of a generic RCI package, we will not use the body of the - -- generic package. + -- If we are generating the calling stubs from the instantiation of + -- a generic RCI package, we will not use the body of the generic + -- package. if Distribution_Stub_Mode = Generate_Caller_Stub_Body and then Is_Compilation_Unit (Defining_Entity (N)) @@ -2650,11 +3219,13 @@ package body Sem_Ch12 is Check_Forward_Instantiation (Gen_Decl); if Nkind (N) = N_Package_Instantiation then declare - Enclosing_Master : Entity_Id := Current_Scope; + Enclosing_Master : Entity_Id; begin - while Enclosing_Master /= Standard_Standard loop + -- Loop to search enclosing masters + Enclosing_Master := Current_Scope; + Scope_Loop : while Enclosing_Master /= Standard_Standard loop if Ekind (Enclosing_Master) = E_Package then if Is_Compilation_Unit (Enclosing_Master) then if In_Package_Body (Enclosing_Master) then @@ -2665,7 +3236,7 @@ package body Sem_Ch12 is (Enclosing_Master); end if; - exit; + exit Scope_Loop; else Enclosing_Master := Scope (Enclosing_Master); @@ -2681,15 +3252,19 @@ package body Sem_Ch12 is -- the enclosing instance, if any. enclosing scope -- is void in the formal part of a generic subp. - exit; + exit Scope_Loop; else if Ekind (Enclosing_Master) = E_Entry and then Ekind (Scope (Enclosing_Master)) = E_Protected_Type then - Enclosing_Master := - Protected_Body_Subprogram (Enclosing_Master); + if not Expander_Active then + exit Scope_Loop; + else + Enclosing_Master := + Protected_Body_Subprogram (Enclosing_Master); + end if; end if; Set_Delay_Cleanups (Enclosing_Master); @@ -2706,7 +3281,6 @@ package body Sem_Ch12 is TBP : constant Node_Id := Get_Task_Body_Procedure (Enclosing_Master); - begin if Present (TBP) then Delay_Descriptors (TBP); @@ -2715,9 +3289,9 @@ package body Sem_Ch12 is end; end if; - exit; + exit Scope_Loop; end if; - end loop; + end loop Scope_Loop; end; -- Make entry in table @@ -2744,13 +3318,12 @@ package body Sem_Ch12 is Insert_Before (N, Act_Decl); Analyze (Act_Decl); - -- For an instantiation that is a compilation unit, place - -- declaration on current node so context is complete - -- for analysis (including nested instantiations). It this - -- is the main unit, the declaration eventually replaces the - -- instantiation node. If the instance body is later created, it - -- replaces the instance node, and the declation is attached to - -- it (see Build_Instance_Compilation_Unit_Nodes). + -- For an instantiation that is a compilation unit, place declaration + -- on current node so context is complete for analysis (including + -- nested instantiations). It this is the main unit, the declaration + -- eventually replaces the instantiation node. If the instance body + -- is later created, it replaces the instance node, and the declation + -- is attached to it (see Build_Instance_Compilation_Unit_Nodes). else if Cunit_Entity (Current_Sem_Unit) = Defining_Entity (N) then @@ -2760,7 +3333,7 @@ package body Sem_Ch12 is Set_Cunit_Entity (Current_Sem_Unit, Act_Decl_Id); - -- If this is the main unit, replace the main entity as well. + -- If this is the main unit, replace the main entity as well if Current_Sem_Unit = Main_Unit then Main_Unit_Entity := Act_Decl_Id; @@ -2769,13 +3342,14 @@ package body Sem_Ch12 is Set_Unit (Parent (N), Act_Decl); Set_Parent_Spec (Act_Decl, Parent_Spec (N)); + Set_Package_Instantiation (Act_Decl_Id, N); Analyze (Act_Decl); Set_Unit (Parent (N), N); Set_Body_Required (Parent (N), False); - -- We never need elaboration checks on instantiations, since - -- by definition, the body instantiation is elaborated at the - -- same time as the spec instantiation. + -- We never need elaboration checks on instantiations, since by + -- definition, the body instantiation is elaborated at the same + -- time as the spec instantiation. Set_Suppress_Elaboration_Warnings (Act_Decl_Id); Set_Kill_Elaboration_Checks (Act_Decl_Id); @@ -2791,10 +3365,10 @@ package body Sem_Ch12 is Set_First_Private_Entity (Defining_Unit_Name (Unit_Renaming), First_Private_Entity (Act_Decl_Id)); - -- If the instantiation will receive a body, the unit will - -- be transformed into a package body, and receive its own - -- elaboration entity. Otherwise, the nature of the unit is - -- now a package declaration. + -- If the instantiation will receive a body, the unit will be + -- transformed into a package body, and receive its own elaboration + -- entity. Otherwise, the nature of the unit is now a package + -- declaration. if Nkind (Parent (N)) = N_Compilation_Unit and then not Needs_Body @@ -2821,12 +3395,13 @@ package body Sem_Ch12 is end if; Restore_Env; + Env_Installed := False; end if; Validate_Categorization_Dependency (N, Act_Decl_Id); - -- Check restriction, but skip this if something went wrong in - -- the above analysis, indicated by Act_Decl_Id being void. + -- Check restriction, but skip this if something went wrong in the above + -- analysis, indicated by Act_Decl_Id being void. if Ekind (Act_Decl_Id) /= E_Void and then not Is_Library_Level_Entity (Act_Decl_Id) @@ -2838,11 +3413,26 @@ package body Sem_Ch12 is Inline_Instance_Body (N, Gen_Unit, Act_Decl); end if; + -- The following is a tree patch for ASIS: ASIS needs separate nodes to + -- be used as defining identifiers for a formal package and for the + -- corresponding expanded package + + if Nkind (N) = N_Formal_Package_Declaration then + Act_Decl_Id := New_Copy (Defining_Entity (N)); + Set_Comes_From_Source (Act_Decl_Id, True); + Set_Is_Generic_Instance (Act_Decl_Id, False); + Set_Defining_Identifier (N, Act_Decl_Id); + end if; + exception when Instantiation_Error => if Parent_Installed then Remove_Parent; end if; + + if Env_Installed then + Restore_Env; + end if; end Analyze_Package_Instantiation; -------------------------- @@ -2863,31 +3453,41 @@ package body Sem_Ch12 is Cunit_Entity (Current_Sem_Unit); Removed : Boolean := False; Num_Scopes : Int := 0; - Use_Clauses : array (1 .. Scope_Stack.Last) of Node_Id; - Instances : array (1 .. Scope_Stack.Last) of Entity_Id; - Inner_Scopes : array (1 .. Scope_Stack.Last) of Entity_Id; + + Scope_Stack_Depth : constant Int := + Scope_Stack.Last - Scope_Stack.First + 1; + + Use_Clauses : array (1 .. Scope_Stack_Depth) of Node_Id; + Instances : array (1 .. Scope_Stack_Depth) of Entity_Id; + Inner_Scopes : array (1 .. Scope_Stack_Depth) of Entity_Id; Num_Inner : Int := 0; N_Instances : Int := 0; S : Entity_Id; begin - -- Case of generic unit defined in another unit. We must remove - -- the complete context of the current unit to install that of - -- the generic. + -- Case of generic unit defined in another unit. We must remove the + -- complete context of the current unit to install that of the generic. if Gen_Comp /= Cunit_Entity (Current_Sem_Unit) then - S := Current_Scope; - while Present (S) - and then S /= Standard_Standard - loop - Num_Scopes := Num_Scopes + 1; + -- Add some comments for the following two loops ??? - Use_Clauses (Num_Scopes) := - (Scope_Stack.Table - (Scope_Stack.Last - Num_Scopes + 1). - First_Use_Clause); - End_Use_Clauses (Use_Clauses (Num_Scopes)); + S := Current_Scope; + while Present (S) and then S /= Standard_Standard loop + loop + Num_Scopes := Num_Scopes + 1; + + Use_Clauses (Num_Scopes) := + (Scope_Stack.Table + (Scope_Stack.Last - Num_Scopes + 1). + First_Use_Clause); + End_Use_Clauses (Use_Clauses (Num_Scopes)); + + exit when Scope_Stack.Last - Num_Scopes + 1 = Scope_Stack.First + or else Scope_Stack.Table + (Scope_Stack.Last - Num_Scopes).Entity + = Scope (S); + end loop; exit when Is_Generic_Instance (S) and then (In_Package_Body (S) @@ -2915,22 +3515,40 @@ package body Sem_Ch12 is S := Scope (S); end loop; - -- Remove context of current compilation unit, unless we - -- are within a nested package instantiation, in which case - -- the context has been removed previously. + -- Remove context of current compilation unit, unless we are within a + -- nested package instantiation, in which case the context has been + -- removed previously. - -- If current scope is the body of a child unit, remove context - -- of spec as well. + -- If current scope is the body of a child unit, remove context of + -- spec as well. If an enclosing scope is an instance body. the + -- context has already been removed, but the entities in the body + -- must be made invisible as well. S := Current_Scope; while Present (S) and then S /= Standard_Standard loop - exit when Is_Generic_Instance (S) - and then (In_Package_Body (S) - or else Ekind (S) = E_Procedure - or else Ekind (S) = E_Function); + if Is_Generic_Instance (S) + and then (In_Package_Body (S) + or else Ekind (S) = E_Procedure + or else Ekind (S) = E_Function) + then + -- We still have to remove the entities of the enclosing + -- instance from direct visibility. + + declare + E : Entity_Id; + begin + E := First_Entity (S); + while Present (E) loop + Set_Is_Immediately_Visible (E, False); + Next_Entity (E); + end loop; + end; + + exit; + end if; if S = Curr_Unit or else (Ekind (Curr_Unit) = E_Package_Body @@ -2942,16 +3560,16 @@ package body Sem_Ch12 is then Removed := True; - -- Remove entities in current scopes from visibility, so - -- than instance body is compiled in a clean environment. + -- Remove entities in current scopes from visibility, so that + -- instance body is compiled in a clean environment. Save_Scope_Stack (Handle_Use => False); if Is_Child_Unit (S) then -- Remove child unit from stack, as well as inner scopes. - -- Removing the context of a child unit removes parent - -- units as well. + -- Removing the context of a child unit removes parent units + -- as well. while Current_Scope /= S loop Num_Inner := Num_Inner + 1; @@ -2974,8 +3592,9 @@ package body Sem_Ch12 is S := Scope (S); end loop; + pragma Assert (Num_Inner < Num_Scopes); - New_Scope (Standard_Standard); + Push_Scope (Standard_Standard); Scope_Stack.Table (Scope_Stack.Last).Is_Active_Stack_Base := True; Instantiate_Package_Body ((N, Act_Decl, Expander_Active, Current_Sem_Unit), True); @@ -2999,23 +3618,45 @@ package body Sem_Ch12 is if Present (Curr_Scope) and then Is_Child_Unit (Curr_Scope) then - New_Scope (Curr_Scope); + Push_Scope (Curr_Scope); Set_Is_Immediately_Visible (Curr_Scope); - -- Finally, restore inner scopes as well. + -- Finally, restore inner scopes as well for J in reverse 1 .. Num_Inner loop - New_Scope (Inner_Scopes (J)); + Push_Scope (Inner_Scopes (J)); end loop; end if; Restore_Scope_Stack (Handle_Use => False); + + if Present (Curr_Scope) + and then + (In_Private_Part (Curr_Scope) + or else In_Package_Body (Curr_Scope)) + then + -- Install private declaration of ancestor units, which are + -- currently available. Restore_Scope_Stack and Install_Context + -- only install the visible part of parents. + + declare + Par : Entity_Id; + begin + Par := Scope (Curr_Scope); + while (Present (Par)) + and then Par /= Standard_Standard + loop + Install_Private_Declarations (Par); + Par := Scope (Par); + end loop; + end; + end if; end if; - -- Restore use clauses. For a child unit, use clauses in the - -- parents are restored when installing the context, so only - -- those in inner scopes (and those local to the child unit itself) - -- need to be installed explicitly. + -- Restore use clauses. For a child unit, use clauses in the parents + -- are restored when installing the context, so only those in inner + -- scopes (and those local to the child unit itself) need to be + -- installed explicitly. if Is_Child_Unit (Curr_Unit) and then Removed @@ -3034,11 +3675,32 @@ package body Sem_Ch12 is end loop; end if; - for J in 1 .. N_Instances loop - Set_Is_Generic_Instance (Instances (J), True); - end loop; + -- Restore status of instances. If one of them is a body, make + -- its local entities visible again. + + declare + E : Entity_Id; + Inst : Entity_Id; + + begin + for J in 1 .. N_Instances loop + Inst := Instances (J); + Set_Is_Generic_Instance (Inst, True); + + if In_Package_Body (Inst) + or else Ekind (S) = E_Procedure + or else Ekind (S) = E_Function + then + E := First_Entity (Instances (J)); + while Present (E) loop + Set_Is_Immediately_Visible (E); + Next_Entity (E); + end loop; + end if; + end loop; + end; - -- If generic unit is in current unit, current context is correct. + -- If generic unit is in current unit, current context is correct else Instantiate_Package_Body @@ -3076,6 +3738,7 @@ package body Sem_Ch12 is Act_Spec : Node_Id; Act_Tree : Node_Id; + Env_Installed : Boolean := False; Gen_Unit : Entity_Id; Gen_Decl : Node_Id; Pack_Id : Entity_Id; @@ -3083,11 +3746,11 @@ package body Sem_Ch12 is Renaming_List : List_Id; procedure Analyze_Instance_And_Renamings; - -- The instance must be analyzed in a context that includes the - -- mappings of generic parameters into actuals. We create a package - -- declaration for this purpose, and a subprogram with an internal - -- name within the package. The subprogram instance is simply an - -- alias for the internal subprogram, declared in the current scope. + -- The instance must be analyzed in a context that includes the mappings + -- of generic parameters into actuals. We create a package declaration + -- for this purpose, and a subprogram with an internal name within the + -- package. The subprogram instance is simply an alias for the internal + -- subprogram, declared in the current scope. ------------------------------------ -- Analyze_Instance_And_Renamings -- @@ -3100,11 +3763,11 @@ package body Sem_Ch12 is begin if Nkind (Parent (N)) = N_Compilation_Unit then - -- For the case of a compilation unit, the container package - -- has the same name as the instantiation, to insure that the - -- binder calls the elaboration procedure with the right name. - -- Copy the entity of the instance, which may have compilation - -- level flags (e.g. Is_Child_Unit) set. + -- For the case of a compilation unit, the container package has + -- the same name as the instantiation, to insure that the binder + -- calls the elaboration procedure with the right name. Copy the + -- entity of the instance, which may have compilation level flags + -- (e.g. Is_Child_Unit) set. Pack_Id := New_Copy (Def_Ent); @@ -3140,9 +3803,9 @@ package body Sem_Ch12 is -- Case of an instantiation that is a compilation unit - -- Place declaration on current node so context is complete - -- for analysis (including nested instantiations), and for - -- use in a context_clause (see Analyze_With_Clause). + -- Place declaration on current node so context is complete for + -- analysis (including nested instantiations), and for use in a + -- context_clause (see Analyze_With_Clause). else Set_Unit (Parent (N), Pack_Decl); @@ -3153,8 +3816,8 @@ package body Sem_Ch12 is Check_Formal_Packages (Pack_Id); Set_Is_Generic_Instance (Pack_Id, False); - -- Body of the enclosing package is supplied when instantiating - -- the subprogram body, after semantic analysis is completed. + -- Body of the enclosing package is supplied when instantiating the + -- subprogram body, after semantic analysis is completed. if Nkind (Parent (N)) = N_Compilation_Unit then @@ -3163,18 +3826,17 @@ package body Sem_Ch12 is Set_Name_Entity_Id (Chars (Pack_Id), Homonym (Pack_Id)); - -- Set name and scope of internal subprogram so that the - -- proper external name will be generated. The proper scope - -- is the scope of the wrapper package. We need to generate - -- debugging information for the internal subprogram, so set - -- flag accordingly. + -- Set name and scope of internal subprogram so that the proper + -- external name will be generated. The proper scope is the scope + -- of the wrapper package. We need to generate debugging info for + -- the internal subprogram, so set flag accordingly. Set_Chars (Anon_Id, Chars (Defining_Entity (N))); Set_Scope (Anon_Id, Scope (Pack_Id)); - -- Mark wrapper package as referenced, to avoid spurious - -- warnings if the instantiation appears in various with_ - -- clauses of subunits of the main unit. + -- Mark wrapper package as referenced, to avoid spurious warnings + -- if the instantiation appears in various with_ clauses of + -- subunits of the main unit. Set_Referenced (Pack_Id); end if; @@ -3188,11 +3850,13 @@ package body Sem_Ch12 is Set_Sloc (Act_Decl_Id, Sloc (Defining_Entity (N))); Set_Comes_From_Source (Act_Decl_Id, True); - -- The signature may involve types that are not frozen yet, but - -- the subprogram will be frozen at the point the wrapper package - -- is frozen, so it does not need its own freeze node. In fact, if - -- one is created, it might conflict with the freezing actions from - -- the wrapper package (see 7206-013). + -- The signature may involve types that are not frozen yet, but the + -- subprogram will be frozen at the point the wrapper package is + -- frozen, so it does not need its own freeze node. In fact, if one + -- is created, it might conflict with the freezing actions from the + -- wrapper package (see 7206-013). + + -- Should not really reference non-public TN's in comments ??? Set_Has_Delayed_Freeze (Anon_Id, False); @@ -3217,7 +3881,7 @@ package body Sem_Ch12 is Set_Cunit_Entity (Current_Sem_Unit, Pack_Id); end if; - -- The instance is not a freezing point for the new subprogram. + -- The instance is not a freezing point for the new subprogram Set_Is_Frozen (Act_Decl_Id, False); @@ -3246,12 +3910,13 @@ package body Sem_Ch12 is Text_IO_Kludge (Gen_Id); - -- Make node global for error reporting. + -- Make node global for error reporting Instantiation_Node := N; Pre_Analyze_Actuals (N); Init_Env; + Env_Installed := True; Check_Generic_Child_Unit (Gen_Id, Parent_Installed); Gen_Unit := Entity (Gen_Id); @@ -3332,19 +3997,14 @@ package body Sem_Ch12 is Gen_Decl := Unit_Declaration_Node (Gen_Unit); - -- The subprogram itself cannot contain a nested instance, so - -- the current parent is left empty. - - Set_Instance_Env (Gen_Unit, Empty); - - -- Initialize renamings map, for error checking. + -- Initialize renamings map, for error checking Generic_Renamings.Set_Last (0); Generic_Renamings_HTable.Reset; Create_Instantiation_Source (N, Gen_Unit, False, S_Adjustment); - -- Copy original generic tree, to produce text for instantiation. + -- Copy original generic tree, to produce text for instantiation Act_Tree := Copy_Generic_Node @@ -3357,9 +4017,14 @@ package body Sem_Ch12 is Generic_Formal_Declarations (Act_Tree), Generic_Formal_Declarations (Gen_Decl)); - -- Build the subprogram declaration, which does not appear - -- in the generic template, and give it a sloc consistent - -- with that of the template. + -- The subprogram itself cannot contain a nested instance, so the + -- current parent is left empty. + + Set_Instance_Env (Gen_Unit, Empty); + + -- Build the subprogram declaration, which does not appear in the + -- generic template, and give it a sloc consistent with that of the + -- template. Set_Defining_Unit_Name (Act_Spec, Anon_Id); Set_Generic_Parent (Act_Spec, Gen_Unit); @@ -3377,11 +4042,11 @@ package body Sem_Ch12 is Analyze_Instance_And_Renamings; -- If the generic is marked Import (Intrinsic), then so is the - -- instance. This indicates that there is no body to instantiate. - -- If generic is marked inline, so it the instance, and the - -- anonymous subprogram it renames. If inlined, or else if inlining - -- is enabled for the compilation, we generate the instance body - -- even if it is not within the main unit. + -- instance. This indicates that there is no body to instantiate. If + -- generic is marked inline, so it the instance, and the anonymous + -- subprogram it renames. If inlined, or else if inlining is enabled + -- for the compilation, we generate the instance body even if it is + -- not within the main unit. -- Any other pragmas might also be inherited ??? @@ -3403,6 +4068,30 @@ package body Sem_Ch12 is Check_Elab_Instantiation (N); end if; + if Is_Dispatching_Operation (Act_Decl_Id) + and then Ada_Version >= Ada_05 + then + declare + Formal : Entity_Id; + + begin + Formal := First_Formal (Act_Decl_Id); + while Present (Formal) loop + if Ekind (Etype (Formal)) = E_Anonymous_Access_Type + and then Is_Controlling_Formal (Formal) + and then not Can_Never_Be_Null (Formal) + then + Error_Msg_NE ("access parameter& is controlling,", + N, Formal); + Error_Msg_NE ("\corresponding parameter of & must be" + & " explicitly null-excluding", N, Gen_Id); + end if; + + Next_Formal (Formal); + end loop; + end; + end if; + Check_Hidden_Child_Unit (N, Gen_Unit, Act_Decl_Id); -- Subject to change, pending on if other pragmas are inherited ??? @@ -3410,7 +4099,6 @@ package body Sem_Ch12 is Validate_Categorization_Dependency (N, Act_Decl_Id); if not Is_Intrinsic_Subprogram (Act_Decl_Id) then - if not Generic_Separately_Compiled (Gen_Unit) then Inherit_Context (Gen_Decl, N); end if; @@ -3424,7 +4112,7 @@ package body Sem_Ch12 is or else Is_Inlined (Act_Decl_Id)) and then (Operating_Mode = Generate_Code or else (Operating_Mode = Check_Semantics - and then ASIS_Mode)) + and then ASIS_Mode)) and then (Expander_Active or else ASIS_Mode) and then not ABE_Is_Certain (N) and then not Is_Eliminated (Act_Decl_Id) @@ -3434,11 +4122,11 @@ package body Sem_Ch12 is (N, Act_Decl, Expander_Active, Current_Sem_Unit); Check_Forward_Instantiation (Gen_Decl); - -- The wrapper package is always delayed, because it does - -- not constitute a freeze point, but to insure that the - -- freeze node is placed properly, it is created directly - -- when instantiating the body (otherwise the freeze node - -- might appear to early for nested instantiations). + -- The wrapper package is always delayed, because it does not + -- constitute a freeze point, but to insure that the freeze + -- node is placed properly, it is created directly when + -- instantiating the body (otherwise the freeze node might + -- appear to early for nested instantiations). elsif Nkind (Parent (N)) = N_Compilation_Unit then @@ -3451,8 +4139,8 @@ package body Sem_Ch12 is elsif Nkind (Parent (N)) = N_Compilation_Unit then - -- Replace instance node for library-level instantiations - -- of intrinsic subprograms, for ASIS use. + -- Replace instance node for library-level instantiations of + -- intrinsic subprograms, for ASIS use. Rewrite (N, Unit (Parent (N))); Set_Unit (Parent (N), N); @@ -3463,6 +4151,7 @@ package body Sem_Ch12 is end if; Restore_Env; + Env_Installed := False; Generic_Renamings.Set_Last (0); Generic_Renamings_HTable.Reset; end if; @@ -3472,6 +4161,10 @@ package body Sem_Ch12 is if Parent_Installed then Remove_Parent; end if; + + if Env_Installed then + Restore_Env; + end if; end Analyze_Subprogram_Instantiation; ------------------------- @@ -3563,7 +4256,7 @@ package body Sem_Ch12 is Set_Library_Unit (Decl_Cunit, Body_Cunit); Set_Library_Unit (Body_Cunit, Decl_Cunit); - -- Preserve the private nature of the package if needed. + -- Preserve the private nature of the package if needed Set_Private_Present (Decl_Cunit, Private_Present (Body_Cunit)); @@ -3574,11 +4267,11 @@ package body Sem_Ch12 is return; end if; - -- The context clause items on the instantiation, which are now - -- attached to the body compilation unit (since the body overwrote - -- the original instantiation node), semantically belong on the spec, - -- so copy them there. It's harmless to leave them on the body as well. - -- In fact one could argue that they belong in both places. + -- The context clause items on the instantiation, which are now attached + -- to the body compilation unit (since the body overwrote the original + -- instantiation node), semantically belong on the spec, so copy them + -- there. It's harmless to leave them on the body as well. In fact one + -- could argue that they belong in both places. Citem := First (Context_Items (Body_Cunit)); while Present (Citem) loop @@ -3586,8 +4279,8 @@ package body Sem_Ch12 is Next (Citem); end loop; - -- Propagate categorization flags on packages, so that they appear - -- in ali file for the spec of the unit. + -- Propagate categorization flags on packages, so that they appear in + -- the ali file for the spec of the unit. if Ekind (New_Main) = E_Package then Set_Is_Pure (Old_Main, Is_Pure (New_Main)); @@ -3605,21 +4298,32 @@ package body Sem_Ch12 is Main_Unit_Entity := New_Main; Set_Cunit_Entity (Main_Unit, Main_Unit_Entity); - -- Build elaboration entity, since the instance may certainly - -- generate elaboration code requiring a flag for protection. + -- Build elaboration entity, since the instance may certainly generate + -- elaboration code requiring a flag for protection. Build_Elaboration_Entity (Decl_Cunit, New_Main); end Build_Instance_Compilation_Unit_Nodes; + ----------------------------- + -- Check_Access_Definition -- + ----------------------------- + + procedure Check_Access_Definition (N : Node_Id) is + begin + pragma Assert + (Ada_Version >= Ada_05 + and then Present (Access_Definition (N))); + null; + end Check_Access_Definition; + ----------------------------------- -- Check_Formal_Package_Instance -- ----------------------------------- -- If the formal has specific parameters, they must match those of the - -- actual. Both of them are instances, and the renaming declarations - -- for their formal parameters appear in the same order in both. The - -- analyzed formal has been analyzed in the context of the current - -- instance. + -- actual. Both of them are instances, and the renaming declarations for + -- their formal parameters appear in the same order in both. The analyzed + -- formal has been analyzed in the context of the current instance. procedure Check_Formal_Package_Instance (Formal_Pack : Entity_Id; @@ -3632,14 +4336,14 @@ package body Sem_Ch12 is Expr2 : Node_Id; procedure Check_Mismatch (B : Boolean); - -- Common error routine for mismatch between the parameters of - -- the actual instance and those of the formal package. + -- Common error routine for mismatch between the parameters of the + -- actual instance and those of the formal package. function Same_Instantiated_Constant (E1, E2 : Entity_Id) return Boolean; - -- The formal may come from a nested formal package, and the actual - -- may have been constant-folded. To determine whether the two denote - -- the same entity we may have to traverse several definitions to - -- recover the ultimate entity that they refer to. + -- The formal may come from a nested formal package, and the actual may + -- have been constant-folded. To determine whether the two denote the + -- same entity we may have to traverse several definitions to recover + -- the ultimate entity that they refer to. function Same_Instantiated_Variable (E1, E2 : Entity_Id) return Boolean; -- Similarly, if the formal comes from a nested formal package, the @@ -3651,8 +4355,19 @@ package body Sem_Ch12 is -------------------- procedure Check_Mismatch (B : Boolean) is + Kind : constant Node_Kind := Nkind (Parent (E2)); + begin - if B then + if Kind = N_Formal_Type_Declaration then + return; + + elsif Kind = N_Formal_Object_Declaration + or else Kind in N_Formal_Subprogram_Declaration + or else Kind = N_Formal_Package_Declaration + then + null; + + elsif B then Error_Msg_NE ("actual for & in actual instance does not match formal", Parent (Actual_Pack), E1); @@ -3667,6 +4382,7 @@ package body Sem_Ch12 is (E1, E2 : Entity_Id) return Boolean is Ent : Entity_Id; + begin Ent := E2; while Present (Ent) loop @@ -3704,7 +4420,7 @@ package body Sem_Ch12 is (E1, E2 : Entity_Id) return Boolean is function Original_Entity (E : Entity_Id) return Entity_Id; - -- Follow chain of renamings to the ultimate ancestor. + -- Follow chain of renamings to the ultimate ancestor --------------------- -- Original_Entity -- @@ -3741,12 +4457,48 @@ package body Sem_Ch12 is exit when Ekind (E1) = E_Package and then Renamed_Entity (E1) = Renamed_Entity (Actual_Pack); - if Is_Type (E1) then + -- If the formal is the renaming of the formal package, this + -- is the end of its formal part, which may occur before the + -- end of the formal part in the actual in the presence of + -- defaulted parameters in the formal package. + + exit when Nkind (Parent (E2)) = N_Package_Renaming_Declaration + and then Renamed_Entity (E2) = Scope (E2); + + -- The analysis of the actual may generate additional internal + -- entities. If the formal is defaulted, there is no corresponding + -- analysis and the internal entities must be skipped, until we + -- find corresponding entities again. + + if Comes_From_Source (E2) + and then not Comes_From_Source (E1) + and then Chars (E1) /= Chars (E2) + then + while Present (E1) + and then Chars (E1) /= Chars (E2) + loop + Next_Entity (E1); + end loop; + end if; + + if No (E1) then + return; + + -- If the formal entity comes from a formal declaration. it was + -- defaulted in the formal package, and no check is needed on it. - -- Subtypes must statically match. E1 and E2 are the - -- local entities that are subtypes of the actuals. - -- Itypes generated for other parameters need not be checked, - -- the check will be performed on the parameters themselves. + elsif Nkind (Parent (E2)) = N_Formal_Object_Declaration then + goto Next_E; + + elsif Is_Type (E1) then + + -- Subtypes must statically match. E1, E2 are the local entities + -- that are subtypes of the actuals. Itypes generated for other + -- parameters need not be checked, the check will be performed + -- on the parameters themselves. + + -- If E2 is a formal type declaration, it is a defaulted parameter + -- and needs no checking. if not Is_Itype (E1) and then not Is_Itype (E2) @@ -3759,8 +4511,8 @@ package body Sem_Ch12 is elsif Ekind (E1) = E_Constant then - -- IN parameters must denote the same static value, or - -- the same constant, or the literal null. + -- IN parameters must denote the same static value, or the same + -- constant, or the literal null. Expr1 := Expression (Parent (E1)); @@ -3776,8 +4528,7 @@ package body Sem_Ch12 is if not Is_Static_Expression (Expr2) then Check_Mismatch (True); - elsif Is_Integer_Type (Etype (E1)) then - + elsif Is_Discrete_Type (Etype (E1)) then declare V1 : constant Uint := Expr_Value (Expr1); V2 : constant Uint := Expr_Value (Expr2); @@ -3796,7 +4547,6 @@ package body Sem_Ch12 is elsif Is_String_Type (Etype (E1)) and then Nkind (Expr1) = N_String_Literal then - if Nkind (Expr2) /= N_String_Literal then Check_Mismatch (True); else @@ -3843,8 +4593,8 @@ package body Sem_Ch12 is elsif Is_Overloadable (E1) then - -- Verify that the names of the entities match. - -- What if actual is an attribute ??? + -- Verify that the names of the entities match. Note that actuals + -- that are attributes are rewritten as subprograms. Check_Mismatch (Ekind (E2) /= Ekind (E1) or else (Alias (E1)) /= Alias (E2)); @@ -3868,11 +4618,11 @@ package body Sem_Ch12 is Formal_P : Entity_Id; begin - -- Iterate through the declarations in the instance, looking for - -- package renaming declarations that denote instances of formal - -- packages. Stop when we find the renaming of the current package - -- itself. The declaration for a formal package without a box is - -- followed by an internal entity that repeats the instantiation. + -- Iterate through the declarations in the instance, looking for package + -- renaming declarations that denote instances of formal packages. Stop + -- when we find the renaming of the current package itself. The + -- declaration for a formal package without a box is followed by an + -- internal entity that repeats the instantiation. E := First_Entity (P_Id); while Present (E) loop @@ -3886,6 +4636,12 @@ package body Sem_Ch12 is elsif not Box_Present (Parent (Associated_Formal_Package (E))) then Formal_P := Next_Entity (E); Check_Formal_Package_Instance (Formal_P, E); + + -- After checking, remove the internal validating package. It + -- is only needed for semantic checks, and as it may contain + -- generic formal declarations it should not reach gigi. + + Remove (Unit_Declaration_Node (Formal_P)); end if; end if; @@ -3932,8 +4688,8 @@ package body Sem_Ch12 is -- Check_Generic_Actuals -- --------------------------- - -- The visibility of the actuals may be different between the - -- point of generic instantiation and the instantiation of the body. + -- The visibility of the actuals may be different between the point of + -- generic instantiation and the instantiation of the body. procedure Check_Generic_Actuals (Instance : Entity_Id; @@ -3943,11 +4699,12 @@ package body Sem_Ch12 is Astype : Entity_Id; function Denotes_Previous_Actual (Typ : Entity_Id) return Boolean; - -- For a formal that is an array type, the component type is often - -- a previous formal in the same unit. The privacy status of the - -- component type will have been examined earlier in the traversal - -- of the corresponding actuals, and this status should not be - -- modified for the array type itself. + -- For a formal that is an array type, the component type is often a + -- previous formal in the same unit. The privacy status of the component + -- type will have been examined earlier in the traversal of the + -- corresponding actuals, and this status should not be modified for the + -- array type itself. + -- -- To detect this case we have to rescan the list of formals, which -- is usually short enough to ignore the resulting inefficiency. @@ -3993,19 +4750,22 @@ package body Sem_Ch12 is Set_Is_Potentially_Use_Visible (E, In_Use (Instance)); - -- We constructed the generic actual type as a subtype of - -- the supplied type. This means that it normally would not - -- inherit subtype specific attributes of the actual, which - -- is wrong for the generic case. + -- We constructed the generic actual type as a subtype of the + -- supplied type. This means that it normally would not inherit + -- subtype specific attributes of the actual, which is wrong for + -- the generic case. Astype := Ancestor_Subtype (E); if No (Astype) then - -- can happen when E is an itype that is the full view of - -- a private type completed, e.g. with a constrained array. + -- This can happen when E is an itype that is the full view of + -- a private type completed, e.g. with a constrained array. In + -- that case, use the first subtype, which will carry size + -- information. The base type itself is unconstrained and will + -- not carry it. - Astype := Base_Type (E); + Astype := First_Subtype (E); end if; Set_Size_Info (E, (Astype)); @@ -4045,9 +4805,14 @@ package body Sem_Ch12 is elsif Denotes_Formal_Package (E) then null; - elsif Present (Associated_Formal_Package (E)) then + elsif Present (Associated_Formal_Package (E)) + and then not Is_Generic_Formal (E) + then if Box_Present (Parent (Associated_Formal_Package (E))) then Check_Generic_Actuals (Renamed_Object (E), True); + + else + Check_Generic_Actuals (Renamed_Object (E), False); end if; Set_Is_Hidden (E, False); @@ -4059,8 +4824,13 @@ package body Sem_Ch12 is elsif Is_Wrapper_Package (Instance) then Set_Is_Hidden (E, False); - else - Set_Is_Hidden (E, not Is_Formal_Box); + -- If the formal package is declared with a box, or if the formal + -- parameter is defaulted, it is visible in the body. + + elsif Is_Formal_Box + or else Is_Visible_Formal (E) + then + Set_Is_Hidden (E, False); end if; Next_Entity (E); @@ -4084,7 +4854,7 @@ package body Sem_Ch12 is function Find_Generic_Child (Scop : Entity_Id; Id : Node_Id) return Entity_Id; - -- Search generic parent for possible child unit with the given name. + -- Search generic parent for possible child unit with the given name function In_Enclosing_Instance return Boolean; -- Within an instance of the parent, the child unit may be denoted @@ -4145,8 +4915,18 @@ package body Sem_Ch12 is Instance_Decl : Node_Id; begin - Enclosing_Instance := Current_Scope; + -- We do not inline any call that contains instantiations, except + -- for instantiations of Unchecked_Conversion, so if we are within + -- an inlined body the current instance does not require parents. + + if In_Inlined_Body then + pragma Assert (Chars (Gen_Id) = Name_Unchecked_Conversion); + return False; + end if; + -- Loop to check enclosing scopes + + Enclosing_Instance := Current_Scope; while Present (Enclosing_Instance) loop Instance_Decl := Unit_Declaration_Node (Enclosing_Instance); @@ -4155,8 +4935,8 @@ package body Sem_Ch12 is and then Present (Generic_Parent (Specification (Instance_Decl))) then - -- Check whether the generic we are looking for is a child - -- of this instance. + -- Check whether the generic we are looking for is a child of + -- this instance. E := Find_Generic_Child (Generic_Parent (Specification (Instance_Decl)), Gen_Id); @@ -4193,13 +4973,13 @@ package body Sem_Ch12 is -- Start of processing for Check_Generic_Child_Unit begin - -- If the name of the generic is given by a selected component, it - -- may be the name of a generic child unit, and the prefix is the name - -- of an instance of the parent, in which case the child unit must be - -- visible. If this instance is not in scope, it must be placed there - -- and removed after instantiation, because what is being instantiated - -- is not the original child, but the corresponding child present in - -- the instance of the parent. + -- If the name of the generic is given by a selected component, it may + -- be the name of a generic child unit, and the prefix is the name of an + -- instance of the parent, in which case the child unit must be visible. + -- If this instance is not in scope, it must be placed there and removed + -- after instantiation, because what is being instantiated is not the + -- original child, but the corresponding child present in the instance + -- of the parent. -- If the child is instantiated within the parent, it can be given by -- a simple name. In this case the instance is already in scope, but @@ -4239,8 +5019,8 @@ package body Sem_Ch12 is if Present (Gen_Par) then - -- The prefix denotes an instantiation. The entity itself - -- may be a nested generic, or a child unit. + -- The prefix denotes an instantiation. The entity itself may be a + -- nested generic, or a child unit. E := Find_Generic_Child (Gen_Par, S); @@ -4251,15 +5031,15 @@ package body Sem_Ch12 is Set_Entity (S, E); Set_Etype (S, Etype (E)); - -- Indicate that this is a reference to the parent. + -- Indicate that this is a reference to the parent if In_Extended_Main_Source_Unit (Gen_Id) then Set_Is_Instantiated (Inst_Par); end if; - -- A common mistake is to replicate the naming scheme of - -- a hierarchy by instantiating a generic child directly, - -- rather than the implicit child in a parent instance: + -- A common mistake is to replicate the naming scheme of a + -- hierarchy by instantiating a generic child directly, rather + -- than the implicit child in a parent instance: -- generic .. package Gpar is .. -- generic .. package Gpar.Child is .. @@ -4269,10 +5049,10 @@ package body Sem_Ch12 is -- package Par.Child is new Gpar.Child (); -- rather than Par.Child - -- In this case the instantiation is within Par, which is - -- an instance, but Gpar does not denote Par because we are - -- not IN the instance of Gpar, so this is illegal. The test - -- below recognizes this particular case. + -- In this case the instantiation is within Par, which is an + -- instance, but Gpar does not denote Par because we are not IN + -- the instance of Gpar, so this is illegal. The test below + -- recognizes this particular case. if Is_Child_Unit (E) and then not Comes_From_Source (Entity (Prefix (Gen_Id))) @@ -4291,6 +5071,17 @@ package body Sem_Ch12 is then Install_Parent (Inst_Par); Parent_Installed := True; + + elsif In_Open_Scopes (Inst_Par) then + + -- If the parent is already installed verify that the + -- actuals for its formal packages declared with a box + -- are already installed. This is necessary when the + -- child instance is a child of the parent instance. + -- In this case the parent is placed on the scope stack + -- but the formal packages are not made visible. + + Install_Formal_Packages (Inst_Par); end if; else @@ -4437,8 +5228,8 @@ package body Sem_Ch12 is and then Present (Full_View (T)) and then not In_Open_Scopes (Scope (T)) then - -- In the generic, the full type was visible. Save the - -- private entity, for subsequent exchange. + -- In the generic, the full type was visible. Save the private + -- entity, for subsequent exchange. Switch_View (T); @@ -4463,12 +5254,12 @@ package body Sem_Ch12 is elsif Nkind (Parent (N)) = N_Subtype_Declaration or else not In_Private_Part (Scope (Base_Type (T))) then - Append_Elmt (T, Exchanged_Views); + Prepend_Elmt (T, Exchanged_Views); Exchange_Declarations (Etype (Get_Associated_Node (N))); end if; - -- For composite types with inconsistent representation - -- exchange component types accordingly. + -- For composite types with inconsistent representation exchange + -- component types accordingly. elsif Is_Access_Type (T) and then Is_Private_Type (Designated_Type (T)) @@ -4477,12 +5268,39 @@ package body Sem_Ch12 is then Switch_View (Designated_Type (T)); - elsif Is_Array_Type (T) - and then Is_Private_Type (Component_Type (T)) - and then not Has_Private_View (N) - and then Present (Full_View (Component_Type (T))) - then - Switch_View (Component_Type (T)); + elsif Is_Array_Type (T) then + if Is_Private_Type (Component_Type (T)) + and then not Has_Private_View (N) + and then Present (Full_View (Component_Type (T))) + then + Switch_View (Component_Type (T)); + end if; + + -- The normal exchange mechanism relies on the setting of a + -- flag on the reference in the generic. However, an additional + -- mechanism is needed for types that are not explicitly mentioned + -- in the generic, but may be needed in expanded code in the + -- instance. This includes component types of arrays and + -- designated types of access types. This processing must also + -- include the index types of arrays which we take care of here. + + declare + Indx : Node_Id; + Typ : Entity_Id; + + begin + Indx := First_Index (T); + Typ := Base_Type (Etype (Indx)); + while Present (Indx) loop + if Is_Private_Type (Typ) + and then Present (Full_View (Typ)) + then + Switch_View (Typ); + end if; + + Next_Index (Indx); + end loop; + end; elsif Is_Private_Type (T) and then Present (Full_View (T)) @@ -4491,20 +5309,25 @@ package body Sem_Ch12 is then Switch_View (T); - -- Finally, a non-private subtype may have a private base type, - -- which must be exchanged for consistency. This can happen when - -- instantiating a package body, when the scope stack is empty - -- but in fact the subtype and the base type are declared in an - -- enclosing scope. + -- Finally, a non-private subtype may have a private base type, which + -- must be exchanged for consistency. This can happen when a package + -- body is instantiated, when the scope stack is empty but in fact + -- the subtype and the base type are declared in an enclosing scope. + + -- Note that in this case we introduce an inconsistency in the view + -- set, because we switch the base type BT, but there could be some + -- private dependent subtypes of BT which remain unswitched. Such + -- subtypes might need to be switched at a later point (see specific + -- provision for that case in Switch_View). elsif not Is_Private_Type (T) and then not Has_Private_View (N) - and then Is_Private_Type (Base_Type (T)) + and then Is_Private_Type (BT) and then Present (Full_View (BT)) and then not Is_Generic_Type (BT) and then not In_Open_Scopes (BT) then - Append_Elmt (Full_View (BT), Exchanged_Views); + Prepend_Elmt (Full_View (BT), Exchanged_Views); Exchange_Declarations (BT); end if; end if; @@ -4567,7 +5390,7 @@ package body Sem_Ch12 is Next_Elmt (Elmt); end loop; - -- Indicate that Inner is being instantiated within Scop. + -- Indicate that Inner is being instantiated within Scop Append_Elmt (Inner, Inner_Instances (Scop)); end if; @@ -4601,15 +5424,15 @@ package body Sem_Ch12 is -- value (Sloc, Uint, Char) in which case it need not be copied. procedure Copy_Descendants; - -- Common utility for various nodes. + -- Common utility for various nodes function Copy_Generic_Elist (E : Elist_Id) return Elist_Id; - -- Make copy of element list. + -- Make copy of element list function Copy_Generic_List (L : List_Id; Parent_Id : Node_Id) return List_Id; - -- Apply Copy_Node recursively to the members of a node list. + -- Apply Copy_Node recursively to the members of a node list function In_Defining_Unit_Name (Nam : Node_Id) return Boolean; -- True if an identifier is part of the defining program unit name @@ -4771,20 +5594,20 @@ package body Sem_Ch12 is -- must preserve references that were global to the enclosing -- parent at that point. Other occurrences, whether global or -- local to the current generic, must be resolved anew, so we - -- reset the entity in the generic copy. A global reference has - -- a smaller depth than the parent, or else the same depth in - -- case both are distinct compilation units. + -- reset the entity in the generic copy. A global reference has a + -- smaller depth than the parent, or else the same depth in case + -- both are distinct compilation units. -- It is also possible for Current_Instantiated_Parent to be - -- defined, and for this not to be a nested generic, namely - -- if the unit is loaded through Rtsfind. In that case, the - -- entity of New_N is only a link to the associated node, and - -- not a defining occurrence. + -- defined, and for this not to be a nested generic, namely if the + -- unit is loaded through Rtsfind. In that case, the entity of + -- New_N is only a link to the associated node, and not a defining + -- occurrence. - -- The entities for parent units in the defining_program_unit - -- of a generic child unit are established when the context of - -- the unit is first analyzed, before the generic copy is made. - -- They are preserved in the copy for use in ASIS queries. + -- The entities for parent units in the defining_program_unit of a + -- generic child unit are established when the context of the unit + -- is first analyzed, before the generic copy is made. They are + -- preserved in the copy for use in ASIS queries. Ent := Entity (New_N); @@ -4817,11 +5640,11 @@ package body Sem_Ch12 is -- Case of instantiating identifier or some other name or operator else - -- If the associated node is still defined, the entity in - -- it is global, and must be copied to the instance. - -- If this copy is being made for a body to inline, it is - -- applied to an instantiated tree, and the entity is already - -- present and must be also preserved. + -- If the associated node is still defined, the entity in it is + -- global, and must be copied to the instance. If this copy is + -- being made for a body to inline, it is applied to an + -- instantiated tree, and the entity is already present and must + -- be also preserved. declare Assoc : constant Node_Id := Get_Associated_Node (N); @@ -4840,8 +5663,8 @@ package body Sem_Ch12 is and then Expander_Active then -- Inlining case: we are copying a tree that contains - -- global entities, which are preserved in the copy - -- to be used for subsequent inlining. + -- global entities, which are preserved in the copy to be + -- used for subsequent inlining. null; @@ -4912,9 +5735,9 @@ package body Sem_Ch12 is Subunit => True, Error_Node => N); - -- If the proper body is not found, a warning message will - -- be emitted when analyzing the stub, or later at the the - -- point of instantiation. Here we just leave the stub as is. + -- If the proper body is not found, a warning message will be + -- emitted when analyzing the stub, or later at the the point + -- of instantiation. Here we just leave the stub as is. if Unum = No_Unit then Subunits_Missing := True; @@ -4931,32 +5754,32 @@ package body Sem_Ch12 is goto Subunit_Not_Found; end if; - -- We must create a generic copy of the subunit, in order - -- to perform semantic analysis on it, and we must replace - -- the stub in the original generic unit with the subunit, - -- in order to preserve non-local references within. + -- We must create a generic copy of the subunit, in order to + -- perform semantic analysis on it, and we must replace the + -- stub in the original generic unit with the subunit, in order + -- to preserve non-local references within. -- Only the proper body needs to be copied. Library_Unit and -- context clause are simply inherited by the generic copy. -- Note that the copy (which may be recursive if there are - -- nested subunits) must be done first, before attaching it - -- to the enclosing generic. + -- nested subunits) must be done first, before attaching it to + -- the enclosing generic. New_Body := Copy_Generic_Node (Proper_Body (Unit (Subunit)), Empty, Instantiating => False); - -- Now place the original proper body in the original - -- generic unit. This is a body, not a compilation unit. + -- Now place the original proper body in the original generic + -- unit. This is a body, not a compilation unit. Rewrite (N, Proper_Body (Unit (Subunit))); Set_Is_Compilation_Unit (Defining_Entity (N), False); Set_Was_Originally_Stub (N); - -- Finally replace the body of the subunit with its copy, - -- and make this new subunit into the library unit of the - -- generic copy, which does not have stubs any longer. + -- Finally replace the body of the subunit with its copy, and + -- make this new subunit into the library unit of the generic + -- copy, which does not have stubs any longer. Set_Proper_Body (Unit (Subunit), New_Body); Set_Library_Unit (New_N, Subunit); @@ -4964,9 +5787,9 @@ package body Sem_Ch12 is end; -- If we are instantiating, this must be an error case, since - -- otherwise we would have replaced the stub node by the proper - -- body that corresponds. So just ignore it in the copy (i.e. - -- we have copied it, and that is good enough). + -- otherwise we would have replaced the stub node by the proper body + -- that corresponds. So just ignore it in the copy (i.e. we have + -- copied it, and that is good enough). else null; @@ -4974,22 +5797,22 @@ package body Sem_Ch12 is <> null; - -- If the node is a compilation unit, it is the subunit of a stub, - -- which has been loaded already (see code below). In this case, - -- the library unit field of N points to the parent unit (which - -- is a compilation unit) and need not (and cannot!) be copied. + -- If the node is a compilation unit, it is the subunit of a stub, which + -- has been loaded already (see code below). In this case, the library + -- unit field of N points to the parent unit (which is a compilation + -- unit) and need not (and cannot!) be copied. - -- When the proper body of the stub is analyzed, thie library_unit - -- link is used to establish the proper context (see sem_ch10). + -- When the proper body of the stub is analyzed, thie library_unit link + -- is used to establish the proper context (see sem_ch10). -- The other fields of a compilation unit are copied as usual elsif Nkind (N) = N_Compilation_Unit then - -- This code can only be executed when not instantiating, because - -- in the copy made for an instantiation, the compilation unit - -- node has disappeared at the point that a stub is replaced by - -- its proper body. + -- This code can only be executed when not instantiating, because in + -- the copy made for an instantiation, the compilation unit node has + -- disappeared at the point that a stub is replaced by its proper + -- body. pragma Assert (not Instantiating); @@ -5101,7 +5924,8 @@ package body Sem_Ch12 is begin if Present (T) then - -- Retrieve the allocator node in the generic copy. + + -- Retrieve the allocator node in the generic copy Acc_T := Etype (Parent (Parent (T))); if Present (Acc_T) @@ -5116,10 +5940,10 @@ package body Sem_Ch12 is -- For a proper body, we must catch the case of a proper body that -- replaces a stub. This represents the point at which a separate - -- compilation unit, and hence template file, may be referenced, so - -- we must make a new source instantiation entry for the template - -- of the subunit, and ensure that all nodes in the subunit are - -- adjusted using this new source instantiation entry. + -- compilation unit, and hence template file, may be referenced, so we + -- must make a new source instantiation entry for the template of the + -- subunit, and ensure that all nodes in the subunit are adjusted using + -- this new source instantiation entry. elsif Nkind (N) in N_Proper_Body then declare @@ -5144,8 +5968,8 @@ package body Sem_Ch12 is S_Adjustment := Save_Adjustment; end; - -- Don't copy Ident or Comment pragmas, since the comment belongs - -- to the generic unit, not to the instantiating unit. + -- Don't copy Ident or Comment pragmas, since the comment belongs to the + -- generic unit, not to the instantiating unit. elsif Nkind (N) = N_Pragma and then Instantiating @@ -5166,6 +5990,7 @@ package body Sem_Ch12 is elsif Nkind (N) = N_Integer_Literal or else Nkind (N) = N_Real_Literal + or else Nkind (N) = N_String_Literal then -- No descendant fields need traversing @@ -5213,16 +6038,17 @@ package body Sem_Ch12 is then return True; - elsif Nkind (Parent (Pack)) = N_Formal_Package_Declaration then + elsif Nkind (Original_Node (Unit_Declaration_Node (Pack))) = + N_Formal_Package_Declaration + then return True; elsif No (Par) then return False; else - -- Check whether this package is associated with a formal - -- package of the enclosing instantiation. Iterate over the - -- list of renamings. + -- Check whether this package is associated with a formal package of + -- the enclosing instantiation. Iterate over the list of renamings. E := First_Entity (Par); while Present (E) loop @@ -5230,6 +6056,7 @@ package body Sem_Ch12 is or else Nkind (Parent (E)) /= N_Package_Renaming_Declaration then null; + elsif Renamed_Object (E) = Par then return False; @@ -5250,8 +6077,8 @@ package body Sem_Ch12 is procedure End_Generic is begin - -- ??? More things could be factored out in this - -- routine. Should probably be done at a later stage. + -- ??? More things could be factored out in this routine. Should + -- probably be done at a later stage. Inside_A_Generic := Generic_Flags.Table (Generic_Flags.Last); Generic_Flags.Decrement_Last; @@ -5283,6 +6110,9 @@ package body Sem_Ch12 is while Present (T) loop if In_Open_Scopes (Scope (T)) then return T; + + elsif Is_Generic_Actual_Type (T) then + return T; end if; T := Homonym (T); @@ -5324,7 +6154,7 @@ package body Sem_Ch12 is -- node for it. function True_Parent (N : Node_Id) return Node_Id; - -- For a subunit, return parent of corresponding stub. + -- For a subunit, return parent of corresponding stub ------------- -- Earlier -- @@ -5337,7 +6167,7 @@ package body Sem_Ch12 is P2 : Node_Id := N2; procedure Find_Depth (P : in out Node_Id; D : in out Integer); - -- Find distance from given node to enclosing compilation unit. + -- Find distance from given node to enclosing compilation unit ---------------- -- Find_Depth -- @@ -5469,13 +6299,13 @@ package body Sem_Ch12 is -- Start of processing of Freeze_Subprogram_Body begin - -- If the instance and the generic body appear within the same - -- unit, and the instance preceeds the generic, the freeze node for - -- the instance must appear after that of the generic. If the generic - -- is nested within another instance I2, then current instance must - -- be frozen after I2. In both cases, the freeze nodes are those of - -- enclosing packages. Otherwise, the freeze node is placed at the end - -- of the current declarative part. + -- If the instance and the generic body appear within the same unit, and + -- the instance preceeds the generic, the freeze node for the instance + -- must appear after that of the generic. If the generic is nested + -- within another instance I2, then current instance must be frozen + -- after I2. In both cases, the freeze nodes are those of enclosing + -- packages. Otherwise, the freeze node is placed at the end of the + -- current declarative part. Enc_G := Enclosing_Body (Gen_Body); Enc_I := Enclosing_Body (Inst_Node); @@ -5489,8 +6319,8 @@ package body Sem_Ch12 is then if ABE_Is_Certain (Get_Package_Instantiation_Node (Par)) then - -- The parent was a premature instantiation. Insert freeze - -- node at the end the current declarative part. + -- The parent was a premature instantiation. Insert freeze node at + -- the end the current declarative part. Insert_After_Last_Decl (Inst_Node, F_Node); @@ -5498,12 +6328,12 @@ package body Sem_Ch12 is Insert_After (Freeze_Node (Par), F_Node); end if; - -- The body enclosing the instance should be frozen after the body - -- that includes the generic, because the body of the instance may - -- make references to entities therein. If the two are not in the - -- same declarative part, or if the one enclosing the instance is - -- frozen already, freeze the instance at the end of the current - -- declarative part. + -- The body enclosing the instance should be frozen after the body that + -- includes the generic, because the body of the instance may make + -- references to entities therein. If the two are not in the same + -- declarative part, or if the one enclosing the instance is frozen + -- already, freeze the instance at the end of the current declarative + -- part. elsif Is_Generic_Instance (Par) and then Present (Freeze_Node (Par)) @@ -5540,8 +6370,8 @@ package body Sem_Ch12 is -- Freeze package that encloses instance, and place node after -- package that encloses generic. If enclosing package is already - -- frozen we have to assume it is at the proper place. This may - -- be a potential ABE that requires dynamic checking. + -- frozen we have to assume it is at the proper place. This may be + -- a potential ABE that requires dynamic checking. Insert_After_Last_Decl (Enc_G, Package_Freeze_Node (Enc_I)); @@ -5556,8 +6386,8 @@ package body Sem_Ch12 is Insert_After_Last_Decl (Inst_Node, F_Node); else - -- If none of the above, insert freeze node at the end of the - -- current declarative part. + -- If none of the above, insert freeze node at the end of the current + -- declarative part. Insert_After_Last_Decl (Inst_Node, F_Node); end if; @@ -5583,8 +6413,8 @@ package body Sem_Ch12 is if Res /= Assoc_Null then return Generic_Renamings.Table (Res).Act_Id; else - -- On exit, entity is not instantiated: not a generic parameter, - -- or else parameter of an inner generic unit. + -- On exit, entity is not instantiated: not a generic parameter, or + -- else parameter of an inner generic unit. return A; end if; @@ -5599,21 +6429,39 @@ package body Sem_Ch12 is Inst : Node_Id; begin - -- If the instantiation is a compilation unit that does not need a - -- body then the instantiation node has been rewritten as a package + -- If the Package_Instantiation attribute has been set on the package + -- entity, then use it directly when it (or its Original_Node) refers + -- to an N_Package_Instantiation node. In principle it should be + -- possible to have this field set in all cases, which should be + -- investigated, and would allow this function to be significantly + -- simplified. ??? + + if Present (Package_Instantiation (A)) then + if Nkind (Package_Instantiation (A)) = N_Package_Instantiation then + return Package_Instantiation (A); + + elsif Nkind (Original_Node (Package_Instantiation (A))) + = N_Package_Instantiation + then + return Original_Node (Package_Instantiation (A)); + end if; + end if; + + -- If the instantiation is a compilation unit that does not need body + -- then the instantiation node has been rewritten as a package -- declaration for the instance, and we return the original node. -- If it is a compilation unit and the instance node has not been - -- rewritten, then it is still the unit of the compilation. Finally, - -- if a body is present, this is a parent of the main unit whose body - -- has been compiled for inlining purposes, and the instantiation node - -- has been rewritten with the instance body. + -- rewritten, then it is still the unit of the compilation. Finally, if + -- a body is present, this is a parent of the main unit whose body has + -- been compiled for inlining purposes, and the instantiation node has + -- been rewritten with the instance body. - -- Otherwise the instantiation node appears after the declaration. - -- If the entity is a formal package, the declaration may have been - -- rewritten as a generic declaration (in the case of a formal with a - -- box) or left as a formal package declaration if it has actuals, and - -- is found with a forward search. + -- Otherwise the instantiation node appears after the declaration. If + -- the entity is a formal package, the declaration may have been + -- rewritten as a generic declaration (in the case of a formal with box) + -- or left as a formal package declaration if it has actuals, and is + -- found with a forward search. if Nkind (Parent (Decl)) = N_Compilation_Unit then if Nkind (Decl) = N_Package_Declaration @@ -5628,7 +6476,7 @@ package body Sem_Ch12 is return Unit (Parent (Decl)); end if; - elsif Nkind (Decl) = N_Generic_Package_Declaration + elsif Nkind (Decl) = N_Package_Declaration and then Nkind (Original_Node (Decl)) = N_Formal_Package_Declaration then return Original_Node (Decl); @@ -5650,9 +6498,10 @@ package body Sem_Ch12 is ------------------------ function Has_Been_Exchanged (E : Entity_Id) return Boolean is - Next : Elmt_Id := First_Elmt (Exchanged_Views); + Next : Elmt_Id; begin + Next := First_Elmt (Exchanged_Views); while Present (Next) loop if Full_View (Node (Next)) = E then return True; @@ -5683,8 +6532,8 @@ package body Sem_Ch12 is begin Set_Is_Hidden_Open_Scope (C); - E := First_Entity (C); + E := First_Entity (C); while Present (E) loop if Is_Immediately_Visible (E) then Set_Is_Immediately_Visible (E, False); @@ -5694,11 +6543,11 @@ package body Sem_Ch12 is Next_Entity (E); end loop; - -- Make the scope name invisible as well. This is necessary, but - -- might conflict with calls to Rtsfind later on, in case the scope - -- is a predefined one. There is no clean solution to this problem, so - -- for now we depend on the user not redefining Standard itself in one - -- of the parent units. + -- Make the scope name invisible as well. This is necessary, but might + -- conflict with calls to Rtsfind later on, in case the scope is a + -- predefined one. There is no clean solution to this problem, so for + -- now we depend on the user not redefining Standard itself in one of + -- the parent units. if Is_Immediately_Visible (C) and then C /= Standard_Standard @@ -5717,19 +6566,26 @@ package body Sem_Ch12 is Saved : Instance_Env; begin - Saved.Ada_Version := Ada_Version; - Saved.Instantiated_Parent := Current_Instantiated_Parent; - Saved.Exchanged_Views := Exchanged_Views; - Saved.Hidden_Entities := Hidden_Entities; - Saved.Current_Sem_Unit := Current_Sem_Unit; + Saved.Instantiated_Parent := Current_Instantiated_Parent; + Saved.Exchanged_Views := Exchanged_Views; + Saved.Hidden_Entities := Hidden_Entities; + Saved.Current_Sem_Unit := Current_Sem_Unit; + Saved.Parent_Unit_Visible := Parent_Unit_Visible; + Saved.Instance_Parent_Unit := Instance_Parent_Unit; + + -- Save configuration switches. These may be reset if the unit is a + -- predefined unit, and the current mode is not Ada 2005. + + Save_Opt_Config_Switches (Saved.Switches); + Instance_Envs.Increment_Last; Instance_Envs.Table (Instance_Envs.Last) := Saved; Exchanged_Views := New_Elmt_List; Hidden_Entities := New_Elmt_List; - -- Make dummy entry for Instantiated parent. If generic unit is - -- legal, this is set properly in Set_Instance_Env. + -- Make dummy entry for Instantiated parent. If generic unit is legal, + -- this is set properly in Set_Instance_Env. Current_Instantiated_Parent := (Current_Scope, Current_Scope, Assoc_Null); @@ -5773,6 +6629,51 @@ package body Sem_Ch12 is end In_Same_Declarative_Part; --------------------- + -- In_Main_Context -- + --------------------- + + function In_Main_Context (E : Entity_Id) return Boolean is + Context : List_Id; + Clause : Node_Id; + Nam : Node_Id; + + begin + if not Is_Compilation_Unit (E) + or else Ekind (E) /= E_Package + or else In_Private_Part (E) + then + return False; + end if; + + Context := Context_Items (Cunit (Main_Unit)); + + Clause := First (Context); + while Present (Clause) loop + if Nkind (Clause) = N_With_Clause then + Nam := Name (Clause); + + -- If the current scope is part of the context of the main unit, + -- analysis of the corresponding with_clause is not complete, and + -- the entity is not set. We use the Chars field directly, which + -- might produce false positives in rare cases, but guarantees + -- that we produce all the instance bodies we will need. + + if (Nkind (Nam) = N_Identifier + and then Chars (Nam) = Chars (E)) + or else (Nkind (Nam) = N_Selected_Component + and then Chars (Selector_Name (Nam)) = Chars (E)) + then + return True; + end if; + end if; + + Next (Clause); + end loop; + + return False; + end In_Main_Context; + + --------------------- -- Inherit_Context -- --------------------- @@ -5863,7 +6764,7 @@ package body Sem_Ch12 is Act_Unit : constant Node_Id := Unit (Cunit (Get_Source_Unit (N))); Gen_Id : constant Entity_Id := Corresponding_Spec (Gen_Body); Par : constant Entity_Id := Scope (Gen_Id); - Gen_Unit : constant Node_Id := + Gen_Unit : constant Node_Id := Unit (Cunit (Get_Source_Unit (Gen_Decl))); Orig_Body : Node_Id := Gen_Body; F_Node : Node_Id; @@ -5872,7 +6773,7 @@ package body Sem_Ch12 is Must_Delay : Boolean; function Enclosing_Subp (Id : Entity_Id) return Entity_Id; - -- Find subprogram (if any) that encloses instance and/or generic body. + -- Find subprogram (if any) that encloses instance and/or generic body function True_Sloc (N : Node_Id) return Source_Ptr; -- If the instance is nested inside a generic unit, the Sloc of the @@ -5880,7 +6781,7 @@ package body Sem_Ch12 is -- point of the current enclosing instance. Pending a better usage of -- Slocs to indicate instantiation places, we determine the place of -- origin of a node by finding the maximum sloc of any ancestor node. - -- Why is this not equivalent fo Top_Level_Location ??? + -- Why is this not equivalent to Top_Level_Location ??? -------------------- -- Enclosing_Subp -- @@ -5935,11 +6836,11 @@ package body Sem_Ch12 is Body_Unit := Unit (Cunit (Get_Source_Unit (Orig_Body))); - -- If the instantiation and the generic definition appear in the - -- same package declaration, this is an early instantiation. - -- If they appear in the same declarative part, it is an early - -- instantiation only if the generic body appears textually later, - -- and the generic body is also in the main unit. + -- If the instantiation and the generic definition appear in the same + -- package declaration, this is an early instantiation. If they appear + -- in the same declarative part, it is an early instantiation only if + -- the generic body appears textually later, and the generic body is + -- also in the main unit. -- If instance is nested within a subprogram, and the generic body is -- not, the instance is delayed because the enclosing body is. If @@ -6018,6 +6919,42 @@ package body Sem_Ch12 is Mark_Rewrite_Insertion (Act_Body); end Install_Body; + ----------------------------- + -- Install_Formal_Packages -- + ----------------------------- + + procedure Install_Formal_Packages (Par : Entity_Id) is + E : Entity_Id; + + begin + E := First_Entity (Par); + while Present (E) loop + if Ekind (E) = E_Package + and then Nkind (Parent (E)) = N_Package_Renaming_Declaration + then + -- If this is the renaming for the parent instance, done + + if Renamed_Object (E) = Par then + exit; + + -- The visibility of a formal of an enclosing generic is + -- already correct. + + elsif Denotes_Formal_Package (E) then + null; + + elsif Present (Associated_Formal_Package (E)) + and then Box_Present (Parent (Associated_Formal_Package (E))) + then + Check_Generic_Actuals (Renamed_Object (E), True); + Set_Is_Hidden (E, False); + end if; + end if; + + Next_Entity (E); + end loop; + end Install_Formal_Packages; + -------------------- -- Install_Parent -- -------------------- @@ -6032,57 +6969,13 @@ package body Sem_Ch12 is First_Gen : Entity_Id; Elmt : Elmt_Id; - procedure Install_Formal_Packages (Par : Entity_Id); - -- If any of the formals of the parent are formal packages with box, - -- their formal parts are visible in the parent and thus in the child - -- unit as well. Analogous to what is done in Check_Generic_Actuals - -- for the unit itself. - procedure Install_Noninstance_Specs (Par : Entity_Id); - -- Install the scopes of noninstance parent units ending with Par. + -- Install the scopes of noninstance parent units ending with Par procedure Install_Spec (Par : Entity_Id); -- The child unit is within the declarative part of the parent, so -- the declarations within the parent are immediately visible. - ----------------------------- - -- Install_Formal_Packages -- - ----------------------------- - - procedure Install_Formal_Packages (Par : Entity_Id) is - E : Entity_Id; - - begin - E := First_Entity (Par); - - while Present (E) loop - - if Ekind (E) = E_Package - and then Nkind (Parent (E)) = N_Package_Renaming_Declaration - then - -- If this is the renaming for the parent instance, done. - - if Renamed_Object (E) = Par then - exit; - - -- The visibility of a formal of an enclosing generic is - -- already correct. - - elsif Denotes_Formal_Package (E) then - null; - - elsif Present (Associated_Formal_Package (E)) - and then Box_Present (Parent (Associated_Formal_Package (E))) - then - Check_Generic_Actuals (Renamed_Object (E), True); - Set_Is_Hidden (E, False); - end if; - end if; - - Next_Entity (E); - end loop; - end Install_Formal_Packages; - ------------------------------- -- Install_Noninstance_Specs -- ------------------------------- @@ -6107,12 +7000,43 @@ package body Sem_Ch12 is Specification (Unit_Declaration_Node (Par)); begin - New_Scope (Par); + -- If this parent of the child instance is a top-level unit, + -- then record the unit and its visibility for later resetting + -- in Remove_Parent. We exclude units that are generic instances, + -- as we only want to record this information for the ultimate + -- top-level noninstance parent (is that always correct???). + + if Scope (Par) = Standard_Standard + and then not Is_Generic_Instance (Par) + then + Parent_Unit_Visible := Is_Immediately_Visible (Par); + Instance_Parent_Unit := Par; + end if; + + -- Open the parent scope and make it and its declarations visible. + -- If this point is not within a body, then only the visible + -- declarations should be made visible, and installation of the + -- private declarations is deferred until the appropriate point + -- within analysis of the spec being instantiated (see the handling + -- of parent visibility in Analyze_Package_Specification). This is + -- relaxed in the case where the parent unit is Ada.Tags, to avoid + -- private view problems that occur when compiling instantiations of + -- a generic child of that package (Generic_Dispatching_Constructor). + -- If the instance freezes a tagged type, inlinings of operations + -- from Ada.Tags may need the full view of type Tag. If inlining took + -- proper account of establishing visibility of inlined subprograms' + -- parents then it should be possible to remove this + -- special check. ??? + + Push_Scope (Par); Set_Is_Immediately_Visible (Par); Install_Visible_Declarations (Par); - Install_Private_Declarations (Par); Set_Use (Visible_Declarations (Spec)); - Set_Use (Private_Declarations (Spec)); + + if In_Body or else Is_RTU (Par, Ada_Tags) then + Install_Private_Declarations (Par); + Set_Use (Private_Declarations (Spec)); + end if; end Install_Spec; -- Start of processing for Install_Parent @@ -6120,9 +7044,9 @@ package body Sem_Ch12 is begin -- We need to install the parent instance to compile the instantiation -- of the child, but the child instance must appear in the current - -- scope. Given that we cannot place the parent above the current - -- scope in the scope stack, we duplicate the current scope and unstack - -- both after the instantiation is complete. + -- scope. Given that we cannot place the parent above the current scope + -- in the scope stack, we duplicate the current scope and unstack both + -- after the instantiation is complete. -- If the parent is itself the instantiation of a child unit, we must -- also stack the instantiation of its parent, and so on. Each such @@ -6202,7 +7126,7 @@ package body Sem_Ch12 is end if; if not In_Body then - New_Scope (S); + Push_Scope (S); end if; end Install_Parent; @@ -6236,16 +7160,23 @@ package body Sem_Ch12 is -- because each actual has the same name as the formal, and they do -- appear in the same order. - function Formal_Entity - (F : Node_Id; - Act_Ent : Entity_Id) return Entity_Id; - -- Returns the entity associated with the given formal F. In the - -- case where F is a formal package, this function will iterate - -- through all of F's formals and enter map associations from the + function Get_Formal_Entity (N : Node_Id) return Entity_Id; + -- Retrieve entity of defining entity of generic formal parameter. + -- Only the declarations of formals need to be considered when + -- linking them to actuals, but the declarative list may include + -- internal entities generated during analysis, and those are ignored. + + procedure Match_Formal_Entity + (Formal_Node : Node_Id; + Formal_Ent : Entity_Id; + Actual_Ent : Entity_Id); + -- Associates the formal entity with the actual. In the case + -- where Formal_Ent is a formal package, this procedure iterates + -- through all of its formals and enters associations betwen the -- actuals occurring in the formal package's corresponding actual - -- package (obtained via Act_Ent) to the formal package's formal - -- parameters. This function is called recursively for arbitrary - -- levels of formal packages. + -- package (given by Actual_Ent) and the formal package's formal + -- parameters. This procedure recurses if any of the parameters is + -- itself a package. function Is_Instance_Of (Act_Spec : Entity_Id; @@ -6309,107 +7240,110 @@ package body Sem_Ch12 is end case; end Find_Matching_Actual; - ------------------- - -- Formal_Entity -- - ------------------- + ------------------------- + -- Match_Formal_Entity -- + ------------------------- - function Formal_Entity - (F : Node_Id; - Act_Ent : Entity_Id) return Entity_Id + procedure Match_Formal_Entity + (Formal_Node : Node_Id; + Formal_Ent : Entity_Id; + Actual_Ent : Entity_Id) is - Orig_Node : Node_Id := F; Act_Pkg : Entity_Id; begin - case Nkind (Original_Node (F)) is - when N_Formal_Object_Declaration => - return Defining_Identifier (F); + Set_Instance_Of (Formal_Ent, Actual_Ent); - when N_Formal_Type_Declaration => - return Defining_Identifier (F); + if Ekind (Actual_Ent) = E_Package then - when N_Formal_Subprogram_Declaration => - return Defining_Unit_Name (Specification (F)); + -- Record associations for each parameter - when N_Package_Declaration => - return Defining_Unit_Name (Specification (F)); + Act_Pkg := Actual_Ent; - when N_Formal_Package_Declaration | - N_Generic_Package_Declaration => + declare + A_Ent : Entity_Id := First_Entity (Act_Pkg); + F_Ent : Entity_Id; + F_Node : Node_Id; - if Nkind (F) = N_Generic_Package_Declaration then - Orig_Node := Original_Node (F); - end if; + Gen_Decl : Node_Id; + Formals : List_Id; + Actual : Entity_Id; - Act_Pkg := Act_Ent; + begin + -- Retrieve the actual given in the formal package declaration - -- Find matching actual package, skipping over itypes and - -- other entities generated when analyzing the formal. We - -- know that if the instantiation is legal then there is - -- a matching package for the formal. + Actual := Entity (Name (Original_Node (Formal_Node))); - while Ekind (Act_Pkg) /= E_Package loop - Act_Pkg := Next_Entity (Act_Pkg); - end loop; + -- The actual in the formal package declaration may be a + -- renamed generic package, in which case we want to retrieve + -- the original generic in order to traverse its formal part. - declare - Actual_Ent : Entity_Id := First_Entity (Act_Pkg); - Formal_Node : Node_Id; - Formal_Ent : Entity_Id; + if Present (Renamed_Entity (Actual)) then + Gen_Decl := Unit_Declaration_Node (Renamed_Entity (Actual)); + else + Gen_Decl := Unit_Declaration_Node (Actual); + end if; - Gen_Decl : constant Node_Id := - Unit_Declaration_Node - (Entity (Name (Orig_Node))); + Formals := Generic_Formal_Declarations (Gen_Decl); - Formals : constant List_Id := - Generic_Formal_Declarations (Gen_Decl); + if Present (Formals) then + F_Node := First_Non_Pragma (Formals); + else + F_Node := Empty; + end if; - begin - if Present (Formals) then - Formal_Node := First_Non_Pragma (Formals); - else - Formal_Node := Empty; + while Present (A_Ent) + and then Present (F_Node) + and then A_Ent /= First_Private_Entity (Act_Pkg) + loop + F_Ent := Get_Formal_Entity (F_Node); + + if Present (F_Ent) then + + -- This is a formal of the original package. Record + -- association and recurse. + + Find_Matching_Actual (F_Node, A_Ent); + Match_Formal_Entity (F_Node, F_Ent, A_Ent); + Next_Entity (A_Ent); end if; - while Present (Actual_Ent) - and then Present (Formal_Node) - and then Actual_Ent /= First_Private_Entity (Act_Ent) - loop - -- ??? Are the following calls also needed here: - -- - -- Set_Is_Hidden (Actual_Ent, False); - -- Set_Is_Potentially_Use_Visible - -- (Actual_Ent, In_Use (Act_Ent)); - - Formal_Ent := Formal_Entity (Formal_Node, Actual_Ent); - if Present (Formal_Ent) then - Set_Instance_Of (Formal_Ent, Actual_Ent); - end if; - Next_Non_Pragma (Formal_Node); + Next_Non_Pragma (F_Node); + end loop; + end; + end if; + end Match_Formal_Entity; - Next_Entity (Actual_Ent); - end loop; - end; + ----------------------- + -- Get_Formal_Entity -- + ----------------------- - return Defining_Identifier (Orig_Node); + function Get_Formal_Entity (N : Node_Id) return Entity_Id is + Kind : constant Node_Kind := Nkind (Original_Node (N)); + begin + case Kind is + when N_Formal_Object_Declaration => + return Defining_Identifier (N); - when N_Use_Package_Clause => - return Empty; + when N_Formal_Type_Declaration => + return Defining_Identifier (N); - when N_Use_Type_Clause => - return Empty; + when N_Formal_Subprogram_Declaration => + return Defining_Unit_Name (Specification (N)); + + when N_Formal_Package_Declaration => + return Defining_Identifier (Original_Node (N)); + + when N_Generic_Package_Declaration => + return Defining_Identifier (Original_Node (N)); - -- We return Empty for all other encountered forms of - -- declarations because there are some cases of nonformal - -- sorts of declaration that can show up (e.g., when array - -- formals are present). Since it's not clear what kinds - -- can appear among the formals, we won't raise failure here. + -- All other declarations are introduced by semantic analysis and + -- have no match in the actual. when others => return Empty; - end case; - end Formal_Entity; + end Get_Formal_Entity; -------------------- -- Is_Instance_Of -- @@ -6425,7 +7359,7 @@ package body Sem_Ch12 is if No (Gen_Par) then return False; - -- Simplest case: the generic parent of the actual is the formal. + -- Simplest case: the generic parent of the actual is the formal elsif Gen_Par = Gen_Anc then return True; @@ -6466,9 +7400,13 @@ package body Sem_Ch12 is while Present (E1) and then E1 /= First_Private_Entity (Form) loop + -- Could this test be a single condition??? + -- Seems like it could, and isn't FPE (Form) a constant anyway??? + if not Is_Internal (E1) - and then not Is_Class_Wide_Type (E1) and then Present (Parent (E1)) + and then not Is_Class_Wide_Type (E1) + and then not Is_Internal_Name (Chars (E1)) then while Present (E2) and then Chars (E2) /= Chars (E1) @@ -6514,6 +7452,7 @@ package body Sem_Ch12 is Ent := First_Entity (Formal); while Present (Ent) loop Set_Is_Hidden (Ent, False); + Set_Is_Visible_Formal (Ent); Set_Is_Potentially_Use_Visible (Ent, Is_Potentially_Use_Visible (Formal)); @@ -6544,8 +7483,8 @@ package body Sem_Ch12 is Actual_Pack := Entity (Actual); Set_Is_Instantiated (Actual_Pack); - -- The actual may be a renamed package, or an outer generic - -- formal package whose instantiation is converted into a renaming. + -- The actual may be a renamed package, or an outer generic formal + -- package whose instantiation is converted into a renaming. if Present (Renamed_Object (Actual_Pack)) then Actual_Pack := Renamed_Object (Actual_Pack); @@ -6603,69 +7542,125 @@ package body Sem_Ch12 is -- current instance, those entities are made private again. If the -- actual is currently in use, these entities are also use-visible. - -- The loop through the actual entities also steps through the - -- formal entities and enters associations from formals to - -- actuals into the renaming map. This is necessary to properly - -- handle checking of actual parameter associations for later - -- formals that depend on actuals declared in the formal package. + -- The loop through the actual entities also steps through the formal + -- entities and enters associations from formals to actuals into the + -- renaming map. This is necessary to properly handle checking of + -- actual parameter associations for later formals that depend on + -- actuals declared in the formal package. - if Box_Present (Formal) then - declare - Gen_Decl : constant Node_Id := - Unit_Declaration_Node (Gen_Parent); - Formals : constant List_Id := - Generic_Formal_Declarations (Gen_Decl); - Actual_Ent : Entity_Id; - Formal_Node : Node_Id; - Formal_Ent : Entity_Id; + -- In Ada 2005, partial parametrization requires that we make visible + -- the actuals corresponding to formals that were defaulted in the + -- formal package. There formals are identified because they remain + -- formal generics within the formal package, rather than being + -- renamings of the actuals supplied. - begin - if Present (Formals) then - Formal_Node := First_Non_Pragma (Formals); - else - Formal_Node := Empty; - end if; + declare + Gen_Decl : constant Node_Id := + Unit_Declaration_Node (Gen_Parent); + Formals : constant List_Id := + Generic_Formal_Declarations (Gen_Decl); - Actual_Ent := First_Entity (Actual_Pack); + Actual_Ent : Entity_Id; + Actual_Of_Formal : Node_Id; + Formal_Node : Node_Id; + Formal_Ent : Entity_Id; - while Present (Actual_Ent) - and then Actual_Ent /= First_Private_Entity (Actual_Pack) - loop - Set_Is_Hidden (Actual_Ent, False); - Set_Is_Potentially_Use_Visible - (Actual_Ent, In_Use (Actual_Pack)); + begin + if Present (Formals) then + Formal_Node := First_Non_Pragma (Formals); + else + Formal_Node := Empty; + end if; - if Ekind (Actual_Ent) = E_Package then - Process_Nested_Formal (Actual_Ent); - end if; + Actual_Ent := First_Entity (Actual_Pack); + Actual_Of_Formal := + First (Visible_Declarations (Specification (Analyzed_Formal))); + while Present (Actual_Ent) + and then Actual_Ent /= First_Private_Entity (Actual_Pack) + loop + if Present (Formal_Node) then + Formal_Ent := Get_Formal_Entity (Formal_Node); - if Present (Formal_Node) then - Formal_Ent := Formal_Entity (Formal_Node, Actual_Ent); + if Present (Formal_Ent) then + Find_Matching_Actual (Formal_Node, Actual_Ent); + Match_Formal_Entity + (Formal_Node, Formal_Ent, Actual_Ent); - if Present (Formal_Ent) then - Find_Matching_Actual (Formal_Node, Actual_Ent); - Set_Instance_Of (Formal_Ent, Actual_Ent); - end if; + -- We iterate at the same time over the actuals of the + -- local package created for the formal, to determine + -- which one of the formals of the original generic were + -- defaulted in the formal. The corresponding actual + -- entities are visible in the enclosing instance. - Next_Non_Pragma (Formal_Node); + if Box_Present (Formal) + or else + (Present (Actual_Of_Formal) + and then + Is_Generic_Formal + (Get_Formal_Entity (Actual_Of_Formal))) + then + Set_Is_Hidden (Actual_Ent, False); + Set_Is_Visible_Formal (Actual_Ent); + Set_Is_Potentially_Use_Visible + (Actual_Ent, In_Use (Actual_Pack)); - else - -- No further formals to match, but the generic - -- part may contain inherited operation that are - -- not hidden in the enclosing instance. + if Ekind (Actual_Ent) = E_Package then + Process_Nested_Formal (Actual_Ent); + end if; - Next_Entity (Actual_Ent); + else + Set_Is_Hidden (Actual_Ent); + Set_Is_Potentially_Use_Visible (Actual_Ent, False); + end if; end if; - end loop; - end; + Next_Non_Pragma (Formal_Node); + Next (Actual_Of_Formal); + + else + -- No further formals to match, but the generic part may + -- contain inherited operation that are not hidden in the + -- enclosing instance. + + Next_Entity (Actual_Ent); + end if; + end loop; + + -- Inherited subprograms generated by formal derived types are + -- also visible if the types are. + + Actual_Ent := First_Entity (Actual_Pack); + while Present (Actual_Ent) + and then Actual_Ent /= First_Private_Entity (Actual_Pack) + loop + if Is_Overloadable (Actual_Ent) + and then + Nkind (Parent (Actual_Ent)) = N_Subtype_Declaration + and then + not Is_Hidden (Defining_Identifier (Parent (Actual_Ent))) + then + Set_Is_Hidden (Actual_Ent, False); + Set_Is_Potentially_Use_Visible + (Actual_Ent, In_Use (Actual_Pack)); + end if; + + Next_Entity (Actual_Ent); + end loop; + end; - -- If the formal is not declared with a box, reanalyze it as - -- an instantiation, to verify the matching rules of 12.7. The - -- actual checks are performed after the generic associations - -- been analyzed. + -- If the formal is not declared with a box, reanalyze it as an + -- abbreviated instantiation, to verify the matching rules of 12.7. + -- The actual checks are performed after the generic associations + -- have been analyzed, to guarantee the same visibility for this + -- instantiation and for the actuals. - else + -- In Ada 2005, the generic associations for the formal can include + -- defaulted parameters. These are ignored during check. This + -- internal instantiation is removed from the tree after conformance + -- checking, because it contains formal declarations for those + -- defaulted parameters, and those should not reach the back-end. + + if not Box_Present (Formal) then declare I_Pack : constant Entity_Id := Make_Defining_Identifier (Sloc (Actual), @@ -6677,7 +7672,9 @@ package body Sem_Ch12 is Append_To (Decls, Make_Package_Instantiation (Sloc (Actual), Defining_Unit_Name => I_Pack, - Name => New_Occurrence_Of (Gen_Parent, Sloc (Actual)), + Name => + New_Occurrence_Of + (Get_Instance_Of (Gen_Parent), Sloc (Actual)), Generic_Associations => Generic_Associations (Formal))); end; @@ -6696,7 +7693,7 @@ package body Sem_Ch12 is Actual : Node_Id; Analyzed_Formal : Node_Id) return Node_Id is - Loc : Source_Ptr := Sloc (Instantiation_Node); + Loc : Source_Ptr; Formal_Sub : constant Entity_Id := Defining_Unit_Name (Specification (Formal)); Analyzed_S : constant Entity_Id := @@ -6706,25 +7703,26 @@ package body Sem_Ch12 is New_Spec : Node_Id; function From_Parent_Scope (Subp : Entity_Id) return Boolean; - -- If the generic is a child unit, the parent has been installed - -- on the scope stack, but a default subprogram cannot resolve to - -- something on the parent because that parent is not really part - -- of the visible context (it is there to resolve explicit local - -- entities). If the default has resolved in this way, we remove - -- the entity from immediate visibility and analyze the node again - -- to emit an error message or find another visible candidate. + -- If the generic is a child unit, the parent has been installed on the + -- scope stack, but a default subprogram cannot resolve to something on + -- the parent because that parent is not really part of the visible + -- context (it is there to resolve explicit local entities). If the + -- default has resolved in this way, we remove the entity from + -- immediate visibility and analyze the node again to emit an error + -- message or find another visible candidate. procedure Valid_Actual_Subprogram (Act : Node_Id); - -- Perform legality check and raise exception on failure. + -- Perform legality check and raise exception on failure ----------------------- -- From_Parent_Scope -- ----------------------- function From_Parent_Scope (Subp : Entity_Id) return Boolean is - Gen_Scope : Node_Id := Scope (Analyzed_S); + Gen_Scope : Node_Id; begin + Gen_Scope := Scope (Analyzed_S); while Present (Gen_Scope) and then Is_Child_Unit (Gen_Scope) loop @@ -6743,15 +7741,19 @@ package body Sem_Ch12 is ----------------------------- procedure Valid_Actual_Subprogram (Act : Node_Id) is - Act_E : Entity_Id := Empty; + Act_E : Entity_Id; begin if Is_Entity_Name (Act) then Act_E := Entity (Act); + elsif Nkind (Act) = N_Selected_Component and then Is_Entity_Name (Selector_Name (Act)) then Act_E := Entity (Selector_Name (Act)); + + else + Act_E := Empty; end if; if (Present (Act_E) and then Is_Overloadable (Act_E)) @@ -6775,18 +7777,40 @@ package body Sem_Ch12 is begin New_Spec := New_Copy_Tree (Specification (Formal)); - -- Create new entity for the actual (New_Copy_Tree does not). + -- The tree copy has created the proper instantiation sloc for the + -- new specification. Use this location for all other constructed + -- declarations. + + Loc := Sloc (Defining_Unit_Name (New_Spec)); + + -- Create new entity for the actual (New_Copy_Tree does not) Set_Defining_Unit_Name (New_Spec, Make_Defining_Identifier (Loc, Chars (Formal_Sub))); + -- Create new entities for the each of the formals in the + -- specification of the renaming declaration built for the actual. + + if Present (Parameter_Specifications (New_Spec)) then + declare + F : Node_Id; + begin + F := First (Parameter_Specifications (New_Spec)); + while Present (F) loop + Set_Defining_Identifier (F, + Make_Defining_Identifier (Loc, + Chars => Chars (Defining_Identifier (F)))); + Next (F); + end loop; + end; + end if; + -- Find entity of actual. If the actual is an attribute reference, it -- cannot be resolved here (its formal is missing) but is handled -- instead in Attribute_Renaming. If the actual is overloaded, it is -- fully resolved subsequently, when the renaming declaration for the -- formal is analyzed. If it is an explicit dereference, resolve the - -- prefix but not the actual itself, to prevent interpretation as a - -- call. + -- prefix but not the actual itself, to prevent interpretation as call. if Present (Actual) then Loc := Sloc (Actual); @@ -6820,8 +7844,8 @@ package body Sem_Ch12 is elsif Box_Present (Formal) then - -- Actual is resolved at the point of instantiation. Create - -- an identifier or operator with the same name as the formal. + -- Actual is resolved at the point of instantiation. Create an + -- identifier or operator with the same name as the formal. if Nkind (Formal_Sub) = N_Defining_Operator_Symbol then Nam := Make_Operator_Symbol (Loc, @@ -6831,6 +7855,22 @@ package body Sem_Ch12 is Nam := Make_Identifier (Loc, Chars (Formal_Sub)); end if; + elsif Nkind (Specification (Formal)) = N_Procedure_Specification + and then Null_Present (Specification (Formal)) + then + -- Generate null body for procedure, for use in the instance + + Decl_Node := + Make_Subprogram_Body (Loc, + Specification => New_Spec, + Declarations => New_List, + Handled_Statement_Sequence => + Make_Handled_Sequence_Of_Statements (Loc, + Statements => New_List (Make_Null_Statement (Loc)))); + + Set_Is_Intrinsic_Subprogram (Defining_Unit_Name (New_Spec)); + return Decl_Node; + else Error_Msg_Sloc := Sloc (Scope (Analyzed_S)); Error_Msg_NE @@ -6846,8 +7886,8 @@ package body Sem_Ch12 is Specification => New_Spec, Name => Nam); - -- If we do not have an actual and the formal specified <> then - -- set to get proper default. + -- If we do not have an actual and the formal specified <> then set to + -- get proper default. if No (Actual) and then Box_Present (Formal) then Set_From_Default (Decl_Node); @@ -6897,17 +7937,19 @@ package body Sem_Ch12 is end if; end if; - -- The generic instantiation freezes the actual. This can only be - -- done once the actual is resolved, in the analysis of the renaming - -- declaration. To indicate that must be done, we set the corresponding - -- spec of the node to point to the formal subprogram entity. + -- The generic instantiation freezes the actual. This can only be done + -- once the actual is resolved, in the analysis of the renaming + -- declaration. To make the formal subprogram entity available, we set + -- Corresponding_Formal_Spec to point to the formal subprogram entity. + -- This is also needed in Analyze_Subprogram_Renaming for the processing + -- of formal abstract subprograms. - Set_Corresponding_Spec (Decl_Node, Analyzed_S); + Set_Corresponding_Formal_Spec (Decl_Node, Analyzed_S); - -- We cannot analyze the renaming declaration, and thus find the - -- actual, until the all the actuals are assembled in the instance. - -- For subsequent checks of other actuals, indicate the node that - -- will hold the instance of this formal. + -- We cannot analyze the renaming declaration, and thus find the actual, + -- until all the actuals are assembled in the instance. For subsequent + -- checks of other actuals, indicate the node that will hold the + -- instance of this formal. Set_Instance_Of (Analyzed_S, Nam); @@ -6953,19 +7995,30 @@ package body Sem_Ch12 is Actual : Node_Id; Analyzed_Formal : Node_Id) return List_Id is - Formal_Id : constant Entity_Id := Defining_Identifier (Formal); - Type_Id : constant Node_Id := Subtype_Mark (Formal); - Loc : constant Source_Ptr := Sloc (Actual); - Act_Assoc : constant Node_Id := Parent (Actual); - Orig_Ftyp : constant Entity_Id := - Etype (Defining_Identifier (Analyzed_Formal)); - List : constant List_Id := New_List; - Ftyp : Entity_Id; - Decl_Node : Node_Id; - Subt_Decl : Node_Id := Empty; + Acc_Def : Node_Id := Empty; + Act_Assoc : constant Node_Id := Parent (Actual); + Actual_Decl : Node_Id := Empty; + Formal_Id : constant Entity_Id := Defining_Identifier (Formal); + Decl_Node : Node_Id; + Def : Node_Id; + Ftyp : Entity_Id; + List : constant List_Id := New_List; + Loc : constant Source_Ptr := Sloc (Actual); + Orig_Ftyp : constant Entity_Id := + Etype (Defining_Identifier (Analyzed_Formal)); + Subt_Decl : Node_Id := Empty; + Subt_Mark : Node_Id := Empty; begin - -- Sloc for error message on missing actual. + if Present (Subtype_Mark (Formal)) then + Subt_Mark := Subtype_Mark (Formal); + else + Check_Access_Definition (Formal); + Acc_Def := Access_Definition (Formal); + end if; + + -- Sloc for error message on missing actual + Error_Msg_Sloc := Sloc (Scope (Defining_Identifier (Analyzed_Formal))); if Get_Instance_Of (Formal_Id) /= Formal_Id then @@ -6978,12 +8031,12 @@ package body Sem_Ch12 is if Out_Present (Formal) then - -- An IN OUT generic actual must be a name. The instantiation is - -- a renaming declaration. The actual is the name being renamed. - -- We use the actual directly, rather than a copy, because it is not + -- An IN OUT generic actual must be a name. The instantiation is a + -- renaming declaration. The actual is the name being renamed. We + -- use the actual directly, rather than a copy, because it is not -- used further in the list of actuals, and because a copy or a use - -- of relocate_node is incorrect if the instance is nested within - -- a generic. In order to simplify ASIS searches, the Generic_Parent + -- of relocate_node is incorrect if the instance is nested within a + -- generic. In order to simplify ASIS searches, the Generic_Parent -- field links the declaration to the generic association. if No (Actual) then @@ -6997,11 +8050,20 @@ package body Sem_Ch12 is Abandon_Instantiation (Instantiation_Node); end if; - Decl_Node := - Make_Object_Renaming_Declaration (Loc, - Defining_Identifier => New_Copy (Formal_Id), - Subtype_Mark => New_Copy_Tree (Type_Id), - Name => Actual); + if Present (Subt_Mark) then + Decl_Node := + Make_Object_Renaming_Declaration (Loc, + Defining_Identifier => New_Copy (Formal_Id), + Subtype_Mark => New_Copy_Tree (Subt_Mark), + Name => Actual); + + else pragma Assert (Present (Acc_Def)); + Decl_Node := + Make_Object_Renaming_Declaration (Loc, + Defining_Identifier => New_Copy (Formal_Id), + Access_Definition => New_Copy_Tree (Acc_Def), + Name => Actual); + end if; Set_Corresponding_Generic_Association (Decl_Node, Act_Assoc); @@ -7011,10 +8073,16 @@ package body Sem_Ch12 is Append (Decl_Node, List); Analyze (Actual); - -- This check is performed here because Analyze_Object_Renaming - -- will not check it when Comes_From_Source is False. Note - -- though that the check for the actual being the name of an - -- object will be performed in Analyze_Object_Renaming. + -- Return if the analysis of the actual reported some error + + if Etype (Actual) = Any_Type then + return List; + end if; + + -- This check is performed here because Analyze_Object_Renaming will + -- not check it when Comes_From_Source is False. Note though that the + -- check for the actual being the name of an object will be performed + -- in Analyze_Object_Renaming. if Is_Object_Reference (Actual) and then Is_Dependent_Component_Of_Mutable_Object (Actual) @@ -7024,8 +8092,8 @@ package body Sem_Ch12 is Actual); end if; - -- The actual has to be resolved in order to check that it is - -- a variable (due to cases such as F(1), where F returns + -- The actual has to be resolved in order to check that it is a + -- variable (due to cases such as F(1), where F returns -- access to an array, and for overloaded prefixes). Ftyp := @@ -7036,11 +8104,11 @@ package body Sem_Ch12 is and then (Base_Type (Full_View (Ftyp)) = Base_Type (Etype (Actual)) or else Base_Type (Etype (Actual)) = Ftyp) then - -- If the actual has the type of the full view of the formal, - -- or else a non-private subtype of the formal, then - -- the visibility of the formal type has changed. Add to the - -- actuals a subtype declaration that will force the exchange - -- of views in the body of the instance as well. + -- If the actual has the type of the full view of the formal, or + -- else a non-private subtype of the formal, then the visibility + -- of the formal type has changed. Add to the actuals a subtype + -- declaration that will force the exchange of views in the body + -- of the instance as well. Subt_Decl := Make_Subtype_Declaration (Loc, @@ -7050,7 +8118,7 @@ package body Sem_Ch12 is Prepend (Subt_Decl, List); - Append_Elmt (Full_View (Ftyp), Exchanged_Views); + Prepend_Elmt (Full_View (Ftyp), Exchanged_Views); Exchange_Declarations (Ftyp); end if; @@ -7061,9 +8129,22 @@ package body Sem_Ch12 is ("actual for& must be a variable", Actual, Formal_Id); elsif Base_Type (Ftyp) /= Base_Type (Etype (Actual)) then - Error_Msg_NE ( - "type of actual does not match type of&", Actual, Formal_Id); + -- Ada 2005 (AI-423): For a generic formal object of mode in out, + -- the type of the actual shall resolve to a specific anonymous + -- access type. + + if Ada_Version < Ada_05 + or else + Ekind (Base_Type (Ftyp)) /= + E_Anonymous_Access_Type + or else + Ekind (Base_Type (Etype (Actual))) /= + E_Anonymous_Access_Type + then + Error_Msg_NE ("type of actual does not match type of&", + Actual, Formal_Id); + end if; end if; Note_Possible_Modification (Actual); @@ -7089,23 +8170,27 @@ package body Sem_Ch12 is -- OUT not present else - -- The instantiation of a generic formal in-parameter - -- is a constant declaration. The actual is the expression for - -- that declaration. + -- The instantiation of a generic formal in-parameter is constant + -- declaration. The actual is the expression for that declaration. if Present (Actual) then + if Present (Subt_Mark) then + Def := Subt_Mark; + else pragma Assert (Present (Acc_Def)); + Def := Acc_Def; + end if; - Decl_Node := Make_Object_Declaration (Loc, - Defining_Identifier => New_Copy (Formal_Id), - Constant_Present => True, - Object_Definition => New_Copy_Tree (Type_Id), - Expression => Actual); + Decl_Node := + Make_Object_Declaration (Loc, + Defining_Identifier => New_Copy (Formal_Id), + Constant_Present => True, + Object_Definition => New_Copy_Tree (Def), + Expression => Actual); Set_Corresponding_Generic_Association (Decl_Node, Act_Assoc); - -- A generic formal object of a tagged type is defined - -- to be aliased so the new constant must also be treated - -- as aliased. + -- A generic formal object of a tagged type is defined to be + -- aliased so the new constant must also be treated as aliased. if Is_Tagged_Type (Etype (Defining_Identifier (Analyzed_Formal))) @@ -7120,6 +8205,12 @@ package body Sem_Ch12 is if Nkind (Actual) /= N_Allocator then Analyze (Actual); + + -- Return if the analysis of the actual reported some error + + if Etype (Actual) = Any_Type then + return List; + end if; end if; declare @@ -7130,26 +8221,41 @@ package body Sem_Ch12 is begin Freeze_Before (Instantiation_Node, Typ); - -- If the actual is an aggregate, perform name resolution - -- on its components (the analysis of an aggregate does not - -- do it) to capture local names that may be hidden if the - -- generic is a child unit. + -- If the actual is an aggregate, perform name resolution on + -- its components (the analysis of an aggregate does not do it) + -- to capture local names that may be hidden if the generic is + -- a child unit. if Nkind (Actual) = N_Aggregate then Pre_Analyze_And_Resolve (Actual, Typ); end if; + + if Is_Limited_Type (Typ) + and then not OK_For_Limited_Init (Actual) + then + Error_Msg_N + ("initialization not allowed for limited types", Actual); + Explain_Limited_Type (Typ, Actual); + end if; end; - elsif Present (Expression (Formal)) then + elsif Present (Default_Expression (Formal)) then + + -- Use default to construct declaration - -- Use default to construct declaration. + if Present (Subt_Mark) then + Def := Subt_Mark; + else pragma Assert (Present (Acc_Def)); + Def := Acc_Def; + end if; Decl_Node := Make_Object_Declaration (Sloc (Formal), Defining_Identifier => New_Copy (Formal_Id), Constant_Present => True, - Object_Definition => New_Copy (Type_Id), - Expression => New_Copy_Tree (Expression (Formal))); + Object_Definition => New_Copy (Def), + Expression => New_Copy_Tree (Default_Expression + (Formal))); Append (Decl_Node, List); Set_Analyzed (Expression (Decl_Node), False); @@ -7165,18 +8271,24 @@ package body Sem_Ch12 is if Is_Scalar_Type (Etype (Defining_Identifier (Analyzed_Formal))) then - -- Create dummy constant declaration so that instance can - -- be analyzed, to minimize cascaded visibility errors. + -- Create dummy constant declaration so that instance can be + -- analyzed, to minimize cascaded visibility errors. + + if Present (Subt_Mark) then + Def := Subt_Mark; + else pragma Assert (Present (Acc_Def)); + Def := Acc_Def; + end if; Decl_Node := Make_Object_Declaration (Loc, Defining_Identifier => New_Copy (Formal_Id), Constant_Present => True, - Object_Definition => New_Copy (Type_Id), + Object_Definition => New_Copy (Def), Expression => Make_Attribute_Reference (Sloc (Formal_Id), Attribute_Name => Name_First, - Prefix => New_Copy (Type_Id))); + Prefix => New_Copy (Def))); Append (Decl_Node, List); @@ -7184,7 +8296,35 @@ package body Sem_Ch12 is Abandon_Instantiation (Instantiation_Node); end if; end if; + end if; + if Nkind (Actual) in N_Has_Entity then + Actual_Decl := Parent (Entity (Actual)); + end if; + + -- Ada 2005 (AI-423): For a formal object declaration with a null + -- exclusion or an access definition that has a null exclusion: If the + -- actual matching the formal object declaration denotes a generic + -- formal object of another generic unit G, and the instantiation + -- containing the actual occurs within the body of G or within the body + -- of a generic unit declared within the declarative region of G, then + -- the declaration of the formal object of G must have a null exclusion. + -- Otherwise, the subtype of the actual matching the formal object + -- declaration shall exclude null. + + if Ada_Version >= Ada_05 + and then Present (Actual_Decl) + and then + (Nkind (Actual_Decl) = N_Formal_Object_Declaration + or else Nkind (Actual_Decl) = N_Object_Declaration) + and then Nkind (Analyzed_Formal) = N_Formal_Object_Declaration + and then Has_Null_Exclusion (Actual_Decl) + and then not Has_Null_Exclusion (Analyzed_Formal) + then + Error_Msg_Sloc := Sloc (Actual_Decl); + Error_Msg_N + ("`NOT NULL` required in formal, to match actual #", + Analyzed_Formal); end if; return List; @@ -7220,8 +8360,8 @@ package body Sem_Ch12 is begin Gen_Body_Id := Corresponding_Body (Gen_Decl); - -- The instance body may already have been processed, as the parent - -- of another instance that is inlined. (Load_Parent_Of_Generic). + -- The instance body may already have been processed, as the parent of + -- another instance that is inlined (Load_Parent_Of_Generic). if Present (Corresponding_Body (Instance_Spec (Inst_Node))) then return; @@ -7234,8 +8374,7 @@ package body Sem_Ch12 is Gen_Body_Id := Corresponding_Body (Gen_Decl); end if; - -- Establish global variable for sloc adjustment and for error - -- recovery. + -- Establish global variable for sloc adjustment and for error recovery Instantiation_Node := Inst_Node; @@ -7257,8 +8396,7 @@ package body Sem_Ch12 is Act_Body_Id := New_Copy (Act_Decl_Id); - -- Some attributes of the spec entity are not inherited by the - -- body entity. + -- Some attributes of spec entity are not inherited by body entity Set_Handler_Records (Act_Body_Id, No_List); @@ -7293,19 +8431,19 @@ package body Sem_Ch12 is Parent_Installed := True; end if; - -- If the instantiation is a library unit, and this is the main - -- unit, then build the resulting compilation unit nodes for the - -- instance. If this is a compilation unit but it is not the main - -- unit, then it is the body of a unit in the context, that is being - -- compiled because it is encloses some inlined unit or another - -- generic unit being instantiated. In that case, this body is not - -- part of the current compilation, and is not attached to the tree, - -- but its parent must be set for analysis. + -- If the instantiation is a library unit, and this is the main unit, + -- then build the resulting compilation unit nodes for the instance. + -- If this is a compilation unit but it is not the main unit, then it + -- is the body of a unit in the context, that is being compiled + -- because it is encloses some inlined unit or another generic unit + -- being instantiated. In that case, this body is not part of the + -- current compilation, and is not attached to the tree, but its + -- parent must be set for analysis. if Nkind (Parent (Inst_Node)) = N_Compilation_Unit then - -- Replace instance node with body of instance, and create - -- new node for corresponding instance declaration. + -- Replace instance node with body of instance, and create new + -- node for corresponding instance declaration. Build_Instance_Compilation_Unit_Nodes (Inst_Node, Act_Body, Act_Decl); @@ -7313,10 +8451,10 @@ package body Sem_Ch12 is if Parent (Inst_Node) = Cunit (Main_Unit) then - -- If the instance is a child unit itself, then set the - -- scope of the expanded body to be the parent of the - -- instantiation (ensuring that the fully qualified name - -- will be generated for the elaboration subprogram). + -- If the instance is a child unit itself, then set the scope + -- of the expanded body to be the parent of the instantiation + -- (ensuring that the fully qualified name will be generated + -- for the elaboration subprogram). if Nkind (Defining_Unit_Name (Act_Spec)) = N_Defining_Program_Unit_Name @@ -7335,14 +8473,14 @@ package body Sem_Ch12 is Install_Body (Act_Body, Inst_Node, Gen_Body, Gen_Decl); - -- Now analyze the body. We turn off all checks if this is - -- an internal unit, since there is no reason to have checks - -- on for any predefined run-time library code. All such - -- code is designed to be compiled with checks off. + -- Now analyze the body. We turn off all checks if this is an + -- internal unit, since there is no reason to have checks on for + -- any predefined run-time library code. All such code is designed + -- to be compiled with checks off. - -- Note that we do NOT apply this criterion to children of - -- GNAT (or on VMS, children of DEC). The latter units must - -- suppress checks explicitly if this is needed. + -- Note that we do NOT apply this criterion to children of GNAT + -- (or on VMS, children of DEC). The latter units must suppress + -- checks explicitly if this is needed. if Is_Predefined_File_Name (Unit_File_Name (Get_Source_Unit (Gen_Decl))) @@ -7357,8 +8495,8 @@ package body Sem_Ch12 is Inherit_Context (Gen_Body, Inst_Node); end if; - -- Remove the parent instances if they have been placed on the - -- scope stack to compile the body. + -- Remove the parent instances if they have been placed on the scope + -- stack to compile the body. if Parent_Installed then Remove_Parent (In_Body => True); @@ -7376,17 +8514,17 @@ package body Sem_Ch12 is Restore_Env; Style_Check := Save_Style_Check; - -- If we have no body, and the unit requires a body, then complain. - -- This complaint is suppressed if we have detected other errors - -- (since a common reason for missing the body is that it had errors). + -- If we have no body, and the unit requires a body, then complain. This + -- complaint is suppressed if we have detected other errors (since a + -- common reason for missing the body is that it had errors). elsif Unit_Requires_Body (Gen_Unit) then if Serious_Errors_Detected = 0 then Error_Msg_NE ("cannot find body of generic package &", Inst_Node, Gen_Unit); - -- Don't attempt to perform any cleanup actions if some other - -- error was aready detected, since this can cause blowups. + -- Don't attempt to perform any cleanup actions if some other error + -- was aready detected, since this can cause blowups. else return; @@ -7395,25 +8533,25 @@ package body Sem_Ch12 is -- Case of package that does not need a body else - -- If the instantiation of the declaration is a library unit, - -- rewrite the original package instantiation as a package - -- declaration in the compilation unit node. + -- If the instantiation of the declaration is a library unit, rewrite + -- the original package instantiation as a package declaration in the + -- compilation unit node. if Nkind (Parent (Inst_Node)) = N_Compilation_Unit then Set_Parent_Spec (Act_Decl, Parent_Spec (Inst_Node)); Rewrite (Inst_Node, Act_Decl); - -- Generate elaboration entity, in case spec has elaboration - -- code. This cannot be done when the instance is analyzed, - -- because it is not known yet whether the body exists. + -- Generate elaboration entity, in case spec has elaboration code. + -- This cannot be done when the instance is analyzed, because it + -- is not known yet whether the body exists. Set_Elaboration_Entity_Required (Act_Decl_Id, False); Build_Elaboration_Entity (Parent (Inst_Node), Act_Decl_Id); -- If the instantiation is not a library unit, then append the - -- declaration to the list of implicitly generated entities. - -- unless it is already a list member which means that it was - -- already processed + -- declaration to the list of implicitly generated entities. unless + -- it is already a list member which means that it was already + -- processed elsif not Is_List_Member (Act_Decl) then Mark_Rewrite_Insertion (Act_Decl); @@ -7445,7 +8583,6 @@ package body Sem_Ch12 is Gen_Body : Node_Id; Gen_Body_Id : Node_Id; Act_Body : Node_Id; - Act_Body_Id : Entity_Id; Pack_Body : Node_Id; Prev_Formal : Entity_Id; Ret_Expr : Node_Id; @@ -7498,13 +8635,25 @@ package body Sem_Ch12 is Act_Body := Copy_Generic_Node (Original_Node (Gen_Body), Empty, Instantiating => True); - Act_Body_Id := Defining_Entity (Act_Body); - Set_Chars (Act_Body_Id, Chars (Anon_Id)); - Set_Sloc (Act_Body_Id, Sloc (Defining_Entity (Inst_Node))); + + -- Create proper defining name for the body, to correspond to + -- the one in the spec. + + Set_Defining_Unit_Name (Specification (Act_Body), + Make_Defining_Identifier + (Sloc (Defining_Entity (Inst_Node)), Chars (Anon_Id))); Set_Corresponding_Spec (Act_Body, Anon_Id); Set_Has_Completion (Anon_Id); Check_Generic_Actuals (Pack_Id, False); + -- Generate a reference to link the visible subprogram instance to + -- the the generic body, which for navigation purposes is the only + -- available source for the instance. + + Generate_Reference + (Related_Instance (Pack_Id), + Gen_Body_Id, 'b', Set_Ref => False, Force => True); + -- If it is a child unit, make the parent instance (which is an -- instance of the parent of the generic) visible. The parent -- instance is the prefix of the name of the generic unit. @@ -7533,9 +8682,9 @@ package body Sem_Ch12 is Instantiating => True), Name => New_Occurrence_Of (Anon_Id, Loc)); - -- If there is a formal subprogram with the same name as the - -- unit itself, do not add this renaming declaration. This is - -- a temporary fix for one ACVC test. ??? + -- If there is a formal subprogram with the same name as the unit + -- itself, do not add this renaming declaration. This is a temporary + -- fix for one ACVC test. ??? Prev_Formal := First_Entity (Pack_Id); while Present (Prev_Formal) loop @@ -7554,9 +8703,9 @@ package body Sem_Ch12 is Decls := New_List (Unit_Renaming, Act_Body); end if; - -- The subprogram body is placed in the body of a dummy package - -- body, whose spec contains the subprogram declaration as well - -- as the renaming declarations for the generic parameters. + -- The subprogram body is placed in the body of a dummy package body, + -- whose spec contains the subprogram declaration as well as the + -- renaming declarations for the generic parameters. Pack_Body := Make_Package_Body (Loc, Defining_Unit_Name => New_Copy (Pack_Id), @@ -7604,11 +8753,13 @@ package body Sem_Ch12 is Restore_Env; Style_Check := Save_Style_Check; - -- Body not found. Error was emitted already. If there were no - -- previous errors, this may be an instance whose scope is a premature - -- instance. In that case we must insure that the (legal) program does - -- raise program error if executed. We generate a subprogram body for - -- this purpose. See DEC ac30vso. + -- Body not found. Error was emitted already. If there were no previous + -- errors, this may be an instance whose scope is a premature instance. + -- In that case we must insure that the (legal) program does raise + -- program error if executed. We generate a subprogram body for this + -- purpose. See DEC ac30vso. + + -- Should not reference proprietary DEC tests in comments ??? elsif Serious_Errors_Detected = 0 and then Nkind (Parent (Inst_Node)) /= N_Compilation_Unit @@ -7618,7 +8769,8 @@ package body Sem_Ch12 is Make_Subprogram_Body (Loc, Specification => Make_Procedure_Specification (Loc, - Defining_Unit_Name => New_Copy (Anon_Id), + Defining_Unit_Name => + Make_Defining_Identifier (Loc, Chars (Anon_Id)), Parameter_Specifications => New_Copy_List (Parameter_Specifications (Parent (Anon_Id)))), @@ -7644,11 +8796,12 @@ package body Sem_Ch12 is Make_Subprogram_Body (Loc, Specification => Make_Function_Specification (Loc, - Defining_Unit_Name => New_Copy (Anon_Id), + Defining_Unit_Name => + Make_Defining_Identifier (Loc, Chars (Anon_Id)), Parameter_Specifications => New_Copy_List (Parameter_Specifications (Parent (Anon_Id))), - Subtype_Mark => + Result_Definition => New_Occurrence_Of (Etype (Anon_Id), Loc)), Declarations => Empty_List, @@ -7678,20 +8831,25 @@ package body Sem_Ch12 is (Formal : Node_Id; Actual : Node_Id; Analyzed_Formal : Node_Id; - Actual_Decls : List_Id) return Node_Id + Actual_Decls : List_Id) return List_Id is - Loc : constant Source_Ptr := Sloc (Actual); - Gen_T : constant Entity_Id := Defining_Identifier (Formal); - A_Gen_T : constant Entity_Id := Defining_Identifier (Analyzed_Formal); - Ancestor : Entity_Id := Empty; - Def : constant Node_Id := Formal_Type_Definition (Formal); - Act_T : Entity_Id; - Decl_Node : Node_Id; + Gen_T : constant Entity_Id := Defining_Identifier (Formal); + A_Gen_T : constant Entity_Id := + Defining_Identifier (Analyzed_Formal); + Ancestor : Entity_Id := Empty; + Def : constant Node_Id := Formal_Type_Definition (Formal); + Act_T : Entity_Id; + Decl_Node : Node_Id; + Decl_Nodes : List_Id; + Loc : Source_Ptr; + Subt : Entity_Id; procedure Validate_Array_Type_Instance; procedure Validate_Access_Subprogram_Instance; procedure Validate_Access_Type_Instance; procedure Validate_Derived_Type_Instance; + procedure Validate_Derived_Interface_Type_Instance; + procedure Validate_Interface_Type_Instance; procedure Validate_Private_Type_Instance; -- These procedures perform validation tests for the named case @@ -7708,16 +8866,22 @@ package body Sem_Ch12 is begin return (Base_Type (T) = Base_Type (Act_T) --- why is the and then commented out here??? --- and then Is_Constrained (T) = Is_Constrained (Act_T) and then Subtypes_Statically_Match (T, Act_T)) or else (Is_Class_Wide_Type (Gen_T) and then Is_Class_Wide_Type (Act_T) and then - Subtypes_Match ( - Get_Instance_Of (Root_Type (Gen_T)), - Root_Type (Act_T))); + Subtypes_Match + (Get_Instance_Of (Root_Type (Gen_T)), + Root_Type (Act_T))) + + or else + ((Ekind (Gen_T) = E_Anonymous_Access_Subprogram_Type + or else Ekind (Gen_T) = E_Anonymous_Access_Type) + and then Ekind (Act_T) = Ekind (Gen_T) + and then + Subtypes_Statically_Match + (Designated_Type (Gen_T), Designated_Type (Act_T))); end Subtypes_Match; ----------------------------------------- @@ -7813,6 +8977,14 @@ package body Sem_Ch12 is Actual, Gen_T); Abandon_Instantiation (Actual); end if; + + -- Ada 2005: null-exclusion indicators of the two types must agree + + if Can_Never_Be_Null (A_Gen_T) /= Can_Never_Be_Null (Act_T) then + Error_Msg_NE + ("non null exclusion of actual and formal & do not match", + Actual, Gen_T); + end if; end Validate_Access_Type_Instance; ---------------------------------- @@ -7928,6 +9100,46 @@ package body Sem_Ch12 is end Validate_Array_Type_Instance; + ----------------------------------------------- + -- Validate_Derived_Interface_Type_Instance -- + ----------------------------------------------- + + procedure Validate_Derived_Interface_Type_Instance is + Par : constant Entity_Id := Entity (Subtype_Indication (Def)); + Elmt : Elmt_Id; + + begin + -- First apply interface instance checks + + Validate_Interface_Type_Instance; + + -- Verify that immediate parent interface is an ancestor of + -- the actual. + + if Present (Par) + and then not Interface_Present_In_Ancestor (Act_T, Par) + then + Error_Msg_NE + ("interface actual must include progenitor&", Actual, Par); + end if; + + -- Now verify that the actual includes all other ancestors of + -- the formal. + + Elmt := First_Elmt (Abstract_Interfaces (A_Gen_T)); + while Present (Elmt) loop + if not Interface_Present_In_Ancestor + (Act_T, Get_Instance_Of (Node (Elmt))) + then + Error_Msg_NE + ("interface actual must include progenitor&", + Actual, Node (Elmt)); + end if; + + Next_Elmt (Elmt); + end loop; + end Validate_Derived_Interface_Type_Instance; + ------------------------------------ -- Validate_Derived_Type_Instance -- ------------------------------------ @@ -7937,18 +9149,18 @@ package body Sem_Ch12 is Ancestor_Discr : Entity_Id; begin - -- If the parent type in the generic declaration is itself - -- a previous formal type, then it is local to the generic - -- and absent from the analyzed generic definition. In that - -- case the ancestor is the instance of the formal (which must - -- have been instantiated previously), unless the ancestor is - -- itself a formal derived type. In this latter case (which is the - -- subject of Corrigendum 8652/0038 (AI-202) the ancestor of the - -- formals is the ancestor of its parent. Otherwise, the analyzed - -- generic carries the parent type. If the parent type is defined - -- in a previous formal package, then the scope of that formal - -- package is that of the generic type itself, and it has already - -- been mapped into the corresponding type in the actual package. + -- If the parent type in the generic declaration is itself a previous + -- formal type, then it is local to the generic and absent from the + -- analyzed generic definition. In that case the ancestor is the + -- instance of the formal (which must have been instantiated + -- previously), unless the ancestor is itself a formal derived type. + -- In this latter case (which is the subject of Corrigendum 8652/0038 + -- (AI-202) the ancestor of the formals is the ancestor of its + -- parent. Otherwise, the analyzed generic carries the parent type. + -- If the parent type is defined in a previous formal package, then + -- the scope of that formal package is that of the generic type + -- itself, and it has already been mapped into the corresponding type + -- in the actual package. -- Common case: parent type defined outside of the generic @@ -7965,15 +9177,15 @@ package body Sem_Ch12 is Ancestor := Get_Instance_Of (Base_Type (Etype (A_Gen_T))); - -- The type may be a local derivation, or a type extension of - -- a previous formal, or of a formal of a parent package. + -- The type may be a local derivation, or a type extension of a + -- previous formal, or of a formal of a parent package. elsif Is_Derived_Type (Get_Instance_Of (A_Gen_T)) or else Ekind (Get_Instance_Of (A_Gen_T)) = E_Record_Type_With_Private then - -- Check whether the parent is another derived formal type - -- in the same generic unit. + -- Check whether the parent is another derived formal type in the + -- same generic unit. if Etype (A_Gen_T) /= A_Gen_T and then Is_Generic_Type (Etype (A_Gen_T)) @@ -8012,13 +9224,51 @@ package body Sem_Ch12 is Ancestor := Get_Instance_Of (Etype (Base_Type (A_Gen_T))); end if; - if not Is_Ancestor (Base_Type (Ancestor), Act_T) then + -- Ada 2005 (AI-251) + + if Ada_Version >= Ada_05 + and then Is_Interface (Ancestor) + then + if not Interface_Present_In_Ancestor (Act_T, Ancestor) then + Error_Msg_NE + ("(Ada 2005) expected type implementing & in instantiation", + Actual, Ancestor); + end if; + + elsif not Is_Ancestor (Base_Type (Ancestor), Act_T) then Error_Msg_NE ("expect type derived from & in instantiation", Actual, First_Subtype (Ancestor)); Abandon_Instantiation (Actual); end if; + -- Ada 2005 (AI-443): Synchronized formal derived type ckecks. Note + -- that the formal type declaration has been rewritten as a private + -- extension. + + if Ada_Version >= Ada_05 + and then Nkind (Parent (A_Gen_T)) = N_Private_Extension_Declaration + and then Synchronized_Present (Parent (A_Gen_T)) + then + -- The actual must be a synchronized tagged type + + if not Is_Tagged_Type (Act_T) then + Error_Msg_N + ("actual of synchronized type must be tagged", Actual); + Abandon_Instantiation (Actual); + + elsif Nkind (Parent (Act_T)) = N_Full_Type_Declaration + and then Nkind (Type_Definition (Parent (Act_T))) = + N_Derived_Type_Definition + and then not Synchronized_Present (Type_Definition + (Parent (Act_T))) + then + Error_Msg_N + ("actual of synchronized type must be synchronized", Actual); + Abandon_Instantiation (Actual); + end if; + end if; + -- Perform atomic/volatile checks (RM C.6(12)) if Is_Atomic (Act_T) and then not Is_Atomic (Ancestor) then @@ -8035,10 +9285,10 @@ package body Sem_Ch12 is Actual); end if; - -- It should not be necessary to check for unknown discriminants - -- on Formal, but for some reason Has_Unknown_Discriminants is - -- false for A_Gen_T, so Is_Indefinite_Subtype incorrectly - -- returns False. This needs fixing. ??? + -- It should not be necessary to check for unknown discriminants on + -- Formal, but for some reason Has_Unknown_Discriminants is false for + -- A_Gen_T, so Is_Indefinite_Subtype incorrectly returns False. This + -- needs fixing. ??? if not Is_Indefinite_Subtype (A_Gen_T) and then not Unknown_Discriminants_Present (Formal) @@ -8057,19 +9307,23 @@ package body Sem_Ch12 is Abandon_Instantiation (Actual); end if; - -- Ancestor is unconstrained + -- Ancestor is unconstrained, Check if generic formal and actual + -- agree on constrainedness. The check only applies to array types + -- and discriminated types. elsif Is_Constrained (Act_T) then if Ekind (Ancestor) = E_Access_Type - or else Is_Composite_Type (Ancestor) + or else + (not Is_Constrained (A_Gen_T) + and then Is_Composite_Type (A_Gen_T)) then Error_Msg_N ("actual subtype must be unconstrained", Actual); Abandon_Instantiation (Actual); end if; - -- A class-wide type is only allowed if the formal has - -- unknown discriminants. + -- A class-wide type is only allowed if the formal has unknown + -- discriminants. elsif Is_Class_Wide_Type (Act_T) and then not Has_Unknown_Discriminants (Ancestor) @@ -8078,9 +9332,9 @@ package body Sem_Ch12 is ("actual for & cannot be a class-wide type", Actual, Gen_T); Abandon_Instantiation (Actual); - -- Otherwise, the formal and actual shall have the same - -- number of discriminants and each discriminant of the - -- actual must correspond to a discriminant of the formal. + -- Otherwise, the formal and actual shall have the same number + -- of discriminants and each discriminant of the actual must + -- correspond to a discriminant of the formal. elsif Has_Discriminants (Act_T) and then not Has_Unknown_Discriminants (Act_T) @@ -8092,7 +9346,7 @@ package body Sem_Ch12 is and then Present (Ancestor_Discr) loop if Base_Type (Act_T) /= Base_Type (Ancestor) and then - not Present (Corresponding_Discriminant (Actual_Discr)) + No (Corresponding_Discriminant (Actual_Discr)) then Error_Msg_NE ("discriminant & does not correspond " & @@ -8111,9 +9365,8 @@ package body Sem_Ch12 is Abandon_Instantiation (Actual); end if; - -- This case should be caught by the earlier check for - -- for constrainedness, but the check here is added for - -- completeness. + -- This case should be caught by the earlier check for for + -- constrainedness, but the check here is added for completeness. elsif Has_Discriminants (Act_T) and then not Has_Unknown_Discriminants (Act_T) @@ -8136,6 +9389,33 @@ package body Sem_Ch12 is end if; end Validate_Derived_Type_Instance; + -------------------------------------- + -- Validate_Interface_Type_Instance -- + -------------------------------------- + + procedure Validate_Interface_Type_Instance is + begin + if not Is_Interface (Act_T) then + Error_Msg_NE + ("actual for formal interface type must be an interface", + Actual, Gen_T); + + elsif Is_Limited_Type (Act_T) /= Is_Limited_Type (A_Gen_T) + or else + Is_Task_Interface (A_Gen_T) /= Is_Task_Interface (Act_T) + or else + Is_Protected_Interface (A_Gen_T) /= + Is_Protected_Interface (Act_T) + or else + Is_Synchronized_Interface (A_Gen_T) /= + Is_Synchronized_Interface (Act_T) + then + Error_Msg_NE + ("actual for interface& does not match ('R'M 12.5.5(4))", + Actual, Gen_T); + end if; + end Validate_Interface_Type_Instance; + ------------------------------------ -- Validate_Private_Type_Instance -- ------------------------------------ @@ -8150,11 +9430,18 @@ package body Sem_Ch12 is and then not Is_Limited_Type (A_Gen_T) then Error_Msg_NE - ("actual for non-limited & cannot be a limited type", Actual, + ("actual for non-limited & cannot be a limited type", Actual, Gen_T); Explain_Limited_Type (Act_T, Actual); Abandon_Instantiation (Actual); + elsif Known_To_Have_Preelab_Init (A_Gen_T) + and then not Has_Preelaborable_Initialization (Act_T) + then + Error_Msg_NE + ("actual for & must have preelaborable initialization", Actual, + Gen_T); + elsif Is_Indefinite_Subtype (Act_T) and then not Is_Indefinite_Subtype (A_Gen_T) and then Ada_Version >= Ada_95 @@ -8192,19 +9479,20 @@ package body Sem_Ch12 is Formal_Subt := Get_Instance_Of (Etype (Formal_Discr)); - -- access discriminants match if designated types do. + -- Access discriminants match if designated types do if Ekind (Base_Type (Formal_Subt)) = E_Anonymous_Access_Type - and then (Ekind (Base_Type (Etype (Actual_Discr)))) - = E_Anonymous_Access_Type - and then Get_Instance_Of ( - Designated_Type (Base_Type (Formal_Subt))) - = Designated_Type (Base_Type (Etype (Actual_Discr))) + and then (Ekind (Base_Type (Etype (Actual_Discr)))) = + E_Anonymous_Access_Type + and then + Get_Instance_Of + (Designated_Type (Base_Type (Formal_Subt))) = + Designated_Type (Base_Type (Etype (Actual_Discr))) then null; elsif Base_Type (Formal_Subt) /= - Base_Type (Etype (Actual_Discr)) + Base_Type (Etype (Actual_Discr)) then Error_Msg_NE ("types of actual discriminants must match formal", @@ -8243,7 +9531,7 @@ package body Sem_Ch12 is begin if Get_Instance_Of (A_Gen_T) /= A_Gen_T then Error_Msg_N ("duplicate instantiation of generic type", Actual); - return Error; + return New_List (Error); elsif not Is_Entity_Name (Actual) or else not Is_Type (Entity (Actual)) @@ -8285,8 +9573,14 @@ package body Sem_Ch12 is -- Deal with error of using incomplete type as generic actual - if Ekind (Act_T) = E_Incomplete_Type then - if No (Underlying_Type (Act_T)) then + if Ekind (Act_T) = E_Incomplete_Type + or else (Is_Class_Wide_Type (Act_T) + and then + Ekind (Root_Type (Act_T)) = E_Incomplete_Type) + then + if Is_Class_Wide_Type (Act_T) + or else No (Underlying_Type (Act_T)) + then Error_Msg_N ("premature use of incomplete type", Actual); Abandon_Instantiation (Actual); else @@ -8326,14 +9620,18 @@ package body Sem_Ch12 is Class_Wide_Type (Act_T)); end if; - if not Is_Abstract (A_Gen_T) - and then Is_Abstract (Act_T) + if not Is_Abstract_Type (A_Gen_T) + and then Is_Abstract_Type (Act_T) then Error_Msg_N ("actual of non-abstract formal cannot be abstract", Actual); end if; - if Is_Scalar_Type (Gen_T) then + -- A generic scalar type is a first subtype for which we generate + -- an anonymous base type. Indicate that the instance of this base + -- is the base type of the actual. + + if Is_Scalar_Type (A_Gen_T) then Set_Instance_Of (Etype (A_Gen_T), Etype (Act_T)); end if; end if; @@ -8400,14 +9698,27 @@ package body Sem_Ch12 is N_Access_Procedure_Definition => Validate_Access_Subprogram_Instance; + when N_Record_Definition => + Validate_Interface_Type_Instance; + + when N_Derived_Type_Definition => + Validate_Derived_Interface_Type_Instance; + when others => raise Program_Error; end case; + Subt := New_Copy (Gen_T); + + -- Use adjusted sloc of subtype name as the location for other nodes in + -- the subtype declaration. + + Loc := Sloc (Subt); + Decl_Node := Make_Subtype_Declaration (Loc, - Defining_Identifier => New_Copy (Gen_T), + Defining_Identifier => Subt, Subtype_Indication => New_Reference_To (Act_T, Loc)); if Is_Private_Type (Act_T) then @@ -8419,6 +9730,8 @@ package body Sem_Ch12 is Set_Has_Private_View (Subtype_Indication (Decl_Node)); end if; + Decl_Nodes := New_List (Decl_Node); + -- Flag actual derived types so their elaboration produces the -- appropriate renamings for the primitive operations of the ancestor. -- Flag actual for formal private types as well, to determine whether @@ -8430,9 +9743,73 @@ package body Sem_Ch12 is Set_Generic_Parent_Type (Decl_Node, Ancestor); end if; - return Decl_Node; + -- If the actual is a synchronized type that implements an interface, + -- the primitive operations are attached to the corresponding record, + -- and we have to treat it as an additional generic actual, so that its + -- primitive operations become visible in the instance. The task or + -- protected type itself does not carry primitive operations. + + if Is_Concurrent_Type (Act_T) + and then Is_Tagged_Type (Act_T) + and then Present (Corresponding_Record_Type (Act_T)) + and then Present (Ancestor) + and then Is_Interface (Ancestor) + then + declare + Corr_Rec : constant Entity_Id := + Corresponding_Record_Type (Act_T); + New_Corr : Entity_Id; + Corr_Decl : Node_Id; + + begin + New_Corr := Make_Defining_Identifier (Loc, + Chars => New_Internal_Name ('S')); + Corr_Decl := + Make_Subtype_Declaration (Loc, + Defining_Identifier => New_Corr, + Subtype_Indication => + New_Reference_To (Corr_Rec, Loc)); + Append_To (Decl_Nodes, Corr_Decl); + + if Ekind (Act_T) = E_Task_Type then + Set_Ekind (Subt, E_Task_Subtype); + else + Set_Ekind (Subt, E_Protected_Subtype); + end if; + + Set_Corresponding_Record_Type (Subt, Corr_Rec); + Set_Generic_Parent_Type (Corr_Decl, Ancestor); + Set_Generic_Parent_Type (Decl_Node, Empty); + end; + end if; + + return Decl_Nodes; end Instantiate_Type; + ----------------------- + -- Is_Generic_Formal -- + ----------------------- + + function Is_Generic_Formal (E : Entity_Id) return Boolean is + Kind : Node_Kind; + + begin + if No (E) then + return False; + else + Kind := Nkind (Parent (E)); + return + Kind = N_Formal_Object_Declaration + or else Kind = N_Formal_Package_Declaration + or else Kind = N_Formal_Type_Declaration + or else + (Is_Formal_Subprogram (E) + and then + Nkind (Parent (Parent (E))) in + N_Formal_Subprogram_Declaration); + end if; + end Is_Generic_Formal; + --------------------- -- Is_In_Main_Unit -- --------------------- @@ -8445,8 +9822,8 @@ package body Sem_Ch12 is if Unum = Main_Unit then return True; - -- If the current unit is a subunit then it is either the main unit - -- or is being compiled as part of the main unit. + -- If the current unit is a subunit then it is either the main unit or + -- is being compiled as part of the main unit. elsif Nkind (N) = N_Compilation_Unit then return Nkind (Unit (N)) = N_Subunit; @@ -8459,10 +9836,10 @@ package body Sem_Ch12 is Current_Unit := Parent (Current_Unit); end loop; - -- The instantiation node is in the main unit, or else the current - -- node (perhaps as the result of nested instantiations) is in the - -- main unit, or in the declaration of the main unit, which in this - -- last case must be a body. + -- The instantiation node is in the main unit, or else the current node + -- (perhaps as the result of nested instantiations) is in the main unit, + -- or in the declaration of the main unit, which in this last case must + -- be a body. return Unum = Main_Unit or else Current_Unit = Cunit (Main_Unit) @@ -8488,16 +9865,15 @@ package body Sem_Ch12 is or else (Nkind (Unit (Comp_Unit)) = N_Package_Body and then not Is_In_Main_Unit (Spec)) then - -- Find body of parent of spec, and analyze it. A special case - -- arises when the parent is an instantiation, that is to say when - -- we are currently instantiating a nested generic. In that case, - -- there is no separate file for the body of the enclosing instance. - -- Instead, the enclosing body must be instantiated as if it were - -- a pending instantiation, in order to produce the body for the - -- nested generic we require now. Note that in that case the - -- generic may be defined in a package body, the instance defined - -- in the same package body, and the original enclosing body may not - -- be in the main unit. + -- Find body of parent of spec, and analyze it. A special case arises + -- when the parent is an instantiation, that is to say when we are + -- currently instantiating a nested generic. In that case, there is + -- no separate file for the body of the enclosing instance. Instead, + -- the enclosing body must be instantiated as if it were a pending + -- instantiation, in order to produce the body for the nested generic + -- we require now. Note that in that case the generic may be defined + -- in a package body, the instance defined in the same package body, + -- and the original enclosing body may not be in the main unit. True_Parent := Parent (Spec); Inst_Node := Empty; @@ -8564,13 +9940,13 @@ package body Sem_Ch12 is if No (Corresponding_Body (Instance_Spec (Inst_Node))) then - -- We need to determine the expander mode to instantiate - -- the enclosing body. Because the generic body we need - -- may use global entities declared in the enclosing package - -- (including aggregates) it is in general necessary to - -- compile this body with expansion enabled. The exception - -- is if we are within a generic package, in which case - -- the usual generic rule applies. + -- We need to determine the expander mode to instantiate the + -- enclosing body. Because the generic body we need may use + -- global entities declared in the enclosing package (including + -- aggregates) it is in general necessary to compile this body + -- with expansion enabled. The exception is if we are within a + -- generic package, in which case the usual generic rule + -- applies. declare Exp_Status : Boolean := True; @@ -8617,8 +9993,7 @@ package body Sem_Ch12 is begin Error_Msg_Unit_1 := Bname; Error_Msg_N ("this instantiation requires$!", N); - Error_Msg_Name_1 := - Get_File_Name (Bname, Subunit => False); + Error_Msg_File_1 := Get_File_Name (Bname, Subunit => False); Error_Msg_N ("\but file{ was not found!", N); raise Unrecoverable_Error; end; @@ -8626,10 +10001,9 @@ package body Sem_Ch12 is end if; end if; - -- If loading the parent of the generic caused an instantiation - -- circularity, we abandon compilation at this point, because - -- otherwise in some cases we get into trouble with infinite - -- recursions after this point. + -- If loading parent of the generic caused an instantiation circularity, + -- we abandon compilation at this point, because otherwise in some cases + -- we get into trouble with infinite recursions after this point. if Circularity_Detected then raise Unrecoverable_Error; @@ -8667,7 +10041,6 @@ package body Sem_Ch12 is else while Scop /= Standard_Standard loop - if Scop = Out_Of then return False; else @@ -8763,51 +10136,71 @@ package body Sem_Ch12 is begin Assoc := First (Generic_Associations (N)); - while Present (Assoc) loop - Act := Explicit_Generic_Actual_Parameter (Assoc); + if Nkind (Assoc) /= N_Others_Choice then + Act := Explicit_Generic_Actual_Parameter (Assoc); - -- Within a nested instantiation, a defaulted actual is an - -- empty association, so nothing to analyze. If the actual for - -- a subprogram is an attribute, analyze prefix only, because - -- actual is not a complete attribute reference. + -- Within a nested instantiation, a defaulted actual is an empty + -- association, so nothing to analyze. If the subprogram actual + -- isan attribute, analyze prefix only, because actual is not a + -- complete attribute reference. - -- If actual is an allocator, analyze expression only. The full - -- analysis can generate code, and if the instance is a compilation - -- unit we have to wait until the package instance is installed to - -- have a proper place to insert this code. + -- If actual is an allocator, analyze expression only. The full + -- analysis can generate code, and if instance is a compilation + -- unit we have to wait until the package instance is installed + -- to have a proper place to insert this code. - -- String literals may be operators, but at this point we do not - -- know whether the actual is a formal subprogram or a string. + -- String literals may be operators, but at this point we do not + -- know whether the actual is a formal subprogram or a string. - if No (Act) then - null; + if No (Act) then + null; - elsif Nkind (Act) = N_Attribute_Reference then - Analyze (Prefix (Act)); + elsif Nkind (Act) = N_Attribute_Reference then + Analyze (Prefix (Act)); - elsif Nkind (Act) = N_Explicit_Dereference then - Analyze (Prefix (Act)); + elsif Nkind (Act) = N_Explicit_Dereference then + Analyze (Prefix (Act)); - elsif Nkind (Act) = N_Allocator then - declare - Expr : constant Node_Id := Expression (Act); + elsif Nkind (Act) = N_Allocator then + declare + Expr : constant Node_Id := Expression (Act); - begin - if Nkind (Expr) = N_Subtype_Indication then - Analyze (Subtype_Mark (Expr)); - Analyze_List (Constraints (Constraint (Expr))); - else - Analyze (Expr); - end if; - end; + begin + if Nkind (Expr) = N_Subtype_Indication then + Analyze (Subtype_Mark (Expr)); - elsif Nkind (Act) /= N_Operator_Symbol then - Analyze (Act); - end if; + -- Analyze separately each discriminant constraint, + -- when given with a named association. + + declare + Constr : Node_Id; - if Errs /= Serious_Errors_Detected then - Abandon_Instantiation (Act); + begin + Constr := First (Constraints (Constraint (Expr))); + while Present (Constr) loop + if Nkind (Constr) = N_Discriminant_Association then + Analyze (Expression (Constr)); + else + Analyze (Constr); + end if; + + Next (Constr); + end loop; + end; + + else + Analyze (Expr); + end if; + end; + + elsif Nkind (Act) /= N_Operator_Symbol then + Analyze (Act); + end if; + + if Errs /= Serious_Errors_Detected then + Abandon_Instantiation (Act); + end if; end if; Next (Assoc); @@ -8825,9 +10218,8 @@ package body Sem_Ch12 is Hidden : Elmt_Id; begin - -- After child instantiation is complete, remove from scope stack - -- the extra copy of the current scope, and then remove parent - -- instances. + -- After child instantiation is complete, remove from scope stack the + -- extra copy of the current scope, and then remove parent instances. if not In_Body then Pop_Scope; @@ -8848,21 +10240,29 @@ package body Sem_Ch12 is and then P /= Current_Scope then -- We are within an instance of some sibling. Retain - -- visibility of parent, for proper subsequent cleanup. + -- visibility of parent, for proper subsequent cleanup, + -- and reinstall private declarations as well. Set_In_Private_Part (P); + Install_Private_Declarations (P); end if; - -- This looks incomplete: what about compilation units that - -- were made visible by Install_Parent but should not remain - -- visible??? Standard is on the scope stack. + -- If the ultimate parent is a top-level unit recorded in + -- Instance_Parent_Unit, then reset its visibility to what + -- it was before instantiation. (It's not clear what the + -- purpose is of testing whether Scope (P) is In_Open_Scopes, + -- but that test was present before the ultimate parent test + -- was added.???) - elsif not In_Open_Scopes (Scope (P)) then + elsif not In_Open_Scopes (Scope (P)) + or else (P = Instance_Parent_Unit + and then not Parent_Unit_Visible) + then Set_Is_Immediately_Visible (P, False); end if; end loop; - -- Reset visibility of entities in the enclosing scope. + -- Reset visibility of entities in the enclosing scope Set_Is_Hidden_Open_Scope (Current_Scope, False); Hidden := First_Elmt (Hidden_Entities); @@ -8884,7 +10284,6 @@ package body Sem_Ch12 is exit when S = Standard_Standard; end loop; end if; - end Remove_Parent; ----------------- @@ -8895,8 +10294,6 @@ package body Sem_Ch12 is Saved : Instance_Env renames Instance_Envs.Table (Instance_Envs.Last); begin - Ada_Version := Saved.Ada_Version; - if No (Current_Instantiated_Parent.Act_Id) then -- Restore environment after subprogram inlining @@ -8908,6 +10305,10 @@ package body Sem_Ch12 is Exchanged_Views := Saved.Exchanged_Views; Hidden_Entities := Saved.Hidden_Entities; Current_Sem_Unit := Saved.Current_Sem_Unit; + Parent_Unit_Visible := Saved.Parent_Unit_Visible; + Instance_Parent_Unit := Saved.Instance_Parent_Unit; + + Restore_Opt_Config_Switches (Saved.Switches); Instance_Envs.Decrement_Last; end Restore_Env; @@ -8930,19 +10331,22 @@ package body Sem_Ch12 is -- Hide the generic formals of formal packages declared with box -- which were reachable in the current instantiation. + --------------------------- + -- Restore_Nested_Formal -- + --------------------------- + procedure Restore_Nested_Formal (Formal : Entity_Id) is Ent : Entity_Id; + begin if Present (Renamed_Object (Formal)) and then Denotes_Formal_Package (Renamed_Object (Formal), True) then return; - elsif Present (Associated_Formal_Package (Formal)) - and then Box_Present (Parent (Associated_Formal_Package (Formal))) - then - Ent := First_Entity (Formal); + elsif Present (Associated_Formal_Package (Formal)) then + Ent := First_Entity (Formal); while Present (Ent) loop exit when Ekind (Ent) = E_Package and then Renamed_Entity (Ent) = Renamed_Entity (Formal); @@ -8950,8 +10354,9 @@ package body Sem_Ch12 is Set_Is_Hidden (Ent); Set_Is_Potentially_Use_Visible (Ent, False); + -- If package, then recurse + if Ekind (Ent) = E_Package then - -- Recurse. Restore_Nested_Formal (Ent); end if; @@ -8960,6 +10365,8 @@ package body Sem_Ch12 is end if; end Restore_Nested_Formal; + -- Start of processing for Restore_Private_Views + begin M := First_Elmt (Exchanged_Views); while Present (M) loop @@ -8976,7 +10383,6 @@ package body Sem_Ch12 is or else Ekind (Typ) = E_Record_Type_With_Private then Dep_Elmt := First_Elmt (Private_Dependents (Typ)); - while Present (Dep_Elmt) loop Dep_Typ := Node (Dep_Elmt); @@ -9003,7 +10409,6 @@ package body Sem_Ch12 is -- types into subtypes of the actuals again. E := First_Entity (Pack_Id); - while Present (E) loop Set_Is_Hidden (E, True); @@ -9013,14 +10418,13 @@ package body Sem_Ch12 is Set_Is_Generic_Actual_Type (E, False); -- An unusual case of aliasing: the actual may also be directly - -- visible in the generic, and be private there, while it is - -- fully visible in the context of the instance. The internal - -- subtype is private in the instance, but has full visibility - -- like its parent in the enclosing scope. This enforces the - -- invariant that the privacy status of all private dependents of - -- a type coincide with that of the parent type. This can only - -- happen when a generic child unit is instantiated within a - -- sibling. + -- visible in the generic, and be private there, while it is fully + -- visible in the context of the instance. The internal subtype is + -- private in the instance, but has full visibility like its + -- parent in the enclosing scope. This enforces the invariant that + -- the privacy status of all private dependents of a type coincide + -- with that of the parent type. This can only happen when a + -- generic child unit is instantiated within sibling. if Is_Private_Type (E) and then not Is_Private_Type (Etype (E)) @@ -9107,18 +10511,17 @@ package body Sem_Ch12 is N2 : Node_Id; function Is_Global (E : Entity_Id) return Boolean; - -- Check whether entity is defined outside of generic unit. - -- Examine the scope of an entity, and the scope of the scope, - -- etc, until we find either Standard, in which case the entity - -- is global, or the generic unit itself, which indicates that - -- the entity is local. If the entity is the generic unit itself, - -- as in the case of a recursive call, or the enclosing generic unit, - -- if different from the current scope, then it is local as well, - -- because it will be replaced at the point of instantiation. On - -- the other hand, if it is a reference to a child unit of a common - -- ancestor, which appears in an instantiation, it is global because - -- it is used to denote a specific compilation unit at the time the - -- instantiations will be analyzed. + -- Check whether entity is defined outside of generic unit. Examine the + -- scope of an entity, and the scope of the scope, etc, until we find + -- either Standard, in which case the entity is global, or the generic + -- unit itself, which indicates that the entity is local. If the entity + -- is the generic unit itself, as in the case of a recursive call, or + -- the enclosing generic unit, if different from the current scope, then + -- it is local as well, because it will be replaced at the point of + -- instantiation. On the other hand, if it is a reference to a child + -- unit of a common ancestor, which appears in an instantiation, it is + -- global because it is used to denote a specific compilation unit at + -- the time the instantiations will be analyzed. procedure Reset_Entity (N : Node_Id); -- Save semantic information on global entity, so that it is not @@ -9128,11 +10531,11 @@ package body Sem_Ch12 is -- Apply Save_Global_References to the two syntactic descendants of -- non-terminal nodes that carry an Associated_Node and are processed -- through Reset_Entity. Once the global entity (if any) has been - -- captured together with its type, only two syntactic descendants - -- need to be traversed to complete the processing of the tree rooted - -- at N. This applies to Selected_Components, Expanded_Names, and to - -- Operator nodes. N can also be a character literal, identifier, or - -- operator symbol node, but the call has no effect in these cases. + -- captured together with its type, only two syntactic descendants need + -- to be traversed to complete the processing of the tree rooted at N. + -- This applies to Selected_Components, Expanded_Names, and to Operator + -- nodes. N can also be a character literal, identifier, or operator + -- symbol node, but the call has no effect in these cases. procedure Save_Global_Defaults (N1, N2 : Node_Id); -- Default actuals in nested instances must be handled specially @@ -9147,7 +10550,7 @@ package body Sem_Ch12 is -- so that it can be properly resolved in a subsequent instantiation. procedure Save_Global_Descendant (D : Union_Id); - -- Apply Save_Global_References recursively to the descendents of + -- Apply Save_Global_References recursively to the descendents of the -- current node. procedure Save_References (N : Node_Id); @@ -9316,9 +10719,7 @@ package body Sem_Ch12 is Set_Etype (N, Empty); end if; - if (Nkind (Parent (N)) = N_Package_Instantiation - or else Nkind (Parent (N)) = N_Function_Instantiation - or else Nkind (Parent (N)) = N_Procedure_Instantiation) + if Nkind (Parent (N)) in N_Generic_Instantiation and then N = Name (Parent (N)) then Save_Global_Defaults (Parent (N), Parent (N2)); @@ -9327,20 +10728,19 @@ package body Sem_Ch12 is elsif Nkind (Parent (N)) = N_Selected_Component and then Nkind (Parent (N2)) = N_Expanded_Name then - if Is_Global (Entity (Parent (N2))) then Change_Selected_Component_To_Expanded_Name (Parent (N)); Set_Associated_Node (Parent (N), Parent (N2)); Set_Global_Type (Parent (N), Parent (N2)); Save_Entity_Descendants (N); - -- If this is a reference to the current generic entity, - -- replace by the name of the generic homonym of the current - -- package. This is because in an instantiation Par.P.Q will - -- not resolve to the name of the instance, whose enclosing - -- scope is not necessarily Par. We use the generic homonym - -- rather that the name of the generic itself, because it may - -- be hidden by a local declaration. + -- If this is a reference to the current generic entity, replace + -- by the name of the generic homonym of the current package. This + -- is because in an instantiation Par.P.Q will not resolve to the + -- name of the instance, whose enclosing scope is not necessarily + -- Par. We use the generic homonym rather that the name of the + -- generic itself, because it may be hidden by a local + -- declaration. elsif In_Open_Scopes (Entity (Parent (N2))) and then not @@ -9358,19 +10758,15 @@ package body Sem_Ch12 is end if; end if; - if (Nkind (Parent (Parent (N))) = N_Package_Instantiation - or else Nkind (Parent (Parent (N))) - = N_Function_Instantiation - or else Nkind (Parent (Parent (N))) - = N_Procedure_Instantiation) + if Nkind (Parent (Parent (N))) in N_Generic_Instantiation and then Parent (N) = Name (Parent (Parent (N))) then Save_Global_Defaults (Parent (Parent (N)), Parent (Parent ((N2)))); end if; - -- A selected component may denote a static constant that has - -- been folded. Make the same replacement in original tree. + -- A selected component may denote a static constant that has been + -- folded. Make the same replacement in original tree. elsif Nkind (Parent (N)) = N_Selected_Component and then (Nkind (Parent (N2)) = N_Integer_Literal @@ -9381,23 +10777,38 @@ package body Sem_Ch12 is Set_Analyzed (Parent (N), False); -- A selected component may be transformed into a parameterless - -- function call. If the called entity is global, rewrite the - -- node appropriately, i.e. as an extended name for the global - -- entity. + -- function call. If the called entity is global, rewrite the node + -- appropriately, i.e. as an extended name for the global entity. elsif Nkind (Parent (N)) = N_Selected_Component and then Nkind (Parent (N2)) = N_Function_Call - and then Is_Global (Entity (Name (Parent (N2)))) + and then N = Selector_Name (Parent (N)) then - Change_Selected_Component_To_Expanded_Name (Parent (N)); - Set_Associated_Node (Parent (N), Name (Parent (N2))); - Set_Global_Type (Parent (N), Name (Parent (N2))); - Save_Entity_Descendants (N); + if No (Parameter_Associations (Parent (N2))) then + if Is_Global (Entity (Name (Parent (N2)))) then + Change_Selected_Component_To_Expanded_Name (Parent (N)); + Set_Associated_Node (Parent (N), Name (Parent (N2))); + Set_Global_Type (Parent (N), Name (Parent (N2))); + Save_Entity_Descendants (N); - else - -- Entity is local. Reset in generic unit, so that node - -- is resolved anew at the point of instantiation. + else + Set_Associated_Node (N, Empty); + Set_Etype (N, Empty); + end if; + + -- In Ada 2005, X.F may be a call to a primitive operation, + -- rewritten as F (X). This rewriting will be done again in an + -- instance, so keep the original node. Global entities will be + -- captured as for other constructs. + else + null; + end if; + + -- Entity is local. Reset in generic unit, so that node is resolved + -- anew at the point of instantiation. + + else Set_Associated_Node (N, Empty); Set_Etype (N, Empty); end if; @@ -9467,7 +10878,7 @@ package body Sem_Ch12 is Next (Act2); end loop; - -- Find the associations added for default suprograms. + -- Find the associations added for default suprograms if Present (Act2) then while Nkind (Act2) /= N_Generic_Association @@ -9511,9 +10922,8 @@ package body Sem_Ch12 is Append (Ndec, Assoc1); - -- If there are other defaults, add a dummy association - -- in case there are other defaulted formals with the same - -- name. + -- If there are other defaults, add a dummy association in case + -- there are other defaulted formals with the same name. elsif Present (Next (Act2)) then Ndec := @@ -9608,7 +11018,7 @@ package body Sem_Ch12 is -- specially a number of node rewritings that are required by semantic -- processing and which change the kind of nodes in the generic copy: -- typically constant-folding, replacing an operator node by a string - -- literal, or a selected component by an expanded name. In each of + -- literal, or a selected component by an expanded name. In each of -- those cases, the transformation is propagated to the generic unit. procedure Save_References (N : Node_Id) is @@ -9629,9 +11039,7 @@ package body Sem_Ch12 is end if; elsif Nkind (N) in N_Op then - if Nkind (N) = Nkind (Get_Associated_Node (N)) then - if Nkind (N) = N_Op_Concat then Set_Is_Component_Left_Opnd (N, Is_Component_Left_Opnd (Get_Associated_Node (N))); @@ -9641,6 +11049,7 @@ package body Sem_Ch12 is end if; Reset_Entity (N); + else -- Node may be transformed into call to a user-defined operator @@ -9662,19 +11071,39 @@ package body Sem_Ch12 is or else Nkind (N2) = N_Real_Literal or else Nkind (N2) = N_String_Literal then - -- Operation was constant-folded, perform the same - -- replacement in generic. + if Present (Original_Node (N2)) + and then Nkind (Original_Node (N2)) = Nkind (N) + then - Rewrite (N, New_Copy (N2)); - Set_Analyzed (N, False); + -- Operation was constant-folded. Whenever possible, + -- recover semantic information from unfolded node, + -- for ASIS use. + + Set_Associated_Node (N, Original_Node (N2)); + + if Nkind (N) = N_Op_Concat then + Set_Is_Component_Left_Opnd (N, + Is_Component_Left_Opnd (Get_Associated_Node (N))); + Set_Is_Component_Right_Opnd (N, + Is_Component_Right_Opnd (Get_Associated_Node (N))); + end if; + + Reset_Entity (N); + + else + -- If original node is already modified, propagate + -- constant-folding to template. + + Rewrite (N, New_Copy (N2)); + Set_Analyzed (N, False); + end if; elsif Nkind (N2) = N_Identifier and then Ekind (Entity (N2)) = E_Enumeration_Literal then - -- Same if call was folded into a literal, but in this - -- case retain the entity to avoid spurious ambiguities - -- if id is overloaded at the point of instantiation or - -- inlining. + -- Same if call was folded into a literal, but in this case + -- retain the entity to avoid spurious ambiguities if id is + -- overloaded at the point of instantiation or inlining. Rewrite (N, New_Copy (N2)); Set_Analyzed (N, False); @@ -9691,9 +11120,9 @@ package body Sem_Ch12 is elsif Nkind (N) = N_Identifier then if Nkind (N) = Nkind (Get_Associated_Node (N)) then - -- If this is a discriminant reference, always save it. - -- It is used in the instance to find the corresponding - -- discriminant positionally rather than by name. + -- If this is a discriminant reference, always save it. It is + -- used in the instance to find the corresponding discriminant + -- positionally rather than by name. Set_Original_Discriminant (N, Original_Discriminant (Get_Associated_Node (N))); @@ -9705,8 +11134,8 @@ package body Sem_Ch12 is if Nkind (N2) = N_Function_Call then E := Entity (Name (N2)); - -- Name resolves to a call to parameterless function. - -- If original entity is global, mark node as resolved. + -- Name resolves to a call to parameterless function. If + -- original entity is global, mark node as resolved. if Present (E) and then Is_Global (E) @@ -9718,16 +11147,25 @@ package body Sem_Ch12 is end if; elsif - Nkind (N2) = N_Integer_Literal or else - Nkind (N2) = N_Real_Literal or else - Nkind (N2) = N_String_Literal + (Nkind (N2) = N_Integer_Literal + or else + Nkind (N2) = N_Real_Literal) + and then Is_Entity_Name (Original_Node (N2)) then -- Name resolves to named number that is constant-folded, - -- or to string literal from concatenation. - -- Perform the same replacement in generic. + -- We must preserve the original name for ASIS use, and + -- undo the constant-folding, which will be repeated in + -- each instance. + + Set_Associated_Node (N, Original_Node (N2)); + Reset_Entity (N); + + elsif Nkind (N2) = N_String_Literal then + + -- Name resolves to string literal. Perform the same + -- replacement in generic. Rewrite (N, New_Copy (N2)); - Set_Analyzed (N, False); elsif Nkind (N2) = N_Explicit_Dereference then @@ -9736,7 +11174,7 @@ package body Sem_Ch12 is -- access to a composite type, or a parameterless function -- call that returns an access type. - -- Check whether corresponding entity in prefix is global. + -- Check whether corresponding entity in prefix is global if Is_Entity_Name (Prefix (N2)) and then Present (Entity (Prefix (N2))) @@ -9766,9 +11204,9 @@ package body Sem_Ch12 is Set_Etype (N, Empty); end if; - -- The subtype mark of a nominally unconstrained object - -- is rewritten as a subtype indication using the bounds - -- of the expression. Recover the original subtype mark. + -- The subtype mark of a nominally unconstrained object is + -- rewritten as a subtype indication using the bounds of the + -- expression. Recover the original subtype mark. elsif Nkind (N2) = N_Subtype_Indication and then Is_Entity_Name (Original_Node (N2)) @@ -9786,6 +11224,11 @@ package body Sem_Ch12 is else declare + Loc : constant Source_Ptr := Sloc (N); + Qual : Node_Id := Empty; + Typ : Entity_Id := Empty; + Nam : Node_Id; + use Atree.Unchecked_Access; -- This code section is part of implementing an untyped tree -- traversal, so it needs direct access to node fields. @@ -9797,11 +11240,66 @@ package body Sem_Ch12 is then N2 := Get_Associated_Node (N); + if No (N2) then + Typ := Empty; + else + Typ := Etype (N2); + + -- In an instance within a generic, use the name of + -- the actual and not the original generic parameter. + -- If the actual is global in the current generic it + -- must be preserved for its instantiation. + + if Nkind (Parent (Typ)) = N_Subtype_Declaration + and then + Present (Generic_Parent_Type (Parent (Typ))) + then + Typ := Base_Type (Typ); + Set_Etype (N2, Typ); + end if; + end if; + if No (N2) - or else No (Etype (N2)) - or else not Is_Global (Etype (N2)) + or else No (Typ) + or else not Is_Global (Typ) then Set_Associated_Node (N, Empty); + + -- If the aggregate is an actual in a call, it has been + -- resolved in the current context, to some local type. + -- The enclosing call may have been disambiguated by the + -- aggregate, and this disambiguation might fail at + -- instantiation time because the type to which the + -- aggregate did resolve is not preserved. In order to + -- preserve some of this information, we wrap the + -- aggregate in a qualified expression, using the id of + -- its type. For further disambiguation we qualify the + -- type name with its scope (if visible) because both + -- id's will have corresponding entities in an instance. + -- This resolves most of the problems with missing type + -- information on aggregates in instances. + + if Nkind (N2) = Nkind (N) + and then + (Nkind (Parent (N2)) = N_Procedure_Call_Statement + or else Nkind (Parent (N2)) = N_Function_Call) + and then Comes_From_Source (Typ) + then + if Is_Immediately_Visible (Scope (Typ)) then + Nam := Make_Selected_Component (Loc, + Prefix => + Make_Identifier (Loc, Chars (Scope (Typ))), + Selector_Name => + Make_Identifier (Loc, Chars (Typ))); + else + Nam := Make_Identifier (Loc, Chars (Typ)); + end if; + + Qual := + Make_Qualified_Expression (Loc, + Subtype_Mark => Nam, + Expression => Relocate_Node (N)); + end if; end if; Save_Global_Descendant (Field1 (N)); @@ -9809,6 +11307,10 @@ package body Sem_Ch12 is Save_Global_Descendant (Field3 (N)); Save_Global_Descendant (Field5 (N)); + if Present (Qual) then + Rewrite (N, Qual); + end if; + -- All other cases than aggregates else @@ -9827,9 +11329,9 @@ package body Sem_Ch12 is begin Gen_Scope := Current_Scope; - -- If the generic unit is a child unit, references to entities in - -- the parent are treated as local, because they will be resolved - -- anew in the context of the instance of the parent. + -- If the generic unit is a child unit, references to entities in the + -- parent are treated as local, because they will be resolved anew in + -- the context of the instance of the parent. while Is_Child_Unit (Gen_Scope) and then Ekind (Scope (Gen_Scope)) = E_Generic_Package @@ -9875,8 +11377,8 @@ package body Sem_Ch12 is procedure Start_Generic is begin - -- ??? I am sure more things could be factored out in this - -- routine. Should probably be done at a later stage. + -- ??? I am sure more things could be factored out in this routine. + -- Should probably be done at a later stage. Generic_Flags.Increment_Last; Generic_Flags.Table (Generic_Flags.Last) := Inside_A_Generic; @@ -9893,17 +11395,16 @@ package body Sem_Ch12 is (Gen_Unit : Entity_Id; Act_Unit : Entity_Id) is - begin -- Regardless of the current mode, predefined units are analyzed in -- the most current Ada mode, and earlier version Ada checks do not -- apply to predefined units. - if Is_Internal_File_Name + Set_Opt_Config_Switches ( + Is_Internal_File_Name (Fname => Unit_File_Name (Get_Source_Unit (Gen_Unit)), - Renamings_Included => True) then - Ada_Version := Ada_Version_Type'Last; - end if; + Renamings_Included => True), + Current_Sem_Unit = Main_Unit); Current_Instantiated_Parent := (Gen_Unit, Act_Unit, Assoc_Null); end Set_Instance_Env; @@ -9919,35 +11420,39 @@ package body Sem_Ch12 is begin -- T may be private but its base type may have been exchanged through - -- some other occurrence, in which case there is nothing to switch. + -- some other occurrence, in which case there is nothing to switch + -- besides T itself. Note that a private dependent subtype of a private + -- type might not have been switched even if the base type has been, + -- because of the last branch of Check_Private_View (see comment there). if not Is_Private_Type (BT) then + Prepend_Elmt (Full_View (T), Exchanged_Views); + Exchange_Declarations (T); return; end if; Priv_Elmt := First_Elmt (Private_Dependents (BT)); if Present (Full_View (BT)) then - Append_Elmt (Full_View (BT), Exchanged_Views); + Prepend_Elmt (Full_View (BT), Exchanged_Views); Exchange_Declarations (BT); end if; while Present (Priv_Elmt) loop Priv_Sub := (Node (Priv_Elmt)); - -- We avoid flipping the subtype if the Etype of its full - -- view is private because this would result in a malformed - -- subtype. This occurs when the Etype of the subtype full - -- view is the full view of the base type (and since the - -- base types were just switched, the subtype is pointing - -- to the wrong view). This is currently the case for - -- tagged record types, access types (maybe more?) and - -- needs to be resolved. ??? + -- We avoid flipping the subtype if the Etype of its full view is + -- private because this would result in a malformed subtype. This + -- occurs when the Etype of the subtype full view is the full view of + -- the base type (and since the base types were just switched, the + -- subtype is pointing to the wrong view). This is currently the case + -- for tagged record types, access types (maybe more?) and needs to + -- be resolved. ??? if Present (Full_View (Priv_Sub)) and then not Is_Private_Type (Etype (Full_View (Priv_Sub))) then - Append_Elmt (Full_View (Priv_Sub), Exchanged_Views); + Prepend_Elmt (Full_View (Priv_Sub), Exchanged_Views); Exchange_Declarations (Priv_Sub); end if;