home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Geek Gadgets 1
/
ADE-1.bin
/
ade-dist
/
gnat-2.06-src.tgz
/
tar.out
/
fsf
/
gnat
/
ada
/
sem_ch12.adb
< prev
next >
Wrap
Text File
|
1996-09-28
|
154KB
|
4,380 lines
------------------------------------------------------------------------------
-- --
-- GNAT COMPILER COMPONENTS --
-- --
-- S E M _ C H 1 2 --
-- --
-- B o d y --
-- --
-- $Revision: 1.302 $ --
-- --
-- Copyright (c) 1992,1993,1994,1995 NYU, All Rights Reserved --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
-- ware Foundation; either version 2, or (at your option) any later ver- --
-- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
-- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
-- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
-- for more details. You should have received a copy of the GNU General --
-- Public License distributed with GNAT; see file COPYING. If not, write --
-- to the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA. --
-- --
------------------------------------------------------------------------------
with Atree; use Atree;
with Einfo; use Einfo;
with Elists; use Elists;
with Errout; use Errout;
with Expander; use Expander;
with Exp_Ch7; use Exp_Ch7;
with Features; use Features;
with Freeze; use Freeze;
with Inline; use Inline;
with Lib; use Lib;
with Lib.Load; use Lib.Load;
with Nlists; use Nlists;
with Nmake; use Nmake;
with Opt; use Opt;
with Output; use Output;
with Rtsfind; use Rtsfind;
with Sem; use Sem;
with Sem_Ch3; use Sem_Ch3;
with Sem_Ch6; use Sem_Ch6;
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_Dist; use Sem_Dist;
with Sem_Eval; use Sem_Eval;
with Sem_Res; use Sem_Res;
with Sem_Type; use Sem_Type;
with Sem_Util; use Sem_Util;
with Stand; use Stand;
with Sinfo; use Sinfo;
with Sinfo.CN; use Sinfo.CN;
with Snames; use Snames;
with Stringt; use Stringt;
with Uname; use Uname;
with Table;
with Tbuild; use Tbuild;
with Uintp; use Uintp;
with Urealp; use Urealp;
with System.Parameters;
package body Sem_Ch12 is
use Atree.Unchecked_Access;
-- This package performs untyped traversals of the tree, therefore it
-- needs direct access to the fields of a node.
-----------------------------------------------------------
-- Implementation of generic analysis and instantiation --
-----------------------------------------------------------
-- GNAT implements generics by macro expansion. No attempt is made to
-- share generic instantions (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
-- do not affect the original tree. Links are kept between the original
-- tree and the copy, in order to recognize non-local references within
-- 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 |
-- | |==============>| |
-- |___________| global |__________|
-- references | | |
-- | | |
-- .-----|--|.
-- | .-----|---.
-- | | .----------.
-- | | | generic |
-- |__| | |
-- |__| 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
-- specification, before the visible declarations of the package. The
-- renamings are analyzed before any of the text of the instance, and are
-- thus visible at the right place. Furthermore, outside of the instance,
-- the generic parameters are visible and denote their corresponding
-- actuals.
-- For subprograms, we create a container package to hold the renamings
-- and the subprogram instance itself. Analysis of the package makes the
-- renaming declarations visible to the subprogram. after analyzing the
-- package, the defining entity for the subprogram is touched-up so that
-- it appears declared in the current scope, and not inside the container
-- package.
-- If the instantiation is a compilation unit, the container package is
-- given the same name as the subprogram instance. This ensures that
-- the elaboration procedure called by the binder, using the compilation
-- unit name, calls in fact the elaboration procedure for the package.
-- Not surprisingly, private types complicate this approach. By saving in
-- the original generic object the non-local references, we guarantee that
-- the proper entities are referenced at the point of instantiation.
-- However, for private types, this by itself does not insure that the
-- proper VIEW of the entity is used (the full type may be visible at the
-- point of generic definition, but not at instantiation, or viceversa).
-- In order to reference the proper view, we special-case any reference
-- to private types in the generic object, by saving boths views, one in
-- the generic and one in the semantic copy. At time of instantiation, we
-- check whether the two views are consistent, and exchange declarations if
-- necessary, in order to restore the correct visibility. Similarly, if
-- the instance view is private when the generic view was not, we perform
-- the exchange. After completing the instantiation, we restore the
-- current visibility. The flag Has_Private_View marks identifiers in the
-- the generic unit that require checking.
-- 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;
-- package New_Outer is new Outer (...); -- 2
-- procedure New_Inner is new New_Outer.Inner (...); -- 3
-- The semantic analysis of Outer captures all occurrences of Global.
-- The semantic analysis of Inner (at 1) captures both occurrences of
-- Global and Semi_Global.
-- At point 2 (instantiation of Outer), we also produce a generic copy
-- of Inner, even though Inner is at that point not being instantiated.
-- (This is just part of the semantic analysis of New_Outer).
-- Critically, references to Global within Inner must be preserved, while
-- references to Semi_Global should not preserved, because they must now
-- resolve to an entity within New_Outer. To distinguish between these, we
-- use a global variable, Current_Instantiated_Parent, which is set when
-- performing a generic copy during instantiation (at 2). This variable is
-- used when performing a generic copy that is not an instantiation, but
-- that is nested within one, as the occurrence of 1 within 2. The analysis
-- of a nested generic only preserves references that are global to the
-- enclosing Current_Instantiated_Parent. We use the Scope_Depth value to
-- determine whether a reference is external to the given parent.
-- The instantiation at point 3 requires no special treatment. The method
-- works as well for further nestings of generic units, but of course the
-- variable Current_Instantiated_Parent must be stacked because nested
-- instantiations can occur, e.g. the occurrence of 4 within 2.
Current_Instantiated_Parent : Entity_Id := Empty;
-----------------------
-- Local subprograms --
-----------------------
procedure Abandon_Instantiation (N : Node_Id);
-- Posts an error message "instnatiation 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;
Def : Node_Id);
-- A formal array type is treated like an array type declaration, and
-- invokes Array_Type_Declaration (sem_ch3) whose first parameter 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.
procedure Analyze_Formal_Derived_Type
(N : Node_Id;
T : Entity_Id;
Def : Node_Id);
procedure Analyze_Formal_Decimal_Fixed_Point (T : Entity_Id; Def : Node_Id);
procedure Analyze_Formal_Discrete_Type (T : Entity_Id; Def : Node_Id);
procedure Analyze_Formal_Floating_Type (T : Entity_Id; Def : Node_Id);
procedure Analyze_Formal_Signed_Integer_Type (T : Entity_Id; Def : Node_Id);
procedure Analyze_Formal_Modular_Type (T : Entity_Id; Def : Node_Id);
procedure Analyze_Formal_Ordinary_Fixed_Point_Type
(T : Entity_Id; Def : Node_Id);
procedure Analyze_Formal_Private_Type
(N : Node_Id;
T : Entity_Id;
Def : Node_Id);
procedure Analyze_Generic_Formal_Part (N : Node_Id);
procedure Analyze_Generic_Access_Type (T : Entity_Id; Def : Node_Id);
function Analyze_Associations
(Formals : List_Id;
Actuals : List_Id;
F_Copy : List_Id)
return List_Id;
-- At instantiation time, build the list of associations between formals
-- and actuals. Each association becomes a renaming declaration for the
-- formal entity. F_Copy is the analyzed list of formals in the generic
-- copy. It is used to apply legality checks to the actuals.
procedure Analyze_Subprogram_Instantiation
(N : Node_Id;
K : Entity_Kind);
procedure Build_Instance_Compilation_Unit_Nodes
(N : Node_Id;
Act_Body : Node_Id;
Act_Decl : Node_Id);
-- This procedure is used in the case where the generic instance of a
-- subprogram body or package body is a library unit. In this case, the
-- original library unit node for the generic instantiation must be
-- replaced by the resulting generic body, and a link made to a new
-- compilation unit node for the generic declaration. The argument N is
-- the original generic instantiation. Act_Body and Act_Decl are the body
-- and declaration of the instance (either package body and declaration
-- 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_Formal_Packages (P_Id : Entity_Id);
-- Apply the following to all formal packages in generic associations.
procedure Check_Formal_Package_Instance
(Actual : Node_Id;
Form_Pkg : Entity_Id;
Act_Pkg : Entity_Id);
-- Verify that the actuals of the actual instance match the actuals of
-- the template for a formal package that is not declared with a box.
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.
procedure Check_Generic_Actuals (Instance : Entity_Id);
-- Similar to previous one. Check the actuals in the instantiation,
-- whose views can change between the point of instantiation and the point
-- of instantiation of the body. In addition, mark the generic renamings
-- as generic actuals, so that they are not compatible with other actuals.
-- Recurse on an actual that is a formal package whose declaration has
-- a box.
procedure Check_Generic_Child_Unit
(Gen_Id : Node_Id;
Parent_Installed : in out Boolean);
-- If the name of the generic unit in an instantiation is a selected
-- component, then the prefix may be an instance and the selector may
-- designate a child unit. Retrieve the parent generic and search for
-- the child unit that must be declared within.
function Get_Instance_Of (A : Entity_Id) return Entity_Id;
-- Retrieve actual associated with given generic parameter.
-- If A is uninstantiated or not a generic parameter, return A.
procedure Set_Instance_Of (A : Entity_Id; B : Entity_Id);
-- Associate analyzed generic parameter with corresponding
-- instance. Used for semantic checks at instantiation time.
procedure Install_Body
(Act_Body : Node_Id;
N : Node_Id;
Gen_Body : Node_Id;
Gen_Decl : Node_Id);
-- If the instantiation happens textually before the body of the generic,
-- the instantiation of the body must be placed after the generic body,
-- and not at the point of instantiation. Such early instantiations can
-- happen if the generic and the instance appear in a package declaration
-- because the generic body can only appear in the corresponding package
-- body. Early instantiations can also appear if generic, instance and
-- body are all in the declarative part of a subprogram or entry.
procedure Install_Parent (P : Entity_Id);
-- 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.
procedure Remove_Parent;
-- Reverse effect after instantiation of child is complete.
-- The functions Instantiate_XXX perform various legality checks and build
-- the declarations for instantiated generic parameters.
-- Need to describe what the parameters are ???
function Instantiate_Object
(Formal : Node_Id;
Actual : Node_Id;
Analyzed_Formal : Node_Id)
return Node_Id;
function Instantiate_Type
(Formal : Node_Id;
Actual : Node_Id;
Analyzed_Formal : Node_Id)
return Node_Id;
function Instantiate_Formal_Subprogram
(Formal : Node_Id;
Actual : Node_Id;
Analyzed_Formal : Node_Id)
return Node_Id;
function Instantiate_Formal_Package
(Formal : Node_Id;
Actual : Node_Id;
Analyzed_Formal : Node_Id)
return Node_Id;
-- If the formal package is declared with a box, special visibility rules
-- apply to its formals: they are in the visible part of the package. This
-- is true in the declarative region of the formal package, that is to say
-- in the enclosing generic or instantiation. For an instantiation, the
-- parameters of the formal package are made visible in an explicit step.
-- Furthermore, if the actual is a visible use_clause, these formals must
-- be made potentially use_visible as well. On exit from the enclosing
-- instantiation, the reverse must be done.
-- For a formal package declared without a box, there are conformance rules
-- that apply to the actuals in the generic declaration and the actuals of
-- the actual package in the enclosing instantiation. The simplest way to
-- 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.
function Is_In_Main_Unit (N : Node_Id) return Boolean;
-- Test if given node is in the main unit
procedure Load_Parent_Of_Generic (N : Entity_Id; Spec : Node_Id);
-- If the generic appears in a separate non-generic library unit,
-- load the corresponding body to retrieve the body of the generic.
procedure Inherit_Context (Gen_Decl : Node_Id; Inst : Node_Id);
-- If a generic is a compilation unit, its instantiation has semantic
-- dependences on the context units of the generic. Eventually these
-- dependences will be reflected in actual ali files for generic units.
-- In the meantime, the simplest is to attach the with clauses of the
-- generic compilation to the compilation that contains the instance.
function Associated_Node (N : Node_Id) return Node_Id;
-- Nodes in a generic unit that have an entity field are linked to the
-- corresponding nodes in the semantic copy, so that non-local references
-- in the copy can be marked in the original generic nodes. The link
-- overlaps the Entity field of the node, and must be reset correctly
-- after collecting global references.
procedure Move_Freeze_Nodes
(Out_Of : Entity_Id;
After : Node_Id;
L : List_Id);
-- Freeze nodes can be generated in the analysis of a generic unit, but
-- will not be seen by the back-end. It is necessary to move those nodes
-- to the enclosing scope if they freeze an outer entity. We place them
-- at the end of the enclosing generic package, which is semantically
-- neutral.
procedure Set_Associated_Node
(Gen_Node : Node_Id;
Copy_Node : Node_Id);
-- Establish the link between an identifier in the generic unit, and the
-- corresponding node in the semantic copy.
-------------------------------------------
-- Data structures for generic renamings --
-------------------------------------------
-- Need more documentation of what Assoc and the table are for ???
type Assoc is record
Gen_Id : Entity_Id;
Act_Id : Entity_Id;
end record;
package Generic_Renamings is new Table
(Table_Component_Type => Assoc,
Table_Index_Type => Int,
Table_Low_Bound => 0,
Table_Initial => 10,
Table_Increment => 10,
Table_Name => "Generic_Renamings");
Exchanged_Views : Elist_Id;
-- This list holds the private views that have been exchanged during
-- instantiation to restore the visibility of the generic declaration.
-- (see comments above). After instantiation, the current visibility is
-- reestablished by means of a traversal of this list.
procedure Restore_Private_Views
(Pack_Id : Entity_Id;
Is_Package : Boolean := True);
-- Restore the private views of external types, and unmark the generic
-- renamings of actuals, so that they become comptible subtypes again.
-- For subprograms, Pack_Id is the package constructed to hold the
-- renamings.
------------------------------------
-- Structures for Error Reporting --
------------------------------------
Instantiation_Node : Node_Id;
-- Used by subprograms that validate instantiation of formal parameters
-- where there might be no actual on which to place the error message.
Instantiation_Error : exception;
-- When there is a semantic error in the generic parameter matching,
-- there is no point in continuing the instantiation, because the
-- number of cascaded errors is unpredictable. This exception aborts
-- the instantiation process altogether.
---------------------------
-- Abandon_Instantiation --
---------------------------
procedure Abandon_Instantiation (N : Node_Id) is
begin
Error_Msg_N ("instantiation abandoned!", N);
raise Instantiation_Error;
end Abandon_Instantiation;
------------------------------------------
-- Analyze_Generic_Package_Declaration --
------------------------------------------
procedure Analyze_Generic_Package_Declaration (N : Node_Id) is
Id : Entity_Id;
New_N : Node_Id;
Save_Parent : Node_Id;
begin
Validate_RCI_Nested_Generic_Declaration (N);
-- 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);
New_N := Copy_Generic_Node (N, Empty, Instantiating => False);
Set_Parent_Spec (New_N, Save_Parent);
Rewrite_Substitute_Tree (N, New_N);
Id := Defining_Unit_Simple_Name (Specification (N));
-- Expansion is not applied to generic units.
Expander_Mode_Save_And_Set (False);
Enter_Name (Id);
Set_Ekind (Id, E_Generic_Package);
Set_Etype (Id, Standard_Void_Type);
New_Scope (Id);
Set_Categorization_From_Following_Pragmas (N);
-- Entities declared in Pure unit should be set Is_Pure
-- Since 'Partition_Id cannot be applied to such an entity
Set_Is_Pure (Id, Is_Pure (Current_Scope));
Analyze_Generic_Formal_Part (N);
-- After processing the generic formals, analysis proceeds
-- as for a non-generic package.
Analyze (Specification (N));
Validate_Categorization_Dependency (N, Id);
Save_Global_References (Original_Node (N));
Expander_Mode_Restore;
End_Package_Scope (Id);
if Nkind (Parent (N)) /= N_Compilation_Unit then
Move_Freeze_Nodes (Id, N, Visible_Declarations (Specification (N)));
Move_Freeze_Nodes (Id, N, Private_Declarations (Specification (N)));
end if;
end Analyze_Generic_Package_Declaration;
---------------------------------------------
-- Analyze_Generic_Subprogram_Declaration --
---------------------------------------------
procedure Analyze_Generic_Subprogram_Declaration (N : Node_Id) is
Spec : Node_Id;
Id : Entity_Id;
Formals : List_Id;
New_N : Node_Id;
Save_Parent : Node_Id;
begin
-- The visible part of an RCI unit must not contain a
-- nested generic_declaration. (RM E.2.3(11)).
if Inside_Remote_Call_Interface_Unit
and then Nkind (Parent (N)) /= N_Compilation_Unit
then
Error_Msg_N
("nested generic declaration not allowed in rci unit", N);
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.
Save_Parent := Parent_Spec (N);
Set_Parent_Spec (N, Empty);
New_N := Copy_Generic_Node (N, Empty, Instantiating => False);
Set_Parent_Spec (New_N, Save_Parent);
Rewrite_Substitute_Tree (N, New_N);
Spec := Specification (N);
Id := Defining_Unit_Simple_Name (Spec);
if Nkind (Id) = N_Defining_Operator_Symbol then
Error_Msg_N
("operator symbol not allowed for generic subprogram", Id);
end if;
-- Expansion is not applied to generic units.
Expander_Mode_Save_And_Set (False);
Enter_Name (Id);
if Nkind (Spec) = N_Function_Specification then
Set_Ekind (Id, E_Generic_Function);
else
Set_Ekind (Id, E_Generic_Procedure);
Set_Etype (Id, Standard_Void_Type);
end if;
New_Scope (Id);
Set_Categorization_From_Following_Pragmas (N);
-- Entities declared in Pure unit should be set Is_Pure
-- Since 'Partition_Id cannot be applied to such an entity
Set_Is_Pure (Id, Is_Pure (Current_Scope));
Analyze_Generic_Formal_Part (N);
Formals := Parameter_Specifications (Spec);
if Present (Formals) then
Process_Formals (Id, Formals, Spec);
end if;
Validate_Categorization_Dependency (N, Id);
if Nkind (Spec) = N_Function_Specification then
Find_Type (Subtype_Mark (Spec));
Set_Etype (Id, Entity (Subtype_Mark (Spec)));
end if;
Save_Global_References (Original_Node (N));
Expander_Mode_Restore;
End_Scope;
end Analyze_Generic_Subprogram_Declaration;
----------------------------------
-- Analyze_Generic_Formal_Part --
----------------------------------
procedure Analyze_Generic_Formal_Part (N : Node_Id) 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.
Gen_Parm_Decl := First (Generic_Formal_Declarations (N));
while Present (Gen_Parm_Decl) loop
Analyze (Gen_Parm_Decl);
Gen_Parm_Decl := Next (Gen_Parm_Decl);
end loop;
end Analyze_Generic_Formal_Part;
----------------------
-- Is_In_Main_Unit --
----------------------
function Is_In_Main_Unit (N : Node_Id) return Boolean is
Unum : constant Unit_Number_Type := Get_Sloc_Unit_Number (Sloc (N));
Current_Unit : Node_Id;
begin
if Unum = Main_Unit then
return True;
elsif Nkind (N) = N_Compilation_Unit then
return False;
end if;
Current_Unit := Parent (N);
while Present (Current_Unit)
and then Nkind (Current_Unit) /= N_Compilation_Unit
loop
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.
return Unum = Main_Unit
or else Current_Unit = Cunit (Main_Unit)
or else Current_Unit = Library_Unit (Cunit (Main_Unit))
or else (Present (Library_Unit (Current_Unit))
and then Is_In_Main_Unit (Library_Unit (Current_Unit)));
end Is_In_Main_Unit;
-----------------------------------
-- Analyze_Package_Instantiation --
-----------------------------------
procedure Analyze_Package_Instantiation (N : Node_Id) is
Loc : constant Source_Ptr := Sloc (N);
Actuals : constant List_Id := Generic_Associations (N);
Gen_Id : constant Node_Id := Name (N);
Act_Decl : Node_Id;
Act_Decl_Id : Entity_Id;
Act_Spec : Node_Id;
Act_Tree : Node_Id;
Gen_Decl : Node_Id;
Gen_Unit : Entity_Id;
Parent_Installed : Boolean := False;
Renaming_List : List_Id;
Unit_Renaming : Node_Id;
Needs_Body : Boolean;
Save_Instantiated_Parent : Entity_Id;
Save_Exchanged_Views : Elist_Id;
begin
-- Very first thing: apply the special kludge for Text_IO processing
-- in case we are instantiating one of the children of [Wide_]Text_IO.
Text_IO_Kludge (Name (N));
-- Make node global for error reporting.
Instantiation_Node := N;
if Nkind (N) = N_Package_Instantiation then
Act_Decl_Id := New_Copy (Defining_Unit_Simple_Name (N));
else
-- Instantiation of a formal package.
Act_Decl_Id := Defining_Identifier (N);
end if;
Check_Generic_Child_Unit (Gen_Id, Parent_Installed);
Gen_Unit := Entity (Gen_Id);
-- If renaming, indicate this is an instantiation of renamed unit
if Present (Renamed_Object (Gen_Unit))
and then Ekind (Renamed_Object (Gen_Unit)) = E_Generic_Package
then
Gen_Unit := Renamed_Object (Gen_Unit);
Set_Entity (Gen_Id, Gen_Unit);
end if;
-- Verify that it is the name of a generic package
if Etype (Gen_Unit) = Any_Type then
return;
end if;
if Ekind (Gen_Unit) /= E_Generic_Package then
Error_Msg_N
("expect name of generic package in instantiation", Gen_Id);
elsif In_Open_Scopes (Gen_Unit) then
Error_Msg_NE
("instantiation of & within itself", N, Gen_Id);
else
Gen_Decl := Get_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.
Save_Exchanged_Views := Exchanged_Views;
Exchanged_Views := New_Elmt_List;
Generic_Renamings.Set_Last (0);
-- Copy original generic tree, to produce text for instantiation.
Save_Instantiated_Parent := Current_Instantiated_Parent;
Current_Instantiated_Parent := Gen_Unit;
Act_Tree := Copy_Generic_Node
(Original_Node (Gen_Decl), Empty, Instantiating => True);
Act_Spec := Specification (Act_Tree);
Renaming_List := Analyze_Associations
(Generic_Formal_Declarations (Act_Tree),
Actuals,
Generic_Formal_Declarations (Gen_Decl));
Set_Defining_Unit_Name (Act_Spec, 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
-- 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.
Unit_Renaming :=
Make_Package_Renaming_Declaration (Loc,
Defining_Unit_Name =>
Make_Defining_Identifier (Loc, Chars (Gen_Unit)),
Name => New_Reference_To (Act_Decl_Id, Loc));
Append (Unit_Renaming, Renaming_List);
-- The renaming declarations are the first local declarations of
-- the new unit.
if Is_Non_Empty_List (Visible_Declarations (Act_Spec)) then
Insert_List_Before
(First (Visible_Declarations (Act_Spec)), Renaming_List);
else
Set_Visible_Declarations (Act_Spec, Renaming_List);
end if;
Act_Decl := 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.
Needs_Body :=
(Unit_Requires_Body (Gen_Unit)
or else Present (Corresponding_Body (Gen_Decl)))
and then Is_In_Main_Unit (N)
and then (Expander_Active or Xref_Analyze);
if Needs_Body then
Pending_Instantiations.Increment_Last;
-- Here is a defence against a ludicrous number of instantiations
-- which can be caused by a nested set of instantiation attempts.
if Pending_Instantiations.Last >
System.Parameters.Max_Instantiations
then
Error_Msg_N ("too many instantiations", N);
raise Unrecoverable_Error;
end if;
-- If OK, then make entry in table
Pending_Instantiations.Table (Pending_Instantiations.Last) :=
(N, Act_Decl);
end if;
Set_Categorization_From_Following_Pragmas (Act_Decl);
if Nkind (Parent (N)) /= N_Compilation_Unit then
Mark_Rewrite_Insertion (Act_Decl);
Insert_Before (N, Act_Decl);
Analyze (Act_Decl);
else
-- Place declaration on current node so context is complete
-- for analysis (including nested instantiations).
Set_Unit (Parent (N), Act_Decl);
Set_Parent_Spec (Act_Decl, Parent_Spec (N));
Analyze (Act_Decl);
Set_Unit (Parent (N), N);
Set_Body_Required (Parent (N), False);
end if;
Current_Instantiated_Parent := Save_Instantiated_Parent;
if not Needs_Body
and then Nkind (Parent (N)) = N_Compilation_Unit
then
Rewrite_Substitute_Tree (N, Act_Decl);
end if;
Set_Has_Completion (Act_Decl_Id);
Check_Formal_Packages (Act_Decl_Id);
Restore_Private_Views (Act_Decl_Id);
Exchanged_Views := Save_Exchanged_Views;
Inherit_Context (Gen_Decl, N);
if Parent_Installed then
Remove_Parent;
end if;
end if;
Validate_Categorization_Dependency (N, Act_Decl_Id);
exception
when Instantiation_Error =>
null;
end Analyze_Package_Instantiation;
------------------------------
-- Instantiate_Package_Body --
------------------------------
procedure Instantiate_Package_Body
(N : Node_Id;
Act_Decl : Node_Id)
is
Gen_Id : constant Node_Id := Name (N);
Gen_Unit : constant Entity_Id := Entity (Name (N));
Gen_Decl : constant Node_Id := Get_Declaration_Node (Gen_Unit);
Act_Decl_Id : constant Entity_Id :=
Defining_Unit_Name (Specification (Act_Decl));
Gen_Body : Node_Id;
Gen_Body_Id : Node_Id;
Act_Body : Node_Id;
Act_Body_Id : Entity_Id;
Save_Instantiated_Parent : Entity_Id;
Save_Exchanged_Views : Elist_Id;
begin
Gen_Body_Id := Corresponding_Body (Gen_Decl);
if No (Gen_Body_Id) then
Load_Parent_Of_Generic (N, Specification (Gen_Decl));
Gen_Body_Id := Corresponding_Body (Gen_Decl);
end if;
if Present (Gen_Body_Id) then
Save_Instantiated_Parent := Current_Instantiated_Parent;
Current_Instantiated_Parent := Gen_Unit;
Save_Exchanged_Views := Exchanged_Views;
Exchanged_Views := New_Elmt_List;
Gen_Body := Get_Declaration_Node (Gen_Body_Id);
Act_Body := Copy_Generic_Node
(Original_Node (Gen_Body), Empty, Instantiating => True);
Act_Body_Id := Defining_Unit_Simple_Name (Act_Body);
Set_Chars (Act_Body_Id, Chars (Act_Decl_Id));
Set_Corresponding_Spec (Act_Body, Act_Decl_Id);
Check_Generic_Actuals (Act_Decl_Id);
-- 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.
if Ekind (Scope (Gen_Unit)) = E_Generic_Package
and then Nkind (Gen_Id) = N_Expanded_Name
then
Install_Parent (Entity (Prefix (Gen_Id)));
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.
if Nkind (Parent (N)) = N_Compilation_Unit then
if Parent (N) = Cunit (Main_Unit) then
Build_Instance_Compilation_Unit_Nodes (N, Act_Body, Act_Decl);
else
null;
end if;
-- If the instantiation is not a library unit, then place the
-- body either at the instantiation node, or after the generic
-- body itself.
else
Install_Body (Act_Body, N, Gen_Body, Gen_Decl);
end if;
Analyze (Act_Body);
Inherit_Context (Gen_Body, N);
Current_Instantiated_Parent := Save_Instantiated_Parent;
Restore_Private_Views (Act_Decl_Id);
Exchanged_Views := Save_Exchanged_Views;
-- If the body instance contains finalizable objects, and the
-- enclosing scope does not, we must create the finalization chain
-- and the finalization procedure now. We must find the right
-- enclosing scope, reinstall it, and expand the required actions.
declare
P : Entity_Id;
begin
if Parent (N) /= Cunit (Main_Unit) then
P := Enclosing_Dynamic_Scope (Act_Decl_Id);
if Present (Finalization_Chain_Entity (P))
and then No (Parent (Finalization_Chain_Entity (P)))
then
New_Scope (P);
Expand_Cleanup_Actions (Get_Declaration_Node (P));
End_Scope;
end if;
end if;
end;
elsif Unit_Requires_Body (Gen_Unit) then
Error_Msg_NE ("cannot find body of generic package &", N, Gen_Unit);
-- 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 Nkind (Parent (N)) = N_Compilation_Unit then
Set_Parent_Spec (Act_Decl, Parent_Spec (N));
Rewrite_Substitute_Tree (N, Act_Decl);
-- If the instantiation is not a library unit, then append the
-- declaration to the list of implicitly generated entities.
else
Mark_Rewrite_Insertion (Act_Decl);
Insert_Before (N, Act_Decl);
end if;
end if;
end Instantiate_Package_Body;
---------------------------------
-- Instantiate_Subprogram_Body --
---------------------------------
procedure Instantiate_Subprogram_Body
(N : Node_Id;
Act_Decl : Node_Id)
is
Loc : constant Source_Ptr := Sloc (N);
Gen_Unit : constant Entity_Id := Entity (Name (N));
Gen_Decl : constant Node_Id := Get_Declaration_Node (Gen_Unit);
Act_Decl_Id : constant Entity_Id :=
Defining_Unit_Name (Specification (Act_Decl));
Gen_Body : Node_Id;
Gen_Body_Id : Node_Id;
Act_Body : Node_Id;
Act_Body_Id : Entity_Id;
Pack_Id : Entity_Id := Defining_Unit_Name (Parent (Act_Decl));
Pack_Body : Node_Id;
Unit_Renaming : Node_Id;
Save_Instantiated_Parent : Entity_Id;
Save_Exchanged_Views : Elist_Id;
begin
Gen_Body_Id := Corresponding_Body (Gen_Decl);
if No (Gen_Body_Id) then
Load_Parent_Of_Generic (N, Specification (Gen_Decl));
Gen_Body_Id := Corresponding_Body (Gen_Decl);
end if;
if Present (Gen_Body_Id) then
Save_Exchanged_Views := Exchanged_Views;
Exchanged_Views := New_Elmt_List;
Save_Instantiated_Parent := Current_Instantiated_Parent;
Current_Instantiated_Parent := Gen_Unit;
Gen_Body := Get_Declaration_Node (Gen_Body_Id);
Act_Body := Copy_Generic_Node
(Original_Node (Gen_Body), Empty, Instantiating => True);
Act_Body_Id := Defining_Unit_Simple_Name (Specification (Act_Body));
Set_Chars (Act_Body_Id, Chars (Act_Decl_Id));
Set_Corresponding_Spec (Act_Body, Act_Decl_Id);
Check_Generic_Actuals (Pack_Id);
-- Inside its body, a reference to the generic unit is a reference
-- to the instance. The corresponding renaming is the first
-- declaration in the body.
Unit_Renaming :=
Make_Subprogram_Renaming_Declaration (Loc,
Specification =>
Copy_Generic_Node (
Specification (Original_Node (Gen_Body)),
Empty,
Instantiating => True),
Name => New_Occurrence_Of (Act_Decl_Id, Loc));
-- 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),
Declarations => New_List (Unit_Renaming, Act_Body));
Set_Corresponding_Spec (Pack_Body, Pack_Id);
-- If the instantiation is a library unit, then build
-- the resulting compilation unit nodes for the instance
-- The declaration of the enclosing package is the grandparent
-- of the subprogram declaration. First replace the instantiation
-- node as the unit of the corresponding compilation.
if Nkind (Parent (N)) = N_Compilation_Unit then
Set_Unit (Parent (N), N);
Build_Instance_Compilation_Unit_Nodes (N, Pack_Body,
Parent (Parent (Act_Decl)));
-- If the instantiation is not a library unit, then place the
-- body either at the instantiation node, or after the generic
-- body itself.
else
Install_Body (Pack_Body, N, Gen_Body, Gen_Decl);
end if;
Analyze (Pack_Body);
Inherit_Context (Gen_Body, N);
Current_Instantiated_Parent := Save_Instantiated_Parent;
Restore_Private_Views (Pack_Id, False);
Exchanged_Views := Save_Exchanged_Views;
else
-- Body not found. Error was emitted already.
null;
end if;
end Instantiate_Subprogram_Body;
------------------
-- Install_Body --
------------------
procedure Install_Body
(Act_Body : Node_Id;
N : Node_Id;
Gen_Body : Node_Id;
Gen_Decl : Node_Id)
is
Act_Unit : constant Node_Id :=
Unit (Cunit (Get_Sloc_Unit_Number (Sloc (N))));
Gen_Unit : constant Node_Id :=
Unit (Cunit (Get_Sloc_Unit_Number (Sloc (Gen_Decl))));
Body_Unit : constant Node_Id :=
Unit (Cunit (Get_Sloc_Unit_Number (Sloc (Gen_Body))));
function True_Sloc (N : Node_Id) return Source_Ptr;
-- If the instance is nested inside a generic unit, the Sloc of the
-- instance indicates the place of the original definition, not the
-- 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.
function True_Sloc (N : Node_Id) return Source_Ptr is
Res : Source_Ptr;
N1 : Node_Id;
begin
Res := Sloc (N);
N1 := N;
while Present (N1) and then N1 /= Act_Unit loop
if Sloc (N1) > Res then
Res := Sloc (N1);
end if;
N1 := Parent (N1);
end loop;
return Res;
end True_Sloc;
-- Start of processing for Install_Body
begin
-- 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.
if Gen_Unit = Act_Unit
and then ((Nkind (Gen_Unit) = N_Package_Declaration)
or else Nkind (Gen_Unit) = N_Generic_Package_Declaration
or else (Gen_Unit = Body_Unit
and then True_Sloc (N) < Sloc (Gen_Body)))
then
Insert_After (Gen_Body, Act_Body);
else
Insert_Before (N, Act_Body);
end if;
Mark_Rewrite_Insertion (Act_Body);
end Install_Body;
--------------------
-- Install_Parent --
--------------------
procedure Install_Parent (P : Entity_Id) is
S : Entity_Id := Current_Scope;
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.
New_Scope (P);
Set_Is_Immediately_Visible (P);
Install_Visible_Declarations (P);
Install_Private_Declarations (P);
New_Scope (S);
end Install_Parent;
-------------------
-- Remove_Parent --
-------------------
procedure Remove_Parent is
begin
-- After child instantiation is complete, remove from scope stack
-- the extra copy of the current scope, and then remove parent
-- instance.
Pop_Scope;
End_Package_Scope (Current_Scope);
end Remove_Parent;
-------------------------------------
-- Analyze_Procedure_Instantiation --
-------------------------------------
procedure Analyze_Procedure_Instantiation (N : Node_Id) is
begin
Analyze_Subprogram_Instantiation (N, E_Procedure);
end Analyze_Procedure_Instantiation;
------------------------------------
-- Analyze_Function_Instantiation --
------------------------------------
procedure Analyze_Function_Instantiation (N : Node_Id) is
begin
Analyze_Subprogram_Instantiation (N, E_Function);
end Analyze_Function_Instantiation;
------------------------------------
-- Analyze_Subprogram_Instantiation --
------------------------------------
procedure Analyze_Subprogram_Instantiation
(N : Node_Id;
K : Entity_Kind)
is
Loc : constant Source_Ptr := Sloc (N);
Actuals : constant List_Id := Generic_Associations (N);
Gen_Id : constant Node_Id := Name (N);
Act_Decl_Id : Entity_Id := New_Copy (Defining_Unit_Simple_Name (N));
Act_Decl : Node_Id;
Act_Spec : Node_Id;
Act_Tree : Node_Id;
Gen_Unit : Entity_Id;
Gen_Decl : Node_Id;
Pack_Id : Entity_Id;
Parent_Installed : Boolean := False;
Renaming_List : List_Id;
Spec : Node_Id;
Save_Exchanged_Views : Elist_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. After analysis, we reset the scope
-- of the instance to be the current one, rather than the bogus package.
procedure Analyze_Instance_And_Renamings is
Pack_Decl : Node_Id;
begin
if Nkind (Parent (N)) = N_Compilation_Unit then
-- The container package has the same name as the instantiation,
-- to insure that the binder calls the elaboration procedure
-- with the right name.
Pack_Id := Make_Defining_Identifier (Loc, Chars (Act_Decl_Id));
else
Pack_Id := Make_Defining_Identifier (Loc, New_Internal_Name ('P'));
end if;
Pack_Decl := Make_Package_Declaration (Loc,
Specification => Make_Package_Specification (Loc,
Defining_Unit_Name => Pack_Id,
Visible_Declarations => Renaming_List));
if Nkind (Parent (N)) /= N_Compilation_Unit then
Mark_Rewrite_Insertion (Pack_Decl);
Insert_Before (N, Pack_Decl);
Set_Has_Completion (Pack_Id);
else
-- 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).
Set_Unit (Parent (N), Pack_Decl);
end if;
Analyze (Pack_Decl);
Check_Formal_Packages (Pack_Id);
-- Body of the enclosing package is supplied when instantiating
-- the subprogram body, after semantic analysis is completed.
-- Insert subprogram entity into current scope, so that
-- visiblity is correct for callers. First remove subprogram
-- from visibility, so that subsequent insertion works properly.
declare
Prev : Entity_Id;
begin
Prev := First_Entity (Pack_Id);
while Present (Prev) loop
exit when Next_Entity (Prev) = Act_Decl_Id;
Prev := Next_Entity (Prev);
end loop;
if Act_Decl_Id = First_Entity (Pack_Id) then
Set_First_Entity (Pack_Id, Empty);
Set_Last_Entity (Pack_Id, Empty);
else
Set_Next_Entity (Prev, Next_Entity (Act_Decl_Id));
Set_Last_Entity (Pack_Id, Prev);
end if;
end;
if Nkind (Parent (N)) = N_Compilation_Unit then
-- Skip package as well.
Set_Name_Entity_Id
(Chars (Act_Decl_Id), Homonym (Homonym (Act_Decl_Id)));
else
declare
Prev : Entity_Id := Current_Entity (Act_Decl_Id);
begin
while Present (Prev)
and then Homonym (Prev) /= Act_Decl_Id
loop
Prev := Homonym (Prev);
end loop;
if No (Prev) then
Set_Name_Entity_Id (Chars (Act_Decl_Id),
Homonym (Act_Decl_Id));
else
Set_Homonym (Prev, Homonym (Act_Decl_Id));
end if;
end;
end if;
New_Overloaded_Entity (Act_Decl_Id);
end Analyze_Instance_And_Renamings;
-- Start of processing for Analyze_Subprogram_Instantiation
begin
-- Make node global for error reporting.
Instantiation_Node := N;
Check_Generic_Child_Unit (Gen_Id, Parent_Installed);
Gen_Unit := Entity (Gen_Id);
-- If renaming, indicate that this is instantiation of renamed unit
if Present (Renamed_Object (Gen_Unit))
and then (Ekind (Renamed_Object (Gen_Unit)) = E_Generic_Procedure
or else Ekind (Renamed_Object (Gen_Unit)) = E_Generic_Function)
then
Gen_Unit := Renamed_Object (Gen_Unit);
Set_Entity (Gen_Id, Gen_Unit);
end if;
if Etype (Gen_Unit) = Any_Type then return; end if;
-- Verify that it is a generic subprogram of the right kind.
if K = E_Procedure and then Ekind (Gen_Unit) /= E_Generic_Procedure then
Error_Msg_N
("expect name of generic procedure in instantiation", Gen_Id);
elsif K = E_Function and then Ekind (Gen_Unit) /= E_Generic_Function then
Error_Msg_N
("expect name of generic function in instantiation", Gen_Id);
elsif In_Open_Scopes (Gen_Unit) then
Error_Msg_NE
("instantiation of & within itself", N, Gen_Id);
else
Gen_Decl := Get_Declaration_Node (Gen_Unit);
Spec := Specification (Gen_Decl);
-- Initialize renamings map, for error checking.
Save_Exchanged_Views := Exchanged_Views;
Exchanged_Views := New_Elmt_List;
Generic_Renamings.Set_Last (0);
-- Copy original generic tree, to produce text for instantiation.
Act_Tree := Copy_Generic_Node
(Original_Node (Gen_Decl), Empty, Instantiating => True);
Act_Spec := Specification (Act_Tree);
Renaming_List := Analyze_Associations
(Generic_Formal_Declarations (Act_Tree),
Actuals,
Generic_Formal_Declarations (Gen_Decl));
Set_Defining_Unit_Name (Act_Spec, Act_Decl_Id);
Set_Generic_Parent (Act_Spec, Gen_Unit);
Act_Decl :=
Make_Subprogram_Declaration (Loc,
Specification => Act_Spec);
Set_Categorization_From_Following_Pragmas (Act_Decl);
Append (Act_Decl, Renaming_List);
Set_Has_Completion (Act_Decl_Id);
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.
-- Other pragmas might also be inherited ???
if Is_Intrinsic_Subprogram (Gen_Unit) then
Set_Is_Intrinsic_Subprogram (Act_Decl_Id);
if Chars (Gen_Unit) = Name_Unchecked_Conversion then
Validate_Unchecked_Conversion (N, Act_Decl_Id);
end if;
end if;
if not Is_Intrinsic_Subprogram (Act_Decl_Id) then
Inherit_Context (Gen_Decl, N);
Restore_Private_Views (Pack_Id, False);
-- If the context requires a full instantiation, mark node for
-- subsequent construction of the body.
if Is_In_Main_Unit (N)
and then (Expander_Active or Xref_Analyze)
then
Pending_Instantiations.Increment_Last;
Pending_Instantiations.Table (Pending_Instantiations.Last) :=
(N, Act_Decl);
end if;
end if;
Exchanged_Views := Save_Exchanged_Views;
-- Subject to change, pending on if other pragmas are inherited ???
Validate_Categorization_Dependency (N, Act_Decl_Id);
if Parent_Installed then
Remove_Parent;
end if;
end if;
exception
when Instantiation_Error =>
null;
end Analyze_Subprogram_Instantiation;
----------------------------
-- Load_Parent_Of_Generic --
----------------------------
procedure Load_Parent_Of_Generic (N : Entity_Id; Spec : Node_Id) is
Comp_Unit : constant Node_Id :=
Cunit (Get_Sloc_Unit_Number (Sloc (Spec)));
True_Parent : Node_Id;
Inst_Node : Node_Id;
begin
if Get_Sloc_Unit_Number (Sloc (N)) /=
Get_Sloc_Unit_Number (Sloc (Spec))
or else Nkind (Unit (Comp_Unit)) = N_Package_Declaration
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.
True_Parent := Parent (Spec);
Inst_Node := Empty;
while Present (True_Parent)
and then Nkind (True_Parent) /= N_Compilation_Unit
loop
if Nkind (True_Parent) = N_Package_Declaration
and then Nkind (Original_Node (True_Parent))
= N_Package_Instantiation
then
-- Parent is a compilation unit that is an instantiation.
-- Instantiation node has been replaced with package decl.
Inst_Node := Original_Node (True_Parent);
exit;
elsif Nkind (True_Parent) = N_Package_Declaration
and then Present (Generic_Parent (Specification (True_Parent)))
then
-- Parent is an instantiation within another specification.
-- Declaration for instance has been inserted before original
-- instantiation node. A direct link would be preferable?
Inst_Node := Next (True_Parent);
while Nkind (Inst_Node) /= N_Package_Instantiation loop
Inst_Node := Next (Inst_Node);
end loop;
exit;
else
True_Parent := Parent (True_Parent);
end if;
end loop;
if Present (Inst_Node) then
if Nkind (Parent (True_Parent)) = N_Compilation_Unit then
-- Instantiation node and declaration of instantiated package
-- were exchanged when only the declaration was needed.
-- Restore instantiation node before proceeding with body.
Set_Unit (Parent (True_Parent), Inst_Node);
end if;
-- Now complete instantiation of enclosing body.
Instantiate_Package_Body (Inst_Node, True_Parent);
else
Load_Needed_Body (Comp_Unit);
end if;
end if;
end Load_Parent_Of_Generic;
---------------------
-- Inherit_Context --
---------------------
procedure Inherit_Context (Gen_Decl : Node_Id; Inst : Node_Id) is
Current_Context : List_Id;
Current_Unit : Node_Id;
Item : Node_Id;
New_I : Node_Id;
begin
if Nkind (Parent (Gen_Decl)) = N_Compilation_Unit then
-- The inherited context is attached to the enclosing compilation
-- unit. This is either the main unit, or the declaration for the
-- main unit (in case the instantation appears within the package
-- declaration and the main unit is its body).
Current_Unit := Parent (Inst);
while Present (Current_Unit)
and then Nkind (Current_Unit) /= N_Compilation_Unit
loop
Current_Unit := Parent (Current_Unit);
end loop;
Current_Context := Context_Items (Current_Unit);
Item := First (Context_Items (Parent (Gen_Decl)));
while Present (Item) loop
if Nkind (Item) = N_With_Clause then
New_I := New_Copy (Item);
Set_Implicit_With (New_I, True);
Append (New_I, Current_Context);
end if;
Item := Next (Item);
end loop;
end if;
end Inherit_Context;
--------------------------
-- Analyze_Associations --
--------------------------
function Analyze_Associations
(Formals : List_Id;
Actuals : List_Id;
F_Copy : List_Id)
return List_Id
is
Actual : Node_Id;
Assoc : List_Id := New_List;
Formal : Node_Id;
Analyzed_Formal : Node_Id;
Match : Node_Id;
Named : Node_Id;
First_Named : Node_Id := Empty;
Num_Matched : Int := 0;
Num_Actuals : Int := 0;
function Matching_Actual (F : Entity_Id) return Node_Id;
-- Find actual that corresponds to a given a formal parameter. If the
-- actuals are positional, return the next one, if any. If the actuals
-- are named, scan the parameter associations to find the right one.
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
-- checks on the actuals. Because semantic analysis can introduce some
-- anonymous entities or modify the declaration node itself, the
-- correspondence between the two lists is not one-one.
---------------------
-- Matching_Actual --
---------------------
function Matching_Actual (F : Entity_Id) return Node_Id is
Found : Node_Id;
begin
-- End of list of purely positional parameters
if No (Actual) then
Found := Empty;
-- Case of positional parameter correspond to current formal
elsif No (Selector_Name (Actual)) then
Found := Explicit_Generic_Actual_Parameter (Actual);
Num_Matched := Num_Matched + 1;
Actual := Next (Actual);
-- Otherwise scan list of named actuals to find the one with the
-- desired name. All remaining actuals have explicit names.
else
Found := Empty;
while Present (Actual) loop
if Chars (Selector_Name (Actual)) = Chars (F) then
Found := Explicit_Generic_Actual_Parameter (Actual);
Num_Matched := Num_Matched + 1;
exit;
end if;
Actual := Next (Actual);
end loop;
-- Reset for subsequent searches.
Actual := First_Named;
end if;
return Found;
end Matching_Actual;
-------------------------
-- Set_Analyzed_Formal --
-------------------------
procedure Set_Analyzed_Formal is
begin
while Present (Analyzed_Formal) loop
case Nkind (Formal) is
when N_Formal_Subprogram_Declaration =>
exit when Nkind (Analyzed_Formal)
= N_Formal_Subprogram_Declaration
and then Chars
(Defining_Unit_Name (Specification (Formal)))
= Chars
(Defining_Unit_Name (Specification (Analyzed_Formal)));
when N_Formal_Package_Declaration =>
exit when
Nkind (Analyzed_Formal) = N_Formal_Package_Declaration
or else
Nkind (Analyzed_Formal) = N_Generic_Package_Declaration;
when N_Use_Package_Clause | N_Use_Type_Clause => exit;
when others =>
exit when
Nkind (Analyzed_Formal) /= N_Formal_Subprogram_Declaration
and then Nkind (Analyzed_Formal) /= N_Implicit_Types
and then Chars (Defining_Identifier (Formal)) =
Chars (Defining_Identifier (Analyzed_Formal));
end case;
Analyzed_Formal := 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.
if Present (Actuals) then
First_Named := First (Actuals);
while Present (First_Named)
and then No (Selector_Name (First_Named))
loop
Num_Actuals := Num_Actuals + 1;
First_Named := Next (First_Named);
end loop;
end if;
Named := First_Named;
while Present (Named) loop
if No (Selector_Name (Named)) then
Error_Msg_N ("invalid positional actual after named one", Named);
Abandon_Instantiation (Named);
end if;
Num_Actuals := Num_Actuals + 1;
Named := Next (Named);
end loop;
if Present (Formals) then
Formal := First (Formals);
Analyzed_Formal := First (F_Copy);
if Present (Actuals) then
Actual := First (Actuals);
-- All formals should have default values
else
Actual := Empty;
end if;
while Present (Formal) loop
Set_Analyzed_Formal;
case Nkind (Formal) is
when N_Formal_Object_Declaration =>
Match := Matching_Actual (Defining_Identifier (Formal));
Append (Instantiate_Object (Formal, Match, Analyzed_Formal),
Assoc);
when N_Formal_Type_Declaration =>
Match := Matching_Actual (Defining_Identifier (Formal));
if No (Match) then
Error_Msg_NE ("missing actual for instantiation of &",
Instantiation_Node, Defining_Identifier (Formal));
Abandon_Instantiation (Instantiation_Node);
else
Analyze (Match);
Append_To (Assoc,
Instantiate_Type (Formal, Match, Analyzed_Formal));
-- Even though the internal type appears as a subtype
-- of the actual, it inherits all operations and they
-- are immediately visible. This is equivalent to a use
-- type clause on the actual.
if Is_First_Subtype (Entity (Match)) then
Append_To (Assoc,
Make_Use_Type_Clause (Sloc (Match),
Subtype_Marks => New_List (New_Occurrence_Of
(Base_Type (Entity (Match)), Sloc (Match)))));
end if;
end if;
-- A remote access-to-class-wide type must not be an
-- actual parameter for a generic formal (RM E.2.3(22))
Validate_Remote_Access_To_Class_Wide_Type (Match);
when N_Formal_Subprogram_Declaration =>
Append_To (Assoc,
Instantiate_Formal_Subprogram
(Formal,
Matching_Actual
(Defining_Unit_Name (Specification (Formal))),
Analyzed_Formal));
when N_Formal_Package_Declaration =>
Match := Matching_Actual (Defining_Identifier (Formal));
if No (Match) then
Error_Msg_NE
("missing actual for instantiation of&",
Instantiation_Node,
Defining_Identifier (Formal));
Abandon_Instantiation (Instantiation_Node);
else
Analyze (Match);
Append
(Instantiate_Formal_Package
(Formal, Match, Analyzed_Formal),
Assoc);
-- 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 have been analyzed.
if not Box_Present (Formal) then
declare
F_Pack : constant Entity_Id :=
Make_Defining_Identifier (Sloc (Match),
Chars => New_Internal_Name ('P'));
Decl : Node_Id;
begin
Decl :=
Make_Package_Instantiation (Sloc (Match),
Defining_Unit_Name => F_Pack,
Name => New_Occurrence_Of
(Entity (Name (Formal)), Sloc (Match)),
Generic_Associations =>
Generic_Associations (Formal));
Append (Decl, Assoc);
end;
end if;
end if;
when N_Use_Package_Clause =>
Append (Copy_Generic_Node (Formal, Empty, True), Assoc);
when N_Use_Type_Clause =>
Append (Copy_Generic_Node (Formal, Empty, True), Assoc);
when others => pragma Assert (False); null;
end case;
Formal := Next (Formal);
Analyzed_Formal := Next (Analyzed_Formal);
end loop;
if Num_Actuals > Num_Matched then
Error_Msg_N
("unmatched actuals in instantiation", Instantiation_Node);
end if;
elsif Present (Actuals) then
Error_Msg_N
("too many actuals in generic instantiation", Instantiation_Node);
end if;
return Assoc;
end Analyze_Associations;
-------------------------------
-- Analyze_Formal_Array_Type --
-------------------------------
procedure Analyze_Formal_Array_Type
(T : in out Entity_Id;
Def : Node_Id)
is
J : Node_Id;
begin
-- Treated like a non-generic array declaration, with
-- additional semantic checks.
Enter_Name (T);
if Nkind (Def) = N_Constrained_Array_Definition then
J := First (Discrete_Subtype_Definitions (Def));
while Present (J) loop
if Nkind (J) = N_Subtype_Indication
or else Nkind (J) = N_Range
or else Nkind (J) = N_Attribute_Reference
then
Error_Msg_N ("only a subtype mark is allowed in a formal", Def);
end if;
J := Next_Index (J);
end loop;
end if;
Array_Type_Declaration (T, Def);
if Is_Incomplete_Or_Private_Type (Component_Type (T))
and then No (Full_View (Component_Type (T)))
and then not Is_Generic_Type (Component_Type (T))
then
Error_Msg_N ("premature usage of incomplete type", Def);
elsif Is_Internal (Component_Type (T)) then
Error_Msg_N
("only a subtype mark is allowed in a formal", Def);
end if;
end Analyze_Formal_Array_Type;
----------------------------------------
-- Analyze_Formal_Decimal_Fixed_Point --
----------------------------------------
-- 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.
procedure Analyze_Formal_Decimal_Fixed_Point
(T : Entity_Id;
Def : Node_Id)
is
Loc : constant Source_Ptr := Sloc (Def);
Base : constant Entity_Id :=
New_Internal_Entity
(E_Decimal_Fixed_Point_Type,
Current_Scope, Sloc (Def), 'G');
Int_Base : constant Entity_Id := Standard_Integer;
Delta_Val : constant Ureal := Ureal_1;
Digs_Val : constant Uint := Uint_6;
begin
Note_Feature (Generic_Formal_Decimal_Types, Loc);
Enter_Name (T);
Set_Etype (Base, Base);
Set_Esize (Base, Esize (Int_Base));
Set_Alignment_Clause (Base, Alignment_Clause (Int_Base));
Set_Digits_Value (Base, Digs_Val);
Set_Delta_Value (Base, Delta_Val);
Set_Small_Value (Base, Delta_Val);
Set_Scalar_Range (Base, Scalar_Range (Int_Base));
Set_Ekind (T, E_Decimal_Fixed_Point_Subtype);
Set_Etype (T, Base);
Set_Esize (T, Esize (Int_Base));
Set_Alignment_Clause (T, Alignment_Clause (Int_Base));
Set_Digits_Value (T, Digs_Val);
Set_Delta_Value (T, Delta_Val);
Set_Small_Value (T, Delta_Val);
Set_Scalar_Range (T, Scalar_Range (Int_Base));
end Analyze_Formal_Decimal_Fixed_Point;
---------------------------------
-- Analyze_Formal_Derived_Type --
---------------------------------
procedure Analyze_Formal_Derived_Type
(N : Node_Id;
T : Entity_Id;
Def : Node_Id)
is
Loc : constant Source_Ptr := Sloc (Def);
New_N : Node_Id;
New_Def : Node_Id;
begin
Note_Feature (Generic_Formal_Derived_Types, Loc);
Set_Is_Generic_Type (T);
if Private_Present (Def) then
New_N :=
Make_Private_Extension_Declaration (Loc,
Defining_Identifier => T,
Discriminant_Specifications => Discriminant_Specifications (N),
Unknown_Discriminants_Present =>
Unknown_Discriminants_Present (N),
Subtype_Indication => Subtype_Mark (Def));
Set_Abstract_Present (New_N, Abstract_Present (Def));
else
New_N :=
Make_Full_Type_Declaration (Loc,
Defining_Identifier => T,
Discriminant_Specifications =>
Discriminant_Specifications (Parent (T)),
Type_Definition =>
Make_Derived_Type_Definition (Loc,
Subtype_Indication => Subtype_Mark (Def)));
Set_Abstract_Present
(Type_Definition (New_N), Abstract_Present (Def));
end if;
Rewrite_Substitute_Tree (N, New_N);
Analyze (N);
end Analyze_Formal_Derived_Type;
----------------------------------
-- 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.
procedure Analyze_Formal_Discrete_Type (T : Entity_Id; Def : Node_Id) is
Loc : constant Source_Ptr := Sloc (Def);
Bounds : Node_Id;
Lo : Node_Id;
Hi : Node_Id;
begin
Enter_Name (T);
Set_Ekind (T, E_Enumeration_Type);
Set_Etype (T, T);
Set_Esize (T, Uint_0);
-- 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
-- analyzed but serve as place-holders.
Lo :=
Make_Attribute_Reference (Loc,
Attribute_Name => Name_First,
Prefix => New_Reference_To (T, Loc));
Set_Etype (Lo, T);
Hi :=
Make_Attribute_Reference (Loc,
Attribute_Name => Name_Last,
Prefix => New_Reference_To (T, Loc));
Set_Etype (Hi, T);
Set_Scalar_Range (T,
Make_Range (Loc,
Low_Bound => Lo,
High_Bound => Hi));
end Analyze_Formal_Discrete_Type;
----------------------------------
-- Analyze_Formal_Floating_Type --
---------------------------------
procedure Analyze_Formal_Floating_Type (T : Entity_Id; Def : Node_Id) is
-- the various semantic attributes are taken from the predefined type
-- Float, just so that all of them are initialized. Their values are
-- never used because no constant folding or expansion takes place in
-- the generic itself.
Base : constant Entity_Id :=
New_Internal_Entity
(E_Floating_Point_Type, Current_Scope, Sloc (Def), 'G');
begin
Enter_Name (T);
Set_Ekind (T, E_Floating_Point_Subtype);
Set_Etype (T, Base);
Set_Esize (T, Esize (Standard_Float));
Set_Digits_Value (T, Digits_Value (Standard_Float));
Set_Scalar_Range (T, Scalar_Range (Standard_Float));
Set_Is_Generic_Type (Base);
Set_Etype (Base, Base);
Set_Esize (Base, Esize (Standard_Float));
Set_Digits_Value (Base, Digits_Value (Standard_Float));
Set_Scalar_Range (Base, Scalar_Range (Standard_Float));
end Analyze_Formal_Floating_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.
Analyze_Formal_Signed_Integer_Type (T, Def);
Set_Ekind (T, E_Modular_Integer_Subtype);
Set_Ekind (Etype (T), E_Modular_Integer_Type);
end Analyze_Formal_Modular_Type;
---------------------------------------
-- Analyze_Formal_Object_Declaration --
---------------------------------------
procedure Analyze_Formal_Object_Declaration (N : Node_Id) is
E : constant Node_Id := Expression (N);
Id : Node_Id;
K : Entity_Kind;
T : Node_Id;
begin
-- Determine the mode of the formal object
if Out_Present (N) then
K := E_Generic_In_Out_Parameter;
if not In_Present (N) then
Error_Msg_N ("formal generic objects cannot have mode OUT", N);
end if;
else
K := E_Generic_In_Parameter;
end if;
Find_Type (Subtype_Mark (N));
T := Entity (Subtype_Mark (N));
Id := Defining_Identifier (N);
Enter_Name (Id);
if K = E_Generic_In_Parameter then
if Is_Limited_Type (T) then
Error_Msg_N
("generic formal of mode IN must not be of limited type", N);
end if;
if Present (E) then
-- This is wrong, should set In_Default_Expression ???
Analyze (E);
Resolve (E, T);
end if;
Set_Ekind (Id, K);
Set_Etype (Id, T);
-- 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.
Set_Ekind (Id, K);
Set_Etype (Id, T);
if (Is_Array_Type (T)
and then not Is_Constrained (T))
or else
(Ekind (T) = E_Record_Type
and then Has_Discriminants (T))
then
declare
Decl : Node_Id := Build_Actual_Subtype (T, Id);
begin
Insert_Before (N, Decl);
Analyze (Decl);
Set_Actual_Subtype (Id, Defining_Identifier (Decl));
end;
else
Set_Actual_Subtype (Id, T);
end if;
if Present (E) then
Error_Msg_N
("initialization not allowed for `IN OUT` formals", N);
end if;
end if;
end Analyze_Formal_Object_Declaration;
----------------------------------------------
-- Analyze_Formal_Ordinary_Fixed_Point_Type --
----------------------------------------------
procedure Analyze_Formal_Ordinary_Fixed_Point_Type
(T : Entity_Id;
Def : Node_Id)
is
Base : constant Entity_Id :=
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.
Enter_Name (T);
Set_Ekind (T, E_Ordinary_Fixed_Point_Subtype);
Set_Etype (T, Base);
Set_Esize (T, Esize (Standard_Integer));
Set_Small_Value (T, Ureal_1);
Set_Delta_Value (T, Ureal_1);
Set_Scalar_Range (T, Scalar_Range (Standard_Integer));
Set_Is_Generic_Type (Base);
Set_Etype (Base, Base);
Set_Esize (Base, Esize (Standard_Integer));
Set_Small_Value (Base, Ureal_1);
Set_Delta_Value (Base, Ureal_1);
Set_Scalar_Range (Base, Scalar_Range (Standard_Integer));
end Analyze_Formal_Ordinary_Fixed_Point_Type;
----------------------------
-- Analyze_Formal_Package --
----------------------------
procedure Analyze_Formal_Package (N : Node_Id) is
Formal : Entity_Id := Defining_Identifier (N);
Gen_Id : constant Node_Id := Name (N);
Gen_Decl : Node_Id;
Gen_Unit : Entity_Id;
New_N : Node_Id;
Parent_Installed : Boolean := False;
begin
Note_Feature (Generic_Formal_Packages, Sloc (N));
Check_Generic_Child_Unit (Gen_Id, Parent_Installed);
Gen_Unit := Entity (Gen_Id);
if Ekind (Gen_Unit) /= E_Generic_Package then
Error_Msg_N ("expect generic package name", Gen_Id);
return;
end if;
-- 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;
-- The formal package is treated like a regular instance, but only
-- the specification needs to be instantiated, to make entities visible.
if not Box_Present (N) then
Analyze_Package_Instantiation (N);
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.
Gen_Decl := Get_Declaration_Node (Gen_Unit);
New_N := Copy_Generic_Node
(Original_Node (Gen_Decl), Empty, Instantiating => True);
Set_Defining_Unit_Name (Specification (New_N), Formal);
Rewrite_Substitute_Tree (N, New_N);
Formal := Defining_Unit_Name (Specification (N));
Enter_Name (Formal);
Set_Ekind (Formal, E_Generic_Package);
Set_Etype (Formal, Standard_Void_Type);
New_Scope (Formal);
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. Mark its generic parent.
Set_Ekind (Formal, E_Package);
Set_Generic_Parent (Specification (N), Gen_Unit);
Set_Has_Completion (Formal, True);
end if;
if Parent_Installed then
Remove_Parent;
end if;
end Analyze_Formal_Package;
---------------------------------
-- Analyze_Formal_Private_Type --
---------------------------------
procedure Analyze_Formal_Private_Type
(N : Node_Id;
T : Entity_Id;
Def : Node_Id)
is
begin
New_Private_Type (N, T, Def);
-- Set the size to an arbitrary but legal value.
Set_Esize (T, Esize (Standard_Integer));
end Analyze_Formal_Private_Type;
----------------------------------------
-- Analyze_Formal_Signed_Integer_Type --
----------------------------------------
procedure Analyze_Formal_Signed_Integer_Type
(T : Entity_Id;
Def : Node_Id)
is
Base : constant Entity_Id :=
New_Internal_Entity
(E_Signed_Integer_Type, Current_Scope, Sloc (Def), 'G');
begin
Enter_Name (T);
Set_Ekind (T, E_Signed_Integer_Subtype);
Set_Etype (T, Base);
Set_Esize (T, Esize (Standard_Integer));
Set_Scalar_Range (T, Scalar_Range (Standard_Integer));
Set_Is_Generic_Type (Base);
Set_Esize (Base, Esize (Standard_Integer));
Set_Etype (Base, Base);
Set_Scalar_Range (Base, Scalar_Range (Standard_Integer));
end Analyze_Formal_Signed_Integer_Type;
-------------------------------
-- Analyze_Formal_Subprogram --
-------------------------------
procedure Analyze_Formal_Subprogram (N : Node_Id) is
Spec : constant Node_Id := Specification (N);
Def : constant Node_Id := Default_Name (N);
Nam : constant Entity_Id := Defining_Unit_Name (Spec);
Subp : Entity_Id;
begin
Analyze_Subprogram_Declaration (N);
Set_Has_Completion (Nam);
-- Default name is resolved at the point of instantiation
if Box_Present (N) then
null;
-- Else default is bound at the point of generic declaration
elsif Present (Def) then
if Nkind (Def) = N_Operator_Symbol then
Find_Direct_Name (Def);
elsif Nkind (Def) /= N_Attribute_Reference then
Analyze (Def);
else
-- For an attribute reference, analyze the prefix. Whether the
-- attribute is legal will be determined at instantiation time.
Analyze (Prefix (Def));
return;
end if;
-- Default name may be overloaded, in which case the interpretation
-- with the correct profile must be selected, as for a renaming.
if Etype (Def) = Any_Type then
return;
elsif not Is_Overloadable (Entity (Def)) then
Error_Msg_N ("expect valid subprogram name as default", Def);
return;
elsif not Is_Overloaded (Def) then
Subp := Entity (Def);
if Subp = Nam then
Error_Msg_N ("premature usage of formal subprogram", Def);
elsif not Entity_Matches_Spec (Subp, Nam) then
Error_Msg_N ("no visible entity matches specification", Def);
end if;
else
declare
I : Interp_Index;
I1 : Interp_Index;
It : Interp;
It1 : Interp;
begin
Subp := Any_Id;
Get_First_Interp (Def, I, It);
while Present (It.Nam) loop
if Entity_Matches_Spec (It.Nam, Nam) then
if Subp /= Any_Id then
It1 := Disambiguate (Def, I1, I, Etype (Subp));
if It1 = No_Interp then
Error_Msg_N ("ambiguous default subprogram", Def);
else
Subp := It1.Nam;
end if;
exit;
else
I1 := I;
Subp := It.Nam;
end if;
end if;
Get_Next_Interp (I, It);
end loop;
end;
if Subp /= Any_Id then
Set_Entity (Def, Subp);
if Subp = Nam then
Error_Msg_N ("premature usage of formal subprogram", Def);
elsif Ekind (Subp) /= E_Operator then
Check_Mode_Conformant (Subp, Nam);
end if;
else
Error_Msg_N ("no visible subprogram matches specification", N);
end if;
end if;
end if;
end Analyze_Formal_Subprogram;
-------------------------------------
-- Analyze_Formal_Type_Declaration --
-------------------------------------
procedure Analyze_Formal_Type_Declaration (N : Node_Id) is
Def : constant Node_Id := Formal_Type_Definition (N);
T : Entity_Id;
begin
T := Defining_Identifier (N);
if Present (Discriminant_Specifications (N))
and then Nkind (Def) /= N_Formal_Private_Type_Definition
then
Error_Msg_N
("discriminants not allowed for this formal type",
Defining_Identifier (First (Discriminant_Specifications (N))));
end if;
-- Enter the new name, and branch to specific routine.
case Nkind (Def) is
when N_Formal_Private_Type_Definition
=> Analyze_Formal_Private_Type (N, T, Def);
when N_Formal_Derived_Type_Definition
=> Analyze_Formal_Derived_Type (N, T, Def);
when N_Formal_Discrete_Type_Definition
=> Analyze_Formal_Discrete_Type (T, Def);
when N_Formal_Signed_Integer_Type_Definition
=> Analyze_Formal_Signed_Integer_Type (T, Def);
when N_Formal_Modular_Type_Definition
=> Analyze_Formal_Modular_Type (T, Def);
when N_Formal_Floating_Point_Definition
=> Analyze_Formal_Floating_Type (T, Def);
when N_Formal_Ordinary_Fixed_Point_Definition
=> Analyze_Formal_Ordinary_Fixed_Point_Type (T, Def);
when N_Formal_Decimal_Fixed_Point_Definition
=> Analyze_Formal_Decimal_Fixed_Point (T, Def);
when N_Array_Type_Definition
=> Analyze_Formal_Array_Type (T, Def);
when N_Access_To_Object_Definition |
N_Access_Function_Definition |
N_Access_Procedure_Definition
=> Analyze_Generic_Access_Type (T, Def);
when others =>
pragma Assert (False); null;
end case;
Set_Is_Generic_Type (T);
end Analyze_Formal_Type_Declaration;
---------------------------------
-- Analyze_Generic_Access_Type --
---------------------------------
procedure Analyze_Generic_Access_Type (T : Entity_Id; Def : Node_Id) is
begin
Enter_Name (T);
if Nkind (Def) = N_Access_To_Object_Definition then
Access_Type_Declaration (T, Def);
if Is_Incomplete_Or_Private_Type (Designated_Type (T))
and then No (Full_View (Designated_Type (T)))
and then not Is_Generic_Type (Designated_Type (T))
then
Error_Msg_N ("premature usage of incomplete type", Def);
elsif Is_Internal (Designated_Type (T)) then
Error_Msg_N
("only a subtype mark is allowed in a formal", Def);
end if;
else
Access_Subprogram_Declaration (T, Def);
end if;
end Analyze_Generic_Access_Type;
---------------------
-- Associated_Node --
---------------------
function Associated_Node (N : Node_Id) return Node_Id is
Assoc : Node_Id := Node4 (N);
-- ??? what is Node4 being used for here?
begin
if Nkind (Assoc) /= Nkind (N) then
return Assoc;
else
-- If the node is part of an inner generic, it may itself have been
-- remapped into a further generic copy. Node4 is otherwise used for
-- the entity of the node, and will be of a different node kind, or
-- else N has been rewritten as a literal or function call.
while Present (Node4 (Assoc))
and then Nkind (Node4 (Assoc)) = Nkind (Assoc)
loop
Assoc := Node4 (Assoc);
end loop;
-- Follow and additional link in case the final node was rewritten.
-- This can only happen with nested generic units.
if (Nkind (Assoc) = N_Identifier or else Nkind (Assoc) in N_Op)
and then Present (Node4 (Assoc))
and then (Nkind (Node4 (Assoc)) = N_Function_Call
or else Nkind (Node4 (Assoc)) = N_Explicit_Dereference
or else Nkind (Node4 (Assoc)) = N_Integer_Literal
or else Nkind (Node4 (Assoc)) = N_Real_Literal
or else Nkind (Node4 (Assoc)) = N_String_Literal)
then
Assoc := Node4 (Assoc);
end if;
return Assoc;
end if;
end Associated_Node;
---------------------------------------------
-- Build_Instance_Compilation_Unit_Nodes --
---------------------------------------------
procedure Build_Instance_Compilation_Unit_Nodes
(N : Node_Id;
Act_Body : Node_Id;
Act_Decl : Node_Id)
is
Decl_Cunit : Node_Id;
Body_Cunit : Node_Id;
Citem : Node_Id;
begin
-- A new compilation unit node is built for the instance declaration
Decl_Cunit := New_Node (N_Compilation_Unit, Sloc (N));
Set_Context_Items (Decl_Cunit, Empty_List);
Set_Unit (Decl_Cunit, Act_Decl);
Set_Parent_Spec (Act_Decl, Parent_Spec (N));
Set_Body_Required (Decl_Cunit, True);
-- We use the original instantiation compilation unit as the resulting
-- compilation unit of the instance, since this is the main unit.
Rewrite_Substitute_Tree (N, Act_Body);
Body_Cunit := Parent (N);
-- The two compilation unit nodes are linked by the Library_Unit field
Set_Library_Unit (Decl_Cunit, Body_Cunit);
Set_Library_Unit (Body_Cunit, Decl_Cunit);
-- The context clause items on the instantiation, which are now
-- attached to the body compilation unit (since the body overwrote
-- the orginal 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
Append (New_Copy (Citem), Context_Items (Decl_Cunit));
Citem := Next (Citem);
end loop;
-- Make entry in Units table, so that binder can generate call to
-- elaboration procedure for body, if any.
Make_Instance_Unit (Body_Cunit);
end Build_Instance_Compilation_Unit_Nodes;
---------------------------
-- Check_Generic_Actuals --
---------------------------
-- 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) is
E : Entity_Id;
begin
E := First_Entity (Instance);
while Present (E) loop
if Nkind (Parent (E)) = N_Subtype_Declaration
and then Scope (Etype (E)) /= Instance
and then Is_Entity_Name (Subtype_Indication (Parent (E)))
then
Check_Private_View (Subtype_Indication (Parent (E)));
Set_Is_Generic_Actual_Type (E, True);
Set_Is_Private (E, False);
elsif Ekind (E) = E_Package then
-- If this is the renaming for the current instance, we're done.
-- Otherwise it is a formal package. If the corresponding formal
-- was declared with a box, the (instantiations of the) generic
-- formal part are also visible. Otherwise, ignore the entity
-- created to validate the actuals.
if Renamed_Object (E) = Instance then
exit;
elsif Nkind (Parent (E)) /= N_Package_Renaming_Declaration then
null;
elsif Box_Present (Parent (Associated_Formal_Package (E))) then
Check_Generic_Actuals (Renamed_Object (E));
end if;
end if;
E := Next_Entity (E);
end loop;
end Check_Generic_Actuals;
------------------------
-- Check_Private_View --
------------------------
procedure Check_Private_View (N : Node_Id) is
T : constant Entity_Id := Etype (N);
begin
if Present (T) then
if Is_Private_Type (T)
and then not Has_Private_View (N)
and then Present (Full_View (T))
then
-- In the generic, the full type was visible. Save the
-- private entity, for subsequent exchange.
Append_Elmt (Full_View (T), Exchanged_Views);
if Base_Type (T) /= T
and then Is_Private_Type (Base_Type (T))
then
Append_Elmt (Full_View (Base_Type (T)), Exchanged_Views);
Exchange_Declarations (Base_Type (T));
end if;
Exchange_Declarations (T);
elsif Has_Private_View (N)
and then not Is_Private_Type (T)
then
-- Only the private declaration was visible in the generic.
Append_Elmt (T, Exchanged_Views);
Exchange_Declarations (Etype (Associated_Node (N)));
end if;
end if;
end Check_Private_View;
-----------------------
-- Copy_Generic_Node --
-----------------------
function Copy_Generic_Node
(N : Node_Id;
Parent_Id : Node_Id;
Instantiating : Boolean)
return Node_Id
is
New_N : Node_Id;
function Copy_Generic_Descendant (D : Union_Id) return Union_Id;
-- Check the given value of one of the Fields referenced by the
-- current node to determine whether to copy it recursively. The
-- field may hold a Node_Id, a List_Id, or an Elist_Id, or a plain
-- value (Sloc, Uint, Char) in which case it need not be copied.
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.
function Copy_Generic_Elist (E : Elist_Id) return Elist_Id;
-- Make copy of element list.
-----------------------------
-- Copy_Generic_Descendant --
-----------------------------
function Copy_Generic_Descendant (D : Union_Id) return Union_Id is
begin
if D in Node_Range then
if D = Union_Id (Empty) then
return D;
else
return Union_Id (Copy_Generic_Node
(Node_Id (D), New_N, Instantiating));
end if;
elsif D in List_Range then
if D = Union_Id (No_List) then
return Union_Id (D);
else
return Union_Id (Copy_Generic_List (List_Id (D), New_N));
end if;
elsif D in Elist_Range then
if D = Union_Id (No_Elist) then
return Union_Id (D);
else
return Union_Id (Copy_Generic_Elist (Elist_Id (D)));
end if;
else
-- Field is not Id of copyable structure: return as is
return D;
end if;
end Copy_Generic_Descendant;
-----------------------
-- Copy_Generic_List --
-----------------------
function Copy_Generic_List
(L : List_Id;
Parent_Id : Node_Id)
return List_Id
is
N : Node_Id;
New_L : List_Id := New_List;
begin
Set_Parent (New_L, Parent_Id);
N := First (L);
while Present (N) loop
Append (Copy_Generic_Node (N, Empty, Instantiating), New_L);
N := Next (N);
end loop;
return New_L;
end Copy_Generic_List;
------------------------
-- Copy_Generic_Elist --
------------------------
function Copy_Generic_Elist (E : Elist_Id) return Elist_Id is
M : Elmt_Id;
L : Elist_Id := New_Elmt_List;
begin
M := First_Elmt (E);
while Present (M) loop
Append_Elmt
(Copy_Generic_Node (Node (M), Empty, Instantiating), L);
M := Next_Elmt (M);
end loop;
return L;
end Copy_Generic_Elist;
-- Start of processing for Copy_Generic_Node
begin
if N = Empty then
return N;
end if;
New_N := New_Copy (N);
if not Is_List_Member (N) then
Set_Parent (New_N, Parent_Id);
end if;
-- If defining identifier, then all fields have been copied already
if Nkind (New_N) in N_Entity then
null;
elsif (Nkind (New_N) = N_Identifier
or else Nkind (New_N) = N_Character_Literal
or else Nkind (New_N) = N_Expanded_Name
or else Nkind (New_N) = N_Operator_Symbol
or else Nkind (New_N) in N_Op)
then
if not Instantiating then
-- Link both nodes in order to assign subsequently the
-- entity of the copy to the original node, in case this
-- is a global reference.
Set_Associated_Node (N, New_N);
-- If we are within an instantiation, this is a nested generic
-- that has already been analyzed at the point of definition. We
-- 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.
-- 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.
if No (Current_Instantiated_Parent)
or else No (Entity (New_N))
or else
not (Nkind (Entity (New_N)) = N_Defining_Identifier
or Nkind (Entity (New_N)) = N_Defining_Character_Literal
or Nkind (Entity (New_N)) = N_Defining_Operator_Symbol)
or else No (Scope (Entity (New_N)))
or else Scope (Entity (New_N)) = Current_Instantiated_Parent
or else (Scope_Depth (Scope (Entity (New_N))) >
Scope_Depth (Current_Instantiated_Parent)
and then Get_Sloc_Unit_Number (Sloc (New_N))
= Get_Sloc_Unit_Number (Sloc (Current_Instantiated_Parent)))
then
Set_Associated_Node (New_N, Empty);
end if;
else
-- If the associated node is still defined, the entity in
-- it is global, and must be copied to the instance.
if Present (Associated_Node (N)) then
if Nkind (Associated_Node (N)) = Nkind (N) then
Set_Entity (New_N, Entity (Associated_Node (N)));
Check_Private_View (N);
elsif Nkind (Associated_Node (N)) = N_Function_Call then
-- Name resolves to a call to parameterless function.
Set_Entity (New_N, Entity (Name (Associated_Node (N))));
else
Set_Entity (New_N, Empty);
end if;
end if;
end if;
if Nkind (N) = N_Expanded_Name
or else Nkind (N) in N_Op
then
-- Complete the copy of remaining descendants.
Set_Field2 (New_N, Copy_Generic_Descendant (Field2 (N)));
Set_Field3 (New_N, Copy_Generic_Descendant (Field3 (N)));
end if;
else
-- For all remaining nodes, copy recursively their descendants.
Set_Field1 (New_N, Copy_Generic_Descendant (Field1 (N)));
Set_Field2 (New_N, Copy_Generic_Descendant (Field2 (N)));
Set_Field3 (New_N, Copy_Generic_Descendant (Field3 (N)));
Set_Field4 (New_N, Copy_Generic_Descendant (Field4 (N)));
Set_Field5 (New_N, Copy_Generic_Descendant (Field5 (N)));
if (Nkind (N) = N_Package_Body_Stub
or else Nkind (N) = N_Protected_Body_Stub
or else Nkind (N) = N_Subprogram_Body_Stub
or else Nkind (N) = N_Task_Body_Stub)
and then not Instantiating
then
-- Subunits of generic units must be loaded and analyzed at the
-- point the stubs occur. A more permissive system might defer
-- this analysis to the point of instantiation, but this seems
-- too complicated for now.
declare
Context : List_Id;
Subunit_Name : constant Unit_Name_Type := Get_Unit_Name (N);
Subunit : Node_Id;
New_Subunit : Node_Id;
Parent_Unit : Node_Id;
Unum : Unit_Number_Type;
New_Body : Node_Id;
Lib : Node_Id;
begin
Unum := Load_Unit (Subunit_Name, True, N);
Subunit := Cunit (Unum);
-- 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.
New_Body := Copy_Generic_Node (Proper_Body (Unit (Subunit)),
Empty, Instantiating => False);
-- Now place the original proper body in the original
-- generic unit.
Rewrite_Substitute_Tree (N, Proper_Body (Unit (Subunit)));
-- 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);
Inherit_Context (Unit (Subunit), N);
end;
end if;
end if;
return New_N;
end Copy_Generic_Node;
------------------------------
-- Check_Generic_Child_Unit --
------------------------------
procedure Check_Generic_Child_Unit
(Gen_Id : Node_Id;
Parent_Installed : in out Boolean)
is
Gen_Par : Entity_Id;
E : Entity_Id;
S : Node_Id;
Found : Boolean;
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 the name
-- of an instance of the parent, in which case the child unit must
-- be visible. If the instance is not in scope, it must be placed there
-- and removed after instantiation.
if Nkind (Gen_Id) = N_Selected_Component then
S := Selector_Name (Gen_Id);
Analyze (Prefix (Gen_Id));
Gen_Par := Entity (Prefix (Gen_Id));
if Ekind (Gen_Par) = E_Package
and then Nkind (Parent (Gen_Par)) = N_Package_Specification
and then Present (Generic_Parent (Parent (Gen_Par)))
then
-- The prefix denotes an instantiation. The entity itself
-- may be a nested generic, or a child unit.
E := First_Entity (Generic_Parent (Parent (Gen_Par)));
Found := False;
while Present (E) loop
if Chars (E) = Chars (S) then
Found := True;
exit;
end if;
E := Next_Entity (E);
end loop;
if Found
and then Is_Child_Unit (E)
then
Change_Selected_Component_To_Expanded_Name (Gen_Id);
Set_Entity (Gen_Id, E);
Set_Etype (Gen_Id, Etype (E));
Set_Entity (S, E);
Set_Etype (S, Etype (E));
if not In_Open_Scopes (Gen_Par) then
Install_Parent (Gen_Par);
Parent_Installed := True;
end if;
else
-- If the generic parent does not contain an entity that
-- corresponds to the selector, the instance doesn't either.
-- Analyzing the node will yield the appropriate error message.
-- If the entity is not a child unit, then it is an inner
-- generic in the parent.
Analyze (Gen_Id);
end if;
else
Analyze (Gen_Id);
end if;
else
Analyze (Gen_Id);
end if;
end Check_Generic_Child_Unit;
---------------------
-- Get_Instance_Of --
---------------------
function Get_Instance_Of (A : Entity_Id) return Entity_Id is
begin
for J in 0 .. Generic_Renamings.Last - 1 loop
if Chars (A) = Chars (Generic_Renamings.Table (J).Gen_Id) then
return Generic_Renamings.Table (J).Act_Id;
end if;
end loop;
-- On exit, entity is not instantiated: not a generic parameter,
-- or else parameter of an inner generic unit.
return A;
end Get_Instance_Of;
------------------------
-- Instantiate_Object --
------------------------
function Instantiate_Object
(Formal : Node_Id;
Actual : Node_Id;
Analyzed_Formal : Node_Id)
return Node_Id
is
Formal_Id : constant Entity_Id := Defining_Identifier (Formal);
Type_Id : constant Node_Id := Subtype_Mark (Formal);
Loc : constant Source_Ptr := Sloc (Actual);
Decl_Node : Node_Id;
begin
if Get_Instance_Of (Formal_Id) /= Formal_Id then
Error_Msg_N ("duplicate instantiation of generic parameter", Actual);
end if;
if Out_Present (Formal) then
if No (Actual) then
Error_Msg_NE
("missing actual for instantiation of &",
Instantiation_Node, Formal_Id);
Abandon_Instantiation (Instantiation_Node);
end if;
-- An IN OUT generic actual must be a name. The instantiation
-- is a renaming declaration.
Analyze (Actual);
Decl_Node :=
Make_Object_Renaming_Declaration (Loc,
Defining_Identifier => New_Copy (Formal_Id),
Subtype_Mark => New_Copy (Type_Id),
Name => New_Copy (Actual));
-- The following check is not entirely correct for the
-- (very rare) case of an overloaded actual. ???
if not Is_Variable (Actual) or else Paren_Count (Actual) > 0 then
Error_Msg_NE
("actual for& must be a variable", Actual, Formal_Id);
end if;
-- Propagate interpretations, in case actual is overloaded.
Save_Interps (Actual, Name (Decl_Node));
else
-- The instantiation of a generic formal in-parameter
-- is a constant declaration.
if Present (Actual) then
Analyze (Actual);
Decl_Node := Make_Object_Declaration (Loc,
Defining_Identifier => New_Copy (Formal_Id),
Constant_Present => True,
Object_Definition => New_Copy (Type_Id),
Expression => New_Copy (Actual));
-- Propagate interpretations, in case actual is overloaded.
Save_Interps (Actual, Expression (Decl_Node));
Freeze_Before (Instantiation_Node, Etype (Expression (Decl_Node)));
elsif Present (Expression (Formal)) then
-- Use default to construct declaration.
Decl_Node := Make_Object_Declaration (Loc,
Defining_Identifier => New_Copy (Formal_Id),
Constant_Present => True,
Object_Definition => New_Copy (Type_Id),
Expression => New_Copy (Expression (Formal)));
else
Error_Msg_NE
("missing actual for instantiation of &",
Instantiation_Node, Formal_Id);
Abandon_Instantiation (Instantiation_Node);
end if;
end if;
return Decl_Node;
end Instantiate_Object;
--------------------------------
-- Instantiate_Formal_Package --
--------------------------------
function Instantiate_Formal_Package
(Formal : Node_Id;
Actual : Node_Id;
Analyzed_Formal : Node_Id)
return Node_Id
is
Act_Pkg : Entity_Id;
Formal_Pack : Entity_Id;
Loc : constant Source_Ptr := Sloc (Actual);
Nod : Node_Id;
begin
Analyze (Actual);
if not Is_Entity_Name (Actual)
or else Ekind (Entity (Actual)) /= E_Package
then
Error_Msg_N
("expect package instance to instantiate formal", Actual);
Abandon_Instantiation (Actual);
else
Act_Pkg := Entity (Actual);
-- The actual may be a renamed package, or an outer generic
-- formal package whose instantiation is converted into a renaming.
if Present (Renamed_Object (Act_Pkg)) then
Act_Pkg := Renamed_Object (Act_Pkg);
end if;
if Nkind (Analyzed_Formal) = N_Formal_Package_Declaration then
Formal_Pack := Entity (Name (Formal));
else
Formal_Pack :=
Generic_Parent (Specification (Analyzed_Formal));
end if;
if Generic_Parent (Parent (Act_Pkg)) /= Formal_Pack then
Error_Msg_N
("expect package instance to instantiate formal", Actual);
Abandon_Instantiation (Actual);
end if;
Set_Instance_Of (Defining_Identifier (Formal), Act_Pkg);
-- If the formal F has a box, then the generic declarations are
-- visible in the generic G. In an instance of G, the corresponding
-- entities in the actual for F (which are the actuals for the
-- instantiation of the generic that F denotes) must also be made
-- visible for analysis of the current instance. On exit from the
-- current instance, those entities are made private again. If the
-- actual is currently in use, these entities are also use-visible.
if Box_Present (Formal) then
declare
E : Entity_Id := First_Entity (Act_Pkg);
begin
while Present (E)
and then E /= First_Private_Entity (Act_Pkg)
loop
Set_Is_Private (E, False);
Set_Is_Potentially_Use_Visible (E, In_Use (Act_Pkg));
E := Next_Entity (E);
end loop;
end;
end if;
Nod :=
Make_Package_Renaming_Declaration (Loc,
Defining_Unit_Name => New_Copy (Defining_Identifier (Formal)),
Name => New_Reference_To (Act_Pkg, Loc));
Set_Associated_Formal_Package (Defining_Unit_Name (Nod),
Defining_Identifier (Formal));
return Nod;
end if;
end Instantiate_Formal_Package;
---------------------------
-- Check_Formal_Packages --
---------------------------
procedure Check_Formal_Packages (P_Id : Entity_Id) is
E : Entity_Id;
Formal_P : Entity_Id;
begin
E := First_Entity (P_Id);
while Present (E) loop
if Ekind (E) = E_Package then
if Renamed_Object (E) = P_Id then
exit;
elsif Nkind (Parent (E)) /= N_Package_Renaming_Declaration then
null;
elsif not Box_Present (Parent (Associated_Formal_Package (E))) then
Formal_P := Next_Entity (E);
Check_Formal_Package_Instance
(Parent (Formal_P), Formal_P, E);
end if;
end if;
E := Next_Entity (E);
end loop;
end Check_Formal_Packages;
-----------------------------------
-- 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.
procedure Check_Formal_Package_Instance
(Actual : Node_Id;
Form_Pkg : Entity_Id;
Act_Pkg : Entity_Id)
is
E1 : Entity_Id := First_Entity (Act_Pkg);
E2 : Entity_Id := First_Entity (Form_Pkg);
Expr1 : Node_Id;
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.
procedure Check_Mismatch (B : Boolean) is
begin
if B then
Error_Msg_NE (
"actual for & in actual instance does not match formal",
Actual, E1);
end if;
end Check_Mismatch;
-- Start of processing for Check_Formal_Package_Instance
begin
while Present (E1)
and then Present (E2)
loop
exit when Ekind (E1) = E_Package
and then Renamed_Entity (E1) = Renamed_Entity (Act_Pkg);
if Is_Type (E1) then
-- Subtypes must statically match. E1 and E2 are the
-- local entities that are subtypes of the actuals.
Check_Mismatch
(not Is_Type (E2)
or else not Subtypes_Statically_Match
(Etype (E1), (Etype (E2))));
elsif Ekind (E1) = E_Constant then
-- IN parameters must denote the same static value, or
-- the same constant, or the literal null.
Expr1 := Expression (Parent (E1));
if Ekind (E2) /= E_Constant then
Check_Mismatch (True);
else
Expr2 := Expression (Parent (E2));
end if;
if Is_Static_Expression (Expr1) then
if not Is_Static_Expression (Expr2) then
Check_Mismatch (True);
elsif Is_Integer_Type (Etype (E1)) then
declare
V1 : Uint := Expr_Value (Expr1);
V2 : Uint := Expr_Value (Expr2);
begin
Check_Mismatch (V1 /= V2);
end;
elsif Is_Real_Type (Etype (E1)) then
declare
V1 : Ureal := Expr_Value_R (Expr1);
V2 : Ureal := Expr_Value_R (Expr2);
begin
Check_Mismatch (V1 /= V2);
end;
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
Check_Mismatch
(String_Equal (Strval (Expr1), Strval (Expr2)));
end if;
end if;
elsif Is_Entity_Name (Expr1) then
Check_Mismatch
(not Is_Entity_Name (Expr2)
or else Entity (Expr1) /= Entity (Expr2));
elsif Nkind (Expr1) = N_Null then
Check_Mismatch (Nkind (Expr1) /= N_Null);
else
Check_Mismatch (True);
end if;
elsif Ekind (E1) = E_Variable
or else Ekind (E1) = E_Package
then
Check_Mismatch
(Ekind (E1) /= Ekind (E2)
or else Renamed_Object (E1) /= Renamed_Object (E2));
elsif Is_Overloadable (E1) then
-- Verify that the names of the entities match.
-- What if actual is an attribute ???
Check_Mismatch
(Ekind (E2) /= Ekind (E1) or else (Alias (E1)) /= Alias (E2));
else
pragma Assert (False);
null;
end if;
E1 := Next_Entity (E1);
E2 := Next_Entity (E2);
end loop;
end Check_Formal_Package_Instance;
-----------------------------------
-- Instantiate_Formal_Subprogram --
-----------------------------------
function Instantiate_Formal_Subprogram
(Formal : Node_Id;
Actual : Node_Id;
Analyzed_Formal : Node_Id)
return Node_Id
is
Loc : Source_Ptr := Sloc (Instantiation_Node);
Formal_Sub : constant Entity_Id :=
Defining_Unit_Name (Specification (Formal));
Analyzed_S : constant Entity_Id :=
Defining_Unit_Name (Specification (Analyzed_Formal));
Decl_Node : Node_Id;
Nam : Node_Id;
New_Spec : Node_Id := New_Copy (Specification (Formal));
procedure Valid_Actual_Subprogram (Act : Node_Id);
-- Perform legality check and raise exception on failure.
procedure Valid_Actual_Subprogram (Act : Node_Id) is
begin
if not Is_Entity_Name (Act)
and then Nkind (Act) /= N_Operator_Symbol
and then Nkind (Act) /= N_Attribute_Reference
then
if Etype (Act) /= Any_Type then
Error_Msg_NE
("Expect subprogram name to instantiate &",
Instantiation_Node, Formal_Sub);
end if;
-- In any case, instantiation cannot continue.
Abandon_Instantiation (Instantiation_Node);
end if;
end Valid_Actual_Subprogram;
-- Start of processing for Instantiate_Formal_Subprogram
begin
-- 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 Present (Actual) then
Loc := Sloc (Actual);
if Nkind (Actual) = N_Operator_Symbol then
Find_Direct_Name (Actual);
elsif Nkind (Actual) /= N_Attribute_Reference then
Analyze (Actual);
end if;
Valid_Actual_Subprogram (Actual);
Nam := Actual;
elsif Present (Default_Name (Formal)) then
if Nkind (Default_Name (Formal)) /= N_Attribute_Reference then
Nam := New_Occurrence_Of (Entity (Default_Name (Formal)), Loc);
else
Nam := New_Copy (Default_Name (Formal));
Set_Sloc (Nam, Loc);
end if;
elsif Box_Present (Formal) then
-- Actual is resolved at the point of instantiation.
Nam := Make_Identifier (Loc, Chars (Formal_Sub));
else
Error_Msg_NE
("missing actual for instantiation of &",
Instantiation_Node, Formal_Sub);
Abandon_Instantiation (Instantiation_Node);
end if;
Decl_Node :=
Make_Subprogram_Renaming_Declaration (Loc,
Specification => New_Spec,
Name => Nam);
-- 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 declaration.
Set_Corresponding_Spec (Decl_Node, Analyzed_Formal);
-- 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.
Set_Instance_Of (Analyzed_S, Nam);
return Decl_Node;
end Instantiate_Formal_Subprogram;
----------------------
-- Instantiate_Type --
----------------------
function Instantiate_Type
(Formal : Node_Id;
Actual : Node_Id;
Analyzed_Formal : Node_Id)
return Node_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);
Def : constant Node_Id := Formal_Type_Definition (Formal);
Act_T : Entity_Id;
Decl_Node : Node_Id;
procedure Validate_Array_Type_Instance;
procedure Validate_Access_Subprogram_Instance;
procedure Validate_Access_Type_Instance;
procedure Validate_Derived_Type_Instance;
procedure Validate_Private_Type_Instance;
-- These procedures perform validation tests for the named case
function Subtypes_Match (Gen_T, Act_T : Entity_Id) return Boolean;
-- Check that base types are the same and that the subtypes match
-- Statically. Used in several of the above.
--------------------
-- Subtypes_Match --
--------------------
function Subtypes_Match (Gen_T, Act_T : Entity_Id) return Boolean is
T : constant Entity_Id := Get_Instance_Of (Gen_T);
begin
return (Base_Type (T) = Base_Type (Act_T)
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 (Etype (Gen_T)), Etype (Act_T)));
end Subtypes_Match;
----------------------------------
-- Validate_Array_Type_Instance --
----------------------------------
procedure Validate_Array_Type_Instance is
I1 : Node_Id;
I2 : Node_Id;
T2 : Entity_Id;
function Formal_Dimensions return Int;
-- Count number of dimensions in array type formal
function Formal_Dimensions return Int is
Num : Int := 0;
Index : Node_Id;
begin
if Nkind (Def) = N_Constrained_Array_Definition then
Index := First (Discrete_Subtype_Definitions (Def));
else
Index := First (Subtype_Marks (Def));
end if;
while Present (Index) loop
Num := Num + 1;
Index := Next_Index (Index);
end loop;
return Num;
end Formal_Dimensions;
begin
if not Is_Array_Type (Act_T) then
Error_Msg_NE
("expect array type in instantiation of &", Actual, Gen_T);
Abandon_Instantiation (Actual);
elsif Nkind (Def) = N_Constrained_Array_Definition then
if not (Is_Constrained (Act_T)) then
Error_Msg_NE
("expect constrained array in instantiation of &",
Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
else
if Is_Constrained (Act_T) then
Error_Msg_NE
("expect unconstrained array in instantiation of &",
Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
end if;
if Formal_Dimensions /= Number_Dimensions (Act_T) then
Error_Msg_NE
("dimensions of actual do not match formal &", Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
I1 := First_Index (A_Gen_T);
I2 := First_Index (Act_T);
for I in 1 .. Formal_Dimensions loop
-- If the indices of the actual were given by a subtype_mark,
-- the index was transformed into a range attribute. Retrieve
-- the original type mark for checking.
if Is_Entity_Name (Original_Node (I2)) then
T2 := Entity (Original_Node (I2));
else
T2 := Etype (I2);
end if;
if not Subtypes_Match (Etype (I1), T2) then
Error_Msg_NE
("index types of actual do not match those of formal &",
Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
I1 := Next_Index (I1);
I2 := Next_Index (I2);
end loop;
if not Subtypes_Match
(Component_Type (A_Gen_T), Component_Type (Act_T))
then
Error_Msg_NE
("component subtype of actual does not match that of formal &",
Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
end Validate_Array_Type_Instance;
-----------------------------------
-- Validate_Access_Type_Instance --
-----------------------------------
procedure Validate_Access_Type_Instance is
Desig_Type : Entity_Id := Get_Instance_Of (Designated_Type (A_Gen_T));
begin
if not Is_Access_Type (Act_T) then
Error_Msg_NE
("expect access type in instantiation of &", Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
if not Subtypes_Match
(Desig_Type, Designated_Type (Act_T))
then
Error_Msg_NE
("designated type of actual does not match that of formal &",
Actual, Gen_T);
Abandon_Instantiation (Actual);
elsif Is_Access_Type (Designated_Type (Act_T))
and then Is_Constrained (Designated_Type (Designated_Type (Act_T)))
/= Is_Constrained (Designated_Type (Desig_Type))
then
Error_Msg_NE
("designated type of actual does not match that of formal &",
Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
end Validate_Access_Type_Instance;
----------------------------------
-- Validate_Subprogram_Instance --
----------------------------------
procedure Validate_Access_Subprogram_Instance is
begin
if not Is_Access_Type (Act_T)
or else Ekind (Designated_Type (Act_T)) /= E_Subprogram_Type
then
Error_Msg_NE
("expect access type in instantiation of &", Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
end Validate_Access_Subprogram_Instance;
------------------------------------
-- Validate_Private_Type_Instance --
------------------------------------
procedure Validate_Private_Type_Instance is
Formal_Discr : Entity_Id;
Actual_Discr : Entity_Id;
Formal_Subt : Entity_Id;
begin
if Is_Limited_Type (Act_T)
and then not Is_Limited_Type (A_Gen_T)
then
Error_Msg_NE
("actual for non-limited & cannot be a limited type", Actual,
Gen_T);
Abandon_Instantiation (Actual);
elsif Is_Indefinite_Subtype (Act_T)
and then not Is_Indefinite_Subtype (A_Gen_T)
and then Ada_95
then
Error_Msg_NE
("actual for & must be a definite subtype", Actual, Gen_T);
elsif not Is_Tagged_Type (Act_T)
and then Is_Tagged_Type (A_Gen_T)
then
Error_Msg_NE
("actual for & must be a tagged type", Actual, Gen_T);
elsif Has_Discriminants (A_Gen_T) then
if not Has_Discriminants (Act_T) then
Error_Msg_NE
("actual for & must have discriminants", Actual, Gen_T);
Abandon_Instantiation (Actual);
elsif Is_Constrained (Act_T) then
Error_Msg_NE
("actual for & must be unconstrained", Actual, Gen_T);
Abandon_Instantiation (Actual);
else
Formal_Discr := First_Discriminant (A_Gen_T);
Actual_Discr := First_Discriminant (Act_T);
while Formal_Discr /= Empty loop
if Actual_Discr = Empty then
Error_Msg_NE
("discriminants on actual do not match formal",
Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
Formal_Subt := Get_Instance_Of (Etype (Formal_Discr));
if Base_Type (Formal_Subt)
/= Base_Type (Etype (Actual_Discr))
then
Error_Msg_NE
("types of actual discriminants must match formal",
Actual, Gen_T);
Abandon_Instantiation (Actual);
elsif not Subtypes_Statically_Match
(Formal_Subt, Etype (Actual_Discr))
and then Ada_95
then
Error_Msg_NE
("subtypes of actual discriminants must match formal",
Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
Formal_Discr := Next_Discriminant (Formal_Discr);
Actual_Discr := Next_Discriminant (Actual_Discr);
end loop;
if Actual_Discr /= Empty then
Error_Msg_NE
("discriminants on actual do not match formal",
Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
end if;
end if;
end Validate_Private_Type_Instance;
------------------------------------
-- Validate_Derived_Type_Instance --
------------------------------------
procedure Validate_Derived_Type_Instance is
Ancestor : Entity_Id := Get_Instance_Of (Root_Type (A_Gen_T));
begin
if not Is_Ancestor (Ancestor, Act_T) then
Error_Msg_NE
("expect type derived from & in instantiation",
Actual, Ancestor);
Abandon_Instantiation (Actual);
end if;
end Validate_Derived_Type_Instance;
-- Start of processing for Instantiate_Type
begin
if Get_Instance_Of (A_Gen_T) /= A_Gen_T then
Error_Msg_N ("duplicate instantiation of generic type", Actual);
return Error;
elsif not Is_Entity_Name (Actual)
or else not Is_Type (Entity (Actual))
then
Error_Msg_NE
("expect valid subtype mark to instantiate &", Actual, Gen_T);
Abandon_Instantiation (Actual);
else
Act_T := Entity (Actual);
if Ekind (Act_T) = E_Incomplete_Type then
if No (Underlying_Type (Act_T)) then
Error_Msg_N ("premature use of incomplete type", Actual);
else
Act_T := Full_View (Act_T);
end if;
elsif Is_Private_Type (Act_T)
and then not Is_Generic_Type (Act_T)
and then not Is_Derived_Type (Act_T)
and then No (Full_View (Root_Type (Act_T)))
then
Error_Msg_N ("premature use of private type", Actual);
elsif Has_Private_Component (Act_T) then
Error_Msg_N
("premature use of type with private component", Actual);
end if;
Set_Instance_Of (A_Gen_T, Act_T);
if not Is_Abstract (A_Gen_T)
and then Is_Abstract (Act_T)
then
Error_Msg_N
("actual of non-abstract formal cannot be abstract", Actual);
end if;
if Is_Scalar_Type (Gen_T) then
Set_Instance_Of (Etype (A_Gen_T), Etype (Act_T));
end if;
end if;
Freeze_Before (Instantiation_Node, Act_T);
case Nkind (Def) is
when N_Formal_Private_Type_Definition =>
Validate_Private_Type_Instance;
when N_Formal_Derived_Type_Definition =>
Validate_Derived_Type_Instance;
when N_Formal_Discrete_Type_Definition =>
if not Is_Discrete_Type (Act_T) then
Error_Msg_NE
("expect discrete type in instantiation of&", Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
when N_Formal_Signed_Integer_Type_Definition =>
if not Is_Signed_Integer_Type (Act_T) then
Error_Msg_NE
("expect signed integer type in instantiation of&",
Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
when N_Formal_Modular_Type_Definition =>
if not Is_Modular_Integer_Type (Act_T) then
Error_Msg_NE
("expect modular type in instantiation of &", Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
when N_Formal_Floating_Point_Definition =>
if not Is_Floating_Point_Type (Act_T) then
Error_Msg_NE
("expect float type in instantiation of &", Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
when N_Formal_Ordinary_Fixed_Point_Definition =>
if not Is_Fixed_Point_Type (Act_T) then
Error_Msg_NE
("expect fixed point type in instantiation of &",
Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
when N_Formal_Decimal_Fixed_Point_Definition =>
if not Is_Decimal_Fixed_Point_Type (Act_T) then
Error_Msg_NE
("expect decimal type in instantiation of &",
Actual, Gen_T);
Abandon_Instantiation (Actual);
end if;
when N_Array_Type_Definition =>
Validate_Array_Type_Instance;
when N_Access_To_Object_Definition =>
Validate_Access_Type_Instance;
when N_Access_Function_Definition |
N_Access_Procedure_Definition =>
Validate_Access_Subprogram_Instance;
when others =>
pragma Assert (False); null;
end case;
Decl_Node :=
Make_Subtype_Declaration (Loc,
Defining_Identifier => New_Copy (Gen_T),
Subtype_Indication => New_Reference_To (Act_T, Loc));
if Is_Private_Type (Act_T) then
Set_Has_Private_View (Subtype_Indication (Decl_Node));
end if;
return Decl_Node;
end Instantiate_Type;
-----------------------
-- Move_Freeze_Nodes --
-----------------------
procedure Move_Freeze_Nodes
(Out_Of : Entity_Id;
After : Node_Id;
L : List_Id)
is
Decl : Node_Id;
Next_Decl : Node_Id;
Next_Node : Node_Id := After;
Spec : Node_Id;
begin
if No (L) then
return;
end if;
-- First remove the freeze nodes that may appear before all other
-- declarations.
Decl := First (L);
while Present (Decl)
and then Nkind (Decl) = N_Freeze_Entity
and then Scope_Depth (Scope (Entity (Decl))) < Scope_Depth (Out_Of)
loop
Decl := Remove_Head (L);
Insert_After (Next_Node, Decl);
Set_Analyzed (Decl, False);
Next_Node := Decl;
Decl := First (L);
end loop;
-- Next scan the list of declarations and remove each freeze node that
-- appears ahead of the current node.
while Present (Decl) loop
while Present (Next (Decl))
and then Nkind (Next (Decl)) = N_Freeze_Entity
and then Scope_Depth (Scope (Entity (Next (Decl))))
< Scope_Depth (Out_Of)
loop
Next_Decl := Remove_Next (Decl);
Insert_After (Next_Node, Next_Decl);
Set_Analyzed (Next_Decl, False);
Next_Node := Next_Decl;
end loop;
-- If the declaration is a nested package or concurrent type, then
-- recurse. Nested generic packages will have been processed from the
-- inside out.
if Nkind (Decl) = N_Package_Specification then
Spec := Decl;
elsif Nkind (Decl) = N_Task_Type_Declaration then
Spec := Task_Definition (Decl);
elsif Nkind (Decl) = N_Protected_Type_Declaration then
Spec := Protected_Definition (Decl);
else
Spec := Empty;
end if;
if Present (Spec) then
Move_Freeze_Nodes (Out_Of, After, Visible_Declarations (Spec));
Move_Freeze_Nodes (Out_Of, After, Private_Declarations (Spec));
end if;
Decl := Next (Decl);
end loop;
end Move_Freeze_Nodes;
---------------------------
-- Restore_Private_Views --
---------------------------
procedure Restore_Private_Views
(Pack_Id : Entity_Id;
Is_Package : Boolean := True)
is
M : Elmt_Id;
E : Entity_Id;
begin
M := First_Elmt (Exchanged_Views);
while Present (M) loop
Exchange_Declarations (Node (M));
M := Next_Elmt (M);
end loop;
-- Make the generic formal parameters private, and make the formal
-- types into subtypes of the actuals again.
E := First_Entity (Pack_Id);
while Present (E) loop
Set_Is_Private (E, True);
if Nkind (Parent (E)) = N_Subtype_Declaration then
Set_Is_Generic_Actual_Type (E, False);
elsif Ekind (E) = E_Package then
-- The end of the renaming list is the renaming of the generic
-- package itself. If the instance is a subprogram, all entities
-- in the corresponding package are renamings. If this entity is
-- a formal package, make its own formals private as well. The
-- actual in this case is itself the renaming of an instantation.
-- If the entity is not a package renaming, it is the entity
-- created to validate formal package actuals: ignore.
if Is_Package
and then Renamed_Object (E) = Pack_Id
then
exit;
elsif Nkind (Parent (E)) /= N_Package_Renaming_Declaration then
null;
else
declare
Act_P : Entity_Id := Renamed_Object (E);
Id : Entity_Id := First_Entity (Act_P);
begin
while Present (Id)
and then Id /= First_Private_Entity (Act_P)
loop
Set_Is_Private (Id, True);
Set_Is_Potentially_Use_Visible (Id, In_Use (Act_P));
exit when Ekind (Id) = E_Package
and then Renamed_Object (Id) = Act_P;
Id := Next_Entity (Id);
end loop;
end;
null;
end if;
end if;
E := Next_Entity (E);
end loop;
end Restore_Private_Views;
----------------------------
-- Save_Global_References --
----------------------------
procedure Save_Global_References (N : Node_Id) is
Gen_Scope : Entity_Id;
E : Entity_Id;
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.
procedure Reset_Entity (N : Node_Id);
-- Save semantic information on global entity, so that it is not
-- resolved again at instantiation time.
procedure Save_Global_Descendant (D : Union_Id);
-- Apply Save_Global_References recursively to the descendents of
-- current node.
procedure Save_References (N : Node_Id);
-- This is the recursive procedure that does the work, once the
-- enclosing generic scope has been established.
---------------
-- Is_Global --
---------------
function Is_Global (E : Entity_Id) return Boolean is
Se : Entity_Id := Scope (E);
begin
if E = Gen_Scope then
return False;
elsif E = Standard_Standard then
return True;
else
while Se /= Gen_Scope loop
if Se = Standard_Standard then
return true;
else
Se := Scope (Se);
end if;
end loop;
return False;
end if;
end Is_Global;
----------------------------
-- Save_Global_Descendant --
----------------------------
procedure Save_Global_Descendant (D : Union_Id) is
N1 : Node_Id;
begin
if D in Node_Range then
if D = Union_Id (Empty) then
null;
elsif Nkind (Node_Id (D)) /= N_Compilation_Unit then
Save_References (Node_Id (D));
end if;
elsif D in List_Range then
if D = Union_Id (No_List)
or else Is_Empty_List (List_Id (D))
then
null;
else
N1 := First (List_Id (D));
while Present (N1) loop
Save_References (N1);
N1 := Next (N1);
end loop;
end if;
-- Element list or other non-node field, nothing to do
else
null;
end if;
end Save_Global_Descendant;
------------------
-- Reset_Entity --
------------------
procedure Reset_Entity (N : Node_Id) is
procedure Set_Global_Type (N : Node_Id; N2 : Node_Id);
-- The type of N2 is global to the generic unit. Save the
-- type in the generic node.
procedure Set_Global_Type (N : Node_Id; N2 : Node_Id) is
begin
Set_Etype (N, Etype (N2));
if Is_Private_Type (Etype (N)) then
Set_Has_Private_View (N);
if Present (Full_View (Etype (N2))) then
Set_Etype (N2, Full_View (Etype (N2)));
end if;
end if;
end Set_Global_Type;
-- Start of processing for Reset_Entity
begin
N2 := Associated_Node (N);
E := Entity (N2);
if Present (E) then
if Is_Global (E) then
Set_Global_Type (N, N2);
else
-- Entity is local. Mark generic node as unresolved.
-- Note that now it does not have an entity.
Set_Associated_Node (N, Empty);
Set_Etype (N, Empty);
end if;
elsif Nkind (Parent (N)) = N_Selected_Component
and then Nkind (Parent (N2)) = N_Expanded_Name
and then 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_Global_Descendant (Field2 (N));
Save_Global_Descendant (Field3 (N));
else
-- Entity is local. Reset in generic unit, so that node
-- is resolved anew at the point of instantiation.
Set_Associated_Node (N, Empty);
Set_Etype (N, Empty);
end if;
end Reset_Entity;
----------------------
-- Save_References --
----------------------
-- This is the recursive procedure that does the work, once the
-- enclosing generic scope has been established.
procedure Save_References (N : Node_Id) is
begin
if N = Empty then
null;
elsif (Nkind (N) = N_Character_Literal
or else Nkind (N) = N_Operator_Symbol)
and then Nkind (N) = Nkind (Associated_Node (N))
then
Reset_Entity (N);
elsif Nkind (N) in N_Op then
if Nkind (N) = Nkind (Associated_Node (N)) then
Reset_Entity (N);
else
-- Node may be transformed into call to a user-defined operator
N2 := Associated_Node (N);
if Nkind (N2) = N_Function_Call then
E := Entity (Name (N2));
if Present (E)
and then Is_Global (E)
then
Set_Etype (N, Etype (N2));
else
Set_Associated_Node (N, Empty);
Set_Etype (N, Empty);
end if;
elsif Nkind (N2) = N_Integer_Literal
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.
Rewrite_Substitute_Tree (N, New_Copy (N2));
Set_Analyzed (N, False);
end if;
end if;
-- Complete the check on operands.
Save_Global_Descendant (Field2 (N));
Save_Global_Descendant (Field3 (N));
elsif Nkind (N) = N_Identifier then
if Nkind (N) = Nkind (Associated_Node (N)) then
Reset_Entity (N);
else
N2 := Associated_Node (N);
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.
if Present (E)
and then Is_Global (E)
then
Set_Etype (N, Etype (N2));
else
Set_Associated_Node (N, Empty);
Set_Etype (N, Empty);
end if;
elsif Nkind (N2) = N_Integer_Literal
or else Nkind (N2) = N_Real_Literal
or else Nkind (N2) = N_String_Literal
then
-- Name resolves to named number that is constant-folded,
-- or to string literal from concatenation.
-- Perform the same replacement in generic.
Rewrite_Substitute_Tree (N, New_Copy (N2));
Set_Analyzed (N, False);
elsif Nkind (N2) = N_Explicit_Dereference then
-- Check whether entity of prefix is global.
if Present (Entity (Prefix (N2)))
and then Is_Global (Entity (Prefix (N2)))
then
Rewrite_Substitute_Tree (N, New_Copy (N2));
Set_Analyzed (N, False);
else
Set_Associated_Node (N, Empty);
Set_Etype (N, Empty);
end if;
else
null;
end if;
end if;
elsif Nkind (N) in N_Entity then
null;
else
Save_Global_Descendant (Field1 (N));
Save_Global_Descendant (Field2 (N));
Save_Global_Descendant (Field3 (N));
Save_Global_Descendant (Field4 (N));
Save_Global_Descendant (Field5 (N));
end if;
end Save_References;
begin
-- Start of processing for Save_Global_References
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.
while Is_Child_Unit (Gen_Scope)
and then Ekind (Scope (Gen_Scope)) = E_Generic_Package
loop
Gen_Scope := Scope (Gen_Scope);
end loop;
Save_References (N);
end Save_Global_References;
-------------------------
-- Set_Associated_Node --
-------------------------
procedure Set_Associated_Node
(Gen_Node : Node_Id;
Copy_Node : Node_Id)
is
begin
Set_Node4 (Gen_Node, Copy_Node);
end Set_Associated_Node;
---------------------
-- Set_Instance_Of --
---------------------
procedure Set_Instance_Of (A : Entity_Id; B : Entity_Id) is
begin
Generic_Renamings.Table (Generic_Renamings.Last) := (A, B);
Generic_Renamings.Increment_Last;
end Set_Instance_Of;
end Sem_Ch12;