blob: e7fb9d494404b161779c92ff68146669ed25504c [file] [log] [blame]
------------------------------------------------------------------------------
-- --
-- GNAT COMPILER COMPONENTS --
-- --
-- S E M _ C H 3 --
-- --
-- B o d y --
-- --
-- Copyright (C) 1992-2004, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
-- ware Foundation; either version 2, or (at your option) any later ver- --
-- 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, 59 Temple Place - Suite 330, Boston, --
-- MA 02111-1307, USA. --
-- --
-- GNAT was originally developed by the GNAT team at New York University. --
-- Extensive contributions were provided by Ada Core Technologies Inc. --
-- --
------------------------------------------------------------------------------
with Atree; use Atree;
with Checks; use Checks;
with Elists; use Elists;
with Einfo; use Einfo;
with Errout; use Errout;
with Eval_Fat; use Eval_Fat;
with Exp_Ch3; use Exp_Ch3;
with Exp_Dist; use Exp_Dist;
with Exp_Tss; use Exp_Tss;
with Exp_Util; use Exp_Util;
with Freeze; use Freeze;
with Itypes; use Itypes;
with Layout; use Layout;
with Lib; use Lib;
with Lib.Xref; use Lib.Xref;
with Namet; use Namet;
with Nmake; use Nmake;
with Opt; use Opt;
with Restrict; use Restrict;
with Rtsfind; use Rtsfind;
with Sem; use Sem;
with Sem_Case; use Sem_Case;
with Sem_Cat; use Sem_Cat;
with Sem_Ch6; use Sem_Ch6;
with Sem_Ch7; use Sem_Ch7;
with Sem_Ch8; use Sem_Ch8;
with Sem_Ch13; use Sem_Ch13;
with Sem_Disp; use Sem_Disp;
with Sem_Dist; use Sem_Dist;
with Sem_Elim; use Sem_Elim;
with Sem_Eval; use Sem_Eval;
with Sem_Mech; use Sem_Mech;
with Sem_Res; use Sem_Res;
with Sem_Smem; use Sem_Smem;
with Sem_Type; use Sem_Type;
with Sem_Util; use Sem_Util;
with Sem_Warn; use Sem_Warn;
with Stand; use Stand;
with Sinfo; use Sinfo;
with Snames; use Snames;
with Tbuild; use Tbuild;
with Ttypes; use Ttypes;
with Uintp; use Uintp;
with Urealp; use Urealp;
package body Sem_Ch3 is
-----------------------
-- Local Subprograms --
-----------------------
procedure Build_Derived_Type
(N : Node_Id;
Parent_Type : Entity_Id;
Derived_Type : Entity_Id;
Is_Completion : Boolean;
Derive_Subps : Boolean := True);
-- Create and decorate a Derived_Type given the Parent_Type entity.
-- N is the N_Full_Type_Declaration node containing the derived type
-- definition. Parent_Type is the entity for the parent type in the derived
-- type definition and Derived_Type the actual derived type. Is_Completion
-- must be set to False if Derived_Type is the N_Defining_Identifier node
-- in N (ie Derived_Type = Defining_Identifier (N)). In this case N is not
-- the completion of a private type declaration. If Is_Completion is
-- set to True, N is the completion of a private type declaration and
-- Derived_Type is different from the defining identifier inside N (i.e.
-- Derived_Type /= Defining_Identifier (N)). Derive_Subps indicates whether
-- the parent subprograms should be derived. The only case where this
-- parameter is False is when Build_Derived_Type is recursively called to
-- process an implicit derived full type for a type derived from a private
-- type (in that case the subprograms must only be derived for the private
-- view of the type).
-- ??? These flags need a bit of re-examination and re-documentation:
-- ??? are they both necessary (both seem related to the recursion)?
procedure Build_Derived_Access_Type
(N : Node_Id;
Parent_Type : Entity_Id;
Derived_Type : Entity_Id);
-- Subsidiary procedure to Build_Derived_Type. For a derived access type,
-- create an implicit base if the parent type is constrained or if the
-- subtype indication has a constraint.
procedure Build_Derived_Array_Type
(N : Node_Id;
Parent_Type : Entity_Id;
Derived_Type : Entity_Id);
-- Subsidiary procedure to Build_Derived_Type. For a derived array type,
-- create an implicit base if the parent type is constrained or if the
-- subtype indication has a constraint.
procedure Build_Derived_Concurrent_Type
(N : Node_Id;
Parent_Type : Entity_Id;
Derived_Type : Entity_Id);
-- Subsidiary procedure to Build_Derived_Type. For a derived task or pro-
-- tected type, inherit entries and protected subprograms, check legality
-- of discriminant constraints if any.
procedure Build_Derived_Enumeration_Type
(N : Node_Id;
Parent_Type : Entity_Id;
Derived_Type : Entity_Id);
-- Subsidiary procedure to Build_Derived_Type. For a derived enumeration
-- type, we must create a new list of literals. Types derived from
-- Character and Wide_Character are special-cased.
procedure Build_Derived_Numeric_Type
(N : Node_Id;
Parent_Type : Entity_Id;
Derived_Type : Entity_Id);
-- Subsidiary procedure to Build_Derived_Type. For numeric types, create
-- an anonymous base type, and propagate constraint to subtype if needed.
procedure Build_Derived_Private_Type
(N : Node_Id;
Parent_Type : Entity_Id;
Derived_Type : Entity_Id;
Is_Completion : Boolean;
Derive_Subps : Boolean := True);
-- Subsidiary procedure to Build_Derived_Type. This procedure is complex
-- because the parent may or may not have a completion, and the derivation
-- may itself be a completion.
procedure Build_Derived_Record_Type
(N : Node_Id;
Parent_Type : Entity_Id;
Derived_Type : Entity_Id;
Derive_Subps : Boolean := True);
-- Subsidiary procedure to Build_Derived_Type and
-- Analyze_Private_Extension_Declaration used for tagged and untagged
-- record types. All parameters are as in Build_Derived_Type except that
-- N, in addition to being an N_Full_Type_Declaration node, can also be an
-- N_Private_Extension_Declaration node. See the definition of this routine
-- for much more info. Derive_Subps indicates whether subprograms should
-- be derived from the parent type. The only case where Derive_Subps is
-- False is for an implicit derived full type for a type derived from a
-- private type (see Build_Derived_Type).
function Inherit_Components
(N : Node_Id;
Parent_Base : Entity_Id;
Derived_Base : Entity_Id;
Is_Tagged : Boolean;
Inherit_Discr : Boolean;
Discs : Elist_Id) return Elist_Id;
-- Called from Build_Derived_Record_Type to inherit the components of
-- Parent_Base (a base type) into the Derived_Base (the derived base type).
-- For more information on derived types and component inheritance please
-- consult the comment above the body of Build_Derived_Record_Type.
--
-- N is the original derived type declaration.
--
-- Is_Tagged is set if we are dealing with tagged types.
--
-- If Inherit_Discr is set, Derived_Base inherits its discriminants
-- from Parent_Base, otherwise no discriminants are inherited.
--
-- Discs gives the list of constraints that apply to Parent_Base in the
-- derived type declaration. If Discs is set to No_Elist, then we have
-- the following situation:
--
-- type Parent (D1..Dn : ..) is [tagged] record ...;
-- type Derived is new Parent [with ...];
--
-- which gets treated as
--
-- type Derived (D1..Dn : ..) is new Parent (D1,..,Dn) [with ...];
--
-- For untagged types the returned value is an association list. The list
-- starts from the association (Parent_Base => Derived_Base), and then it
-- contains a sequence of the associations of the form
--
-- (Old_Component => New_Component),
--
-- where Old_Component is the Entity_Id of a component in Parent_Base
-- and New_Component is the Entity_Id of the corresponding component
-- in Derived_Base. For untagged records, this association list is
-- needed when copying the record declaration for the derived base.
-- In the tagged case the value returned is irrelevant.
procedure Build_Discriminal (Discrim : Entity_Id);
-- Create the discriminal corresponding to discriminant Discrim, that is
-- the parameter corresponding to Discrim to be used in initialization
-- procedures for the type where Discrim is a discriminant. Discriminals
-- are not used during semantic analysis, and are not fully defined
-- entities until expansion. Thus they are not given a scope until
-- initialization procedures are built.
function Build_Discriminant_Constraints
(T : Entity_Id;
Def : Node_Id;
Derived_Def : Boolean := False) return Elist_Id;
-- Validate discriminant constraints, and return the list of the
-- constraints in order of discriminant declarations. T is the
-- discriminated unconstrained type. Def is the N_Subtype_Indication
-- node where the discriminants constraints for T are specified.
-- Derived_Def is True if we are building the discriminant constraints
-- in a derived type definition of the form "type D (...) is new T (xxx)".
-- In this case T is the parent type and Def is the constraint "(xxx)" on
-- T and this routine sets the Corresponding_Discriminant field of the
-- discriminants in the derived type D to point to the corresponding
-- discriminants in the parent type T.
procedure Build_Discriminated_Subtype
(T : Entity_Id;
Def_Id : Entity_Id;
Elist : Elist_Id;
Related_Nod : Node_Id;
For_Access : Boolean := False);
-- Subsidiary procedure to Constrain_Discriminated_Type and to
-- Process_Incomplete_Dependents. Given
--
-- T (a possibly discriminated base type)
-- Def_Id (a very partially built subtype for T),
--
-- the call completes Def_Id to be the appropriate E_*_Subtype.
--
-- The Elist is the list of discriminant constraints if any (it is set to
-- No_Elist if T is not a discriminated type, and to an empty list if
-- T has discriminants but there are no discriminant constraints). The
-- Related_Nod is the same as Decl_Node in Create_Constrained_Components.
-- The For_Access says whether or not this subtype is really constraining
-- an access type. That is its sole purpose is the designated type of an
-- access type -- in which case a Private_Subtype Is_For_Access_Subtype
-- is built to avoid freezing T when the access subtype is frozen.
function Build_Scalar_Bound
(Bound : Node_Id;
Par_T : Entity_Id;
Der_T : Entity_Id) return Node_Id;
-- The bounds of a derived scalar type are conversions of the bounds of
-- the parent type. Optimize the representation if the bounds are literals.
-- Needs a more complete spec--what are the parameters exactly, and what
-- exactly is the returned value, and how is Bound affected???
procedure Build_Underlying_Full_View
(N : Node_Id;
Typ : Entity_Id;
Par : Entity_Id);
-- If the completion of a private type is itself derived from a private
-- type, or if the full view of a private subtype is itself private, the
-- back-end has no way to compute the actual size of this type. We build
-- an internal subtype declaration of the proper parent type to convey
-- this information. This extra mechanism is needed because a full
-- view cannot itself have a full view (it would get clobbered during
-- view exchanges).
procedure Check_Access_Discriminant_Requires_Limited
(D : Node_Id;
Loc : Node_Id);
-- Check the restriction that the type to which an access discriminant
-- belongs must be a concurrent type or a descendant of a type with
-- the reserved word 'limited' in its declaration.
procedure Check_Delta_Expression (E : Node_Id);
-- Check that the expression represented by E is suitable for use
-- as a delta expression, i.e. it is of real type and is static.
procedure Check_Digits_Expression (E : Node_Id);
-- Check that the expression represented by E is suitable for use as
-- a digits expression, i.e. it is of integer type, positive and static.
procedure Check_Initialization (T : Entity_Id; Exp : Node_Id);
-- Validate the initialization of an object declaration. T is the
-- required type, and Exp is the initialization expression.
procedure Check_Or_Process_Discriminants
(N : Node_Id;
T : Entity_Id;
Prev : Entity_Id := Empty);
-- If T is the full declaration of an incomplete or private type, check
-- the conformance of the discriminants, otherwise process them. Prev
-- is the entity of the partial declaration, if any.
procedure Check_Real_Bound (Bound : Node_Id);
-- Check given bound for being of real type and static. If not, post an
-- appropriate message, and rewrite the bound with the real literal zero.
procedure Constant_Redeclaration
(Id : Entity_Id;
N : Node_Id;
T : out Entity_Id);
-- Various checks on legality of full declaration of deferred constant.
-- Id is the entity for the redeclaration, N is the N_Object_Declaration,
-- node. The caller has not yet set any attributes of this entity.
procedure Convert_Scalar_Bounds
(N : Node_Id;
Parent_Type : Entity_Id;
Derived_Type : Entity_Id;
Loc : Source_Ptr);
-- For derived scalar types, convert the bounds in the type definition
-- to the derived type, and complete their analysis. Given a constraint
-- of the form:
-- .. new T range Lo .. Hi;
-- Lo and Hi are analyzed and resolved with T'Base, the parent_type.
-- The bounds of the derived type (the anonymous base) are copies of
-- Lo and Hi. Finally, the bounds of the derived subtype are conversions
-- of those bounds to the derived_type, so that their typing is
-- consistent.
procedure Copy_Array_Base_Type_Attributes (T1, T2 : Entity_Id);
-- Copies attributes from array base type T2 to array base type T1.
-- Copies only attributes that apply to base types, but not subtypes.
procedure Copy_Array_Subtype_Attributes (T1, T2 : Entity_Id);
-- Copies attributes from array subtype T2 to array subtype T1. Copies
-- attributes that apply to both subtypes and base types.
procedure Create_Constrained_Components
(Subt : Entity_Id;
Decl_Node : Node_Id;
Typ : Entity_Id;
Constraints : Elist_Id);
-- Build the list of entities for a constrained discriminated record
-- subtype. If a component depends on a discriminant, replace its subtype
-- using the discriminant values in the discriminant constraint.
-- Subt is the defining identifier for the subtype whose list of
-- constrained entities we will create. Decl_Node is the type declaration
-- node where we will attach all the itypes created. Typ is the base
-- discriminated type for the subtype Subt. Constraints is the list of
-- discriminant constraints for Typ.
function Constrain_Component_Type
(Compon_Type : Entity_Id;
Constrained_Typ : Entity_Id;
Related_Node : Node_Id;
Typ : Entity_Id;
Constraints : Elist_Id) return Entity_Id;
-- Given a discriminated base type Typ, a list of discriminant constraint
-- Constraints for Typ and the type of a component of Typ, Compon_Type,
-- create and return the type corresponding to Compon_type where all
-- discriminant references are replaced with the corresponding
-- constraint. If no discriminant references occur in Compon_Typ then
-- return it as is. Constrained_Typ is the final constrained subtype to
-- which the constrained Compon_Type belongs. Related_Node is the node
-- where we will attach all the itypes created.
procedure Constrain_Access
(Def_Id : in out Entity_Id;
S : Node_Id;
Related_Nod : Node_Id);
-- Apply a list of constraints to an access type. If Def_Id is empty,
-- it is an anonymous type created for a subtype indication. In that
-- case it is created in the procedure and attached to Related_Nod.
procedure Constrain_Array
(Def_Id : in out Entity_Id;
SI : Node_Id;
Related_Nod : Node_Id;
Related_Id : Entity_Id;
Suffix : Character);
-- Apply a list of index constraints to an unconstrained array type. The
-- first parameter is the entity for the resulting subtype. A value of
-- Empty for Def_Id indicates that an implicit type must be created, but
-- creation is delayed (and must be done by this procedure) because other
-- subsidiary implicit types must be created first (which is why Def_Id
-- is an in/out parameter). The second parameter is a subtype indication
-- node for the constrained array to be created (e.g. something of the
-- form string (1 .. 10)). Related_Nod gives the place where this type
-- has to be inserted in the tree. The Related_Id and Suffix parameters
-- are used to build the associated Implicit type name.
procedure Constrain_Concurrent
(Def_Id : in out Entity_Id;
SI : Node_Id;
Related_Nod : Node_Id;
Related_Id : Entity_Id;
Suffix : Character);
-- Apply list of discriminant constraints to an unconstrained concurrent
-- type.
--
-- SI is the N_Subtype_Indication node containing the constraint and
-- the unconstrained type to constrain.
--
-- Def_Id is the entity for the resulting constrained subtype. A
-- value of Empty for Def_Id indicates that an implicit type must be
-- created, but creation is delayed (and must be done by this procedure)
-- because other subsidiary implicit types must be created first (which
-- is why Def_Id is an in/out parameter).
--
-- Related_Nod gives the place where this type has to be inserted
-- in the tree
--
-- The last two arguments are used to create its external name if needed.
function Constrain_Corresponding_Record
(Prot_Subt : Entity_Id;
Corr_Rec : Entity_Id;
Related_Nod : Node_Id;
Related_Id : Entity_Id) return Entity_Id;
-- When constraining a protected type or task type with discriminants,
-- constrain the corresponding record with the same discriminant values.
procedure Constrain_Decimal (Def_Id : Node_Id; S : Node_Id);
-- Constrain a decimal fixed point type with a digits constraint and/or a
-- range constraint, and build E_Decimal_Fixed_Point_Subtype entity.
procedure Constrain_Discriminated_Type
(Def_Id : Entity_Id;
S : Node_Id;
Related_Nod : Node_Id;
For_Access : Boolean := False);
-- Process discriminant constraints of composite type. Verify that values
-- have been provided for all discriminants, that the original type is
-- unconstrained, and that the types of the supplied expressions match
-- the discriminant types. The first three parameters are like in routine
-- Constrain_Concurrent. See Build_Discriminated_Subtype for an explanation
-- of For_Access.
procedure Constrain_Enumeration (Def_Id : Node_Id; S : Node_Id);
-- Constrain an enumeration type with a range constraint. This is
-- identical to Constrain_Integer, but for the Ekind of the
-- resulting subtype.
procedure Constrain_Float (Def_Id : Node_Id; S : Node_Id);
-- Constrain a floating point type with either a digits constraint
-- and/or a range constraint, building a E_Floating_Point_Subtype.
procedure Constrain_Index
(Index : Node_Id;
S : Node_Id;
Related_Nod : Node_Id;
Related_Id : Entity_Id;
Suffix : Character;
Suffix_Index : Nat);
-- Process an index constraint in a constrained array declaration.
-- The constraint can be a subtype name, or a range with or without
-- an explicit subtype mark. The index is the corresponding index of the
-- unconstrained array. The Related_Id and Suffix parameters are used to
-- build the associated Implicit type name.
procedure Constrain_Integer (Def_Id : Node_Id; S : Node_Id);
-- Build subtype of a signed or modular integer type.
procedure Constrain_Ordinary_Fixed (Def_Id : Node_Id; S : Node_Id);
-- Constrain an ordinary fixed point type with a range constraint, and
-- build an E_Ordinary_Fixed_Point_Subtype entity.
procedure Copy_And_Swap (Priv, Full : Entity_Id);
-- Copy the Priv entity into the entity of its full declaration
-- then swap the two entities in such a manner that the former private
-- type is now seen as a full type.
procedure Decimal_Fixed_Point_Type_Declaration
(T : Entity_Id;
Def : Node_Id);
-- Create a new decimal fixed point type, and apply the constraint to
-- obtain a subtype of this new type.
procedure Complete_Private_Subtype
(Priv : Entity_Id;
Full : Entity_Id;
Full_Base : Entity_Id;
Related_Nod : Node_Id);
-- Complete the implicit full view of a private subtype by setting
-- the appropriate semantic fields. If the full view of the parent is
-- a record type, build constrained components of subtype.
procedure Derived_Standard_Character
(N : Node_Id;
Parent_Type : Entity_Id;
Derived_Type : Entity_Id);
-- Subsidiary procedure to Build_Derived_Enumeration_Type which handles
-- derivations from types Standard.Character and Standard.Wide_Character.
procedure Derived_Type_Declaration
(T : Entity_Id;
N : Node_Id;
Is_Completion : Boolean);
-- Process a derived type declaration. This routine will invoke
-- Build_Derived_Type to process the actual derived type definition.
-- Parameters N and Is_Completion have the same meaning as in
-- Build_Derived_Type. T is the N_Defining_Identifier for the entity
-- defined in the N_Full_Type_Declaration node N, that is T is the
-- derived type.
function Find_Type_Of_Subtype_Indic (S : Node_Id) return Entity_Id;
-- Given a subtype indication S (which is really an N_Subtype_Indication
-- node or a plain N_Identifier), find the type of the subtype mark.
procedure Enumeration_Type_Declaration (T : Entity_Id; Def : Node_Id);
-- Insert each literal in symbol table, as an overloadable identifier
-- Each enumeration type is mapped into a sequence of integers, and
-- each literal is defined as a constant with integer value. If any
-- of the literals are character literals, the type is a character
-- type, which means that strings are legal aggregates for arrays of
-- components of the type.
function Expand_To_Stored_Constraint
(Typ : Entity_Id;
Constraint : Elist_Id) return Elist_Id;
-- Given a Constraint (ie a list of expressions) on the discriminants of
-- Typ, expand it into a constraint on the stored discriminants and
-- return the new list of expressions constraining the stored
-- discriminants.
function Find_Type_Of_Object
(Obj_Def : Node_Id;
Related_Nod : Node_Id) return Entity_Id;
-- Get type entity for object referenced by Obj_Def, attaching the
-- implicit types generated to Related_Nod
procedure Floating_Point_Type_Declaration (T : Entity_Id; Def : Node_Id);
-- Create a new float, and apply the constraint to obtain subtype of it
function Has_Range_Constraint (N : Node_Id) return Boolean;
-- Given an N_Subtype_Indication node N, return True if a range constraint
-- is present, either directly, or as part of a digits or delta constraint.
-- In addition, a digits constraint in the decimal case returns True, since
-- it establishes a default range if no explicit range is present.
function Is_Valid_Constraint_Kind
(T_Kind : Type_Kind;
Constraint_Kind : Node_Kind) return Boolean;
-- Returns True if it is legal to apply the given kind of constraint
-- to the given kind of type (index constraint to an array type,
-- for example).
procedure Modular_Type_Declaration (T : Entity_Id; Def : Node_Id);
-- Create new modular type. Verify that modulus is in bounds and is
-- a power of two (implementation restriction).
procedure New_Concatenation_Op (Typ : Entity_Id);
-- Create an abbreviated declaration for an operator in order to
-- materialize concatenation on array types.
procedure Ordinary_Fixed_Point_Type_Declaration
(T : Entity_Id;
Def : Node_Id);
-- Create a new ordinary fixed point type, and apply the constraint
-- to obtain subtype of it.
procedure Prepare_Private_Subtype_Completion
(Id : Entity_Id;
Related_Nod : Node_Id);
-- Id is a subtype of some private type. Creates the full declaration
-- associated with Id whenever possible, i.e. when the full declaration
-- of the base type is already known. Records each subtype into
-- Private_Dependents of the base type.
procedure Process_Incomplete_Dependents
(N : Node_Id;
Full_T : Entity_Id;
Inc_T : Entity_Id);
-- Process all entities that depend on an incomplete type. There include
-- subtypes, subprogram types that mention the incomplete type in their
-- profiles, and subprogram with access parameters that designate the
-- incomplete type.
-- Inc_T is the defining identifier of an incomplete type declaration, its
-- Ekind is E_Incomplete_Type.
--
-- N is the corresponding N_Full_Type_Declaration for Inc_T.
--
-- Full_T is N's defining identifier.
--
-- Subtypes of incomplete types with discriminants are completed when the
-- parent type is. This is simpler than private subtypes, because they can
-- only appear in the same scope, and there is no need to exchange views.
-- Similarly, access_to_subprogram types may have a parameter or a return
-- type that is an incomplete type, and that must be replaced with the
-- full type.
-- If the full type is tagged, subprogram with access parameters that
-- designated the incomplete may be primitive operations of the full type,
-- and have to be processed accordingly.
procedure Process_Real_Range_Specification (Def : Node_Id);
-- Given the type definition for a real type, this procedure processes
-- and checks the real range specification of this type definition if
-- one is present. If errors are found, error messages are posted, and
-- the Real_Range_Specification of Def is reset to Empty.
procedure Record_Type_Declaration
(T : Entity_Id;
N : Node_Id;
Prev : Entity_Id);
-- Process a record type declaration (for both untagged and tagged
-- records). Parameters T and N are exactly like in procedure
-- Derived_Type_Declaration, except that no flag Is_Completion is
-- needed for this routine. If this is the completion of an incomplete
-- type declaration, Prev is the entity of the incomplete declaration,
-- used for cross-referencing. Otherwise Prev = T.
procedure Record_Type_Definition (Def : Node_Id; Prev_T : Entity_Id);
-- This routine is used to process the actual record type definition
-- (both for untagged and tagged records). Def is a record type
-- definition node. This procedure analyzes the components in this
-- record type definition. Prev_T is the entity for the enclosing record
-- type. It is provided so that its Has_Task flag can be set if any of
-- the component have Has_Task set. If the declaration is the completion
-- of an incomplete type declaration, Prev_T is the original incomplete
-- type, whose full view is the record type.
procedure Replace_Components (Typ : Entity_Id; Decl : Node_Id);
-- Subsidiary to Build_Derived_Record_Type. For untagged records, we
-- build a copy of the declaration tree of the parent, and we create
-- independently the list of components for the derived type. Semantic
-- information uses the component entities, but record representation
-- clauses are validated on the declaration tree. This procedure replaces
-- discriminants and components in the declaration with those that have
-- been created by Inherit_Components.
procedure Set_Fixed_Range
(E : Entity_Id;
Loc : Source_Ptr;
Lo : Ureal;
Hi : Ureal);
-- Build a range node with the given bounds and set it as the Scalar_Range
-- of the given fixed-point type entity. Loc is the source location used
-- for the constructed range. See body for further details.
procedure Set_Scalar_Range_For_Subtype
(Def_Id : Entity_Id;
R : Node_Id;
Subt : Entity_Id);
-- This routine is used to set the scalar range field for a subtype
-- given Def_Id, the entity for the subtype, and R, the range expression
-- for the scalar range. Subt provides the parent subtype to be used
-- to analyze, resolve, and check the given range.
procedure Signed_Integer_Type_Declaration (T : Entity_Id; Def : Node_Id);
-- Create a new signed integer entity, and apply the constraint to obtain
-- the required first named subtype of this type.
procedure Set_Stored_Constraint_From_Discriminant_Constraint
(E : Entity_Id);
-- E is some record type. This routine computes E's Stored_Constraint
-- from its Discriminant_Constraint.
-----------------------
-- Access_Definition --
-----------------------
function Access_Definition
(Related_Nod : Node_Id;
N : Node_Id) return Entity_Id
is
Anon_Type : constant Entity_Id :=
Create_Itype (E_Anonymous_Access_Type, Related_Nod,
Scope_Id => Scope (Current_Scope));
Desig_Type : Entity_Id;
begin
if Is_Entry (Current_Scope)
and then Is_Task_Type (Etype (Scope (Current_Scope)))
then
Error_Msg_N ("task entries cannot have access parameters", N);
end if;
Find_Type (Subtype_Mark (N));
Desig_Type := Entity (Subtype_Mark (N));
Set_Directly_Designated_Type
(Anon_Type, Desig_Type);
Set_Etype (Anon_Type, Anon_Type);
Init_Size_Align (Anon_Type);
Set_Depends_On_Private (Anon_Type, Has_Private_Component (Anon_Type));
-- The anonymous access type is as public as the discriminated type or
-- subprogram that defines it. It is imported (for back-end purposes)
-- if the designated type is.
Set_Is_Public (Anon_Type, Is_Public (Scope (Anon_Type)));
-- Ada0Y (AI-50217): Propagate the attribute that indicates that the
-- designated type comes from the limited view (for back-end purposes).
Set_From_With_Type (Anon_Type, From_With_Type (Desig_Type));
-- The context is either a subprogram declaration or an access
-- discriminant, in a private or a full type declaration. In
-- the case of a subprogram, If the designated type is incomplete,
-- the operation will be a primitive operation of the full type, to
-- be updated subsequently.
if Ekind (Desig_Type) = E_Incomplete_Type
and then Is_Overloadable (Current_Scope)
then
Append_Elmt (Current_Scope, Private_Dependents (Desig_Type));
Set_Has_Delayed_Freeze (Current_Scope);
end if;
return Anon_Type;
end Access_Definition;
-----------------------------------
-- Access_Subprogram_Declaration --
-----------------------------------
procedure Access_Subprogram_Declaration
(T_Name : Entity_Id;
T_Def : Node_Id)
is
Formals : constant List_Id := Parameter_Specifications (T_Def);
Formal : Entity_Id;
Desig_Type : constant Entity_Id :=
Create_Itype (E_Subprogram_Type, Parent (T_Def));
begin
if Nkind (T_Def) = N_Access_Function_Definition then
Analyze (Subtype_Mark (T_Def));
Set_Etype (Desig_Type, Entity (Subtype_Mark (T_Def)));
if not (Is_Type (Etype (Desig_Type))) then
Error_Msg_N
("expect type in function specification", Subtype_Mark (T_Def));
end if;
else
Set_Etype (Desig_Type, Standard_Void_Type);
end if;
if Present (Formals) then
New_Scope (Desig_Type);
Process_Formals (Formals, Parent (T_Def));
-- A bit of a kludge here, End_Scope requires that the parent
-- pointer be set to something reasonable, but Itypes don't
-- have parent pointers. So we set it and then unset it ???
-- If and when Itypes have proper parent pointers to their
-- declarations, this kludge can be removed.
Set_Parent (Desig_Type, T_Name);
End_Scope;
Set_Parent (Desig_Type, Empty);
end if;
-- The return type and/or any parameter type may be incomplete. Mark
-- the subprogram_type as depending on the incomplete type, so that
-- it can be updated when the full type declaration is seen.
if Present (Formals) then
Formal := First_Formal (Desig_Type);
while Present (Formal) loop
if Ekind (Formal) /= E_In_Parameter
and then Nkind (T_Def) = N_Access_Function_Definition
then
Error_Msg_N ("functions can only have IN parameters", Formal);
end if;
if Ekind (Etype (Formal)) = E_Incomplete_Type then
Append_Elmt (Desig_Type, Private_Dependents (Etype (Formal)));
Set_Has_Delayed_Freeze (Desig_Type);
end if;
Next_Formal (Formal);
end loop;
end if;
if Ekind (Etype (Desig_Type)) = E_Incomplete_Type
and then not Has_Delayed_Freeze (Desig_Type)
then
Append_Elmt (Desig_Type, Private_Dependents (Etype (Desig_Type)));
Set_Has_Delayed_Freeze (Desig_Type);
end if;
Check_Delayed_Subprogram (Desig_Type);
if Protected_Present (T_Def) then
Set_Ekind (T_Name, E_Access_Protected_Subprogram_Type);
Set_Convention (Desig_Type, Convention_Protected);
else
Set_Ekind (T_Name, E_Access_Subprogram_Type);
end if;
Set_Etype (T_Name, T_Name);
Init_Size_Align (T_Name);
Set_Directly_Designated_Type (T_Name, Desig_Type);
Check_Restriction (No_Access_Subprograms, T_Def);
end Access_Subprogram_Declaration;
----------------------------
-- Access_Type_Declaration --
----------------------------
procedure Access_Type_Declaration (T : Entity_Id; Def : Node_Id) is
S : constant Node_Id := Subtype_Indication (Def);
P : constant Node_Id := Parent (Def);
Desig : Entity_Id;
-- Designated type
N_Desig : Entity_Id;
-- Non-limited view, when needed
begin
-- Check for permissible use of incomplete type
if Nkind (S) /= N_Subtype_Indication then
Analyze (S);
if Ekind (Root_Type (Entity (S))) = E_Incomplete_Type then
Set_Directly_Designated_Type (T, Entity (S));
else
Set_Directly_Designated_Type (T,
Process_Subtype (S, P, T, 'P'));
end if;
else
Set_Directly_Designated_Type (T,
Process_Subtype (S, P, T, 'P'));
end if;
if All_Present (Def) or Constant_Present (Def) then
Set_Ekind (T, E_General_Access_Type);
else
Set_Ekind (T, E_Access_Type);
end if;
if Base_Type (Designated_Type (T)) = T then
Error_Msg_N ("access type cannot designate itself", S);
end if;
Set_Etype (T, T);
-- If the type has appeared already in a with_type clause, it is
-- frozen and the pointer size is already set. Else, initialize.
if not From_With_Type (T) then
Init_Size_Align (T);
end if;
Set_Is_Access_Constant (T, Constant_Present (Def));
Desig := Designated_Type (T);
-- If designated type is an imported tagged type, indicate that the
-- access type is also imported, and therefore restricted in its use.
-- The access type may already be imported, so keep setting otherwise.
-- Ada0Y (AI-50217): If the non-limited view of the designated type is
-- available, use it as the designated type of the access type, so that
-- the back-end gets a usable entity.
if From_With_Type (Desig) then
Set_From_With_Type (T);
if Ekind (Desig) = E_Incomplete_Type then
N_Desig := Non_Limited_View (Desig);
elsif Ekind (Desig) = E_Class_Wide_Type then
if From_With_Type (Etype (Desig)) then
N_Desig := Non_Limited_View (Etype (Desig));
else
N_Desig := Etype (Desig);
end if;
else
null;
pragma Assert (False);
end if;
pragma Assert (Present (N_Desig));
Set_Directly_Designated_Type (T, N_Desig);
end if;
-- Note that Has_Task is always false, since the access type itself
-- is not a task type. See Einfo for more description on this point.
-- Exactly the same consideration applies to Has_Controlled_Component.
Set_Has_Task (T, False);
Set_Has_Controlled_Component (T, False);
end Access_Type_Declaration;
-----------------------------------
-- Analyze_Component_Declaration --
-----------------------------------
procedure Analyze_Component_Declaration (N : Node_Id) is
Id : constant Entity_Id := Defining_Identifier (N);
T : Entity_Id;
P : Entity_Id;
begin
Generate_Definition (Id);
Enter_Name (Id);
T := Find_Type_Of_Object (Subtype_Indication (Component_Definition (N)),
N);
-- If the subtype is a constrained subtype of the enclosing record,
-- (which must have a partial view) the back-end does not handle
-- properly the recursion. Rewrite the component declaration with
-- an explicit subtype indication, which is acceptable to Gigi. We
-- can copy the tree directly because side effects have already been
-- removed from discriminant constraints.
if Ekind (T) = E_Access_Subtype
and then Is_Entity_Name (Subtype_Indication (Component_Definition (N)))
and then Comes_From_Source (T)
and then Nkind (Parent (T)) = N_Subtype_Declaration
and then Etype (Directly_Designated_Type (T)) = Current_Scope
then
Rewrite
(Subtype_Indication (Component_Definition (N)),
New_Copy_Tree (Subtype_Indication (Parent (T))));
T := Find_Type_Of_Object
(Subtype_Indication (Component_Definition (N)), N);
end if;
-- If the component declaration includes a default expression, then we
-- check that the component is not of a limited type (RM 3.7(5)),
-- and do the special preanalysis of the expression (see section on
-- "Handling of Default and Per-Object Expressions" in the spec of
-- package Sem).
if Present (Expression (N)) then
Analyze_Per_Use_Expression (Expression (N), T);
Check_Initialization (T, Expression (N));
end if;
-- The parent type may be a private view with unknown discriminants,
-- and thus unconstrained. Regular components must be constrained.
if Is_Indefinite_Subtype (T) and then Chars (Id) /= Name_uParent then
Error_Msg_N
("unconstrained subtype in component declaration",
Subtype_Indication (Component_Definition (N)));
-- Components cannot be abstract, except for the special case of
-- the _Parent field (case of extending an abstract tagged type)
elsif Is_Abstract (T) and then Chars (Id) /= Name_uParent then
Error_Msg_N ("type of a component cannot be abstract", N);
end if;
Set_Etype (Id, T);
Set_Is_Aliased (Id, Aliased_Present (Component_Definition (N)));
-- If this component is private (or depends on a private type),
-- flag the record type to indicate that some operations are not
-- available.
P := Private_Component (T);
if Present (P) then
-- Check for circular definitions.
if P = Any_Type then
Set_Etype (Id, Any_Type);
-- There is a gap in the visibility of operations only if the
-- component type is not defined in the scope of the record type.
elsif Scope (P) = Scope (Current_Scope) then
null;
elsif Is_Limited_Type (P) then
Set_Is_Limited_Composite (Current_Scope);
else
Set_Is_Private_Composite (Current_Scope);
end if;
end if;
if P /= Any_Type
and then Is_Limited_Type (T)
and then Chars (Id) /= Name_uParent
and then Is_Tagged_Type (Current_Scope)
then
if Is_Derived_Type (Current_Scope)
and then not Is_Limited_Record (Root_Type (Current_Scope))
then
Error_Msg_N
("extension of nonlimited type cannot have limited components",
N);
Explain_Limited_Type (T, N);
Set_Etype (Id, Any_Type);
Set_Is_Limited_Composite (Current_Scope, False);
elsif not Is_Derived_Type (Current_Scope)
and then not Is_Limited_Record (Current_Scope)
then
Error_Msg_N
("nonlimited tagged type cannot have limited components", N);
Explain_Limited_Type (T, N);
Set_Etype (Id, Any_Type);
Set_Is_Limited_Composite (Current_Scope, False);
end if;
end if;
Set_Original_Record_Component (Id, Id);
end Analyze_Component_Declaration;
--------------------------
-- Analyze_Declarations --
--------------------------
procedure Analyze_Declarations (L : List_Id) is
D : Node_Id;
Next_Node : Node_Id;
Freeze_From : Entity_Id := Empty;
procedure Adjust_D;
-- Adjust D not to include implicit label declarations, since these
-- have strange Sloc values that result in elaboration check problems.
-- (They have the sloc of the label as found in the source, and that
-- is ahead of the current declarative part).
--------------
-- Adjust_D --
--------------
procedure Adjust_D is
begin
while Present (Prev (D))
and then Nkind (D) = N_Implicit_Label_Declaration
loop
Prev (D);
end loop;
end Adjust_D;
-- Start of processing for Analyze_Declarations
begin
D := First (L);
while Present (D) loop
-- Complete analysis of declaration
Analyze (D);
Next_Node := Next (D);
if No (Freeze_From) then
Freeze_From := First_Entity (Current_Scope);
end if;
-- At the end of a declarative part, freeze remaining entities
-- declared in it. The end of the visible declarations of a
-- package specification is not the end of a declarative part
-- if private declarations are present. The end of a package
-- declaration is a freezing point only if it a library package.
-- A task definition or protected type definition is not a freeze
-- point either. Finally, we do not freeze entities in generic
-- scopes, because there is no code generated for them and freeze
-- nodes will be generated for the instance.
-- The end of a package instantiation is not a freeze point, but
-- for now we make it one, because the generic body is inserted
-- (currently) immediately after. Generic instantiations will not
-- be a freeze point once delayed freezing of bodies is implemented.
-- (This is needed in any case for early instantiations ???).
if No (Next_Node) then
if Nkind (Parent (L)) = N_Component_List
or else Nkind (Parent (L)) = N_Task_Definition
or else Nkind (Parent (L)) = N_Protected_Definition
then
null;
elsif Nkind (Parent (L)) /= N_Package_Specification then
if Nkind (Parent (L)) = N_Package_Body then
Freeze_From := First_Entity (Current_Scope);
end if;
Adjust_D;
Freeze_All (Freeze_From, D);
Freeze_From := Last_Entity (Current_Scope);
elsif Scope (Current_Scope) /= Standard_Standard
and then not Is_Child_Unit (Current_Scope)
and then No (Generic_Parent (Parent (L)))
then
null;
elsif L /= Visible_Declarations (Parent (L))
or else No (Private_Declarations (Parent (L)))
or else Is_Empty_List (Private_Declarations (Parent (L)))
then
Adjust_D;
Freeze_All (Freeze_From, D);
Freeze_From := Last_Entity (Current_Scope);
end if;
-- If next node is a body then freeze all types before the body.
-- An exception occurs for expander generated bodies, which can
-- be recognized by their already being analyzed. The expander
-- ensures that all types needed by these bodies have been frozen
-- but it is not necessary to freeze all types (and would be wrong
-- since it would not correspond to an RM defined freeze point).
elsif not Analyzed (Next_Node)
and then (Nkind (Next_Node) = N_Subprogram_Body
or else Nkind (Next_Node) = N_Entry_Body
or else Nkind (Next_Node) = N_Package_Body
or else Nkind (Next_Node) = N_Protected_Body
or else Nkind (Next_Node) = N_Task_Body
or else Nkind (Next_Node) in N_Body_Stub)
then
Adjust_D;
Freeze_All (Freeze_From, D);
Freeze_From := Last_Entity (Current_Scope);
end if;
D := Next_Node;
end loop;
end Analyze_Declarations;
----------------------------------
-- Analyze_Incomplete_Type_Decl --
----------------------------------
procedure Analyze_Incomplete_Type_Decl (N : Node_Id) is
F : constant Boolean := Is_Pure (Current_Scope);
T : Entity_Id;
begin
Generate_Definition (Defining_Identifier (N));
-- Process an incomplete declaration. The identifier must not have been
-- declared already in the scope. However, an incomplete declaration may
-- appear in the private part of a package, for a private type that has
-- already been declared.
-- In this case, the discriminants (if any) must match.
T := Find_Type_Name (N);
Set_Ekind (T, E_Incomplete_Type);
Init_Size_Align (T);
Set_Is_First_Subtype (T, True);
Set_Etype (T, T);
New_Scope (T);
Set_Stored_Constraint (T, No_Elist);
if Present (Discriminant_Specifications (N)) then
Process_Discriminants (N);
end if;
End_Scope;
-- If the type has discriminants, non-trivial subtypes may be
-- be declared before the full view of the type. The full views
-- of those subtypes will be built after the full view of the type.
Set_Private_Dependents (T, New_Elmt_List);
Set_Is_Pure (T, F);
end Analyze_Incomplete_Type_Decl;
-----------------------------
-- Analyze_Itype_Reference --
-----------------------------
-- Nothing to do. This node is placed in the tree only for the benefit
-- of Gigi processing, and has no effect on the semantic processing.
procedure Analyze_Itype_Reference (N : Node_Id) is
begin
pragma Assert (Is_Itype (Itype (N)));
null;
end Analyze_Itype_Reference;
--------------------------------
-- Analyze_Number_Declaration --
--------------------------------
procedure Analyze_Number_Declaration (N : Node_Id) is
Id : constant Entity_Id := Defining_Identifier (N);
E : constant Node_Id := Expression (N);
T : Entity_Id;
Index : Interp_Index;
It : Interp;
begin
Generate_Definition (Id);
Enter_Name (Id);
-- This is an optimization of a common case of an integer literal
if Nkind (E) = N_Integer_Literal then
Set_Is_Static_Expression (E, True);
Set_Etype (E, Universal_Integer);
Set_Etype (Id, Universal_Integer);
Set_Ekind (Id, E_Named_Integer);
Set_Is_Frozen (Id, True);
return;
end if;
Set_Is_Pure (Id, Is_Pure (Current_Scope));
-- Process expression, replacing error by integer zero, to avoid
-- cascaded errors or aborts further along in the processing
-- Replace Error by integer zero, which seems least likely to
-- cause cascaded errors.
if E = Error then
Rewrite (E, Make_Integer_Literal (Sloc (E), Uint_0));
Set_Error_Posted (E);
end if;
Analyze (E);
-- Verify that the expression is static and numeric. If
-- the expression is overloaded, we apply the preference
-- rule that favors root numeric types.
if not Is_Overloaded (E) then
T := Etype (E);
else
T := Any_Type;
Get_First_Interp (E, Index, It);
while Present (It.Typ) loop
if (Is_Integer_Type (It.Typ)
or else Is_Real_Type (It.Typ))
and then (Scope (Base_Type (It.Typ))) = Standard_Standard
then
if T = Any_Type then
T := It.Typ;
elsif It.Typ = Universal_Real
or else It.Typ = Universal_Integer
then
-- Choose universal interpretation over any other.
T := It.Typ;
exit;
end if;
end if;
Get_Next_Interp (Index, It);
end loop;
end if;
if Is_Integer_Type (T) then
Resolve (E, T);
Set_Etype (Id, Universal_Integer);
Set_Ekind (Id, E_Named_Integer);
elsif Is_Real_Type (T) then
-- Because the real value is converted to universal_real, this
-- is a legal context for a universal fixed expression.
if T = Universal_Fixed then
declare
Loc : constant Source_Ptr := Sloc (N);
Conv : constant Node_Id := Make_Type_Conversion (Loc,
Subtype_Mark =>
New_Occurrence_Of (Universal_Real, Loc),
Expression => Relocate_Node (E));
begin
Rewrite (E, Conv);
Analyze (E);
end;
elsif T = Any_Fixed then
Error_Msg_N ("illegal context for mixed mode operation", E);
-- Expression is of the form : universal_fixed * integer.
-- Try to resolve as universal_real.
T := Universal_Real;
Set_Etype (E, T);
end if;
Resolve (E, T);
Set_Etype (Id, Universal_Real);
Set_Ekind (Id, E_Named_Real);
else
Wrong_Type (E, Any_Numeric);
Resolve (E, T);
Set_Etype (Id, T);
Set_Ekind (Id, E_Constant);
Set_Never_Set_In_Source (Id, True);
Set_Is_True_Constant (Id, True);
return;
end if;
if Nkind (E) = N_Integer_Literal
or else Nkind (E) = N_Real_Literal
then
Set_Etype (E, Etype (Id));
end if;
if not Is_OK_Static_Expression (E) then
Flag_Non_Static_Expr
("non-static expression used in number declaration!", E);
Rewrite (E, Make_Integer_Literal (Sloc (N), 1));
Set_Etype (E, Any_Type);
end if;
end Analyze_Number_Declaration;
--------------------------------
-- Analyze_Object_Declaration --
--------------------------------
procedure Analyze_Object_Declaration (N : Node_Id) is
Loc : constant Source_Ptr := Sloc (N);
Id : constant Entity_Id := Defining_Identifier (N);
T : Entity_Id;
Act_T : Entity_Id;
E : Node_Id := Expression (N);
-- E is set to Expression (N) throughout this routine. When
-- Expression (N) is modified, E is changed accordingly.
Prev_Entity : Entity_Id := Empty;
function Build_Default_Subtype return Entity_Id;
-- If the object is limited or aliased, and if the type is unconstrained
-- and there is no expression, the discriminants cannot be modified and
-- the subtype of the object is constrained by the defaults, so it is
-- worthile building the corresponding subtype.
---------------------------
-- Build_Default_Subtype --
---------------------------
function Build_Default_Subtype return Entity_Id is
Constraints : constant List_Id := New_List;
Act : Entity_Id;
Decl : Node_Id;
Disc : Entity_Id;
begin
Disc := First_Discriminant (T);
if No (Discriminant_Default_Value (Disc)) then
return T; -- previous error.
end if;
Act := Make_Defining_Identifier (Loc, New_Internal_Name ('S'));
while Present (Disc) loop
Append (
New_Copy_Tree (
Discriminant_Default_Value (Disc)), Constraints);
Next_Discriminant (Disc);
end loop;
Decl :=
Make_Subtype_Declaration (Loc,
Defining_Identifier => Act,
Subtype_Indication =>
Make_Subtype_Indication (Loc,
Subtype_Mark => New_Occurrence_Of (T, Loc),
Constraint =>
Make_Index_Or_Discriminant_Constraint
(Loc, Constraints)));
Insert_Before (N, Decl);
Analyze (Decl);
return Act;
end Build_Default_Subtype;
-- Start of processing for Analyze_Object_Declaration
begin
-- There are three kinds of implicit types generated by an
-- object declaration:
-- 1. Those for generated by the original Object Definition
-- 2. Those generated by the Expression
-- 3. Those used to constrained the Object Definition with the
-- expression constraints when it is unconstrained
-- They must be generated in this order to avoid order of elaboration
-- issues. Thus the first step (after entering the name) is to analyze
-- the object definition.
if Constant_Present (N) then
Prev_Entity := Current_Entity_In_Scope (Id);
-- If homograph is an implicit subprogram, it is overridden by the
-- current declaration.
if Present (Prev_Entity)
and then Is_Overloadable (Prev_Entity)
and then Is_Inherited_Operation (Prev_Entity)
then
Prev_Entity := Empty;
end if;
end if;
if Present (Prev_Entity) then
Constant_Redeclaration (Id, N, T);
Generate_Reference (Prev_Entity, Id, 'c');
Set_Completion_Referenced (Id);
if Error_Posted (N) then
-- Type mismatch or illegal redeclaration, Do not analyze
-- expression to avoid cascaded errors.
T := Find_Type_Of_Object (Object_Definition (N), N);
Set_Etype (Id, T);
Set_Ekind (Id, E_Variable);
return;
end if;
-- In the normal case, enter identifier at the start to catch
-- premature usage in the initialization expression.
else
Generate_Definition (Id);
Enter_Name (Id);
T := Find_Type_Of_Object (Object_Definition (N), N);
if Error_Posted (Id) then
Set_Etype (Id, T);
Set_Ekind (Id, E_Variable);
return;
end if;
end if;
Set_Is_Pure (Id, Is_Pure (Current_Scope));
-- If deferred constant, make sure context is appropriate. We detect
-- a deferred constant as a constant declaration with no expression.
-- A deferred constant can appear in a package body if its completion
-- is by means of an interface pragma.
if Constant_Present (N)
and then No (E)
then
if not Is_Package (Current_Scope) then
Error_Msg_N
("invalid context for deferred constant declaration ('R'M 7.4)",
N);
Error_Msg_N
("\declaration requires an initialization expression",
N);
Set_Constant_Present (N, False);
-- In Ada 83, deferred constant must be of private type
elsif not Is_Private_Type (T) then
if Ada_83 and then Comes_From_Source (N) then
Error_Msg_N
("(Ada 83) deferred constant must be private type", N);
end if;
end if;
-- If not a deferred constant, then object declaration freezes its type
else
Check_Fully_Declared (T, N);
Freeze_Before (N, T);
end if;
-- If the object was created by a constrained array definition, then
-- set the link in both the anonymous base type and anonymous subtype
-- that are built to represent the array type to point to the object.
if Nkind (Object_Definition (Declaration_Node (Id))) =
N_Constrained_Array_Definition
then
Set_Related_Array_Object (T, Id);
Set_Related_Array_Object (Base_Type (T), Id);
end if;
-- Special checks for protected objects not at library level
if Is_Protected_Type (T)
and then not Is_Library_Level_Entity (Id)
then
Check_Restriction (No_Local_Protected_Objects, Id);
-- Protected objects with interrupt handlers must be at library level
if Has_Interrupt_Handler (T) then
Error_Msg_N
("interrupt object can only be declared at library level", Id);
end if;
end if;
-- The actual subtype of the object is the nominal subtype, unless
-- the nominal one is unconstrained and obtained from the expression.
Act_T := T;
-- Process initialization expression if present and not in error
if Present (E) and then E /= Error then
Analyze (E);
-- If an initialization expression is present, then we set the
-- Is_True_Constant flag. It will be reset if this is a variable
-- and it is indeed modified.
Set_Is_True_Constant (Id, True);
if not Assignment_OK (N) then
Check_Initialization (T, E);
end if;
Set_Etype (Id, T); -- may be overridden later on.
Resolve (E, T);
Check_Unset_Reference (E);
if Compile_Time_Known_Value (E) then
Set_Current_Value (Id, E);
end if;
-- Check incorrect use of dynamically tagged expressions. Note
-- the use of Is_Tagged_Type (T) which seems redundant but is in
-- fact important to avoid spurious errors due to expanded code
-- for dispatching functions over an anonymous access type
if (Is_Class_Wide_Type (Etype (E)) or else Is_Dynamically_Tagged (E))
and then Is_Tagged_Type (T)
and then not Is_Class_Wide_Type (T)
then
Error_Msg_N ("dynamically tagged expression not allowed!", E);
end if;
Apply_Scalar_Range_Check (E, T);
Apply_Static_Length_Check (E, T);
end if;
-- Abstract type is never permitted for a variable or constant.
-- Note: we inhibit this check for objects that do not come from
-- source because there is at least one case (the expansion of
-- x'class'input where x is abstract) where we legitimately
-- generate an abstract object.
if Is_Abstract (T) and then Comes_From_Source (N) then
Error_Msg_N ("type of object cannot be abstract",
Object_Definition (N));
if Is_CPP_Class (T) then
Error_Msg_NE ("\} may need a cpp_constructor",
Object_Definition (N), T);
end if;
-- Case of unconstrained type
elsif Is_Indefinite_Subtype (T) then
-- Nothing to do in deferred constant case
if Constant_Present (N) and then No (E) then
null;
-- Case of no initialization present
elsif No (E) then
if No_Initialization (N) then
null;
elsif Is_Class_Wide_Type (T) then
Error_Msg_N
("initialization required in class-wide declaration ", N);
else
Error_Msg_N
("unconstrained subtype not allowed (need initialization)",
Object_Definition (N));
end if;
-- Case of initialization present but in error. Set initial
-- expression as absent (but do not make above complaints)
elsif E = Error then
Set_Expression (N, Empty);
E := Empty;
-- Case of initialization present
else
-- Not allowed in Ada 83
if not Constant_Present (N) then
if Ada_83
and then Comes_From_Source (Object_Definition (N))
then
Error_Msg_N
("(Ada 83) unconstrained variable not allowed",
Object_Definition (N));
end if;
end if;
-- Now we constrain the variable from the initializing expression
-- If the expression is an aggregate, it has been expanded into
-- individual assignments. Retrieve the actual type from the
-- expanded construct.
if Is_Array_Type (T)
and then No_Initialization (N)
and then Nkind (Original_Node (E)) = N_Aggregate
then
Act_T := Etype (E);
else
Expand_Subtype_From_Expr (N, T, Object_Definition (N), E);
Act_T := Find_Type_Of_Object (Object_Definition (N), N);
end if;
Set_Is_Constr_Subt_For_U_Nominal (Act_T);
if Aliased_Present (N) then
Set_Is_Constr_Subt_For_UN_Aliased (Act_T);
end if;
Freeze_Before (N, Act_T);
Freeze_Before (N, T);
end if;
elsif Is_Array_Type (T)
and then No_Initialization (N)
and then Nkind (Original_Node (E)) = N_Aggregate
then
if not Is_Entity_Name (Object_Definition (N)) then
Act_T := Etype (E);
Check_Compile_Time_Size (Act_T);
if Aliased_Present (N) then
Set_Is_Constr_Subt_For_UN_Aliased (Act_T);
end if;
end if;
-- When the given object definition and the aggregate are specified
-- independently, and their lengths might differ do a length check.
-- This cannot happen if the aggregate is of the form (others =>...)
if not Is_Constrained (T) then
null;
elsif Nkind (E) = N_Raise_Constraint_Error then
-- Aggregate is statically illegal. Place back in declaration
Set_Expression (N, E);
Set_No_Initialization (N, False);
elsif T = Etype (E) then
null;
elsif Nkind (E) = N_Aggregate
and then Present (Component_Associations (E))
and then Present (Choices (First (Component_Associations (E))))
and then Nkind (First
(Choices (First (Component_Associations (E))))) = N_Others_Choice
then
null;
else
Apply_Length_Check (E, T);
end if;
elsif (Is_Limited_Record (T)
or else Is_Concurrent_Type (T))
and then not Is_Constrained (T)
and then Has_Discriminants (T)
then
Act_T := Build_Default_Subtype;
Rewrite (Object_Definition (N), New_Occurrence_Of (Act_T, Loc));
elsif not Is_Constrained (T)
and then Has_Discriminants (T)
and then Constant_Present (N)
and then Nkind (E) = N_Function_Call
then
-- The back-end has problems with constants of a discriminated type
-- with defaults, if the initial value is a function call. We
-- generate an intermediate temporary for the result of the call.
-- It is unclear why this should make it acceptable to gcc. ???
Remove_Side_Effects (E);
end if;
if T = Standard_Wide_Character
or else Root_Type (T) = Standard_Wide_String
then
Check_Restriction (No_Wide_Characters, Object_Definition (N));
end if;
-- Now establish the proper kind and type of the object
if Constant_Present (N) then
Set_Ekind (Id, E_Constant);
Set_Never_Set_In_Source (Id, True);
Set_Is_True_Constant (Id, True);
else
Set_Ekind (Id, E_Variable);
-- A variable is set as shared passive if it appears in a shared
-- passive package, and is at the outer level. This is not done
-- for entities generated during expansion, because those are
-- always manipulated locally.
if Is_Shared_Passive (Current_Scope)
and then Is_Library_Level_Entity (Id)
and then Comes_From_Source (Id)
then
Set_Is_Shared_Passive (Id);
Check_Shared_Var (Id, T, N);
end if;
-- Case of no initializing expression present. If the type is not
-- fully initialized, then we set Never_Set_In_Source, since this
-- is a case of a potentially uninitialized object. Note that we
-- do not consider access variables to be fully initialized for
-- this purpose, since it still seems dubious if someone declares
-- Note that we only do this for source declarations. If the object
-- is declared by a generated declaration, we assume that it is not
-- appropriate to generate warnings in that case.
if No (E) then
if (Is_Access_Type (T)
or else not Is_Fully_Initialized_Type (T))
and then Comes_From_Source (N)
then
Set_Never_Set_In_Source (Id);
end if;
end if;
end if;
Init_Alignment (Id);
Init_Esize (Id);
if Aliased_Present (N) then
Set_Is_Aliased (Id);
if No (E)
and then Is_Record_Type (T)
and then not Is_Constrained (T)
and then Has_Discriminants (T)
then
Set_Actual_Subtype (Id, Build_Default_Subtype);
end if;
end if;
Set_Etype (Id, Act_T);
if Has_Controlled_Component (Etype (Id))
or else Is_Controlled (Etype (Id))
then
if not Is_Library_Level_Entity (Id) then
Check_Restriction (No_Nested_Finalization, N);
else
Validate_Controlled_Object (Id);
end if;
-- Generate a warning when an initialization causes an obvious
-- ABE violation. If the init expression is a simple aggregate
-- there shouldn't be any initialize/adjust call generated. This
-- will be true as soon as aggregates are built in place when
-- possible. ??? at the moment we do not generate warnings for
-- temporaries created for those aggregates although a
-- Program_Error might be generated if compiled with -gnato
if Is_Controlled (Etype (Id))
and then Comes_From_Source (Id)
then
declare
BT : constant Entity_Id := Base_Type (Etype (Id));
Implicit_Call : Entity_Id;
pragma Warnings (Off, Implicit_Call);
-- What is this about, it is never referenced ???
function Is_Aggr (N : Node_Id) return Boolean;
-- Check that N is an aggregate
-------------
-- Is_Aggr --
-------------
function Is_Aggr (N : Node_Id) return Boolean is
begin
case Nkind (Original_Node (N)) is
when N_Aggregate | N_Extension_Aggregate =>
return True;
when N_Qualified_Expression |
N_Type_Conversion |
N_Unchecked_Type_Conversion =>
return Is_Aggr (Expression (Original_Node (N)));
when others =>
return False;
end case;
end Is_Aggr;
begin
-- If no underlying type, we already are in an error situation
-- don't try to add a warning since we do not have access
-- prim-op list.
if No (Underlying_Type (BT)) then
Implicit_Call := Empty;
-- A generic type does not have usable primitive operators.
-- Initialization calls are built for instances.
elsif Is_Generic_Type (BT) then
Implicit_Call := Empty;
-- if the init expression is not an aggregate, an adjust
-- call will be generated
elsif Present (E) and then not Is_Aggr (E) then
Implicit_Call := Find_Prim_Op (BT, Name_Adjust);
-- if no init expression and we are not in the deferred
-- constant case, an Initialize call will be generated
elsif No (E) and then not Constant_Present (N) then
Implicit_Call := Find_Prim_Op (BT, Name_Initialize);
else
Implicit_Call := Empty;
end if;
end;
end if;
end if;
if Has_Task (Etype (Id)) then
Check_Restriction (Max_Tasks, N);
if not Is_Library_Level_Entity (Id) then
Check_Restriction (No_Task_Hierarchy, N);
Check_Potentially_Blocking_Operation (N);
end if;
-- A rather specialized test. If we see two tasks being declared
-- of the same type in the same object declaration, and the task
-- has an entry with an address clause, we know that program error
-- will be raised at run-time since we can't have two tasks with
-- entries at the same address.
if Is_Task_Type (Etype (Id))
and then More_Ids (N)
then
declare
E : Entity_Id;
begin
E := First_Entity (Etype (Id));
while Present (E) loop
if Ekind (E) = E_Entry
and then Present (Get_Attribute_Definition_Clause
(E, Attribute_Address))
then
Error_Msg_N
("?more than one task with same entry address", N);
Error_Msg_N
("\?Program_Error will be raised at run time", N);
Insert_Action (N,
Make_Raise_Program_Error (Loc,
Reason => PE_Duplicated_Entry_Address));
exit;
end if;
Next_Entity (E);
end loop;
end;
end if;
end if;
-- Some simple constant-propagation: if the expression is a constant
-- string initialized with a literal, share the literal. This avoids
-- a run-time copy.
if Present (E)
and then Is_Entity_Name (E)
and then Ekind (Entity (E)) = E_Constant
and then Base_Type (Etype (E)) = Standard_String
then
declare
Val : constant Node_Id := Constant_Value (Entity (E));
begin
if Present (Val)
and then Nkind (Val) = N_String_Literal
then
Rewrite (E, New_Copy (Val));
end if;
end;
end if;
-- Another optimization: if the nominal subtype is unconstrained and
-- the expression is a function call that returns an unconstrained
-- type, rewrite the declaration as a renaming of the result of the
-- call. The exceptions below are cases where the copy is expected,
-- either by the back end (Aliased case) or by the semantics, as for
-- initializing controlled types or copying tags for classwide types.
if Present (E)
and then Nkind (E) = N_Explicit_Dereference
and then Nkind (Original_Node (E)) = N_Function_Call
and then not Is_Library_Level_Entity (Id)
and then not Is_Constrained (T)
and then not Is_Aliased (Id)
and then not Is_Class_Wide_Type (T)
and then not Is_Controlled (T)
and then not Has_Controlled_Component (Base_Type (T))
and then Expander_Active
then
Rewrite (N,
Make_Object_Renaming_Declaration (Loc,
Defining_Identifier => Id,
Subtype_Mark => New_Occurrence_Of
(Base_Type (Etype (Id)), Loc),
Name => E));
Set_Renamed_Object (Id, E);
-- Force generation of debugging information for the constant
-- and for the renamed function call.
Set_Needs_Debug_Info (Id);
Set_Needs_Debug_Info (Entity (Prefix (E)));
end if;
if Present (Prev_Entity)
and then Is_Frozen (Prev_Entity)
and then not Error_Posted (Id)
then
Error_Msg_N ("full constant declaration appears too late", N);
end if;
Check_Eliminated (Id);
end Analyze_Object_Declaration;
---------------------------
-- Analyze_Others_Choice --
---------------------------
-- Nothing to do for the others choice node itself, the semantic analysis
-- of the others choice will occur as part of the processing of the parent
procedure Analyze_Others_Choice (N : Node_Id) is
pragma Warnings (Off, N);
begin
null;
end Analyze_Others_Choice;
--------------------------------
-- Analyze_Per_Use_Expression --
--------------------------------
procedure Analyze_Per_Use_Expression (N : Node_Id; T : Entity_Id) is
Save_In_Default_Expression : constant Boolean := In_Default_Expression;
begin
In_Default_Expression := True;
Pre_Analyze_And_Resolve (N, T);
In_Default_Expression := Save_In_Default_Expression;
end Analyze_Per_Use_Expression;
-------------------------------------------
-- Analyze_Private_Extension_Declaration --
-------------------------------------------
procedure Analyze_Private_Extension_Declaration (N : Node_Id) is
T : constant Entity_Id := Defining_Identifier (N);
Indic : constant Node_Id := Subtype_Indication (N);
Parent_Type : Entity_Id;
Parent_Base : Entity_Id;
begin
Generate_Definition (T);
Enter_Name (T);
Parent_Type := Find_Type_Of_Subtype_Indic (Indic);
Parent_Base := Base_Type (Parent_Type);
if Parent_Type = Any_Type
or else Etype (Parent_Type) = Any_Type
then
Set_Ekind (T, Ekind (Parent_Type));
Set_Etype (T, Any_Type);
return;
elsif not Is_Tagged_Type (Parent_Type) then
Error_Msg_N
("parent of type extension must be a tagged type ", Indic);
return;
elsif Ekind (Parent_Type) = E_Void
or else Ekind (Parent_Type) = E_Incomplete_Type
then
Error_Msg_N ("premature derivation of incomplete type", Indic);
return;
end if;
-- Perhaps the parent type should be changed to the class-wide type's
-- specific type in this case to prevent cascading errors ???
if Is_Class_Wide_Type (Parent_Type) then
Error_Msg_N
("parent of type extension must not be a class-wide type", Indic);
return;
end if;
if (not Is_Package (Current_Scope)
and then Nkind (Parent (N)) /= N_Generic_Subprogram_Declaration)
or else In_Private_Part (Current_Scope)
then
Error_Msg_N ("invalid context for private extension", N);
end if;
-- Set common attributes
Set_Is_Pure (T, Is_Pure (Current_Scope));
Set_Scope (T, Current_Scope);
Set_Ekind (T, E_Record_Type_With_Private);
Init_Size_Align (T);
Set_Etype (T, Parent_Base);
Set_Has_Task (T, Has_Task (Parent_Base));
Set_Convention (T, Convention (Parent_Type));
Set_First_Rep_Item (T, First_Rep_Item (Parent_Type));
Set_Is_First_Subtype (T);
Make_Class_Wide_Type (T);
Build_Derived_Record_Type (N, Parent_Type, T);
end Analyze_Private_Extension_Declaration;
---------------------------------
-- Analyze_Subtype_Declaration --
---------------------------------
procedure Analyze_Subtype_Declaration (N : Node_Id) is
Id : constant Entity_Id := Defining_Identifier (N);
T : Entity_Id;
R_Checks : Check_Result;
begin
Generate_Definition (Id);
Set_Is_Pure (Id, Is_Pure (Current_Scope));
Init_Size_Align (Id);
-- The following guard condition on Enter_Name is to handle cases
-- where the defining identifier has already been entered into the
-- scope but the declaration as a whole needs to be analyzed.
-- This case in particular happens for derived enumeration types.
-- The derived enumeration type is processed as an inserted enumeration
-- type declaration followed by a rewritten subtype declaration. The
-- defining identifier, however, is entered into the name scope very
-- early in the processing of the original type declaration and
-- therefore needs to be avoided here, when the created subtype
-- declaration is analyzed. (See Build_Derived_Types)
-- This also happens when the full view of a private type is a
-- derived type with constraints. In this case the entity has been
-- introduced in the private declaration.
if Present (Etype (Id))
and then (Is_Private_Type (Etype (Id))
or else Is_Task_Type (Etype (Id))
or else Is_Rewrite_Substitution (N))
then
null;
else
Enter_Name (Id);
end if;
T := Process_Subtype (Subtype_Indication (N), N, Id, 'P');
-- Inherit common attributes
Set_Is_Generic_Type (Id, Is_Generic_Type (Base_Type (T)));
Set_Is_Volatile (Id, Is_Volatile (T));
Set_Treat_As_Volatile (Id, Treat_As_Volatile (T));
Set_Is_Atomic (Id, Is_Atomic (T));
-- In the case where there is no constraint given in the subtype
-- indication, Process_Subtype just returns the Subtype_Mark,
-- so its semantic attributes must be established here.
if Nkind (Subtype_Indication (N)) /= N_Subtype_Indication then
Set_Etype (Id, Base_Type (T));
case Ekind (T) is
when Array_Kind =>
Set_Ekind (Id, E_Array_Subtype);
-- Shouldn't we call Copy_Array_Subtype_Attributes here???
Set_First_Index (Id, First_Index (T));
Set_Is_Aliased (Id, Is_Aliased (T));
Set_Is_Constrained (Id, Is_Constrained (T));
when Decimal_Fixed_Point_Kind =>
Set_Ekind (Id, E_Decimal_Fixed_Point_Subtype);
Set_Digits_Value (Id, Digits_Value (T));
Set_Delta_Value (Id, Delta_Value (T));
Set_Scale_Value (Id, Scale_Value (T));
Set_Small_Value (Id, Small_Value (T));
Set_Scalar_Range (Id, Scalar_Range (T));
Set_Machine_Radix_10 (Id, Machine_Radix_10 (T));
Set_Is_Constrained (Id, Is_Constrained (T));
Set_RM_Size (Id, RM_Size (T));
when Enumeration_Kind =>
Set_Ekind (Id, E_Enumeration_Subtype);
Set_First_Literal (Id, First_Literal (Base_Type (T)));
Set_Scalar_Range (Id, Scalar_Range (T));
Set_Is_Character_Type (Id, Is_Character_Type (T));
Set_Is_Constrained (Id, Is_Constrained (T));
Set_RM_Size (Id, RM_Size (T));
when Ordinary_Fixed_Point_Kind =>
Set_Ekind (Id, E_Ordinary_Fixed_Point_Subtype);
Set_Scalar_Range (Id, Scalar_Range (T));
Set_Small_Value (Id, Small_Value (T));
Set_Delta_Value (Id, Delta_Value (T));
Set_Is_Constrained (Id, Is_Constrained (T));
Set_RM_Size (Id, RM_Size (T));
when Float_Kind =>
Set_Ekind (Id, E_Floating_Point_Subtype);
Set_Scalar_Range (Id, Scalar_Range (T));
Set_Digits_Value (Id, Digits_Value (T));
Set_Is_Constrained (Id, Is_Constrained (T));
when Signed_Integer_Kind =>
Set_Ekind (Id, E_Signed_Integer_Subtype);
Set_Scalar_Range (Id, Scalar_Range (T));
Set_Is_Constrained (Id, Is_Constrained (T));
Set_RM_Size (Id, RM_Size (T));
when Modular_Integer_Kind =>
Set_Ekind (Id, E_Modular_Integer_Subtype);
Set_Scalar_Range (Id, Scalar_Range (T));
Set_Is_Constrained (Id, Is_Constrained (T));
Set_RM_Size (Id, RM_Size (T));
when Class_Wide_Kind =>
Set_Ekind (Id, E_Class_Wide_Subtype);
Set_First_Entity (Id, First_Entity (T));
Set_Last_Entity (Id, Last_Entity (T));
Set_Class_Wide_Type (Id, Class_Wide_Type (T));
Set_Cloned_Subtype (Id, T);
Set_Is_Tagged_Type (Id, True);
Set_Has_Unknown_Discriminants
(Id, True);
if Ekind (T) = E_Class_Wide_Subtype then
Set_Equivalent_Type (Id, Equivalent_Type (T));
end if;
when E_Record_Type | E_Record_Subtype =>
Set_Ekind (Id, E_Record_Subtype);
if Ekind (T) = E_Record_Subtype
and then Present (Cloned_Subtype (T))
then
Set_Cloned_Subtype (Id, Cloned_Subtype (T));
else
Set_Cloned_Subtype (Id, T);
end if;
Set_First_Entity (Id, First_Entity (T));
Set_Last_Entity (Id, Last_Entity (T));
Set_Has_Discriminants (Id, Has_Discriminants (T));
Set_Is_Constrained (Id, Is_Constrained (T));
Set_Is_Limited_Record (Id, Is_Limited_Record (T));
Set_Has_Unknown_Discriminants
(Id, Has_Unknown_Discriminants (T));
if Has_Discriminants (T) then
Set_Discriminant_Constraint
(Id, Discriminant_Constraint (T));
Set_Stored_Constraint_From_Discriminant_Constraint (Id);
elsif Has_Unknown_Discriminants (Id) then
Set_Discriminant_Constraint (Id, No_Elist);
end if;
if Is_Tagged_Type (T) then
Set_Is_Tagged_Type (Id);
Set_Is_Abstract (Id, Is_Abstract (T));
Set_Primitive_Operations
(Id, Primitive_Operations (T));
Set_Class_Wide_Type (Id, Class_Wide_Type (T));
end if;
when Private_Kind =>
Set_Ekind (Id, Subtype_Kind (Ekind (T)));
Set_Has_Discriminants (Id, Has_Discriminants (T));
Set_Is_Constrained (Id, Is_Constrained (T));
Set_First_Entity (Id, First_Entity (T));
Set_Last_Entity (Id, Last_Entity (T));
Set_Private_Dependents (Id, New_Elmt_List);
Set_Is_Limited_Record (Id, Is_Limited_Record (T));
Set_Has_Unknown_Discriminants
(Id, Has_Unknown_Discriminants (T));
if Is_Tagged_Type (T) then
Set_Is_Tagged_Type (Id);
Set_Is_Abstract (Id, Is_Abstract (T));
Set_Primitive_Operations
(Id, Primitive_Operations (T));
Set_Class_Wide_Type (Id, Class_Wide_Type (T));
end if;
-- In general the attributes of the subtype of a private
-- type are the attributes of the partial view of parent.
-- However, the full view may be a discriminated type,
-- and the subtype must share the discriminant constraint
-- to generate correct calls to initialization procedures.
if Has_Discriminants (T) then
Set_Discriminant_Constraint
(Id, Discriminant_Constraint (T));
Set_Stored_Constraint_From_Discriminant_Constraint (Id);
elsif Present (Full_View (T))
and then Has_Discriminants (Full_View (T))
then
Set_Discriminant_Constraint
(Id, Discriminant_Constraint (Full_View (T)));
Set_Stored_Constraint_From_Discriminant_Constraint (Id);
-- This would seem semantically correct, but apparently
-- confuses the back-end (4412-009). To be explained ???
-- Set_Has_Discriminants (Id);
end if;
Prepare_Private_Subtype_Completion (Id, N);
when Access_Kind =>
Set_Ekind (Id, E_Access_Subtype);
Set_Is_Constrained (Id, Is_Constrained (T));
Set_Is_Access_Constant
(Id, Is_Access_Constant (T));
Set_Directly_Designated_Type
(Id, Designated_Type (T));
-- A Pure library_item must not contain the declaration of a
-- named access type, except within a subprogram, generic
-- subprogram, task unit, or protected unit (RM 10.2.1(16)).
if Comes_From_Source (Id)
and then In_Pure_Unit
and then not In_Subprogram_Task_Protected_Unit
then
Error_Msg_N
("named access types not allowed in pure unit", N);
end if;
when Concurrent_Kind =>
Set_Ekind (Id, Subtype_Kind (Ekind (T)));
Set_Corresponding_Record_Type (Id,
Corresponding_Record_Type (T));
Set_First_Entity (Id, First_Entity (T));
Set_First_Private_Entity (Id, First_Private_Entity (T));
Set_Has_Discriminants (Id, Has_Discriminants (T));
Set_Is_Constrained (Id, Is_Constrained (T));
Set_Last_Entity (Id, Last_Entity (T));
if Has_Discriminants (T) then
Set_Discriminant_Constraint (Id,
Discriminant_Constraint (T));
Set_Stored_Constraint_From_Discriminant_Constraint (Id);
end if;
-- If the subtype name denotes an incomplete type
-- an error was already reported by Process_Subtype.
when E_Incomplete_Type =>
Set_Etype (Id, Any_Type);
when others =>
raise Program_Error;
end case;
end if;
if Etype (Id) = Any_Type then
return;
end if;
-- Some common processing on all types
Set_Size_Info (Id, T);
Set_First_Rep_Item (Id, First_Rep_Item (T));
T := Etype (Id);
Set_Is_Immediately_Visible (Id, True);
Set_Depends_On_Private (Id, Has_Private_Component (T));
if Present (Generic_Parent_Type (N))
and then
(Nkind
(Parent (Generic_Parent_Type (N))) /= N_Formal_Type_Declaration
or else Nkind
(Formal_Type_Definition (Parent (Generic_Parent_Type (N))))
/= N_Formal_Private_Type_Definition)
then
if Is_Tagged_Type (Id) then
if Is_Class_Wide_Type (Id) then
Derive_Subprograms (Generic_Parent_Type (N), Id, Etype (T));
else
Derive_Subprograms (Generic_Parent_Type (N), Id, T);
end if;
elsif Scope (Etype (Id)) /= Standard_Standard then
Derive_Subprograms (Generic_Parent_Type (N), Id);
end if;
end if;
if Is_Private_Type (T)
and then Present (Full_View (T))
then
Conditional_Delay (Id, Full_View (T));
-- The subtypes of components or subcomponents of protected types
-- do not need freeze nodes, which would otherwise appear in the
-- wrong scope (before the freeze node for the protected type). The
-- proper subtypes are those of the subcomponents of the corresponding
-- record.
elsif Ekind (Scope (Id)) /= E_Protected_Type
and then Present (Scope (Scope (Id))) -- error defense!
and then Ekind (Scope (Scope (Id))) /= E_Protected_Type
then
Conditional_Delay (Id, T);
end if;
-- Check that constraint_error is raised for a scalar subtype
-- indication when the lower or upper bound of a non-null range
-- lies outside the range of the type mark.
if Nkind (Subtype_Indication (N)) = N_Subtype_Indication then
if Is_Scalar_Type (Etype (Id))
and then Scalar_Range (Id) /=
Scalar_Range (Etype (Subtype_Mark
(Subtype_Indication (N))))
then
Apply_Range_Check
(Scalar_Range (Id),
Etype (Subtype_Mark (Subtype_Indication (N))));
elsif Is_Array_Type (Etype (Id))
and then Present (First_Index (Id))
then
-- This really should be a subprogram that finds the indications
-- to check???
if ((Nkind (First_Index (Id)) = N_Identifier
and then Ekind (Entity (First_Index (Id))) in Scalar_Kind)
or else Nkind (First_Index (Id)) = N_Subtype_Indication)
and then
Nkind (Scalar_Range (Etype (First_Index (Id)))) = N_Range
then
declare
Target_Typ : constant Entity_Id :=
Etype
(First_Index (Etype
(Subtype_Mark (Subtype_Indication (N)))));
begin
R_Checks :=
Range_Check
(Scalar_Range (Etype (First_Index (Id))),
Target_Typ,
Etype (First_Index (Id)),
Defining_Identifier (N));
Insert_Range_Checks
(R_Checks,
N,
Target_Typ,
Sloc (Defining_Identifier (N)));
end;
end if;
end if;
end if;
Check_Eliminated (Id);
end Analyze_Subtype_Declaration;
--------------------------------
-- Analyze_Subtype_Indication --
--------------------------------
procedure Analyze_Subtype_Indication (N : Node_Id) is
T : constant Entity_Id := Subtype_Mark (N);
R : constant Node_Id := Range_Expression (Constraint (N));
begin
Analyze (T);
if R /= Error then
Analyze (R);
Set_Etype (N, Etype (R));
else
Set_Error_Posted (R);
Set_Error_Posted (T);
end if;
end Analyze_Subtype_Indication;
------------------------------
-- Analyze_Type_Declaration --
------------------------------
procedure Analyze_Type_Declaration (N : Node_Id) is
Def : constant Node_Id := Type_Definition (N);
Def_Id : constant Entity_Id := Defining_Identifier (N);
T : Entity_Id;
Prev : Entity_Id;
Is_Remote : constant Boolean :=
(Is_Remote_Types (Current_Scope)
or else Is_Remote_Call_Interface (Current_Scope))
and then not (In_Private_Part (Current_Scope)
or else
In_Package_Body (Current_Scope));
begin
Prev := Find_Type_Name (N);
-- The full view, if present, now points to the current type
-- Ada0Y (AI-50217): If the type was previously decorated when imported
-- through a LIMITED WITH clause, it appears as incomplete but has no
-- full view.
if Ekind (Prev) = E_Incomplete_Type
and then Present (Full_View (Prev))
then
T := Full_View (Prev);
else
T := Prev;
end if;
Set_Is_Pure (T, Is_Pure (Current_Scope));
-- We set the flag Is_First_Subtype here. It is needed to set the
-- corresponding flag for the Implicit class-wide-type created
-- during tagged types processing.
Set_Is_First_Subtype (T, True);
-- Only composite types other than array types are allowed to have
-- discriminants.
case Nkind (Def) is
-- For derived types, the rule will be checked once we've figured
-- out the parent type.
when N_Derived_Type_Definition =>
null;
-- For record types, discriminants are allowed.
when N_Record_Definition =>
null;
when others =>
if Present (Discriminant_Specifications (N)) then
Error_Msg_N
("elementary or array type cannot have discriminants",
Defining_Identifier
(First (Discriminant_Specifications (N))));
end if;
end case;
-- Elaborate the type definition according to kind, and generate
-- subsidiary (implicit) subtypes where needed. We skip this if
-- it was already done (this happens during the reanalysis that
-- follows a call to the high level optimizer).
if not Analyzed (T) then
Set_Analyzed (T);
case Nkind (Def) is
when N_Access_To_Subprogram_Definition =>
Access_Subprogram_Declaration (T, Def);
-- If this is a remote access to subprogram, we must create
-- the equivalent fat pointer type, and related subprograms.
if Is_Remote then
Process_Remote_AST_Declaration (N);
end if;
-- Validate categorization rule against access type declaration
-- usually a violation in Pure unit, Shared_Passive unit.
Validate_Access_Type_Declaration (T, N);
when N_Access_To_Object_Definition =>
Access_Type_Declaration (T, Def);
-- Validate categorization rule against access type declaration
-- usually a violation in Pure unit, Shared_Passive unit.
Validate_Access_Type_Declaration (T, N);
-- If we are in a Remote_Call_Interface package and define
-- a RACW, Read and Write attribute must be added.
if Is_Remote
and then Is_Remote_Access_To_Class_Wide_Type (Def_Id)
then
Add_RACW_Features (Def_Id);
end if;
when N_Array_Type_Definition =>
Array_Type_Declaration (T, Def);
when N_Derived_Type_Definition =>
Derived_Type_Declaration (T, N, T /= Def_Id);
when N_Enumeration_Type_Definition =>
Enumeration_Type_Declaration (T, Def);
when N_Floating_Point_Definition =>
Floating_Point_Type_Declaration (T, Def);
when N_Decimal_Fixed_Point_Definition =>
Decimal_Fixed_Point_Type_Declaration (T, Def);
when N_Ordinary_Fixed_Point_Definition =>
Ordinary_Fixed_Point_Type_Declaration (T, Def);
when N_Signed_Integer_Type_Definition =>
Signed_Integer_Type_Declaration (T, Def);
when N_Modular_Type_Definition =>
Modular_Type_Declaration (T, Def);
when N_Record_Definition =>
Record_Type_Declaration (T, N, Prev);
when others =>
raise Program_Error;
end case;
end if;
if Etype (T) = Any_Type then
return;
end if;
-- Some common processing for all types
Set_Depends_On_Private (T, Has_Private_Component (T));
-- Both the declared entity, and its anonymous base type if one
-- was created, need freeze nodes allocated.
declare
B : constant Entity_Id := Base_Type (T);
begin
-- In the case where the base type is different from the first
-- subtype, we pre-allocate a freeze node, and set the proper
-- link to the first subtype. Freeze_Entity will use this
-- preallocated freeze node when it freezes the entity.
if B /= T then
Ensure_Freeze_Node (B);
Set_First_Subtype_Link (Freeze_Node (B), T);
end if;
if not From_With_Type (T) then
Set_Has_Delayed_Freeze (T);
end if;
end;
-- Case of T is the full declaration of some private type which has
-- been swapped in Defining_Identifier (N).
if T /= Def_Id and then Is_Private_Type (Def_Id) then
Process_Full_View (N, T, Def_Id);
-- Record the reference. The form of this is a little strange,
-- since the full declaration has been swapped in. So the first
-- parameter here represents the entity to which a reference is
-- made which is the "real" entity, i.e. the one swapped in,
-- and the second parameter provides the reference location.
Generate_Reference (T, T, 'c');
Set_Completion_Referenced (Def_Id);
-- For completion of incomplete type, process incomplete dependents
-- and always mark the full type as referenced (it is the incomplete
-- type that we get for any real reference).
elsif Ekind (Prev) = E_Incomplete_Type then
Process_Incomplete_Dependents (N, T, Prev);
Generate_Reference (Prev, Def_Id, 'c');
Set_Completion_Referenced (Def_Id);
-- If not private type or incomplete type completion, this is a real
-- definition of a new entity, so record it.
else
Generate_Definition (Def_Id);
end if;
Check_Eliminated (Def_Id);
end Analyze_Type_Declaration;
--------------------------
-- Analyze_Variant_Part --
--------------------------
procedure Analyze_Variant_Part (N : Node_Id) is
procedure Non_Static_Choice_Error (Choice : Node_Id);
-- Error routine invoked by the generic instantiation below when
-- the variant part has a non static choice.
procedure Process_Declarations (Variant : Node_Id);
-- Analyzes all the declarations associated with a Variant.
-- Needed by the generic instantiation below.
package Variant_Choices_Processing is new
Generic_Choices_Processing
(Get_Alternatives => Variants,
Get_Choices => Discrete_Choices,
Process_Empty_Choice => No_OP,
Process_Non_Static_Choice => Non_Static_Choice_Error,
Process_Associated_Node => Process_Declarations);
use Variant_Choices_Processing;
-- Instantiation of the generic choice processing package.
-----------------------------
-- Non_Static_Choice_Error --
-----------------------------
procedure Non_Static_Choice_Error (Choice : Node_Id) is
begin
Flag_Non_Static_Expr
("choice given in variant part is not static!", Choice);
end Non_Static_Choice_Error;
--------------------------
-- Process_Declarations --
--------------------------
procedure Process_Declarations (Variant : Node_Id) is
begin
if not Null_Present (Component_List (Variant)) then
Analyze_Declarations (Component_Items (Component_List (Variant)));
if Present (Variant_Part (Component_List (Variant))) then
Analyze (Variant_Part (Component_List (Variant)));
end if;
end if;
end Process_Declarations;
-- Variables local to Analyze_Case_Statement.
Discr_Name : Node_Id;
Discr_Type : Entity_Id;
Case_Table : Choice_Table_Type (1 .. Number_Of_Choices (N));
Last_Choice : Nat;
Dont_Care : Boolean;
Others_Present : Boolean := False;
-- Start of processing for Analyze_Variant_Part
begin
Discr_Name := Name (N);
Analyze (Discr_Name);
if Ekind (Entity (Discr_Name)) /= E_Discriminant then
Error_Msg_N ("invalid discriminant name in variant part", Discr_Name);
end if;
Discr_Type := Etype (Entity (Discr_Name));
if not Is_Discrete_Type (Discr_Type) then
Error_Msg_N
("discriminant in a variant part must be of a discrete type",
Name (N));
return;
end if;
-- Call the instantiated Analyze_Choices which does the rest of the work
Analyze_Choices
(N, Discr_Type, Case_Table, Last_Choice, Dont_Care, Others_Present);
end Analyze_Variant_Part;
----------------------------
-- Array_Type_Declaration --
----------------------------
procedure Array_Type_Declaration (T : in out Entity_Id; Def : Node_Id) is
Component_Def : constant Node_Id := Component_Definition (Def);
Element_Type : Entity_Id;
Implicit_Base : Entity_Id;
Index : Node_Id;
Related_Id : Entity_Id := Empty;
Nb_Index : Nat;
P : constant Node_Id := Parent (Def);
Priv : Entity_Id;
begin
if Nkind (Def) = N_Constrained_Array_Definition then
Index := First (Discrete_Subtype_Definitions (Def));
-- Find proper names for the implicit types which may be public.
-- in case of anonymous arrays we use the name of the first object
-- of that type as prefix.
if No (T) then
Related_Id := Defining_Identifier (P);
else
Related_Id := T;
end if;
else
Index := First (Subtype_Marks (Def));
end if;
Nb_Index := 1;
while Present (Index) loop
Analyze (Index);
Make_Index (Index, P, Related_Id, Nb_Index);
Next_Index (Index);
Nb_Index := Nb_Index + 1;
end loop;
Element_Type := Process_Subtype (Subtype_Indication (Component_Def),
P, Related_Id, 'C');
-- Constrained array case
if No (T) then
T := Create_Itype (E_Void, P, Related_Id, 'T');
end if;
if Nkind (Def) = N_Constrained_Array_Definition then
-- Establish Implicit_Base as unconstrained base type
Implicit_Base := Create_Itype (E_Array_Type, P, Related_Id, 'B');
Init_Size_Align (Implicit_Base);
Set_Etype (Implicit_Base, Implicit_Base);
Set_Scope (Implicit_Base, Current_Scope);
Set_Has_Delayed_Freeze (Implicit_Base);
-- The constrained array type is a subtype of the unconstrained one
Set_Ekind (T, E_Array_Subtype);
Init_Size_Align (T);
Set_Etype (T, Implicit_Base);
Set_Scope (T, Current_Scope);
Set_Is_Constrained (T, True);
Set_First_Index (T, First (Discrete_Subtype_Definitions (Def)));
Set_Has_Delayed_Freeze (T);
-- Complete setup of implicit base type
Set_First_Index (Implicit_Base, First_Index (T));
Set_Component_Type (Implicit_Base, Element_Type);
Set_Has_Task (Implicit_Base, Has_Task (Element_Type));
Set_Component_Size (Implicit_Base, Uint_0);
Set_Has_Controlled_Component
(Implicit_Base, Has_Controlled_Component
(Element_Type)
or else
Is_Controlled (Element_Type));
Set_Finalize_Storage_Only
(Implicit_Base, Finalize_Storage_Only
(Element_Type));
-- Unconstrained array case
else
Set_Ekind (T, E_Array_Type);
Init_Size_Align (T);
Set_Etype (T, T);
Set_Scope (T, Current_Scope);
Set_Component_Size (T, Uint_0);
Set_Is_Constrained (T, False);
Set_First_Index (T, First (Subtype_Marks (Def)));
Set_Has_Delayed_Freeze (T, True);
Set_Has_Task (T, Has_Task (Element_Type));
Set_Has_Controlled_Component (T, Has_Controlled_Component
(Element_Type)
or else
Is_Controlled (Element_Type));
Set_Finalize_Storage_Only (T, Finalize_Storage_Only
(Element_Type));
end if;
Set_Component_Type (Base_Type (T), Element_Type);
if Aliased_Present (Component_Definition (Def)) then
Set_Has_Aliased_Components (Etype (T));
end if;
Priv := Private_Component (Element_Type);
if Present (Priv) then
-- Check for circular definitions
if Priv = Any_Type then
Set_Component_Type (Etype (T), Any_Type);
-- There is a gap in the visibility of operations on the composite
-- type only if the component type is defined in a different scope.
elsif Scope (Priv) = Current_Scope then
null;
elsif Is_Limited_Type (Priv) then
Set_Is_Limited_Composite (Etype (T));
Set_Is_Limited_Composite (T);
else
Set_Is_Private_Composite (Etype (T));
Set_Is_Private_Composite (T);
end if;
end if;
-- Create a concatenation operator for the new type. Internal
-- array types created for packed entities do not need such, they
-- are compatible with the user-defined type.
if Number_Dimensions (T) = 1
and then not Is_Packed_Array_Type (T)
then
New_Concatenation_Op (T);
end if;
-- In the case of an unconstrained array the parser has already
-- verified that all the indices are unconstrained but we still
-- need to make sure that the element type is constrained.
if Is_Indefinite_Subtype (Element_Type) then
Error_Msg_N
("unconstrained element type in array declaration",
Subtype_Indication (Component_Def));
elsif Is_Abstract (Element_Type) then
Error_Msg_N
("The type of a component cannot be abstract",
Subtype_Indication (Component_Def));
end if;
end Array_Type_Declaration;
-------------------------------
-- Build_Derived_Access_Type --
-------------------------------
procedure Build_Derived_Access_Type
(N : Node_Id;
Parent_Type : Entity_Id;
Derived_Type : Entity_Id)
is
S : constant Node_Id := Subtype_Indication (Type_Definition (N));
Desig_Type : Entity_Id;
Discr : Entity_Id;
Discr_Con_Elist : Elist_Id;
Discr_Con_El : Elmt_Id;
Subt : Entity_Id;
begin
-- Set the designated type so it is available in case this is
-- an access to a self-referential type, e.g. a standard list
-- type with a next pointer. Will be reset after subtype is built.
Set_Directly_Designated_Type
(Derived_Type, Designated_Type (Parent_Type));
Subt := Process_Subtype (S, N);
if Nkind (S) /= N_Subtype_Indication
and then Subt /= Base_Type (Subt)
then
Set_Ekind (Derived_Type, E_Access_Subtype);
end if;
if Ekind (Derived_Type) = E_Access_Subtype then
declare
Pbase : constant Entity_Id := Base_Type (Parent_Type);
Ibase : constant Entity_Id :=
Create_Itype (Ekind (Pbase), N, Derived_Type, 'B');
Svg_Chars : constant Name_Id := Chars (Ibase);
Svg_Next_E : constant Entity_Id := Next_Entity (Ibase);
begin
Copy_Node (Pbase, Ibase);
Set_Chars (Ibase, Svg_Chars);
Set_Next_Entity (Ibase, Svg_Next_E);
Set_Sloc (Ibase, Sloc (Derived_Type));
Set_Scope (Ibase, Scope (Derived_Type));
Set_Freeze_Node (Ibase, Empty);
Set_Is_Frozen (Ibase, False);
Set_Comes_From_Source (Ibase, False);
Set_Is_First_Subtype (Ibase, False);
Set_Etype (Ibase, Pbase);
Set_Etype (Derived_Type, Ibase);
end;
end if;
Set_Directly_Designated_Type
(Derived_Type, Designated_Type (Subt));
Set_Is_Constrained (Derived_Type, Is_Constrained (Subt));
Set_Is_Access_Constant (Derived_Type, Is_Access_Constant (Parent_Type));
Set_Size_Info (Derived_Type, Parent_Type);
Set_RM_Size (Derived_Type, RM_Size (Parent_Type));
Set_Depends_On_Private (Derived_Type,
Has_Private_Component (Derived_Type));
Conditional_Delay (Derived_Type, Subt);
-- Note: we do not copy the Storage_Size_Variable, since
-- we always go to the root type for this information.
-- Apply range checks to discriminants for derived record case
-- ??? THIS CODE SHOULD NOT BE HERE REALLY.
Desig_Type := Designated_Type (Derived_Type);
if Is_Composite_Type (Desig_Type)
and then (not Is_Array_Type (Desig_Type))
and then Has_Discriminants (Desig_Type)
and then Base_Type (Desig_Type) /= Desig_Type
then
Discr_Con_Elist := Discriminant_Constraint (Desig_Type);
Discr_Con_El := First_Elmt (Discr_Con_Elist);
Discr := First_Discriminant (Base_Type (Desig_Type));
while Present (Discr_Con_El) loop
Apply_Range_Check (Node (Discr_Con_El), Etype (Discr));
Next_Elmt (Discr_Con_El);
Next_Discriminant (Discr);
end loop;
end if;
end Build_Derived_Access_Type;
------------------------------
-- Build_Derived_Array_Type --
------------------------------
procedure Build_Derived_Array_Type
(N : Node_Id;
Parent_Type : Entity_Id;
Derived_Type : Entity_Id)
is
Loc : constant Source_Ptr := Sloc (N);
Tdef : constant Node_Id := Type_Definition (N);
Indic : constant Node_Id := Subtype_Indication (Tdef);
Parent_Base : constant Entity_Id := Base_Type (Parent_Type);
Implicit_Base : Entity_Id;
New_Indic : Node_Id;
procedure Make_Implicit_Base;
-- If the parent subtype is constrained, the derived type is a
-- subtype of an implicit base type derived from the parent base.
------------------------
-- Make_Implicit_Base --
------------------------
procedure Make_Implicit_Base is
begin
Implicit_Base :=
Create_Itype (Ekind (Parent_Base), N, Derived_Type, 'B');
Set_Ekind (Implicit_Base, Ekind (Parent_Base));
Set_Etype (Implicit_Base, Parent_Base);
Copy_Array_Subtype_Attributes (Implicit_Base, Parent_Base);
Copy_Array_Base_Type_Attributes (Implicit_Base, Parent_Base);
Set_Has_Delayed_Freeze (Implicit_Base, True);
end Make_Implicit_Base;
-- Start of processing for Build_Derived_Array_Type
begin
if not Is_Constrained (Parent_Type) then
if Nkind (Indic) /= N_Subtype_Indication then
Set_Ekind (Derived_Type, E_Array_Type);
Copy_Array_Subtype_Attributes (Derived_Type, Parent_Type);
Copy_Array_Base_Type_Attributes (Derived_Type, Parent_Type);
Set_Has_Delayed_Freeze (Derived_Type, True);
else
Make_Implicit_Base;
Set_Etype (Derived_Type, Implicit_Base);
New_Indic :=
Make_Subtype_Declaration (Loc,
Defining_Identifier => Derived_Type,
Subtype_Indication =>
Make_Subtype_Indication (Loc,
Subtype_Mark => New_Reference_To (Implicit_Base, Loc),
Constraint => Constraint (Indic)));
Rewrite (N, New_Indic);
Analyze (N);
end if;
else
if Nkind (Indic) /= N_Subtype_Indication then
Make_Implicit_Base;
Set_Ekind (Derived_Type, Ekind (Parent_Type));
Set_Etype (Derived_Type, Implicit_Base);
Copy_Array_Subtype_Attributes (Derived_Type, Parent_Type);
else
Error_Msg_N ("illegal constraint on constrained type", Indic);
end if;
end if;
-- If the parent type is not a derived type itself, and is
-- declared in a closed scope (e.g., a subprogram), then we
-- need to explicitly introduce the new type's concatenation
-- operator since Derive_Subprograms will not inherit the
-- parent's operator. If the parent type is unconstrained, the
-- operator is of the unconstrained base type.
if Number_Dimensions (Parent_Type) = 1
and then not Is_Limited_Type (Parent_Type)
and then not Is_Derived_Type (Parent_Type)
and then not Is_Package (Scope (Base_Type (Parent_Type)))
then
if not Is_Constrained (Parent_Type)
and then Is_Constrained (Derived_Type)
then
New_Concatenation_Op (Implicit_Base);
else
New_Concatenation_Op (Derived_Type);
end if;
end if;
end Build_Derived_Array_Type;
-----------------------------------
-- Build_Derived_Concurrent_Type --
-----------------------------------
procedure Build_Derived_Concurrent_Type
(N : Node_Id;
Parent_Type : Entity_Id;
Derived_Type : Entity_Id)
is
D_Constraint : Node_Id;
Disc_Spec : Node_Id;
Old_Disc : Entity_Id;
New_Disc : Entity_Id;
Constraint_Present : constant Boolean :=
Nkind (Subtype_Indication (Type_Definition (N)))
= N_Subtype_Indication;
begin
Set_Stored_Constraint (Derived_Type, No_Elist);
if Is_Task_Type (Parent_Type) then
Set_Storage_Size_Variable (Derived_Type,
Storage_Size_Variable (Parent_Type));
end if;
if Present (Discriminant_Specifications (N)) then
New_Scope (Derived_Type);
Check_Or_Process_Discriminants (N, Derived_Type);
End_Scope;
elsif Constraint_Present then
-- Build constrained subtype and derive from it
declare
Loc : constant Source_Ptr := Sloc (N);
Anon : constant Entity_Id :=
Make_Defining_Identifier (Loc,
New_External_Name (Chars (Derived_Type), 'T'));
Decl : Node_Id;
begin
Decl :=
Make_Subtype_Declaration (Loc,
Defining_Identifier => Anon,
Subtype_Indication =>
New_Copy_Tree (Subtype_Indication (Type_Definition (N))));
Insert_Before (N, Decl);
Rewrite (Subtype_Indication (Type_Definition (N)),
New_Occurrence_Of (Anon, Loc));
Analyze (Decl);
Set_Analyzed (Derived_Type, False);
Analyze (N);
return;
end;
end if;
-- All attributes are inherited from parent. In particular,
-- entries and the corresponding record type are the same.
-- Discriminants may be renamed, and must be treated separately.
Set_Has_Discriminants
(Derived_Type, Has_Discriminants (Parent_Type));
Set_Corresponding_Record_Type
(Derived_Type, Corresponding_Record_Type (Parent_Type));
if Constraint_Present then
if not Has_Discriminants (Parent_Type) then
Error_Msg_N ("untagged parent must have discriminants", N);
elsif Present (Discriminant_Specifications (N)) then
-- Verify that new discriminants are used to constrain
-- the old ones.
Old_Disc := First_Discriminant (Parent_Type);
New_Disc := First_Discriminant (Derived_Type);
Disc_Spec := First (Discriminant_Specifications (N));
D_Constraint :=
First
(Constraints
(Constraint (Subtype_Indication (Type_Definition (N)))));
while Present (Old_Disc) and then Present (Disc_Spec) loop
if Nkind (Discriminant_Type (Disc_Spec)) /=
N_Access_Definition
then
Analyze (Discriminant_Type (Disc_Spec));
if not Subtypes_Statically_Compatible (
Etype (Discriminant_Type (Disc_Spec)),
Etype (Old_Disc))
then
Error_Msg_N
("not statically compatible with parent discriminant",
Discriminant_Type (Disc_Spec));
end if;
end if;
if Nkind (D_Constraint) = N_Identifier
and then Chars (D_Constraint) /=
Chars (Defining_Identifier (Disc_Spec))
then
Error_Msg_N ("new discriminants must constrain old ones",
D_Constraint);
else
Set_Corresponding_Discriminant (New_Disc, Old_Disc);
end if;
Next_Discriminant (Old_Disc);
Next_Discriminant (New_Disc);
Next (Disc_Spec);
end loop;
if Present (Old_Disc) or else Present (Disc_Spec) then
Error_Msg_N ("discriminant mismatch in derivation", N);
end if;
end if;
elsif Present (Discriminant_Specifications (N)) then
Error_Msg_N
("missing discriminant constraint in untagged derivation",
N);
end if;
if Present (Discriminant_Specifications (N)) then
Old_Disc := First_Discriminant (Parent_Type);
while Present (Old_Disc) loop
if No (Next_Entity (Old_Disc))
or else Ekind (Next_Entity (Old_Disc)) /= E_Discriminant
then
Set_Next_Entity (Last_Entity (Derived_Type),
Next_Entity (Old_Disc));
exit;
end if;
Next_Discriminant (Old_Disc);
end loop;
else
Set_First_Entity (Derived_Type, First_Entity (Parent_Type));
if Has_Discriminants (Parent_Type) then
Set_Discriminant_Constraint (
Derived_Type, Discriminant_Constraint (Parent_Type));
end if;
end if;
Set_Last_Entity (Derived_Type, Last_Entity (Parent_Type));
Set_Has_Completion (Derived_Type);
end Build_Derived_Concurrent_Type;
------------------------------------
-- Build_Derived_Enumeration_Type --
------------------------------------
procedure Build_Derived_Enumeration_Type
(N : Node_Id;
Parent_Type : Entity_Id;
Derived_Type : Entity_Id)
is
Loc : constant Source_Ptr := Sloc (N);
Def : constant Node_Id := Type_Definition (N);
Indic : constant Node_Id := Subtype_Indication (Def);
Implicit_Base : Entity_Id;
Literal : Entity_Id;
New_Lit : Entity_Id;
Literals_List : List_Id;
Type_Decl : Node_Id;
Hi, Lo : Node_Id;
Rang_Expr : Node_Id;
begin
-- Since types Standard.Character and Standard.Wide_Character do
-- not have explicit literals lists we need to process types derived
-- from them specially. This is handled by Derived_Standard_Character.
-- If the parent type is a generic type, there are no literals either,
-- and we construct the same skeletal representation as for the generic
-- parent type.
if Root_Type (Parent_Type) = Standard_Character
or else Root_Type (Parent_Type) = Standard_Wide_Character
then
Derived_Standard_Character (N, Parent_Type, Derived_Type);
elsif Is_Generic_Type (Root_Type (Parent_Type)) then
declare
Lo : Node_Id;
Hi : Node_Id;
begin
Lo :=
Make_Attribute_Reference (Loc,
Attribute_Name => Name_First,
Prefix => New_Reference_To (Derived_Type, Loc));
Set_Etype (Lo, Derived_Type);
Hi :=
Make_Attribute_Reference (Loc,
Attribute_Name => Name_Last,
Prefix => New_Reference_To (Derived_Type, Loc));
Set_Etype (Hi, Derived_Type);
Set_Scalar_Range (Derived_Type,
Make_Range (Loc,
Low_Bound => Lo,
High_Bound => Hi));
end;
else
-- If a constraint is present, analyze the bounds to catch
-- premature usage of the derived literals.
if Nkind (Indic) = N_Subtype_Indication
and then Nkind (Range_Expression (Constraint (Indic))) = N_Range
then
Analyze (Low_Bound (Range_Expression (Constraint (Indic))));
Analyze (High_Bound (Range_Expression (Constraint (Indic))));
end if;
-- Introduce an implicit base type for the derived type even
-- if there is no constraint attached to it, since this seems
-- closer to the Ada semantics. Build a full type declaration
-- tree for the derived type using the implicit base type as
-- the defining identifier. The build a subtype declaration
-- tree which applies the constraint (if any) have it replace
-- the derived type declaration.
Literal := First_Literal (Parent_Type);
Literals_List := New_List;
while Present (Literal)
and then Ekind (Literal) = E_Enumeration_Literal
loop
-- Literals of the derived type have the same representation as
-- those of the parent type, but this representation can be
-- overridden by an explicit representation clause. Indicate
-- that there is no explicit representation given yet. These
-- derived literals are implicit operations of the new type,
-- and can be overriden by explicit ones.
if Nkind (Literal) = N_Defining_Character_Literal then
New_Lit :=
Make_Defining_Character_Literal (Loc, Chars (Literal));
else
New_Lit := Make_Defining_Identifier (Loc, Chars (Literal));
end if;
Set_Ekind (New_Lit, E_Enumeration_Literal);
Set_Enumeration_Pos (New_Lit, Enumeration_Pos (Literal));
Set_Enumeration_Rep (New_Lit, Enumeration_Rep (Literal));
Set_Enumeration_Rep_Expr (New_Lit, Empty);
Set_Alias (New_Lit, Literal);
Set_Is_Known_Valid (New_Lit, True);
Append (New_Lit, Literals_List);
Next_Literal (Literal);
end loop;
Implicit_Base :=
Make_Defining_Identifier (Sloc (Derived_Type),
New_External_Name (Chars (Derived_Type), 'B'));
-- Indicate the proper nature of the derived type. This must
-- be done before analysis of the literals, to recognize cases
-- when a literal may be hidden by a previous explicit function
-- definition (cf. c83031a).
Set_Ekind (Derived_Type, E_Enumeration_Subtype);
Set_Etype (Derived_Type, Implicit_Base);
Type_Decl :=
Make_Full_Type_Declaration (Loc,
Defining_Identifier => Implicit_Base,
Discriminant_Specifications => No_List,
Type_Definition =>
Make_Enumeration_Type_Definition (Loc, Literals_List));
Mark_Rewrite_Insertion (Type_Decl);
Insert_Before (N, Type_Decl);
Analyze (Type_Decl);
-- After the implicit base is analyzed its Etype needs to be
-- changed to reflect the fact that it is derived from the
-- parent type which was ignored during analysis. We also set
-- the size at this point.
Set_Etype (Implicit_Base, Parent_Type);
Set_Size_Info (Implicit_Base, Parent_Type);
Set_RM_Size (Implicit_Base, RM_Size (Parent_Type));
Set_First_Rep_Item (Implicit_Base, First_Rep_Item (Parent_Type));
Set_Has_Non_Standard_Rep
(Implicit_Base, Has_Non_Standard_Rep
(Parent_Type));
Set_Has_Delayed_Freeze (Implicit_Base);
-- Process the subtype indication including a validation check
-- on the constraint, if any. If a constraint is given, its bounds
-- must be implicitly converted to the new type.
if Nkind (Indic) = N_Subtype_Indication then
declare
R : constant Node_Id :=
Range_Expression (Constraint (Indic));
begin
if Nkind (R) = N_Range then
Hi := Build_Scalar_Bound
(High_Bound (R), Parent_Type, Implicit_Base);
Lo := Build_Scalar_Bound
(Low_Bound (R), Parent_Type, Implicit_Base);
else
-- Constraint is a Range attribute. Replace with the
-- explicit mention of the bounds of the prefix, which
-- must be a subtype.
Analyze (Prefix (R));
Hi :=
Convert_To (Implicit_Base,
Make_Attribute_Reference (Loc,
Attribute_Name => Name_Last,
Prefix =>
New_Occurrence_Of (Entity (Prefix (R)), Loc)));
Lo :=
Convert_To (Implicit_Base,
Make_Attribute_Reference (Loc,
Attribute_Name => Name_First,
Prefix =>
New_Occurrence_Of (Entity (Prefix (R)), Loc)));
end if;
end;
else
Hi :=
Build_Scalar_Bound
(Type_High_Bound (Parent_Type),
Parent_Type, Implicit_Base);
Lo :=
Build_Scalar_Bound
(Type_Low_Bound (Parent_Type),
Parent_Type, Implicit_Base);
end if;
Rang_Expr :=
Make_Range (Loc,
Low_Bound => Lo,
High_Bound => Hi);
-- If we constructed a default range for the case where no range
-- was given, then the expressions in the range must not freeze
-- since they do not correspond to expressions in the source.
if Nkind (Indic) /= N_Subtype_Indication then
Set_Must_Not_Freeze (Lo);
Set_Must_Not_Freeze (Hi);
Set_Must_Not_Freeze (Rang_Expr);
end if;
Rewrite (N,
Make_Subtype_Declaration (Loc,
Defining_Identifier => Derived_Type,
Subtype_Indication =>
Make_Subtype_Indication (Loc,
Subtype_Mark => New_Occurrence_Of (Implicit_Base, Loc),
Constraint =>
Make_Range_Constraint (Loc,
Range_Expression => Rang_Expr))));
Analyze (N);
-- If pragma Discard_Names applies on the first subtype
-- of the parent type, then it must be applied on this
-- subtype as well.
if Einfo.Discard_Names (First_Subtype (Parent_Type)) then
Set_Discard_Names (Derived_Type);
end if;
-- Apply a range check. Since this range expression doesn't
-- have an Etype, we have to specifically pass the Source_Typ
-- parameter. Is this right???
if Nkind (Indic) = N_Subtype_Indication then
Apply_Range_Check (Range_Expression (Constraint (Indic)),
Parent_Type,
Source_Typ => Entity (Subtype_Mark (Indic)));
end if;
end if;
end Build_Derived_Enumeration_Type;
--------------------------------
-- Build_Derived_Numeric_Type --
--------------------------------
procedure Build_Derived_Numeric_Type
(N : Node_Id;
Parent_Type : Entity_Id;
Derived_Type : Entity_Id)
is
Loc : constant Source_Ptr := Sloc (N);
Tdef : constant Node_Id := Type_Definition (N);
Indic : constant Node_Id := Subtype_Indication (Tdef);
Parent_Base : constant Entity_Id := Base_Type (Parent_Type);
No_Constraint : constant Boolean := Nkind (Indic) /=
N_Subtype_Indication;
Implicit_Base : Entity_Id;
Lo : Node_Id;
Hi : Node_Id;
begin
-- Process the subtype indication including a validation check on
-- the constraint if any.
Discard_Node (Process_Subtype (Indic, N));
-- Introduce an implicit base type for the derived type even if
-- there is no constraint attached to it, since this seems closer
-- to the Ada semantics.
Implicit_Base :=
Create_Itype (Ekind (Parent_Base), N, Derived_Type, 'B');
Set_Etype (Implicit_Base, Parent_Base);
Set_Ekind (Implicit_Base, Ekind (Parent_Base));
Set_Size_Info (Implicit_Base, Parent_Base);
Set_RM_Size (Implicit_Base, RM_Size (Parent_Base));
Set_First_Rep_Item (Implicit_Base, First_Rep_Item (Parent_Base));
Set_Parent (Implicit_Base, Parent (Derived_Type));
if Is_Discrete_Or_Fixed_Point_Type (Parent_Base) then
Set_RM_Size (Implicit_Base, RM_Size (Parent_Base));
end if;
Set_Has_Delayed_Freeze (Implicit_Base);
Lo := New_Copy_Tree (Type_Low_Bound (Parent_Base));
Hi := New_Copy_Tree (Type_High_Bound (Parent_Base));
Set_Scalar_Range (Implicit_Base,
Make_Range (Loc,
Low_Bound => Lo,
High_Bound => Hi));
if Has_Infinities (Parent_Base) then
Set_Includes_Infinities (Scalar_Range (Implicit_Base));
end if;
-- The Derived_Type, which is the entity of the declaration, is
-- a subtype of the implicit base. Its Ekind is a subtype, even
-- in the absence of an explicit constraint.
Set_Etype (Derived_Type, Implicit_Base);
-- If we did not have a constraint, then the Ekind is set from the
-- parent type (otherwise Process_Subtype has set the bounds)
if No_Constraint then
Set_Ekind (Derived_Type, Subtype_Kind (Ekind (Parent_Type)));
end if;
-- If we did not have a range constraint, then set the range
-- from the parent type. Otherwise, the call to Process_Subtype
-- has set the bounds.
if No_Constraint
or else not Has_Range_Constraint (Indic)
then
Set_Scalar_Range (Derived_Type,
Make_Range (Loc,
Low_Bound => New_Copy_Tree (Type_Low_Bound (Parent_Type)),
High_Bound => New_Copy_Tree (Type_High_Bound (Parent_Type))));
Set_Is_Constrained (Derived_Type, Is_Constrained (Parent_Type));
if Has_Infinities (Parent_Type) then
Set_Includes_Infinities (Scalar_Range (Derived_Type));
end if;
end if;
-- Set remaining type-specific fields, depending on numeric type
if Is_Modular_Integer_Type (Parent_Type) then
Set_Modulus (Implicit_Base, Modulus (Parent_Base));
Set_Non_Binary_Modulus
(Implicit_Base, Non_Binary_Modulus (Parent_Base));
elsif Is_Floating_Point_Type (Parent_Type) then
-- Digits of base type is always copied from the digits value of
-- the parent base type, but the digits of the derived type will
-- already have been set if there was a constraint present.
Set_Digits_Value (Implicit_Base, Digits_Value (Parent_Base));
Set_Vax_Float (Implicit_Base, Vax_Float (Parent_Base));
if No_Constraint then
Set_Digits_Value (Derived_Type, Digits_Value (Parent_Type));
end if;
elsif Is_Fixed_Point_Type (Parent_Type) then
-- Small of base type and derived type are always copied from
-- the parent base type, since smalls never change. The delta
-- of the base type is also copied from the parent base type.
-- However the delta of the derived type will have been set
-- already if a constraint was present.
Set_Small_Value (Derived_Type, Small_Value (Parent_Base));
Set_Small_Value (Implicit_Base, Small_Value (Parent_Base));
Set_Delta_Value (Implicit_Base, Delta_Value (Parent_Base));
if No_Constraint then
Set_Delta_Value (Derived_Type, Delta_Value (Parent_Type));
end if;
-- The scale and machine radix in the decimal case are always
-- copied from the parent base type.
if Is_Decimal_Fixed_Point_Type (Parent_Type) then
Set_Scale_Value (Derived_Type, Scale_Value (Parent_Base));
Set_Scale_Value (Implicit_Base, Scale_Value (Parent_Base));
Set_Machine_Radix_10
(Derived_Type, Machine_Radix_10 (Parent_Base));
Set_Machine_Radix_10
(Implicit_Base, Machine_Radix_10 (Parent_Base));
Set_Digits_Value (Implicit_Base, Digits_Value (Parent_Base));
if No_Constraint then
Set_Digits_Value (Derived_Type, Digits_Value (Parent_Base));
else
-- the analysis of the subtype_indication sets the
-- digits value of the derived type.
null;
end if;
end if;
end if;
-- The type of the bounds is that of the parent type, and they
-- must be converted to the derived type.
Convert_Scalar_Bounds (N, Parent_Type, Derived_Type, Loc);
-- The implicit_base should be frozen when the derived type is frozen,
-- but note that it is used in the conversions of the bounds. For
-- fixed types we delay the determination of the bounds until the proper
-- freezing point. For other numeric types this is rejected by GCC, for
-- reasons that are currently unclear (???), so we choose to freeze the
-- implicit base now. In the case of integers and floating point types
-- this is harmless because subsequent representation clauses cannot
-- affect anything, but it is still baffling that we cannot use the
-- same mechanism for all derived numeric types.
if Is_Fixed_Point_Type (Parent_Type) then
Conditional_Delay (Implicit_Base, Parent_Type);
else
Freeze_Before (N, Implicit_Base);
end if;
end Build_Derived_Numeric_Type;
--------------------------------
-- Build_Derived_Private_Type --
--------------------------------
procedure Build_Derived_Private_Type
(N : Node_Id;
Parent_Type : Entity_Id;
Derived_Type : Entity_Id;
Is_Completion : Boolean;
Derive_Subps : Boolean := True)
is
Der_Base : Entity_Id;
Discr : Entity_Id;
Full_Decl : Node_Id := Empty;
Full_Der : Entity_Id;
Full_P : Entity_Id;
Last_Discr : Entity_Id;
Par_Scope : constant Entity_Id := Scope (Base_Type (Parent_Type));
Swapped : Boolean := False;
procedure Copy_And_Build;
-- Copy derived type declaration, replace parent with its full view,
-- and analyze new declaration.
--------------------
-- Copy_And_Build --
--------------------
procedure Copy_And_Build is
Full_N : Node_Id;
begin
if Ekind (Parent_Type) in Record_Kind
or else (Ekind (Parent_Type) in Enumeration_Kind
and then Root_Type (Parent_Type) /= Standard_Character
and then Root_Type (Parent_Type) /= Standard_Wide_Character
and then not Is_Generic_Type (Root_Type (Parent_Type)))
then
Full_N := New_Copy_Tree (N);
Insert_After (N, Full_N);
Build_Derived_Type (
Full_N, Parent_Type, Full_Der, True, Derive_Subps => False);
else
Build_Derived_Type (
N, Parent_Type, Full_Der, True, Derive_Subps => False);
end if;
end Copy_And_Build;
-- Start of processing for Build_Derived_Private_Type
begin
if Is_Tagged_Type (Parent_Type) then
Build_Derived_Record_Type
(N, Parent_Type, Derived_Type, Derive_Subps);
return;
elsif Has_Discriminants (Parent_Type) then
if Present (Full_View (Parent_Type)) then
if not Is_Completion then
-- Copy declaration for subsequent analysis, to
-- provide a completion for what is a private
-- declaration.
Full_Decl := New_Copy_Tree (N);
Full_Der := New_Copy (Derived_Type);
Insert_After (N, Full_Decl);
else
-- If this is a completion, the full view being built is
-- itself private. We build a subtype of the parent with
-- the same constraints as this full view, to convey to the
-- back end the constrained components and the size of this
-- subtype. If the parent is constrained, its full view can
-- serve as the underlying full view of the derived type.
if No (Discriminant_Specifications (N)) then
if Nkind (Subtype_Indication (Type_Definition (N)))
= N_Subtype_Indication
then
Build_Underlying_Full_View (N, Derived_Type, Parent_Type);
elsif Is_Constrained (Full_View (Parent_Type)) then
Set_Underlying_Full_View (Derived_Type,
Full_View (Parent_Type));
end if;
else
-- If there are new discriminants, the parent subtype is
-- constrained by them, but it is not clear how to build
-- the underlying_full_view in this case ???
null;
end if;
end if;
end if;
-- Build partial view of derived type from partial view of parent.
Build_Derived_Record_Type
(N, Parent_Type, Derived_Type, Derive_Subps);
if Present (Full_View (Parent_Type))
and then not Is_Completion
then
if not In_Open_Scopes (Par_Scope)
or else not In_Same_Source_Unit (N, Parent_Type)
then
-- Swap partial and full views temporarily
Install_Private_Declarations (Par_Scope);
Install_Visible_Declarations (Par_Scope);
Swapped := True;
end if;
-- Build full view of derived type from full view of
-- parent which is now installed.
-- Subprograms have been derived on the partial view,
-- the completion does not derive them anew.
if not Is_Tagged_Type (Parent_Type) then
Build_Derived_Record_Type
(Full_Decl, Parent_Type, Full_Der, False);
else
-- If full view of parent is tagged, the completion
-- inherits the proper primitive operations.
Set_Defining_Identifier (Full_Decl, Full_Der);
Build_Derived_Record_Type
(Full_Decl, Parent_Type, Full_Der, Derive_Subps);
Set_Analyzed (Full_Decl);
end if;
if Swapped then
Uninstall_Declarations (Par_Scope);
if In_Open_Scopes (Par_Scope) then
Install_Visible_Declarations (Par_Scope);
end if;
end if;
Der_Base := Base_Type (Derived_Type);
Set_Full_View (Derived_Type, Full_Der);
Set_Full_View (Der_Base, Base_Type (Full_Der));
-- Copy the discriminant list from full view to
-- the partial views (base type and its subtype).
-- Gigi requires that the partial and full views
-- have the same discriminants.
-- ??? Note that since the partial view is pointing
-- to discriminants in the full view, their scope
-- will be that of the full view. This might
-- cause some front end problems and need
-- adjustment?
Discr := First_Discriminant (Base_Type (Full_Der));
Set_First_Entity (Der_Base, Discr);
loop
Last_Discr := Discr;
Next_Discriminant (Discr);
exit when No (Discr);
end loop;
Set_Last_Entity (Der_Base, Last_Discr);
Set_First_Entity (Derived_Type, First_Entity (Der_Base));
Set_Last_Entity (Derived_Type, Last_Entity (Der_Base));
else
-- If this is a completion, the derived type stays private
-- and there is no need to create a further full view, except
-- in the unusual case when the derivation is nested within a
-- child unit, see below.
null;
end if;
elsif Present (Full_View (Parent_Type))
and then Has_Discriminants (Full_View (Parent_Type))
then
if Has_Unknown_Discriminants (Parent_Type)
and then Nkind (Subtype_Indication (Type_Definition (N)))
= N_Subtype_Indication
then
Error_Msg_N
("cannot constrain type with unknown discriminants",
Subtype_Indication (Type_Definition (N)));
return;
end if;
-- If full view of parent is a record type, Build full view as
-- a derivation from the parent's full view. Partial view remains
-- private. For code generation and linking, the full view must
-- have the same public status as the partial one. This full view
-- is only needed if the parent type is in an enclosing scope, so
-- that the full view may actually become visible, e.g. in a child
-- unit. This is both more efficient, and avoids order of freezing
-- problems with the added entities.
if not Is_Private_Type (Full_View (Parent_Type))
and then (In_Open_Scopes (Scope (Parent_Type)))
then
Full_Der := Make_Defining_Identifier (Sloc (Derived_Type),
Chars (Derived_Type));
Set_Is_Itype (Full_Der);
Set_Has_Private_Declaration (Full_Der);
Set_Has_Private_Declaration (Derived_Type);
Set_Associated_Node_For_Itype (Full_Der, N);
Set_Parent (Full_Der, Parent (Derived_Type));
Set_Full_View (Derived_Type, Full_Der);
Set_Is_Public (Full_Der, Is_Public (Derived_Type));
Full_P := Full_View (Parent_Type);
Exchange_Declarations (Parent_Type);
Copy_And_Build;
Exchange_Declarations (Full_P);
else
Build_Derived_Record_Type
(N, Full_View (Parent_Type), Derived_Type,
Derive_Subps => False);
end if;
-- In any case, the primitive operations are inherited from
-- the parent type, not from the internal full view.
Set_Etype (Base_Type (Derived_Type), Base_Type (Parent_Type));
if Derive_Subps then
Derive_Subprograms (Parent_Type, Derived_Type);
end if;
else
-- Untagged type, No discriminants on either view
if Nkind (Subtype_Indication (Type_Definition (N)))
= N_Subtype_Indication
then
Error_Msg_N
("illegal constraint on type without discriminants", N);
end if;
if Present (Discriminant_Specifications (N))
and then Present (Full_View (Parent_Type))
and then not Is_Tagged_Type (Full_View (Parent_Type))
then
Error_Msg_N
("cannot add discriminants to untagged type", N);
end if;
Set_Stored_Constraint (Derived_Type, No_Elist);
Set_Is_Constrained (Derived_Type, Is_Constrained (Parent_Type));
Set_Is_Controlled (Derived_Type, Is_Controlled (Parent_Type));
Set_Has_Controlled_Component
(Derived_Type, Has_Controlled_Component
(Parent_Type));
-- Direct controlled types do not inherit Finalize_Storage_Only flag
if not Is_Controlled (Parent_Type) then
Set_Finalize_Storage_Only
(Base_Type (Derived_Type), Finalize_Storage_Only (Parent_Type));
end if;
-- Construct the implicit full view by deriving from full
-- view of the parent type. In order to get proper visibility,
-- we install the parent scope and its declarations.
-- ??? if the parent is untagged private and its
-- completion is tagged, this mechanism will not
-- work because we cannot derive from the tagged
-- full view unless we have an extension
if Present (Full_View (Parent_Type))
and then not Is_Tagged_Type (Full_View (Parent_Type))
and then not Is_Completion
then
Full_Der := Make_Defining_Identifier (Sloc (Derived_Type),
Chars (Derived_Type));
Set_Is_Itype (Full_Der);
Set_Has_Private_Declaration (Full_Der);
Set_Has_Private_Declaration (Derived_Type);
Set_Associated_Node_For_Itype (Full_Der, N);
Set_Parent (Full_Der, Parent (Derived_Type));
Set_Full_View (Derived_Type, Full_Der);
if not In_Open_Scopes (Par_Scope) then
Install_Private_Declarations (Par_Scope);
Install_Visible_Declarations (Par_Scope);
Copy_And_Build;
Uninstall_Declarations (Par_Scope);
-- If parent scope is open and in another unit, and
-- parent has a completion, then the derivation is taking
-- place in the visible part of a child unit. In that
-- case retrieve the full view of the parent momentarily.
elsif not In_Same_Source_Unit (N, Parent_Type) then
Full_P := Full_View (Parent_Type);
Exchange_Declarations (Parent_Type);
Copy_And_Build;
Exchange_Declarations (Full_P);
-- Otherwise it is a local derivation.
else
Copy_And_Build;
end if;
Set_Scope (Full_Der, Current_Scope);
Set_Is_First_Subtype (Full_Der,
Is_First_Subtype (Derived_Type));
Set_Has_Size_Clause (Full_Der, False);
Set_Has_Alignment_Clause (Full_Der, False);
Set_Next_Entity (Full_Der, Empty);
Set_Has_Delayed_Freeze (Full_Der);
Set_Is_Frozen (Full_Der, False);
Set_Freeze_Node (Full_Der, Empty);
Set_Depends_On_Private (Full_Der,
Has_Private_Component (Full_Der));
Set_Public_Status (Full_Der);
end if;
end if;
Set_Has_Unknown_Discriminants (Derived_Type,
Has_Unknown_Discriminants (Parent_Type));
if Is_Private_Type (Derived_Type) then
Set_Private_Dependents (Derived_Type, New_Elmt_List);
end if;
if Is_Private_Type (Parent_Type)
and then Base_Type (Parent_Type) = Parent_Type
and then In_Open_Scopes (Scope (Parent_Type))
then
Append_Elmt (Derived_Type, Private_Dependents (Parent_Type));
if Is_Child_Unit (Scope (Current_Scope))
and then Is_Completion
and then In_Private_Part (Current_Scope)
and then Scope (Parent_Type) /= Current_Scope
then
-- This is the unusual case where a type completed by a private
-- derivation occurs within a package nested in a child unit,
-- and the parent is declared in an ancestor. In this case, the
-- full view of the parent type will become visible in the body
-- of the enclosing child, and only then will the current type
-- be possibly non-private. We build a underlying full view that
-- will be installed when the enclosing child body is compiled.
declare
IR : constant Node_Id := Make_Itype_Reference (Sloc (N));
begin
Full_Der :=
Make_Defining_Identifier (Sloc (Derived_Type),
Chars (Derived_Type));
Set_Is_Itype (Full_Der);
Set_Itype (IR, Full_Der);
Insert_After (N, IR);
-- The full view will be used to swap entities on entry/exit
-- to the body, and must appear in the entity list for the
-- package.
Append_Entity (Full_Der, Scope (Derived_Type));
Set_Has_Private_Declaration (Full_Der);
Set_Has_Private_Declaration (Derived_Type);
Set_Associated_Node_For_Itype (Full_Der, N);
Set_Parent (Full_Der, Parent (Derived_Type));
Full_P := Full_View (Parent_Type);
Exchange_Declarations (Parent_Type);
Copy_And_Build;
Exchange_Declarations (Full_P);
Set_Underlying_Full_View (Derived_Type, Full_Der);
end;
end if;
end if;
end Build_Derived_Private_Type;
-------------------------------
-- Build_Derived_Record_Type --
-------------------------------
-- 1. INTRODUCTION.
-- Ideally we would like to use the same model of type derivation for
-- tagged and untagged record types. Unfortunately this is not quite
-- possible because the semantics of representation clauses is different
-- for tagged and untagged records under inheritance. Consider the
-- following:
-- type R (...) is [tagged] record ... end record;
-- type T (...) is new R (...) [with ...];
-- The representation clauses of T can specify a completely different
-- record layout from R's. Hence the same component can be placed in
-- two very different positions in objects of type T and R. If R and T
-- are tagged types, representation clauses for T can only specify the
-- layout of non inherited components, thus components that are common
-- in R and T have the same position in objects of type R and T.
-- This has two implications. The first is that the entire tree for R's
-- declaration needs to be copied for T in the untagged case, so that
-- T can be viewed as a record type of its own with its own representation
-- clauses. The second implication is the way we handle discriminants.
-- Specifically, in the untagged case we need a way to communicate to Gigi
-- what are the real discriminants in the record, while for the semantics
-- we need to consider those introduced by the user to rename the
-- discriminants in the parent type. This is handled by introducing the
-- notion of stored discriminants. See below for more.
-- Fortunately the way regular components are inherited can be handled in
-- the same way in tagged and untagged types.
-- To complicate things a bit more the private view of a private extension
-- cannot be handled in the same way as the full view (for one thing the
-- semantic rules are somewhat different). We will explain what differs
-- below.
-- 2. DISCRIMINANTS UNDER INHERITANCE.
-- The semantic rules governing the discriminants of derived types are
-- quite subtle.
-- type Derived_Type_Name [KNOWN_DISCRIMINANT_PART] is new
-- [abstract] Parent_Type_Name [CONSTRAINT] [RECORD_EXTENSION_PART]
-- If parent type has discriminants, then the discriminants that are
-- declared in the derived type are [3.4 (11)]:
-- o The discriminants specified by a new KNOWN_DISCRIMINANT_PART, if
-- there is one;
-- o Otherwise, each discriminant of the parent type (implicitly
-- declared in the same order with the same specifications). In this
-- case, the discriminants are said to be "inherited", or if unknown in
-- the parent are also unknown in the derived type.
-- Furthermore if a KNOWN_DISCRIMINANT_PART is provided, then [3.7(13-18)]:
-- o The parent subtype shall be constrained;
-- o If the parent type is not a tagged type, then each discriminant of
-- the derived type shall be used in the constraint defining a parent
-- subtype [Implementation note: this ensures that the new discriminant
-- can share storage with an existing discriminant.].
-- For the derived type each discriminant of the parent type is either
-- inherited, constrained to equal some new discriminant of the derived
-- type, or constrained to the value of an expression.
-- When inherited or constrained to equal some new discriminant, the
-- parent discriminant and the discriminant of the derived type are said
-- to "correspond".
-- If a discriminant of the parent type is constrained to a specific value
-- in the derived type definition, then the discriminant is said to be
-- "specified" by that derived type definition.
-- 3. DISCRIMINANTS IN DERIVED UNTAGGED RECORD TYPES.
-- We have spoken about stored discriminants in point 1 (introduction)
-- above. There are two sort of stored discriminants: implicit and
-- explicit. As long as the derived type inherits the same discriminants as
-- the root record type, stored discriminants are the same as regular
-- discriminants, and are said to be implicit. However, if any discriminant
-- in the root type was renamed in the derived type, then the derived
-- type will contain explicit stored discriminants. Explicit stored
-- discriminants are discriminants in addition to the semantically visible
-- discriminants defined for the derived type. Stored discriminants are
-- used by Gigi to figure out what are the physical discriminants in
-- objects of the derived type (see precise definition in einfo.ads).
-- As an example, consider the following:
-- type R (D1, D2, D3 : Int) is record ... end record;
-- type T1 is new R;
-- type T2 (X1, X2: Int) is new T1 (X2, 88, X1);
-- type T3 is new T2;
-- type T4 (Y : Int) is new T3 (Y, 99);
-- The following table summarizes the discriminants and stored
-- discriminants in R and T1 through T4.
-- Type Discrim Stored Discrim Comment
-- R (D1, D2, D3) (D1, D2, D3) Gider discrims are implicit in R
-- T1 (D1, D2, D3) (D1, D2, D3) Gider discrims are implicit in T1
-- T2 (X1, X2) (D1, D2, D3) Gider discrims are EXPLICIT in T2
-- T3 (X1, X2) (D1, D2, D3) Gider discrims are EXPLICIT in T3
-- T4 (Y) (D1, D2, D3) Gider discrims are EXPLICIT in T4
-- Field Corresponding_Discriminant (abbreviated CD below) allows to find
-- the corresponding discriminant in the parent type, while
-- Original_Record_Component (abbreviated ORC below), the actual physical
-- component that is renamed. Finally the field Is_Completely_Hidden
-- (abbreviated ICH below) is set for all explicit stored discriminants
-- (see einfo.ads for more info). For the above example this gives:
-- Discrim CD ORC ICH
-- ^^^^^^^ ^^ ^^^ ^^^
-- D1 in R empty itself no
-- D2 in R empty itself no
-- D3 in R empty itself no
-- D1 in T1 D1 in R itself no
-- D2 in T1 D2 in R itself no
-- D3 in T1 D3 in R itself no
-- X1 in T2 D3 in T1 D3 in T2 no
-- X2 in T2 D1 in T1 D1 in T2 no
-- D1 in T2 empty itself yes
-- D2 in T2 empty itself yes
-- D3 in T2 empty itself yes
-- X1 in T3 X1 in T2 D3 in T3 no
-- X2 in T3 X2 in T2 D1 in T3 no
-- D1 in T3 empty itself yes
-- D2 in T3 empty itself yes
-- D3 in T3 empty itself yes
-- Y in T4 X1 in T3 D3 in T3 no
-- D1 in T3 empty itself yes
-- D2 in T3 empty itself yes
-- D3 in T3 empty itself yes
-- 4. DISCRIMINANTS IN DERIVED TAGGED RECORD TYPES.
-- Type derivation for tagged types is fairly straightforward. if no
-- discriminants are specified by the derived type, these are inherited
-- from the parent. No explicit stored discriminants are ever necessary.
-- The only manipulation that is done to the tree is that of adding a
-- _parent field with parent type and constrained to the same constraint
-- specified for the parent in the derived type definition. For instance:
-- type R (D1, D2, D3 : Int) is tagged record ... end record;
-- type T1 is new R with null record;
-- type T2 (X1, X2: Int) is new T1 (X2, 88, X1) with null record;
-- are changed into :
-- type T1 (D1, D2, D3 : Int) is new R (D1, D2, D3) with record
-- _parent : R (D1, D2, D3);
-- end record;
-- type T2 (X1, X2: Int) is new T1 (X2, 88, X1) with record
-- _parent : T1 (X2, 88, X1);
-- end record;
-- The discriminants actually present in R, T1 and T2 as well as their CD,
-- ORC and ICH fields are:
-- Discrim CD ORC ICH
-- ^^^^^^^ ^^ ^^^ ^^^
-- D1 in R empty itself no
-- D2 in R empty itself no
-- D3 in R empty itself no
-- D1 in T1 D1 in R D1 in R no
-- D2 in T1 D2 in R D2 in R no
-- D3 in T1 D3 in R D3 in R no
-- X1 in T2 D3 in T1 D3 in R no
-- X2 in T2 D1 in T1 D1 in R no
-- 5. FIRST TRANSFORMATION FOR DERIVED RECORDS.
--
-- Regardless of whether we dealing with a tagged or untagged type
-- we will transform all derived type declarations of the form
--
-- type T is new R (...) [with ...];
-- or
-- subtype S is R (...);
-- type T is new S [with ...];
-- into
--