blob: 3c55dda5a85666d52d2087e10b54470d6b5f6854 [file] [log] [blame]
------------------------------------------------------------------------------
-- --
-- GNAT COMPILER COMPONENTS --
-- --
-- S E M _ U T I L --
-- --
-- B o d y --
-- --
-- Copyright (C) 1992-2022, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
-- ware Foundation; either version 3, or (at your option) any later ver- --
-- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
-- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
-- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
-- for more details. You should have received a copy of the GNU General --
-- Public License distributed with GNAT; see file COPYING3. If not, go to --
-- http://www.gnu.org/licenses for a complete copy of the license. --
-- --
-- GNAT was originally developed by the GNAT team at New York University. --
-- Extensive contributions were provided by Ada Core Technologies Inc. --
-- --
------------------------------------------------------------------------------
with Casing; use Casing;
with Checks; use Checks;
with Debug; use Debug;
with Einfo.Utils; use Einfo.Utils;
with Elists; use Elists;
with Errout; use Errout;
with Erroutc; use Erroutc;
with Exp_Ch3; use Exp_Ch3;
with Exp_Ch11; use Exp_Ch11;
with Exp_Util; use Exp_Util;
with Fname; use Fname;
with Freeze; use Freeze;
with Itypes; use Itypes;
with Lib; use Lib;
with Lib.Xref; use Lib.Xref;
with Namet.Sp; use Namet.Sp;
with Nlists; use Nlists;
with Nmake; use Nmake;
with Output; use Output;
with Restrict; use Restrict;
with Rident; use Rident;
with Rtsfind; use Rtsfind;
with Sem; use Sem;
with Sem_Aux; use Sem_Aux;
with Sem_Attr; use Sem_Attr;
with Sem_Cat; use Sem_Cat;
with Sem_Ch6; use Sem_Ch6;
with Sem_Ch8; use Sem_Ch8;
with Sem_Ch13; use Sem_Ch13;
with Sem_Disp; use Sem_Disp;
with Sem_Elab; use Sem_Elab;
with Sem_Eval; use Sem_Eval;
with Sem_Prag; use Sem_Prag;
with Sem_Res; use Sem_Res;
with Sem_Warn; use Sem_Warn;
with Sem_Type; use Sem_Type;
with Sinfo; use Sinfo;
with Sinfo.Nodes; use Sinfo.Nodes;
with Sinfo.Utils; use Sinfo.Utils;
with Sinput; use Sinput;
with Stand; use Stand;
with Style;
with Stringt; use Stringt;
with Targparm; use Targparm;
with Tbuild; use Tbuild;
with Ttypes; use Ttypes;
with Uname; use Uname;
with GNAT.Heap_Sort_G;
with GNAT.HTable; use GNAT.HTable;
package body Sem_Util is
---------------------------
-- Local Data Structures --
---------------------------
Invalid_Binder_Values : array (Scalar_Id) of Entity_Id := (others => Empty);
-- A collection to hold the entities of the variables declared in package
-- System.Scalar_Values which describe the invalid values of scalar types.
Invalid_Binder_Values_Set : Boolean := False;
-- This flag prevents multiple attempts to initialize Invalid_Binder_Values
Invalid_Floats : array (Float_Scalar_Id) of Ureal := (others => No_Ureal);
-- A collection to hold the invalid values of float types as specified by
-- pragma Initialize_Scalars.
Invalid_Integers : array (Integer_Scalar_Id) of Uint := (others => No_Uint);
-- A collection to hold the invalid values of integer types as specified
-- by pragma Initialize_Scalars.
-----------------------
-- Local Subprograms --
-----------------------
function Build_Component_Subtype
(C : List_Id;
Loc : Source_Ptr;
T : Entity_Id) return Node_Id;
-- This function builds the subtype for Build_Actual_Subtype_Of_Component
-- and Build_Discriminal_Subtype_Of_Component. C is a list of constraints,
-- Loc is the source location, T is the original subtype.
procedure Examine_Array_Bounds
(Typ : Entity_Id;
All_Static : out Boolean;
Has_Empty : out Boolean);
-- Inspect the index constraints of array type Typ. Flag All_Static is set
-- when all ranges are static. Flag Has_Empty is set only when All_Static
-- is set and indicates that at least one range is empty.
function Has_Enabled_Property
(Item_Id : Entity_Id;
Property : Name_Id) return Boolean;
-- Subsidiary to routines Async_xxx_Enabled and Effective_xxx_Enabled.
-- Determine whether the state abstraction, object, or type denoted by
-- entity Item_Id has enabled property Property.
function Has_Null_Extension (T : Entity_Id) return Boolean;
-- T is a derived tagged type. Check whether the type extension is null.
-- If the parent type is fully initialized, T can be treated as such.
function Is_Atomic_Object_Entity (Id : Entity_Id) return Boolean;
-- Determine whether arbitrary entity Id denotes an atomic object as per
-- RM C.6(7).
function Is_Container_Aggregate (Exp : Node_Id) return Boolean;
-- Is the given expression a container aggregate?
generic
with function Is_Effectively_Volatile_Entity
(Id : Entity_Id) return Boolean;
-- Function to use on object and type entities
function Is_Effectively_Volatile_Object_Shared
(N : Node_Id) return Boolean;
-- Shared function used to detect effectively volatile objects and
-- effectively volatile objects for reading.
function Is_Fully_Initialized_Variant (Typ : Entity_Id) return Boolean;
-- Subsidiary to Is_Fully_Initialized_Type. For an unconstrained type
-- with discriminants whose default values are static, examine only the
-- components in the selected variant to determine whether all of them
-- have a default.
function Is_Preelaborable_Function (Id : Entity_Id) return Boolean;
-- Ada 2022: Determine whether the specified function is suitable as the
-- name of a call in a preelaborable construct (RM 10.2.1(7/5)).
type Null_Status_Kind is
(Is_Null,
-- This value indicates that a subexpression is known to have a null
-- value at compile time.
Is_Non_Null,
-- This value indicates that a subexpression is known to have a non-null
-- value at compile time.
Unknown);
-- This value indicates that it cannot be determined at compile time
-- whether a subexpression yields a null or non-null value.
function Null_Status (N : Node_Id) return Null_Status_Kind;
-- Determine whether subexpression N of an access type yields a null value,
-- a non-null value, or the value cannot be determined at compile time. The
-- routine does not take simple flow diagnostics into account, it relies on
-- static facts such as the presence of null exclusions.
function Subprogram_Name (N : Node_Id) return String;
-- Return the fully qualified name of the enclosing subprogram for the
-- given node N, with file:line:col information appended, e.g.
-- "subp:file:line:col", corresponding to the source location of the
-- body of the subprogram.
-----------------------------
-- Abstract_Interface_List --
-----------------------------
function Abstract_Interface_List (Typ : Entity_Id) return List_Id is
Nod : Node_Id;
begin
if Is_Concurrent_Type (Typ) then
-- If we are dealing with a synchronized subtype, go to the base
-- type, whose declaration has the interface list.
Nod := Declaration_Node (Base_Type (Typ));
if Nkind (Nod) in N_Full_Type_Declaration | N_Private_Type_Declaration
then
return Empty_List;
end if;
elsif Ekind (Typ) = E_Record_Type_With_Private then
if Nkind (Parent (Typ)) = N_Full_Type_Declaration then
Nod := Type_Definition (Parent (Typ));
elsif Nkind (Parent (Typ)) = N_Private_Type_Declaration then
if Present (Full_View (Typ))
and then
Nkind (Parent (Full_View (Typ))) = N_Full_Type_Declaration
then
Nod := Type_Definition (Parent (Full_View (Typ)));
-- If the full-view is not available we cannot do anything else
-- here (the source has errors).
else
return Empty_List;
end if;
-- Support for generic formals with interfaces is still missing ???
elsif Nkind (Parent (Typ)) = N_Formal_Type_Declaration then
return Empty_List;
else
pragma Assert
(Nkind (Parent (Typ)) = N_Private_Extension_Declaration);
Nod := Parent (Typ);
end if;
elsif Ekind (Typ) = E_Record_Subtype then
Nod := Type_Definition (Parent (Etype (Typ)));
elsif Ekind (Typ) = E_Record_Subtype_With_Private then
-- Recurse, because parent may still be a private extension. Also
-- note that the full view of the subtype or the full view of its
-- base type may (both) be unavailable.
return Abstract_Interface_List (Etype (Typ));
elsif Ekind (Typ) = E_Record_Type then
if Nkind (Parent (Typ)) = N_Formal_Type_Declaration then
Nod := Formal_Type_Definition (Parent (Typ));
else
Nod := Type_Definition (Parent (Typ));
end if;
-- Otherwise the type is of a kind which does not implement interfaces
else
return Empty_List;
end if;
return Interface_List (Nod);
end Abstract_Interface_List;
-------------------------
-- Accessibility_Level --
-------------------------
function Accessibility_Level
(Expr : Node_Id;
Level : Accessibility_Level_Kind;
In_Return_Context : Boolean := False;
Allow_Alt_Model : Boolean := True) return Node_Id
is
Loc : constant Source_Ptr := Sloc (Expr);
function Accessibility_Level (Expr : Node_Id) return Node_Id
is (Accessibility_Level (Expr, Level, In_Return_Context));
-- Renaming of the enclosing function to facilitate recursive calls
function Make_Level_Literal (Level : Uint) return Node_Id;
-- Construct an integer literal representing an accessibility level
-- with its type set to Natural.
function Innermost_Master_Scope_Depth (N : Node_Id) return Uint;
-- Returns the scope depth of the given node's innermost
-- enclosing dynamic scope (effectively the accessibility
-- level of the innermost enclosing master).
function Function_Call_Or_Allocator_Level (N : Node_Id) return Node_Id;
-- Centralized processing of subprogram calls which may appear in
-- prefix notation.
function Typ_Access_Level (Typ : Entity_Id) return Uint
is (Type_Access_Level (Typ, Allow_Alt_Model));
-- Renaming of Type_Access_Level with Allow_Alt_Model specified to avoid
-- passing the parameter specifically in every call.
----------------------------------
-- Innermost_Master_Scope_Depth --
----------------------------------
function Innermost_Master_Scope_Depth (N : Node_Id) return Uint is
Encl_Scop : Entity_Id;
Ent : Entity_Id;
Node_Par : Node_Id := Parent (N);
Master_Lvl_Modifier : Int := 0;
begin
-- Locate the nearest enclosing node (by traversing Parents)
-- that Defining_Entity can be applied to, and return the
-- depth of that entity's nearest enclosing dynamic scope.
-- The rules that define what a master are defined in
-- RM 7.6.1 (3), and include statements and conditions for loops
-- among other things. These cases are detected properly ???
while Present (Node_Par) loop
Ent := Defining_Entity_Or_Empty (Node_Par);
if Present (Ent) then
Encl_Scop := Nearest_Dynamic_Scope (Ent);
-- Ignore transient scopes made during expansion
if Comes_From_Source (Node_Par) then
return
Scope_Depth_Default_0 (Encl_Scop) + Master_Lvl_Modifier;
end if;
-- For a return statement within a function, return
-- the depth of the function itself. This is not just
-- a small optimization, but matters when analyzing
-- the expression in an expression function before
-- the body is created.
elsif Nkind (Node_Par) in N_Extended_Return_Statement
| N_Simple_Return_Statement
and then Ekind (Current_Scope) = E_Function
then
return Scope_Depth (Current_Scope);
-- Statements are counted as masters
elsif Is_Master (Node_Par) then
Master_Lvl_Modifier := Master_Lvl_Modifier + 1;
end if;
Node_Par := Parent (Node_Par);
end loop;
-- Should never reach the following return
pragma Assert (False);
return Scope_Depth (Current_Scope) + 1;
end Innermost_Master_Scope_Depth;
------------------------
-- Make_Level_Literal --
------------------------
function Make_Level_Literal (Level : Uint) return Node_Id is
Result : constant Node_Id := Make_Integer_Literal (Loc, Level);
begin
Set_Etype (Result, Standard_Natural);
return Result;
end Make_Level_Literal;
--------------------------------------
-- Function_Call_Or_Allocator_Level --
--------------------------------------
function Function_Call_Or_Allocator_Level (N : Node_Id) return Node_Id is
Par : Node_Id;
Prev_Par : Node_Id;
begin
-- Results of functions are objects, so we either get the
-- accessibility of the function or, in case of a call which is
-- indirect, the level of the access-to-subprogram type.
-- This code looks wrong ???
if Nkind (N) = N_Function_Call
and then Ada_Version < Ada_2005
then
if Is_Entity_Name (Name (N)) then
return Make_Level_Literal
(Subprogram_Access_Level (Entity (Name (N))));
else
return Make_Level_Literal
(Typ_Access_Level (Etype (Prefix (Name (N)))));
end if;
-- We ignore coextensions as they cannot be implemented under the
-- "small-integer" model.
elsif Nkind (N) = N_Allocator
and then (Is_Static_Coextension (N)
or else Is_Dynamic_Coextension (N))
then
return Make_Level_Literal (Scope_Depth (Standard_Standard));
end if;
-- Named access types have a designated level
if Is_Named_Access_Type (Etype (N)) then
return Make_Level_Literal (Typ_Access_Level (Etype (N)));
-- Otherwise, the level is dictated by RM 3.10.2 (10.7/3)
else
-- Check No_Dynamic_Accessibility_Checks restriction override for
-- alternative accessibility model.
if Allow_Alt_Model
and then No_Dynamic_Accessibility_Checks_Enabled (N)
and then Is_Anonymous_Access_Type (Etype (N))
then
-- In the alternative model the level is that of the
-- designated type.
if Debug_Flag_Underscore_B then
return Make_Level_Literal (Typ_Access_Level (Etype (N)));
-- For function calls the level is that of the innermost
-- master, otherwise (for allocators etc.) we get the level
-- of the corresponding anonymous access type, which is
-- calculated through the normal path of execution.
elsif Nkind (N) = N_Function_Call then
return Make_Level_Literal
(Innermost_Master_Scope_Depth (Expr));
end if;
end if;
if Nkind (N) = N_Function_Call then
-- Dynamic checks are generated when we are within a return
-- value or we are in a function call within an anonymous
-- access discriminant constraint of a return object (signified
-- by In_Return_Context) on the side of the callee.
-- So, in this case, return accessibility level of the
-- enclosing subprogram.
if In_Return_Value (N)
or else In_Return_Context
then
return Make_Level_Literal
(Subprogram_Access_Level (Current_Subprogram));
end if;
end if;
-- When the call is being dereferenced the level is that of the
-- enclosing master of the dereferenced call.
if Nkind (Parent (N)) in N_Explicit_Dereference
| N_Indexed_Component
| N_Selected_Component
then
return Make_Level_Literal
(Innermost_Master_Scope_Depth (Expr));
end if;
-- Find any relevant enclosing parent nodes that designate an
-- object being initialized.
-- Note: The above is only relevant if the result is used "in its
-- entirety" as RM 3.10.2 (10.2/3) states. However, this is
-- accounted for in the case statement in the main body of
-- Accessibility_Level for N_Selected_Component.
Par := Parent (Expr);
Prev_Par := Empty;
while Present (Par) loop
-- Detect an expanded implicit conversion, typically this
-- occurs on implicitly converted actuals in calls.
-- Does this catch all implicit conversions ???
if Nkind (Par) = N_Type_Conversion
and then Is_Named_Access_Type (Etype (Par))
then
return Make_Level_Literal
(Typ_Access_Level (Etype (Par)));
end if;
-- Jump out when we hit an object declaration or the right-hand
-- side of an assignment, or a construct such as an aggregate
-- subtype indication which would be the result is not used
-- "in its entirety."
exit when Nkind (Par) in N_Object_Declaration
or else (Nkind (Par) = N_Assignment_Statement
and then Name (Par) /= Prev_Par);
Prev_Par := Par;
Par := Parent (Par);
end loop;
-- Assignment statements are handled in a similar way in
-- accordance to the left-hand part. However, strictly speaking,
-- this is illegal according to the RM, but this change is needed
-- to pass an ACATS C-test and is useful in general ???
case Nkind (Par) is
when N_Object_Declaration =>
return Make_Level_Literal
(Scope_Depth
(Scope (Defining_Identifier (Par))));
when N_Assignment_Statement =>
-- Return the accessibility level of the left-hand part
return Accessibility_Level
(Expr => Name (Par),
Level => Object_Decl_Level,
In_Return_Context => In_Return_Context);
when others =>
return Make_Level_Literal
(Innermost_Master_Scope_Depth (Expr));
end case;
end if;
end Function_Call_Or_Allocator_Level;
-- Local variables
E : Entity_Id := Original_Node (Expr);
Pre : Node_Id;
-- Start of processing for Accessibility_Level
begin
-- We could be looking at a reference to a formal due to the expansion
-- of entries and other cases, so obtain the renaming if necessary.
if Present (Param_Entity (Expr)) then
E := Param_Entity (Expr);
end if;
-- Extract the entity
if Nkind (E) in N_Has_Entity and then Present (Entity (E)) then
E := Entity (E);
-- Deal with a possible renaming of a private protected component
if Ekind (E) in E_Constant | E_Variable and then Is_Prival (E) then
E := Prival_Link (E);
end if;
end if;
-- Perform the processing on the expression
case Nkind (E) is
-- The level of an aggregate is that of the innermost master that
-- evaluates it as defined in RM 3.10.2 (10/4).
when N_Aggregate =>
return Make_Level_Literal (Innermost_Master_Scope_Depth (Expr));
-- The accessibility level is that of the access type, except for an
-- anonymous allocators which have special rules defined in RM 3.10.2
-- (14/3).
when N_Allocator =>
return Function_Call_Or_Allocator_Level (E);
-- We could reach this point for two reasons. Either the expression
-- applies to a special attribute ('Loop_Entry, 'Result, or 'Old), or
-- we are looking at the access attributes directly ('Access,
-- 'Address, or 'Unchecked_Access).
when N_Attribute_Reference =>
Pre := Original_Node (Prefix (E));
-- Regular 'Access attribute presence means we have to look at the
-- prefix.
if Attribute_Name (E) = Name_Access then
return Accessibility_Level (Prefix (E));
-- Unchecked or unrestricted attributes have unlimited depth
elsif Attribute_Name (E) in Name_Address
| Name_Unchecked_Access
| Name_Unrestricted_Access
then
return Make_Level_Literal (Scope_Depth (Standard_Standard));
-- 'Access can be taken further against other special attributes,
-- so handle these cases explicitly.
elsif Attribute_Name (E)
in Name_Old | Name_Loop_Entry | Name_Result
then
-- Named access types
if Is_Named_Access_Type (Etype (Pre)) then
return Make_Level_Literal
(Typ_Access_Level (Etype (Pre)));
-- Anonymous access types
elsif Nkind (Pre) in N_Has_Entity
and then Present (Get_Dynamic_Accessibility (Entity (Pre)))
and then Level = Dynamic_Level
then
return New_Occurrence_Of
(Get_Dynamic_Accessibility (Entity (Pre)), Loc);
-- Otherwise the level is treated in a similar way as
-- aggregates according to RM 6.1.1 (35.1/4) which concerns
-- an implicit constant declaration - in turn defining the
-- accessibility level to be that of the implicit constant
-- declaration.
else
return Make_Level_Literal
(Innermost_Master_Scope_Depth (Expr));
end if;
else
raise Program_Error;
end if;
-- This is the "base case" for accessibility level calculations which
-- means we are near the end of our recursive traversal.
when N_Defining_Identifier =>
-- A dynamic check is performed on the side of the callee when we
-- are within a return statement, so return a library-level
-- accessibility level to null out checks on the side of the
-- caller.
if Is_Explicitly_Aliased (E)
and then (In_Return_Context
or else (Level /= Dynamic_Level
and then In_Return_Value (Expr)))
then
return Make_Level_Literal (Scope_Depth (Standard_Standard));
-- Something went wrong and an extra accessibility formal has not
-- been generated when one should have ???
elsif Is_Formal (E)
and then not Present (Get_Dynamic_Accessibility (E))
and then Ekind (Etype (E)) = E_Anonymous_Access_Type
then
return Make_Level_Literal (Scope_Depth (Standard_Standard));
-- Stand-alone object of an anonymous access type "SAOAAT"
elsif (Is_Formal (E)
or else Ekind (E) in E_Variable
| E_Constant)
and then Present (Get_Dynamic_Accessibility (E))
and then (Level = Dynamic_Level
or else Level = Zero_On_Dynamic_Level)
then
if Level = Zero_On_Dynamic_Level then
return Make_Level_Literal
(Scope_Depth (Standard_Standard));
end if;
-- No_Dynamic_Accessibility_Checks restriction override for
-- alternative accessibility model.
if Allow_Alt_Model
and then No_Dynamic_Accessibility_Checks_Enabled (E)
then
-- In the alternative model the level is that of the
-- designated type entity's context.
if Debug_Flag_Underscore_B then
return Make_Level_Literal (Typ_Access_Level (Etype (E)));
-- Otherwise the level depends on the entity's context
elsif Is_Formal (E) then
return Make_Level_Literal
(Subprogram_Access_Level
(Enclosing_Subprogram (E)));
else
return Make_Level_Literal
(Scope_Depth (Enclosing_Dynamic_Scope (E)));
end if;
end if;
-- Return the dynamic level in the normal case
return New_Occurrence_Of
(Get_Dynamic_Accessibility (E), Loc);
-- Initialization procedures have a special extra accessibility
-- parameter associated with the level at which the object
-- being initialized exists
elsif Ekind (E) = E_Record_Type
and then Is_Limited_Record (E)
and then Current_Scope = Init_Proc (E)
and then Present (Init_Proc_Level_Formal (Current_Scope))
then
return New_Occurrence_Of
(Init_Proc_Level_Formal (Current_Scope), Loc);
-- Current instance of the type is deeper than that of the type
-- according to RM 3.10.2 (21).
elsif Is_Type (E) then
-- When restriction No_Dynamic_Accessibility_Checks is active
-- along with -gnatd_b.
if Allow_Alt_Model
and then No_Dynamic_Accessibility_Checks_Enabled (E)
and then Debug_Flag_Underscore_B
then
return Make_Level_Literal (Typ_Access_Level (E));
end if;
-- Normal path
return Make_Level_Literal (Typ_Access_Level (E) + 1);
-- Move up the renamed entity or object if it came from source
-- since expansion may have created a dummy renaming under
-- certain circumstances.
-- Note: We check if the original node of the renaming comes
-- from source because the node may have been rewritten.
elsif Present (Renamed_Entity_Or_Object (E))
and then Comes_From_Source
(Original_Node (Renamed_Entity_Or_Object (E)))
then
return Accessibility_Level (Renamed_Entity_Or_Object (E));
-- Named access types get their level from their associated type
elsif Is_Named_Access_Type (Etype (E)) then
return Make_Level_Literal
(Typ_Access_Level (Etype (E)));
-- Check if E is an expansion-generated renaming of an iterator
-- by examining Related_Expression. If so, determine the
-- accessibility level based on the original expression.
elsif Ekind (E) in E_Constant | E_Variable
and then Present (Related_Expression (E))
then
return Accessibility_Level (Related_Expression (E));
elsif Level = Dynamic_Level
and then Ekind (E) in E_In_Parameter | E_In_Out_Parameter
and then Present (Init_Proc_Level_Formal (Scope (E)))
then
return New_Occurrence_Of
(Init_Proc_Level_Formal (Scope (E)), Loc);
-- Normal object - get the level of the enclosing scope
else
return Make_Level_Literal
(Scope_Depth (Enclosing_Dynamic_Scope (E)));
end if;
-- Handle indexed and selected components including the special cases
-- whereby there is an implicit dereference, a component of a
-- composite type, or a function call in prefix notation.
-- We don't handle function calls in prefix notation correctly ???
when N_Indexed_Component | N_Selected_Component =>
Pre := Original_Node (Prefix (E));
-- When E is an indexed component or selected component and
-- the current Expr is a function call, we know that we are
-- looking at an expanded call in prefix notation.
if Nkind (Expr) = N_Function_Call then
return Function_Call_Or_Allocator_Level (Expr);
-- If the prefix is a named access type, then we are dealing
-- with an implicit deferences. In that case the level is that
-- of the named access type in the prefix.
elsif Is_Named_Access_Type (Etype (Pre)) then
return Make_Level_Literal
(Typ_Access_Level (Etype (Pre)));
-- The current expression is a named access type, so there is no
-- reason to look at the prefix. Instead obtain the level of E's
-- named access type.
elsif Is_Named_Access_Type (Etype (E)) then
return Make_Level_Literal
(Typ_Access_Level (Etype (E)));
-- A nondiscriminant selected component where the component
-- is an anonymous access type means that its associated
-- level is that of the containing type - see RM 3.10.2 (16).
-- Note that when restriction No_Dynamic_Accessibility_Checks is
-- in effect we treat discriminant components as regular
-- components.
elsif Nkind (E) = N_Selected_Component
and then Ekind (Etype (E)) = E_Anonymous_Access_Type
and then Ekind (Etype (Pre)) /= E_Anonymous_Access_Type
and then (not (Nkind (Selector_Name (E)) in N_Has_Entity
and then Ekind (Entity (Selector_Name (E)))
= E_Discriminant)
-- The alternative accessibility models both treat
-- discriminants as regular components.
or else (No_Dynamic_Accessibility_Checks_Enabled (E)
and then Allow_Alt_Model))
then
-- When restriction No_Dynamic_Accessibility_Checks is active
-- and -gnatd_b set, the level is that of the designated type.
if Allow_Alt_Model
and then No_Dynamic_Accessibility_Checks_Enabled (E)
and then Debug_Flag_Underscore_B
then
return Make_Level_Literal
(Typ_Access_Level (Etype (E)));
end if;
-- Otherwise proceed normally
return Make_Level_Literal
(Typ_Access_Level (Etype (Prefix (E))));
-- Similar to the previous case - arrays featuring components of
-- anonymous access components get their corresponding level from
-- their containing type's declaration.
elsif Nkind (E) = N_Indexed_Component
and then Ekind (Etype (E)) = E_Anonymous_Access_Type
and then Ekind (Etype (Pre)) in Array_Kind
and then Ekind (Component_Type (Base_Type (Etype (Pre))))
= E_Anonymous_Access_Type
then
-- When restriction No_Dynamic_Accessibility_Checks is active
-- and -gnatd_b set, the level is that of the designated type.
if Allow_Alt_Model
and then No_Dynamic_Accessibility_Checks_Enabled (E)
and then Debug_Flag_Underscore_B
then
return Make_Level_Literal
(Typ_Access_Level (Etype (E)));
end if;
-- Otherwise proceed normally
return Make_Level_Literal
(Typ_Access_Level (Etype (Prefix (E))));
-- The accessibility calculation routine that handles function
-- calls (Function_Call_Level) assumes, in the case the
-- result is of an anonymous access type, that the result will be
-- used "in its entirety" when the call is present within an
-- assignment or object declaration.
-- To properly handle cases where the result is not used in its
-- entirety, we test if the prefix of the component in question is
-- a function call, which tells us that one of its components has
-- been identified and is being accessed. Therefore we can
-- conclude that the result is not used "in its entirety"
-- according to RM 3.10.2 (10.2/3).
elsif Nkind (Pre) = N_Function_Call
and then not Is_Named_Access_Type (Etype (Pre))
then
-- Dynamic checks are generated when we are within a return
-- value or we are in a function call within an anonymous
-- access discriminant constraint of a return object (signified
-- by In_Return_Context) on the side of the callee.
-- So, in this case, return a library accessibility level to
-- null out the check on the side of the caller.
if (In_Return_Value (E)
or else In_Return_Context)
and then Level /= Dynamic_Level
then
return Make_Level_Literal
(Scope_Depth (Standard_Standard));
end if;
return Make_Level_Literal
(Innermost_Master_Scope_Depth (Expr));
-- Otherwise, continue recursing over the expression prefixes
else
return Accessibility_Level (Prefix (E));
end if;
-- Qualified expressions
when N_Qualified_Expression =>
if Is_Named_Access_Type (Etype (E)) then
return Make_Level_Literal
(Typ_Access_Level (Etype (E)));
else
return Accessibility_Level (Expression (E));
end if;
-- Handle function calls
when N_Function_Call =>
return Function_Call_Or_Allocator_Level (E);
-- Explicit dereference accessibility level calculation
when N_Explicit_Dereference =>
Pre := Original_Node (Prefix (E));
-- The prefix is a named access type so the level is taken from
-- its type.
if Is_Named_Access_Type (Etype (Pre)) then
return Make_Level_Literal (Typ_Access_Level (Etype (Pre)));
-- Otherwise, recurse deeper
else
return Accessibility_Level (Prefix (E));
end if;
-- Type conversions
when N_Type_Conversion | N_Unchecked_Type_Conversion =>
-- View conversions are special in that they require use to
-- inspect the expression of the type conversion.
-- Allocators of anonymous access types are internally generated,
-- so recurse deeper in that case as well.
if Is_View_Conversion (E)
or else Ekind (Etype (E)) = E_Anonymous_Access_Type
then
return Accessibility_Level (Expression (E));
-- We don't care about the master if we are looking at a named
-- access type.
elsif Is_Named_Access_Type (Etype (E)) then
return Make_Level_Literal
(Typ_Access_Level (Etype (E)));
-- In section RM 3.10.2 (10/4) the accessibility rules for
-- aggregates and value conversions are outlined. Are these
-- followed in the case of initialization of an object ???
-- Should use Innermost_Master_Scope_Depth ???
else
return Accessibility_Level (Current_Scope);
end if;
-- Default to the type accessibility level for the type of the
-- expression's entity.
when others =>
return Make_Level_Literal (Typ_Access_Level (Etype (E)));
end case;
end Accessibility_Level;
--------------------------------
-- Static_Accessibility_Level --
--------------------------------
function Static_Accessibility_Level
(Expr : Node_Id;
Level : Static_Accessibility_Level_Kind;
In_Return_Context : Boolean := False) return Uint
is
begin
return Intval
(Accessibility_Level (Expr, Level, In_Return_Context));
end Static_Accessibility_Level;
----------------------------------
-- Acquire_Warning_Match_String --
----------------------------------
function Acquire_Warning_Match_String (Str_Lit : Node_Id) return String is
S : constant String := To_String (Strval (Str_Lit));
begin
if S = "" then
return "";
else
-- Put "*" before or after or both, if it's not already there
declare
F : constant Boolean := S (S'First) = '*';
L : constant Boolean := S (S'Last) = '*';
begin
if F then
if L then
return S;
else
return S & "*";
end if;
else
if L then
return "*" & S;
else
return "*" & S & "*";
end if;
end if;
end;
end if;
end Acquire_Warning_Match_String;
--------------------------------
-- Add_Access_Type_To_Process --
--------------------------------
procedure Add_Access_Type_To_Process (E : Entity_Id; A : Entity_Id) is
L : Elist_Id;
begin
Ensure_Freeze_Node (E);
L := Access_Types_To_Process (Freeze_Node (E));
if No (L) then
L := New_Elmt_List;
Set_Access_Types_To_Process (Freeze_Node (E), L);
end if;
Append_Elmt (A, L);
end Add_Access_Type_To_Process;
--------------------------
-- Add_Block_Identifier --
--------------------------
procedure Add_Block_Identifier (N : Node_Id; Id : out Entity_Id) is
Loc : constant Source_Ptr := Sloc (N);
begin
pragma Assert (Nkind (N) = N_Block_Statement);
-- The block already has a label, return its entity
if Present (Identifier (N)) then
Id := Entity (Identifier (N));
-- Create a new block label and set its attributes
else
Id := New_Internal_Entity (E_Block, Current_Scope, Loc, 'B');
Set_Etype (Id, Standard_Void_Type);
Set_Parent (Id, N);
Set_Identifier (N, New_Occurrence_Of (Id, Loc));
Set_Block_Node (Id, Identifier (N));
end if;
end Add_Block_Identifier;
----------------------------
-- Add_Global_Declaration --
----------------------------
procedure Add_Global_Declaration (N : Node_Id) is
Aux_Node : constant Node_Id := Aux_Decls_Node (Cunit (Current_Sem_Unit));
begin
if No (Declarations (Aux_Node)) then
Set_Declarations (Aux_Node, New_List);
end if;
Append_To (Declarations (Aux_Node), N);
Analyze (N);
end Add_Global_Declaration;
--------------------------------
-- Address_Integer_Convert_OK --
--------------------------------
function Address_Integer_Convert_OK (T1, T2 : Entity_Id) return Boolean is
begin
if Allow_Integer_Address
and then ((Is_Descendant_Of_Address (T1)
and then Is_Private_Type (T1)
and then Is_Integer_Type (T2))
or else
(Is_Descendant_Of_Address (T2)
and then Is_Private_Type (T2)
and then Is_Integer_Type (T1)))
then
return True;
else
return False;
end if;
end Address_Integer_Convert_OK;
-------------------
-- Address_Value --
-------------------
function Address_Value (N : Node_Id) return Node_Id is
Expr : Node_Id := N;
begin
loop
-- For constant, get constant expression
if Is_Entity_Name (Expr)
and then Ekind (Entity (Expr)) = E_Constant
then
Expr := Constant_Value (Entity (Expr));
-- For unchecked conversion, get result to convert
elsif Nkind (Expr) = N_Unchecked_Type_Conversion then
Expr := Expression (Expr);
-- For (common case) of To_Address call, get argument
elsif Nkind (Expr) = N_Function_Call
and then Is_Entity_Name (Name (Expr))
and then Is_RTE (Entity (Name (Expr)), RE_To_Address)
then
Expr := First_Actual (Expr);
-- We finally have the real expression
else
exit;
end if;
end loop;
return Expr;
end Address_Value;
-----------------
-- Addressable --
-----------------
function Addressable (V : Uint) return Boolean is
begin
if No (V) then
return False;
end if;
return V = Uint_8 or else
V = Uint_16 or else
V = Uint_32 or else
V = Uint_64 or else
(V = Uint_128 and then System_Max_Integer_Size = 128);
end Addressable;
function Addressable (V : Int) return Boolean is
begin
return V = 8 or else
V = 16 or else
V = 32 or else
V = 64 or else
V = System_Max_Integer_Size;
end Addressable;
---------------------------------
-- Aggregate_Constraint_Checks --
---------------------------------
procedure Aggregate_Constraint_Checks
(Exp : Node_Id;
Check_Typ : Entity_Id)
is
Exp_Typ : constant Entity_Id := Etype (Exp);
begin
if Raises_Constraint_Error (Exp) then
return;
end if;
-- Ada 2005 (AI-230): Generate a conversion to an anonymous access
-- component's type to force the appropriate accessibility checks.
-- Ada 2005 (AI-231): Generate conversion to the null-excluding type to
-- force the corresponding run-time check
if Is_Access_Type (Check_Typ)
and then Is_Local_Anonymous_Access (Check_Typ)
then
Rewrite (Exp, Convert_To (Check_Typ, Relocate_Node (Exp)));
Analyze_And_Resolve (Exp, Check_Typ);
Check_Unset_Reference (Exp);
end if;
-- What follows is really expansion activity, so check that expansion
-- is on and is allowed. In GNATprove mode, we also want check flags to
-- be added in the tree, so that the formal verification can rely on
-- those to be present. In GNATprove mode for formal verification, some
-- treatment typically only done during expansion needs to be performed
-- on the tree, but it should not be applied inside generics. Otherwise,
-- this breaks the name resolution mechanism for generic instances.
if not Expander_Active
and (Inside_A_Generic or not Full_Analysis or not GNATprove_Mode)
then
return;
end if;
if Is_Access_Type (Check_Typ)
and then Can_Never_Be_Null (Check_Typ)
and then not Can_Never_Be_Null (Exp_Typ)
then
Install_Null_Excluding_Check (Exp);
end if;
-- First check if we have to insert discriminant checks
if Has_Discriminants (Exp_Typ) then
Apply_Discriminant_Check (Exp, Check_Typ);
-- Next emit length checks for array aggregates
elsif Is_Array_Type (Exp_Typ) then
Apply_Length_Check (Exp, Check_Typ);
-- Finally emit scalar and string checks. If we are dealing with a
-- scalar literal we need to check by hand because the Etype of
-- literals is not necessarily correct.
elsif Is_Scalar_Type (Exp_Typ)
and then Compile_Time_Known_Value (Exp)
then
if Is_Out_Of_Range (Exp, Base_Type (Check_Typ)) then
Apply_Compile_Time_Constraint_Error
(Exp, "value not in range of}??", CE_Range_Check_Failed,
Ent => Base_Type (Check_Typ),
Typ => Base_Type (Check_Typ));
elsif Is_Out_Of_Range (Exp, Check_Typ) then
Apply_Compile_Time_Constraint_Error
(Exp, "value not in range of}??", CE_Range_Check_Failed,
Ent => Check_Typ,
Typ => Check_Typ);
elsif not Range_Checks_Suppressed (Check_Typ) then
Apply_Scalar_Range_Check (Exp, Check_Typ);
end if;
-- Verify that target type is also scalar, to prevent view anomalies
-- in instantiations.
elsif (Is_Scalar_Type (Exp_Typ)
or else Nkind (Exp) = N_String_Literal)
and then Is_Scalar_Type (Check_Typ)
and then Exp_Typ /= Check_Typ
then
if Is_Entity_Name (Exp)
and then Ekind (Entity (Exp)) = E_Constant
then
-- If expression is a constant, it is worthwhile checking whether
-- it is a bound of the type.
if (Is_Entity_Name (Type_Low_Bound (Check_Typ))
and then Entity (Exp) = Entity (Type_Low_Bound (Check_Typ)))
or else
(Is_Entity_Name (Type_High_Bound (Check_Typ))
and then Entity (Exp) = Entity (Type_High_Bound (Check_Typ)))
then
return;
else
Rewrite (Exp, Convert_To (Check_Typ, Relocate_Node (Exp)));
Analyze_And_Resolve (Exp, Check_Typ);
Check_Unset_Reference (Exp);
end if;
-- Could use a comment on this case ???
else
Rewrite (Exp, Convert_To (Check_Typ, Relocate_Node (Exp)));
Analyze_And_Resolve (Exp, Check_Typ);
Check_Unset_Reference (Exp);
end if;
end if;
end Aggregate_Constraint_Checks;
-----------------------
-- Alignment_In_Bits --
-----------------------
function Alignment_In_Bits (E : Entity_Id) return Uint is
begin
return Alignment (E) * System_Storage_Unit;
end Alignment_In_Bits;
--------------------------------------
-- All_Composite_Constraints_Static --
--------------------------------------
function All_Composite_Constraints_Static
(Constr : Node_Id) return Boolean
is
begin
if No (Constr) or else Error_Posted (Constr) then
return True;
end if;
case Nkind (Constr) is
when N_Subexpr =>
if Nkind (Constr) in N_Has_Entity
and then Present (Entity (Constr))
then
if Is_Type (Entity (Constr)) then
return
not Is_Discrete_Type (Entity (Constr))
or else Is_OK_Static_Subtype (Entity (Constr));
end if;
elsif Nkind (Constr) = N_Range then
return
Is_OK_Static_Expression (Low_Bound (Constr))
and then
Is_OK_Static_Expression (High_Bound (Constr));
elsif Nkind (Constr) = N_Attribute_Reference
and then Attribute_Name (Constr) = Name_Range
then
return
Is_OK_Static_Expression
(Type_Low_Bound (Etype (Prefix (Constr))))
and then
Is_OK_Static_Expression
(Type_High_Bound (Etype (Prefix (Constr))));
end if;
return
not Present (Etype (Constr)) -- previous error
or else not Is_Discrete_Type (Etype (Constr))
or else Is_OK_Static_Expression (Constr);
when N_Discriminant_Association =>
return All_Composite_Constraints_Static (Expression (Constr));
when N_Range_Constraint =>
return
All_Composite_Constraints_Static (Range_Expression (Constr));
when N_Index_Or_Discriminant_Constraint =>
declare
One_Cstr : Entity_Id;
begin
One_Cstr := First (Constraints (Constr));
while Present (One_Cstr) loop
if not All_Composite_Constraints_Static (One_Cstr) then
return False;
end if;
Next (One_Cstr);
end loop;
end;
return True;
when N_Subtype_Indication =>
return
All_Composite_Constraints_Static (Subtype_Mark (Constr))
and then
All_Composite_Constraints_Static (Constraint (Constr));
when others =>
raise Program_Error;
end case;
end All_Composite_Constraints_Static;
------------------------
-- Append_Entity_Name --
------------------------
procedure Append_Entity_Name (Buf : in out Bounded_String; E : Entity_Id) is
Temp : Bounded_String;
procedure Inner (E : Entity_Id);
-- Inner recursive routine, keep outer routine nonrecursive to ease
-- debugging when we get strange results from this routine.
-----------
-- Inner --
-----------
procedure Inner (E : Entity_Id) is
Scop : Node_Id;
begin
-- If entity has an internal name, skip by it, and print its scope.
-- Note that we strip a final R from the name before the test; this
-- is needed for some cases of instantiations.
declare
E_Name : Bounded_String;
begin
Append (E_Name, Chars (E));
if E_Name.Chars (E_Name.Length) = 'R' then
E_Name.Length := E_Name.Length - 1;
end if;
if Is_Internal_Name (E_Name) then
Inner (Scope (E));
return;
end if;
end;
Scop := Scope (E);
-- Just print entity name if its scope is at the outer level
if Scop = Standard_Standard then
null;
-- If scope comes from source, write scope and entity
elsif Comes_From_Source (Scop) then
Append_Entity_Name (Temp, Scop);
Append (Temp, '.');
-- If in wrapper package skip past it
elsif Present (Scop) and then Is_Wrapper_Package (Scop) then
Append_Entity_Name (Temp, Scope (Scop));
Append (Temp, '.');
-- Otherwise nothing to output (happens in unnamed block statements)
else
null;
end if;
-- Output the name
declare
E_Name : Bounded_String;
begin
Append_Unqualified_Decoded (E_Name, Chars (E));
-- Remove trailing upper-case letters from the name (useful for
-- dealing with some cases of internal names generated in the case
-- of references from within a generic).
while E_Name.Length > 1
and then E_Name.Chars (E_Name.Length) in 'A' .. 'Z'
loop
E_Name.Length := E_Name.Length - 1;
end loop;
-- Adjust casing appropriately (gets name from source if possible)
Adjust_Name_Case (E_Name, Sloc (E));
Append (Temp, E_Name);
end;
end Inner;
-- Start of processing for Append_Entity_Name
begin
Inner (E);
Append (Buf, Temp);
end Append_Entity_Name;
---------------------------------
-- Append_Inherited_Subprogram --
---------------------------------
procedure Append_Inherited_Subprogram (S : Entity_Id) is
Par : constant Entity_Id := Alias (S);
-- The parent subprogram
Scop : constant Entity_Id := Scope (Par);
-- The scope of definition of the parent subprogram
Typ : constant Entity_Id := Defining_Entity (Parent (S));
-- The derived type of which S is a primitive operation
Decl : Node_Id;
Next_E : Entity_Id;
begin
if Ekind (Current_Scope) = E_Package
and then In_Private_Part (Current_Scope)
and then Has_Private_Declaration (Typ)
and then Is_Tagged_Type (Typ)
and then Scop = Current_Scope
then
-- The inherited operation is available at the earliest place after
-- the derived type declaration (RM 7.3.1 (6/1)). This is only
-- relevant for type extensions. If the parent operation appears
-- after the type extension, the operation is not visible.
Decl := First
(Visible_Declarations
(Package_Specification (Current_Scope)));
while Present (Decl) loop
if Nkind (Decl) = N_Private_Extension_Declaration
and then Defining_Entity (Decl) = Typ
then
if Sloc (Decl) > Sloc (Par) then
Next_E := Next_Entity (Par);
Link_Entities (Par, S);
Link_Entities (S, Next_E);
return;
else
exit;
end if;
end if;
Next (Decl);
end loop;
end if;
-- If partial view is not a type extension, or it appears before the
-- subprogram declaration, insert normally at end of entity list.
Append_Entity (S, Current_Scope);
end Append_Inherited_Subprogram;
-----------------------------------------
-- Apply_Compile_Time_Constraint_Error --
-----------------------------------------
procedure Apply_Compile_Time_Constraint_Error
(N : Node_Id;
Msg : String;
Reason : RT_Exception_Code;
Ent : Entity_Id := Empty;
Typ : Entity_Id := Empty;
Loc : Source_Ptr := No_Location;
Warn : Boolean := False;
Emit_Message : Boolean := True)
is
Stat : constant Boolean := Is_Static_Expression (N);
R_Stat : constant Node_Id :=
Make_Raise_Constraint_Error (Sloc (N), Reason => Reason);
Rtyp : Entity_Id;
begin
if No (Typ) then
Rtyp := Etype (N);
else
Rtyp := Typ;
end if;
if Emit_Message then
Discard_Node
(Compile_Time_Constraint_Error (N, Msg, Ent, Loc, Warn => Warn));
end if;
-- Now we replace the node by an N_Raise_Constraint_Error node
-- This does not need reanalyzing, so set it as analyzed now.
Rewrite (N, R_Stat);
Set_Analyzed (N, True);
Set_Etype (N, Rtyp);
Set_Raises_Constraint_Error (N);
-- Now deal with possible local raise handling
Possible_Local_Raise (N, Standard_Constraint_Error);
-- If the original expression was marked as static, the result is
-- still marked as static, but the Raises_Constraint_Error flag is
-- always set so that further static evaluation is not attempted.
if Stat then
Set_Is_Static_Expression (N);
end if;
end Apply_Compile_Time_Constraint_Error;
---------------------------
-- Async_Readers_Enabled --
---------------------------
function Async_Readers_Enabled (Id : Entity_Id) return Boolean is
begin
return Has_Enabled_Property (Id, Name_Async_Readers);
end Async_Readers_Enabled;
---------------------------
-- Async_Writers_Enabled --
---------------------------
function Async_Writers_Enabled (Id : Entity_Id) return Boolean is
begin
return Has_Enabled_Property (Id, Name_Async_Writers);
end Async_Writers_Enabled;
--------------------------------------
-- Available_Full_View_Of_Component --
--------------------------------------
function Available_Full_View_Of_Component (T : Entity_Id) return Boolean is
ST : constant Entity_Id := Scope (T);
SCT : constant Entity_Id := Scope (Component_Type (T));
begin
return In_Open_Scopes (ST)
and then In_Open_Scopes (SCT)
and then Scope_Depth (ST) >= Scope_Depth (SCT);
end Available_Full_View_Of_Component;
----------------
-- Bad_Aspect --
----------------
procedure Bad_Aspect
(N : Node_Id;
Nam : Name_Id;
Warn : Boolean := False)
is
begin
Error_Msg_Warn := Warn;
Error_Msg_N ("<<& is not a valid aspect identifier", N);
-- Check bad spelling
Error_Msg_Name_1 := Aspect_Spell_Check (Nam);
if Error_Msg_Name_1 /= No_Name then
Error_Msg_N -- CODEFIX
("\<<possible misspelling of %", N);
end if;
end Bad_Aspect;
-------------------
-- Bad_Attribute --
-------------------
procedure Bad_Attribute
(N : Node_Id;
Nam : Name_Id;
Warn : Boolean := False)
is
begin
Error_Msg_Warn := Warn;
Error_Msg_N ("<<unrecognized attribute&", N);
-- Check for possible misspelling
Error_Msg_Name_1 := Attribute_Spell_Check (Nam);
if Error_Msg_Name_1 /= No_Name then
Error_Msg_N -- CODEFIX
("\<<possible misspelling of %", N);
end if;
end Bad_Attribute;
--------------------------------
-- Bad_Predicated_Subtype_Use --
--------------------------------
procedure Bad_Predicated_Subtype_Use
(Msg : String;
N : Node_Id;
Typ : Entity_Id;
Suggest_Static : Boolean := False)
is
Gen : Entity_Id;
begin
-- Avoid cascaded errors
if Error_Posted (N) then
return;
end if;
if Inside_A_Generic then
Gen := Current_Scope;
while Present (Gen) and then Ekind (Gen) /= E_Generic_Package loop
Gen := Scope (Gen);
end loop;
if No (Gen) then
return;
end if;
if Is_Generic_Formal (Typ) and then Is_Discrete_Type (Typ) then
Set_No_Predicate_On_Actual (Typ);
end if;
elsif Has_Predicates (Typ) then
if Is_Generic_Actual_Type (Typ) then
-- The restriction on loop parameters is only that the type
-- should have no dynamic predicates.
if Nkind (Parent (N)) = N_Loop_Parameter_Specification
and then not Has_Dynamic_Predicate_Aspect (Typ)
and then Is_OK_Static_Subtype (Typ)
then
return;
end if;
Gen := Current_Scope;
while not Is_Generic_Instance (Gen) loop
Gen := Scope (Gen);
end loop;
pragma Assert (Present (Gen));
if Ekind (Gen) = E_Package and then In_Package_Body (Gen) then
Error_Msg_Warn := SPARK_Mode /= On;
Error_Msg_FE (Msg & "<<", N, Typ);
Error_Msg_F ("\Program_Error [<<", N);
Insert_Action (N,
Make_Raise_Program_Error (Sloc (N),
Reason => PE_Bad_Predicated_Generic_Type));
else
Error_Msg_FE (Msg, N, Typ);
end if;
else
Error_Msg_FE (Msg, N, Typ);
end if;
-- Emit an optional suggestion on how to remedy the error if the
-- context warrants it.
if Suggest_Static and then Has_Static_Predicate (Typ) then
Error_Msg_FE ("\predicate of & should be marked static", N, Typ);
end if;
end if;
end Bad_Predicated_Subtype_Use;
-----------------------------------------
-- Bad_Unordered_Enumeration_Reference --
-----------------------------------------
function Bad_Unordered_Enumeration_Reference
(N : Node_Id;
T : Entity_Id) return Boolean
is
begin
return Is_Enumeration_Type (T)
and then Warn_On_Unordered_Enumeration_Type
and then not Is_Generic_Type (T)
and then Comes_From_Source (N)
and then not Has_Pragma_Ordered (T)
and then not In_Same_Extended_Unit (N, T);
end Bad_Unordered_Enumeration_Reference;
----------------------------
-- Begin_Keyword_Location --
----------------------------
function Begin_Keyword_Location (N : Node_Id) return Source_Ptr is
HSS : Node_Id;
begin
pragma Assert
(Nkind (N) in
N_Block_Statement |
N_Entry_Body |
N_Package_Body |
N_Subprogram_Body |
N_Task_Body);
HSS := Handled_Statement_Sequence (N);
-- When the handled sequence of statements comes from source, the
-- location of the "begin" keyword is that of the sequence itself.
-- Note that an internal construct may inherit a source sequence.
if Comes_From_Source (HSS) then
return Sloc (HSS);
-- The parser generates an internal handled sequence of statements to
-- capture the location of the "begin" keyword if present in the source.
-- Since there are no source statements, the location of the "begin"
-- keyword is effectively that of the "end" keyword.
elsif Comes_From_Source (N) then
return Sloc (HSS);
-- Otherwise the construct is internal and should carry the location of
-- the original construct which prompted its creation.
else
return Sloc (N);
end if;
end Begin_Keyword_Location;
--------------------------
-- Build_Actual_Subtype --
--------------------------
function Build_Actual_Subtype
(T : Entity_Id;
N : Node_Or_Entity_Id) return Node_Id
is
Loc : Source_Ptr;
-- Normally Sloc (N), but may point to corresponding body in some cases
Constraints : List_Id;
Decl : Node_Id;
Discr : Entity_Id;
Hi : Node_Id;
Lo : Node_Id;
Subt : Entity_Id;
Disc_Type : Entity_Id;
Obj : Node_Id;
Index : Node_Id;
begin
Loc := Sloc (N);
if Nkind (N) = N_Defining_Identifier then
Obj := New_Occurrence_Of (N, Loc);
-- If this is a formal parameter of a subprogram declaration, and
-- we are compiling the body, we want the declaration for the
-- actual subtype to carry the source position of the body, to
-- prevent anomalies in gdb when stepping through the code.
if Is_Formal (N) then
declare
Decl : constant Node_Id := Unit_Declaration_Node (Scope (N));
begin
if Nkind (Decl) = N_Subprogram_Declaration
and then Present (Corresponding_Body (Decl))
then
Loc := Sloc (Corresponding_Body (Decl));
end if;
end;
end if;
else
Obj := N;
end if;
if Is_Array_Type (T) then
Constraints := New_List;
Index := First_Index (T);
for J in 1 .. Number_Dimensions (T) loop
-- Build an array subtype declaration with the nominal subtype and
-- the bounds of the actual. Add the declaration in front of the
-- local declarations for the subprogram, for analysis before any
-- reference to the formal in the body.
-- If this is for an index with a fixed lower bound, then use
-- the fixed lower bound as the lower bound of the actual
-- subtype's corresponding index.
if not Is_Constrained (T)
and then Is_Fixed_Lower_Bound_Index_Subtype (Etype (Index))
then
Lo := New_Copy_Tree (Type_Low_Bound (Etype (Index)));
else
Lo :=
Make_Attribute_Reference (Loc,
Prefix =>
Duplicate_Subexpr_No_Checks (Obj, Name_Req => True),
Attribute_Name => Name_First,
Expressions => New_List (
Make_Integer_Literal (Loc, J)));
end if;
Hi :=
Make_Attribute_Reference (Loc,
Prefix =>
Duplicate_Subexpr_No_Checks (Obj, Name_Req => True),
Attribute_Name => Name_Last,
Expressions => New_List (
Make_Integer_Literal (Loc, J)));
Append (Make_Range (Loc, Lo, Hi), Constraints);
Next_Index (Index);
end loop;
-- If the type has unknown discriminants there is no constrained
-- subtype to build. This is never called for a formal or for a
-- lhs, so returning the type is ok ???
elsif Has_Unknown_Discriminants (T) then
return T;
else
Constraints := New_List;
-- Type T is a generic derived type, inherit the discriminants from
-- the parent type.
if Is_Private_Type (T)
and then No (Full_View (T))
-- T was flagged as an error if it was declared as a formal
-- derived type with known discriminants. In this case there
-- is no need to look at the parent type since T already carries
-- its own discriminants.
and then not Error_Posted (T)
then
Disc_Type := Etype (Base_Type (T));
else
Disc_Type := T;
end if;
Discr := First_Discriminant (Disc_Type);
while Present (Discr) loop
Append_To (Constraints,
Make_Selected_Component (Loc,
Prefix =>
Duplicate_Subexpr_No_Checks (Obj),
Selector_Name => New_Occurrence_Of (Discr, Loc)));
Next_Discriminant (Discr);
end loop;
end if;
Subt := Make_Temporary (Loc, 'S', Related_Node => N);
Set_Is_Internal (Subt);
Decl :=
Make_Subtype_Declaration (Loc,
Defining_Identifier => Subt,
Subtype_Indication =>
Make_Subtype_Indication (Loc,
Subtype_Mark => New_Occurrence_Of (T, Loc),
Constraint =>
Make_Index_Or_Discriminant_Constraint (Loc,
Constraints => Constraints)));
Mark_Rewrite_Insertion (Decl);
return Decl;
end Build_Actual_Subtype;
---------------------------------------
-- Build_Actual_Subtype_Of_Component --
---------------------------------------
function Build_Actual_Subtype_Of_Component
(T : Entity_Id;
N : Node_Id) return Node_Id
is
Loc : constant Source_Ptr := Sloc (N);
P : constant Node_Id := Prefix (N);
D : Elmt_Id;
Id : Node_Id;
Index_Typ : Entity_Id;
Sel : Entity_Id := Empty;
Desig_Typ : Entity_Id;
-- This is either a copy of T, or if T is an access type, then it is
-- the directly designated type of this access type.
function Build_Access_Record_Constraint (C : List_Id) return List_Id;
-- If the record component is a constrained access to the current
-- record, the subtype has not been constructed during analysis of
-- the enclosing record type (see Analyze_Access). In that case, build
-- a constrained access subtype after replacing references to the
-- enclosing discriminants with the corresponding discriminant values
-- of the prefix.
function Build_Actual_Array_Constraint return List_Id;
-- If one or more of the bounds of the component depends on
-- discriminants, build actual constraint using the discriminants
-- of the prefix, as above.
function Build_Actual_Record_Constraint return List_Id;
-- Similar to previous one, for discriminated components constrained
-- by the discriminant of the enclosing object.
function Build_Discriminant_Reference
(Discrim_Name : Node_Id; Obj : Node_Id := P) return Node_Id;
-- Build a reference to the discriminant denoted by Discrim_Name.
-- The prefix of the result is usually Obj, but it could be
-- a prefix of Obj in some corner cases.
function Copy_And_Maybe_Dereference (N : Node_Id) return Node_Id;
-- Copy the subtree rooted at N and insert an explicit dereference if it
-- is of an access type.
-----------------------------------
-- Build_Actual_Array_Constraint --
-----------------------------------
function Build_Actual_Array_Constraint return List_Id is
Constraints : constant List_Id := New_List;
Indx : Node_Id;
Hi : Node_Id;
Lo : Node_Id;
Old_Hi : Node_Id;
Old_Lo : Node_Id;
begin
Indx := First_Index (Desig_Typ);
while Present (Indx) loop
Old_Lo := Type_Low_Bound (Etype (Indx));
Old_Hi := Type_High_Bound (Etype (Indx));
if Denotes_Discriminant (Old_Lo) then
Lo := Build_Discriminant_Reference (Old_Lo);
else
Lo := New_Copy_Tree (Old_Lo);
-- The new bound will be reanalyzed in the enclosing
-- declaration. For literal bounds that come from a type
-- declaration, the type of the context must be imposed, so
-- insure that analysis will take place. For non-universal
-- types this is not strictly necessary.
Set_Analyzed (Lo, False);
end if;
if Denotes_Discriminant (Old_Hi) then
Hi := Build_Discriminant_Reference (Old_Hi);
else
Hi := New_Copy_Tree (Old_Hi);
Set_Analyzed (Hi, False);
end if;
Append (Make_Range (Loc, Lo, Hi), Constraints);
Next_Index (Indx);
end loop;
return Constraints;
end Build_Actual_Array_Constraint;
------------------------------------
-- Build_Actual_Record_Constraint --
------------------------------------
function Build_Actual_Record_Constraint return List_Id is
Constraints : constant List_Id := New_List;
D : Elmt_Id;
D_Val : Node_Id;
begin
D := First_Elmt (Discriminant_Constraint (Desig_Typ));
while Present (D) loop
if Denotes_Discriminant (Node (D)) then
D_Val := Build_Discriminant_Reference (Node (D));
else
D_Val := New_Copy_Tree (Node (D));
end if;
Append (D_Val, Constraints);
Next_Elmt (D);
end loop;
return Constraints;
end Build_Actual_Record_Constraint;
----------------------------------
-- Build_Discriminant_Reference --
----------------------------------
function Build_Discriminant_Reference
(Discrim_Name : Node_Id; Obj : Node_Id := P) return Node_Id
is
Discrim : constant Entity_Id := Entity (Discrim_Name);
function Obj_Is_Good_Prefix return Boolean;
-- Returns True if Obj.Discrim makes sense; that is, if
-- Obj has Discrim as one of its discriminants (or is an
-- access value that designates such an object).
------------------------
-- Obj_Is_Good_Prefix --
------------------------
function Obj_Is_Good_Prefix return Boolean is
Obj_Type : Entity_Id :=
Implementation_Base_Type (Etype (Obj));
Discriminated_Type : constant Entity_Id :=
Implementation_Base_Type
(Scope (Original_Record_Component (Discrim)));
begin
-- The order of the following two tests matters in the
-- access-to-class-wide case.
if Is_Access_Type (Obj_Type) then
Obj_Type := Implementation_Base_Type
(Designated_Type (Obj_Type));
end if;
if Is_Class_Wide_Type (Obj_Type) then
Obj_Type := Implementation_Base_Type
(Find_Specific_Type (Obj_Type));
end if;
-- If a type T1 defines a discriminant D1, then Obj.D1 is ok (for
-- our purposes here) if T1 is an ancestor of the type of Obj.
-- So that's what we would like to test for here.
-- The bad news: Is_Ancestor is only defined in the tagged case.
-- The good news: in the untagged case, Implementation_Base_Type
-- looks through derived types so we can use a simpler test.
if Is_Tagged_Type (Discriminated_Type) then
return Is_Ancestor (Discriminated_Type, Obj_Type);
else
return Discriminated_Type = Obj_Type;
end if;
end Obj_Is_Good_Prefix;
-- Start of processing for Build_Discriminant_Reference
begin
if not Obj_Is_Good_Prefix then
-- If the given discriminant is not a component of the given
-- object, then try the enclosing object.
if Nkind (Obj) = N_Selected_Component then
return Build_Discriminant_Reference
(Discrim_Name => Discrim_Name,
Obj => Prefix (Obj));
elsif Nkind (Obj) in N_Has_Entity
and then Nkind (Parent (Entity (Obj))) =
N_Object_Renaming_Declaration
then
-- Look through a renaming (a corner case of a corner case).
return Build_Discriminant_Reference
(Discrim_Name => Discrim_Name,
Obj => Name (Parent (Entity (Obj))));
else
-- We are in some unexpected case here, so revert to the
-- old behavior (by falling through to it).
null;
end if;
end if;
return Make_Selected_Component (Loc,
Prefix => Copy_And_Maybe_Dereference (Obj),
Selector_Name => New_Occurrence_Of (Discrim, Loc));
end Build_Discriminant_Reference;
------------------------------------
-- Build_Access_Record_Constraint --
------------------------------------
function Build_Access_Record_Constraint (C : List_Id) return List_Id is
Constraints : constant List_Id := New_List;
D : Node_Id;
D_Val : Node_Id;
begin
-- Retrieve the constraint from the component declaration, because
-- the component subtype has not been constructed and the component
-- type is an unconstrained access.
D := First (C);
while Present (D) loop
if Nkind (D) = N_Discriminant_Association
and then Denotes_Discriminant (Expression (D))
then
D_Val := New_Copy_Tree (D);
Set_Expression (D_Val,
Make_Selected_Component (Loc,
Prefix => Copy_And_Maybe_Dereference (P),
Selector_Name =>
New_Occurrence_Of (Entity (Expression (D)), Loc)));
elsif Denotes_Discriminant (D) then
D_Val := Make_Selected_Component (Loc,
Prefix => Copy_And_Maybe_Dereference (P),
Selector_Name => New_Occurrence_Of (Entity (D), Loc));
else
D_Val := New_Copy_Tree (D);
end if;
Append (D_Val, Constraints);
Next (D);
end loop;
return Constraints;
end Build_Access_Record_Constraint;
--------------------------------
-- Copy_And_Maybe_Dereference --
--------------------------------
function Copy_And_Maybe_Dereference (N : Node_Id) return Node_Id is
New_N : constant Node_Id := New_Copy_Tree (N);
begin
if Is_Access_Type (Etype (N)) then
return Make_Explicit_Dereference (Sloc (Parent (N)), New_N);
else
return New_N;
end if;
end Copy_And_Maybe_Dereference;
-- Start of processing for Build_Actual_Subtype_Of_Component
begin
-- The subtype does not need to be created for a selected component
-- in a Spec_Expression.
if In_Spec_Expression then
return Empty;
-- More comments for the rest of this body would be good ???
elsif Nkind (N) = N_Explicit_Dereference then
if Is_Composite_Type (T)
and then not Is_Constrained (T)
and then not (Is_Class_Wide_Type (T)
and then Is_Constrained (Root_Type (T)))
and then not Has_Unknown_Discriminants (T)
then
-- If the type of the dereference is already constrained, it is an
-- actual subtype.
if Is_Array_Type (Etype (N))
and then Is_Constrained (Etype (N))
then
return Empty;
else
Remove_Side_Effects (P);
return Build_Actual_Subtype (T, N);
end if;
else
return Empty;
end if;
elsif Nkind (N) = N_Selected_Component then
-- The entity of the selected component allows us to retrieve
-- the original constraint from its component declaration.
Sel := Entity (Selector_Name (N));
if Parent_Kind (Sel) /= N_Component_Declaration then
return Empty;
end if;
end if;
if Is_Access_Type (T) then
Desig_Typ := Designated_Type (T);
else
Desig_Typ := T;
end if;
if Ekind (Desig_Typ) = E_Array_Subtype then
Id := First_Index (Desig_Typ);
-- Check whether an index bound is constrained by a discriminant
while Present (Id) loop
Index_Typ := Underlying_Type (Etype (Id));
if Denotes_Discriminant (Type_Low_Bound (Index_Typ))
or else
Denotes_Discriminant (Type_High_Bound (Index_Typ))
then
Remove_Side_Effects (P);
return
Build_Component_Subtype
(Build_Actual_Array_Constraint, Loc, Base_Type (T));
end if;
Next_Index (Id);
end loop;
elsif Is_Composite_Type (Desig_Typ)
and then Has_Discriminants (Desig_Typ)
and then not Is_Empty_Elmt_List (Discriminant_Constraint (Desig_Typ))
and then not Has_Unknown_Discriminants (Desig_Typ)
then
if Is_Private_Type (Desig_Typ)
and then No (Discriminant_Constraint (Desig_Typ))
then
Desig_Typ := Full_View (Desig_Typ);
end if;
D := First_Elmt (Discriminant_Constraint (Desig_Typ));
while Present (D) loop
if Denotes_Discriminant (Node (D)) then
Remove_Side_Effects (P);
return
Build_Component_Subtype (
Build_Actual_Record_Constraint, Loc, Base_Type (T));
end if;
Next_Elmt (D);
end loop;
-- Special processing for an access record component that is
-- the target of an assignment. If the designated type is an
-- unconstrained discriminated record we create its actual
-- subtype now.
elsif Ekind (T) = E_Access_Type
and then Present (Sel)
and then Has_Per_Object_Constraint (Sel)
and then Nkind (Parent (N)) = N_Assignment_Statement
and then N = Name (Parent (N))
-- and then not Inside_Init_Proc
-- and then Has_Discriminants (Desig_Typ)
-- and then not Is_Constrained (Desig_Typ)
then
declare
S_Indic : constant Node_Id :=
(Subtype_Indication
(Component_Definition (Parent (Sel))));
Discs : List_Id;
begin
if Nkind (S_Indic) = N_Subtype_Indication then
Discs := Constraints (Constraint (S_Indic));
Remove_Side_Effects (P);
return Build_Component_Subtype
(Build_Access_Record_Constraint (Discs), Loc, T);
else
return Empty;
end if;
end;
end if;
-- If none of the above, the actual and nominal subtypes are the same
return Empty;
end Build_Actual_Subtype_Of_Component;
-----------------------------
-- Build_Component_Subtype --
-----------------------------
function Build_Component_Subtype
(C : List_Id;
Loc : Source_Ptr;
T : Entity_Id) return Node_Id
is
Subt : Entity_Id;
Decl : Node_Id;
begin
-- Unchecked_Union components do not require component subtypes
if Is_Unchecked_Union (T) then
return Empty;
end if;
Subt := Make_Temporary (Loc, 'S');
Set_Is_Internal (Subt);
Decl :=
Make_Subtype_Declaration (Loc,
Defining_Identifier => Subt,
Subtype_Indication =>
Make_Subtype_Indication (Loc,
Subtype_Mark => New_Occurrence_Of (Base_Type (T), Loc),
Constraint =>
Make_Index_Or_Discriminant_Constraint (Loc,
Constraints => C)));
Mark_Rewrite_Insertion (Decl);
return Decl;
end Build_Component_Subtype;
-----------------------------
-- Build_Constrained_Itype --
-----------------------------
procedure Build_Constrained_Itype
(N : Node_Id;
Typ : Entity_Id;
New_Assoc_List : List_Id)
is
Constrs : constant List_Id := New_List;
Loc : constant Source_Ptr := Sloc (N);
Def_Id : Entity_Id;
Indic : Node_Id;
New_Assoc : Node_Id;
Subtyp_Decl : Node_Id;
begin
New_Assoc := First (New_Assoc_List);
while Present (New_Assoc) loop
-- There is exactly one choice in the component association (and
-- it is either a discriminant, a component or the others clause).
pragma Assert (List_Length (Choices (New_Assoc)) = 1);
-- Duplicate expression for the discriminant and put it on the
-- list of constraints for the itype declaration.
if Is_Entity_Name (First (Choices (New_Assoc)))
and then
Ekind (Entity (First (Choices (New_Assoc)))) = E_Discriminant
then
Append_To (Constrs, Duplicate_Subexpr (Expression (New_Assoc)));
end if;
Next (New_Assoc);
end loop;
if Has_Unknown_Discriminants (Typ)
and then Present (Underlying_Record_View (Typ))
then
Indic :=
Make_Subtype_Indication (Loc,
Subtype_Mark =>
New_Occurrence_Of (Underlying_Record_View (Typ), Loc),
Constraint =>
Make_Index_Or_Discriminant_Constraint (Loc,
Constraints => Constrs));
else
Indic :=
Make_Subtype_Indication (Loc,
Subtype_Mark =>
New_Occurrence_Of (Base_Type (Typ), Loc),
Constraint =>
Make_Index_Or_Discriminant_Constraint (Loc,
Constraints => Constrs));
end if;
Def_Id := Create_Itype (Ekind (Typ), N);
Subtyp_Decl :=
Make_Subtype_Declaration (Loc,
Defining_Identifier => Def_Id,
Subtype_Indication => Indic);
Set_Parent (Subtyp_Decl, Parent (N));
-- Itypes must be analyzed with checks off (see itypes.ads)
Analyze (Subtyp_Decl, Suppress => All_Checks);
Set_Etype (N, Def_Id);
end Build_Constrained_Itype;
---------------------------
-- Build_Default_Subtype --
---------------------------
function Build_Default_Subtype
(T : Entity_Id;
N : Node_Id) return Entity_Id
is
Loc : constant Source_Ptr := Sloc (N);
Disc : Entity_Id;
Bas : Entity_Id;
-- The base type that is to be constrained by the defaults
begin
if not Has_Discriminants (T) or else Is_Constrained (T) then
return T;
end if;
Bas := Base_Type (T);
-- If T is non-private but its base type is private, this is the
-- completion of a subtype declaration whose parent type is private
-- (see Complete_Private_Subtype in Sem_Ch3). The proper discriminants
-- are to be found in the full view of the base. Check that the private
-- status of T and its base differ.
if Is_Private_Type (Bas)
and then not Is_Private_Type (T)
and then Present (Full_View (Bas))
then
Bas := Full_View (Bas);
end if;
Disc := First_Discriminant (T);
if No (Discriminant_Default_Value (Disc)) then
return T;
end if;
declare
Act : constant Entity_Id := Make_Temporary (Loc, 'S');
Constraints : constant List_Id := New_List;
Decl : Node_Id;
begin
while Present (Disc) loop
Append_To (Constraints,
New_Copy_Tree (Discriminant_Default_Value (Disc)));
Next_Discriminant (Disc);
end loop;
Decl :=
Make_Subtype_Declaration (Loc,
Defining_Identifier => Act,
Subtype_Indication =>
Make_Subtype_Indication (Loc,
Subtype_Mark => New_Occurrence_Of (Bas, Loc),
Constraint =>
Make_Index_Or_Discriminant_Constraint (Loc,
Constraints => Constraints)));
Insert_Action (N, Decl);
-- If the context is a component declaration the subtype declaration
-- will be analyzed when the enclosing type is frozen, otherwise do
-- it now.
if Ekind (Current_Scope) /= E_Record_Type then
Analyze (Decl);
end if;
return Act;
end;
end Build_Default_Subtype;
--------------------------------------------
-- Build_Discriminal_Subtype_Of_Component --
--------------------------------------------
function Build_Discriminal_Subtype_Of_Component
(T : Entity_Id) return Node_Id
is
Loc : constant Source_Ptr := Sloc (T);
D : Elmt_Id;
Id : Node_Id;
function Build_Discriminal_Array_Constraint return List_Id;
-- If one or more of the bounds of the component depends on
-- discriminants, build actual constraint using the discriminants
-- of the prefix.
function Build_Discriminal_Record_Constraint return List_Id;
-- Similar to previous one, for discriminated components constrained by
-- the discriminant of the enclosing object.
----------------------------------------
-- Build_Discriminal_Array_Constraint --
----------------------------------------
function Build_Discriminal_Array_Constraint return List_Id is
Constraints : constant List_Id := New_List;
Indx : Node_Id;
Hi : Node_Id;
Lo : Node_Id;
Old_Hi : Node_Id;
Old_Lo : Node_Id;
begin
Indx := First_Index (T);
while Present (Indx) loop
Old_Lo := Type_Low_Bound (Etype (Indx));
Old_Hi := Type_High_Bound (Etype (Indx));
if Denotes_Discriminant (Old_Lo) then
Lo := New_Occurrence_Of (Discriminal (Entity (Old_Lo)), Loc);
else
Lo := New_Copy_Tree (Old_Lo);
end if;
if Denotes_Discriminant (Old_Hi) then
Hi := New_Occurrence_Of (Discriminal (Entity (Old_Hi)), Loc);
else
Hi := New_Copy_Tree (Old_Hi);
end if;
Append (Make_Range (Loc, Lo, Hi), Constraints);
Next_Index (Indx);
end loop;
return Constraints;
end Build_Discriminal_Array_Constraint;
-----------------------------------------
-- Build_Discriminal_Record_Constraint --
-----------------------------------------
function Build_Discriminal_Record_Constraint return List_Id is
Constraints : constant List_Id := New_List;
D : Elmt_Id;
D_Val : Node_Id;
begin
D := First_Elmt (Discriminant_Constraint (T));
while Present (D) loop
if Denotes_Discriminant (Node (D)) then
D_Val :=
New_Occurrence_Of (Discriminal (Entity (Node (D))), Loc);
else
D_Val := New_Copy_Tree (Node (D));
end if;
Append (D_Val, Constraints);
Next_Elmt (D);
end loop;
return Constraints;
end Build_Discriminal_Record_Constraint;
-- Start of processing for Build_Discriminal_Subtype_Of_Component
begin
if Ekind (T) = E_Array_Subtype then
Id := First_Index (T);
while Present (Id) loop
if Denotes_Discriminant (Type_Low_Bound (Etype (Id)))
or else
Denotes_Discriminant (Type_High_Bound (Etype (Id)))
then
return Build_Component_Subtype
(Build_Discriminal_Array_Constraint, Loc, T);
end if;
Next_Index (Id);
end loop;
elsif Ekind (T) = E_Record_Subtype
and then Has_Discriminants (T)
and then not Has_Unknown_Discriminants (T)
then
D := First_Elmt (Discriminant_Constraint (T));
while Present (D) loop
if Denotes_Discriminant (Node (D)) then
return Build_Component_Subtype
(Build_Discriminal_Record_Constraint, Loc, T);
end if;
Next_Elmt (D);
end loop;
end if;
-- If none of the above, the actual and nominal subtypes are the same
return Empty;
end Build_Discriminal_Subtype_Of_Component;
------------------------------
-- Build_Elaboration_Entity --
------------------------------
procedure Build_Elaboration_Entity (N : Node_Id; Spec_Id : Entity_Id) is
Loc : constant Source_Ptr := Sloc (N);
Decl : Node_Id;
Elab_Ent : Entity_Id;
procedure Set_Package_Name (Ent : Entity_Id);
-- Given an entity, sets the fully qualified name of the entity in
-- Name_Buffer, with components separated by double underscores. This
-- is a recursive routine that climbs the scope chain to Standard.
----------------------
-- Set_Package_Name --
----------------------
procedure Set_Package_Name (Ent : Entity_Id) is
begin
if Scope (Ent) /= Standard_Standard then
Set_Package_Name (Scope (Ent));
declare
Nam : constant String := Get_Name_String (Chars (Ent));
begin
Name_Buffer (Name_Len + 1) := '_';
Name_Buffer (Name_Len + 2) := '_';
Name_Buffer (Name_Len + 3 .. Name_Len + Nam'Length + 2) := Nam;
Name_Len := Name_Len + Nam'Length + 2;
end;
else
Get_Name_String (Chars (Ent));
end if;
end Set_Package_Name;
-- Start of processing for Build_Elaboration_Entity
begin
-- Ignore call if already constructed
if Present (Elaboration_Entity (Spec_Id)) then
return;
-- Do not generate an elaboration entity in GNATprove move because the
-- elaboration counter is a form of expansion.
elsif GNATprove_Mode then
return;
-- See if we need elaboration entity
-- We always need an elaboration entity when preserving control flow, as
-- we want to remain explicit about the unit's elaboration order.
elsif Opt.Suppress_Control_Flow_Optimizations then
null;
-- We always need an elaboration entity for the dynamic elaboration
-- model, since it is needed to properly generate the PE exception for
-- access before elaboration.
elsif Dynamic_Elaboration_Checks then
null;
-- For the static model, we don't need the elaboration counter if this
-- unit is sure to have no elaboration code, since that means there
-- is no elaboration unit to be called. Note that we can't just decide
-- after the fact by looking to see whether there was elaboration code,
-- because that's too late to make this decision.
elsif Restriction_Active (No_Elaboration_Code) then
return;
-- Similarly, for the static model, we can skip the elaboration counter
-- if we have the No_Multiple_Elaboration restriction, since for the
-- static model, that's the only purpose of the counter (to avoid
-- multiple elaboration).
elsif Restriction_Active (No_Multiple_Elaboration) then
return;
end if;
-- Here we need the elaboration entity
-- Construct name of elaboration entity as xxx_E, where xxx is the unit
-- name with dots replaced by double underscore. We have to manually
-- construct this name, since it will be elaborated in the outer scope,
-- and thus will not have the unit name automatically prepended.
Set_Package_Name (Spec_Id);
Add_Str_To_Name_Buffer ("_E");
-- Create elaboration counter
Elab_Ent := Make_Defining_Identifier (Loc, Chars => Name_Find);
Set_Elaboration_Entity (Spec_Id, Elab_Ent);
Decl :=
Make_Object_Declaration (Loc,
Defining_Identifier => Elab_Ent,
Object_Definition =>
New_Occurrence_Of (Standard_Short_Integer, Loc),
Expression => Make_Integer_Literal (Loc, Uint_0));
Push_Scope (Standard_Standard);
Add_Global_Declaration (Decl);
Pop_Scope;
-- Reset True_Constant indication, since we will indeed assign a value
-- to the variable in the binder main. We also kill the Current_Value
-- and Last_Assignment fields for the same reason.
Set_Is_True_Constant (Elab_Ent, False);
Set_Current_Value (Elab_Ent, Empty);
Set_Last_Assignment (Elab_Ent, Empty);
-- We do not want any further qualification of the name (if we did not
-- do this, we would pick up the name of the generic package in the case
-- of a library level generic instantiation).
Set_Has_Qualified_Name (Elab_Ent);
Set_Has_Fully_Qualified_Name (Elab_Ent);
end Build_Elaboration_Entity;
--------------------------------
-- Build_Explicit_Dereference --
--------------------------------
procedure Build_Explicit_Dereference
(Expr : Node_Id;
Disc : Entity_Id)
is
Loc : constant Source_Ptr := Sloc (Expr);
I : Interp_Index;
It : Interp;
begin
-- An entity of a type with a reference aspect is overloaded with
-- both interpretations: with and without the dereference. Now that
-- the dereference is made explicit, set the type of the node properly,
-- to prevent anomalies in the backend. Same if the expression is an
-- overloaded function call whose return type has a reference aspect.
if Is_Entity_Name (Expr) then
Set_Etype (Expr, Etype (Entity (Expr)));
-- The designated entity will not be examined again when resolving
-- the dereference, so generate a reference to it now.
Generate_Reference (Entity (Expr), Expr);
elsif Nkind (Expr) = N_Function_Call then
-- If the name of the indexing function is overloaded, locate the one
-- whose return type has an implicit dereference on the desired
-- discriminant, and set entity and type of function call.
if Is_Overloaded (Name (Expr)) then
Get_First_Interp (Name (Expr), I, It);
while Present (It.Nam) loop
if Ekind ((It.Typ)) = E_Record_Type
and then First_Entity ((It.Typ)) = Disc
then
Set_Entity (Name (Expr), It.Nam);
Set_Etype (Name (Expr), Etype (It.Nam));
exit;
end if;
Get_Next_Interp (I, It);
end loop;
end if;
-- Set type of call from resolved function name.
Set_Etype (Expr, Etype (Name (Expr)));
end if;
Set_Is_Overloaded (Expr, False);
-- The expression will often be a generalized indexing that yields a
-- container element that is then dereferenced, in which case the
-- generalized indexing call is also non-overloaded.
if Nkind (Expr) = N_Indexed_Component
and then Present (Generalized_Indexing (Expr))
then
Set_Is_Overloaded (Generalized_Indexing (Expr), False);
end if;
Rewrite (Expr,
Make_Explicit_Dereference (Loc,
Prefix =>
Make_Selected_Component (Loc,
Prefix => Relocate_Node (Expr),
Selector_Name => New_Occurrence_Of (Disc, Loc))));
Set_Etype (Prefix (Expr), Etype (Disc));
Set_Etype (Expr, Designated_Type (Etype (Disc)));
end Build_Explicit_Dereference;
---------------------------
-- Build_Overriding_Spec --
---------------------------
function Build_Overriding_Spec
(Op : Entity_Id;
Typ : Entity_Id) return Node_Id
is
Loc : constant Source_Ptr := Sloc (Typ);
Par_Typ : constant Entity_Id := Find_Dispatching_Type (Op);
Spec : constant Node_Id := Specification (Unit_Declaration_Node (Op));
Formal_Spec : Node_Id;
Formal_Type : Node_Id;
New_Spec : Node_Id;
begin
New_Spec := Copy_Subprogram_Spec (Spec);
Formal_Spec := First (Parameter_Specifications (New_Spec));
while Present (Formal_Spec) loop
Formal_Type := Parameter_Type (Formal_Spec);
if Is_Entity_Name (Formal_Type)
and then Entity (Formal_Type) = Par_Typ
then
Rewrite (Formal_Type, New_Occurrence_Of (Typ, Loc));
end if;
-- Nothing needs to be done for access parameters
Next (Formal_Spec);
end loop;
return New_Spec;
end Build_Overriding_Spec;
-------------------
-- Build_Subtype --
-------------------
function Build_Subtype
(Related_Node : Node_Id;
Loc : Source_Ptr;
Typ : Entity_Id;
Constraints : List_Id)
return Entity_Id
is
Indic : Node_Id;
Subtyp_Decl : Node_Id;
Def_Id : Entity_Id;
Btyp : Entity_Id := Base_Type (Typ);
begin
-- The Related_Node better be here or else we won't be able to
-- attach new itypes to a node in the tree.
pragma Assert (Present (Related_Node));
-- If the view of the component's type is incomplete or private
-- with unknown discriminants, then the constraint must be applied
-- to the full type.
if Has_Unknown_Discriminants (Btyp)
and then Present (Underlying_Type (Btyp))
then
Btyp := Underlying_Type (Btyp);
end if;
Indic :=
Make_Subtype_Indication (Loc,
Subtype_Mark => New_Occurrence_Of (Btyp, Loc),
Constraint =>
Make_Index_Or_Discriminant_Constraint (Loc, Constraints));
Def_Id := Create_Itype (Ekind (Typ), Related_Node);
Subtyp_Decl :=
Make_Subtype_Declaration (Loc,
Defining_Identifier => Def_Id,
Subtype_Indication => Indic);
Set_Parent (Subtyp_Decl, Parent (Related_Node));
-- Itypes must be analyzed with checks off (see package Itypes)
Analyze (Subtyp_Decl, Suppress => All_Checks);
if Is_Itype (Def_Id) and then Has_Predicates (Typ) then
Inherit_Predicate_Flags (Def_Id, Typ);
-- Indicate where the predicate function may be found
if Is_Itype (Typ) then
if Present (Predicate_Function (Def_Id)) then
null;
elsif Present (Predicate_Function (Typ)) then
Set_Predicate_Function (Def_Id, Predicate_Function (Typ));
else
Set_Predicated_Parent (Def_Id, Predicated_Parent (Typ));
end if;
elsif No (Predicate_Function (Def_Id)) then
Set_Predicated_Parent (Def_Id, Typ);
end if;
end if;
return Def_Id;
end Build_Subtype;
-----------------------------------
-- Cannot_Raise_Constraint_Error --
-----------------------------------
function Cannot_Raise_Constraint_Error (Expr : Node_Id) return Boolean is
function List_Cannot_Raise_CE (L : List_Id) return Boolean;
-- Returns True if none of the list members cannot possibly raise
-- Constraint_Error.
--------------------------
-- List_Cannot_Raise_CE --
--------------------------
function List_Cannot_Raise_CE (L : List_Id) return Boolean is
N : Node_Id;
begin
N := First (L);
while Present (N) loop
if Cannot_Raise_Constraint_Error (N) then
Next (N);
else
return False;
end if;
end loop;
return True;
end List_Cannot_Raise_CE;
-- Start of processing for Cannot_Raise_Constraint_Error
begin
if Compile_Time_Known_Value (Expr) then
return True;
elsif Do_Range_Check (Expr) then
return False;
elsif Raises_Constraint_Error (Expr) then
return False;
else
case Nkind (Expr) is
when N_Identifier =>
return True;
when N_Expanded_Name =>
return True;
when N_Indexed_Component =>
return not Do_Range_Check (Expr)
and then Cannot_Raise_Constraint_Error (Prefix (Expr))
and then List_Cannot_Raise_CE (Expressions (Expr));
when N_Selected_Component =>
return not Do_Discriminant_Check (Expr)
and then Cannot_Raise_Constraint_Error (Prefix (Expr));
when N_Attribute_Reference =>
if Do_Overflow_Check (Expr) then
return False;
elsif No (Expressions (Expr)) then
return True;
else
return List_Cannot_Raise_CE (Expressions (Expr));
end if;
when N_Type_Conversion =>
if Do_Overflow_Check (Expr)
or else Do_Length_Check (Expr)
then
return False;
else
return Cannot_Raise_Constraint_Error (Expression (Expr));
end if;
when N_Unchecked_Type_Conversion =>
return Cannot_Raise_Constraint_Error (Expression (Expr));
when N_Unary_Op =>
if Do_Overflow_Check (Expr) then
return False;
else
return Cannot_Raise_Constraint_Error (Right_Opnd (Expr));
end if;
when N_Op_Divide
| N_Op_Mod
| N_Op_Rem
=>
if Do_Division_Check (Expr)
or else
Do_Overflow_Check (Expr)
then
return False;
else
return
Cannot_Raise_Constraint_Error (Left_Opnd (Expr))
and then
Cannot_Raise_Constraint_Error (Right_Opnd (Expr));
end if;
when N_Op_Add
| N_Op_And
| N_Op_Concat
| N_Op_Eq
| N_Op_Expon
| N_Op_Ge
| N_Op_Gt
| N_Op_Le
| N_Op_Lt
| N_Op_Multiply
| N_Op_Ne
| N_Op_Or
| N_Op_Rotate_Left
| N_Op_Rotate_Right
| N_Op_Shift_Left
| N_Op_Shift_Right
| N_Op_Shift_Right_Arithmetic
| N_Op_Subtract
| N_Op_Xor
=>
if Do_Overflow_Check (Expr) then
return False;
else
return
Cannot_Raise_Constraint_Error (Left_Opnd (Expr))
and then
Cannot_Raise_Constraint_Error (Right_Opnd (Expr));
end if;
when others =>
return False;
end case;
end if;
end Cannot_Raise_Constraint_Error;
-------------------------------
-- Check_Ambiguous_Aggregate --
-------------------------------
procedure Check_Ambiguous_Aggregate (Call : Node_Id) is
Actual : Node_Id;
begin
if Extensions_Allowed then
Actual := First_Actual (Call);
while Present (Actual) loop
if Nkind (Actual) = N_Aggregate then
Error_Msg_N
("\add type qualification to aggregate actual", Actual);
exit;
end if;
Next_Actual (Actual);
end loop;
end if;
end Check_Ambiguous_Aggregate;
-----------------------------------------
-- Check_Dynamically_Tagged_Expression --
-----------------------------------------
procedure Check_Dynamically_Tagged_Expression
(Expr : Node_Id;
Typ : Entity_Id;
Related_Nod : Node_Id)
is
begin
pragma Assert (Is_Tagged_Type (Typ));
-- In order to avoid spurious errors when analyzing the expanded code,
-- this check is done only for nodes that come from source and for
-- actuals of generic instantiations.
if (Comes_From_Source (Related_Nod)
or else In_Generic_Actual (Expr))
and then (Is_Class_Wide_Type (Etype (Expr))
or else Is_Dynamically_Tagged (Expr))
and then not Is_Class_Wide_Type (Typ)
then
Error_Msg_N ("dynamically tagged expression not allowed!", Expr);
end if;
end Check_Dynamically_Tagged_Expression;
--------------------------
-- Check_Fully_Declared --
--------------------------
procedure Check_Fully_Declared (T : Entity_Id; N : Node_Id) is
begin
if Ekind (T) = E_Incomplete_Type then
-- Ada 2005 (AI-50217): If the type is available through a limited
-- with_clause, verify that its full view has been analyzed.
if From_Limited_With (T)
and then Present (Non_Limited_View (T))
and then Ekind (Non_Limited_View (T)) /= E_Incomplete_Type
then
-- The non-limited view is fully declared
null;
else
Error_Msg_NE
("premature usage of incomplete}", N, First_Subtype (T));
end if;
-- Need comments for these tests ???
elsif Has_Private_Component (T)
and then not Is_Generic_Type (Root_Type (T))
and then not In_Spec_Expression
then
-- Special case: if T is the anonymous type created for a single
-- task or protected object, use the name of the source object.
if Is_Concurrent_Type (T)
and then not Comes_From_Source (T)
and then Nkind (N) = N_Object_Declaration
then
Error_Msg_NE
("type of& has incomplete component",
N, Defining_Identifier (N));
else
Error_Msg_NE
("premature usage of incomplete}",
N, First_Subtype (T));
end if;
end if;
end Check_Fully_Declared;
-------------------------------------------
-- Check_Function_With_Address_Parameter --
-------------------------------------------
procedure Check_Function_With_Address_Parameter (Subp_Id : Entity_Id) is
F : Entity_Id;
T : Entity_Id;
begin
F := First_Formal (Subp_Id);
while Present (F) loop
T := Etype (F);
if Is_Private_Type (T) and then Present (Full_View (T)) then
T := Full_View (T);
end if;
if Is_Descendant_Of_Address (T) or else Is_Limited_Type (T) then
Set_Is_Pure (Subp_Id, False);
exit;
end if;
Next_Formal (F);
end loop;
end Check_Function_With_Address_Parameter;
-------------------------------------
-- Check_Function_Writable_Actuals --
-------------------------------------
procedure Check_Function_Writable_Actuals (N : Node_Id) is
Writable_Actuals_List : Elist_Id := No_Elist;
Identifiers_List : Elist_Id := No_Elist;
Aggr_Error_Node : Node_Id := Empty;
Error_Node : Node_Id := Empty;
procedure Collect_Identifiers (N : Node_Id);
-- In a single traversal of subtree N collect in Writable_Actuals_List
-- all the actuals of functions with writable actuals, and in the list
-- Identifiers_List collect all the identifiers that are not actuals of
-- functions with writable actuals. If a writable actual is referenced
-- twice as writable actual then Error_Node is set to reference its
-- second occurrence, the error is reported, and the tree traversal
-- is abandoned.
-------------------------
-- Collect_Identifiers --
-------------------------
procedure Collect_Identifiers (N : Node_Id) is
function Check_Node (N : Node_Id) return Traverse_Result;
-- Process a single node during the tree traversal to collect the
-- writable actuals of functions and all the identifiers which are
-- not writable actuals of functions.
function Contains (List : Elist_Id; N : Node_Id) return Boolean;
-- Returns True if List has a node whose Entity is Entity (N)
----------------
-- Check_Node --
----------------
function Check_Node (N : Node_Id) return Traverse_Result is
Is_Writable_Actual : Boolean := False;
Id : Entity_Id;
begin
if Nkind (N) = N_Identifier then
-- No analysis possible if the entity is not decorated
if No (Entity (N)) then
return Skip;
-- Don't collect identifiers of packages, called functions, etc
elsif Ekind (Entity (N)) in
E_Package | E_Function | E_Procedure | E_Entry
then
return Skip;
-- For rewritten nodes, continue the traversal in the original
-- subtree. Needed to handle aggregates in original expressions
-- extracted from the tree by Remove_Side_Effects.
elsif Is_Rewrite_Substitution (N) then
Collect_Identifiers (Original_Node (N));
return Skip;
-- For now we skip aggregate discriminants, since they require
-- performing the analysis in two phases to identify conflicts:
-- first one analyzing discriminants and second one analyzing
-- the rest of components (since at run time, discriminants are
-- evaluated prior to components): too much computation cost
-- to identify a corner case???
elsif Nkind (Parent (N)) = N_Component_Association
and then Nkind (Parent (Parent (N))) in
N_Aggregate | N_Extension_Aggregate
then
declare
Choice : constant Node_Id := First (Choices (Parent (N)));
begin
if Ekind (Entity (N)) = E_Discriminant then
return Skip;
elsif Expression (Parent (N)) = N
and then Nkind (Choice) = N_Identifier
and then Ekind (Entity (Choice)) = E_Discriminant
then
return Skip;
end if;
end;
-- Analyze if N is a writable actual of a function
elsif Nkind (Parent (N)) = N_Function_Call then
declare
Call : constant Node_Id := Parent (N);
Actual : Node_Id;
Formal : Node_Id;
begin
Id := Get_Called_Entity (Call);
-- In case of previous error, no check is possible
if No (Id) then
return Abandon;
end if;
if Ekind (Id) in E_Function | E_Generic_Function
and then Has_Out_Or_In_Out_Parameter (Id)
then
Formal := First_Formal (Id);
Actual := First_Actual (Call);
while Present (Actual) and then Present (Formal) loop
if Actual = N then
if Ekind (Formal) in E_Out_Parameter
| E_In_Out_Parameter
then
Is_Writable_Actual := True;
end if;
exit;
end if;
Next_Formal (Formal);
Next_Actual (Actual);
end loop;
end if;
end;
end if;
if Is_Writable_Actual then
-- Skip checking the error in non-elementary types since
-- RM 6.4.1(6.15/3) is restricted to elementary types, but
-- store this actual in Writable_Actuals_List since it is
-- needed to perform checks on other constructs that have
-- arbitrary order of evaluation (for example, aggregates).
if not Is_Elementary_Type (Etype (N)) then
if not Contains (Writable_Actuals_List, N) then
Append_New_Elmt (N, To => Writable_Actuals_List);
end if;
-- Second occurrence of an elementary type writable actual
elsif Contains (Writable_Actuals_List, N) then
-- Report the error on the second occurrence of the
-- identifier. We cannot assume that N is the second
-- occurrence (according to their location in the
-- sources), since Traverse_Func walks through Field2
-- last (see comment in the body of Traverse_Func).
declare
Elmt : Elmt_Id;
begin
Elmt := First_Elmt (Writable_Actuals_List);
while Present (Elmt)
and then Entity (Node (Elmt)) /= Entity (N)
loop
Next_Elmt (Elmt);
end loop;
if Sloc (N) > Sloc (Node (Elmt)) then
Error_Node := N;
else
Error_Node := Node (Elmt);
end if;
Error_Msg_NE
("value may be affected by call to & "
& "because order of evaluation is arbitrary",
Error_Node, Id);
return Abandon;
end;
-- First occurrence of a elementary type writable actual
else
Append_New_Elmt (N, To => Writable_Actuals_List);
end if;
else
if Identifiers_List = No_Elist then
Identifiers_List := New_Elmt_List;
end if;
Append_Unique_Elmt (N, Identifiers_List);
end if;
end if;
return OK;
end Check_Node;
--------------
-- Contains --
--------------
function Contains
(List : Elist_Id;
N : Node_Id) return Boolean
is
pragma Assert (Nkind (N) in N_Has_Entity);
Elmt : Elmt_Id;
begin
if List = No_Elist then
return False;
end if;
Elmt := First_Elmt (List);
while Present (Elmt) loop
if Entity (Node (Elmt)) = Entity (N) then
return True;
else
Next_Elmt (Elmt);
end if;
end loop;
return False;
end Contains;
------------------
-- Do_Traversal --
------------------
procedure Do_Traversal is new Traverse_Proc (Check_Node);
-- The traversal procedure
-- Start of processing for Collect_Identifiers
begin
if Present (Error_Node) then
return;
end if;
if Nkind (N) in N_Subexpr and then Is_OK_Static_Expression (N) then
return;
end if;
Do_Traversal (N);
end Collect_Identifiers;
-- Start of processing for Check_Function_Writable_Actuals
begin
-- The check only applies to Ada 2012 code on which Check_Actuals has
-- been set, and only to constructs that have multiple constituents
-- whose order of evaluation is not specified by the language.
if Ada_Version < Ada_2012
or else not Check_Actuals (N)
or else Nkind (N) not in N_Op
| N_Membership_Test
| N_Range
| N_Aggregate
| N_Extension_Aggregate
| N_Full_Type_Declaration
| N_Function_Call
| N_Procedure_Call_Statement
| N_Entry_Call_Statement
or else (Nkind (N) = N_Full_Type_Declaration
and then not Is_Record_Type (Defining_Identifier (N)))
-- In addition, this check only applies to source code, not to code
-- generated by constraint checks.
or else not Comes_From_Source (N)
then
return;
end if;
-- If a construct C has two or more direct constituents that are names
-- or expressions whose evaluation may occur in an arbitrary order, at
-- least one of which contains a function call with an in out or out
-- parameter, then the construct is legal only if: for each name N that
-- is passed as a parameter of mode in out or out to some inner function
-- call C2 (not including the construct C itself), there is no other
-- name anywhere within a direct constituent of the construct C other
-- than the one containing C2, that is known to refer to the same
-- object (RM 6.4.1(6.17/3)).
case Nkind (N) is
when N_Range =>
Collect_Identifiers (Low_Bound (N));
Collect_Identifiers (High_Bound (N));
when N_Membership_Test
| N_Op
=>
declare
Expr : Node_Id;
begin
Collect_Identifiers (Left_Opnd (N));
if Present (Right_Opnd (N)) then
Collect_Identifiers (Right_Opnd (N));
end if;
if Nkind (N) in N_In | N_Not_In
and then Present (Alternatives (N))
then
Expr := First (Alternatives (N));
while Present (Expr) loop
Collect_Identifiers (Expr);
Next (Expr);
end loop;
end if;
end;
when N_Full_Type_Declaration =>
declare
function Get_Record_Part (N : Node_Id) return Node_Id;
-- Return the record part of this record type definition
function Get_Record_Part (N : Node_Id) return Node_Id is
Type_Def : constant Node_Id := Type_Definition (N);
begin
if Nkind (Type_Def) = N_Derived_Type_Definition then
return Record_Extension_Part (Type_Def);
else
return Type_Def;
end if;
end Get_Record_Part;
Comp : Node_Id;
Def_Id : Entity_Id := Defining_Identifier (N);
Rec : Node_Id := Get_Record_Part (N);
begin
-- No need to perform any analysis if the record has no
-- components
if No (Rec) or else No (Component_List (Rec)) then
return;
end if;
-- Collect the identifiers starting from the deepest
-- derivation. Done to report the error in the deepest
-- derivation.
loop
if Present (Component_List (Rec)) then
Comp := First (Component_Items (Component_List (Rec)));
while Present (Comp) loop
if Nkind (Comp) = N_Component_Declaration
and then Present (Expression (Comp))
then
Collect_Identifiers (Expression (Comp));
end if;
Next (Comp);
end loop;
end if;
exit when No (Underlying_Type (Etype (Def_Id)))
or else Base_Type (Underlying_Type (Etype (Def_Id)))
= Def_Id;
Def_Id := Base_Type (Underlying_Type (Etype (Def_Id)));
Rec := Get_Record_Part (Parent (Def_Id));
end loop;
end;
when N_Entry_Call_Statement
| N_Subprogram_Call
=>
declare
Id : constant Entity_Id := Get_Called_Entity (N);
Formal : Node_Id;
Actual : Node_Id;
begin
Formal := First_Formal (Id);
Actual := First_Actual (N);
while Present (Actual) and then Present (Formal) loop
if Ekind (Formal) in E_Out_Parameter | E_In_Out_Parameter
then
Collect_Identifiers (Actual);
end if;
Next_Formal (Formal);
Next_Actual (Actual);
end loop;
end;
when N_Aggregate
| N_Extension_Aggregate
=>
declare
Assoc : Node_Id;
Choice : Node_Id;
Comp_Expr : Node_Id;
begin
-- Handle the N_Others_Choice of array aggregates with static
-- bounds. There is no need to perform this analysis in
-- aggregates without static bounds since we cannot evaluate
-- if the N_Others_Choice covers several elements. There is
-- no need to handle the N_Others choice of record aggregates
-- since at this stage it has been already expanded by
-- Resolve_Record_Aggregate.
if Is_Array_Type (Etype (N))
and then Nkind (N) = N_Aggregate
and then Present (Aggregate_Bounds (N))
and then Compile_Time_Known_Bounds (Etype (N))
and then Expr_Value (High_Bound (Aggregate_Bounds (N)))
>
Expr_Value (Low_Bound (Aggregate_Bounds (N)))
then
declare
Count_Components : Uint := Uint_0;
Num_Components : Uint;
Others_Assoc : Node_Id := Empty;
Others_Choice : Node_Id := Empty;
Others_Box_Present : Boolean := False;
begin
-- Count positional associations
if Present (Expressions (N)) then
Comp_Expr := First (Expressions (N));
while Present (Comp_Expr) loop
Count_Components := Count_Components + 1;
Next (Comp_Expr);
end loop;
end if;
-- Count the rest of elements and locate the N_Others
-- choice (if any)
Assoc := First (Component_Associations (N));
while Present (Assoc) loop
Choice := First (Choices (Assoc));
while Present (Choice) loop
if Nkind (Choice) = N_Others_Choice then
Others_Assoc := Assoc;
Others_Choice := Choice;
Others_Box_Present := Box_Present (Assoc);
-- Count several components
elsif Nkind (Choice) in
N_Range | N_Subtype_Indication
or else (Is_Entity_Name (Choice)
and then Is_Type (Entity (Choice)))
then
declare
L, H : Node_Id;
begin
Get_Index_Bounds (Choice, L, H);
pragma Assert
(Compile_Time_Known_Value (L)
and then Compile_Time_Known_Value (H));
Count_Components :=
Count_Components
+ Expr_Value (H) - Expr_Value (L) + 1;
end;
-- Count single component. No other case available
-- since we are handling an aggregate with static
-- bounds.
else
pragma Assert (Is_OK_Static_Expression (Choice)
or else Nkind (Choice) = N_Identifier
or else Nkind (Choice) = N_Integer_Literal);
Count_Components := Count_Components + 1;
end if;
Next (Choice);
end loop;
Next (Assoc);
end loop;
Num_Components :=
Expr_Value (High_Bound (Aggregate_Bounds (N))) -
Expr_Value (Low_Bound (Aggregate_Bounds (N))) + 1;
pragma Assert (Count_Components <= Num_Components);
-- Handle the N_Others choice if it covers several
-- components
if Present (Others_Choice)
and then (Num_Components - Count_Components) > 1
then
if not Others_Box_Present then
-- At this stage, if expansion is active, the
-- expression of the others choice has not been
-- analyzed. Hence we generate a duplicate and
-- we analyze it silently to have available the
-- minimum decoration required to collect the
-- identifiers.
pragma Assert (Present (Others_Assoc));
if not Expander_Active then
Comp_Expr := Expression (Others_Assoc);
else
Comp_Expr :=
New_Copy_Tree (Expression (Others_Assoc));
Preanalyze_Without_Errors (Comp_Expr);
end if;
Collect_Identifiers (Comp_Expr);
if Writable_Actuals_List /= No_Elist then
-- As suggested by Robert, at current stage we
-- report occurrences of this case as warnings.
Error_Msg_N
("writable function parameter may affect "
& "value in other component because order "
& "of evaluation is unspecified??",
Node (First_Elmt (Writable_Actuals_List)));
end if;
end if;
end if;
end;
-- For an array aggregate, a discrete_choice_list that has
-- a nonstatic range is considered as two or more separate
-- occurrences of the expression (RM 6.4.1(20/3)).
elsif Is_Array_Type (Etype (N))
and then Nkind (N) = N_Aggregate
and then Present (Aggregate_Bounds (N))
and then not Compile_Time_Known_Bounds (Etype (N))
then
-- Collect identifiers found in the dynamic bounds
declare
Count_Components : Natural := 0;
Low, High : Node_Id;
begin
Assoc := First (Component_Associations (N));
while Present (Assoc) loop
Choice := First (Choices (Assoc));
while Present (Choice) loop
if Nkind (Choice) in
N_Range | N_Subtype_Indication
or else (Is_Entity_Name (Choice)
and then Is_Type (Entity (Choice)))
then
Get_Index_Bounds (Choice, Low, High);
if not Compile_Time_Known_Value (Low) then
Collect_Identifiers (Low);
if No (Aggr_Error_Node) then
Aggr_Error_Node := Low;
end if;
end if;
if not Compile_Time_Known_Value (High) then
Collect_Identifiers (High);
if No (Aggr_Error_Node) then
Aggr_Error_Node := High;
end if;
end if;
-- The RM rule is violated if there is more than
-- a single choice in a component association.
else
Count_Components := Count_Components + 1;
if No (Aggr_Error_Node)
and then Count_Components > 1
then
Aggr_Error_Node := Choice;
end if;
if not Compile_Time_Known_Value (Choice) then
Collect_Identifiers (Choice);
end if;
end if;
Next (Choice);
end loop;
Next (Assoc);
end loop;
end;
end if;
-- Handle ancestor part of extension aggregates
if Nkind (N) = N_Extension_Aggregate then
Collect_Identifiers (Ancestor_Part (N));
end if;
-- Handle positional associations
if Present (Expressions (N)) then
Comp_Expr := First (Expressions (N));
while Present (Comp_Expr) loop
if not Is_OK_Static_Expression (Comp_Expr) then
Collect_Identifiers (Comp_Expr);
end if;
Next (Comp_Expr);
end loop;
end if;
-- Handle discrete associations
if Present (Component_Associations (N)) then
Assoc := First (Component_Associations (N));
while Present (Assoc) loop
if not Box_Present (Assoc) then
Choice := First (Choices (Assoc));
while Present (Choice) loop
-- For now we skip discriminants since it requires
-- performing the analysis in two phases: first one
-- analyzing discriminants and second one analyzing
-- the rest of components since discriminants are
-- evaluated prior to components: too much extra
-- work to detect a corner case???
if Nkind (Choice) in N_Has_Entity
and then Present (Entity (Choice))
and then Ekind (Entity (Choice)) = E_Discriminant
then
null;
elsif Box_Present (Assoc) then
null;
else
if not Analyzed (Expression (Assoc)) then
Comp_Expr :=
New_Copy_Tree (Expression (Assoc));
Set_Parent (Comp_Expr, Parent (N));
Preanalyze_Without_Errors (Comp_Expr);
else
Comp_Expr := Expression (Assoc);
end if;
Collect_Identifiers (Comp_Expr);
end if;
Next (Choice);
end loop;
end if;
Next (Assoc);
end loop;
end if;
end;
when others =>
return;
end case;
-- No further action needed if we already reported an error
if Present (Error_Node) then
return;
end if;
-- Check violation of RM 6.20/3 in aggregates
if Present (Aggr_Error_Node)
and then Writable_Actuals_List /= No_Elist
then
Error_Msg_N
("value may be affected by call in other component because they "
& "are evaluated in unspecified order",
Node (First_Elmt (Writable_Actuals_List)));
return;
end if;
-- Check if some writable argument of a function is referenced
if Writable_Actuals_List /= No_Elist
and then Identifiers_List /= No_Elist
then
declare
Elmt_1 : Elmt_Id;
Elmt_2 : Elmt_Id;
begin
Elmt_1 := First_Elmt (Writable_Actuals_List);
while Present (Elmt_1) loop
Elmt_2 := First_Elmt (Identifiers_List);
while Present (Elmt_2) loop
if Entity (Node (Elmt_1)) = Entity (Node (Elmt_2)) then
case Nkind (Parent (Node (Elmt_2))) is
when N_Aggregate
| N_Component_Association
| N_Component_Declaration
=>
Error_Msg_N
("value may be affected by call in other "
& "component because they are evaluated "
& "in unspecified order",
Node (Elmt_2));
when N_In
| N_Not_In
=>
Error_Msg_N
("value may be affected by call in other "
& "alternative because they are evaluated "
& "in unspecified order",
Node (Elmt_2));
when others =>
Error_Msg_N
("value of actual may be affected by call in "
& "other actual because they are evaluated "
& "in unspecified order",
Node (Elmt_2));
end case;
end if;
Next_Elmt (Elmt_2);
end loop;
Next_Elmt (Elmt_1);
end loop;
end;
end if;
end Check_Function_Writable_Actuals;
--------------------------------
-- Check_Implicit_Dereference --
--------------------------------
procedure Check_Implicit_Dereference (N : Node_Id; Typ : Entity_Id) is
Disc : Entity_Id;
Desig : Entity_Id;
Nam : Node_Id;
begin
if Nkind (N) = N_Indexed_Component
and then Present (Generalized_Indexing (N))
then
Nam := Generalized_Indexing (N);
else
Nam := N;
end if;
if Ada_Version < Ada_2012
or else not Has_Implicit_Dereference (Base_Type (Typ))
then
return;
elsif not Comes_From_Source (N)
and then Nkind (N) /= N_Indexed_Component
then
return;
elsif Is_Entity_Name (Nam) and then Is_Type (Entity (Nam)) then
null;
else
Disc := First_Discriminant (Typ);
while Present (Disc) loop
if Has_Implicit_Dereference (Disc) then
Desig := Designated_Type (Etype (Disc));
Add_One_Interp (Nam, Disc, Desig);
-- If the node is a generalized indexing, add interpretation
-- to that node as well, for subsequent resolution.
if Nkind (N) = N_Indexed_Component then
Add_One_Interp (N, Disc, Desig);
end if;
-- If the operation comes from a generic unit and the context
-- is a selected component, the selector name may be global
-- and set in the instance already. Remove the entity to
-- force resolution of the selected component, and the
-- generation of an explicit dereference if needed.
if In_Instance
and then Nkind (Parent (Nam)) = N_Selected_Component
then
Set_Entity (Selector_Name (Parent (Nam)), Empty);
end if;
exit;
end if;
Next_Discriminant (Disc);
end loop;
end if;
end Check_Implicit_Dereference;
----------------------------------
-- Check_Internal_Protected_Use --
----------------------------------
procedure Check_Internal_Protected_Use (N : Node_Id; Nam : Entity_Id) is
S : Entity_Id;
Prot : Entity_Id;
begin
Prot := Empty;
S := Current_Scope;
while Present (S) loop
if S = Standard_Standard then
exit;
elsif Ekind (S) = E_Function
and then Ekind (Scope (S)) = E_Protected_Type
then
Prot := Scope (S);
exit;
end if;
S := Scope (S);
end loop;
if Present (Prot)
and then Scope (Nam) = Prot
and then Ekind (Nam) /= E_Function
then
-- An indirect function call (e.g. a callback within a protected
-- function body) is not statically illegal. If the access type is
-- anonymous and is the type of an access parameter, the scope of Nam
-- will be the protected type, but it is not a protected operation.
if Ekind (Nam) = E_Subprogram_Type
and then Nkind (Associated_Node_For_Itype (Nam)) =
N_Function_Specification
then
null;
elsif Nkind (N) = N_Subprogram_Renaming_Declaration then
Error_Msg_N
("within protected function cannot use protected procedure in "
& "renaming or as generic actual", N);
elsif Nkind (N) = N_Attribute_Reference then
Error_Msg_N
("within protected function cannot take access of protected "
& "procedure", N);
else
Error_Msg_N
("within protected function, protected object is constant", N);
Error_Msg_N
("\cannot call operation that may modify it", N);
end if;
end if;
-- Verify that an internal call does not appear within a precondition
-- of a protected operation. This implements AI12-0166.
-- The precondition aspect has been rewritten as a pragma Precondition
-- and we check whether the scope of the called subprogram is the same
-- as that of the entity to which the aspect applies.
if Convention (Nam) = Convention_Protected then
declare
P : Node_Id;
begin
P := Parent (N);
while Present (P) loop
if Nkind (P) = N_Pragma
and then Chars (Pragma_Identifier (P)) = Name_Precondition
and then From_Aspect_Specification (P)
and then
Scope (Entity (Corresponding_Aspect (P))) = Scope (Nam)
then
Error_Msg_N
("internal call cannot appear in precondition of "
& "protected operation", N);
return;
elsif Nkind (P) = N_Pragma
and then Chars (Pragma_Identifier (P)) = Name_Contract_Cases
then
-- Check whether call is in a case guard. It is legal in a
-- consequence.
P := N;
while Present (P) loop
if Nkind (Parent (P)) = N_Component_Association
and then P /= Expression (Parent (P))
then
Error_Msg_N
("internal call cannot appear in case guard in a "
& "contract case", N);
end if;
P := Parent (P);
end loop;
return;
elsif Nkind (P) = N_Parameter_Specification
and then Scope (Current_Scope) = Scope (Nam)
and then Nkind (Parent (P)) in
N_Entry_Declaration | N_Subprogram_Declaration
then
Error_Msg_N
("internal call cannot appear in default for formal of "
& "protected operation", N);
return;
end if;
P := Parent (P);
end loop;
end;
end if;
end Check_Internal_Protected_Use;
---------------------------------------
-- Check_Later_Vs_Basic_Declarations --
---------------------------------------
procedure Check_Later_Vs_Basic_Declarations
(Decls : List_Id;
During_Parsing : Boolean)
is
Body_Sloc : Source_Ptr;
Decl : Node_Id;
function Is_Later_Declarative_Item (Decl : Node_Id) return Boolean;
-- Return whether Decl is considered as a declarative item.
-- When During_Parsing is True, the semantics of Ada 83 is followed.
-- When During_Parsing is False, the semantics of SPARK is followed.
-------------------------------
-- Is_Later_Declarative_Item --
-------------------------------
function Is_Later_Declarative_Item (Decl : Node_Id) return Boolean is
begin
if Nkind (Decl) in N_Later_Decl_Item then
return True;
elsif Nkind (Decl) = N_Pragma then
return True;
elsif During_Parsing then
return False;
-- In SPARK, a package declaration is not considered as a later
-- declarative item.
elsif Nkind (Decl) = N_Package_Declaration then
return False;
-- In SPARK, a renaming is considered as a later declarative item
elsif Nkind (Decl) in N_Renaming_Declaration then
return True;
else
return False;
end if;
end Is_Later_Declarative_Item;
-- Start of processing for Check_Later_Vs_Basic_Declarations
begin
Decl := First (Decls);
-- Loop through sequence of basic declarative items
Outer : while Present (Decl) loop
if Nkind (Decl) not in
N_Subprogram_Body | N_Package_Body | N_Task_Body
and then Nkind (Decl) not in N_Body_Stub
then
Next (Decl);
-- Once a body is encountered, we only allow later declarative
-- items. The inner loop checks the rest of the list.
else
Body_Sloc := Sloc (Decl);
Inner : while Present (Decl) loop
if not Is_Later_Declarative_Item (Decl) then
if During_Parsing then
if Ada_Version = Ada_83 then
Error_Msg_Sloc := Body_Sloc;
Error_Msg_N
("(Ada 83) decl cannot appear after body#", Decl);
end if;
end if;
end if;
Next (Decl);
end loop Inner;
end if;
end loop Outer;
end Check_Later_Vs_Basic_Declarations;
---------------------------
-- Check_No_Hidden_State --
---------------------------
procedure Check_No_Hidden_State (Id : Entity_Id) is
Context : Entity_Id := Empty;
Not_Visible : Boolean := False;
Scop : Entity_Id;
begin
pragma Assert (Ekind (Id) in E_Abstract_State | E_Variable);
-- Nothing to do for internally-generated abstract states and variables
-- because they do not represent the hidden state of the source unit.
if not Comes_From_Source (Id) then
return;
end if;
-- Find the proper context where the object or state appears
Scop := Scope (Id);
while Present (Scop) loop
Context := Scop;
-- Keep track of the context's visibility
Not_Visible := Not_Visible or else In_Private_Part (Context);
-- Prevent the search from going too far
if Context = Standard_Standard then
return;
-- Objects and states that appear immediately within a subprogram or
-- entry inside a construct nested within a subprogram do not
-- introduce a hidden state. They behave as local variable
-- declarations. The same is true for elaboration code inside a block
-- or a task.
elsif Is_Subprogram_Or_Entry (Context)
or else Ekind (Context) in E_Block | E_Task_Type
then
return;
end if;
-- Stop the traversal when a package subject to a null abstract state
-- has been found.
if Is_Package_Or_Generic_Package (Context)
and then Has_Null_Abstract_State (Context)
then
exit;
end if;
Scop := Scope (Scop);
end loop;
-- At this point we know that there is at least one package with a null
-- abstract state in visibility. Emit an error message unconditionally
-- if the entity being processed is a state because the placement of the
-- related package is irrelevant. This is not the case for objects as
-- the intermediate context matters.
if Present (Context)
and then (Ekind (Id) = E_Abstract_State or else Not_Visible)
then
Error_Msg_N ("cannot introduce hidden state &", Id);
Error_Msg_NE ("\package & has null abstract state", Id, Context);
end if;
end Check_No_Hidden_State;
---------------------------------------------
-- Check_Nonoverridable_Aspect_Consistency --
---------------------------------------------
procedure Check_Inherited_Nonoverridable_Aspects
(Inheritor : Entity_Id;
Interface_List : List_Id;
Parent_Type : Entity_Id) is
-- array needed for iterating over subtype values
Nonoverridable_Aspects : constant array (Positive range <>) of
Nonoverridable_Aspect_Id :=
(Aspect_Default_Iterator,
Aspect_Iterator_Element,
Aspect_Implicit_Dereference,
Aspect_Constant_Indexing,
Aspect_Variable_Indexing,
Aspect_Aggregate,
Aspect_Max_Entry_Queue_Length
-- , Aspect_No_Controlled_Parts
);
-- Note that none of these 8 aspects can be specified (for a type)
-- via a pragma. For 7 of them, the corresponding pragma does not
-- exist. The Pragma_Id enumeration type does include
-- Pragma_Max_Entry_Queue_Length, but that pragma is only use to
-- specify the aspect for a protected entry or entry family, not for
-- a type, and therefore cannot introduce the sorts of inheritance
-- issues that we are concerned with in this procedure.
type Entity_Array is array (Nat range <>) of Entity_Id;
function Ancestor_Entities return Entity_Array;
-- Returns all progenitors (including parent type, if present)
procedure Check_Consistency_For_One_Aspect_Of_Two_Ancestors
(Aspect : Nonoverridable_Aspect_Id;
Ancestor_1 : Entity_Id;
Aspect_Spec_1 : Node_Id;
Ancestor_2 : Entity_Id;
Aspect_Spec_2 : Node_Id);
-- A given aspect has been specified for each of two ancestors;
-- check that the two aspect specifications are compatible (see
-- RM 13.1.1(18.5) and AI12-0211).
-----------------------
-- Ancestor_Entities --
-----------------------
function Ancestor_Entities return Entity_Array is
Ifc_Count : constant Nat := List_Length (Interface_List);
Ifc_Ancestors : Entity_Array (1 .. Ifc_Count);
Ifc : Node_Id := First (Interface_List);
begin
for Idx in Ifc_Ancestors'Range loop
Ifc_Ancestors (Idx) := Entity (Ifc);
pragma Assert (Present (Ifc_Ancestors (Idx)));
Ifc := Next (Ifc);
end loop;
pragma Assert (not Present (Ifc));
if Present (Parent_Type) then
return Parent_Type & Ifc_Ancestors;
else
return Ifc_Ancestors;
end if;
end Ancestor_Entities;
-------------------------------------------------------
-- Check_Consistency_For_One_Aspect_Of_Two_Ancestors --
-------------------------------------------------------
procedure Check_Consistency_For_One_Aspect_Of_Two_Ancestors
(Aspect : Nonoverridable_Aspect_Id;
Ancestor_1 : Entity_Id;
Aspect_Spec_1 : Node_Id;
Ancestor_2 : Entity_Id;
Aspect_Spec_2 : Node_Id) is
begin
if not Is_Confirming (Aspect, Aspect_Spec_1, Aspect_Spec_2) then
Error_Msg_Name_1 := Aspect_Names (Aspect);
Error_Msg_Name_2 := Chars (Ancestor_1);
Error_Msg_Name_3 := Chars (Ancestor_2);
Error_Msg (
"incompatible % aspects inherited from ancestors % and %",
Sloc (Inheritor));
end if;
end Check_Consistency_For_One_Aspect_Of_Two_Ancestors;
Ancestors : constant Entity_Array := Ancestor_Entities;
-- start of processing for Check_Inherited_Nonoverridable_Aspects
begin
-- No Ada_Version check here; AI12-0211 is a binding interpretation.
if Ancestors'Length < 2 then
return; -- Inconsistency impossible; it takes 2 to disagree.
elsif In_Instance_Body then
return; -- No legality checking in an instance body.
end if;
for Aspect of Nonoverridable_Aspects loop
declare
First_Ancestor_With_Aspect : Entity_Id := Empty;
First_Aspect_Spec, Current_Aspect_Spec : Node_Id := Empty;
begin
for Ancestor of Ancestors loop
Current_Aspect_Spec := Find_Aspect (Ancestor, Aspect);
if Present (Current_Aspect_Spec) then
if Present (First_Ancestor_With_Aspect) then
Check_Consistency_For_One_Aspect_Of_Two_Ancestors
(Aspect => Aspect,
Ancestor_1 => First_Ancestor_With_Aspect,
Aspect_Spec_1 => First_Aspect_Spec,
Ancestor_2 => Ancestor,
Aspect_Spec_2 => Current_Aspect_Spec);
else
First_Ancestor_With_Aspect := Ancestor;
First_Aspect_Spec := Current_Aspect_Spec;
end if;
end if;
end loop;
end;
end loop;
end Check_Inherited_Nonoverridable_Aspects;
----------------------------------------
-- Check_Nonvolatile_Function_Profile --
----------------------------------------
procedure Check_Nonvolatile_Function_Profile (Func_Id : Entity_Id) is
Formal : Entity_Id;
begin
-- Inspect all formal parameters
Formal := First_Formal (Func_Id);
while Present (Formal) loop
if Is_Effectively_Volatile_For_Reading (Etype (Formal)) then
Error_Msg_NE
("nonvolatile function & cannot have a volatile parameter",
Formal, Func_Id);
end if;
Next_Formal (Formal);
end loop;
-- Inspect the return type
if Is_Effectively_Volatile_For_Reading (Etype (Func_Id)) then
Error_Msg_NE
("nonvolatile function & cannot have a volatile return type",
Result_Definition (Parent (Func_Id)), Func_Id);
end if;
end Check_Nonvolatile_Function_Profile;
-------------------
-- Check_Parents --
-------------------
function Check_Parents (N : Node_Id; List : Elist_Id) return Boolean is
function Check_Node
(Parent_Node : Node_Id;
N : Node_Id) return Traverse_Result;
-- Process a single node.
----------------
-- Check_Node --
----------------
function Check_Node
(Parent_Node : Node_Id;
N : Node_Id) return Traverse_Result is
begin
if Nkind (N) = N_Identifier
and then Parent (N) /= Parent_Node
and then Present (Entity (N))
and then Contains (List, Entity (N))
then
return Abandon;
end if;
return OK;
end Check_Node;
function Traverse is new Traverse_Func_With_Parent (Check_Node);
-- Start of processing for Check_Parents
begin
return Traverse (N) = OK;
end Check_Parents;
-----------------------------
-- Check_Part_Of_Reference --
-----------------------------
procedure Check_Part_Of_Reference (Var_Id : Entity_Id; Ref : Node_Id) is
function Is_Enclosing_Package_Body
(Body_Decl : Node_Id;
Obj_Id : Entity_Id) return Boolean;
pragma Inline (Is_Enclosing_Package_Body);
-- Determine whether package body Body_Decl or its corresponding spec
-- immediately encloses the declaration of object Obj_Id.
function Is_Internal_Declaration_Or_Body
(Decl : Node_Id) return Boolean;
pragma Inline (Is_Internal_Declaration_Or_Body);
-- Determine whether declaration or body denoted by Decl is internal
function Is_Single_Declaration_Or_Body
(Decl : Node_Id;
Conc_Typ : Entity_Id) return Boolean;
pragma Inline (Is_Single_Declaration_Or_Body);
-- Determine whether protected/task declaration or body denoted by Decl
-- belongs to single concurrent type Conc_Typ.
function Is_Single_Task_Pragma
(Prag : Node_Id;
Task_Typ : Entity_Id) return Boolean;
pragma Inline (Is_Single_Task_Pragma);
-- Determine whether pragma Prag belongs to single task type Task_Typ
-------------------------------
-- Is_Enclosing_Package_Body --
-------------------------------
function Is_Enclosing_Package_Body
(Body_Decl : Node_Id;
Obj_Id : Entity_Id) return Boolean
is
Obj_Context : Node_Id;
begin
-- Find the context of the object declaration
Obj_Context := Parent (Declaration_Node (Obj_Id));
if Nkind (Obj_Context) = N_Package_Specification then
Obj_Context := Parent (Obj_Context);
end if;
-- The object appears immediately within the package body
if Obj_Context = Body_Decl then
return True;
-- The object appears immediately within the corresponding spec
elsif Nkind (Obj_Context) = N_Package_Declaration
and then Unit_Declaration_Node (Corresponding_Spec (Body_Decl)) =
Obj_Context
then
return True;
end if;
return False;
end Is_Enclosing_Package_Body;
-------------------------------------
-- Is_Internal_Declaration_Or_Body --
-------------------------------------
function Is_Internal_Declaration_Or_Body
(Decl : Node_Id) return Boolean
is
begin
if Comes_From_Source (Decl) then
return False;
-- A body generated for an expression function which has not been
-- inserted into the tree yet (In_Spec_Expression is True) is not
-- considered internal.
elsif Nkind (Decl) = N_Subprogram_Body
and then Was_Expression_Function (Decl)
and then not In_Spec_Expression
then
return False;
end if;
return True;
end Is_Internal_Declaration_Or_Body;
-----------------------------------
-- Is_Single_Declaration_Or_Body --
-----------------------------------
function Is_Single_Declaration_Or_Body
(Decl : Node_Id;
Conc_Typ : Entity_Id) return Boolean
is
Spec_Id : constant Entity_Id := Unique_Defining_Entity (Decl);
begin
return
Present (Anonymous_Object (Spec_Id))
and then Anonymous_Object (Spec_Id) = Conc_Typ;
end Is_Single_Declaration_Or_Body;
---------------------------
-- Is_Single_Task_Pragma --
---------------------------
function Is_Single_Task_Pragma
(Prag : Node_Id;
Task_Typ : Entity_Id) return Boolean
is
Decl : constant Node_Id := Find_Related_Declaration_Or_Body (Prag);
begin
-- To qualify, the pragma must be associated with single task type
-- Task_Typ.
return
Is_Single_Task_Object (Task_Typ)
and then Nkind (Decl) = N_Object_Declaration
and then Defining_Entity (Decl) = Task_Typ;
end Is_Single_Task_Pragma;
-- Local variables
Conc_Obj : constant Entity_Id := Encapsulating_State (Var_Id);
Par : Node_Id;
Prag_Nam : Name_Id;
Prev : Node_Id;
-- Start of processing for Check_Part_Of_Reference
begin
-- Nothing to do when the variable was recorded, but did not become a
-- constituent of a single concurrent type.
if No (Conc_Obj) then
return;
end if;
-- Traverse the parent chain looking for a suitable context for the
-- reference to the concurrent constituent.
Prev := Ref;
Par := Parent (Prev);
while Present (Par) loop
if Nkind (Par) = N_Pragma then
Prag_Nam := Pragma_Name (Par);
-- A concurrent constituent is allowed to appear in pragmas
-- Initial_Condition and Initializes as this is part of the
-- elaboration checks for the constituent (SPARK RM 9(3)).
if Prag_Nam in Name_Initial_Condition | Name_Initializes then
return;
-- When the reference appears within pragma Depends or Global,
-- check whether the pragma applies to a single task type. Note
-- that the pragma may not encapsulated by the type definition,
-- but this is still a valid context.
elsif Prag_Nam in Name_Depends | Name_Global
and then Is_Single_Task_Pragma (Par, Conc_Obj)
then
return;
end if;
-- The reference appears somewhere in the definition of a single
-- concurrent type (SPARK RM 9(3)).
elsif Nkind (Par) in
N_Single_Protected_Declaration | N_Single_Task_Declaration
and then Defining_Entity (Par) = Conc_Obj
then
return;
-- The reference appears within the declaration or body of a single
-- concurrent type (SPARK RM 9(3)).
elsif Nkind (Par) in N_Protected_Body
| N_Protected_Type_Declaration
| N_Task_Body
| N_Task_Type_Declaration
and then Is_Single_Declaration_Or_Body (Par, Conc_Obj)
then
return;
-- The reference appears within the statement list of the object's
-- immediately enclosing package (SPARK RM 9(3)).
elsif Nkind (Par) = N_Package_Body
and then Nkind (Prev) = N_Handled_Sequence_Of_Statements
and then Is_Enclosing_Package_Body (Par, Var_Id)
then
return;
-- The reference has been relocated within an internally generated
-- package or subprogram. Assume that the reference is legal as the
-- real check was already performed in the original context of the
-- reference.
elsif Nkind (Par) in N_Package_Body
| N_Package_Declaration
| N_Subprogram_Body
| N_Subprogram_Declaration
and then Is_Internal_Declaration_Or_Body (Par)
then
return;
-- The reference has been relocated to an inlined body for GNATprove.
-- Assume that the reference is legal as the real check was already
-- performed in the original context of the reference.
elsif GNATprove_Mode
and then Nkind (Par) = N_Subprogram_Body
and then Chars (Defining_Entity (Par)) = Name_uParent
then
return;
end if;
Prev := Par;
Par := Parent (Prev);
end loop;
-- At this point it is known that the reference does not appear within a
-- legal context.
Error_Msg_NE
("reference to variable & cannot appear in this context", Ref, Var_Id);
Error_Msg_Name_1 := Chars (Var_Id);
if Is_Single_Protected_Object (Conc_Obj) then
Error_Msg_NE
("\% is constituent of single protected type &", Ref, Conc_Obj);
else
Error_Msg_NE
("\% is constituent of single task type &", Ref, Conc_Obj);
end if;
end Check_Part_Of_Reference;
------------------------------------------
-- Check_Potentially_Blocking_Operation --
------------------------------------------
procedure Check_Potentially_Blocking_Operation (N : Node_Id) is
S : Entity_Id;
begin
-- N is one of the potentially blocking operations listed in 9.5.1(8).
-- When pragma Detect_Blocking is active, the run time will raise
-- Program_Error. Here we only issue a warning, since we generally
-- support the use of potentially blocking operations in the absence
-- of the pragma.
-- Indirect blocking through a subprogram call cannot be diagnosed
-- statically without interprocedural analysis, so we do not attempt
-- to do it here.
S := Scope (Current_Scope);
while Present (S) and then S /= Standard_Standard loop
if Is_Protected_Type (S) then
Error_Msg_N
("potentially blocking operation in protected operation??", N);
return;
end if;
S := Scope (S);
end loop;
end Check_Potentially_Blocking_Operation;
------------------------------------
-- Check_Previous_Null_Procedure --
------------------------------------
procedure Check_Previous_Null_Procedure
(Decl : Node_Id;
Prev : Entity_Id)
is
begin
if Ekind (Prev) = E_Procedure
and then Nkind (Parent (Prev)) = N_Procedure_Specification
and then Null_Present (Parent (Prev))
then
Error_Msg_Sloc := Sloc (Prev);
Error_Msg_N
("declaration cannot complete previous null procedure#", Decl);
end if;
end Check_Previous_Null_Procedure;
---------------------------------
-- Check_Result_And_Post_State --
---------------------------------
procedure Check_Result_And_Post_State (Subp_Id : Entity_Id) is
procedure Check_Result_And_Post_State_In_Pragma
(Prag : Node_Id;
Result_Seen : in out Boolean);
-- Determine whether pragma Prag mentions attribute 'Result and whether
-- the pragma contains an expression that evaluates differently in pre-
-- and post-state. Prag is a [refined] postcondition or a contract-cases
-- pragma. Result_Seen is set when the pragma mentions attribute 'Result
-------------------------------------------
-- Check_Result_And_Post_State_In_Pragma --
-------------------------------------------
procedure Check_Result_And_Post_State_In_Pragma
(Prag : Node_Id;
Result_Seen : in out Boolean)
is
procedure Check_Conjunct (Expr : Node_Id);
-- Check an individual conjunct in a conjunction of Boolean
-- expressions, connected by "and" or "and then" operators.
procedure Check_Conjuncts (Expr : Node_Id);
-- Apply the post-state check to every conjunct in an expression, in
-- case this is a conjunction of Boolean expressions. Otherwise apply
-- it to the expression as a whole.
procedure Check_Expression (Expr : Node_Id);
-- Perform the 'Result and post-state checks on a given expression
function Is_Function_Result (N : Node_Id) return Traverse_Result;
-- Attempt to find attribute 'Result in a subtree denoted by N
function Is_Trivial_Boolean (N : Node_Id) return Boolean;
-- Determine whether source node N denotes "True" or "False"
function Mentions_Post_State (N : Node_Id) return Boolean;
-- Determine whether a subtree denoted by N mentions any construct
-- that denotes a post-state.
procedure Check_Function_Result is
new Traverse_Proc (Is_Function_Result);
--------------------
-- Check_Conjunct --
--------------------
procedure Check_Conjunct (Expr : Node_Id) is
function Adjust_Message (Msg : String) return String;
-- Prepend a prefix to the input message Msg denoting that the
-- message applies to a conjunct in the expression, when this
-- is the case.
function Applied_On_Conjunct return Boolean;
-- Returns True if the message applies to a conjunct in the
-- expression, instead of the whole expression.
function Has_Global_Output (Subp : Entity_Id) return Boolean;
-- Returns True if Subp has an output in its Global contract
function Has_No_Output (Subp : Entity_Id) return Boolean;
-- Returns True if Subp has no declared output: no function
-- result, no output parameter, and no output in its Global
-- contract.
--------------------
-- Adjust_Message --
--------------------
function Adjust_Message (Msg : String) return String is
begin
if Applied_On_Conjunct then
return "conjunct in " & Msg;
else
return Msg;
end if;
end Adjust_Message;
-------------------------
-- Applied_On_Conjunct --
-------------------------
function Applied_On_Conjunct return Boolean is
begin
-- Expr is the conjunct of an enclosing "and" expression
return Nkind (Parent (Expr)) in N_Subexpr
-- or Expr is a conjunct of an enclosing "and then"
-- expression in a postcondition aspect that was split into
-- multiple pragmas. The first conjunct has the "and then"
-- expression as Original_Node, and other conjuncts have
-- Split_PCC set to True.
or else Nkind (Original_Node (Expr)) = N_And_Then
or else Split_PPC (Prag);
end Applied_On_Conjunct;
-----------------------
-- Has_Global_Output --
-----------------------
function Has_Global_Output (Subp : Entity_Id) return Boolean is
Global : constant Node_Id := Get_Pragma (Subp, Pragma_Global);
List : Node_Id;
Assoc : Node_Id;
begin
if No (Global) then
return False;
end if;
List := Expression (Get_Argument (Global, Subp));
-- Empty list (no global items) or single global item
-- declaration (only input items).
if Nkind (List) in N_Null
| N_Expanded_Name
| N_Identifier
| N_Selected_Component
then
return False;
-- Simple global list (only input items) or moded global list
-- declaration.
elsif Nkind (List) = N_Aggregate then
if Present (Expressions (List)) then
return False;
else
Assoc := First (Component_Associations (List));
while Present (Assoc) loop
if Chars (First (Choices (Assoc))) /= Name_Input then
return True;
end if;
Next (Assoc);
end loop;
return False;
end if;
-- To accommodate partial decoration of disabled SPARK
-- features, this routine may be called with illegal input.
-- If this is the case, do not raise Program_Error.
else
return False;
end if;
end Has_Global_Output;
-------------------
-- Has_No_Output --
-------------------
function Has_No_Output (Subp : Entity_Id) return Boolean is
Param : Node_Id;
begin
-- A function has its result as output
if Ekind (Subp) = E_Function then
return False;
end if;
-- An OUT or IN OUT parameter is an output
Param := First_Formal (Subp);
while Present (Param) loop
if Ekind (Param) in E_Out_Parameter | E_In_Out_Parameter then
return False;
end if;
Next_Formal (Param);
end loop;
-- An item of mode Output or In_Out in the Global contract is
-- an output.
if Has_Global_Output (Subp) then
return False;
end if;
return True;
end Has_No_Output;
-- Local variables
Err_Node : Node_Id;
-- Error node when reporting a warning on a (refined)
-- postcondition.
-- Start of processing for Check_Conjunct
begin
if Applied_On_Conjunct then
Err_Node := Expr;
else
Err_Node := Prag;
end if;
-- Do not report missing reference to outcome in postcondition if
-- either the postcondition is trivially True or False, or if the
-- subprogram is ghost and has no declared output.
if not Is_Trivial_Boolean (Expr)
and then not Mentions_Post_State (Expr)
and then not (Is_Ghost_Entity (Subp_Id)
and then Has_No_Output (Subp_Id))
and then not Is_Wrapper (Subp_Id)
then
if Pragma_Name (Prag) = Name_Contract_Cases then
Error_Msg_NE (Adjust_Message
("contract case does not check the outcome of calling "
& "&?.t?"), Expr, Subp_Id);
elsif Pragma_Name (Prag) = Name_Refined_Post then
Error_Msg_NE (Adjust_Message
("refined postcondition does not check the outcome of "
& "calling &?.t?"), Err_Node, Subp_Id);
else
Error_Msg_NE (Adjust_Message
("postcondition does not check the outcome of calling "
& "&?.t?"), Err_Node, Subp_Id);
end if;
end if;
end Check_Conjunct;
---------------------
-- Check_Conjuncts --
---------------------
procedure Check_Conjuncts (Expr : Node_Id) is
begin
if Nkind (Expr) in N_Op_And | N_And_Then then
Check_Conjuncts (Left_Opnd (Expr));
Check_Conjuncts (Right_Opnd (Expr));
else
Check_Conjunct (Expr);
end if;
end Check_Conjuncts;
----------------------
-- Check_Expression --
----------------------
procedure Check_Expression (Expr : Node_Id) is
begin
if not Is_Trivial_Boolean (Expr) then
Check_Function_Result (Expr);
Check_Conjuncts (Expr);
end if;
end Check_Expression;
------------------------
-- Is_Function_Result --
------------------------
function Is_Function_Result (N : Node_Id) return Traverse_Result is
begin
if Is_Attribute_Result (N) then
Result_Seen := True;
return Abandon;
-- Warn on infinite recursion if call is to current function
elsif Nkind (N) = N_Function_Call
and then Is_Entity_Name (Name (N))
and then Entity (Name (N)) = Subp_Id
and then not Is_Potentially_Unevaluated (N)
then
Error_Msg_NE
("call to & within its postcondition will lead to infinite "
& "recursion?", N, Subp_Id);
return OK;
-- Continue the traversal
else
return OK;
end if;
end Is_Function_Result;
------------------------
-- Is_Trivial_Boolean --
------------------------
function Is_Trivial_Boolean (N : Node_Id) return Boolean is
begin
return
Comes_From_Source (N)
and then Is_Entity_Name (N)
and then (Entity (N) = Standard_True
or else
Entity (N) = Standard_False);
end Is_Trivial_Boolean;
-------------------------
-- Mentions_Post_State --
-------------------------
function Mentions_Post_State (N : Node_Id) return Boolean is
Post_State_Seen : Boolean := False;
function Is_Post_State (N : Node_Id) return Traverse_Result;
-- Attempt to find a construct that denotes a post-state. If this
-- is the case, set flag Post_State_Seen.
-------------------
-- Is_Post_State --
-------------------
function Is_Post_State (N : Node_Id) return Traverse_Result is
Ent : Entity_Id;
begin
if Nkind (N) in N_Explicit_Dereference | N_Function_Call then
Post_State_Seen := True;
return Abandon;
elsif Nkind (N) in N_Expanded_Name | N_Identifier then
Ent := Entity (N);
-- Treat an undecorated reference as OK
if No (Ent)
-- A reference to an assignable entity is considered a
-- change in the post-state of a subprogram.
or else Ekind (Ent) in E_Generic_In_Out_Parameter
| E_In_Out_Parameter
| E_Out_Parameter
| E_Variable
-- The reference may be modified through a dereference
or else (Is_Access_Type (Etype (Ent))
and then Nkind (Parent (N)) =
N_Selected_Component)
then
Post_State_Seen := True;
return Abandon;
end if;
elsif Nkind (N) = N_Attribute_Reference then
if Attribute_Name (N) = Name_Old then
return Skip;
elsif Attribute_Name (N) = Name_Result then
Post_State_Seen := True;
return Abandon;
end if;
end if;
return OK;
end Is_Post_State;
procedure Find_Post_State is new Traverse_Proc (Is_Post_State);
-- Start of processing for Mentions_Post_State
begin
Find_Post_State (N);
return Post_State_Seen;
end Mentions_Post_State;
-- Local variables
Expr : constant Node_Id :=
Get_Pragma_Arg
(First (Pragma_Argument_Associations (Prag)));
Nam : constant Name_Id := Pragma_Name (Prag);
CCase : Node_Id;
-- Start of processing for Check_Result_And_Post_State_In_Pragma
begin
-- Examine all consequences
if Nam = Name_Contract_Cases then
CCase := First (Component_Associations (Expr));
while Present (CCase) loop
Check_Expression (Expression (CCase));
Next (CCase);
end loop;
-- Examine the expression of a postcondition
else pragma Assert (Nam in Name_Postcondition | Name_Refined_Post);
Check_Expression (Expr);
end if;
end Check_Result_And_Post_State_In_Pragma;
-- Local variables
Items : constant Node_Id := Contract (Subp_Id);
Subp_Decl : constant Node_Id := Unit_Declaration_Node (Subp_Id);
Case_Prag : Node_Id := Empty;
Post_Prag : Node_Id := Empty;
Prag : Node_Id;
Seen_In_Case : Boolean := False;
Seen_In_Post : Boolean := False;
Spec_Id : Entity_Id;
-- Start of processing for Check_Result_And_Post_State
begin
-- The lack of attribute 'Result or a post-state is classified as a
-- suspicious contract. Do not perform the check if the corresponding
-- swich is not set.
if not Warn_On_Suspicious_Contract then
return;
-- Nothing to do if there is no contract
elsif No (Items) then
return;
end if;
-- Retrieve the entity of the subprogram spec (if any)
if Nkind (Subp_Decl) = N_Subprogram_Body
and then Present (Corresponding_Spec (Subp_Decl))
then
Spec_Id := Corresponding_Spec (Subp_Decl);
elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
and then Present (Corresponding_Spec_Of_Stub (Subp_Decl))
then
Spec_Id := Corresponding_Spec_Of_Stub (Subp_Decl);
else
Spec_Id := Subp_Id;
end if;
-- Examine all postconditions for attribute 'Result and a post-state
Prag := Pre_Post_Conditions (Items);
while Present (Prag) loop
if Pragma_Name_Unmapped (Prag)
in Name_Postcondition | Name_Refined_Post
and then not Error_Posted (Prag)
then
Post_Prag := Prag;
Check_Result_And_Post_State_In_Pragma (Prag, Seen_In_Post);
end if;
Prag := Next_Pragma (Prag);
end loop;
-- Examine the contract cases of the subprogram for attribute 'Result
-- and a post-state.
Prag := Contract_Test_Cases (Items);
while Present (Prag) loop
if Pragma_Name (Prag) = Name_Contract_Cases
and then not Error_Posted (Prag)
then
Case_Prag := Prag;
Check_Result_And_Post_State_In_Pragma (Prag, Seen_In_Case);
end if;
Prag := Next_Pragma (Prag);
end loop;
-- Do not emit any errors if the subprogram is not a function
if Ekind (Spec_Id) not in E_Function | E_Generic_Function then
null;
-- Regardless of whether the function has postconditions or contract
-- cases, or whether they mention attribute 'Result, an [IN] OUT formal
-- parameter is always treated as a result.
elsif Has_Out_Or_In_Out_Parameter (Spec_Id) then
null;
-- The function has both a postcondition and contract cases and they do
-- not mention attribute 'Result.
elsif Present (Case_Prag)
and then not Seen_In_Case
and then Present (Post_Prag)
and then not Seen_In_Post
then
Error_Msg_N
("neither postcondition nor contract cases mention function "
& "result?.t?", Post_Prag);
-- The function has contract cases only and they do not mention
-- attribute 'Result.
elsif Present (Case_Prag) and then not Seen_In_Case then
Error_Msg_N ("contract cases do not mention result?.t?", Case_Prag);
-- The function has postconditions only and they do not mention
-- attribute 'Result.
elsif Present (Post_Prag) and then not Seen_In_Post then
Error_Msg_N
("postcondition does not mention function result?.t?", Post_Prag);
end if;
end Check_Result_And_Post_State;
-----------------------------
-- Check_State_Refinements --
-----------------------------
procedure Check_State_Refinements
(Context : Node_Id;
Is_Main_Unit : Boolean := False)
is
procedure Check_Package (Pack : Node_Id);
-- Verify that all abstract states of a [generic] package denoted by its
-- declarative node Pack have proper refinement. Recursively verify the
-- visible and private declarations of the [generic] package for other
-- nested packages.
procedure Check_Packages_In (Decls : List_Id);
-- Seek out [generic] package declarations within declarative list Decls
-- and verify the status of their abstract state refinement.
function SPARK_Mode_Is_Off (N : Node_Id) return Boolean;
-- Determine whether construct N is subject to pragma SPARK_Mode Off
-------------------
-- Check_Package --
-------------------
procedure Check_Package (Pack : Node_Id) is
Body_Id : constant Entity_Id := Corresponding_Body (Pack);
Spec : constant Node_Id := Specification (Pack);
States : constant Elist_Id :=
Abstract_States (Defining_Entity (Pack));
State_Elmt : Elmt_Id;
State_Id : Entity_Id;
begin
-- Do not verify proper state refinement when the package is subject
-- to pragma SPARK_Mode Off because this disables the requirement for
-- state refinement.
if SPARK_Mode_Is_Off (Pack) then
null;
-- State refinement can only occur in a completing package body. Do
-- not verify proper state refinement when the body is subject to
-- pragma SPARK_Mode Off because this disables the requirement for
-- state refinement.
elsif Present (Body_Id)
and then SPARK_Mode_Is_Off (Unit_Declaration_Node (Body_Id))
then
null;
-- Do not verify proper state refinement when the package is an
-- instance as this check was already performed in the generic.
elsif Present (Generic_Parent (Spec)) then
null;
-- Otherwise examine the contents of the package
else
if Present (States) then
State_Elmt := First_Elmt (States);
while Present (State_Elmt) loop
State_Id := Node (State_Elmt);
-- Emit an error when a non-null state lacks any form of
-- refinement.
if not Is_Null_State (State_Id)
and then not Has_Null_Refinement (State_Id)
and then not Has_Non_Null_Refinement (State_Id)
then
Error_Msg_N ("state & requires refinement", State_Id);
Error_Msg_N ("\package body should have Refined_State "
& "for state & with constituents", State_Id);
end if;
Next_Elmt (State_Elmt);
end loop;
end if;
Check_Packages_In (Visible_Declarations (Spec));
Check_Packages_In (Private_Declarations (Spec));
end if;
end Check_Package;
-----------------------
-- Check_Packages_In --
-----------------------
procedure Check_Packages_In (Decls : List_Id) is
Decl : Node_Id;
begin
if Present (Decls) then
Decl := First (Decls);
while Present (Decl) loop
if Nkind (Decl) in N_Generic_Package_Declaration
| N_Package_Declaration
then
Check_Package (Decl);
end if;
Next (Decl);
end loop;
end if;
end Check_Packages_In;
-----------------------
-- SPARK_Mode_Is_Off --
-----------------------
function SPARK_Mode_Is_Off (N : Node_Id) return Boolean is
Id : constant Entity_Id := Defining_Entity (N);
Prag : constant Node_Id := SPARK_Pragma (Id);
begin
-- Default the mode to "off" when the context is an instance and all
-- SPARK_Mode pragmas found within are to be ignored.
if Ignore_SPARK_Mode_Pragmas (Id) then
return True;
else
return
Present (Prag)
and then Get_SPARK_Mode_From_Annotation (Prag) = Off;
end if;
end SPARK_Mode_Is_Off;
-- Start of processing for Check_State_Refinements
begin
-- A block may declare a nested package
if Nkind (Context) = N_Block_Statement then
Check_Packages_In (Declarations (Context));
-- An entry, protected, subprogram, or task body may declare a nested
-- package.
elsif Nkind (Context) in N_Entry_Body
| N_Protected_Body
| N_Subprogram_Body
| N_Task_Body
then
-- Do not verify proper state refinement when the body is subject to
-- pragma SPARK_Mode Off because this disables the requirement for
-- state refinement.
if not SPARK_Mode_Is_Off (Context) then
Check_Packages_In (Declarations (Context));
end if;
-- A package body may declare a nested package
elsif Nkind (Context) = N_Package_Body then
Check_Package (Unit_Declaration_Node (Corresponding_Spec (Context)));
-- Do not verify proper state refinement when the body is subject to
-- pragma SPARK_Mode Off because this disables the requirement for
-- state refinement.
if not SPARK_Mode_Is_Off (Context) then
Check_Packages_In (Declarations (Context));
end if;
-- A library level [generic] package may declare a nested package
elsif Nkind (Context) in
N_Generic_Package_Declaration | N_Package_Declaration
and then Is_Main_Unit
then
Check_Package (Context);
end if;
end Check_State_Refinements;
------------------------------
-- Check_Unprotected_Access --
------------------------------
procedure Check_Unprotected_Access
(Context : Node_Id;
Expr : Node_Id)
is
Cont_Encl_Typ : Entity_Id;
Pref_Encl_Typ : Entity_Id;
function Enclosing_Protected_Type (Obj : Node_Id) return Entity_Id;
-- Check whether Obj is a private component of a protected object.
-- Return the protected type where the component resides, Empty
-- otherwise.
function Is_Public_Operation return Boolean;
-- Verify that the enclosing operation is callable from outside the
-- protected object, to minimize false positives.
------------------------------
-- Enclosing_Protected_Type --
------------------------------
function Enclosing_Protected_Type (Obj : Node_Id) return Entity_Id is
begin
if Is_Entity_Name (Obj) then
declare
Ent : Entity_Id := Entity (Obj);
begin
-- The object can be a renaming of a private component, use
-- the original record component.
if Is_Prival (Ent) then
Ent := Prival_Link (Ent);
end if;
if Is_Protected_Type (Scope (Ent)) then
return Scope (Ent);
end if;
end;
end if;
-- For indexed and selected components, recursively check the prefix
if Nkind (Obj) in N_Indexed_Component | N_Selected_Component then
return Enclosing_Protected_Type (Prefix (Obj));
-- The object does not denote a protected component
else
return Empty;
end if;
end Enclosing_Protected_Type;
-------------------------
-- Is_Public_Operation --
-------------------------
function Is_Public_Operation return Boolean is
S : Entity_Id;
E : Entity_Id;
begin
S := Current_Scope;
while Present (S) and then S /= Pref_Encl_Typ loop
if Scope (S) = Pref_Encl_Typ then
E := First_Entity (Pref_Encl_Typ);
while Present (E)
and then E /= First_Private_Entity (Pref_Encl_Typ)
loop
if E = S then
return True;
end if;
Next_Entity (E);
end loop;
end if;
S := Scope (S);
end loop;
return False;
end Is_Public_Operation;
-- Start of processing for Check_Unprotected_Access
begin
if Nkind (Expr) = N_Attribute_Reference
and then Attribute_Name (Expr) = Name_Unchecked_Access
then
Cont_Encl_Typ := Enclosing_Protected_Type (Context);
Pref_Encl_Typ := Enclosing_Protected_Type (Prefix (Expr));
-- Check whether we are trying to export a protected component to a
-- context with an equal or lower access level.
if Present (Pref_Encl_Typ)
and then No (Cont_Encl_Typ)
and then Is_Public_Operation
and then Scope_Depth (Pref_Encl_Typ)
>= Static_Accessibility_Level
(Context, Object_Decl_Level)
then
Error_Msg_N
("??possible unprotected access to protected data", Expr);
end if;
end if;
end Check_Unprotected_Access;
------------------------------
-- Check_Unused_Body_States --
------------------------------
procedure Check_Unused_Body_States (Body_Id : Entity_Id) is
procedure Process_Refinement_Clause
(Clause : Node_Id;
States : Elist_Id);
-- Inspect all constituents of refinement clause Clause and remove any
-- matches from body state list States.
procedure Report_Unused_Body_States (States : Elist_Id);
-- Emit errors for each abstract state or object found in list States
-------------------------------
-- Process_Refinement_Clause --
-------------------------------
procedure Process_Refinement_Clause
(Clause : Node_Id;
States : Elist_Id)
is
procedure Process_Constituent (Constit : Node_Id);
-- Remove constituent Constit from body state list States
-------------------------
-- Process_Constituent --
-------------------------
procedure Process_Constituent (Constit : Node_Id) is
Constit_Id : Entity_Id;
begin
-- Guard against illegal constituents. Only abstract states and
-- objects can appear on the right hand side of a refinement.
if Is_Entity_Name (Constit) then
Constit_Id := Entity_Of (Constit);
if Present (Constit_Id)
and then Ekind (Constit_Id) in
E_Abstract_State | E_Constant | E_Variable
then
Remove (States, Constit_Id);
end if;
end if;
end Process_Constituent;
-- Local variables
Constit : Node_Id;
-- Start of processing for Process_Refinement_Clause
begin
if Nkind (Clause) = N_Component_Association then
Constit := Expression (Clause);
-- Multiple constituents appear as an aggregate
if Nkind (Constit) = N_Aggregate then
Constit := First (Expressions (Constit));
while Present (Constit) loop
Process_Constituent (Constit);
Next (Constit);
end loop;
-- Various forms of a single constituent
else
Process_Constituent (Constit);
end if;
end if;
end Process_Refinement_Clause;
-------------------------------
-- Report_Unused_Body_States --
-------------------------------
procedure Report_Unused_Body_States (States : Elist_Id) is
Posted : Boolean := False;
State_Elmt : Elmt_Id;
State_Id : Entity_Id;
begin
if Present (States) then
State_Elmt := First_Elmt (States);
while Present (State_Elmt) loop
State_Id := Node (State_Elmt);
-- Constants are part of the hidden state of a package, but the
-- compiler cannot determine whether they have variable input
-- (SPARK RM 7.1.1(2)) and cannot classify them properly as a
-- hidden state. Do not emit an error when a constant does not
-- participate in a state refinement, even though it acts as a
-- hidden state.
if Ekind (State_Id) = E_Constant then
null;
-- Overlays do not contribute to package state
elsif Ekind (State_Id) = E_Variable
and then Present (Ultimate_Overlaid_Entity (State_Id))
then
null;
-- Generate an error message of the form:
-- body of package ... has unused hidden states
-- abstract state ... defined at ...
-- variable ... defined at ...
else
if not Posted then
Posted := True;
SPARK_Msg_N
("body of package & has unused hidden states", Body_Id);
end if;
Error_Msg_Sloc := Sloc (State_Id);
if Ekind (State_Id) = E_Abstract_State then
SPARK_Msg_NE
("\abstract state & defined #", Body_Id, State_Id);
else
SPARK_Msg_NE ("\variable & defined #", Body_Id, State_Id);
end if;
end if;
Next_Elmt (State_Elmt);
end loop;
end if;
end Report_Unused_Body_States;
-- Local variables
Prag : constant Node_Id := Get_Pragma (Body_Id, Pragma_Refined_State);
Spec_Id : constant Entity_Id := Spec_Entity (Body_Id);
Clause : Node_Id;
States : Elist_Id;
-- Start of processing for Check_Unused_Body_States
begin
-- Inspect the clauses of pragma Refined_State and determine whether all
-- visible states declared within the package body participate in the
-- refinement.
if Present (Prag) then
Clause := Expression (Get_Argument (Prag, Spec_Id));
States := Collect_Body_States (Body_Id);
-- Multiple non-null state refinements appear as an aggregate
if Nkind (Clause) = N_Aggregate then
Clause := First (Component_Associations (Clause));
while Present (Clause) loop
Process_Refinement_Clause (Clause, States);
Next (Clause);
end loop;
-- Various forms of a single state refinement
else
Process_Refinement_Clause (Clause, States);
end if;
-- Ensure that all abstract states and objects declared in the
-- package body state space are utilized as constituents.
Report_Unused_Body_States (States);
end if;
end Check_Unused_Body_States;
------------------------------------
-- Check_Volatility_Compatibility --
------------------------------------
procedure Check_Volatility_Compatibility
(Id1, Id2 : Entity_Id;
Description_1, Description_2 : String;
Srcpos_Bearer : Node_Id) is
begin
if SPARK_Mode /= On then
return;
end if;
declare
AR1 : constant Boolean := Async_Readers_Enabled (Id1);
AW1 : constant Boolean := Async_Writers_Enabled (Id1);
ER1 : constant Boolean := Effective_Reads_Enabled (Id1);
EW1 : constant Boolean := Effective_Writes_Enabled (Id1);
AR2 : constant Boolean := Async_Readers_Enabled (Id2);
AW2 : constant Boolean := Async_Writers_Enabled (Id2);
ER2 : constant Boolean := Effective_Reads_Enabled (Id2);
EW2 : constant Boolean := Effective_Writes_Enabled (Id2);
AR_Check_Failed : constant Boolean := AR1 and not AR2;
AW_Check_Failed : constant Boolean := AW1 and not AW2;
ER_Check_Failed : constant Boolean := ER1 and not ER2;
EW_Check_Failed : constant Boolean := EW1 and not EW2;
package Failure_Description is
procedure Note_If_Failure
(Failed : Boolean; Aspect_Name : String);
-- If Failed is False, do nothing.
-- If Failed is True, add Aspect_Name to the failure description.
function Failure_Text return String;
-- returns accumulated list of failing aspects
end Failure_Description;
package body Failure_Description is
Description_Buffer : Bounded_String;
---------------------
-- Note_If_Failure --
---------------------
procedure Note_If_Failure
(Failed : Boolean; Aspect_Name : String) is
begin
if Failed then
if Description_Buffer.Length /= 0 then
Append (Description_Buffer, ", ");
end if;
Append (Description_Buffer, Aspect_Name);
end if;
end Note_If_Failure;
------------------
-- Failure_Text --
------------------
function Failure_Text return String is
begin
return +Description_Buffer;
end Failure_Text;
end Failure_Description;
use Failure_Description;
begin
if AR_Check_Failed
or AW_Check_Failed
or ER_Check_Failed
or EW_Check_Failed
then
Note_If_Failure (AR_Check_Failed, "Async_Readers");
Note_If_Failure (AW_Check_Failed, "Async_Writers");
Note_If_Failure (ER_Check_Failed, "Effective_Reads");
Note_If_Failure (EW_Check_Failed, "Effective_Writes");
Error_Msg_N
(Description_1
& " and "
& Description_2
& " are not compatible with respect to volatility due to "
& Failure_Text,
Srcpos_Bearer);
end if;
end;
end Check_Volatility_Compatibility;
-----------------
-- Choice_List --
-----------------
function Choice_List (N : Node_Id) return List_Id is
begin
if Nkind (N) = N_Iterated_Component_Association then
return Discrete_Choices (N);
else
return Choices (N);
end if;
end Choice_List;
---------------------
-- Class_Condition --
---------------------
function Class_Condition
(Kind : Condition_Kind;
Subp : Entity_Id) return Node_Id is
begin
case Kind is
when Class_Postcondition =>
return Class_Postconditions (Subp);
when Class_Precondition =>
return Class_Preconditions (Subp);
when Ignored_Class_Postcondition =>
return Ignored_Class_Postconditions (Subp);
when Ignored_Class_Precondition =>
return Ignored_Class_Preconditions (Subp);
end case;
end Class_Condition;
-------------------------
-- Collect_Body_States --
-------------------------
function Collect_Body_States (Body_Id : Entity_Id) return Elist_Id is
function Is_Visible_Object (Obj_Id : Entity_Id) return Boolean;
-- Determine whether object Obj_Id is a suitable visible state of a
-- package body.
procedure Collect_Visible_States
(Pack_Id : Entity_Id;
States : in out Elist_Id);
-- Gather the entities of all abstract states and objects declared in
-- the visible state space of package Pack_Id.
----------------------------
-- Collect_Visible_States --
----------------------------
procedure Collect_Visible_States
(Pack_Id : Entity_Id;
States : in out Elist_Id)
is
Item_Id : Entity_Id;
begin
-- Traverse the entity chain of the package and inspect all visible
-- items.
Item_Id := First_Entity (Pack_Id);
while Present (Item_Id) and then not In_Private_Part (Item_Id) loop
-- Do not consider internally generated items as those cannot be
-- named and participate in refinement.
if not Comes_From_Source (Item_Id) then
null;
elsif Ekind (Item_Id) = E_Abstract_State then
Append_New_Elmt (Item_Id, States);
elsif Ekind (Item_Id) in E_Constant | E_Variable
and then Is_Visible_Object (Item_Id)
then
Append_New_Elmt (Item_Id, States);
-- Recursively gather the visible states of a nested package
elsif Ekind (Item_Id) = E_Package then
Collect_Visible_States (Item_Id, States);
end if;
Next_Entity (Item_Id);
end loop;
end Collect_Visible_States;
-----------------------
-- Is_Visible_Object --
-----------------------
function Is_Visible_Object (Obj_Id : Entity_Id) return Boolean is
begin
-- Objects that map generic formals to their actuals are not visible
-- from outside the generic instantiation.
if Present (Corresponding_Generic_Association
(Declaration_Node (Obj_Id)))
then
return False;
-- Constituents of a single protected/task type act as components of
-- the type and are not visible from outside the type.
elsif Ekind (Obj_Id) = E_Variable
and then Present (Encapsulating_State (Obj_Id))
and then Is_Single_Concurrent_Object (Encapsulating_State (Obj_Id))
then
return False;
else
return True;
end if;
end Is_Visible_Object;
-- Local variables
Body_Decl : constant Node_Id := Unit_Declaration_Node (Body_Id);
Decl : Node_Id;
Item_Id : Entity_Id;
States : Elist_Id := No_Elist;
-- Start of processing for Collect_Body_States
begin
-- Inspect the declarations of the body looking for source objects,
-- packages and package instantiations. Note that even though this
-- processing is very similar to Collect_Visible_States, a package
-- body does not have a First/Next_Entity list.
Decl := First (Declarations (Body_Decl));
while Present (Decl) loop
-- Capture source objects as internally generated temporaries cannot
-- be named and participate in refinement.
if Nkind (Decl) = N_Object_Declaration then
Item_Id := Defining_Entity (Decl);
if Comes_From_Source (Item_Id)
and then Is_Visible_Object (Item_Id)
then
Append_New_Elmt (Item_Id, States);
end if;
-- Capture the visible abstract states and objects of a source
-- package [instantiation].
elsif Nkind (Decl) = N_Package_Declaration then
Item_Id := Defining_Entity (Decl);
if Comes_From_Source (Item_Id) then
Collect_Visible_States (Item_Id, States);
end if;
end if;
Next (Decl);
end loop;
return States;
end Collect_Body_States;
------------------------
-- Collect_Interfaces --
------------------------
procedure Collect_Interfaces
(T : Entity_Id;
Ifaces_List : out Elist_Id;
Exclude_Parents : Boolean := False;
Use_Full_View : Boolean := True)
is
procedure Collect (Typ : Entity_Id);
-- Subsidiary subprogram used to traverse the whole list
-- of directly and indirectly implemented interfaces
-------------
-- Collect --
-------------
procedure Collect (Typ : Entity_Id) is
Ancestor : Entity_Id;
Full_T : Entity_Id;
Id : Node_Id;
Iface : Entity_Id;
begin
Full_T := Typ;
-- Handle private types and subtypes
if Use_Full_View
and then Is_Private_Type (Typ)
and then Present (Full_View (Typ))
then
Full_T := Full_View (Typ);
if Ekind (Full_T) = E_Record_Subtype then
Full_T := Etype (Typ);
if Present (Full_View (Full_T)) then
Full_T := Full_View (Full_T);
end if;
end if;
end if;
-- Include the ancestor if we are generating the whole list of
-- abstract interfaces.
if Etype (Full_T) /= Typ
-- Protect the frontend against wrong sources. For example:
-- package P is
-- type A is tagged null record;
-- type B is new A with private;
-- type C is new A with private;
-- private
-- type B is new C with null record;
-- type C is new B with null record;
-- end P;
and then Etype (Full_T) /= T
then
Ancestor := Etype (Full_T);
Collect (Ancestor);
if Is_Interface (Ancestor) and then not Exclude_Parents then
Append_Unique_Elmt (Ancestor, Ifaces_List);
end if;
end if;
-- Traverse the graph of ancestor interfaces
Id := First (Abstract_Interface_List (Full_T));
while Present (Id) loop
Iface := Etype (Id);
-- Protect against wrong uses. For example:
-- type I is interface;
-- type O is tagged null record;
-- type Wrong is new I and O with null record; -- ERROR
if Is_Interface (Iface) then
if Exclude_Parents
and then Etype (T) /= T
and then Interface_Present_In_Ancestor (Etype (T), Iface)
then
null;
else
Collect (Iface);
Append_Unique_Elmt (Iface, Ifaces_List);
end if;
end if;
Next (Id);
end loop;
end Collect;
-- Start of processing for Collect_Interfaces
begin
pragma Assert (Is_Tagged_Type (T) or else Is_Concurrent_Type (T));
Ifaces_List := New_Elmt_List;
Collect (T);
end Collect_Interfaces;
----------------------------------
-- Collect_Interface_Components --
----------------------------------
procedure Collect_Interface_Components
(Tagged_Type : Entity_Id;
Components_List : out Elist_Id)
is
procedure Collect (Typ : Entity_Id);
-- Subsidiary subprogram used to climb to the parents
-------------
-- Collect --
-------------
procedure Collect (Typ : Entity_Id) is
Tag_Comp : Entity_Id;
Parent_Typ : Entity_Id;
begin
-- Handle private types
if Present (Full_View (Etype (Typ))) then
Parent_Typ := Full_View (Etype (Typ));
else
Parent_Typ := Etype (Typ);
end if;
if Parent_Typ /= Typ
-- Protect the frontend against wrong sources. For example:
-- package P is
-- type A is tagged null record;
-- type B is new A with private;
-- type C is new A with private;
-- private
-- type B is new C with null record;
-- type C is new B with null record;
-- end P;
and then Parent_Typ /= Tagged_Type
then
Collect (Parent_Typ);
end if;
-- Collect the components containing tags of secondary dispatch
-- tables.
Tag_Comp := Next_Tag_Component (First_Tag_Component (Typ));
while Present (Tag_Comp) loop
pragma Assert (Present (Related_Type (Tag_Comp)));
Append_Elmt (Tag_Comp, Components_List);
Tag_Comp := Next_Tag_Component (Tag_Comp);
end loop;
end Collect;
-- Start of processing for Collect_Interface_Components
begin
pragma Assert (Ekind (Tagged_Type) = E_Record_Type
and then Is_Tagged_Type (Tagged_Type));
Components_List := New_Elmt_List;
Collect (Tagged_Type);
end Collect_Interface_Components;
-----------------------------
-- Collect_Interfaces_Info --
-----------------------------
procedure Collect_Interfaces_Info
(T : Entity_Id;
Ifaces_List : out Elist_Id;
Components_List : out Elist_Id;
Tags_List : out Elist_Id)
is
Comps_List : Elist_Id;
Comp_Elmt : Elmt_Id;
Comp_Iface : Entity_Id;
Iface_Elmt : Elmt_Id;
Iface : Entity_Id;
function Search_Tag (Iface : Entity_Id) return Entity_Id;
-- Search for the secondary tag associated with the interface type
-- Iface that is implemented by T.
----------------
-- Search_Tag --
----------------
function Search_Tag (Iface : Entity_Id) return Entity_Id is
ADT : Elmt_Id;
begin
if not Is_CPP_Class (T) then
ADT := Next_Elmt (Next_Elmt (First_Elmt (Access_Disp_Table (T))));
else
ADT := Next_Elmt (First_Elmt (Access_Disp_Table (T)));
end if;
while Present (ADT)
and then Is_Tag (Node (ADT))
and then Related_Type (Node (ADT)) /= Iface
loop
-- Skip secondary dispatch table referencing thunks to user
-- defined primitives covered by this interface.
pragma Assert (Has_Suffix (Node (ADT), 'P'));
Next_Elmt (ADT);
-- Skip secondary dispatch tables of Ada types
if not Is_CPP_Class (T) then
-- Skip secondary dispatch table referencing thunks to
-- predefined primitives.
pragma Assert (Has_Suffix (Node (ADT), 'Y'));
Next_Elmt (ADT);
-- Skip secondary dispatch table referencing user-defined
-- primitives covered by this interface.
pragma Assert (Has_Suffix (Node (ADT), 'D'));
Next_Elmt (ADT);
-- Skip secondary dispatch table referencing predefined
-- primitives.
pragma Assert (Has_Suffix (Node (ADT), 'Z'));
Next_Elmt (ADT);
end if;
end loop;
pragma Assert (Is_Tag (Node (ADT)));
return Node (ADT);
end Search_Tag;
-- Start of processing for Collect_Interfaces_Info
begin
Collect_Interfaces (T, Ifaces_List);
Collect_Interface_Components (T, Comps_List);
-- Search for the record component and tag associated with each
-- interface type of T.
Components_List := New_Elmt_List;
Tags_List := New_Elmt_List;
Iface_Elmt := First_Elmt (Ifaces_List);
while Present (Iface_Elmt) loop
Iface := Node (Iface_Elmt);
-- Associate the primary tag component and the primary dispatch table
-- with all the interfaces that are parents of T
if Is_Ancestor (Iface, T, Use_Full_View => True) then
Append_Elmt (First_Tag_Component (T), Components_List);
Append_Elmt (Node (First_Elmt (Access_Disp_Table (T))), Tags_List);
-- Otherwise search for the tag component and secondary dispatch
-- table of Iface
else
Comp_Elmt := First_Elmt (Comps_List);
while Present (Comp_Elmt) loop
Comp_Iface := Related_Type (Node (Comp_Elmt));
if Comp_Iface = Iface
or else Is_Ancestor (Iface, Comp_Iface, Use_Full_View => True)
then
Append_Elmt (Node (Comp_Elmt), Components_List);
Append_Elmt (Search_Tag (Comp_Iface), Tags_List);
exit;
end if;
Next_Elmt (Comp_Elmt);
end loop;
pragma Assert (Present (Comp_Elmt));
end if;
Next_Elmt (Iface_Elmt);
end loop;
end Collect_Interfaces_Info;
---------------------
-- Collect_Parents --
---------------------
procedure Collect_Parents
(T : Entity_Id;
List : out Elist_Id;
Use_Full_View : Boolean := True)
is
Current_Typ : Entity_Id := T;
Parent_Typ : Entity_Id;
begin
List := New_Elmt_List;
-- No action if the if the type has no parents
if T = Etype (T) then
return;
end if;
loop
Parent_Typ := Etype (Current_Typ);
if Is_Private_Type (Parent_Typ)
and then Present (Full_View (Parent_Typ))
and then Use_Full_View
then
Parent_Typ := Full_View (Base_Type (Parent_Typ));
end if;
Append_Elmt (Parent_Typ, List);
exit when Parent_Typ = Current_Typ;
Current_Typ := Parent_Typ;
end loop;
end Collect_Parents;
----------------------------------
-- Collect_Primitive_Operations --
----------------------------------
function Collect_Primitive_Operations (T : Entity_Id) return Elist_Id is
B_Type : constant Entity_Id := Base_Type (T);
function Match (E : Entity_Id) return Boolean;
-- True if E's base type is B_Type, or E is of an anonymous access type
-- and the base type of its designated type is B_Type.
-----------
-- Match --
-----------
function Match (E : Entity_Id) return Boolean is
Etyp : Entity_Id := Etype (E);
begin
if Ekind (Etyp) = E_Anonymous_Access_Type then
Etyp := Designated_Type (Etyp);
end if;
-- In Ada 2012 a primitive operation may have a formal of an
-- incomplete view of the parent type.
return Base_Type (Etyp) = B_Type
or else
(Ada_Version >= Ada_2012
and then Ekind (Etyp) = E_Incomplete_Type
and then Full_View (Etyp) = B_Type);
end Match;
-- Local variables
B_Decl : constant Node_Id := Original_Node (Parent (B_Type));
B_Scope : Entity_Id := Scope (B_Type);
Op_List : Elist_Id;
Eq_Prims_List : Elist_Id := No_Elist;
Formal : Entity_Id;
Is_Prim : Boolean;
Is_Type_In_Pkg : Boolean;
Formal_Derived : Boolean := False;
Id : Entity_Id;
-- Start of processing for Collect_Primitive_Operations
begin
-- For tagged types, the primitive operations are collected as they
-- are declared, and held in an explicit list which is simply returned.
if Is_Tagged_Type (B_Type) then
return Primitive_Operations (B_Type);
-- An untagged generic type that is a derived type inherits the
-- primitive operations of its parent type. Other formal types only
-- have predefined operators, which are not explicitly represented.
elsif Is_Generic_Type (B_Type) then
if Nkind (B_Decl) = N_Formal_Type_Declaration
and then Nkind (Formal_Type_Definition (B_Decl)) =
N_Formal_Derived_Type_Definition
then
Formal_Derived := True;
else
return New_Elmt_List;
end if;
end if;
Op_List := New_Elmt_List;
if B_Scope = Standard_Standard then
if B_Type = Standard_String then
Append_Elmt (Standard_Op_Concat, Op_List);
elsif B_Type = Standard_Wide_String then
Append_Elmt (Standard_Op_Concatw, Op_List);
else
null;
end if;
-- Locate the primitive subprograms of the type
else
-- The primitive operations appear after the base type, except if the
-- derivation happens within the private part of B_Scope and the type
-- is a private type, in which case both the type and some primitive
-- operations may appear before the base type, and the list of
-- candidates starts after the type.
if In_Open_Scopes (B_Scope)
and then Scope (T) = B_Scope
and then In_Private_Part (B_Scope)
then
Id := Next_Entity (T);
-- In Ada 2012, If the type has an incomplete partial view, there may
-- be primitive operations declared before the full view, so we need
-- to start scanning from the incomplete view, which is earlier on
-- the entity chain.
elsif Nkind (Parent (B_Type)) = N_Full_Type_Declaration
and then Present (Incomplete_View (Parent (B_Type)))
then
Id := Defining_Entity (Incomplete_View (Parent (B_Type)));
-- If T is a derived from a type with an incomplete view declared
-- elsewhere, that incomplete view is irrelevant, we want the
-- operations in the scope of T.
if Scope (Id) /= Scope (B_Type) then
Id := Next_Entity (B_Type);
end if;
else
Id := Next_Entity (B_Type);
end if;
-- Set flag if this is a type in a package spec
Is_Type_In_Pkg :=
Is_Package_Or_Generic_Package (B_Scope)
and then
Parent_Kind (Declaration_Node (First_Subtype (T))) /=
N_Package_Body;
while Present (Id) loop
-- Test whether the result type or any of the parameter types of
-- each subprogram following the type match that type when the
-- type is declared in a package spec, is a derived type, or the
-- subprogram is marked as primitive. (The Is_Primitive test is
-- needed to find primitives of nonderived types in declarative
-- parts that happen to override the predefined "=" operator.)
-- Note that generic formal subprograms are not considered to be
-- primitive operations and thus are never inherited.
if Is_Overloadable (Id)
and then (Is_Type_In_Pkg
or else Is_Derived_Type (B_Type)
or else Is_Primitive (Id))
and then Parent_Kind (Parent (Id))
not in N_Formal_Subprogram_Declaration
then
Is_Prim := False;
if Match (Id) then
Is_Prim := True;
else
Formal := First_Formal (Id);
while Present (Formal) loop
if Match (Formal) then
Is_Prim := True;
exit;
end if;
Next_Formal (Formal);
end loop;
end if;
-- For a formal derived type, the only primitives are the ones
-- inherited from the parent type. Operations appearing in the
-- package declaration are not primitive for it.
if Is_Prim
and then (not Formal_Derived or else Present (Alias (Id)))
then
-- In the special case of an equality operator aliased to
-- an overriding dispatching equality belonging to the same
-- type, we don't include it in the list of primitives.
-- This avoids inheriting multiple equality operators when
-- deriving from untagged private types whose full type is
-- tagged, which can otherwise cause ambiguities. Note that
-- this should only happen for this kind of untagged parent
-- type, since normally dispatching operations are inherited
-- using the type's Primitive_Operations list.
if Chars (Id) = Name_Op_Eq
and then Is_Dispatching_Operation (Id)
and then Present (Alias (Id))
and then Present (Overridden_Operation (Alias (Id)))
and then Base_Type (Etype (First_Entity (Id))) =
Base_Type (Etype (First_Entity (Alias (Id))))
then
null;
-- Include the subprogram in the list of primitives
else
Append_Elmt (Id, Op_List);
-- Save collected equality primitives for later filtering
-- (if we are processing a private type for which we can
-- collect several candidates).
if Inherits_From_Tagged_Full_View (T)
and then Chars (Id) = Name_Op_Eq
and then Etype (First_Formal (Id)) =
Etype (Next_Formal (First_Formal (Id)))
then
Append_New_Elmt (Id, Eq_Prims_List);
end if;
end if;
end if;
end if;
Next_Entity (Id);
-- For a type declared in System, some of its operations may
-- appear in the target-specific extension to System.
if No (Id)
and then Is_RTU (B_Scope, System)
and then Present_System_Aux
then
B_Scope := System_Aux_Id;
Id := First_Entity (System_Aux_Id);
end if;
end loop;
-- Filter collected equality primitives
if Inherits_From_Tagged_Full_View (T)
and then Present (Eq_Prims_List)
then
declare
First : constant Elmt_Id := First_Elmt (Eq_Prims_List);
Second : Elmt_Id;
begin
pragma Assert (No (Next_Elmt (First))
or else No (Next_Elmt (Next_Elmt (First))));
-- No action needed if we have collected a single equality
-- primitive
if Present (Next_Elmt (First)) then
Second := Next_Elmt (First);
if Is_Dispatching_Operation
(Ultimate_Alias (Node (First)))
then
Remove (Op_List, Node (First));
elsif Is_Dispatching_Operation
(Ultimate_Alias (Node (Second)))
then
Remove (Op_List, Node (Second));
else
raise Program_Error;
end if;
end if;
end;
end if;
end if;
return Op_List;
end Collect_Primitive_Operations;
-----------------------------------
-- Compile_Time_Constraint_Error --
-----------------------------------
function Compile_Time_Constraint_Error
(N : Node_Id;
Msg : String;
Ent : Entity_Id := Empty;
Loc : Source_Ptr := No_Location;
Warn : Boolean := False;
Extra_Msg : String := "") return Node_Id
is
Msgc : String (1 .. Msg'Length + 3);
-- Copy of message, with room for possible ?? or << and ! at end
Msgl : Natural;
Wmsg : Boolean;
Eloc : Source_Ptr;
-- Start of processing for Compile_Time_Constraint_Error
begin
-- If this is a warning, convert it into an error if we are in code
-- subject to SPARK_Mode being set On, unless Warn is True to force a
-- warning. The rationale is that a compile-time constraint error should
-- lead to an error instead of a warning when SPARK_Mode is On, but in
-- a few cases we prefer to issue a warning and generate both a suitable
-- run-time error in GNAT and a suitable check message in GNATprove.
-- Those cases are those that likely correspond to deactivated SPARK
-- code, so that this kind of code can be compiled and analyzed instead
-- of being rejected.
Error_Msg_Warn := Warn or SPARK_Mode /= On;
-- A static constraint error in an instance body is not a fatal error.
-- We choose to inhibit the message altogether, because there is no
-- obvious node (for now) on which to post it. On the other hand the
-- offending node must be replaced with a constraint_error in any case.
-- No messages are generated if we already posted an error on this node
if not Error_Posted (N) then
if Loc /= No_Location then
Eloc := Loc;
else
Eloc := Sloc (N);
end if;
-- Copy message to Msgc, converting any ? in the message into <
-- instead, so that we have an error in GNATprove mode.
Msgl := Msg'Length;
for J in 1 .. Msgl loop
if Msg (J) = '?' and then (J = 1 or else Msg (J - 1) /= ''') then
Msgc (J) := '<';
else
Msgc (J) := Msg (J);
end if;
end loop;
-- Message is a warning, even in Ada 95 case
if Msg (Msg'Last) = '?' or else Msg (Msg'Last) = '<' then
Wmsg := True;
-- In Ada 83, all messages are warnings. In the private part and the
-- body of an instance, constraint_checks are only warnings. We also
-- make this a warning if the Warn parameter is set.
elsif Warn
or else (Ada_Version = Ada_83 and then Comes_From_Source (N))
or else In_Instance_Not_Visible
then
Msgl := Msgl + 1;
Msgc (Msgl) := '<';
Msgl := Msgl + 1;
Msgc (Msgl) := '<';
Wmsg := True;
-- Otherwise we have a real error message (Ada 95 static case) and we
-- make this an unconditional message. Note that in the warning case
-- we do not make the message unconditional, it seems reasonable to
-- delete messages like this (about exceptions that will be raised)
-- in dead code.
else
Wmsg := False;
Msgl := Msgl + 1;
Msgc (Msgl) := '!';
end if;
-- One more test, skip the warning if the related expression is
-- statically unevaluated, since we don't want to warn about what
-- will happen when something is evaluated if it never will be
-- evaluated.
-- Suppress error reporting when checking that the expression of a
-- static expression function is a potentially static expression,
-- because we don't want additional errors being reported during the
-- preanalysis of the expression (see Analyze_Expression_Function).
if not Is_Statically_Unevaluated (N)
and then not Checking_Potentially_Static_Expression
then
if Present (Ent) then
Error_Msg_NEL (Msgc (1 .. Msgl), N, Ent, Eloc);
else
Error_Msg_NEL (Msgc (1 .. Msgl), N, Etype (N), Eloc);
end if;
-- Emit any extra message as a continuation
if Extra_Msg /= "" then
Error_Msg_N ('\' & Extra_Msg, N);
end if;
if Wmsg then
-- Check whether the context is an Init_Proc
if Inside_Init_Proc then
declare
Init_Proc_Type : constant Entity_Id :=
Etype (First_Formal (Current_Scope_No_Loops));
Conc_Typ : constant Entity_Id :=
(if Present (Init_Proc_Type)
and then Init_Proc_Type in E_Record_Type_Id
then Corresponding_Concurrent_Type (Init_Proc_Type)
else Empty);
begin
-- Don't complain if the corresponding concurrent type
-- doesn't come from source (i.e. a single task/protected
-- object).
if Present (Conc_Typ)
and then not Comes_From_Source (Conc_Typ)
then
Error_Msg ("\& [<<", Eloc, N);
else
if GNATprove_Mode then
Error_Msg
("\Constraint_Error would have been raised"
& " for objects of this type", Eloc, N);
else
Error_Msg
("\Constraint_Error will be raised"
& " for objects of this type??", Eloc, N);
end if;
end if;
end;
else
Error_Msg ("\Constraint_Error [<<", Eloc, N);
end if;
else
Error_Msg ("\static expression fails Constraint_Check", Eloc);
Set_Error_Posted (N);
end if;
end if;
end if;
return N;
end Compile_Time_Constraint_Error;
----------------------------
-- Compute_Returns_By_Ref --
----------------------------
procedure Compute_Returns_By_Ref (Func : Entity_Id) is
Typ : constant Entity_Id := Etype (Func);
Utyp : constant Entity_Id := Underlying_Type (Typ);
begin
if Is_Limited_View (Typ) then
Set_Returns_By_Ref (Func);
elsif Present (Utyp) and then CW_Or_Has_Controlled_Part (Utyp) then
Set_Returns_By_Ref (Func);
end if;
end Compute_Returns_By_Ref;
--------------------------------
-- Collect_Types_In_Hierarchy --
--------------------------------
function Collect_Types_In_Hierarchy
(Typ : Entity_Id;
Examine_Components : Boolean := False) return Elist_Id
is
Results : Elist_Id;
procedure Process_Type (Typ : Entity_Id);
-- Collect type Typ if it satisfies function Predicate. Do so for its
-- parent type, base type, progenitor types, and any component types.
------------------
-- Process_Type --
------------------
procedure Process_Type (Typ : Entity_Id) is
Comp : Entity_Id;
Iface_Elmt : Elmt_Id;
begin
if not Is_Type (Typ) or else Error_Posted (Typ) then
return;
end if;
-- Collect the current type if it satisfies the predicate
if Predicate (Typ) then
Append_Elmt (Typ, Results);
end if;
-- Process component types
if Examine_Components then
-- Examine components and discriminants
if Is_Concurrent_Type (Typ)
or else Is_Incomplete_Or_Private_Type (Typ)
or else Is_Record_Type (Typ)
or else Has_Discriminants (Typ)
then
Comp := First_Component_Or_Discriminant (Typ);
while Present (Comp) loop
Process_Type (Etype (Comp));
Next_Component_Or_Discriminant (Comp);
end loop;
-- Examine array components
elsif Ekind (Typ) = E_Array_Type then
Process_Type (Component_Type (Typ));
end if;
end if;
-- Examine parent type
if Etype (Typ) /= Typ then
Process_Type (Etype (Typ));
end if;
-- Examine base type
if Base_Type (Typ) /= Typ then
Process_Type (Base_Type (Typ));
end if;
-- Examine interfaces
if Is_Record_Type (Typ)
and then Present (Interfaces (Typ))
then
Iface_Elmt := First_Elmt (Interfaces (Typ));
while Present (Iface_Elmt) loop
Process_Type (Node (Iface_Elmt));
Next_Elmt (Iface_Elmt);
end loop;
end if;
end Process_Type;
-- Start of processing for Collect_Types_In_Hierarchy
begin
Results := New_Elmt_List;
Process_Type (Typ);
return Results;
end Collect_Types_In_Hierarchy;
-----------------------
-- Conditional_Delay --
-----------------------
procedure Conditional_Delay (New_Ent, Old_Ent : Entity_Id) is
begin
if Has_Delayed_Freeze (Old_Ent) and then not Is_Frozen (Old_Ent) then
Set_Has_Delayed_Freeze (New_Ent);
end if;
end Conditional_Delay;
-------------------------
-- Copy_Component_List --
-------------------------
function Copy_Component_List
(R_Typ : Entity_Id;
Loc : Source_Ptr) return List_Id
is
Comp : Node_Id;
Comps : constant List_Id := New_List;
begin
Comp := First_Component (Underlying_Type (R_Typ));
while Present (Comp) loop
if Comes_From_Source (Comp) then
declare
Comp_Decl : constant Node_Id := Declaration_Node (Comp);
begin
Append_To (Comps,
Make_Component_Declaration (Loc,
Defining_Identifier =>
Make_Defining_Identifier (Loc, Chars (Comp)),
Component_Definition =>
New_Copy_Tree
(Component_Definition (Comp_Decl), New_Sloc => Loc)));
end;
end if;
Next_Component (Comp);
end loop;
return Comps;
end Copy_Component_List;
-------------------------
-- Copy_Parameter_List --
-------------------------
function Copy_Parameter_List (Subp_Id : Entity_Id) return List_Id is
Loc : constant Source_Ptr := Sloc (Subp_Id);
Plist : List_Id;
Formal : Entity_Id := First_Formal (Subp_Id);
begin
if Present (Formal) then
Plist := New_List;
while Present (Formal) loop
Append_To (Plist,
Make_Parameter_Specification (Loc,
Defining_Identifier =>
Make_Defining_Identifier (Sloc (Formal), Chars (Formal)),
In_Present => In_Present (Parent (Formal)),
Out_Present => Out_Present (Parent (Formal)),
Parameter_Type =>
New_Occurrence_Of (Etype (Formal), Loc),
Expression =>
New_Copy_Tree (Expression (Parent (Formal)))));
Next_Formal (Formal);
end loop;
else
Plist := No_List;
end if;
return Plist;
end Copy_Parameter_List;
----------------------------
-- Copy_SPARK_Mode_Aspect --
----------------------------
procedure Copy_SPARK_Mode_Aspect (From : Node_Id; To : Node_Id) is
pragma Assert (not Has_Aspects (To));
Asp : Node_Id;
begin
if Has_Aspects (From) then
Asp := Find_Aspect (Defining_Entity (From), Aspect_SPARK_Mode);
if Present (Asp) then
Set_Aspect_Specifications (To, New_List (New_Copy_Tree (Asp)));
Set_Has_Aspects (To, True);
end if;
end if;
end Copy_SPARK_Mode_Aspect;
--------------------------
-- Copy_Subprogram_Spec --
--------------------------
function Copy_Subprogram_Spec
(Spec : Node_Id;
New_Sloc : Source_Ptr := No_Location) return Node_Id
is
Def_Id : Node_Id;
Formal_Spec : Node_Id;
Result : Node_Id;
begin
-- The structure of the original tree must be replicated without any
-- alterations. Use New_Copy_Tree for this purpose.
Result := New_Copy_Tree (Spec, New_Sloc => New_Sloc);
-- However, the spec of a null procedure carries the corresponding null
-- statement of the body (created by the parser), and this cannot be
-- shared with the new subprogram spec.
if Nkind (Result) = N_Procedure_Specification then
Set_Null_Statement (Result, Empty);
end if;
-- Create a new entity for the defining unit name
Def_Id := Defining_Unit_Name (Result);
Set_Defining_Unit_Name (Result,
Make_Defining_Identifier (Sloc (Def_Id), Chars (Def_Id)));
-- Create new entities for the formal parameters
if Present (Parameter_Specifications (Result)) then
Formal_Spec := First (Parameter_Specifications (Result));
while Present (Formal_Spec) loop
Def_Id := Defining_Identifier (Formal_Spec);
Set_Defining_Identifier (Formal_Spec,
Make_Defining_Identifier (Sloc (Def_Id), Chars (Def_Id)));
Next (Formal_Spec);
end loop;
end if;
return Result;
end Copy_Subprogram_Spec;
--------------------------------
-- Corresponding_Generic_Type --
--------------------------------
function Corresponding_Generic_Type (T : Entity_Id) return Entity_Id is
Inst : Entity_Id;
Gen : Entity_Id;
Typ : Entity_Id;
begin
if not Is_Generic_Actual_Type (T) then
return Any_Type;
-- If the actual is the actual of an enclosing instance, resolution
-- was correct in the generic.
elsif Nkind (Parent (T)) = N_Subtype_Declaration
and then Is_Entity_Name (Subtype_Indication (Parent (T)))
and then
Is_Generic_Actual_Type (Entity (Subtype_Indication (Parent (T))))
then
return Any_Type;
else
Inst := Scope (T);
if Is_Wrapper_Package (Inst) then
Inst := Related_Instance (Inst);
end if;
Gen :=
Generic_Parent
(Specification (Unit_Declaration_Node (Inst)));
-- Generic actual has the same name as the corresponding formal
Typ := First_Entity (Gen);
while Present (Typ) loop
if Chars (Typ) = Chars (T) then
return Typ;
end if;
Next_Entity (Typ);
end loop;
return Any_Type;
end if;
end Corresponding_Generic_Type;
--------------------------------
-- Corresponding_Primitive_Op --
--------------------------------
function Corresponding_Primitive_Op
(Ancestor_Op : Entity_Id;
Descendant_Type : Entity_Id) return Entity_Id
is
Typ : constant Entity_Id := Find_Dispatching_Type (Ancestor_Op);
Elmt : Elmt_Id;
Subp : Entity_Id;
Prim : Entity_Id;
begin
pragma Assert (Is_Dispatching_Operation (Ancestor_Op));
pragma Assert (Is_Ancestor (Typ, Descendant_Type)
or else Is_Progenitor (Typ, Descendant_Type));
Elmt := First_Elmt (Primitive_Operations (Descendant_Type));
while Present (Elmt) loop
Subp := Node (Elmt);
-- For regular primitives we only need to traverse the chain of
-- ancestors when the name matches the name of Ancestor_Op, but
-- for predefined dispatching operations we cannot rely on the
-- name of the primitive to identify a candidate since their name
-- is internally built adding a suffix to the name of the tagged
-- type.
if Chars (Subp) = Chars (Ancestor_Op)
or else Is_Predefined_Dispatching_Operation (Subp)
then
-- Handle case where Ancestor_Op is a primitive of a progenitor.
-- We rely on internal entities that map interface primitives:
-- their attribute Interface_Alias references the interface
-- primitive, and their Alias attribute references the primitive
-- of Descendant_Type implementing that interface primitive.
if Present (Interface_Alias (Subp)) then
if Interface_Alias (Subp) = Ancestor_Op then
return Alias (Subp);
end if;
-- Traverse the chain of ancestors searching for Ancestor_Op.
-- Overridden primitives have attribute Overridden_Operation;
-- inherited primitives have attribute Alias.
else
Prim := Subp;
while Present (Overridden_Operation (Prim))
or else Present (Alias (Prim))
loop
if Present (Overridden_Operation (Prim)) then
Prim := Overridden_Operation (Prim);
else
Prim := Alias (Prim);
end if;
if Prim = Ancestor_Op then
return Subp;
end if;
end loop;
end if;
end if;
Next_Elmt (Elmt);
end loop;
pragma Assert (False);
return Empty;
end Corresponding_Primitive_Op;
--------------------
-- Current_Entity --
--------------------
-- The currently visible definition for a given identifier is the
-- one most chained at the start of the visibility chain, i.e. the
-- one that is referenced by the Node_Id value of the name of the
-- given identifier.
function Current_Entity (N : Node_Id) return Entity_Id is
begin
return Get_Name_Entity_Id (Chars (N));
end Current_Entity;
-----------------------------
-- Current_Entity_In_Scope --
-----------------------------
function Current_Entity_In_Scope (N : Name_Id) return Entity_Id is
CS : constant Entity_Id := Current_Scope;
E : Entity_Id;
begin
E := Get_Name_Entity_Id (N);
if No (E) then
null;
elsif Scope_Is_Transient then
while Present (E) loop
exit when Scope (E) = CS or else Scope (E) = Scope (CS);
E := Homonym (E);
end loop;
else
while Present (E) loop
exit when Scope (E) = CS;
E := Homonym (E);
end loop;
end if;
return E;
end Current_Entity_In_Scope;
-----------------------------
-- Current_Entity_In_Scope --
-----------------------------
function Current_Entity_In_Scope (N : Node_Id) return Entity_Id is
begin
return Current_Entity_In_Scope (Chars (N));
end Current_Entity_In_Scope;
-------------------
-- Current_Scope --
-------------------
function Current_Scope return Entity_Id is
begin
if Scope_Stack.Last = -1 then
return Standard_Standard;
else
declare
C : constant Entity_Id :=
Scope_Stack.Table (Scope_Stack.Last).Entity;
begin
if Present (C) then
return C;
else
return Standard_Standard;
end if;
end;
end if;
end Current_Scope;
----------------------------
-- Current_Scope_No_Loops --
----------------------------
function Current_Scope_No_Loops return Entity_Id is
S : Entity_Id;
begin
-- Examine the scope stack starting from the current scope and skip any
-- internally generated loops.
S := Current_Scope;
while Present (S) and then S /= Standard_Standard loop
if Ekind (S) = E_Loop and then not Comes_From_Source (S) then
S := Scope (S);
else
exit;
end if;
end loop;
return S;
end Current_Scope_No_Loops;
------------------------
-- Current_Subprogram --
------------------------
function Current_Subprogram return Entity_Id is
Scop : constant Entity_Id := Current_Scope;
begin
if Is_Subprogram_Or_Generic_Subprogram (Scop) then
return Scop;
else
return Enclosing_Subprogram (Scop);
end if;
end Current_Subprogram;
-------------------------------
-- CW_Or_Has_Controlled_Part --
-------------------------------
function CW_Or_Has_Controlled_Part (T : Entity_Id) return Boolean is
begin
return Is_Class_Wide_Type (T) or else Needs_Finalization (T);
end CW_Or_Has_Controlled_Part;
-------------------------------
-- Deepest_Type_Access_Level --
-------------------------------
function Deepest_Type_Access_Level
(Typ : Entity_Id;
Allow_Alt_Model : Boolean := True) return Uint
is
begin
if Ekind (Typ) = E_Anonymous_Access_Type
and then not Is_Local_Anonymous_Access (Typ)
and then Nkind (Associated_Node_For_Itype (Typ)) = N_Object_Declaration
then
-- No_Dynamic_Accessibility_Checks override for alternative
-- accessibility model.
if Allow_Alt_Model
and then No_Dynamic_Accessibility_Checks_Enabled (Typ)
then
return Type_Access_Level (Typ, Allow_Alt_Model);
end if;
-- Typ is the type of an Ada 2012 stand-alone object of an anonymous
-- access type.
return
Scope_Depth (Enclosing_Dynamic_Scope
(Defining_Identifier
(Associated_Node_For_Itype (Typ))));
-- For generic formal type, return Int'Last (infinite).
-- See comment preceding Is_Generic_Type call in Type_Access_Level.
elsif Is_Generic_Type (Root_Type (Typ)) then
return UI_From_Int (Int'Last);
else
return Type_Access_Level (Typ, Allow_Alt_Model);
end if;
end Deepest_Type_Access_Level;
---------------------
-- Defining_Entity --
---------------------
function Defining_Entity (N : Node_Id) return Entity_Id is
Ent : constant Entity_Id := Defining_Entity_Or_Empty (N);
begin
if Present (Ent) then
return Ent;
else
raise Program_Error;
end if;
end Defining_Entity;
------------------------------
-- Defining_Entity_Or_Empty --
------------------------------
function Defining_Entity_Or_Empty (N : Node_Id) return Entity_Id is
begin
case Nkind (N) is
when N_Abstract_Subprogram_Declaration
| N_Expression_Function
| N_Formal_Subprogram_Declaration
| N_Generic_Package_Declaration
| N_Generic_Subprogram_Declaration
| N_Package_Declaration
| N_Subprogram_Body
| N_Subprogram_Body_Stub
| N_Subprogram_Declaration
| N_Subprogram_Renaming_Declaration
=>
return Defining_Entity (Specification (N));
when N_Component_Declaration
| N_Defining_Program_Unit_Name
| N_Discriminant_Specification
| N_Entry_Body
| N_Entry_Declaration
| N_Entry_Index_Specification
| N_Exception_Declaration
| N_Exception_Renaming_Declaration
| N_Formal_Object_Declaration
| N_Formal_Package_Declaration
| N_Formal_Type_Declaration
| N_Full_Type_Declaration
| N_Implicit_Label_Declaration
| N_Incomplete_Type_Declaration
| N_Iterator_Specification
| N_Loop_Parameter_Specification
| N_Number_Declaration
| N_Object_Declaration
| N_Object_Renaming_Declaration
| N_Package_Body_Stub
| N_Parameter_Specification
| N_Private_Extension_Declaration
| N_Private_Type_Declaration
| N_Protected_Body
| N_Protected_Body_Stub
| N_Protected_Type_Declaration
| N_Single_Protected_Declaration
| N_Single_Task_Declaration
| N_Subtype_Declaration
| N_Task_Body
| N_Task_Body_Stub
| N_Task_Type_Declaration
=>
return Defining_Identifier (N);
when N_Compilation_Unit =>
return Defining_Entity (Unit (N));
when N_Subunit =>
return Defining_Entity (Proper_Body (N));
when N_Function_Instantiation
| N_Function_Specification
| N_Generic_Function_Renaming_Declaration
| N_Generic_Package_Renaming_Declaration
| N_Generic_Procedure_Renaming_Declaration
| N_Package_Body
| N_Package_Instantiation
| N_Package_Renaming_Declaration
| N_Package_Specification
| N_Procedure_Instantiation
| N_Procedure_Specification
=>
declare
Nam : constant Node_Id := Defining_Unit_Name (N);
Err : Entity_Id := Empty;
begin
if Nkind (Nam) in N_Entity then
return Nam;
-- For Error, make up a name and attach to declaration so we
-- can continue semantic analysis.
elsif Nam = Error then
Err := Make_Temporary (Sloc (N), 'T');
Set_Defining_Unit_Name (N, Err);
return Err;
-- If not an entity, get defining identifier
else
return Defining_Identifier (Nam);
end if;
end;
when N_Block_Statement
| N_Loop_Statement
=>
return Entity (Identifier (N));
when others =>
return Empty;
end case;
end Defining_Entity_Or_Empty;
--------------------------
-- Denotes_Discriminant --
--------------------------
function Denotes_Discriminant
(N : Node_Id;
Check_Concurrent : Boolean := False) return Boolean
is
E : Entity_Id;
begin
if not Is_Entity_Name (N) or else No (Entity (N)) then
return False;
else
E := Entity (N);
end if;
-- If we are checking for a protected type, the discriminant may have
-- been rewritten as the corresponding discriminal of the original type
-- or of the corresponding concurrent record, depending on whether we
-- are in the spec or body of the protected type.
return Ekind (E) = E_Discriminant
or else
(Check_Concurrent
and then Ekind (E) = E_In_Parameter
and then Present (Discriminal_Link (E))
and then
(Is_Concurrent_Type (Scope (Discriminal_Link (E)))
or else
Is_Concurrent_Record_Type (Scope (Discriminal_Link (E)))));
end Denotes_Discriminant;
-------------------------
-- Denotes_Same_Object --
-------------------------
function Denotes_Same_Object (A1, A2 : Node_Id) return Boolean is
function Is_Object_Renaming (N : Node_Id) return Boolean;
-- Return true if N names an object renaming entity
function Is_Valid_Renaming (N : Node_Id) return Boolean;
-- For renamings, return False if the prefix of any dereference within
-- the renamed object_name is a variable, or any expression within the
-- renamed object_name contains references to variables or calls on
-- nonstatic functions; otherwise return True (RM 6.4.1(6.10/3))
------------------------
-- Is_Object_Renaming --
------------------------
function Is_Object_Renaming (N : Node_Id) return Boolean is
begin
return Is_Entity_Name (N)
and then Ekind (Entity (N)) in E_Variable | E_Constant
and then Present (Renamed_Object (Entity (N)));
end Is_Object_Renaming;
-----------------------
-- Is_Valid_Renaming --
-----------------------
function Is_Valid_Renaming (N : Node_Id) return Boolean is
begin
if Is_Object_Renaming (N)
and then not Is_Valid_Renaming (Renamed_Object (Entity (N)))
then
return False;
end if;
-- Check if any expression within the renamed object_name contains no
-- references to variables nor calls on nonstatic functions.
if Nkind (N) = N_Indexed_Component then
declare
Indx : Node_Id;
begin
Indx := First (Expressions (N));
while Present (Indx) loop
if not Is_OK_Static_Expression (Indx) then
return False;
end if;
Next (Indx);
end loop;
end;
elsif Nkind (N) = N_Slice then
declare
Rng : constant Node_Id := Discrete_Range (N);
begin
-- Bounds specified as a range
if Nkind (Rng) = N_Range then
if not Is_OK_Static_Range (Rng) then
return False;
end if;
-- Bounds specified as a constrained subtype indication
elsif Nkind (Rng) = N_Subtype_Indication then
if not Is_OK_Static_Range
(Range_Expression (Constraint (Rng)))
then
return False;
end if;
-- Bounds specified as a subtype name
elsif not Is_OK_Static_Expression (Rng) then
return False;
end if;
end;
end if;
if Has_Prefix (N) then
declare
P : constant Node_Id := Prefix (N);
begin
if Nkind (N) = N_Explicit_Dereference
and then Is_Variable (P)
then
return False;
elsif Is_Entity_Name (P)
and then Ekind (Entity (P)) = E_Function
then
return False;
elsif Nkind (P) = N_Function_Call then
return False;
end if;
-- Recursion to continue traversing the prefix of the
-- renaming expression
return Is_Valid_Renaming (P);
end;
end if;
return True;
end Is_Valid_Renaming;
-- Start of processing for Denotes_Same_Object
begin
-- Both names statically denote the same stand-alone object or
-- parameter (RM 6.4.1(6.6/3)).
if Is_Entity_Name (A1)
and then Is_Entity_Name (A2)
and then Entity (A1) = Entity (A2)
then
return True;
-- Both names are selected_components, their prefixes are known to
-- denote the same object, and their selector_names denote the same
-- component (RM 6.4.1(6.7/3)).
elsif Nkind (A1) = N_Selected_Component
and then Nkind (A2) = N_Selected_Component
then
return Denotes_Same_Object (Prefix (A1), Prefix (A2))
and then
Entity (Selector_Name (A1)) = Entity (Selector_Name (A2));
-- Both names are dereferences and the dereferenced names are known to
-- denote the same object (RM 6.4.1(6.8/3)).
elsif Nkind (A1) = N_Explicit_Dereference
and then Nkind (A2) = N_Explicit_Dereference
then
return Denotes_Same_Object (Prefix (A1), Prefix (A2));
-- Both names are indexed_components, their prefixes are known to denote
-- the same object, and each of the pairs of corresponding index values
-- are either both static expressions with the same static value or both
-- names that are known to denote the same object (RM 6.4.1(6.9/3)).
elsif Nkind (A1) = N_Indexed_Component
and then Nkind (A2) = N_Indexed_Component
then
if not Denotes_Same_Object (Prefix (A1), Prefix (A2)) then
return False;
else
declare
Indx1 : Node_Id;
Indx2 : Node_Id;
begin
Indx1 := First (Expressions (A1));
Indx2 := First (Expressions (A2));
while Present (Indx1) loop
-- Indexes must denote the same static value or same object
if Is_OK_Static_Expression (Indx1) then
if not Is_OK_Static_Expression (Indx2) then
return False;
elsif Expr_Value (Indx1) /= Expr_Value (Indx2) then
return False;
end if;
elsif not Denotes_Same_Object (Indx1, Indx2) then
return False;
end if;
Next (Indx1);
Next (Indx2);
end loop;
return True;
end;
end if;
-- Both names are slices, their prefixes are known to denote the same
-- object, and the two slices have statically matching index constraints
-- (RM 6.4.1(6.10/3)).
elsif Nkind (A1) = N_Slice
and then Nkind (A2) = N_Slice
then
if not Denotes_Same_Object (Prefix (A1), Prefix (A2)) then
return False;
else
declare
Lo1, Lo2, Hi1, Hi2 : Node_Id;
begin
Get_Index_Bounds (Discrete_Range (A1), Lo1, Hi1);
Get_Index_Bounds (Discrete_Range (A2), Lo2, Hi2);
-- Check whether bounds are statically identical. There is no
-- attempt to detect partial overlap of slices.
return Is_OK_Static_Expression (Lo1)
and then Is_OK_Static_Expression (Lo2)
and then Is_OK_Static_Expression (Hi1)
and then Is_OK_Static_Expression (Hi2)
and then Expr_Value (Lo1) = Expr_Value (Lo2)
and then Expr_Value (Hi1) = Expr_Value (Hi2);
end;
end if;
-- One of the two names statically denotes a renaming declaration whose
-- renamed object_name is known to denote the same object as the other;
-- the prefix of any dereference within the renamed object_name is not a
-- variable, and any expression within the renamed object_name contains
-- no references to variables nor calls on nonstatic functions (RM
-- 6.4.1(6.11/3)).
elsif Is_Object_Renaming (A1)
and then Is_Valid_Renaming (A1)
then
return Denotes_Same_Object (Renamed_Object (Entity (A1)), A2);
elsif Is_Object_Renaming (A2)
and then Is_Valid_Renaming (A2)
then
return Denotes_Same_Object (A1, Renamed_Object (Entity (A2)));
else
return False;
end if;
end Denotes_Same_Object;
-------------------------
-- Denotes_Same_Prefix --
-------------------------
function Denotes_Same_Prefix (A1, A2 : Node_Id) return Boolean is
begin
if Is_Entity_Name (A1) then
if Nkind (A2) in N_Selected_Component | N_Indexed_Component
and then not Is_Access_Type (Etype (A1))
then
return Denotes_Same_Object (A1, Prefix (A2))
or else Denotes_Same_Prefix (A1, Prefix (A2));
else
return False;
end if;
elsif Is_Entity_Name (A2) then
return Denotes_Same_Prefix (A1 => A2, A2 => A1);
elsif Nkind (A1) in N_Selected_Component | N_Indexed_Component | N_Slice
and then
Nkind (A2) in N_Selected_Component | N_Indexed_Component | N_Slice
then
declare
Root1, Root2 : Node_Id;
Depth1, Depth2 : Nat := 0;
begin
Root1 := Prefix (A1);
while not Is_Entity_Name (Root1) loop
if Nkind (Root1) not in
N_Selected_Component | N_Indexed_Component
then
return False;
else
Root1 := Prefix (Root1);
end if;
Depth1 := Depth1 + 1;
end loop;
Root2 := Prefix (A2);
while not Is_Entity_Name (Root2) loop
if Nkind (Root2) not in
N_Selected_Component | N_Indexed_Component
then
return False;
else
Root2 := Prefix (Root2);
end if;
Depth2 := Depth2 + 1;
end loop;
-- If both have the same depth and they do not denote the same
-- object, they are disjoint and no warning is needed.
if Depth1 = Depth2 then
return False;
elsif Depth1 > Depth2 then
Root1 := Prefix (A1);
for J in 1 .. Depth1 - Depth2 - 1 loop
Root1 := Prefix (Root1);
end loop;
return Denotes_Same_Object (Root1, A2);
else
Root2 := Prefix (A2);
for J in 1 .. Depth2 - Depth1 - 1 loop
Root2 := Prefix (Root2);
end loop;
return Denotes_Same_Object (A1, Root2);
end if;
end;
else
return False;
end if;
end Denotes_Same_Prefix;
----------------------
-- Denotes_Variable --
----------------------
function Denotes_Variable (N : Node_Id) return Boolean is
begin
return Is_Variable (N) and then Paren_Count (N) = 0;
end Denotes_Variable;
-----------------------------
-- Depends_On_Discriminant --
-----------------------------
function Depends_On_Discriminant (N : Node_Id) return Boolean is
L : Node_Id;
H : Node_Id;
begin
Get_Index_Bounds (N, L, H);
return Denotes_Discriminant (L) or else Denotes_Discriminant (H);
end Depends_On_Discriminant;
-------------------------------------
-- Derivation_Too_Early_To_Inherit --
-------------------------------------
function Derivation_Too_Early_To_Inherit
(Typ : Entity_Id; Streaming_Op : TSS_Name_Type) return Boolean is
Btyp : constant Entity_Id := Implementation_Base_Type (Typ);
Parent_Type : Entity_Id;
Real_Rep : Node_Id;
-- Start of processing for Derivation_Too_Early_To_Inherit
begin
if Is_Derived_Type (Btyp) then
Parent_Type := Implementation_Base_Type (Etype (Btyp));
pragma Assert (Parent_Type /= Btyp);
if Has_Stream_Attribute_Definition
(Parent_Type, Streaming_Op, Real_Rep => Real_Rep)
and then In_Same_Extended_Unit (Btyp, Parent_Type)
and then Instantiation (Get_Source_File_Index (Sloc (Btyp))) =
Instantiation (Get_Source_File_Index (Sloc (Parent_Type)))
then
return Earlier_In_Extended_Unit (Btyp, Real_Rep);
end if;
end if;
return False;
end Derivation_Too_Early_To_Inherit;
-------------------------
-- Designate_Same_Unit --
-------------------------
function Designate_Same_Unit
(Name1 : Node_Id;
Name2 : Node_Id) return Boolean
is
K1 : constant Node_Kind := Nkind (Name1);
K2 : constant Node_Kind := Nkind (Name2);
function Prefix_Node (N : Node_Id) return Node_Id;
-- Returns the parent unit name node of a defining program unit name
-- or the prefix if N is a selected component or an expanded name.
function Select_Node (N : Node_Id) return Node_Id;
-- Returns the defining identifier node of a defining program unit
-- name or the selector node if N is a selected component or an
-- expanded name.
-----------------
-- Prefix_Node --
-----------------
function Prefix_Node (N : Node_Id) return Node_Id is
begin
if Nkind (N) = N_Defining_Program_Unit_Name then
return Name (N);
else
return Prefix (N);
end if;
end Prefix_Node;
-----------------
-- Select_Node --
-----------------
function Select_Node (N : Node_Id) return Node_Id is
begin
if Nkind (N) = N_Defining_Program_Unit_Name then
return Defining_Identifier (N);
else
return Selector_Name (N);
end if;
end Select_Node;
-- Start of processing for Designate_Same_Unit
begin
if K1 in N_Identifier | N_Defining_Identifier
and then
K2 in N_Identifier | N_Defining_Identifier
then
return Chars (Name1) = Chars (Name2);
elsif K1 in N_Expanded_Name
| N_Selected_Component
| N_Defining_Program_Unit_Name
and then
K2 in N_Expanded_Name
| N_Selected_Component
| N_Defining_Program_Unit_Name
then
return
(Chars (Select_Node (Name1)) = Chars (Select_Node (Name2)))
and then
Designate_Same_Unit (Prefix_Node (Name1), Prefix_Node (Name2));
else
return False;
end if;
end Designate_Same_Unit;
---------------------------------------------
-- Diagnose_Iterated_Component_Association --
---------------------------------------------
procedure Diagnose_Iterated_Component_Association (N : Node_Id) is
Def_Id : constant Entity_Id := Defining_Identifier (N);
Aggr : Node_Id;
begin
-- Determine whether the iterated component association appears within
-- an aggregate. If this is the case, raise Program_Error because the
-- iterated component association cannot be left in the tree as is and
-- must always be processed by the related aggregate.
Aggr := N;
while Present (Aggr) loop
if Nkind (Aggr) = N_Aggregate then
raise Program_Error;
-- Prevent the search from going too far
elsif Is_Body_Or_Package_Declaration (Aggr) then
exit;
end if;
Aggr := Parent (Aggr);
end loop;
-- At this point it is known that the iterated component association is
-- not within an aggregate. This is really a quantified expression with
-- a missing "all" or "some" quantifier.
Error_Msg_N ("missing quantifier", Def_Id);
-- Rewrite the iterated component association as True to prevent any
-- cascaded errors.
Rewrite (N, New_Occurrence_Of (Standard_True, Sloc (N)));
Analyze (N);
end Diagnose_Iterated_Component_Association;
------------------------
-- Discriminated_Size --
------------------------
function Discriminated_Size (Comp : Entity_Id) return Boolean is
function Non_Static_Bound (Bound : Node_Id) return Boolean;
-- Check whether the bound of an index is non-static and does denote
-- a discriminant, in which case any object of the type (protected or
-- otherwise) will have a non-static size.
----------------------
-- Non_Static_Bound --
----------------------
function Non_Static_Bound (Bound : Node_Id) return Boolean is
begin
if Is_OK_Static_Expression (Bound) then
return False;
-- If the bound is given by a discriminant it is non-static
-- (A static constraint replaces the reference with the value).
-- In an protected object the discriminant has been replaced by
-- the corresponding discriminal within the protected operation.
elsif Is_Entity_Name (Bound)
and then
(Ekind (Entity (Bound)) = E_Discriminant
or else Present (Discriminal_Link (Entity (Bound))))
then
return False;
else
return True;
end if;
end Non_Static_Bound;
-- Local variables
Typ : constant Entity_Id := Etype (Comp);
Index : Node_Id;
-- Start of processing for Discriminated_Size
begin
if not Is_Array_Type (Typ) then
return False;
end if;
if Ekind (Typ) = E_Array_Subtype then
Index := First_Index (Typ);
while Present (Index) loop
if Non_Static_Bound (Low_Bound (Index))
or else Non_Static_Bound (High_Bound (Index))
then
return False;
end if;
Next_Index (Index);
end loop;
return True;
end if;
return False;
end Discriminated_Size;
-----------------------------------
-- Effective_Extra_Accessibility --
-----------------------------------
function Effective_Extra_Accessibility (Id : Entity_Id) return Entity_Id is
begin
if Present (Renamed_Object (Id))
and then Is_Entity_Name (Renamed_Object (Id))
then
return Effective_Extra_Accessibility (Entity (Renamed_Object (Id)));
else
return Extra_Accessibility (Id);
end if;
end Effective_Extra_Accessibility;
-----------------------------
-- Effective_Reads_Enabled --
-----------------------------
function Effective_Reads_Enabled (Id : Entity_Id) return Boolean is
begin
return Has_Enabled_Property (Id, Name_Effective_Reads);
end Effective_Reads_Enabled;
------------------------------
-- Effective_Writes_Enabled --
------------------------------
function Effective_Writes_Enabled (Id : Entity_Id) return Boolean is
begin
return Has_Enabled_Property (Id, Name_Effective_Writes);
end Effective_Writes_Enabled;
------------------------------
-- Enclosing_Comp_Unit_Node --
------------------------------
function Enclosing_Comp_Unit_Node (N : Node_Id) return Node_Id is
Current_Node : Node_Id;
begin
Current_Node := N;
while Present (Current_Node)
and then Nkind (Current_Node) /= N_Compilation_Unit
loop
Current_Node := Parent (Current_Node);
end loop;
return Current_Node;
end Enclosing_Comp_Unit_Node;
--------------------------
-- Enclosing_CPP_Parent --
--------------------------
function Enclosing_CPP_Parent (Typ : Entity_Id) return Entity_Id is
Parent_Typ : Entity_Id := Typ;
begin
while not Is_CPP_Class (Parent_Typ)
and then Etype (Parent_Typ) /= Parent_Typ
loop
Parent_Typ := Etype (Parent_Typ);
if Is_Private_Type (Parent_Typ) then
Parent_Typ := Full_View (Base_Type (Parent_Typ));
end if;
end loop;
pragma Assert (Is_CPP_Class (Parent_Typ));
return Parent_Typ;
end Enclosing_CPP_Parent;
---------------------------
-- Enclosing_Declaration --
---------------------------
function Enclosing_Declaration (N : Node_Id) return Node_Id is
Decl : Node_Id := N;
begin
while Present (Decl)
and then not (Nkind (Decl) in N_Declaration
or else
Nkind (Decl) in N_Later_Decl_Item
or else
Nkind (Decl) in N_Renaming_Declaration
or else
Nkind (Decl) = N_Number_Declaration)
loop
Decl := Parent (Decl);
end loop;
return Decl;
end Enclosing_Declaration;
----------------------------
-- Enclosing_Generic_Body --
----------------------------
function Enclosing_Generic_Body (N : Node_Id) return Node_Id is
Par : Node_Id;
Spec_Id : Entity_Id;
begin
Par := Parent (N);
while Present (Par) loop
if Nkind (Par) in N_Package_Body | N_Subprogram_Body then
Spec_Id := Corresponding_Spec (Par);
if Present (Spec_Id)
and then Nkind (Unit_Declaration_Node (Spec_Id)) in
N_Generic_Declaration
then
return Par;
end if;
end if;
Par := Parent (Par);
end loop;
return Empty;
end Enclosing_Generic_Body;
----------------------------
-- Enclosing_Generic_Unit --
----------------------------
function Enclosing_Generic_Unit (N : Node_Id) return Node_Id is
Par : Node_Id;
Spec_Decl : Node_Id;
Spec_Id : Entity_Id;
begin
Par := Parent (N);
while Present (Par) loop
if Nkind (Par) in N_Generic_Declaration then
return Par;
elsif Nkind (Par) in N_Package_Body | N_Subprogram_Body then
Spec_Id := Corresponding_Spec (Par);
if Present (Spec_Id) then
Spec_Decl := Unit_Declaration_Node (Spec_Id);
if Nkind (Spec_Decl) in N_Generic_Declaration then
return Spec_Decl;
end if;
end if;
end if;
Par := Parent (Par);
end loop;
return Empty;
end Enclosing_Generic_Unit;
-------------------
-- Enclosing_HSS --
-------------------
function Enclosing_HSS (Stmt : Node_Id) return Node_Id is
Par : Node_Id;
begin
pragma Assert (Is_Statement (Stmt));
Par := Parent (Stmt);
while Present (Par) loop
if Nkind (Par) = N_Handled_Sequence_Of_Statements then
return Par;
-- Prevent the search from going too far
elsif Is_Body_Or_Package_Declaration (Par) then
return Empty;
end if;
Par := Parent (Par);
end loop;
return Par;
end Enclosing_HSS;
-------------------------------
-- Enclosing_Lib_Unit_Entity --
-------------------------------
function Enclosing_Lib_Unit_Entity
(E : Entity_Id := Current_Scope) return Entity_Id
is
Unit_Entity : Entity_Id;
begin
-- Look for enclosing library unit entity by following scope links.
-- Equivalent to, but faster than indexing through the scope stack.
Unit_Entity := E;
while (Present (Scope (Unit_Entity))
and then Scope (Unit_Entity) /= Standard_Standard)
and not Is_Child_Unit (Unit_Entity)
loop
Unit_Entity := Scope (Unit_Entity);
end loop;
return Unit_Entity;
end Enclosing_Lib_Unit_Entity;
-----------------------------
-- Enclosing_Lib_Unit_Node --
-----------------------------
function Enclosing_Lib_Unit_Node (N : Node_Id) return Node_Id is
Encl_Unit : Node_Id;
begin
Encl_Unit := Enclosing_Comp_Unit_Node (N);
while Present (Encl_Unit)
and then Nkind (Unit (Encl_Unit)) = N_Subunit
loop
Encl_Unit := Library_Unit (Encl_Unit);
end loop;
pragma Assert (Nkind (Encl_Unit) = N_Compilation_Unit);
return Encl_Unit;
end Enclosing_Lib_Unit_Node;
-----------------------
-- Enclosing_Package --
-----------------------
function Enclosing_Package (E : Entity_Id) return Entity_Id is
Dynamic_Scope : constant Entity_Id := Enclosing_Dynamic_Scope (E);
begin
if Dynamic_Scope = Standard_Standard then
return Standard_Standard;
elsif Dynamic_Scope = Empty then
return Empty;
elsif Ekind (Dynamic_Scope) in
E_Generic_Package | E_Package | E_Package_Body
then
return Dynamic_Scope;
else
return Enclosing_Package (Dynamic_Scope);
end if;
end Enclosing_Package;
-------------------------------------
-- Enclosing_Package_Or_Subprogram --
-------------------------------------
function Enclosing_Package_Or_Subprogram (E : Entity_Id) return Entity_Id is
S : Entity_Id;
begin
S := Scope (E);
while Present (S) loop
if Is_Package_Or_Generic_Package (S)
or else Is_Subprogram_Or_Generic_Subprogram (S)
then
return S;
else
S := Scope (S);
end if;
end loop;
return Empty;
end Enclosing_Package_Or_Subprogram;
--------------------------
-- Enclosing_Subprogram --
--------------------------
function Enclosing_Subprogram (E : Entity_Id) return Entity_Id is
Dyn_Scop : constant Entity_Id := Enclosing_Dynamic_Scope (E);
begin
if Dyn_Scop = Standard_Standard then
return Empty;
elsif Dyn_Scop = Empty then
return Empty;
elsif Ekind (Dyn_Scop) = E_Subprogram_Body then
return Corresponding_Spec (Parent (Parent (Dyn_Scop)));
elsif Ekind (Dyn_Scop) in E_Block | E_Loop | E_Return_Statement then
return Enclosing_Subprogram (Dyn_Scop);
elsif Ekind (Dyn_Scop) in E_Entry | E_Entry_Family then
-- For a task entry or entry family, return the enclosing subprogram
-- of the task itself.
if Ekind (Scope (Dyn_Scop)) = E_Task_Type then
return Enclosing_Subprogram (Dyn_Scop);
-- A protected entry or entry family is rewritten as a protected
-- procedure which is the desired enclosing subprogram. This is
-- relevant when unnesting a procedure local to an entry body.
else
return Protected_Body_Subprogram (Dyn_Scop);
end if;
elsif Ekind (Dyn_Scop) = E_Task_Type then
return Get_Task_Body_Procedure (Dyn_Scop);
-- The scope may appear as a private type or as a private extension
-- whose completion is a task or protected type.
elsif Ekind (Dyn_Scop) in
E_Limited_Private_Type | E_Record_Type_With_Private
and then Present (Full_View (Dyn_Scop))
and then Ekind (Full_View (Dyn_Scop)) in E_Task_Type | E_Protected_Type
then
return Get_Task_Body_Procedure (Full_View (Dyn_Scop));
-- No body is generated if the protected operation is eliminated
elsif not Is_Eliminated (Dyn_Scop)
and then Present (Protected_Body_Subprogram (Dyn_Scop))
then
return Protected_Body_Subprogram (Dyn_Scop);
else
return Dyn_Scop;
end if;
end Enclosing_Subprogram;
--------------------------
-- End_Keyword_Location --
--------------------------
function End_Keyword_Location (N : Node_Id) return Source_Ptr is
function End_Label_Loc (Nod : Node_Id) return Source_Ptr;
-- Return the source location of Nod's end label according to the
-- following precedence rules:
--
-- 1) If the end label exists, return its location
-- 2) If Nod exists, return its location
-- 3) Return the location of N
-------------------
-- End_Label_Loc --
-------------------
function End_Label_Loc (Nod : Node_Id) return Source_Ptr is
Label : Node_Id;
begin
if Present (Nod) then
Label := End_Label (Nod);
if Present (Label) then
return Sloc (Label);
else
return Sloc (Nod);
end if;
else
return Sloc (N);
end if;
end End_Label_Loc;
-- Local variables
Owner : Node_Id := Empty;
-- Start of processing for End_Keyword_Location
begin
if Nkind (N) in N_Block_Statement
| N_Entry_Body
| N_Package_Body
| N_Subprogram_Body
| N_Task_Body
then
Owner := Handled_Statement_Sequence (N);
elsif Nkind (N) = N_Package_Declaration then
Owner := Specification (N);
elsif Nkind (N) = N_Protected_Body then
Owner := N;
elsif Nkind (N) in N_Protected_Type_Declaration
| N_Single_Protected_Declaration
then
Owner := Protected_Definition (N);
elsif Nkind (N) in N_Single_Task_Declaration | N_Task_Type_Declaration
then
Owner := Task_Definition (N);
-- This routine should not be called with other contexts
else
pragma Assert (False);
null;
end if;
return End_Label_Loc (Owner);
end End_Keyword_Location;
------------------------
-- Ensure_Freeze_Node --
------------------------
procedure Ensure_Freeze_Node (E : Entity_Id) is
FN : Node_Id;
begin
if No (Freeze_Node (E)) then
FN := Make_Freeze_Entity (Sloc (E));
Set_Has_Delayed_Freeze (E);
Set_Freeze_Node (E, FN);
Set_Access_Types_To_Process (FN, No_Elist);
Set_TSS_Elist (FN, No_Elist);
Set_Entity (FN, E);
end if;
end Ensure_Freeze_Node;
----------------
-- Enter_Name --
----------------
procedure Enter_Name (Def_Id : Entity_Id) is
C : constant Entity_Id := Current_Entity (Def_Id);
E : constant Entity_Id := Current_Entity_In_Scope (Def_Id);
S : constant Entity_Id := Current_Scope;
begin
Generate_Definition (Def_Id);
-- Add new name to current scope declarations. Check for duplicate
-- declaration, which may or may not be a genuine error.
if Present (E) then
-- Case of previous entity entered because of a missing declaration
-- or else a bad subtype indication. Best is to use the new entity,
-- and make the previous one invisible.
if Etype (E) = Any_Type then
Set_Is_Immediately_Visible (E, False);
-- Case of renaming declaration constructed for package instances.
-- if there is an explicit declaration with the same identifier,
-- the renaming is not immediately visible any longer, but remains
-- visible through selected component notation.
elsif Nkind (Parent (E)) = N_Package_Renaming_Declaration
and then not Comes_From_Source (E)
then
Set_Is_Immediately_Visible (E, False);
-- The new entity may be the package renaming, which has the same
-- same name as a generic formal which has been seen already.
elsif Nkind (Parent (Def_Id)) = N_Package_Renaming_Declaration
and then not Comes_From_Source (Def_Id)
then
Set_Is_Immediately_Visible (E, False);
-- For a fat pointer corresponding to a remote access to subprogram,
-- we use the same identifier as the RAS type, so that the proper
-- name appears in the stub. This type is only retrieved through
-- the RAS type and never by visibility, and is not added to the
-- visibility list (see below).
elsif Nkind (Parent (Def_Id)) = N_Full_Type_Declaration
and then Ekind (Def_Id) = E_Record_Type
and then Present (Corresponding_Remote_Type (Def_Id))
then
null;
-- Case of an implicit operation or derived literal. The new entity
-- hides the implicit one, which is removed from all visibility,
-- i.e. the entity list of its scope, and homonym chain of its name.
elsif (Is_Overloadable (E) and then Is_Inherited_Operation (E))
or else Is_Internal (E)
then
declare
Decl : constant Node_Id := Parent (E);
Prev : Entity_Id;
Prev_Vis : Entity_Id;
begin
-- If E is an implicit declaration, it cannot be the first
-- entity in the scope.
Prev := First_Entity (Current_Scope);
while Present (Prev) and then Next_Entity (Prev) /= E loop
Next_Entity (Prev);
end loop;
if No (Prev) then
-- If E is not on the entity chain of the current scope,
-- it is an implicit declaration in the generic formal
-- part of a generic subprogram. When analyzing the body,
-- the generic formals are visible but not on the entity
-- chain of the subprogram. The new entity will become
-- the visible one in the body.
pragma Assert
(Nkind (Parent (Decl)) = N_Generic_Subprogram_Declaration);
null;
else
Link_Entities (Prev, Next_Entity (E));
if No (Next_Entity (Prev)) then
Set_Last_Entity (Current_Scope, Prev);
end if;
if E = Current_Entity (E) then
Prev_Vis := Empty;
else
Prev_Vis := Current_Entity (E);
while Homonym (Prev_Vis) /= E loop
Prev_Vis := Homonym (Prev_Vis);
end loop;
end if;
if Present (Prev_Vis) then
-- Skip E in the visibility chain
Set_Homonym (Prev_Vis, Homonym (E));
else
Set_Name_Entity_Id (Chars (E), Homonym (E));
end if;
-- The inherited operation cannot be retrieved
-- by name, even though it may remain accesssible
-- in some cases involving subprogram bodies without
-- specs appearing in with_clauses..
Set_Is_Immediately_Visible (E, False);
end if;
end;
-- This section of code could use a comment ???
elsif Present (Etype (E))
and then Is_Concurrent_Type (Etype (E))
and then E = Def_Id
then
return;
-- If the homograph is a protected component renaming, it should not
-- be hiding the current entity. Such renamings are treated as weak
-- declarations.
elsif Is_Prival (E) then
Set_Is_Immediately_Visible (E, False);
-- In this case the current entity is a protected component renaming.
-- Perform minimal decoration by setting the scope and return since
-- the prival should not be hiding other visible entities.
elsif Is_Prival (Def_Id) then
Set_Scope (Def_Id, Current_Scope);
return;
-- Analogous to privals, the discriminal generated for an entry index
-- parameter acts as a weak declaration. Perform minimal decoration
-- to avoid bogus errors.
elsif Is_Discriminal (Def_Id)
and then Ekind (Discriminal_Link (Def_Id)) = E_Entry_Index_Parameter
then
Set_Scope (Def_Id, Current_Scope);
return;
-- In the body or private part of an instance, a type extension may
-- introduce a component with the same name as that of an actual. The
-- legality rule is not enforced, but the semantics of the full type
-- with two components of same name are not clear at this point???
elsif In_Instance_Not_Visible then
null;
-- When compiling a package body, some child units may have become
-- visible. They cannot conflict with local entities that hide them.
elsif Is_Child_Unit (E)
and then In_Open_Scopes (Scope (E))
and then not Is_Immediately_Visible (E)
then
null;
-- Conversely, with front-end inlining we may compile the parent body
-- first, and a child unit subsequently. The context is now the
-- parent spec, and body entities are not visible.
elsif Is_Child_Unit (Def_Id)
and then Is_Package_Body_Entity (E)
and then not In_Package_Body (Current_Scope)
then
null;
-- Case of genuine duplicate declaration
else
Error_Msg_Sloc := Sloc (E);
-- If the previous declaration is an incomplete type declaration
-- this may be an attempt to complete it with a private type. The
-- following avoids confusing cascaded errors.
if Nkind (Parent (E)) = N_Incomplete_Type_Declaration
and then Nkind (Parent (Def_Id)) = N_Private_Type_Declaration
then
Error_Msg_N
("incomplete type cannot be completed with a private " &
"declaration", Parent (Def_Id));
Set_Is_Immediately_Visible (E, False);
Set_Full_View (E, Def_Id);
-- An inherited component of a record conflicts with a new
-- discriminant. The discriminant is inserted first in the scope,
-- but the error should be posted on it, not on the component.
elsif Ekind (E) = E_Discriminant
and then Present (Scope (Def_Id))
and then Scope (Def_Id) /= Current_Scope
then
Error_Msg_Sloc := Sloc (Def_Id);
Error_Msg_N ("& conflicts with declaration#", E);
return;
-- If the name of the unit appears in its own context clause, a
-- dummy package with the name has already been created, and the
-- error emitted. Try to continue quietly.
elsif Error_Posted (E)
and then Sloc (E) = No_Location
and then Nkind (Parent (E)) = N_Package_Specification
and then Current_Scope = Standard_Standard
then
Set_Scope (Def_Id, Current_Scope);
return;
else
Error_Msg_N ("& conflicts with declaration#", Def_Id);
-- Avoid cascaded messages with duplicate components in
-- derived types.
if Ekind (E) in E_Component | E_Discriminant then
return;
end if;
end if;
if Nkind (Parent (Parent (Def_Id))) =
N_Generic_Subprogram_Declaration
and then Def_Id =
Defining_Entity (Specification (Parent (Parent (Def_Id))))
then
Error_Msg_N ("\generic units cannot be overloaded", Def_Id);
end if;
-- If entity is in standard, then we are in trouble, because it
-- means that we have a library package with a duplicated name.
-- That's hard to recover from, so abort.
if S = Standard_Standard then
raise Unrecoverable_Error;
-- Otherwise we continue with the declaration. Having two
-- identical declarations should not cause us too much trouble.
else
null;
end if;
end if;
end if;
-- If we fall through, declaration is OK, at least OK enough to continue
-- If Def_Id is a discriminant or a record component we are in the midst
-- of inheriting components in a derived record definition. Preserve
-- their Ekind and Etype.
if Ekind (Def_Id) in E_Discriminant | E_Component then
null;
-- If a type is already set, leave it alone (happens when a type
-- declaration is reanalyzed following a call to the optimizer).
elsif Present (Etype (Def_Id)) then
null;
-- Otherwise, the kind E_Void insures that premature uses of the entity
-- will be detected. Any_Type insures that no cascaded errors will occur
else
Mutate_Ekind (Def_Id, E_Void);
Set_Etype (Def_Id, Any_Type);
end if;
-- All entities except Itypes are immediately visible
if not Is_Itype (Def_Id) then
Set_Is_Immediately_Visible (Def_Id);
Set_Current_Entity (Def_Id);
end if;
Set_Homonym (Def_Id, C);
Append_Entity (Def_Id, S);
Set_Public_Status (Def_Id);
-- Warn if new entity hides an old one
if Warn_On_Hiding and then Present (C)
-- Don't warn for record components since they always have a well
-- defined scope which does not confuse other uses. Note that in
-- some cases, Ekind has not been set yet.
and then Ekind (C) /= E_Component
and then Ekind (C) /= E_Discriminant
and then Nkind (Parent (C)) /= N_Component_Declaration
and then Ekind (Def_Id) /= E_Component
and then Ekind (Def_Id) /= E_Discriminant
and then Nkind (Parent (Def_Id)) /= N_Component_Declaration
-- Don't warn for one character variables. It is too common to use
-- such variables as locals and will just cause too many false hits.
and then Length_Of_Name (Chars (C)) /= 1
-- Don't warn for non-source entities
and then Comes_From_Source (C)
and then Comes_From_Source (Def_Id)
-- Don't warn within a generic instantiation
and then not In_Instance
-- Don't warn unless entity in question is in extended main source
and then In_Extended_Main_Source_Unit (Def_Id)
-- Finally, the hidden entity must be either immediately visible or
-- use visible (i.e. from a used package).
and then
(Is_Immediately_Visible (C)
or else
Is_Potentially_Use_Visible (C))
then
Error_Msg_Sloc := Sloc (C);
Error_Msg_N ("declaration hides &#?h?", Def_Id);
end if;
end Enter_Name;
---------------
-- Entity_Of --
---------------
function Entity_Of (N : Node_Id) return Entity_Id is
Id : Entity_Id;
Ren : Node_Id;
begin
-- Assume that the arbitrary node does not have an entity
Id := Empty;
if Is_Entity_Name (N) then
Id := Entity (N);
-- Follow a possible chain of renamings to reach the earliest renamed
-- source object.
while Present (Id)
and then Is_Object (Id)
and then Present (Renamed_Object (Id))
loop
Ren := Renamed_Object (Id);
-- The reference renames an abstract state or a whole object
-- Obj : ...;
-- Ren : ... renames Obj;
if Is_Entity_Name (Ren) then
-- Do not follow a renaming that goes through a generic formal,
-- because these entities are hidden and must not be referenced
-- from outside the generic.
if Is_Hidden (Entity (Ren)) then
exit;
else
Id := Entity (Ren);
end if;
-- The reference renames a function result. Check the original
-- node in case expansion relocates the function call.
-- Ren : ... renames Func_Call;
elsif Nkind (Original_Node (Ren)) = N_Function_Call then
exit;
-- Otherwise the reference renames something which does not yield
-- an abstract state or a whole object. Treat the reference as not
-- having a proper entity for SPARK legality purposes.
else
Id := Empty;
exit;
end if;
end loop;
end if;
return Id;
end Entity_Of;
--------------------------
-- Examine_Array_Bounds --
--------------------------
procedure Examine_Array_Bounds
(Typ : Entity_Id;
All_Static : out Boolean;
Has_Empty : out Boolean)
is
function Is_OK_Static_Bound (Bound : Node_Id) return Boolean;
-- Determine whether bound Bound is a suitable static bound
------------------------
-- Is_OK_Static_Bound --
------------------------
function Is_OK_Static_Bound (Bound : Node_Id) return Boolean is
begin
return
not Error_Posted (Bound)
and then Is_OK_Static_Expression (Bound);
end Is_OK_Static_Bound;
-- Local variables
Hi_Bound : Node_Id;
Index : Node_Id;
Lo_Bound : Node_Id;
-- Start of processing for Examine_Array_Bounds
begin
-- An unconstrained array type does not have static bounds, and it is
-- not known whether they are empty or not.
if not Is_Constrained (Typ) then
All_Static := False;
Has_Empty := False;
-- A string literal has static bounds, and is not empty as long as it
-- contains at least one character.
elsif Ekind (Typ) = E_String_Literal_Subtype then
All_Static := True;
Has_Empty := String_Literal_Length (Typ) > 0;
end if;
-- Assume that all bounds are static and not empty
All_Static := True;
Has_Empty := False;
-- Examine each index
Index := First_Index (Typ);
while Present (Index) loop
if Is_Discrete_Type (Etype (Index)) then
Get_Index_Bounds (Index, Lo_Bound, Hi_Bound);
if Is_OK_Static_Bound (Lo_Bound)
and then
Is_OK_Static_Bound (Hi_Bound)
then
-- The static bounds produce an empty range
if Is_Null_Range (Lo_Bound, Hi_Bound) then
Has_Empty := True;
end if;
-- Otherwise at least one of the bounds is not static
else
All_Static := False;
end if;
-- Otherwise the index is non-discrete, therefore not static
else
All_Static := False;
end if;
Next_Index (Index);
end loop;
end Examine_Array_Bounds;
-------------------
-- Exceptions_OK --
-------------------
function Exceptions_OK return Boolean is
begin
return
not (Restriction_Active (No_Exception_Handlers) or else
Restriction_Active (No_Exception_Propagation) or else
Restriction_Active (No_Exceptions));
end Exceptions_OK;
--------------------------
-- Explain_Limited_Type --
--------------------------
procedure Explain_Limited_Type (T : Entity_Id; N : Node_Id) is
C : Entity_Id;
begin
-- For array, component type must be limited
if Is_Array_Type (T) then
Error_Msg_Node_2 := T;
Error_Msg_NE
("\component type& of type& is limited", N, Component_Type (T));
Explain_Limited_Type (Component_Type (T), N);
elsif Is_Record_Type (T) then
-- No need for extra messages if explicit limited record
if Is_Limited_Record (Base_Type (T)) then
return;
end if;
-- Otherwise find a limited component. Check only components that
-- come from source, or inherited components that appear in the
-- source of the ancestor.
C := First_Component (T);
while Present (C) loop
if Is_Limited_Type (Etype (C))
and then
(Comes_From_Source (C)
or else
(Present (Original_Record_Component (C))
and then
Comes_From_Source (Original_Record_Component (C))))
then
Error_Msg_Node_2 := T;
Error_Msg_NE ("\component& of type& has limited type", N, C);
Explain_Limited_Type (Etype (C), N);
return;
end if;
Next_Component (C);
end loop;
-- The type may be declared explicitly limited, even if no component
-- of it is limited, in which case we fall out of the loop.
return;
end if;
end Explain_Limited_Type;
---------------------------------------
-- Expression_Of_Expression_Function --
---------------------------------------
function Expression_Of_Expression_Function
(Subp : Entity_Id) return Node_Id
is
Expr_Func : Node_Id := Empty;
begin
pragma Assert (Is_Expression_Function_Or_Completion (Subp));
if Nkind (Original_Node (Subprogram_Spec (Subp))) =
N_Expression_Function
then
Expr_Func := Original_Node (Subprogram_Spec (Subp));
elsif Nkind (Original_Node (Subprogram_Body (Subp))) =
N_Expression_Function
then
Expr_Func := Original_Node (Subprogram_Body (Subp));
else
pragma Assert (False);
null;
end if;
return Original_Node (Expression (Expr_Func));
end Expression_Of_Expression_Function;
-------------------------------
-- Extensions_Visible_Status --
-------------------------------
function Extensions_Visible_Status
(Id : Entity_Id) return Extensions_Visible_Mode
is
Arg : Node_Id;
Decl : Node_Id;
Expr : Node_Id;
Prag : Node_Id;
Subp : Entity_Id;
begin
-- When a formal parameter is subject to Extensions_Visible, the pragma
-- is stored in the contract of related subprogram.
if Is_Formal (Id) then
Subp := Scope (Id);
elsif Is_Subprogram_Or_Generic_Subprogram (Id) then
Subp := Id;
-- No other construct carries this pragma
else
return Extensions_Visible_None;
end if;
Prag := Get_Pragma (Subp, Pragma_Extensions_Visible);
-- In certain cases analysis may request the Extensions_Visible status
-- of an expression function before the pragma has been analyzed yet.
-- Inspect the declarative items after the expression function looking
-- for the pragma (if any).
if No (Prag) and then Is_Expression_Function (Subp) then
Decl := Next (Unit_Declaration_Node (Subp));
while Present (Decl) loop
if Nkind (Decl) = N_Pragma
and then Pragma_Name (Decl) = Name_Extensions_Visible
then
Prag := Decl;
exit;
-- A source construct ends the region where Extensions_Visible may
-- appear, stop the traversal. An expanded expression function is
-- no longer a source construct, but it must still be recognized.
elsif Comes_From_Source (Decl)
or else
(Nkind (Decl) in N_Subprogram_Body | N_Subprogram_Declaration
and then Is_Expression_Function (Defining_Entity (Decl)))
then
exit;
end if;
Next (Decl);
end loop;
end if;
-- Extract the value from the Boolean expression (if any)
if Present (Prag) then
Arg := First (Pragma_Argument_Associations (Prag));
if Present (Arg) then
Expr := Get_Pragma_Arg (Arg);
-- When the associated subprogram is an expression function, the
-- argument of the pragma may not have been analyzed.
if not Analyzed (Expr) then
Preanalyze_And_Resolve (Expr, Standard_Boolean);
end if;
-- Guard against cascading errors when the argument of pragma
-- Extensions_Visible is not a valid static Boolean expression.
if Error_Posted (Expr) then
return Extensions_Visible_None;
elsif Is_True (Expr_Value (Expr)) then
return Extensions_Visible_True;
else
return Extensions_Visible_False;
end if;
-- Otherwise the aspect or pragma defaults to True
else
return Extensions_Visible_True;
end if;
-- Otherwise aspect or pragma Extensions_Visible is not inherited or
-- directly specified. In SPARK code, its value defaults to "False".
elsif SPARK_Mode = On then
return Extensions_Visible_False;
-- In non-SPARK code, aspect or pragma Extensions_Visible defaults to
-- "True".
else
return Extensions_Visible_True;
end if;
end Extensions_Visible_Status;
-----------------
-- Find_Actual --
-----------------
procedure Find_Actual
(N : Node_Id;
Formal : out Entity_Id;
Call : out Node_Id)
is
Context : constant Node_Id := Parent (N);
Actual : Node_Id;
Call_Nam : Node_Id;
begin
if Nkind (Context) in N_Indexed_Component | N_Selected_Component
and then N = Prefix (Context)
then
Find_Actual (Context, Formal, Call);
return;
elsif Nkind (Context) = N_Parameter_Association
and then N = Explicit_Actual_Parameter (Context)
then
Call := Parent (Context);
elsif Nkind (Context) in N_Entry_Call_Statement
| N_Function_Call
| N_Procedure_Call_Statement
then
Call := Context;
else
Formal := Empty;
Call := Empty;
return;
end if;
-- If we have a call to a subprogram look for the parameter. Note that
-- we exclude overloaded calls, since we don't know enough to be sure
-- of giving the right answer in this case.
if Nkind (Call) in N_Entry_Call_Statement
| N_Function_Call
| N_Procedure_Call_Statement
then
Call_Nam := Name (Call);
-- A call to an entry family may appear as an indexed component
if Nkind (Call_Nam) = N_Indexed_Component then
Call_Nam := Prefix (Call_Nam);
end if;
-- A call to a protected or task entry appears as a selected
-- component rather than an expanded name.
if Nkind (Call_Nam) = N_Selected_Component then
Call_Nam := Selector_Name (Call_Nam);
end if;
if Is_Entity_Name (Call_Nam)
and then Present (Entity (Call_Nam))
and then (Is_Generic_Subprogram (Entity (Call_Nam))
or else Is_Overloadable (Entity (Call_Nam))
or else Ekind (Entity (Call_Nam)) in E_Entry_Family
| E_Subprogram_Body
| E_Subprogram_Type)
and then not Is_Overloaded (Call_Nam)
then
-- If node is name in call it is not an actual
if N = Call_Nam then
Formal := Empty;
Call := Empty;
return;
end if;
-- Fall here if we are definitely a parameter
Actual := First_Actual (Call);
Formal := First_Formal (Entity (Call_Nam));
while Present (Formal) and then Present (Actual) loop
if Actual = N then
return;
-- An actual that is the prefix in a prefixed call may have
-- been rewritten in the call, after the deferred reference
-- was collected. Check if sloc and kinds and names match.
elsif Sloc (Actual) = Sloc (N)
and then Nkind (Actual) = N_Identifier
and then Nkind (Actual) = Nkind (N)
and then Chars (Actual) = Chars (N)
then
return;
else
Next_Actual (Actual);
Next_Formal (Formal);
end if;
end loop;
end if;
end if;
-- Fall through here if we did not find matching actual
Formal := Empty;
Call := Empty;
end Find_Actual;
---------------------------
-- Find_Body_Discriminal --
---------------------------
function Find_Body_Discriminal
(Spec_Discriminant : Entity_Id) return Entity_Id
is
Tsk : Entity_Id;
Disc : Entity_Id;
begin
-- If expansion is suppressed, then the scope can be the concurrent type
-- itself rather than a corresponding concurrent record type.
if Is_Concurrent_Type (Scope (Spec_Discriminant)) then
Tsk := Scope (Spec_Discriminant);
else
pragma Assert (Is_Concurrent_Record_Type (Scope (Spec_Discriminant)));
Tsk := Corresponding_Concurrent_Type (Scope (Spec_Discriminant));
end if;
-- Find discriminant of original concurrent type, and use its current
-- discriminal, which is the renaming within the task/protected body.
Disc := First_Discriminant (Tsk);
while Present (Disc) loop
if Chars (Disc) = Chars (Spec_Discriminant) then
return Discriminal (Disc);
end if;
Next_Discriminant (Disc);
end loop;
-- That loop should always succeed in finding a matching entry and
-- returning. Fatal error if not.
raise Program_Error;
end Find_Body_Discriminal;
-------------------------------------
-- Find_Corresponding_Discriminant --
-------------------------------------
function Find_Corresponding_Discriminant
(Id : Node_Id;
Typ : Entity_Id) return Entity_Id
is
Par_Disc : Entity_Id;
Old_Disc : Entity_Id;
New_Disc : Entity_Id;
begin
Par_Disc := Original_Record_Component (Original_Discriminant (Id));
-- The original type may currently be private, and the discriminant
-- only appear on its full view.
if Is_Private_Type (Scope (Par_Disc))
and then not Has_Discriminants (Scope (Par_Disc))
and then Present (Full_View (Scope (Par_Disc)))
then
Old_Disc := First_Discriminant (Full_View (Scope (Par_Disc)));
else
Old_Disc := First_Discriminant (Scope (Par_Disc));
end if;
if Is_Class_Wide_Type (Typ) then
New_Disc := First_Discriminant (Root_Type (Typ));
else
New_Disc := First_Discriminant (Typ);
end if;
while Present (Old_Disc) and then Present (New_Disc) loop
if Old_Disc = Par_Disc then
return New_Disc;
end if;
Next_Discriminant (Old_Disc);
Next_Discriminant (New_Disc);
end loop;
-- Should always find it
raise Program_Error;
end Find_Corresponding_Discriminant;
-------------------
-- Find_DIC_Type --
-------------------
function Find_DIC_Type (Typ : Entity_Id) return Entity_Id is
Curr_Typ : Entity_Id;
-- The current type being examined in the parent hierarchy traversal
DIC_Typ : Entity_Id;
-- The type which carries the DIC pragma. This variable denotes the
-- partial view when private types are involved.
Par_Typ : Entity_Id;
-- The parent type of the current type. This variable denotes the full
-- view when private types are involved.
begin
-- The input type defines its own DIC pragma, therefore it is the owner
if Has_Own_DIC (Typ) then
DIC_Typ := Typ;
-- Otherwise the DIC pragma is inherited from a parent type
else
pragma Assert (Has_Inherited_DIC (Typ));
-- Climb the parent chain
Curr_Typ := Typ;
loop
-- Inspect the parent type. Do not consider subtypes as they
-- inherit the DIC attributes from their base types.
DIC_Typ := Base_Type (Etype (Curr_Typ));
-- Look at the full view of a private type because the type may
-- have a hidden parent introduced in the full view.
Par_Typ := DIC_Typ;
if Is_Private_Type (Par_Typ)
and then Present (Full_View (Par_Typ))
then
Par_Typ := Full_View (Par_Typ);
end if;
-- Stop the climb once the nearest parent type which defines a DIC
-- pragma of its own is encountered or when the root of the parent
-- chain is reached.
exit when Has_Own_DIC (DIC_Typ) or else Curr_Typ = Par_Typ;
Curr_Typ := Par_Typ;
end loop;
end if;
return DIC_Typ;
end Find_DIC_Type;
----------------------------------
-- Find_Enclosing_Iterator_Loop --
----------------------------------
function Find_Enclosing_Iterator_Loop (Id : Entity_Id) return Entity_Id is
Constr : Node_Id;
S : Entity_Id;
begin
-- Traverse the scope chain looking for an iterator loop. Such loops are
-- usually transformed into blocks, hence the use of Original_Node.
S := Id;
while Present (S) and then S /= Standard_Standard loop
if Ekind (S) = E_Loop
and then Nkind (Parent (S)) = N_Implicit_Label_Declaration
then
Constr := Original_Node (Label_Construct (Parent (S)));
if Nkind (Constr) = N_Loop_Statement
and then Present (Iteration_Scheme (Constr))
and then Nkind (Iterator_Specification
(Iteration_Scheme (Constr))) =
N_Iterator_Specification
then
return S;
end if;
end if;
S := Scope (S);
end loop;
return Empty;
end Find_Enclosing_Iterator_Loop;
--------------------------
-- Find_Enclosing_Scope --
--------------------------
function Find_Enclosing_Scope (N : Node_Id) return Entity_Id is
Par : Node_Id;
begin
-- Examine the parent chain looking for a construct which defines a
-- scope.
Par := Parent (N);
while Present (Par) loop
case Nkind (Par) is
-- The construct denotes a declaration, the proper scope is its
-- entity.
when N_Entry_Declaration
| N_Expression_Function
| N_Full_Type_Declaration
| N_Generic_Package_Declaration
| N_Generic_Subprogram_Declaration
| N_Package_Declaration
| N_Private_Extension_Declaration
| N_Protected_Type_Declaration
| N_Single_Protected_Declaration
| N_Single_Task_Declaration
| N_Subprogram_Declaration
| N_Task_Type_Declaration
=>
return Defining_Entity (Par);
-- The construct denotes a body, the proper scope is the entity of
-- the corresponding spec or that of the body if the body does not
-- complete a previous declaration.
when N_Entry_Body
| N_Package_Body
| N_Protected_Body
| N_Subprogram_Body
| N_Task_Body
=>
return Unique_Defining_Entity (Par);
-- Special cases
-- Blocks carry either a source or an internally-generated scope,
-- unless the block is a byproduct of exception handling.
when N_Block_Statement =>
if not Exception_Junk (Par) then
return Entity (Identifier (Par));
end if;
-- Loops carry an internally-generated scope
when N_Loop_Statement =>
return Entity (Identifier (Par));
-- Extended return statements carry an internally-generated scope
when N_Extended_Return_Statement =>
return Return_Statement_Entity (Par);
-- A traversal from a subunit continues via the corresponding stub
when N_Subunit =>
Par := Corresponding_Stub (Par);
when others =>
null;
end case;
Par := Parent (Par);
end loop;
return Standard_Standard;
end Find_Enclosing_Scope;
------------------------------------
-- Find_Loop_In_Conditional_Block --
------------------------------------
function Find_Loop_In_Conditional_Block (N : Node_Id) return Node_Id is
Stmt : Node_Id;
begin
Stmt := N;
if Nkind (Stmt) = N_If_Statement then
Stmt := First (Then_Statements (Stmt));
end if;
pragma Assert (Nkind (Stmt) = N_Block_Statement);
-- Inspect the statements of the conditional block. In general the loop
-- should be the first statement in the statement sequence of the block,
-- but the finalization machinery may have introduced extra object
-- declarations.
Stmt := First (Statements (Handled_Statement_Sequence (Stmt)));
while Present (Stmt) loop
if Nkind (Stmt) = N_Loop_Statement then
return Stmt;
end if;
Next (Stmt);
end loop;
-- The expansion of attribute 'Loop_Entry produced a malformed block
raise Program_Error;
end Find_Loop_In_Conditional_Block;
--------------------------
-- Find_Overlaid_Entity --
--------------------------
procedure Find_Overlaid_Entity
(N : Node_Id;
Ent : out Entity_Id;
Off : out Boolean)
is
pragma Assert
(Nkind (N) = N_Attribute_Definition_Clause
and then Chars (N) = Name_Address);
Expr : Node_Id;
begin
-- We are looking for one of the two following forms:
-- for X'Address use Y'Address
-- or
-- Const : constant Address := expr;
-- ...
-- for X'Address use Const;
-- In the second case, the expr is either Y'Address, or recursively a
-- constant that eventually references Y'Address.
Ent := Empty;
Off := False;
Expr := Expression (N);
-- This loop checks the form of the expression for Y'Address, using
-- recursion to deal with intermediate constants.
loop
-- Check for Y'Address
if Nkind (Expr) = N_Attribute_Reference
and then Attribute_Name (Expr) = Name_Address
then
Expr := Prefix (Expr);
exit;
-- Check for Const where Const is a constant entity
elsif Is_Entity_Name (Expr)
and then Ekind (Entity (Expr)) = E_Constant
then
Expr := Constant_Value (Entity (Expr));
-- Anything else does not need checking
else
return;
end if;
end loop;
-- This loop checks the form of the prefix for an entity, using
-- recursion to deal with intermediate components.
loop
-- Check for Y where Y is an entity
if Is_Entity_Name (Expr) then
Ent := Entity (Expr);
-- If expansion is disabled, then we might see an entity of a
-- protected component or of a discriminant of a concurrent unit.
-- Ignore such entities, because further warnings for overlays
-- expect this routine to only collect entities of entire objects.
if Ekind (Ent) in E_Component | E_Discriminant then
pragma Assert
(not Expander_Active
and then Is_Concurrent_Type (Scope (Ent)));
Ent := Empty;
end if;
return;
-- Check for components
elsif Nkind (Expr) in N_Selected_Component | N_Indexed_Component then
Expr := Prefix (Expr);
Off := True;
-- Anything else does not need checking
else
return;
end if;
end loop;
end Find_Overlaid_Entity;
-------------------------
-- Find_Parameter_Type --
-------------------------
function Find_Parameter_Type (Param : Node_Id) return Entity_Id is
begin
if Nkind (Param) /= N_Parameter_Specification then
return Empty;
-- For an access parameter, obtain the type from the formal entity
-- itself, because access to subprogram nodes do not carry a type.
-- Shouldn't we always use the formal entity ???
elsif Nkind (Parameter_Type (Param)) = N_Access_Definition then
return Etype (Defining_Identifier (Param));
else
return Etype (Parameter_Type (Param));
end if;
end Find_Parameter_Type;
-----------------------------------
-- Find_Placement_In_State_Space --
-----------------------------------
procedure Find_Placement_In_State_Space
(Item_Id : Entity_Id;
Placement : out State_Space_Kind;
Pack_Id : out Entity_Id)
is
function Inside_Package_Body (Id : Entity_Id) return Boolean;
function Inside_Private_Part (Id : Entity_Id) return Boolean;
-- Return True if Id is declared directly within the package body
-- and the package private parts, respectively. We cannot use
-- In_Private_Part/In_Body_Part flags, as these are only set during the
-- analysis of the package itself, while Find_Placement_In_State_Space
-- can be called on an entity of another package.
------------------------
-- Inside_Package_Body --
------------------------
function Inside_Package_Body (Id : Entity_Id) return Boolean is
Spec_Id : constant Entity_Id := Scope (Id);
Body_Decl : constant Opt_N_Package_Body_Id := Package_Body (Spec_Id);
Decl : constant Node_Id := Enclosing_Declaration (Id);
begin
if Present (Body_Decl)
and then Is_List_Member (Decl)
and then List_Containing (Decl) = Declarations (Body_Decl)
then
return True;
else
return False;
end if;
end Inside_Package_Body;
-------------------------
-- Inside_Private_Part --
-------------------------
function Inside_Private_Part (Id : Entity_Id) return Boolean is
Spec_Id : constant Entity_Id := Scope (Id);
Private_Decls : constant List_Id :=
Private_Declarations (Package_Specification (Spec_Id));
Decl : constant Node_Id := Enclosing_Declaration (Id);
begin
if Is_List_Member (Decl)
and then List_Containing (Decl) = Private_Decls
then
return True;
elsif Ekind (Id) = E_Package
and then Is_Private_Library_Unit (Id)
then
return True;
else
return False;
end if;
end Inside_Private_Part;
-- Local variables
Context : Entity_Id;
-- Start of processing for Find_Placement_In_State_Space
begin
-- Assume that the item does not appear in the state space of a package
Placement := Not_In_Package;
-- Climb the scope stack and examine the enclosing context
Context := Item_Id;
Pack_Id := Scope (Context);
while Present (Pack_Id) and then Pack_Id /= Standard_Standard loop
if Is_Package_Or_Generic_Package (Pack_Id) then
-- A package body is a cut off point for the traversal as the
-- item cannot be visible to the outside from this point on.
if Inside_Package_Body (Context) then
Placement := Body_State_Space;
return;
-- The private part of a package is a cut off point for the
-- traversal as the item cannot be visible to the outside
-- from this point on.
elsif Inside_Private_Part (Context) then
Placement := Private_State_Space;
return;
-- When the item appears in the visible state space of a package,
-- continue to climb the scope stack as this may not be the final
-- state space.
else
Placement := Visible_State_Space;
-- The visible state space of a child unit acts as the proper
-- placement of an item, unless this is a private child unit.
if Is_Child_Unit (Pack_Id)
and then not Is_Private_Library_Unit (Pack_Id)
then
return;
end if;
end if;
-- The item or its enclosing package appear in a construct that has
-- no state space.
else
Placement := Not_In_Package;
Pack_Id := Empty;
return;
end if;
Context := Scope (Context);
Pack_Id := Scope (Context);
end loop;
end Find_Placement_In_State_Space;
-----------------------
-- Find_Primitive_Eq --
-----------------------
function Find_Primitive_Eq (Typ : Entity_Id) return Entity_Id is
function Find_Eq_Prim (Prims_List : Elist_Id) return Entity_Id;
-- Search for the equality primitive; return Empty if the primitive is
-- not found.
------------------
-- Find_Eq_Prim --
------------------
function Find_Eq_Prim (Prims_List : Elist_Id) return Entity_Id is
Prim : Entity_Id;
Prim_Elmt : Elmt_Id;
begin
Prim_Elmt := First_Elmt (Prims_List);
while Present (Prim_Elmt) loop
Prim := Node (Prim_Elmt);
-- Locate primitive equality with the right signature
if Chars (Prim) = Name_Op_Eq
and then Etype (First_Formal (Prim)) =
Etype (Next_Formal (First_Formal (Prim)))
and then Base_Type (Etype (Prim)) = Standard_Boolean
then
return Prim;
end if;
Next_Elmt (Prim_Elmt);
end loop;
return Empty;
end Find_Eq_Prim;
-- Local Variables
Eq_Prim : Entity_Id;
Full_Type : Entity_Id;
-- Start of processing for Find_Primitive_Eq
begin
if Is_Private_Type (Typ) then
Full_Type := Underlying_Type (Typ);
else
Full_Type := Typ;
end if;
if No (Full_Type) then
return Empty;
end if;
Full_Type := Base_Type (Full_Type);
-- When the base type itself is private, use the full view
if Is_Private_Type (Full_Type) then
Full_Type := Underlying_Type (Full_Type);
end if;
if Is_Class_Wide_Type (Full_Type) then
Full_Type := Root_Type (Full_Type);
end if;
if not Is_Tagged_Type (Full_Type) then
Eq_Prim := Find_Eq_Prim (Collect_Primitive_Operations (Typ));
-- If this is an untagged private type completed with a derivation of
-- an untagged private type whose full view is a tagged type, we use
-- the primitive operations of the private parent type (since it does
-- not have a full view, and also because its equality primitive may
-- have been overridden in its untagged full view). If no equality was
-- defined for it then take its dispatching equality primitive.
elsif Inherits_From_Tagged_Full_View (Typ) then
Eq_Prim := Find_Eq_Prim (Collect_Primitive_Operations (Typ));
if No (Eq_Prim) then
Eq_Prim := Find_Eq_Prim (Primitive_Operations (Full_Type));
end if;
else
Eq_Prim := Find_Eq_Prim (Primitive_Operations (Full_Type));
end if;
return Eq_Prim;
end Find_Primitive_Eq;
------------------------
-- Find_Specific_Type --
------------------------
function Find_Specific_Type (CW : Entity_Id) return Entity_Id is
Typ : Entity_Id := Root_Type (CW);
begin
if Ekind (Typ) = E_Incomplete_Type then
if From_Limited_With (Typ) then
Typ := Non_Limited_View (Typ);
else
Typ := Full_View (Typ);
end if;
end if;
if Is_Private_Type (Typ)
and then not Is_Tagged_Type (Typ)
and then Present (Full_View (Typ))
then
return Full_View (Typ);
else
return Typ;
end if;
end Find_Specific_Type;
-----------------------------
-- Find_Static_Alternative --
-----------------------------
function Find_Static_Alternative (N : Node_Id) return Node_Id is
Expr : constant Node_Id := Expression (N);
Val : constant Uint := Expr_Value (Expr);
Alt : Node_Id;
Choice : Node_Id;
begin
Alt := First (Alternatives (N));
Search : loop
if Nkind (Alt) /= N_Pragma then
Choice := First (Discrete_Choices (Alt));
while Present (Choice) loop
-- Others choice, always matches
if Nkind (Choice) = N_Others_Choice then
exit Search;
-- Range, check if value is in the range
elsif Nkind (Choice) = N_Range then
exit Search when
Val >= Expr_Value (Low_Bound (Choice))
and then
Val <= Expr_Value (High_Bound (Choice));
-- Choice is a subtype name. Note that we know it must
-- be a static subtype, since otherwise it would have
-- been diagnosed as illegal.
elsif Is_Entity_Name (Choice)
and then Is_Type (Entity (Choice))
then
exit Search when Is_In_Range (Expr, Etype (Choice),
Assume_Valid => False);
-- Choice is a subtype indication
elsif Nkind (Choice) = N_Subtype_Indication then
declare
C : constant Node_Id := Constraint (Choice);
R : constant Node_Id := Range_Expression (C);
begin
exit Search when
Val >= Expr_Value (Low_Bound (R))
and then
Val <= Expr_Value (High_Bound (R));
end;
-- Choice is a simple expression
else
exit Search when Val = Expr_Value (Choice);
end if;
Next (Choice);
end loop;
end if;
Next (Alt);
pragma Assert (Present (Alt));
end loop Search;
-- The above loop *must* terminate by finding a match, since we know the
-- case statement is valid, and the value of the expression is known at
-- compile time. When we fall out of the loop, Alt points to the
-- alternative that we know will be selected at run time.
return Alt;
end Find_Static_Alternative;
------------------
-- First_Actual --
------------------
function First_Actual (Node : Node_Id) return Node_Id is
N : Node_Id;
begin
if No (Parameter_Associations (Node)) then
return Empty;
end if;
N := First (Parameter_Associations (Node));
if Nkind (N) = N_Parameter_Association then
return First_Named_Actual (Node);
else
return N;
end if;
end First_Actual;
------------------
-- First_Global --
------------------
function First_Global
(Subp : Entity_Id;
Global_Mode : Name_Id;
Refined : Boolean := False) return Node_Id
is
function First_From_Global_List
(List : Node_Id;
Global_Mode : Name_Id := Name_Input) return Entity_Id;
-- Get the first item with suitable mode from List
----------------------------
-- First_From_Global_List --
----------------------------
function First_From_Global_List
(List : Node_Id;
Global_Mode : Name_Id := Name_Input) return Entity_Id
is
Assoc : Node_Id;
begin
-- Empty list (no global items)
if Nkind (List) = N_Null then
return Empty;
-- Single global item declaration (only input items)
elsif Nkind (List) in N_Expanded_Name | N_Identifier then
if Global_Mode = Name_Input then
return List;
else
return Empty;
end if;
-- Simple global list (only input items) or moded global list
-- declaration.
elsif Nkind (List) = N_Aggregate then
if Present (Expressions (List)) then
if Global_Mode = Name_Input then
return First (Expressions (List));
else
return Empty;
end if;
else
Assoc := First (Component_Associations (List));
while Present (Assoc) loop
-- When we find the desired mode in an association, call
-- recursively First_From_Global_List as if the mode was
-- Name_Input, in order to reuse the existing machinery
-- for the other cases.
if Chars (First (Choices (Assoc))) = Global_Mode then
return First_From_Global_List (Expression (Assoc));
end if;
Next (Assoc);
end loop;
return Empty;
end if;
-- To accommodate partial decoration of disabled SPARK features,
-- this routine may be called with illegal input. If this is the
-- case, do not raise Program_Error.
else
return Empty;
end if;
end First_From_Global_List;
-- Local variables
Global : Node_Id := Empty;
Body_Id : Entity_Id;
-- Start of processing for First_Global
begin
pragma Assert (Global_Mode in Name_In_Out
| Name_Input
| Name_Output
| Name_Proof_In);
-- Retrieve the suitable pragma Global or Refined_Global. In the second
-- case, it can only be located on the body entity.
if Refined then
if Is_Subprogram_Or_Generic_Subprogram (Subp) then
Body_Id := Subprogram_Body_Entity (Subp);
elsif Is_Entry (Subp) or else Is_Task_Type (Subp) then
Body_Id := Corresponding_Body (Parent (Subp));
-- ??? It should be possible to retrieve the Refined_Global on the
-- task body associated to the task object. This is not yet possible.
elsif Is_Single_Task_Object (Subp) then
Body_Id := Empty;
else
Body_Id := Empty;
end if;
if Present (Body_Id) then
Global := Get_Pragma (Body_Id, Pragma_Refined_Global);
end if;
else
Global := Get_Pragma (Subp, Pragma_Global);
end if;
-- No corresponding global if pragma is not present
if No (Global) then
return Empty;
-- Otherwise retrieve the corresponding list of items depending on the
-- Global_Mode.
else
return First_From_Global_List
(Expression (Get_Argument (Global, Subp)), Global_Mode);
end if;
end First_Global;
-------------
-- Fix_Msg --
-------------
function Fix_Msg (Id : Entity_Id; Msg : String) return String is
Is_Task : constant Boolean :=
Ekind (Id) in E_Task_Body | E_Task_Type
or else Is_Single_Task_Object (Id);
Msg_Last : constant Natural := Msg'Last;
Msg_Index : Natural;
Res : String (Msg'Range) := (others => ' ');
Res_Index : Natural;
begin
-- Copy all characters from the input message Msg to result Res with
-- suitable replacements.
Msg_Index := Msg'First;
Res_Index := Res'First;
while Msg_Index <= Msg_Last loop
-- Replace "subprogram" with a different word
if Msg_Index <= Msg_Last - 10
and then Msg (Msg_Index .. Msg_Index + 9) = "subprogram"
then
if Is_Entry (Id) then
Res (Res_Index .. Res_Index + 4) := "entry";
Res_Index := Res_Index + 5;
elsif Is_Task then
Res (Res_Index .. Res_Index + 8) := "task type";
Res_Index := Res_Index + 9;
else
Res (Res_Index .. Res_Index + 9) := "subprogram";
Res_Index := Res_Index + 10;
end if;
Msg_Index := Msg_Index + 10;
-- Replace "protected" with a different word
elsif Msg_Index <= Msg_Last - 9
and then Msg (Msg_Index .. Msg_Index + 8) = "protected"
and then Is_Task
then
Res (Res_Index .. Res_Index + 3) := "task";
Res_Index := Res_Index + 4;
Msg_Index := Msg_Index + 9;
-- Otherwise copy the character
else
Res (Res_Index) := Msg (Msg_Index);
Msg_Index := Msg_Index + 1;
Res_Index := Res_Index + 1;
end if;
end loop;
return Res (Res'First .. Res_Index - 1);
end Fix_Msg;
-------------------------
-- From_Nested_Package --
-------------------------
function From_Nested_Package (T : Entity_Id) return Boolean is
Pack : constant Entity_Id := Scope (T);
begin
return
Ekind (Pack) = E_Package
and then not Is_Frozen (Pack)
and then not Scope_Within_Or_Same (Current_Scope, Pack)
and then In_Open_Scopes (Scope (Pack));
end From_Nested_Package;
-----------------------
-- Gather_Components --
-----------------------
procedure Gather_Components
(Typ : Entity_Id;
Comp_List : Node_Id;
Governed_By : List_Id;
Into : Elist_Id;
Report_Errors : out Boolean;
Allow_Compile_Time : Boolean := False;
Include_Interface_Tag : Boolean := False)
is
Assoc : Node_Id;
Variant : Node_Id;
Discrete_Choice : Node_Id;
Comp_Item : Node_Id;
Discrim : Entity_Id;
Discrim_Name : Node_Id;
type Discriminant_Value_Status is
(Static_Expr, Static_Subtype, Bad);
subtype Good_Discrim_Value_Status is Discriminant_Value_Status
range Static_Expr .. Static_Subtype; -- range excludes Bad
Discrim_Value : Node_Id;
Discrim_Value_Subtype : Node_Id;
Discrim_Value_Status : Discriminant_Value_Status := Bad;
function OK_Scope_For_Discrim_Value_Error_Messages return Boolean is
(Scope (Original_Record_Component
(Entity (First (Choices (Assoc))))) = Typ);
-- Used to avoid generating error messages having a source position
-- which refers to somewhere (e.g., a discriminant value in a derived
-- tagged type declaration) unrelated to the offending construct. This
-- is required for correctness - clients of Gather_Components such as
-- Sem_Ch3.Create_Constrained_Components depend on this function
-- returning True while processing semantically correct examples;
-- generating an error message in this case would be wrong.
begin
Report_Errors := False;
if No (Comp_List) or else Null_Present (Comp_List) then
return;
elsif Present (Component_Items (Comp_List)) then
Comp_Item := First (Component_Items (Comp_List));
else
Comp_Item := Empty;
end if;
while Present (Comp_Item) loop
-- Skip the tag of a tagged record, as well as all items that are not
-- user components (anonymous types, rep clauses, Parent field,
-- controller field).
if Nkind (Comp_Item) = N_Component_Declaration then
declare
Comp : constant Entity_Id := Defining_Identifier (Comp_Item);
begin
if not (Is_Tag (Comp)
and then not
(Include_Interface_Tag
and then Etype (Comp) = RTE (RE_Interface_Tag)))
and then Chars (Comp) /= Name_uParent
then
Append_Elmt (Comp, Into);
end if;
end;
end if;
Next (Comp_Item);
end loop;
if No (Variant_Part (Comp_List)) then
return;
else
Discrim_Name := Name (Variant_Part (Comp_List));
Variant := First_Non_Pragma (Variants (Variant_Part (Comp_List)));
end if;
-- Look for the discriminant that governs this variant part.
-- The discriminant *must* be in the Governed_By List
Assoc := First (Governed_By);
Find_Constraint : loop
Discrim := First (Choices (Assoc));
exit Find_Constraint when
Chars (Discrim_Name) = Chars (Discrim)
or else
(Present (Corresponding_Discriminant (Entity (Discrim)))
and then Chars (Corresponding_Discriminant
(Entity (Discrim))) = Chars (Discrim_Name))
or else
Chars (Original_Record_Component (Entity (Discrim))) =
Chars (Discrim_Name);
if No (Next (Assoc)) then
if not Is_Constrained (Typ) and then Is_Derived_Type (Typ) then
-- If the type is a tagged type with inherited discriminants,
-- use the stored constraint on the parent in order to find
-- the values of discriminants that are otherwise hidden by an
-- explicit constraint. Renamed discriminants are handled in
-- the code above.
-- If several parent discriminants are renamed by a single
-- discriminant of the derived type, the call to obtain the
-- Corresponding_Discriminant field only retrieves the last
-- of them. We recover the constraint on the others from the
-- Stored_Constraint as well.
-- An inherited discriminant may have been constrained in a
-- later ancestor (not the immediate parent) so we must examine
-- the stored constraint of all of them to locate the inherited
-- value.
declare
C : Elmt_Id;
D : Entity_Id;
T : Entity_Id := Typ;
begin
while Is_Derived_Type (T) loop
if Present (Stored_Constraint (T)) then
D := First_Discriminant (Etype (T));
C := First_Elmt (Stored_Constraint (T));
while Present (D) and then Present (C) loop
if Chars (Discrim_Name) = Chars (D) then
if Is_Entity_Name (Node (C))
and then Entity (Node (C)) = Entity (Discrim)
then
-- D is renamed by Discrim, whose value is
-- given in Assoc.
null;
else
Assoc :=
Make_Component_Association (Sloc (Typ),
New_List
(New_Occurrence_Of (D, Sloc (Typ))),
Duplicate_Subexpr_No_Checks (Node (C)));
end if;
exit Find_Constraint;
end if;
Next_Discriminant (D);
Next_Elmt (C);
end loop;
end if;
-- Discriminant may be inherited from ancestor
T := Etype (T);
end loop;
end;
end if;
end if;
if No (Next (Assoc)) then
Error_Msg_NE
(" missing value for discriminant&",
First (Governed_By), Discrim_Name);
Report_Errors := True;
return;
end if;
Next (Assoc);
end loop Find_Constraint;
Discrim_Value := Expression (Assoc);
if Is_OK_Static_Expression (Discrim_Value)
or else (Allow_Compile_Time
and then Compile_Time_Known_Value (Discrim_Value))
then
Discrim_Value_Status := Static_Expr;
else
if Ada_Version >= Ada_2022 then
if Original_Node (Discrim_Value) /= Discrim_Value
and then Nkind (Discrim_Value) = N_Type_Conversion
and then Etype (Original_Node (Discrim_Value))
= Etype (Expression (Discrim_Value))
then
Discrim_Value_Subtype := Etype (Original_Node (Discrim_Value));
-- An unhelpful (for this code) type conversion may be
-- introduced in some cases; deal with it.
else
Discrim_Value_Subtype := Etype (Discrim_Value);
end if;
if Is_OK_Static_Subtype (Discrim_Value_Subtype) and then
not Is_Null_Range (Type_Low_Bound (Discrim_Value_Subtype),
Type_High_Bound (Discrim_Value_Subtype))
then
-- Is_Null_Range test doesn't account for predicates, as in
-- subtype Null_By_Predicate is Natural
-- with Static_Predicate => Null_By_Predicate < 0;
-- so test for that null case separately.
if (not Has_Static_Predicate (Discrim_Value_Subtype))
or else Present (First (Static_Discrete_Predicate
(Discrim_Value_Subtype)))
then
Discrim_Value_Status := Static_Subtype;
end if;
end if;
end if;
if Discrim_Value_Status = Bad then
-- If the variant part is governed by a discriminant of the type
-- this is an error. If the variant part and the discriminant are
-- inherited from an ancestor this is legal (AI05-220) unless the
-- components are being gathered for an aggregate, in which case
-- the caller must check Report_Errors.
--
-- In Ada 2022 the above rules are relaxed. A nonstatic governing
-- discriminant is OK as long as it has a static subtype and
-- every value of that subtype (and there must be at least one)
-- selects the same variant.
if OK_Scope_For_Discrim_Value_Error_Messages then
if Ada_Version >= Ada_2022 then
Error_Msg_FE
("value for discriminant & must be static or " &
"discriminant's nominal subtype must be static " &
"and non-null!",
Discrim_Value, Discrim);
else
Error_Msg_FE
("value for discriminant & must be static!",
Discrim_Value, Discrim);
end if;
Why_Not_Static (Discrim_Value);
end if;
Report_Errors := True;
return;
end if;
end if;
Search_For_Discriminant_Value : declare
Low : Node_Id;
High : Node_Id;
UI_High : Uint;
UI_Low : Uint;
UI_Discrim_Value : Uint;
begin
case Good_Discrim_Value_Status'(Discrim_Value_Status) is
when Static_Expr =>
UI_Discrim_Value := Expr_Value (Discrim_Value);
when Static_Subtype =>
-- Arbitrarily pick one value of the subtype and look
-- for the variant associated with that value; we will
-- check later that the same variant is associated with
-- all of the other values of the subtype.
if Has_Static_Predicate (Discrim_Value_Subtype) then
declare
Range_Or_Expr : constant Node_Id :=
First (Static_Discrete_Predicate
(Discrim_Value_Subtype));
begin
if Nkind (Range_Or_Expr) = N_Range then
UI_Discrim_Value :=
Expr_Value (Low_Bound (Range_Or_Expr));
else
UI_Discrim_Value := Expr_Value (Range_Or_Expr);
end if;
end;
else
UI_Discrim_Value
:= Expr_Value (Type_Low_Bound (Discrim_Value_Subtype));
end if;
end case;
Find_Discrete_Value : while Present (Variant) loop
-- If a choice is a subtype with a static predicate, it must
-- be rewritten as an explicit list of non-predicated choices.
Expand_Static_Predicates_In_Choices (Variant);
Discrete_Choice := First (Discrete_Choices (Variant));
while Present (Discrete_Choice) loop
exit Find_Discrete_Value when
Nkind (Discrete_Choice) = N_Others_Choice;
Get_Index_Bounds (Discrete_Choice, Low, High);
UI_Low := Expr_Value (Low);
UI_High := Expr_Value (High);
exit Find_Discrete_Value when
UI_Low <= UI_Discrim_Value
and then
UI_High >= UI_Discrim_Value;
Next (Discrete_Choice);
end loop;
Next_Non_Pragma (Variant);
end loop Find_Discrete_Value;
end Search_For_Discriminant_Value;
-- The case statement must include a variant that corresponds to the
-- value of the discriminant, unless the discriminant type has a
-- static predicate. In that case the absence of an others_choice that
-- would cover this value becomes a run-time error (3.8.1 (21.1/2)).
if No (Variant)
and then not Has_Static_Predicate (Etype (Discrim_Name))
then
Error_Msg_NE
("value of discriminant & is out of range", Discrim_Value, Discrim);
Report_Errors := True;
return;
end if;
-- If we have found the corresponding choice, recursively add its
-- components to the Into list. The nested components are part of
-- the same record type.
if Present (Variant) then
if Discrim_Value_Status = Static_Subtype then
declare
Discrim_Value_Subtype_Intervals
: constant Interval_Lists.Discrete_Interval_List
:= Interval_Lists.Type_Intervals (Discrim_Value_Subtype);
Variant_Intervals
: constant Interval_Lists.Discrete_Interval_List
:= Interval_Lists.Choice_List_Intervals
(Discrete_Choices => Discrete_Choices (Variant));
begin
if not Interval_Lists.Is_Subset
(Subset => Discrim_Value_Subtype_Intervals,
Of_Set => Variant_Intervals)
then
if OK_Scope_For_Discrim_Value_Error_Messages then
Error_Msg_NE
("no single variant is associated with all values of " &
"the subtype of discriminant value &",
Discrim_Value, Discrim);
end if;
Report_Errors := True;
return;
end if;
end;
end if;
Gather_Components
(Typ, Component_List (Variant), Governed_By, Into,
Report_Errors, Allow_Compile_Time);
end if;
end Gather_Components;
-------------------------------
-- Get_Dynamic_Accessibility --
-------------------------------
function Get_Dynamic_Accessibility (E : Entity_Id) return Entity_Id is
begin
-- When minimum accessibility is set for E then we utilize it - except
-- in a few edge cases like the expansion of select statements where
-- generated subprogram may attempt to unnecessarily use a minimum
-- accessibility object declared outside of scope.
-- To avoid these situations where expansion may get complex we verify
-- that the minimum accessibility object is within scope.
if Is_Formal (E)
and then Present (Minimum_Accessibility (E))
and then In_Open_Scopes (Scope (Minimum_Accessibility (E)))
then
return Minimum_Accessibility (E);
end if;
return Extra_Accessibility (E);
end Get_Dynamic_Accessibility;
------------------------
-- Get_Actual_Subtype --
------------------------
function Get_Actual_Subtype (N : Node_Id) return Entity_Id is
Typ : constant Entity_Id := Etype (N);
Utyp : Entity_Id := Underlying_Type (Typ);
Decl : Node_Id;
Atyp : Entity_Id;
begin
if No (Utyp) then
Utyp := Typ;
end if;
-- If what we have is an identifier that references a subprogram
-- formal, or a variable or constant object, then we get the actual
-- subtype from the referenced entity if one has been built.
if Nkind (N) = N_Identifier
and then
(Is_Formal (Entity (N))
or else Ekind (Entity (N)) = E_Constant
or else Ekind (Entity (N)) = E_Variable)
and then Present (Actual_Subtype (Entity (N)))
then
return Actual_Subtype (Entity (N));
-- Actual subtype of unchecked union is always itself. We never need
-- the "real" actual subtype. If we did, we couldn't get it anyway
-- because the discriminant is not available. The restrictions on
-- Unchecked_Union are designed to make sure that this is OK.
elsif Is_Unchecked_Union (Base_Type (Utyp)) then
return Typ;
-- Here for the unconstrained case, we must find actual subtype
-- No actual subtype is available, so we must build it on the fly.
-- Checking the type, not the underlying type, for constrainedness
-- seems to be necessary. Maybe all the tests should be on the type???
elsif (not Is_Constrained (Typ))
and then (Is_Array_Type (Utyp)
or else (Is_Record_Type (Utyp)
and then Has_Discriminants (Utyp)))
and then not Has_Unknown_Discriminants (Utyp)
and then not (Ekind (Utyp) = E_String_Literal_Subtype)
then
-- Nothing to do if in spec expression (why not???)
if In_Spec_Expression then
return Typ;
elsif Is_Private_Type (Typ) and then not Has_Discriminants (Typ) then
-- If the type has no discriminants, there is no subtype to
-- build, even if the underlying type is discriminated.
return Typ;
-- Else build the actual subtype
else
Decl := Build_Actual_Subtype (Typ, N);
-- The call may yield a declaration, or just return the entity
if Decl = Typ then
return Typ;
end if;
Atyp := Defining_Identifier (Decl);
-- If Build_Actual_Subtype generated a new declaration then use it
if Atyp /= Typ then
-- The actual subtype is an Itype, so analyze the declaration,
-- but do not attach it to the tree, to get the type defined.
Set_Parent (Decl, N);
Set_Is_Itype (Atyp);
Analyze (Decl, Suppress => All_Checks);
Set_Associated_Node_For_Itype (Atyp, N);
Set_Has_Delayed_Freeze (Atyp, False);
-- We need to freeze the actual subtype immediately. This is
-- needed, because otherwise this Itype will not get frozen
-- at all, and it is always safe to freeze on creation because
-- any associated types must be frozen at this point.
Freeze_Itype (Atyp, N);
return Atyp;
-- Otherwise we did not build a declaration, so return original
else
return Typ;
end if;
end if;
-- For all remaining cases, the actual subtype is the same as
-- the nominal type.
else
return Typ;
end if;
end Get_Actual_Subtype;
-------------------------------------
-- Get_Actual_Subtype_If_Available --
-------------------------------------
function Get_Actual_Subtype_If_Available (N : Node_Id) return Entity_Id is
Typ : constant Entity_Id := Etype (N);
begin
-- If what we have is an identifier that references a subprogram
-- formal, or a variable or constant object, then we get the actual
-- subtype from the referenced entity if one has been built.
if Nkind (N) = N_Identifier
and then
(Is_Formal (Entity (N))
or else Ekind (Entity (N)) = E_Constant
or else Ekind (Entity (N)) = E_Variable)
and then Present (Actual_Subtype (Entity (N)))
then
return Actual_Subtype (Entity (N));
-- Otherwise the Etype of N is returned unchanged
else
return Typ;
end if;
end Get_Actual_Subtype_If_Available;
------------------------
-- Get_Body_From_Stub --
------------------------
function Get_Body_From_Stub (N : Node_Id) return Node_Id is
begin
return Proper_Body (Unit (Library_Unit (N)));
end Get_Body_From_Stub;
---------------------
-- Get_Cursor_Type --
---------------------
function Get_Cursor_Type
(Aspect : Node_Id;
Typ : Entity_Id) return Entity_Id
is
Assoc : Node_Id;
Func : Entity_Id;
First_Op : Entity_Id;
Cursor : Entity_Id;
begin
-- If error already detected, return
if Error_Posted (Aspect) then
return Any_Type;
end if;
-- The cursor type for an Iterable aspect is the return type of a
-- non-overloaded First primitive operation. Locate association for
-- First.
Assoc := First (Component_Associations (Expression (Aspect)));
First_Op := Any_Id;
while Present (Assoc) loop
if Chars (First (Choices (Assoc))) = Name_First then
First_Op := Expression (Assoc);
exit;
end if;
Next (Assoc);
end loop;
if First_Op = Any_Id then
Error_Msg_N ("aspect Iterable must specify First operation", Aspect);
return Any_Type;
elsif not Analyzed (First_Op) then
Analyze (First_Op);
end if;
Cursor := Any_Type;
-- Locate function with desired name and profile in scope of type
-- In the rare case where the type is an integer type, a base type
-- is created for it, check that the base type of the first formal
-- of First matches the base type of the domain.
Func := First_Entity (Scope (Typ));
while Present (Func) loop
if Chars (Func) = Chars (First_Op)
and then Ekind (Func) = E_Function
and then Present (First_Formal (Func))
and then Base_Type (Etype (First_Formal (Func))) = Base_Type (Typ)
and then No (Next_Formal (First_Formal (Func)))
then
if Cursor /= Any_Type then
Error_Msg_N
("operation First for iterable type must be unique", Aspect);
return Any_Type;
else
Cursor := Etype (Func);
end if;
end if;
Next_Entity (Func);
end loop;
-- If not found, no way to resolve remaining primitives
if Cursor = Any_Type then
Error_Msg_N
("primitive operation for Iterable type must appear in the same "
& "list of declarations as the type", Aspect);
end if;
return Cursor;
end Get_Cursor_Type;
function Get_Cursor_Type (Typ : Entity_Id) return Entity_Id is
begin
return Etype (Get_Iterable_Type_Primitive (Typ, Name_First));
end Get_Cursor_Type;
-------------------------------
-- Get_Default_External_Name --
-------------------------------
function Get_Default_External_Name (E : Node_Or_Entity_Id) return Node_Id is
begin
Get_Decoded_Name_String (Chars (E));
if Opt.External_Name_Imp_Casing = Uppercase then
Set_Casing (All_Upper_Case);
else
Set_Casing (All_Lower_Case);
end if;
return
Make_String_Literal (Sloc (E),
Strval => String_From_Name_Buffer);
end Get_Default_External_Name;
--------------------------
-- Get_Enclosing_Object --
--------------------------
function Get_Enclosing_Object (N : Node_Id) return Entity_Id is
begin
if Is_Entity_Name (N) then
return Entity (N);
else
case Nkind (N) is
when N_Indexed_Component
| N_Selected_Component
| N_Slice
=>
-- If not generating code, a dereference may be left implicit.
-- In thoses cases, return Empty.
if Is_Access_Type (Etype (Prefix (N))) then
return Empty;
else
return Get_Enclosing_Object (Prefix (N));
end if;
when N_Type_Conversion =>
return Get_Enclosing_Object (Expression (N));
when others =>
return Empty;
end case;
end if;
end Get_Enclosing_Object;
---------------------------
-- Get_Enum_Lit_From_Pos --
---------------------------
function Get_Enum_Lit_From_Pos
(T : Entity_Id;
Pos : Uint;
Loc : Source_Ptr) return Node_Id
is
Btyp : Entity_Id := Base_Type (T);
Lit : Node_Id;
LLoc : Source_Ptr;
begin
-- In the case where the literal is of type Character, Wide_Character
-- or Wide_Wide_Character or of a type derived from them, there needs
-- to be some special handling since there is no explicit chain of
-- literals to search. Instead, an N_Character_Literal node is created
-- with the appropriate Char_Code and Chars fields.
if Is_Standard_Character_Type (T) then
Set_Character_Literal_Name (UI_To_CC (Pos));
return
Make_Character_Literal (Loc,
Chars => Name_Find,
Char_Literal_Value => Pos);
-- For all other cases, we have a complete table of literals, and
-- we simply iterate through the chain of literal until the one
-- with the desired position value is found.
else
if Is_Private_Type (Btyp) and then Present (Full_View (Btyp)) then
Btyp := Full_View (Btyp);
end if;
Lit := First_Literal (Btyp);
-- Position in the enumeration type starts at 0
if Pos < 0 then
raise Constraint_Error;
end if;
for J in 1 .. UI_To_Int (Pos) loop
Next_Literal (Lit);
-- If Lit is Empty, Pos is not in range, so raise Constraint_Error
-- inside the loop to avoid calling Next_Literal on Empty.
if No (Lit) then
raise Constraint_Error;
end if;
end loop;
-- Create a new node from Lit, with source location provided by Loc
-- if not equal to No_Location, or by copying the source location of
-- Lit otherwise.
LLoc := Loc;
if LLoc = No_Location then
LLoc := Sloc (Lit);
end if;
return New_Occurrence_Of (Lit, LLoc);
end if;
end Get_Enum_Lit_From_Pos;
----------------------
-- Get_Fullest_View --
----------------------
function Get_Fullest_View
(E : Entity_Id;
Include_PAT : Boolean := True;
Recurse : Boolean := True) return Entity_Id
is
New_E : Entity_Id := Empty;
begin
-- Prevent cascaded errors
if No (E) then
return E;
end if;
-- Look at each kind of entity to see where we may need to go deeper.
case Ekind (E) is
when Incomplete_Kind =>
if From_Limited_With (E) then
New_E := Non_Limited_View (E);
elsif Present (Full_View (E)) then
New_E := Full_View (E);
elsif Ekind (E) = E_Incomplete_Subtype then
New_E := Etype (E);
end if;
when Private_Kind =>
if Present (Underlying_Full_View (E)) then
New_E := Underlying_Full_View (E);
elsif Present (Full_View (E)) then
New_E := Full_View (E);
elsif Etype (E) /= E then
New_E := Etype (E);
end if;
when Array_Kind =>
if Include_PAT and then Present (Packed_Array_Impl_Type (E)) then
New_E := Packed_Array_Impl_Type (E);
end if;
when E_Record_Subtype =>
if Present (Cloned_Subtype (E)) then
New_E := Cloned_Subtype (E);
end if;
when E_Class_Wide_Type =>
New_E := Root_Type (E);
when E_Class_Wide_Subtype =>
if Present (Equivalent_Type (E)) then
New_E := Equivalent_Type (E);
elsif Present (Cloned_Subtype (E)) then
New_E := Cloned_Subtype (E);
end if;
when E_Protected_Subtype
| E_Protected_Type
| E_Task_Subtype
| E_Task_Type
=>
if Present (Corresponding_Record_Type (E)) then
New_E := Corresponding_Record_Type (E);
end if;
when E_Access_Protected_Subprogram_Type
| E_Anonymous_Access_Protected_Subprogram_Type
=>
if Present (Equivalent_Type (E)) then
New_E := Equivalent_Type (E);
end if;
when E_Access_Subtype =>
New_E := Base_Type (E);
when others =>
null;
end case;
-- If we found a fuller view, either return it or recurse. Otherwise,
-- return our input.
return (if No (New_E) then E
elsif Recurse then Get_Fullest_View (New_E, Include_PAT, Recurse)
else New_E);
end Get_Fullest_View;
------------------------
-- Get_Generic_Entity --
------------------------
function Get_Generic_Entity (N : Node_Id) return Entity_Id is
Ent : constant Entity_Id := Entity (Name (N));
begin
if Present (Renamed_Entity (Ent)) then
return Renamed_Entity (Ent);
else
return Ent;
end if;
end Get_Generic_Entity;
-------------------------------------
-- Get_Incomplete_View_Of_Ancestor --
-------------------------------------
function Get_Incomplete_View_Of_Ancestor (E : Entity_Id) return Entity_Id is
Cur_Unit : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
Par_Scope : Entity_Id;
Par_Type : Entity_Id;
begin
-- The incomplete view of an ancestor is only relevant for private
-- derived types in child units.
if not Is_Derived_Type (E)
or else not Is_Child_Unit (Cur_Unit)
then
return Empty;
else
Par_Scope := Scope (Cur_Unit);
if No (Par_Scope) then
return Empty;
end if;
Par_Type := Etype (Base_Type (E));
-- Traverse list of ancestor types until we find one declared in
-- a parent or grandparent unit (two levels seem sufficient).
while Present (Par_Type) loop
if Scope (Par_Type) = Par_Scope
or else Scope (Par_Type) = Scope (Par_Scope)
then
return Par_Type;
elsif not Is_Derived_Type (Par_Type) then
return Empty;
else
Par_Type := Etype (Base_Type (Par_Type));
end if;
end loop;
-- If none found, there is no relevant ancestor type.
return Empty;
end if;
end Get_Incomplete_View_Of_Ancestor;
----------------------
-- Get_Index_Bounds --
----------------------
procedure Get_Index_Bounds
(N : Node_Id;
L : out Node_Id;
H : out Node_Id;
Use_Full_View : Boolean := False)
is
function Scalar_Range_Of_Type (Typ : Entity_Id) return Node_Id;
-- Obtain the scalar range of type Typ. If flag Use_Full_View is set and
-- Typ qualifies, the scalar range is obtained from the full view of the
-- type.
--------------------------
-- Scalar_Range_Of_Type --
--------------------------
function Scalar_Range_Of_Type (Typ : Entity_Id) return Node_Id is
T : Entity_Id := Typ;
begin
if Use_Full_View and then Present (Full_View (T)) then
T := Full_View (T);
end if;
return Scalar_Range (T);
end Scalar_Range_Of_Type;
-- Local variables
Kind : constant Node_Kind := Nkind (N);
Rng : Node_Id;
-- Start of processing for Get_Index_Bounds
begin
if Kind = N_Range then
L := Low_Bound (N);
H := High_Bound (N);
elsif Kind = N_Subtype_Indication then
Rng := Range_Expression (Constraint (N));
if Rng = Error then
L := Error;
H := Error;
return;
else
L := Low_Bound (Range_Expression (Constraint (N)));
H := High_Bound (Range_Expression (Constraint (N)));
end if;
elsif Is_Entity_Name (N) and then Is_Type (Entity (N)) then
Rng := Scalar_Range_Of_Type (Entity (N));
if Error_Posted (Rng) then
L := Error;
H := Error;
elsif Nkind (Rng) = N_Subtype_Indication then
Get_Index_Bounds (Rng, L, H);
else
L := Low_Bound (Rng);
H := High_Bound (Rng);
end if;
else
-- N is an expression, indicating a range with one value
L := N;
H := N;
end if;
end Get_Index_Bounds;
function Get_Index_Bounds
(N : Node_Id;
Use_Full_View : Boolean := False) return Range_Nodes is
Result : Range_Nodes;
begin
Get_Index_Bounds (N, Result.First, Result.Last, Use_Full_View);
return Result;
end Get_Index_Bounds;
function Get_Index_Bounds
(N : Node_Id;
Use_Full_View : Boolean := False) return Range_Values is
Nodes : constant Range_Nodes := Get_Index_Bounds (N, Use_Full_View);
begin
return (Expr_Value (Nodes.First), Expr_Value (Nodes.Last));
end Get_Index_Bounds;
-----------------------------
-- Get_Interfacing_Aspects --
-----------------------------
procedure Get_Interfacing_Aspects
(Iface_Asp : Node_Id;
Conv_Asp : out Node_Id;
EN_Asp : out Node_Id;
Expo_Asp : out Node_Id;
Imp_Asp : out Node_Id;
LN_Asp : out Node_Id;
Do_Checks : Boolean := False)
is
procedure Save_Or_Duplication_Error
(Asp : Node_Id;
To : in out Node_Id);
-- Save the value of aspect Asp in node To. If To already has a value,
-- then this is considered a duplicate use of aspect. Emit an error if
-- flag Do_Checks is set.
-------------------------------
-- Save_Or_Duplication_Error --
-------------------------------
procedure Save_Or_Duplication_Error
(Asp : Node_Id;
To : in out Node_Id)
is
begin
-- Detect an extra aspect and issue an error
if Present (To) then
if Do_Checks then
Error_Msg_Name_1 := Chars (Identifier (Asp));
Error_Msg_Sloc := Sloc (To);
Error_Msg_N ("aspect % previously given #", Asp);
end if;
-- Otherwise capture the aspect
else
To := Asp;
end if;
end Save_Or_Duplication_Error;
-- Local variables
Asp : Node_Id;
Asp_Id : Aspect_Id;
-- The following variables capture each individual aspect
Conv : Node_Id := Empty;
EN : Node_Id := Empty;
Expo : Node_Id := Empty;
Imp : Node_Id := Empty;
LN : Node_Id := Empty;
-- Start of processing for Get_Interfacing_Aspects
begin
-- The input interfacing aspect should reside in an aspect specification
-- list.
pragma Assert (Is_List_Member (Iface_Asp));
-- Examine the aspect specifications of the related entity. Find and
-- capture all interfacing aspects. Detect duplicates and emit errors
-- if applicable.
Asp := First (List_Containing (Iface_Asp));
while Present (Asp) loop
Asp_Id := Get_Aspect_Id (Asp);
if Asp_Id = Aspect_Convention then
Save_Or_Duplication_Error (Asp, Conv);
elsif Asp_Id = Aspect_External_Name then
Save_Or_Duplication_Error (Asp, EN);
elsif Asp_Id = Aspect_Export then
Save_Or_Duplication_Error (Asp, Expo);
elsif Asp_Id = Aspect_Import then
Save_Or_Duplication_Error (Asp, Imp);
elsif Asp_Id = Aspect_Link_Name then
Save_Or_Duplication_Error (Asp, LN);
end if;
Next (Asp);
end loop;
Conv_Asp := Conv;
EN_Asp := EN;
Expo_Asp := Expo;
Imp_Asp := Imp;
LN_Asp := LN;
end Get_Interfacing_Aspects;
---------------------------------
-- Get_Iterable_Type_Primitive --
---------------------------------
function Get_Iterable_Type_Primitive
(Typ : Entity_Id;
Nam : Name_Id) return Entity_Id
is
pragma Assert
(Is_Type (Typ)
and then
Nam in Name_Element
| Name_First
| Name_Has_Element
| Name_Last
| Name_Next
| Name_Previous);
Funcs : constant Node_Id := Find_Value_Of_Aspect (Typ, Aspect_Iterable);
Assoc : Node_Id;
begin
if No (Funcs) then
return Empty;
else
Assoc := First (Component_Associations (Funcs));
while Present (Assoc) loop
if Chars (First (Choices (Assoc))) = Nam then
return Entity (Expression (Assoc));
end if;
Next (Assoc);
end loop;
return Empty;
end if;
end Get_Iterable_Type_Primitive;
----------------------------------
-- Get_Library_Unit_Name_String --
----------------------------------
procedure Get_Library_Unit_Name_String (Decl_Node : Node_Id) is
Unit_Name_Id : constant Unit_Name_Type := Get_Unit_Name (Decl_Node);
begin
Get_Unit_Name_String (Unit_Name_Id);
-- Remove seven last character (" (spec)" or " (body)")
Name_Len := Name_Len - 7;
pragma Assert (Name_Buffer (Name_Len + 1) = ' ');
end Get_Library_Unit_Name_String;
--------------------------
-- Get_Max_Queue_Length --
--------------------------
function Get_Max_Queue_Length (Id : Entity_Id) return Uint is
pragma Assert (Is_Entry (Id));
Prag : constant Entity_Id := Get_Pragma (Id, Pragma_Max_Queue_Length);
Max : Uint;
begin
-- A value of 0 or -1 represents no maximum specified, and entries and
-- entry families with no Max_Queue_Length aspect or pragma default to
-- it.
if not Present (Prag) then
return Uint_0;
end if;
Max := Expr_Value
(Expression (First (Pragma_Argument_Associations (Prag))));
-- Since -1 and 0 are equivalent, return 0 for instances of -1 for
-- uniformity.
if Max = -1 then
return Uint_0;
end if;
return Max;
end Get_Max_Queue_Length;
------------------------
-- Get_Name_Entity_Id --
------------------------
function Get_Name_Entity_Id (Id : Name_Id) return Entity_Id is
begin
return Entity_Id (Get_Name_Table_Int (Id));
end Get_Name_Entity_Id;
------------------------------
-- Get_Name_From_CTC_Pragma --
------------------------------
function Get_Name_From_CTC_Pragma (N : Node_Id) return String_Id is
Arg : constant Node_Id :=
Get_Pragma_Arg (First (Pragma_Argument_Associations (N)));
begin
return Strval (Expr_Value_S (Arg));
end Get_Name_From_CTC_Pragma;
-----------------------
-- Get_Parent_Entity --
-----------------------
function Get_Parent_Entity (Unit : Node_Id) return Entity_Id is
begin
if Nkind (Unit) = N_Package_Body
and then Nkind (Original_Node (Unit)) = N_Package_Instantiation
then
return Defining_Entity
(Specification (Instance_Spec (Original_Node (Unit))));
elsif Nkind (Unit) = N_Package_Instantiation then
return Defining_Entity (Specification (Instance_Spec (Unit)));
else
return Defining_Entity (Unit);
end if;
end Get_Parent_Entity;
-------------------
-- Get_Pragma_Id --
-------------------
function Get_Pragma_Id (N : Node_Id) return Pragma_Id is
begin
return Get_Pragma_Id (Pragma_Name_Unmapped (N));
end Get_Pragma_Id;
------------------------
-- Get_Qualified_Name --
------------------------
function Get_Qualified_Name
(Id : Entity_Id;
Suffix : Entity_Id := Empty) return Name_Id
is
Suffix_Nam : Name_Id := No_Name;
begin
if Present (Suffix) then
Suffix_Nam := Chars (Suffix);
end if;
return Get_Qualified_Name (Chars (Id), Suffix_Nam, Scope (Id));
end Get_Qualified_Name;
function Get_Qualified_Name
(Nam : Name_Id;
Suffix : Name_Id := No_Name;
Scop : Entity_Id := Current_Scope) return Name_Id
is
procedure Add_Scope (S : Entity_Id);
-- Add the fully qualified form of scope S to the name buffer. The
-- format is:
-- s-1__s__
---------------
-- Add_Scope --
---------------
procedure Add_Scope (S : Entity_Id) is
begin
if S = Empty then
null;
elsif S = Standard_Standard then
null;
else
Add_Scope (Scope (S));
Get_Name_String_And_Append (Chars (S));
Add_Str_To_Name_Buffer ("__");
end if;
end Add_Scope;
-- Start of processing for Get_Qualified_Name
begin
Name_Len := 0;
Add_Scope (Scop);
-- Append the base name after all scopes have been chained
Get_Name_String_And_Append (Nam);
-- Append the suffix (if present)
if Suffix /= No_Name then
Add_Str_To_Name_Buffer ("__");
Get_Name_String_And_Append (Suffix);
end if;
return Name_Find;
end Get_Qualified_Name;
-----------------------
-- Get_Reason_String --
-----------------------
procedure Get_Reason_String (N : Node_Id) is
begin
if Nkind (N) = N_String_Literal then
Store_String_Chars (Strval (N));
elsif Nkind (N) = N_Op_Concat then
Get_Reason_String (Left_Opnd (N));
Get_Reason_String (Right_Opnd (N));
-- If not of required form, error
else
Error_Msg_N
("Reason for pragma Warnings has wrong form", N);
Error_Msg_N
("\must be string literal or concatenation of string literals", N);
return;
end if;
end Get_Reason_String;
--------------------------------
-- Get_Reference_Discriminant --
--------------------------------
function Get_Reference_Discriminant (Typ : Entity_Id) return Entity_Id is
D : Entity_Id;
begin
D := First_Discriminant (Typ);
while Present (D) loop
if Has_Implicit_Dereference (D) then
return D;
end if;
Next_Discriminant (D);
end loop;
return Empty;
end Get_Reference_Discriminant;
---------------------------
-- Get_Referenced_Object --
---------------------------
function Get_Referenced_Object (N : Node_Id) return Node_Id is
R : Node_Id;
begin
R := N;
while Is_Entity_Name (R)
and then Is_Object (Entity (R))
and then Present (Renamed_Object (Entity (R)))
loop
R := Renamed_Object (Entity (R));
end loop;
return R;
end Get_Referenced_Object;
------------------------
-- Get_Renamed_Entity --
------------------------
function Get_Renamed_Entity (E : Entity_Id) return Entity_Id is
R : Entity_Id := E;
begin
while Present (Renamed_Entity (R)) loop
R := Renamed_Entity (R);
end loop;
return R;
end Get_Renamed_Entity;
-----------------------
-- Get_Return_Object --
-----------------------
function Get_Return_Object (N : Node_Id) return Entity_Id is
Decl : Node_Id;
begin
Decl := First (Return_Object_Declarations (N));
while Present (Decl) loop
exit when Nkind (Decl) = N_Object_Declaration
and then Is_Return_Object (Defining_Identifier (Decl));
Next (Decl);
end loop;
pragma Assert (Present (Decl));
return Defining_Identifier (Decl);
end Get_Return_Object;
---------------------------
-- Get_Subprogram_Entity --
---------------------------
function Get_Subprogram_Entity (Nod : Node_Id) return Entity_Id is
Subp : Node_Id;
Subp_Id : Entity_Id;
begin
if Nkind (Nod) = N_Accept_Statement then
Subp := Entry_Direct_Name (Nod);
elsif Nkind (Nod) = N_Slice then
Subp := Prefix (Nod);
else
Subp := Name (Nod);
end if;
-- Strip the subprogram call
loop
if Nkind (Subp) in N_Explicit_Dereference
| N_Indexed_Component
| N_Selected_Component
then
Subp := Prefix (Subp);
elsif Nkind (Subp) in N_Type_Conversion
| N_Unchecked_Type_Conversion
then
Subp := Expression (Subp);
else
exit;
end if;
end loop;
-- Extract the entity of the subprogram call
if Is_Entity_Name (Subp) then
Subp_Id := Entity (Subp);
if Ekind (Subp_Id) = E_Access_Subprogram_Type then
Subp_Id := Directly_Designated_Type (Subp_Id);
end if;
if Is_Subprogram (Subp_Id) then
return Subp_Id;
else
return Empty;
end if;
-- The search did not find a construct that denotes a subprogram
else
return Empty;
end if;
end Get_Subprogram_Entity;
-----------------------------
-- Get_Task_Body_Procedure --
-----------------------------
function Get_Task_Body_Procedure (E : Entity_Id) return Entity_Id is
begin
-- Note: A task type may be the completion of a private type with
-- discriminants. When performing elaboration checks on a task
-- declaration, the current view of the type may be the private one,
-- and the procedure that holds the body of the task is held in its
-- underlying type.
-- This is an odd function, why not have Task_Body_Procedure do
-- the following digging???
return Task_Body_Procedure (Underlying_Type (Root_Type (E)));
end Get_Task_Body_Procedure;
-------------------------
-- Get_User_Defined_Eq --
-------------------------
function Get_User_Defined_Eq (E : Entity_Id) return Entity_Id is
Prim : Elmt_Id;
Op : Entity_Id;
begin
Prim := First_Elmt (Collect_Primitive_Operations (E));
while Present (Prim) loop
Op := Node (Prim);
if Chars (Op) = Name_Op_Eq
and then Etype (Op) = Standard_Boolean
and then Etype (First_Formal (Op)) = E
and then Etype (Next_Formal (First_Formal (Op))) = E
then
return Op;
end if;
Next_Elmt (Prim);
end loop;
return Empty;
end Get_User_Defined_Eq;
---------------
-- Get_Views --
---------------
procedure Get_Views
(Typ : Entity_Id;
Priv_Typ : out Entity_Id;
Full_Typ : out Entity_Id;
UFull_Typ : out Entity_Id;
CRec_Typ : out Entity_Id)
is
IP_View : Entity_Id;
begin
-- Assume that none of the views can be recovered
Priv_Typ := Empty;
Full_Typ := Empty;
UFull_Typ := Empty;
CRec_Typ := Empty;
-- The input type is the corresponding record type of a protected or a
-- task type.
if Ekind (Typ) = E_Record_Type
and then Is_Concurrent_Record_Type (Typ)
then
CRec_Typ := Typ;
Full_Typ := Corresponding_Concurrent_Type (CRec_Typ);
Priv_Typ := Incomplete_Or_Partial_View (Full_Typ);
-- Otherwise the input type denotes an arbitrary type
else
IP_View := Incomplete_Or_Partial_View (Typ);
-- The input type denotes the full view of a private type
if Present (IP_View) then
Priv_Typ := IP_View;
Full_Typ := Typ;
-- The input type is a private type
elsif Is_Private_Type (Typ) then
Priv_Typ := Typ;
Full_Typ := Full_View (Priv_Typ);
-- Otherwise the input type does not have any views
else
Full_Typ := Typ;
end if;
if Present (Full_Typ) and then Is_Private_Type (Full_Typ) then
UFull_Typ := Underlying_Full_View (Full_Typ);
if Present (UFull_Typ)
and then Ekind (UFull_Typ) in E_Protected_Type | E_Task_Type
then
CRec_Typ := Corresponding_Record_Type (UFull_Typ);
end if;
else
if Present (Full_Typ)
and then Ekind (Full_Typ) in E_Protected_Type | E_Task_Type
then
CRec_Typ := Corresponding_Record_Type (Full_Typ);
end if;
end if;
end if;
end Get_Views;
-----------------------
-- Has_Access_Values --
-----------------------
function Has_Access_Values (T : Entity_Id) return Boolean
is
Typ : constant Entity_Id := Underlying_Type (T);
begin
-- Case of a private type which is not completed yet. This can only
-- happen in the case of a generic formal type appearing directly, or
-- as a component of the type to which this function is being applied
-- at the top level. Return False in this case, since we certainly do
-- not know that the type contains access types.
if No (Typ) then
return False;
elsif Is_Access_Type (Typ) then
return True;
elsif Is_Array_Type (Typ) then
return Has_Access_Values (Component_Type (Typ));
elsif Is_Record_Type (Typ) then
declare
Comp : Entity_Id;
begin
-- Loop to check components
Comp := First_Component_Or_Discriminant (Typ);
while Present (Comp) loop
-- Check for access component, tag field does not count, even
-- though it is implemented internally using an access type.
if Has_Access_Values (Etype (Comp))
and then Chars (Comp) /= Name_uTag
then
return True;
end if;
Next_Component_Or_Discriminant (Comp);
end loop;
end;
return False;
else
return False;
end if;
end Has_Access_Values;
---------------------------------------
-- Has_Anonymous_Access_Discriminant --
---------------------------------------
function Has_Anonymous_Access_Discriminant (Typ : Entity_Id) return Boolean
is
Disc : Node_Id;
begin
if not Has_Discriminants (Typ) then
return False;
end if;
Disc := First_Discriminant (Typ);
while Present (Disc) loop
if Ekind (Etype (Disc)) = E_Anonymous_Access_Type then
return True;
end if;
Next_Discriminant (Disc);
end loop;
return False;
end Has_Anonymous_Access_Discriminant;
------------------------------
-- Has_Compatible_Alignment --
------------------------------
function Has_Compatible_Alignment
(Obj : Entity_Id;
Expr : Node_Id;
Layout_Done : Boolean) return Alignment_Result
is
function Has_Compatible_Alignment_Internal
(Obj : Entity_Id;
Expr : Node_Id;
Layout_Done : Boolean;
Default : Alignment_Result) return Alignment_Result;
-- This is the internal recursive function that actually does the work.
-- There is one additional parameter, which says what the result should
-- be if no alignment information is found, and there is no definite
-- indication of compatible alignments. At the outer level, this is set
-- to Unknown, but for internal recursive calls in the case where types
-- are known to be correct, it is set to Known_Compatible.
---------------------------------------
-- Has_Compatible_Alignment_Internal --
---------------------------------------
function Has_Compatible_Alignment_Internal
(Obj : Entity_Id;
Expr : Node_Id;
Layout_Done : Boolean;
Default : Alignment_Result) return Alignment_Result
is
Result : Alignment_Result := Known_Compatible;
-- Holds the current status of the result. Note that once a value of
-- Known_Incompatible is set, it is sticky and does not get changed
-- to Unknown (the value in Result only gets worse as we go along,
-- never better).
Offs : Uint := No_Uint;
-- Set to a factor of the offset from the base object when Expr is a
-- selected or indexed component, based on Component_Bit_Offset and
-- Component_Size respectively. A negative value is used to represent
-- a value that is not known at compile time.
procedure Check_Prefix;
-- Checks the prefix recursively in the case where the expression
-- is an indexed or selected component.
procedure Set_Result (R : Alignment_Result);
-- If R represents a worse outcome (unknown instead of known
-- compatible, or known incompatible), then set Result to R.
------------------
-- Check_Prefix --
------------------
procedure Check_Prefix is
begin
-- The subtlety here is that in doing a recursive call to check
-- the prefix, we have to decide what to do in the case where we
-- don't find any specific indication of an alignment problem.
-- At the outer level, we normally set Unknown as the result in
-- this case, since we can only set Known_Compatible if we really
-- know that the alignment value is OK, but for the recursive
-- call, in the case where the types match, and we have not
-- specified a peculiar alignment for the object, we are only
-- concerned about suspicious rep clauses, the default case does
-- not affect us, since the compiler will, in the absence of such
-- rep clauses, ensure that the alignment is correct.
if Default = Known_Compatible
or else
(Etype (Obj) = Etype (Expr)
and then (not Known_Alignment (Obj)
or else
Alignment (Obj) = Alignment (Etype (Obj))))
then
Set_Result
(Has_Compatible_Alignment_Internal
(Obj, Prefix (Expr), Layout_Done, Known_Compatible));
-- In all other cases, we need a full check on the prefix
else
Set_Result
(Has_Compatible_Alignment_Internal
(Obj, Prefix (Expr), Layout_Done, Unknown));
end if;
end Check_Prefix;
----------------
-- Set_Result --
----------------
procedure Set_Result (R : Alignment_Result) is
begin
if R > Result then
Result := R;
end if;
end Set_Result;
-- Start of processing for Has_Compatible_Alignment_Internal
begin
-- If Expr is a selected component, we must make sure there is no
-- potentially troublesome component clause and that the record is
-- not packed if the layout is not done.
if Nkind (Expr) = N_Selected_Component then
-- Packing generates unknown alignment if layout is not done
if Is_Packed (Etype (Prefix (Expr))) and then not Layout_Done then
Set_Result (Unknown);
end if;
-- Check prefix and component offset
Check_Prefix;
Offs := Component_Bit_Offset (Entity (Selector_Name (Expr)));
-- If Expr is an indexed component, we must make sure there is no
-- potentially troublesome Component_Size clause and that the array
-- is not bit-packed if the layout is not done.
elsif Nkind (Expr) = N_Indexed_Component then
declare
Typ : constant Entity_Id := Etype (Prefix (Expr));
begin
-- Packing generates unknown alignment if layout is not done
if Is_Bit_Packed_Array (Typ) and then not Layout_Done then
Set_Result (Unknown);
end if;
-- Check prefix and component offset (or at least size)
Check_Prefix;
Offs := Indexed_Component_Bit_Offset (Expr);
if No (Offs) then
Offs := Component_Size (Typ);
end if;
end;
end if;
-- If we have a null offset, the result is entirely determined by
-- the base object and has already been computed recursively.
if Present (Offs) and then Offs = Uint_0 then
null;
-- Case where we know the alignment of the object
elsif Known_Alignment (Obj) then
declare
ObjA : constant Uint := Alignment (Obj);
ExpA : Uint := No_Uint;
SizA : Uint := No_Uint;
begin
-- If alignment of Obj is 1, then we are always OK
if ObjA = 1 then
Set_Result (Known_Compatible);
-- Alignment of Obj is greater than 1, so we need to check
else
-- If we have an offset, see if it is compatible
if Present (Offs) and then Offs > Uint_0 then
if Offs mod (System_Storage_Unit * ObjA) /= 0 then
Set_Result (Known_Incompatible);
end if;
-- See if Expr is an object with known alignment
elsif Is_Entity_Name (Expr)
and then Known_Alignment (Entity (Expr))
then
Offs := Uint_0;
ExpA := Alignment (Entity (Expr));
-- Otherwise, we can use the alignment of the type of Expr
-- given that we already checked for discombobulating rep
-- clauses for the cases of indexed and selected components
-- above.
elsif Known_Alignment (Etype (Expr)) then
ExpA := Alignment (Etype (Expr));
-- Otherwise the alignment is unknown
else
Set_Result (Default);
end if;
-- If we got an alignment, see if it is acceptable
if Present (ExpA) and then ExpA < ObjA then
Set_Result (Known_Incompatible);
end if;
-- If Expr is a component or an entire object with a known
-- alignment, then we are fine. Otherwise, if its size is
-- known, it must be big enough for the required alignment.
if Present (Offs) then
null;
-- See if Expr is an object with known size
elsif Is_Entity_Name (Expr)
and then Known_Static_Esize (Entity (Expr))
then
SizA := Esize (Entity (Expr));
-- Otherwise, we check the object size of the Expr type
elsif Known_Static_Esize (Etype (Expr)) then
SizA := Esize (Etype (Expr));
end if;
-- If we got a size, see if it is a multiple of the Obj
-- alignment; if not, then the alignment cannot be
-- acceptable, since the size is always a multiple of the
-- alignment.
if Present (SizA) then
if SizA mod (ObjA * Ttypes.System_Storage_Unit) /= 0 then
Set_Result (Known_Incompatible);
end if;
end if;
end if;
end;
-- If we do not know required alignment, any non-zero offset is a
-- potential problem (but certainly may be OK, so result is unknown).
elsif Present (Offs) then
Set_Result (Unknown);
-- If we can't find the result by direct comparison of alignment
-- values, then there is still one case that we can determine known
-- result, and that is when we can determine that the types are the
-- same, and no alignments are specified. Then we known that the
-- alignments are compatible, even if we don't know the alignment
-- value in the front end.
elsif Etype (Obj) = Etype (Expr) then
-- Types are the same, but we have to check for possible size
-- and alignments on the Expr object that may make the alignment
-- different, even though the types are the same.
if Is_Entity_Name (Expr) then
-- First check alignment of the Expr object. Any alignment less
-- than Maximum_Alignment is worrisome since this is the case
-- where we do not know the alignment of Obj.
if Known_Alignment (Entity (Expr))
and then Alignment (Entity (Expr)) < Ttypes.Maximum_Alignment
then
Set_Result (Unknown);
-- Now check size of Expr object. Any size that is not an even
-- multiple of Maximum_Alignment is also worrisome since it
-- may cause the alignment of the object to be less than the
-- alignment of the type.
elsif Known_Static_Esize (Entity (Expr))
and then
Esize (Entity (Expr)) mod
(Ttypes.Maximum_Alignment * Ttypes.System_Storage_Unit)
/= 0
then
Set_Result (Unknown);
-- Otherwise same type is decisive
else
Set_Result (Known_Compatible);
end if;
end if;
-- Another case to deal with is when there is an explicit size or
-- alignment clause when the types are not the same. If so, then the
-- result is Unknown. We don't need to do this test if the Default is
-- Unknown, since that result will be set in any case.
elsif Default /= Unknown
and then (Has_Size_Clause (Etype (Expr))
or else
Has_Alignment_Clause (Etype (Expr)))
then
Set_Result (Unknown);
-- If no indication found, set default
else
Set_Result (Default);
end if;
-- Return worst result found
return Result;
end Has_Compatible_Alignment_Internal;
-- Start of processing for Has_Compatible_Alignment
begin
-- If Obj has no specified alignment, then set alignment from the type
-- alignment. Perhaps we should always do this, but for sure we should
-- do it when there is an address clause since we can do more if the
-- alignment is known.
if not Known_Alignment (Obj) and then Known_Alignment (Etype (Obj)) then
Set_Alignment (Obj, Alignment (Etype (Obj)));
end if;
-- Now do the internal call that does all the work
return
Has_Compatible_Alignment_Internal (Obj, Expr, Layout_Done, Unknown);
end Has_Compatible_Alignment;
----------------------
-- Has_Declarations --
----------------------
function Has_Declarations (N : Node_Id) return Boolean is
begin
return Nkind (N) in N_Accept_Statement
| N_Block_Statement
| N_Compilation_Unit_Aux
| N_Entry_Body
| N_Package_Body
| N_Protected_Body
| N_Subprogram_Body
| N_Task_Body
| N_Package_Specification;
end Has_Declarations;
---------------------------------
-- Has_Defaulted_Discriminants --
---------------------------------
function Has_Defaulted_Discriminants (Typ : Entity_Id) return Boolean is
begin
return Has_Discriminants (Typ)
and then Present (Discriminant_Default_Value
(First_Discriminant (Typ)));
end Has_Defaulted_Discriminants;
-------------------
-- Has_Denormals --
-------------------
function Has_Denormals (E : Entity_Id) return Boolean is
begin
return Is_Floating_Point_Type (E) and then Denorm_On_Target;
end Has_Denormals;
-------------------------------------------
-- Has_Discriminant_Dependent_Constraint --
-------------------------------------------
function Has_Discriminant_Dependent_Constraint
(Comp : Entity_Id) return Boolean
is
Comp_Decl : constant Node_Id := Parent (Comp);
Subt_Indic : Node_Id;
Constr : Node_Id;
Assn : Node_Id;
begin
-- Discriminants can't depend on discriminants
if Ekind (Comp) = E_Discriminant then
return False;
else
Subt_Indic := Subtype_Indication (Component_Definition (Comp_Decl));
if Nkind (Subt_Indic) = N_Subtype_Indication then
Constr := Constraint (Subt_Indic);
if Nkind (Constr) = N_Index_Or_Discriminant_Constraint then
Assn := First (Constraints (Constr));
while Present (Assn) loop
case Nkind (Assn) is
when N_Identifier
| N_Range
| N_Subtype_Indication
=>
if Depends_On_Discriminant (Assn) then
return True;
end if;
when N_Discriminant_Association =>
if Depends_On_Discriminant (Expression (Assn)) then
return True;
end if;
when others =>
null;
end case;
Next (Assn);
end loop;
end if;
end if;
end if;
return False;
end Has_Discriminant_Dependent_Constraint;
--------------------------------------
-- Has_Effectively_Volatile_Profile --
--------------------------------------
function Has_Effectively_Volatile_Profile
(Subp_Id : Entity_Id) return Boolean
is
Formal : Entity_Id;
begin
-- Inspect the formal parameters looking for an effectively volatile
-- type for reading.
Formal := First_Formal (Subp_Id);
while Present (Formal) loop
if Is_Effectively_Volatile_For_Reading (Etype (Formal)) then
return True;
end if;
Next_Formal (Formal);
end loop;
-- Inspect the return type of functions
if Ekind (Subp_Id) in E_Function | E_Generic_Function
and then Is_Effectively_Volatile_For_Reading (Etype (Subp_Id))
then
return True;
end if;
return False;
end Has_Effectively_Volatile_Profile;
--------------------------
-- Has_Enabled_Property --
--------------------------
function Has_Enabled_Property
(Item_Id : Entity_Id;
Property : Name_Id) return Boolean
is
function Protected_Type_Or_Variable_Has_Enabled_Property return Boolean;
-- Determine whether a protected type or variable denoted by Item_Id
-- has the property enabled.
function State_Has_Enabled_Property return Boolean;
-- Determine whether a state denoted by Item_Id has the property enabled
function Type_Or_Variable_Has_Enabled_Property
(Item_Id : Entity_Id) return Boolean;
-- Determine whether type or variable denoted by Item_Id has the
-- property enabled.
-----------------------------------------------------
-- Protected_Type_Or_Variable_Has_Enabled_Property --
-----------------------------------------------------
function Protected_Type_Or_Variable_Has_Enabled_Property return Boolean
is
begin
-- Protected entities always have the properties Async_Readers and
-- Async_Writers (SPARK RM 7.1.2(16)).
if Property = Name_Async_Readers
or else Property = Name_Async_Writers
then
return True;
-- Protected objects that have Part_Of components also inherit their
-- properties Effective_Reads and Effective_Writes
-- (SPARK RM 7.1.2(16)).
elsif Is_Single_Protected_Object (Item_Id) then
declare
Constit_Elmt : Elmt_Id;
Constit_Id : Entity_Id;
Constits : constant Elist_Id
:= Part_Of_Constituents (Item_Id);
begin
if Present (Constits) then
Constit_Elmt := First_Elmt (Constits);
while Present (Constit_Elmt) loop
Constit_Id := Node (Constit_Elmt);
if Has_Enabled_Property (Constit_Id, Property) then
return True;
end if;
Next_Elmt (Constit_Elmt);
end loop;
end if;
end;
end if;
return False;
end Protected_Type_Or_Variable_Has_Enabled_Property;
--------------------------------
-- State_Has_Enabled_Property --
--------------------------------
function State_Has_Enabled_Property return Boolean is
Decl : constant Node_Id := Parent (Item_Id);
procedure Find_Simple_Properties
(Has_External : out Boolean;
Has_Synchronous : out Boolean);
-- Extract the simple properties associated with declaration Decl
function Is_Enabled_External_Property return Boolean;
-- Determine whether property Property appears within the external
-- property list of declaration Decl, and return its status.
----------------------------
-- Find_Simple_Properties --
----------------------------
procedure Find_Simple_Properties
(Has_External : out Boolean;
Has_Synchronous : out Boolean)
is
Opt : Node_Id;
begin
-- Assume that none of the properties are available
Has_External := False;
Has_Synchronous := False;
Opt := First (Expressions (Decl));
while Present (Opt) loop
if Nkind (Opt) = N_Identifier then
if Chars (Opt) = Name_External then
Has_External := True;
elsif Chars (Opt) = Name_Synchronous then
Has_Synchronous := True;
end if;
end if;
Next (Opt);
end loop;
end Find_Simple_Properties;
----------------------------------
-- Is_Enabled_External_Property --
----------------------------------
function Is_Enabled_External_Property return Boolean is
Opt : Node_Id;
Opt_Nam : Node_Id;
Prop : Node_Id;
Prop_Nam : Node_Id;
Props : Node_Id;
begin
Opt := First (Component_Associations (Decl));
while Present (Opt) loop
Opt_Nam := First (Choices (Opt));
if Nkind (Opt_Nam) = N_Identifier
and then Chars (Opt_Nam) = Name_External
then
Props := Expression (Opt);
-- Multiple properties appear as an aggregate
if Nkind (Props) = N_Aggregate then
-- Simple property form
Prop := First (Expressions (Props));
while Present (Prop) loop
if Chars (Prop) = Property then
return True;
end if;
Next (Prop);
end loop;
-- Property with expression form
Prop := First (Component_Associations (Props));
while Present (Prop) loop
Prop_Nam := First (Choices (Prop));
-- The property can be represented in two ways:
-- others => <value>
-- <property> => <value>
if Nkind (Prop_Nam) = N_Others_Choice
or else (Nkind (Prop_Nam) = N_Identifier
and then Chars (Prop_Nam) = Property)
then
return Is_True (Expr_Value (Expression (Prop)));
end if;
Next (Prop);
end loop;
-- Single property
else
return Chars (Props) = Property;
end if;
end if;
Next (Opt);
end loop;
return False;
end Is_Enabled_External_Property;
-- Local variables
Has_External : Boolean;
Has_Synchronous : Boolean;
-- Start of processing for State_Has_Enabled_Property
begin
-- The declaration of an external abstract state appears as an
-- extension aggregate. If this is not the case, properties can
-- never be set.
if Nkind (Decl) /= N_Extension_Aggregate then
return False;
end if;
Find_Simple_Properties (Has_External, Has_Synchronous);
-- Simple option External enables all properties (SPARK RM 7.1.2(2))
if Has_External then
return True;
-- Option External may enable or disable specific properties
elsif Is_Enabled_External_Property then
return True;
-- Simple option Synchronous
--
-- enables disables
-- Async_Readers Effective_Reads
-- Async_Writers Effective_Writes
--
-- Note that both forms of External have higher precedence than
-- Synchronous (SPARK RM 7.1.4(9)).
elsif Has_Synchronous then
return Property in Name_Async_Readers | Name_Async_Writers;
end if;
return False;
end State_Has_Enabled_Property;
-------------------------------------------
-- Type_Or_Variable_Has_Enabled_Property --
-------------------------------------------
function Type_Or_Variable_Has_Enabled_Property
(Item_Id : Entity_Id) return Boolean
is
function Is_Enabled (Prag : Node_Id) return Boolean;
-- Determine whether property pragma Prag (if present) denotes an
-- enabled property.
----------------
-- Is_Enabled --
----------------
function Is_Enabled (Prag : Node_Id) return Boolean is
Arg1 : Node_Id;
begin
if Present (Prag) then
Arg1 := First (Pragma_Argument_Associations (Prag));
-- The pragma has an optional Boolean expression, the related
-- property is enabled only when the expression evaluates to
-- True.
if Present (Arg1) then
return Is_True (Expr_Value (Get_Pragma_Arg (Arg1)));
-- Otherwise the lack of expression enables the property by
-- default.
else
return True;
end if;
-- The property was never set in the first place
else
return False;
end if;
end Is_Enabled;
-- Local variables
AR : constant Node_Id :=
Get_Pragma (Item_Id, Pragma_Async_Readers);
AW : constant Node_Id :=
Get_Pragma (Item_Id, Pragma_Async_Writers);
ER : constant Node_Id :=
Get_Pragma (Item_Id, Pragma_Effective_Reads);
EW : constant Node_Id :=
Get_Pragma (Item_Id, Pragma_Effective_Writes);
Is_Derived_Type_With_Volatile_Parent_Type : constant Boolean :=
Is_Derived_Type (Item_Id)
and then Is_Effectively_Volatile (Etype (Base_Type (Item_Id)));
-- Start of processing for Type_Or_Variable_Has_Enabled_Property
begin
-- A non-effectively volatile object can never possess external
-- properties.
if not Is_Effectively_Volatile (Item_Id) then
return False;
-- External properties related to variables come in two flavors -
-- explicit and implicit. The explicit case is characterized by the
-- presence of a property pragma with an optional Boolean flag. The
-- property is enabled when the flag evaluates to True or the flag is
-- missing altogether.
elsif Property = Name_Async_Readers and then Present (AR) then
return Is_Enabled (AR);
elsif Property = Name_Async_Writers and then Present (AW) then
return Is_Enabled (AW);
elsif Property = Name_Effective_Reads and then Present (ER) then
return Is_Enabled (ER);
elsif Property = Name_Effective_Writes and then Present (EW) then
return Is_Enabled (EW);
-- If other properties are set explicitly, then this one is set
-- implicitly to False, except in the case of a derived type
-- whose parent type is volatile (in that case, we will inherit
-- from the parent type, below).
elsif (Present (AR)
or else Present (AW)
or else Present (ER)
or else Present (EW))
and then not Is_Derived_Type_With_Volatile_Parent_Type
then
return False;
-- For a private type, may need to look at the full view
elsif Is_Private_Type (Item_Id) and then Present (Full_View (Item_Id))
then
return Type_Or_Variable_Has_Enabled_Property (Full_View (Item_Id));
-- For a derived type whose parent type is volatile, the
-- property may be inherited (but ignore a non-volatile parent).
elsif Is_Derived_Type_With_Volatile_Parent_Type then
return Type_Or_Variable_Has_Enabled_Property
(First_Subtype (Etype (Base_Type (Item_Id))));
-- If not specified explicitly for an object and the type
-- is effectively volatile, then take result from the type.
elsif not Is_Type (Item_Id)
and then Is_Effectively_Volatile (Etype (Item_Id))
then
return Has_Enabled_Property (Etype (Item_Id), Property);
-- The implicit case lacks all property pragmas
elsif No (AR) and then No (AW) and then No (ER) and then No (EW) then
if Is_Protected_Type (Etype (Item_Id)) then
return Protected_Type_Or_Variable_Has_Enabled_Property;
else
return True;
end if;
else
return False;
end if;
end Type_Or_Variable_Has_Enabled_Property;
-- Start of processing for Has_Enabled_Property
begin
-- Abstract states and variables have a flexible scheme of specifying
-- external properties.
if Ekind (Item_Id) = E_Abstract_State then
return State_Has_Enabled_Property;
elsif Ekind (Item_Id) in E_Variable | E_Constant then
return Type_Or_Variable_Has_Enabled_Property (Item_Id);
-- Other objects can only inherit properties through their type. We
-- cannot call directly Type_Or_Variable_Has_Enabled_Property on
-- these as they don't have contracts attached, which is expected by
-- this function.
elsif Is_Object (Item_Id) then
return Type_Or_Variable_Has_Enabled_Property (Etype (Item_Id));
elsif Is_Type (Item_Id) then
return Type_Or_Variable_Has_Enabled_Property
(Item_Id => First_Subtype (Item_Id));
-- Otherwise a property is enabled when the related item is effectively
-- volatile.
else
return Is_Effectively_Volatile (Item_Id);
end if;
end Has_Enabled_Property;
-------------------------------------
-- Has_Full_Default_Initialization --
-------------------------------------
function Has_Full_Default_Initialization (Typ : Entity_Id) return Boolean is
Comp : Entity_Id;
begin
-- A type subject to pragma Default_Initial_Condition may be fully
-- default initialized depending on inheritance and the argument of
-- the pragma. Since any type may act as the full view of a private
-- type, this check must be performed prior to the specialized tests
-- below.
if Has_Fully_Default_Initializing_DIC_Pragma (Typ) then
return True;
end if;
-- A scalar type is fully default initialized if it is subject to aspect
-- Default_Value.
if Is_Scalar_Type (Typ) then
return Has_Default_Aspect (Typ);
-- An access type is fully default initialized by default
elsif Is_Access_Type (Typ) then
return True;
-- An array type is fully default initialized if its element type is
-- scalar and the array type carries aspect Default_Component_Value or
-- the element type is fully default initialized.
elsif Is_Array_Type (Typ) then
return
Has_Default_Aspect (Typ)
or else Has_Full_Default_Initialization (Component_Type (Typ));
-- A protected type, record type, or type extension is fully default
-- initialized if all its components either carry an initialization
-- expression or have a type that is fully default initialized. The
-- parent type of a type extension must be fully default initialized.
elsif Is_Record_Type (Typ) or else Is_Protected_Type (Typ) then
-- Inspect all entities defined in the scope of the type, looking for
-- uninitialized components.
Comp := First_Component (Typ);
while Present (Comp) loop
if Comes_From_Source (Comp)
and then No (Expression (Parent (Comp)))
and then not Has_Full_Default_Initialization (Etype (Comp))
then
return False;
end if;
Next_Component (Comp);
end loop;
-- Ensure that the parent type of a type extension is fully default
-- initialized.
if Etype (Typ) /= Typ
and then not Has_Full_Default_Initialization (Etype (Typ))
then
return False;
end if;
-- If we get here, then all components and parent portion are fully
-- default initialized.
return True;
-- A task type is fully default initialized by default
elsif Is_Task_Type (Typ) then
return True;
-- Otherwise the type is not fully default initialized
else
return False;
end if;
end Has_Full_Default_Initialization;
-----------------------------------------------
-- Has_Fully_Default_Initializing_DIC_Pragma --
-----------------------------------------------
function Has_Fully_Default_Initializing_DIC_Pragma
(Typ : Entity_Id) return Boolean
is
Args : List_Id;
Prag : Node_Id;
begin
-- A type that inherits pragma Default_Initial_Condition from a parent
-- type is automatically fully default initialized.
if Has_Inherited_DIC (Typ) then
return True;
-- Otherwise the type is fully default initialized only when the pragma
-- appears without an argument, or the argument is non-null.
elsif Has_Own_DIC (Typ) then
Prag := Get_Pragma (Typ, Pragma_Default_Initial_Condition);
pragma Assert (Present (Prag));
Args := Pragma_Argument_Associations (Prag);
-- The pragma appears without an argument in which case it defaults
-- to True.
if No (Args) then
return True;
-- The pragma appears with a non-null expression
elsif Nkind (Get_Pragma_Arg (First (Args))) /= N_Null then
return True;
end if;
end if;
return False;
end Has_Fully_Default_Initializing_DIC_Pragma;
---------------------------------
-- Has_Inferable_Discriminants --
---------------------------------
function Has_Inferable_Discriminants (N : Node_Id) return Boolean is
function Prefix_Is_Formal_Parameter (N : Node_Id) return Boolean;
-- Determines whether the left-most prefix of a selected component is a
-- formal parameter in a subprogram. Assumes N is a selected component.
--------------------------------
-- Prefix_Is_Formal_Parameter --
--------------------------------
function Prefix_Is_Formal_Parameter (N : Node_Id) return Boolean is
Sel_Comp : Node_Id;
begin
-- Move to the left-most prefix by climbing up the tree
Sel_Comp := N;
while Present (Parent (Sel_Comp))
and then Nkind (Parent (Sel_Comp)) = N_Selected_Component
loop
Sel_Comp := Parent (Sel_Comp);
end loop;
return Is_Formal (Entity (Prefix (Sel_Comp)));
end Prefix_Is_Formal_Parameter;
-- Start of processing for Has_Inferable_Discriminants
begin
-- For selected components, the subtype of the selector must be a
-- constrained Unchecked_Union. If the component is subject to a
-- per-object constraint, then the enclosing object must have inferable
-- discriminants.
if Nkind (N) = N_Selected_Component then
if Has_Per_Object_Constraint (Entity (Selector_Name (N))) then
-- A small hack. If we have a per-object constrained selected
-- component of a formal parameter, return True since we do not
-- know the actual parameter association yet.
if Prefix_Is_Formal_Parameter (N) then
return True;
-- Otherwise, check the enclosing object and the selector
else
return Has_Inferable_Discriminants (Prefix (N))
and then Has_Inferable_Discriminants (Selector_Name (N));
end if;
-- The call to Has_Inferable_Discriminants will determine whether
-- the selector has a constrained Unchecked_Union nominal type.
else
return Has_Inferable_Discriminants (Selector_Name (N));
end if;
-- A qualified expression has inferable discriminants if its subtype
-- mark is a constrained Unchecked_Union subtype.
elsif Nkind (N) = N_Qualified_Expression then
return Is_Unchecked_Union (Etype (Subtype_Mark (N)))
and then Is_Constrained (Etype (Subtype_Mark (N)));
-- For all other names, it is sufficient to have a constrained
-- Unchecked_Union nominal subtype.
else
return Is_Unchecked_Union (Base_Type (Etype (N)))
and then Is_Constrained (Etype (N));
end if;
end Has_Inferable_Discriminants;
--------------------
-- Has_Infinities --
--------------------
function Has_Infinities (E : Entity_Id) return Boolean is
begin
return
Is_Floating_Point_Type (E)
and then Nkind (Scalar_Range (E)) = N_Range
and then Includes_Infinities (Scalar_Range (E));
end Has_Infinities;
--------------------
-- Has_Interfaces --
--------------------
function Has_Interfaces
(T : Entity_Id;
Use_Full_View : Boolean := True) return Boolean
is
Typ : Entity_Id := Base_Type (T);
begin
-- Handle concurrent types
if Is_Concurrent_Type (Typ) then
Typ := Corresponding_Record_Type (Typ);
end if;
if not Present (Typ)
or else not Is_Record_Type (Typ)
or else not Is_Tagged_Type (Typ)
then
return False;
end if;
-- Handle private types
if Use_Full_View and then Present (Full_View (Typ)) then
Typ := Full_View (Typ);
end if;
-- Handle concurrent record types
if Is_Concurrent_Record_Type (Typ)
and then Is_Non_Empty_List (Abstract_Interface_List (Typ))
then
return True;
end if;
loop
if Is_Interface (Typ)
or else
(Is_Record_Type (Typ)
and then Present (Interfaces (Typ))
and then not Is_Empty_Elmt_List (Interfaces (Typ)))
then
return True;
end if;
exit when Etype (Typ) = Typ
-- Handle private types
or else (Present (Full_View (Etype (Typ)))
and then Full_View (Etype (Typ)) = Typ)
-- Protect frontend against wrong sources with cyclic derivations
or else Etype (Typ) = T;
-- Climb to the ancestor type handling private types
if Present (Full_View (Etype (Typ))) then
Typ := Full_View (Etype (Typ));
else
Typ := Etype (Typ);
end if;
end loop;
return False;
end Has_Interfaces;
--------------------------
-- Has_Max_Queue_Length --
--------------------------
function Has_Max_Queue_Length (Id : Entity_Id) return Boolean is
begin
return
Ekind (Id) = E_Entry
and then Present (Get_Pragma (Id, Pragma_Max_Queue_Length));
end Has_Max_Queue_Length;
---------------------------------
-- Has_No_Obvious_Side_Effects --
---------------------------------
function Has_No_Obvious_Side_Effects (N : Node_Id) return Boolean is
begin
-- For now handle literals, constants, and non-volatile variables and
-- expressions combining these with operators or short circuit forms.
if Nkind (N) in N_Numeric_Or_String_Literal then
return True;
elsif Nkind (N) = N_Character_Literal then
return True;
elsif Nkind (N) in N_Unary_Op then
return Has_No_Obvious_Side_Effects (Right_Opnd (N));
elsif Nkind (N) in N_Binary_Op or else Nkind (N) in N_Short_Circuit then
return Has_No_Obvious_Side_Effects (Left_Opnd (N))
and then
Has_No_Obvious_Side_Effects (Right_Opnd (N));
elsif Nkind (N) = N_Expression_With_Actions
and then Is_Empty_List (Actions (N))
then
return Has_No_Obvious_Side_Effects (Expression (N));
elsif Nkind (N) in N_Has_Entity then
return Present (Entity (N))
and then
Ekind (Entity (N)) in
E_Variable | E_Constant | E_Enumeration_Literal |
E_In_Parameter | E_Out_Parameter | E_In_Out_Parameter
and then not Is_Volatile (Entity (N));
else
return False;
end if;
end Has_No_Obvious_Side_Effects;
-----------------------------
-- Has_Non_Null_Refinement --
-----------------------------
function Has_Non_Null_Refinement (Id : Entity_Id) return Boolean is
Constits : Elist_Id;
begin
pragma Assert (Ekind (Id) = E_Abstract_State);
Constits := Refinement_Constituents (Id);
-- For a refinement to be non-null, the first constituent must be
-- anything other than null.
return
Present (Constits)
and then Nkind (Node (First_Elmt (Constits))) /= N_Null;
end Has_Non_Null_Refinement;
-----------------------------
-- Has_Non_Null_Statements --
-----------------------------
function Has_Non_Null_Statements (L : List_Id) return Boolean is
Node : Node_Id;
begin
Node := First (L);
while Present (Node) loop
if Nkind (Node) not in N_Null_Statement | N_Call_Marker then
return True;
end if;
Next (Node);
end loop;
return False;
end Has_Non_Null_Statements;
----------------------------------
-- Is_Access_Subprogram_Wrapper --
----------------------------------
function Is_Access_Subprogram_Wrapper (E : Entity_Id) return Boolean is
Formal : constant Entity_Id := Last_Formal (E);
begin
return Present (Formal)
and then Ekind (Etype (Formal)) in Access_Subprogram_Kind
and then Access_Subprogram_Wrapper
(Directly_Designated_Type (Etype (Formal))) = E;
end Is_Access_Subprogram_Wrapper;
---------------------------
-- Is_Explicitly_Aliased --
---------------------------
function Is_Explicitly_Aliased (N : Node_Id) return Boolean is
begin
return Is_Formal (N)
and then Present (Parent (N))
and then Nkind (Parent (N)) = N_Parameter_Specification
and then Aliased_Present (Parent (N));
end Is_Explicitly_Aliased;
----------------------------
-- Is_Container_Aggregate --
----------------------------
function Is_Container_Aggregate (Exp : Node_Id) return Boolean is
function Is_Record_Aggregate return Boolean is (False);
-- ??? Unimplemented. Given an aggregate whose type is a
-- record type with specified Aggregate aspect, how do we
-- determine whether it is a record aggregate or a container
-- aggregate? If the code where the aggregate occurs can see only
-- a partial view of the aggregate's type then the aggregate
-- cannot be a record type; an aggregate of a private type has to
-- be a container aggregate.
begin
return Nkind (Exp) = N_Aggregate
and then Present (Find_Aspect (Etype (Exp), Aspect_Aggregate))
and then not Is_Record_Aggregate;
end Is_Container_Aggregate;
---------------------------------
-- Side_Effect_Free_Statements --
---------------------------------
function Side_Effect_Free_Statements (L : List_Id) return Boolean is
Node : Node_Id;
begin
Node := First (L);
while Present (Node) loop
case Nkind (Node) is
when N_Null_Statement | N_Call_Marker | N_Raise_xxx_Error =>
null;
when N_Object_Declaration =>
if Present (Expression (Node))
and then not Side_Effect_Free (Expression (Node))
then
return False;
end if;
when others =>
return False;
end case;
Next (Node);
end loop;
return True;
end Side_Effect_Free_Statements;
---------------------------
-- Side_Effect_Free_Loop --
---------------------------
function Side_Effect_Free_Loop (N : Node_Id) return Boolean is
Scheme : Node_Id;
Spec : Node_Id;
Subt : Node_Id;
begin
-- If this is not a loop (e.g. because the loop has been rewritten),
-- then return false.
if Nkind (N) /= N_Loop_Statement then
return False;
end if;
-- First check the statements
if Side_Effect_Free_Statements (Statements (N)) then
-- Then check the loop condition/indexes
if Present (Iteration_Scheme (N)) then
Scheme := Iteration_Scheme (N);
if Present (Condition (Scheme))
or else Present (Iterator_Specification (Scheme))
then
return False;
elsif Present (Loop_Parameter_Specification (Scheme)) then
Spec := Loop_Parameter_Specification (Scheme);
Subt := Discrete_Subtype_Definition (Spec);
if Present (Subt) then
if Nkind (Subt) = N_Range then
return Side_Effect_Free (Low_Bound (Subt))
and then Side_Effect_Free (High_Bound (Subt));
else
-- subtype indication
return True;
end if;
end if;
end if;
end if;
end if;
return False;
end Side_Effect_Free_Loop;
----------------------------------
-- Has_Non_Trivial_Precondition --
----------------------------------
function Has_Non_Trivial_Precondition (Subp : Entity_Id) return Boolean is
Pre : constant Node_Id := Find_Aspect (Subp, Aspect_Pre,
Class_Present => True);
begin
return
Present (Pre)
and then not Is_Entity_Name (Expression (Pre));
end Has_Non_Trivial_Precondition;
-------------------
-- Has_Null_Body --
-------------------
function Has_Null_Body (Proc_Id : Entity_Id) return Boolean is
Body_Id : Entity_Id;
Decl : Node_Id;
Spec : Node_Id;
Stmt1 : Node_Id;
Stmt2 : Node_Id;
begin
Spec := Parent (Proc_Id);
Decl := Parent (Spec);
-- Retrieve the entity of the procedure body (e.g. invariant proc).
if Nkind (Spec) = N_Procedure_Specification
and then Nkind (Decl) = N_Subprogram_Declaration
then
Body_Id := Corresponding_Body (Decl);
-- The body acts as a spec
else
Body_Id := Proc_Id;
end if;
-- The body will be generated later
if No (Body_Id) then
return False;
end if;
Spec := Parent (Body_Id);
Decl := Parent (Spec);
pragma Assert
(Nkind (Spec) = N_Procedure_Specification
and then Nkind (Decl) = N_Subprogram_Body);
Stmt1 := First (Statements (Handled_Statement_Sequence (Decl)));
-- Look for a null statement followed by an optional return
-- statement.
if Nkind (Stmt1) = N_Null_Statement then
Stmt2 := Next (Stmt1);
if Present (Stmt2) then
return Nkind (Stmt2) = N_Simple_Return_Statement;
else
return True;
end if;
end if;
return False;
end Has_Null_Body;
------------------------
-- Has_Null_Exclusion --
------------------------
function Has_Null_Exclusion (N : Node_Id) return Boolean is
begin
case Nkind (N) is
when N_Access_Definition
| N_Access_Function_Definition
| N_Access_Procedure_Definition
| N_Access_To_Object_Definition
| N_Allocator
| N_Derived_Type_Definition
| N_Function_Specification
| N_Subtype_Declaration
=>
return Null_Exclusion_Present (N);
when N_Component_Definition
| N_Formal_Object_Declaration
=>
if Present (Subtype_Mark (N)) then
return Null_Exclusion_Present (N);
else pragma Assert (Present (Access_Definition (N)));
return Null_Exclusion_Present (Access_Definition (N));
end if;
when N_Object_Renaming_Declaration =>
if Present (Subtype_Mark (N)) then
return Null_Exclusion_Present (N);
elsif Present (Access_Definition (N)) then
return Null_Exclusion_Present (Access_Definition (N));
else
return False; -- Case of no subtype in renaming (AI12-0275)
end if;
when N_Discriminant_Specification =>
if Nkind (Discriminant_Type (N)) = N_Access_Definition then
return Null_Exclusion_Present (Discriminant_Type (N));
else
return Null_Exclusion_Present (N);
end if;
when N_Object_Declaration =>
if Nkind (Object_Definition (N)) = N_Access_Definition then
return Null_Exclusion_Present (Object_Definition (N));
else
return Null_Exclusion_Present (N);
end if;
when N_Parameter_Specification =>
if Nkind (Parameter_Type (N)) = N_Access_Definition then
return Null_Exclusion_Present (Parameter_Type (N))
or else Null_Exclusion_Present (N);
else
return Null_Exclusion_Present (N);
end if;
when others =>
return False;
end case;
end Has_Null_Exclusion;
------------------------
-- Has_Null_Extension --
------------------------
function Has_Null_Extension (T : Entity_Id) return Boolean is
B : constant Entity_Id := Base_Type (T);
Comps : Node_Id;
Ext : Node_Id;
begin
if Nkind (Parent (B)) = N_Full_Type_Declaration
and then Present (Record_Extension_Part (Type_Definition (Parent (B))))
then
Ext := Record_Extension_Part (Type_Definition (Parent (B)));
if Present (Ext) then
if Null_Present (Ext) then
return True;
else
Comps := Component_List (Ext);
-- The null component list is rewritten during analysis to
-- include the parent component. Any other component indicates
-- that the extension was not originally null.
return Null_Present (Comps)
or else No (Next (First (Component_Items (Comps))));
end if;
else
return False;
end if;
else
return False;
end if;
end Has_Null_Extension;
-------------------------
-- Has_Null_Refinement --
-------------------------
function Has_Null_Refinement (Id : Entity_Id) return Boolean is
Constits : Elist_Id;
begin
pragma Assert (Ekind (Id) = E_Abstract_State);
Constits := Refinement_Constituents (Id);
-- For a refinement to be null, the state's sole constituent must be a
-- null.
return
Present (Constits)
and then Nkind (Node (First_Elmt (Constits))) = N_Null;
end Has_Null_Refinement;
------------------------------------------
-- Has_Nonstatic_Class_Wide_Pre_Or_Post --
------------------------------------------
function Is_Prim_Of_Abst_Type_With_Nonstatic_CW_Pre_Post
(Subp : Entity_Id) return Boolean
is
Disp_Type : constant Entity_Id := Find_Dispatching_Type (Subp);
Prag : Node_Id;
Pragma_Arg : Node_Id;
begin
if Present (Disp_Type)
and then Is_Abstract_Type (Disp_Type)
and then Present (Contract (Subp))
then
Prag := Pre_Post_Conditions (Contract (Subp));
while Present (Prag) loop
if Pragma_Name (Prag) in Name_Precondition | Name_Postcondition
and then Class_Present (Prag)
then
Pragma_Arg :=
Nlists.First
(Pragma_Argument_Associations (Prag));
if not Is_Static_Expression (Expression (Pragma_Arg)) then
return True;
end if;
end if;
Prag := Next_Pragma (Prag);
end loop;
end if;
return False;
end Is_Prim_Of_Abst_Type_With_Nonstatic_CW_Pre_Post;
-------------------------------
-- Has_Overriding_Initialize --
-------------------------------
function Has_Overriding_Initialize (T : Entity_Id) return Boolean is
BT : constant Entity_Id := Base_Type (T);
P : Elmt_Id;
begin
if Is_Controlled (BT) then
if Is_RTU (Scope (BT), Ada_Finalization) then
return False;
elsif Present (Primitive_Operations (BT)) then
P := First_Elmt (Primitive_Operations (BT));
while Present (P) loop
declare
Init : constant Entity_Id := Node (P);
Formal : constant Entity_Id := First_Formal (Init);
begin
if Ekind (Init) = E_Procedure
and then Chars (Init) = Name_Initialize
and then Comes_From_Source (Init)
and then Present (Formal)
and then Etype (Formal) = BT
and then No (Next_Formal (Formal))
and then (Ada_Version < Ada_2012
or else not Null_Present (Parent (Init)))
then
return True;
end if;
end;
Next_Elmt (P);
end loop;
end if;
-- Here if type itself does not have a non-null Initialize operation:
-- check immediate ancestor.
if Is_Derived_Type (BT)
and then Has_Overriding_Initialize (Etype (BT))
then
return True;
end if;
end if;
return False;
end Has_Overriding_Initialize;
--------------------------------------
-- Has_Preelaborable_Initialization --
--------------------------------------
function Has_Preelaborable_Initialization
(E : Entity_Id;
Preelab_Init_Expr : Node_Id := Empty) return Boolean
is
Has_PE : Boolean;
procedure Check_Components (E : Entity_Id);
-- Check component/discriminant chain, sets Has_PE False if a component
-- or discriminant does not meet the preelaborable initialization rules.
function Type_Named_In_Preelab_Init_Expression
(Typ : Entity_Id;
Expr : Node_Id) return Boolean;
-- Returns True iff Typ'Preelaborable_Initialization occurs in Expr
-- (where Expr may be a conjunction of one or more P_I attributes).
----------------------
-- Check_Components --
----------------------
procedure Check_Components (E : Entity_Id) is
Ent : Entity_Id;
Exp : Node_Id;
begin
-- Loop through entities of record or protected type
Ent := E;
while Present (Ent) loop
-- We are interested only in components and discriminants
Exp := Empty;
case Ekind (Ent) is
when E_Component =>
-- Get default expression if any. If there is no declaration
-- node, it means we have an internal entity. The parent and
-- tag fields are examples of such entities. For such cases,
-- we just test the type of the entity.
if Present (Declaration_Node (Ent)) then
Exp := Expression (Declaration_Node (Ent));
end if;
when E_Discriminant =>
-- Note: for a renamed discriminant, the Declaration_Node
-- may point to the one from the ancestor, and have a
-- different expression, so use the proper attribute to
-- retrieve the expression from the derived constraint.
Exp := Discriminant_Default_Value (Ent);
when others =>
goto Check_Next_Entity;
end case;
-- A component has PI if it has no default expression and the
-- component type has PI.
if No (Exp) then
if not Has_Preelaborable_Initialization
(Etype (Ent), Preelab_Init_Expr)
then
Has_PE := False;
exit;
end if;
-- Require the default expression to be preelaborable
elsif not Is_Preelaborable_Construct (Exp) then
Has_PE := False;
exit;
end if;
<<Check_Next_Entity>>
Next_Entity (Ent);
end loop;
end Check_Components;
--------------------------------------
-- Type_Named_In_Preelab_Expression --
--------------------------------------
function Type_Named_In_Preelab_Init_Expression
(Typ : Entity_Id;
Expr : Node_Id) return Boolean
is
begin
-- Return True if Expr is a Preelaborable_Initialization attribute
-- and the prefix is a subtype that has the same type as Typ.
if Nkind (Expr) = N_Attribute_Reference
and then Attribute_Name (Expr) = Name_Preelaborable_Initialization
and then Is_Entity_Name (Prefix (Expr))
and then Base_Type (Entity (Prefix (Expr))) = Base_Type (Typ)
then
return True;
-- In the case where Expr is a conjunction, test whether either
-- operand is a Preelaborable_Initialization attribute whose prefix
-- has the same type as Typ, and return True if so.
elsif Nkind (Expr) = N_Op_And
and then
(Type_Named_In_Preelab_Init_Expression (Typ, Left_Opnd (Expr))
or else
Type_Named_In_Preelab_Init_Expression (Typ, Right_Opnd (Expr)))
then
return True;
-- Typ not named in a Preelaborable_Initialization attribute of Expr
else
return False;
end if;
end Type_Named_In_Preelab_Init_Expression;
-- Start of processing for Has_Preelaborable_Initialization
begin
-- Immediate return if already marked as known preelaborable init. This
-- covers types for which this function has already been called once
-- and returned True (in which case the result is cached), and also
-- types to which a pragma Preelaborable_Initialization applies.
if Known_To_Have_Preelab_Init (E) then
return True;
end if;
-- If the type is a subtype representing a generic actual type, then
-- test whether its base type has preelaborable initialization since
-- the subtype representing the actual does not inherit this attribute
-- from the actual or formal. (but maybe it should???)
if Is_Generic_Actual_Type (E) then
return Has_Preelaborable_Initialization (Base_Type (E));
end if;
-- All elementary types have preelaborable initialization
if Is_Elementary_Type (E) then
Has_PE := True;
-- Array types have PI if the component type has PI
elsif Is_Array_Type (E) then
Has_PE := Has_Preelaborable_Initialization
(Component_Type (E), Preelab_Init_Expr);
-- A derived type has preelaborable initialization if its parent type
-- has preelaborable initialization and (in the case of a derived record
-- extension) if the non-inherited components all have preelaborable
-- initialization. However, a user-defined controlled type with an
-- overriding Initialize procedure does not have preelaborable
-- initialization.
elsif Is_Derived_Type (E) then
-- When the rule of RM 10.2.1(11.8/5) applies, we presume a component
-- of a generic formal derived type has preelaborable initialization.
-- (See comment on spec of Has_Preelaborable_Initialization.)
if Is_Generic_Type (E)
and then Present (Preelab_Init_Expr)
and then
Type_Named_In_Preelab_Init_Expression (E, Preelab_Init_Expr)
then
return True;
end if;
-- If the derived type is a private extension then it doesn't have
-- preelaborable initialization.
if Ekind (Base_Type (E)) = E_Record_Type_With_Private then
return False;
end if;
-- First check whether ancestor type has preelaborable initialization
Has_PE := Has_Preelaborable_Initialization
(Etype (Base_Type (E)), Preelab_Init_Expr);
-- If OK, check extension components (if any)
if Has_PE and then Is_Record_Type (E) then
Check_Components (First_Entity (E));
end if;
-- Check specifically for 10.2.1(11.4/2) exception: a controlled type
-- with a user defined Initialize procedure does not have PI. If
-- the type is untagged, the control primitives come from a component
-- that has already been checked.
if Has_PE
and then Is_Controlled (E)
and then Is_Tagged_Type (E)
and then Has_Overriding_Initialize (E)
then
Has_PE := False;
end if;
-- Private types not derived from a type having preelaborable init and
-- that are not marked with pragma Preelaborable_Initialization do not
-- have preelaborable initialization.
elsif Is_Private_Type (E) then
-- When the rule of RM 10.2.1(11.8/5) applies, we presume a component
-- of a generic formal private type has preelaborable initialization.
-- (See comment on spec of Has_Preelaborable_Initialization.)
if Is_Generic_Type (E)
and then Present (Preelab_Init_Expr)
and then
Type_Named_In_Preelab_Init_Expression (E, Preelab_Init_Expr)
then
return True;
else
return False;
end if;
-- Record type has PI if it is non private and all components have PI
elsif Is_Record_Type (E) then
Has_PE := True;
Check_Components (First_Entity (E));
-- Protected types must not have entries, and components must meet
-- same set of rules as for record components.
elsif Is_Protected_Type (E) then
if Has_Entries (E) then
Has_PE := False;
else
Has_PE := True;
Check_Components (First_Entity (E));
Check_Components (First_Private_Entity (E));
end if;
-- Type System.Address always has preelaborable initialization
elsif Is_RTE (E, RE_Address) then
Has_PE := True;
-- In all other cases, type does not have preelaborable initialization
else
return False;
end if;
-- If type has preelaborable initialization, cache result
if Has_PE then
Set_Known_To_Have_Preelab_Init (E);
end if;
return Has_PE;
end Has_Preelaborable_Initialization;
----------------
-- Has_Prefix --
----------------
function Has_Prefix (N : Node_Id) return Boolean is
begin
return Nkind (N) in
N_Attribute_Reference | N_Expanded_Name | N_Explicit_Dereference |
N_Indexed_Component | N_Reference | N_Selected_Component |
N_Slice;
end Has_Prefix;
---------------------------
-- Has_Private_Component --
---------------------------
function Has_Private_Component (Type_Id : Entity_Id) return Boolean is
Btype : Entity_Id := Base_Type (Type_Id);
Component : Entity_Id;
begin
if Error_Posted (Type_Id)
or else Error_Posted (Btype)
then
return False;
end if;
if Is_Class_Wide_Type (Btype) then
Btype := Root_Type (Btype);
end if;
if Is_Private_Type (Btype) then
declare
UT : constant Entity_Id := Underlying_Type (Btype);
begin
if No (UT) then
if No (Full_View (Btype)) then
return not Is_Generic_Type (Btype)
and then
not Is_Generic_Type (Root_Type (Btype));
else
return not Is_Generic_Type (Root_Type (Full_View (Btype)));
end if;
else
return not Is_Frozen (UT) and then Has_Private_Component (UT);
end if;
end;
elsif Is_Array_Type (Btype) then
return Has_Private_Component (Component_Type (Btype));
elsif Is_Record_Type (Btype) then
Component := First_Component (Btype);
while Present (Component) loop
if Has_Private_Component (Etype (Component)) then
return True;
end if;
Next_Component (Component);
end loop;
return False;
elsif Is_Protected_Type (Btype)
and then Present (Corresponding_Record_Type (Btype))
then
return Has_Private_Component (Corresponding_Record_Type (Btype));
else
return False;
end if;
end Has_Private_Component;
--------------------------------
-- Has_Relaxed_Initialization --
--------------------------------
function Has_Relaxed_Initialization (E : Entity_Id) return Boolean is
function Denotes_Relaxed_Parameter
(Expr : Node_Id;
Param : Entity_Id)
return Boolean;
-- Returns True iff expression Expr denotes a formal parameter or
-- function Param (through its attribute Result).
-------------------------------
-- Denotes_Relaxed_Parameter --
-------------------------------
function Denotes_Relaxed_Parameter
(Expr : Node_Id;
Param : Entity_Id) return Boolean is
begin
if Nkind (Expr) in N_Identifier | N_Expanded_Name then
return Entity (Expr) = Param;
else
pragma Assert (Is_Attribute_Result (Expr));
return Entity (Prefix (Expr)) = Param;
end if;
end Denotes_Relaxed_Parameter;
-- Start of processing for Has_Relaxed_Initialization
begin
-- When analyzing, we checked all syntax legality rules for the aspect
-- Relaxed_Initialization, but didn't store the property anywhere (e.g.
-- as an Einfo flag). To query the property we look directly at the AST,
-- but now without any syntactic checks.
case Ekind (E) is
-- Abstract states have option Relaxed_Initialization
when E_Abstract_State =>
return Is_Relaxed_Initialization_State (E);
-- Constants have this aspect attached directly; for deferred
-- constants, the aspect is attached to the partial view.
when E_Constant =>
return Has_Aspect (E, Aspect_Relaxed_Initialization);
-- Variables have this aspect attached directly
when E_Variable =>
return Has_Aspect (E, Aspect_Relaxed_Initialization);
-- Types have this aspect attached directly (though we only allow it
-- to be specified for the first subtype). For private types, the
-- aspect is attached to the partial view.
when Type_Kind =>
pragma Assert (Is_First_Subtype (E));
return Has_Aspect (E, Aspect_Relaxed_Initialization);
-- Formal parameters and functions have the Relaxed_Initialization
-- aspect attached to the subprogram entity and must be listed in
-- the aspect expression.
when Formal_Kind
| E_Function
=>
declare
Subp_Id : Entity_Id;
Aspect_Expr : Node_Id;
Param_Expr : Node_Id;
Assoc : Node_Id;
begin
if Is_Formal (E) then
Subp_Id := Scope (E);
else
Subp_Id := E;
end if;
if Has_Aspect (Subp_Id, Aspect_Relaxed_Initialization) then
Aspect_Expr :=
Find_Value_Of_Aspect
(Subp_Id, Aspect_Relaxed_Initialization);
-- Aspect expression is either an aggregate with an optional
-- Boolean expression (which defaults to True), e.g.:
--
-- function F (X : Integer) return Integer
-- with Relaxed_Initialization => (X => True, F'Result);
if Nkind (Aspect_Expr) = N_Aggregate then
if Present (Component_Associations (Aspect_Expr)) then
Assoc := First (Component_Associations (Aspect_Expr));
while Present (Assoc) loop
if Denotes_Relaxed_Parameter
(First (Choices (Assoc)), E)
then
return
Is_True
(Static_Boolean (Expression (Assoc)));
end if;
Next (Assoc);
end loop;
end if;
Param_Expr := First (Expressions (Aspect_Expr));
while Present (Param_Expr) loop
if Denotes_Relaxed_Parameter (Param_Expr, E) then
return True;
end if;
Next (Param_Expr);
end loop;
return False;
-- or it is a single identifier, e.g.:
--
-- function F (X : Integer) return Integer
-- with Relaxed_Initialization => X;
else
return Denotes_Relaxed_Parameter (Aspect_Expr, E);
end if;
else
return False;
end if;
end;
when others =>
raise Program_Error;
end case;
end Has_Relaxed_Initialization;
----------------------
-- Has_Signed_Zeros --
----------------------
function Has_Signed_Zeros (E : Entity_Id) return Boolean is
begin
return Is_Floating_Point_Type (E) and then Signed_Zeros_On_Target;
end Has_Signed_Zeros;
------------------------------
-- Has_Significant_Contract --
------------------------------
function Has_Significant_Contract (Subp_Id : Entity_Id) return Boolean is
Subp_Nam : constant Name_Id := Chars (Subp_Id);
begin
-- _Finalizer procedure
if Subp_Nam = Name_uFinalizer then
return False;
-- _Postconditions procedure
elsif Subp_Nam = Name_uPostconditions then
return False;
-- Predicate function
elsif Ekind (Subp_Id) = E_Function
and then Is_Predicate_Function (Subp_Id)
then
return False;
-- TSS subprogram
elsif Get_TSS_Name (Subp_Id) /= TSS_Null then
return False;
else
return True;
end if;
end Has_Significant_Contract;
-----------------------------
-- Has_Static_Array_Bounds --
-----------------------------
function Has_Static_Array_Bounds (Typ : Node_Id) return Boolean is
All_Static : Boolean;
Dummy : Boolean;
begin
Examine_Array_Bounds (Typ, All_Static, Dummy);
return All_Static;
end Has_Static_Array_Bounds;
---------------------------------------
-- Has_Static_Non_Empty_Array_Bounds --
---------------------------------------
function Has_Static_Non_Empty_Array_Bounds (Typ : Node_Id) return Boolean is
All_Static : Boolean;
Has_Empty : Boolean;
begin
Examine_Array_Bounds (Typ, All_Static, Has_Empty);
return All_Static and not Has_Empty;
end Has_Static_Non_Empty_Array_Bounds;
----------------
-- Has_Stream --
----------------
function Has_Stream (T : Entity_Id) return Boolean is
E : Entity_Id;
begin
if No (T) then
return False;
elsif Is_RTE (Root_Type (T), RE_Root_Stream_Type) then
return True;
elsif Is_Array_Type (T) then
return Has_Stream (Component_Type (T));
elsif Is_Record_Type (T) then
E := First_Component (T);
while Present (E) loop
if Has_Stream (Etype (E)) then
return True;
else
Next_Component (E);
end if;
end loop;
return False;
elsif Is_Private_Type (T) then
return Has_Stream (Underlying_Type (T));
else
return False;
end if;
end Has_Stream;
----------------
-- Has_Suffix --
----------------
function Has_Suffix (E : Entity_Id; Suffix : Character) return Boolean is
begin
Get_Name_String (Chars (E));
return Name_Buffer (Name_Len) = Suffix;
end Has_Suffix;
----------------
-- Add_Suffix --
----------------
function Add_Suffix (E : Entity_Id; Suffix : Character) return Name_Id is
begin
Get_Name_String (Chars (E));
Add_Char_To_Name_Buffer (Suffix);
return Name_Find;
end Add_Suffix;
-------------------
-- Remove_Suffix --
-------------------
function Remove_Suffix (E : Entity_Id; Suffix : Character) return Name_Id is
begin
pragma Assert (Has_Suffix (E, Suffix));
Get_Name_String (Chars (E));
Name_Len := Name_Len - 1;
return Name_Find;
end Remove_Suffix;
----------------------------------
-- Replace_Null_By_Null_Address --
----------------------------------
procedure Replace_Null_By_Null_Address (N : Node_Id) is
procedure Replace_Null_Operand (Op : Node_Id; Other_Op : Node_Id);
-- Replace operand Op with a reference to Null_Address when the operand
-- denotes a null Address. Other_Op denotes the other operand.
--------------------------
-- Replace_Null_Operand --
--------------------------
procedure Replace_Null_Operand (Op : Node_Id; Other_Op : Node_Id) is
begin
-- Check the type of the complementary operand since the N_Null node
-- has not been decorated yet.
if Nkind (Op) = N_Null
and then Is_Descendant_Of_Address (Etype (Other_Op))
then
Rewrite (Op, New_Occurrence_Of (RTE (RE_Null_Address), Sloc (Op)));
end if;
end Replace_Null_Operand;
-- Start of processing for Replace_Null_By_Null_Address
begin
pragma Assert (Relaxed_RM_Semantics);
pragma Assert
(Nkind (N) in
N_Null | N_Op_Eq | N_Op_Ge | N_Op_Gt | N_Op_Le | N_Op_Lt | N_Op_Ne);
if Nkind (N) = N_Null then
Rewrite (N, New_Occurrence_Of (RTE (RE_Null_Address), Sloc (N)));
else
declare
L : constant Node_Id := Left_Opnd (N);
R : constant Node_Id := Right_Opnd (N);
begin
Replace_Null_Operand (L, Other_Op => R);
Replace_Null_Operand (R, Other_Op => L);
end;
end if;
end Replace_Null_By_Null_Address;
--------------------------
-- Has_Tagged_Component --
--------------------------
function Has_Tagged_Component (Typ : Entity_Id) return Boolean is
Comp : Entity_Id;
begin
if Is_Private_Type (Typ) and then Present (Underlying_Type (Typ)) then
return Has_Tagged_Component (Underlying_Type (Typ));
elsif Is_Array_Type (Typ) then
return Has_Tagged_Component (Component_Type (Typ));
elsif Is_Tagged_Type (Typ) then
return True;
elsif Is_Record_Type (Typ) then
Comp := First_Component (Typ);
while Present (Comp) loop
if Has_Tagged_Component (Etype (Comp)) then
return True;
end if;
Next_Component (Comp);
end loop;
return False;
else
return False;
end if;
end Has_Tagged_Component;
--------------------------------------------
-- Has_Unconstrained_Access_Discriminants --
--------------------------------------------
function Has_Unconstrained_Access_Discriminants
(Subtyp : Entity_Id) return Boolean
is
Discr : Entity_Id;
begin
if Has_Discriminants (Subtyp)
and then not Is_Constrained (Subtyp)
then
Discr := First_Discriminant (Subtyp);
while Present (Discr) loop
if Ekind (Etype (Discr)) = E_Anonymous_Access_Type then
return True;
end if;
Next_Discriminant (Discr);
end loop;
end if;
return False;
end Has_Unconstrained_Access_Discriminants;
-----------------------------
-- Has_Undefined_Reference --
-----------------------------
function Has_Undefined_Reference (Expr : Node_Id) return Boolean is
Has_Undef_Ref : Boolean := False;
-- Flag set when expression Expr contains at least one undefined
-- reference.
function Is_Undefined_Reference (N : Node_Id) return Traverse_Result;
-- Determine whether N denotes a reference and if it does, whether it is
-- undefined.
----------------------------
-- Is_Undefined_Reference --
----------------------------
function Is_Undefined_Reference (N : Node_Id) return Traverse_Result is
begin
if Is_Entity_Name (N)
and then Present (Entity (N))
and then Entity (N) = Any_Id
then
Has_Undef_Ref := True;
return Abandon;
end if;
return OK;
end Is_Undefined_Reference;
procedure Find_Undefined_References is
new Traverse_Proc (Is_Undefined_Reference);
-- Start of processing for Has_Undefined_Reference
begin
Find_Undefined_References (Expr);
return Has_Undef_Ref;
end Has_Undefined_Reference;
----------------------------
-- Has_Volatile_Component --
----------------------------
function Has_Volatile_Component (Typ : Entity_Id) return Boolean is
Comp : Entity_Id;
begin
if Has_Volatile_Components (Typ) then
return True;
elsif Is_Array_Type (Typ) then
return Is_Volatile (Component_Type (Typ));
elsif Is_Record_Type (Typ) then
Comp := First_Component (Typ);
while Present (Comp) loop
if Is_Volatile_Object_Ref (Comp) then
return True;
end if;
Next_Component (Comp);
end loop;
end if;
return False;
end Has_Volatile_Component;
-------------------------
-- Implementation_Kind --
-------------------------
function Implementation_Kind (Subp : Entity_Id) return Name_Id is
Impl_Prag : constant Node_Id := Get_Rep_Pragma (Subp, Name_Implemented);
Arg : Node_Id;
begin
pragma Assert (Present (Impl_Prag));
Arg := Last (Pragma_Argument_Associations (Impl_Prag));
return Chars (Get_Pragma_Arg (Arg));
end Implementation_Kind;
--------------------------
-- Implements_Interface --
--------------------------
function Implements_Interface
(Typ_Ent : Entity_Id;
Iface_Ent : Entity_Id;
Exclude_Parents : Boolean := False) return Boolean
is
Ifaces_List : Elist_Id;
Elmt : Elmt_Id;
Iface : Entity_Id := Base_Type (Iface_Ent);
Typ : Entity_Id := Base_Type (Typ_Ent);
begin
if Is_Class_Wide_Type (Typ) then
Typ := Root_Type (Typ);
end if;
if not Has_Interfaces (Typ) then
return False;
end if;
if Is_Class_Wide_Type (Iface) then
Iface := Root_Type (Iface);
end if;
Collect_Interfaces (Typ, Ifaces_List);
Elmt := First_Elmt (Ifaces_List);
while Present (Elmt) loop
if Is_Ancestor (Node (Elmt), Typ, Use_Full_View => True)
and then Exclude_Parents
then
null;
elsif Node (Elmt) = Iface then
return True;
end if;
Next_Elmt (Elmt);
end loop;
return False;
end Implements_Interface;
--------------------------------
-- Implicitly_Designated_Type --
--------------------------------
function Implicitly_Designated_Type (Typ : Entity_Id) return Entity_Id is
Desig : constant Entity_Id := Designated_Type (Typ);
begin
-- An implicit dereference is a legal occurrence of an incomplete type
-- imported through a limited_with clause, if the full view is visible.
if Is_Incomplete_Type (Desig)
and then From_Limited_With (Desig)
and then not From_Limited_With (Scope (Desig))
and then
(Is_Immediately_Visible (Scope (Desig))
or else
(Is_Child_Unit (Scope (Desig))
and then Is_Visible_Lib_Unit (Scope (Desig))))
then
return Available_View (Desig);
else
return Desig;
end if;
end Implicitly_Designated_Type;
------------------------------------
-- In_Assertion_Expression_Pragma --
------------------------------------
function In_Assertion_Expression_Pragma (N : Node_Id) return Boolean is
Par : Node_Id;
Prag : Node_Id := Empty;
begin
-- Climb the parent chain looking for an enclosing pragma
Par := N;
while Present (Par) loop
if Nkind (Par) = N_Pragma then
Prag := Par;
exit;
-- Precondition-like pragmas are expanded into if statements, check
-- the original node instead.
elsif Nkind (Original_Node (Par)) = N_Pragma then
Prag := Original_Node (Par);
exit;
-- The expansion of attribute 'Old generates a constant to capture
-- the result of the prefix. If the parent traversal reaches
-- one of these constants, then the node technically came from a
-- postcondition-like pragma. Note that the Ekind is not tested here
-- because N may be the expression of an object declaration which is
-- currently being analyzed. Such objects carry Ekind of E_Void.
elsif Nkind (Par) = N_Object_Declaration
and then Constant_Present (Par)
and then Stores_Attribute_Old_Prefix (Defining_Entity (Par))
then
return True;
-- Prevent the search from going too far
elsif Is_Body_Or_Package_Declaration (Par) then
return False;
end if;
Par := Parent (Par);
end loop;
return
Present (Prag)
and then Assertion_Expression_Pragma (Get_Pragma_Id (Prag));
end In_Assertion_Expression_Pragma;
-------------------
-- In_Check_Node --
-------------------
function In_Check_Node (N : Node_Id) return Boolean is
Par : Node_Id := Parent (N);
begin
while Present (Par) loop
if Nkind (Par) in N_Raise_xxx_Error then
return True;
-- Prevent the search from going too far
elsif Is_Body_Or_Package_Declaration (Par) then
return False;
else
Par := Parent (Par);
end if;
end loop;
return False;
end In_Check_Node;
-------------------------------
-- In_Generic_Formal_Package --
-------------------------------
function In_Generic_Formal_Package (E : Entity_Id) return Boolean is
Par : Node_Id;
begin
Par := Parent (E);
while Present (Par) loop
if Nkind (Par) = N_Formal_Package_Declaration
or else Nkind (Original_Node (Par)) = N_Formal_Package_Declaration
then
return True;
end if;
Par := Parent (Par);
end loop;
return False;
end In_Generic_Formal_Package;
----------------------
-- In_Generic_Scope --
----------------------
function In_Generic_Scope (E : Entity_Id) return Boolean is
S : Entity_Id;
begin
S := Scope (E);
while Present (S) and then S /= Standard_Standard loop
if Is_Generic_Unit (S) then
return True;
end if;
S := Scope (S);
end loop;
return False;
end In_Generic_Scope;
-----------------
-- In_Instance --
-----------------
function In_Instance return Boolean is
Curr_Unit : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
S : Entity_Id;
begin
S := Current_Scope;
while Present (S) and then S /= Standard_Standard loop
if Is_Generic_Instance (S) then
-- A child instance is always compiled in the context of a parent
-- instance. Nevertheless, its actuals must not be analyzed in an
-- instance context. We detect this case by examining the current
-- compilation unit, which must be a child instance, and checking
-- that it has not been analyzed yet.
if Is_Child_Unit (Curr_Unit)
and then Nkind (Unit (Cunit (Current_Sem_Unit))) =
N_Package_Instantiation
and then Ekind (Curr_Unit) = E_Void
then
return False;
else
return True;
end if;
end if;
S := Scope (S);
end loop;
return False;
end In_Instance;
----------------------
-- In_Instance_Body --
----------------------
function In_Instance_Body return Boolean is
S : Entity_Id;
begin
S := Current_Scope;
while Present (S) and then S /= Standard_Standard loop
if Ekind (S) in E_Function | E_Procedure
and then Is_Generic_Instance (S)
then
return True;
elsif Ekind (S) = E_Package
and then In_Package_Body (S)
and then Is_Generic_Instance (S)
then
return True;
end if;
S := Scope (S);
end loop;
return False;
end In_Instance_Body;
-----------------------------
-- In_Instance_Not_Visible --
-----------------------------
function In_Instance_Not_Visible return Boolean is
S : Entity_Id;
begin
S := Current_Scope;
while Present (S) and then S /= Standard_Standard loop
if Ekind (S) in E_Function | E_Procedure
and then Is_Generic_Instance (S)
then
return True;
elsif Ekind (S) = E_Package
and then (In_Package_Body (S) or else In_Private_Part (S))
and then Is_Generic_Instance (S)
then
return True;
end if;
S := Scope (S);
end loop;
return False;
end In_Instance_Not_Visible;
------------------------------
-- In_Instance_Visible_Part --
------------------------------
function In_Instance_Visible_Part
(Id : Entity_Id := Current_Scope) return Boolean
is
Inst : Entity_Id;
begin
Inst := Id;
while Present (Inst) and then Inst /= Standard_Standard loop
if Ekind (Inst) = E_Package
and then Is_Generic_Instance (Inst)
and then not In_Package_Body (Inst)
and then not In_Private_Part (Inst)
then
return True;
end if;
Inst := Scope (Inst);
end loop;
return False;
end In_Instance_Visible_Part;
---------------------
-- In_Package_Body --
---------------------
function In_Package_Body return Boolean is
S : Entity_Id;
begin
S := Current_Scope;
while Present (S) and then S /= Standard_Standard loop
if Ekind (S) = E_Package and then In_Package_Body (S) then
return True;
else
S := Scope (S);
end if;
end loop;
return False;
end In_Package_Body;
--------------------------
-- In_Pragma_Expression --
--------------------------
function In_Pragma_Expression (N : Node_Id; Nam : Name_Id) return Boolean is
P : Node_Id;
begin
P := Parent (N);
loop
if No (P) then
return False;
elsif Nkind (P) = N_Pragma and then Pragma_Name (P) = Nam then
return True;
else
P := Parent (P);
end if;
end loop;
end In_Pragma_Expression;
---------------------------
-- In_Pre_Post_Condition --
---------------------------
function In_Pre_Post_Condition
(N : Node_Id; Class_Wide_Only : Boolean := False) return Boolean
is
Par : Node_Id;
Prag : Node_Id := Empty;
Prag_Id : Pragma_Id;
begin
-- Climb the parent chain looking for an enclosing pragma
Par := N;
while Present (Par) loop
if Nkind (Par) = N_Pragma then
Prag := Par;
exit;
-- Prevent the search from going too far
elsif Is_Body_Or_Package_Declaration (Par) then
exit;
end if;
Par := Parent (Par);
end loop;
if Present (Prag) then
Prag_Id := Get_Pragma_Id (Prag);
if Class_Wide_Only then
return
Prag_Id = Pragma_Post_Class
or else Prag_Id = Pragma_Pre_Class
or else (Class_Present (Prag)
and then (Prag_Id = Pragma_Post
or else Prag_Id = Pragma_Postcondition
or else Prag_Id = Pragma_Pre
or else Prag_Id = Pragma_Precondition));
else
return
Prag_Id = Pragma_Post
or else Prag_Id = Pragma_Post_Class
or else Prag_Id = Pragma_Postcondition
or else Prag_Id = Pragma_Pre
or else Prag_Id = Pragma_Pre_Class
or else Prag_Id = Pragma_Precondition;
end if;
-- Otherwise the node is not enclosed by a pre/postcondition pragma
else
return False;
end if;
end In_Pre_Post_Condition;
------------------------------
-- In_Quantified_Expression --
------------------------------
function In_Quantified_Expression (N : Node_Id) return Boolean is
P : Node_Id;
begin
P := Parent (N);
loop
if No (P) then
return False;
elsif Nkind (P) = N_Quantified_Expression then
return True;
else
P := Parent (P);
end if;
end loop;
end In_Quantified_Expression;
-------------------------------------
-- In_Reverse_Storage_Order_Object --
-------------------------------------
function In_Reverse_Storage_Order_Object (N : Node_Id) return Boolean is
Pref : Node_Id;
Btyp : Entity_Id := Empty;
begin
-- Climb up indexed components
Pref := N;
loop
case Nkind (Pref) is
when N_Selected_Component =>
Pref := Prefix (Pref);
exit;
when N_Indexed_Component =>
Pref := Prefix (Pref);
when others =>
Pref := Empty;
exit;
end case;
end loop;
if Present (Pref) then
Btyp := Base_Type (Etype (Pref));
end if;
return Present (Btyp)
and then (Is_Record_Type (Btyp) or else Is_Array_Type (Btyp))
and then Reverse_Storage_Order (Btyp);
end In_Reverse_Storage_Order_Object;
------------------------------
-- In_Same_Declarative_Part --
------------------------------
function In_Same_Declarative_Part
(Context : Node_Id;
N : Node_Id) return Boolean
is
Cont : Node_Id := Context;
Nod : Node_Id;
begin
if Nkind (Cont) = N_Compilation_Unit_Aux then
Cont := Parent (Cont);
end if;
Nod := Parent (N);
while Present (Nod) loop
if Nod = Cont then
return True;
elsif Nkind (Nod) in N_Accept_Statement
| N_Block_Statement
| N_Compilation_Unit
| N_Entry_Body
| N_Package_Body
| N_Package_Declaration
| N_Protected_Body
| N_Subprogram_Body
| N_Task_Body
then
return False;
elsif Nkind (Nod) = N_Subunit then
Nod := Corresponding_Stub (Nod);
else
Nod := Parent (Nod);
end if;
end loop;
return False;
end In_Same_Declarative_Part;
--------------------------------------
-- In_Subprogram_Or_Concurrent_Unit --
--------------------------------------
function In_Subprogram_Or_Concurrent_Unit return Boolean is
E : Entity_Id;
K : Entity_Kind;
begin
-- Use scope chain to check successively outer scopes
E := Current_Scope;
loop
K := Ekind (E);
if K in Subprogram_Kind
or else K in Concurrent_Kind
or else K in Generic_Subprogram_Kind
then
return True;
elsif E = Standard_Standard then
return False;
end if;
E := Scope (E);
end loop;
end In_Subprogram_Or_Concurrent_Unit;
----------------
-- In_Subtree --
----------------
function In_Subtree (N : Node_Id; Root : Node_Id) return Boolean is
Curr : Node_Id;
begin
Curr := N;
while Present (Curr) loop
if Curr = Root then
return True;
end if;
Curr := Parent (Curr);
end loop;
return False;
end In_Subtree;
----------------
-- In_Subtree --
----------------
function In_Subtree
(N : Node_Id;
Root1 : Node_Id;
Root2 : Node_Id) return Boolean
is
Curr : Node_Id;
begin
Curr := N;
while Present (Curr) loop
if Curr = Root1 or else Curr = Root2 then
return True;
end if;
Curr := Parent (Curr);
end loop;
return False;
end In_Subtree;
---------------------
-- In_Return_Value --
---------------------
function In_Return_Value (Expr : Node_Id) return Boolean is
Par : Node_Id;
Prev_Par : Node_Id;
Pre : Node_Id;
In_Function_Call : Boolean := False;
begin
-- Move through parent nodes to determine if Expr contributes to the
-- return value of the current subprogram.
Par := Expr;
Prev_Par := Empty;
while Present (Par) loop
case Nkind (Par) is
-- Ignore ranges and they don't contribute to the result
when N_Range =>
return False;
-- An object declaration whose parent is an extended return
-- statement is a return object.
when N_Object_Declaration =>
if Present (Parent (Par))
and then Nkind (Parent (Par)) = N_Extended_Return_Statement
then
return True;
end if;
-- We hit a simple return statement, so we know we are in one
when N_Simple_Return_Statement =>
return True;
-- Only include one nexting level of function calls
when N_Function_Call =>
if not In_Function_Call then
In_Function_Call := True;
-- When the function return type has implicit dereference
-- specified we know it cannot directly contribute to the
-- return value.
if Present (Etype (Par))
and then Has_Implicit_Dereference
(Get_Full_View (Etype (Par)))
then
return False;
end if;
else
return False;
end if;
-- Check if we are on the right-hand side of an assignment
-- statement to a return object.
-- This is not specified in the RM ???
when N_Assignment_Statement =>
if Prev_Par = Name (Par) then
return False;
end if;
Pre := Name (Par);
while Present (Pre) loop
if Is_Entity_Name (Pre)
and then Is_Return_Object (Entity (Pre))
then
return True;
end if;
exit when Nkind (Pre) not in N_Selected_Component
| N_Indexed_Component
| N_Slice;
Pre := Prefix (Pre);
end loop;
-- Otherwise, we hit a master which was not relevant
when others =>
if Is_Master (Par) then
return False;
end if;
end case;
-- Iterate up to the next parent, keeping track of the previous one
Prev_Par := Par;
Par := Parent (Par);
end loop;
return False;
end In_Return_Value;
---------------------
-- In_Visible_Part --
---------------------
function In_Visible_Part (Scope_Id : Entity_Id) return Boolean is
begin
return Is_Package_Or_Generic_Package (Scope_Id)
and then In_Open_Scopes (Scope_Id)
and then not In_Package_Body (Scope_Id)
and then not In_Private_Part (Scope_Id);
end In_Visible_Part;
-----------------------------
-- In_While_Loop_Condition --
-----------------------------
function In_While_Loop_Condition (N : Node_Id) return Boolean is
Prev : Node_Id := N;
P : Node_Id := Parent (N);
-- P and Prev will be used for traversing the AST, while maintaining an
-- invariant that P = Parent (Prev).
begin
loop
if No (P) then
return False;
elsif Nkind (P) = N_Iteration_Scheme
and then Prev = Condition (P)
then
return True;
else
Prev := P;
P := Parent (P);
end if;
end loop;
end In_While_Loop_Condition;
--------------------------------
-- Incomplete_Or_Partial_View --
--------------------------------
function Incomplete_Or_Partial_View (Id : Entity_Id) return Entity_Id is
S : constant Entity_Id := Scope (Id);
function Inspect_Decls
(Decls : List_Id;
Taft : Boolean := False) return Entity_Id;
-- Check whether a declarative region contains the incomplete or partial
-- view of Id.
-------------------
-- Inspect_Decls --
-------------------
function Inspect_Decls
(Decls : List_Id;
Taft : Boolean := False) return Entity_Id
is
Decl : Node_Id;
Match : Node_Id;
begin
Decl := First (Decls);
while Present (Decl) loop
Match := Empty;
-- The partial view of a Taft-amendment type is an incomplete
-- type.
if Taft then
if Nkind (Decl) = N_Incomplete_Type_Declaration then
Match := Defining_Identifier (Decl);
end if;
-- Otherwise look for a private type whose full view matches the
-- input type. Note that this checks full_type_declaration nodes
-- to account for derivations from a private type where the type
-- declaration hold the partial view and the full view is an
-- itype.
elsif Nkind (Decl) in N_Full_Type_Declaration
| N_Private_Extension_Declaration
| N_Private_Type_Declaration
then
Match := Defining_Identifier (Decl);
end if;
-- Guard against unanalyzed entities
if Present (Match)
and then Is_Type (Match)
and then Present (Full_View (Match))
and then Full_View (Match) = Id
then
return Match;
end if;
Next (Decl);
end loop;
return Empty;
end Inspect_Decls;
-- Local variables
Prev : Entity_Id;
-- Start of processing for Incomplete_Or_Partial_View
begin
-- Deferred constant or incomplete type case
Prev := Current_Entity (Id);
while Present (Prev) loop
exit when Scope (Prev) = S;
Prev := Homonym (Prev);
end loop;
if Present (Prev)
and then (Is_Incomplete_Type (Prev) or else Ekind (Prev) = E_Constant)
and then Present (Full_View (Prev))
and then Full_View (Prev) = Id
then
return Prev;
end if;
-- Private or Taft amendment type case
if Present (S) and then Is_Package_Or_Generic_Package (S) then
declare
Pkg_Decl : constant Node_Id := Package_Specification (S);
begin
-- It is knows that Typ has a private view, look for it in the
-- visible declarations of the enclosing scope. A special case
-- of this is when the two views have been exchanged - the full
-- appears earlier than the private.
if Has_Private_Declaration (Id) then
Prev := Inspect_Decls (Visible_Declarations (Pkg_Decl));
-- Exchanged view case, look in the private declarations
if No (Prev) then
Prev := Inspect_Decls (Private_Declarations (Pkg_Decl));
end if;
return Prev;
-- Otherwise if this is the package body, then Typ is a potential
-- Taft amendment type. The incomplete view should be located in
-- the private declarations of the enclosing scope.
elsif In_Package_Body (S) then
return Inspect_Decls (Private_Declarations (Pkg_Decl), True);
end if;
end;
end if;
-- The type has no incomplete or private view
return Empty;
end Incomplete_Or_Partial_View;
---------------------------------------
-- Incomplete_View_From_Limited_With --
---------------------------------------
function Incomplete_View_From_Limited_With
(Typ : Entity_Id) return Entity_Id
is
begin
-- It might make sense to make this an attribute in Einfo, and set it
-- in Sem_Ch10 in Build_Shadow_Entity. However, we're running short on
-- slots for new attributes, and it seems a bit simpler to just search
-- the Limited_View (if it exists) for an incomplete type whose
-- Non_Limited_View is Typ.
if Ekind (Scope (Typ)) = E_Package
and then Present (Limited_View (Scope (Typ)))
then
declare
Ent : Entity_Id := First_Entity (Limited_View (Scope (Typ)));
begin
while Present (Ent) loop
if Is_Incomplete_Type (Ent)
and then Non_Limited_View (Ent) = Typ
then
return Ent;
end if;
Next_Entity (Ent);
end loop;
end;
end if;
return Typ;
end Incomplete_View_From_Limited_With;
----------------------------------
-- Indexed_Component_Bit_Offset --
----------------------------------
function Indexed_Component_Bit_Offset (N : Node_Id) return Uint is
Exp : constant Node_Id := First (Expressions (N));
Typ : constant Entity_Id := Etype (Prefix (N));
Off : constant Uint := Component_Size (Typ);
Ind : Node_Id;
begin
-- Return early if the component size is not known or variable
if No (Off) or else Off < Uint_0 then
return No_Uint;
end if;
-- Deal with the degenerate case of an empty component
if Off = Uint_0 then
return Off;
end if;
-- Check that both the index value and the low bound are known
if not Compile_Time_Known_Value (Exp) then
return No_Uint;
end if;
Ind := First_Index (Typ);
if No (Ind) then
return No_Uint;
end if;
-- Do not attempt to compute offsets within multi-dimensional arrays
if Present (Next_Index (Ind)) then
return No_Uint;
end if;
if Nkind (Ind) = N_Subtype_Indication then
Ind := Constraint (Ind);
if Nkind (Ind) = N_Range_Constraint then
Ind := Range_Expression (Ind);
end if;
end if;
if Nkind (Ind) /= N_Range
or else not Compile_Time_Known_Value (Low_Bound (Ind))
then
return No_Uint;
end if;
-- Return the scaled offset
return Off * (Expr_Value (Exp) - Expr_Value (Low_Bound (Ind)));
end Indexed_Component_Bit_Offset;
-----------------------------
-- Inherit_Predicate_Flags --
-----------------------------
procedure Inherit_Predicate_Flags (Subt, Par : Entity_Id) is
begin
if Ada_Version < Ada_2012
or else Present (Predicate_Function (Subt))
then
return;
end if;
Set_Has_Predicates (Subt, Has_Predicates (Par));
Set_Has_Static_Predicate_Aspect
(Subt, Has_Static_Predicate_Aspect (Par));
Set_Has_Dynamic_Predicate_Aspect
(Subt, Has_Dynamic_Predicate_Aspect (Par));
-- A named subtype does not inherit the predicate function of its
-- parent but an itype declared for a loop index needs the discrete
-- predicate information of its parent to execute the loop properly.
-- A non-discrete type may has a static predicate (for example True)
-- but has no static_discrete_predicate.
if Is_Itype (Subt) and then Present (Predicate_Function (Par)) then
Set_Subprograms_For_Type (Subt, Subprograms_For_Type (Par));
if Has_Static_Predicate (Par) and then Is_Discrete_Type (Par) then
Set_Static_Discrete_Predicate
(Subt, Static_Discrete_Predicate (Par));
end if;
end if;
end Inherit_Predicate_Flags;
----------------------------
-- Inherit_Rep_Item_Chain --
----------------------------
procedure Inherit_Rep_Item_Chain (Typ : Entity_Id; From_Typ : Entity_Id) is
Item : Node_Id;
Next_Item : Node_Id;
begin
-- There are several inheritance scenarios to consider depending on
-- whether both types have rep item chains and whether the destination
-- type already inherits part of the source type's rep item chain.
-- 1) The source type lacks a rep item chain
-- From_Typ ---> Empty
--
-- Typ --------> Item (or Empty)
-- In this case inheritance cannot take place because there are no items
-- to inherit.
-- 2) The destination type lacks a rep item chain
-- From_Typ ---> Item ---> ...
--
-- Typ --------> Empty
-- Inheritance takes place by setting the First_Rep_Item of the
-- destination type to the First_Rep_Item of the source type.
-- From_Typ ---> Item ---> ...
-- ^
-- Typ -----------+
-- 3.1) Both source and destination types have at least one rep item.
-- The destination type does NOT inherit a rep item from the source
-- type.
-- From_Typ ---> Item ---> Item
--
-- Typ --------> Item ---> Item
-- Inheritance takes place by setting the Next_Rep_Item of the last item
-- of the destination type to the First_Rep_Item of the source type.
-- From_Typ -------------------> Item ---> Item
-- ^
-- Typ --------> Item ---> Item --+
-- 3.2) Both source and destination types have at least one rep item.
-- The destination type DOES inherit part of the rep item chain of the
-- source type.
-- From_Typ ---> Item ---> Item ---> Item
-- ^
-- Typ --------> Item ------+
-- This rare case arises when the full view of a private extension must
-- inherit the rep item chain from the full view of its parent type and
-- the full view of the parent type contains extra rep items. Currently
-- only invariants may lead to such form of inheritance.
-- type From_Typ is tagged private
-- with Type_Invariant'Class => Item_2;
-- type Typ is new From_Typ with private
-- with Type_Invariant => Item_4;
-- At this point the rep item chains contain the following items
-- From_Typ -----------> Item_2 ---> Item_3
-- ^
-- Typ --------> Item_4 --+
-- The full views of both types may introduce extra invariants
-- type From_Typ is tagged null record
-- with Type_Invariant => Item_1;
-- type Typ is new From_Typ with null record;
-- The full view of Typ would have to inherit any new rep items added to
-- the full view of From_Typ.
-- From_Typ -----------> Item_1 ---> Item_2 ---> Item_3
-- ^
-- Typ --------> Item_4 --+
-- To achieve this form of inheritance, the destination type must first
-- sever the link between its own rep chain and that of the source type,
-- then inheritance 3.1 takes place.
-- Case 1: The source type lacks a rep item chain
if No (First_Rep_Item (From_Typ)) then
return;
-- Case 2: The destination type lacks a rep item chain
elsif No (First_Rep_Item (Typ)) then
Set_First_Rep_Item (Typ, First_Rep_Item (From_Typ));
-- Case 3: Both the source and destination types have at least one rep
-- item. Traverse the rep item chain of the destination type to find the
-- last rep item.
else
Item := Empty;
Next_Item := First_Rep_Item (Typ);
while Present (Next_Item) loop
-- Detect a link between the destination type's rep chain and that
-- of the source type. There are two possibilities:
-- Variant 1
-- Next_Item
-- V
-- From_Typ ---> Item_1 --->
-- ^
-- Typ -----------+
--
-- Item is Empty
-- Variant 2
-- Next_Item
-- V
-- From_Typ ---> Item_1 ---> Item_2 --->
-- ^
-- Typ --------> Item_3 ------+
-- ^
-- Item
if Present_In_Rep_Item (From_Typ, Next_Item) then
exit;
end if;
Item := Next_Item;
Next_Item := Next_Rep_Item (Next_Item);
end loop;
-- Inherit the source type's rep item chain
if Present (Item) then
Set_Next_Rep_Item (Item, First_Rep_Item (From_Typ));
else
Set_First_Rep_Item (Typ, First_Rep_Item (From_Typ));
end if;
end if;
end Inherit_Rep_Item_Chain;
------------------------------------
-- Inherits_From_Tagged_Full_View --
------------------------------------
function Inherits_From_Tagged_Full_View (Typ : Entity_Id) return Boolean is
begin
return Is_Private_Type (Typ)
and then Present (Full_View (Typ))
and then Is_Private_Type (Full_View (Typ))
and then not Is_Tagged_Type (Full_View (Typ))
and then Present (Underlying_Type (Full_View (Typ)))
and then Is_Tagged_Type (Underlying_Type (Full_View (Typ)));
end Inherits_From_Tagged_Full_View;
---------------------------------
-- Insert_Explicit_Dereference --
---------------------------------
procedure Insert_Explicit_Dereference (N : Node_Id) is
New_Prefix : constant Node_Id := Relocate_Node (N);
Ent : Entity_Id := Empty;
Pref : Node_Id := Empty;
I : Interp_Index;
It : Interp;
T : Entity_Id;
begin
Save_Interps (N, New_Prefix);
Rewrite (N,
Make_Explicit_Dereference (Sloc (Parent (N)),
Prefix => New_Prefix));
Set_Etype (N, Designated_Type (Etype (New_Prefix)));
if Is_Overloaded (New_Prefix) then
-- The dereference is also overloaded, and its interpretations are
-- the designated types of the interpretations of the original node.
Set_Etype (N, Any_Type);
Get_First_Interp (New_Prefix, I, It);
while Present (It.Nam) loop
T := It.Typ;
if Is_Access_Type (T) then
Add_One_Interp (N, Designated_Type (T), Designated_Type (T));
end if;
Get_Next_Interp (I, It);
end loop;
else
-- Prefix is unambiguous: mark the original prefix (which might
-- Come_From_Source) as a reference, since the new (relocated) one
-- won't be taken into account.
if Is_Entity_Name (New_Prefix) then
Ent := Entity (New_Prefix);
Pref := New_Prefix;
-- For a retrieval of a subcomponent of some composite object,
-- retrieve the ultimate entity if there is one.
elsif Nkind (New_Prefix) in N_Selected_Component | N_Indexed_Component
then
Pref := Prefix (New_Prefix);
while Present (Pref)
and then Nkind (Pref) in
N_Selected_Component | N_Indexed_Component
loop
Pref := Prefix (Pref);
end loop;
if Present (Pref) and then Is_Entity_Name (Pref) then
Ent := Entity (Pref);
end if;
end if;
-- Place the reference on the entity node
if Present (Ent) then
Generate_Reference (Ent, Pref);
end if;
end if;
end Insert_Explicit_Dereference;
------------------------------------------
-- Inspect_Deferred_Constant_Completion --
------------------------------------------
procedure Inspect_Deferred_Constant_Completion (Decls : List_Id) is
Decl : Node_Id;
begin
Decl := First (Decls);
while Present (Decl) loop
-- Deferred constant signature
if Nkind (Decl) = N_Object_Declaration
and then Constant_Present (Decl)
and then No (Expression (Decl))
-- No need to check internally generated constants
and then Comes_From_Source (Decl)
-- The constant is not completed. A full object declaration or a
-- pragma Import complete a deferred constant.
and then not Has_Completion (Defining_Identifier (Decl))
then
Error_Msg_N
("constant declaration requires initialization expression",
Defining_Identifier (Decl));
end if;
Next (Decl);
end loop;
end Inspect_Deferred_Constant_Completion;
-------------------------------
-- Install_Elaboration_Model --
-------------------------------
procedure Install_Elaboration_Model (Unit_Id : Entity_Id) is
function Find_Elaboration_Checks_Pragma (L : List_Id) return Node_Id;
-- Try to find pragma Elaboration_Checks in arbitrary list L. Return
-- Empty if there is no such pragma.
------------------------------------
-- Find_Elaboration_Checks_Pragma --
------------------------------------
function Find_Elaboration_Checks_Pragma (L : List_Id) return Node_Id is
Item : Node_Id;
begin
Item := First (L);
while Present (Item) loop
if Nkind (Item) = N_Pragma
and then Pragma_Name (Item) = Name_Elaboration_Checks
then
return Item;
end if;
Next (Item);
end loop;
return Empty;
end Find_Elaboration_Checks_Pragma;
-- Local variables
Args : List_Id;
Model : Node_Id;
Prag : Node_Id;
Unit : Node_Id;
-- Start of processing for Install_Elaboration_Model
begin
-- Nothing to do when the unit does not exist
if No (Unit_Id) then
return;
end if;
Unit := Parent (Unit_Declaration_Node (Unit_Id));
-- Nothing to do when the unit is not a library unit
if Nkind (Unit) /= N_Compilation_Unit then
return;
end if;
Prag := Find_Elaboration_Checks_Pragma (Context_Items (Unit));
-- The compilation unit is subject to pragma Elaboration_Checks. Set the
-- elaboration model as specified by the pragma.
if Present (Prag) then
Args := Pragma_Argument_Associations (Prag);
-- Guard against an illegal pragma. The sole argument must be an
-- identifier which specifies either Dynamic or Static model.
if Present (Args) then
Model := Get_Pragma_Arg (First (Args));
if Nkind (Model) = N_Identifier then
Dynamic_Elaboration_Checks := Chars (Model) = Name_Dynamic;
end if;
end if;
end if;
end Install_Elaboration_Model;
-----------------------------
-- Install_Generic_Formals --
-----------------------------
procedure Install_Generic_Formals (Subp_Id : Entity_Id) is
E : Entity_Id;
begin
pragma Assert (Is_Generic_Subprogram (Subp_Id));
E := First_Entity (Subp_Id);
while Present (E) loop
Install_Entity (E);
Next_Entity (E);
end loop;
end Install_Generic_Formals;
------------------------
-- Install_SPARK_Mode --
------------------------
procedure Install_SPARK_Mode (Mode : SPARK_Mode_Type; Prag : Node_Id) is
begin
SPARK_Mode := Mode;
SPARK_Mode_Pragma := Prag;
end Install_SPARK_Mode;
--------------------------
-- Invalid_Scalar_Value --
--------------------------
function Invalid_Scalar_Value
(Loc : Source_Ptr;
Scal_Typ : Scalar_Id) return Node_Id
is
function Invalid_Binder_Value return Node_Id;
-- Return a reference to the corresponding invalid value for type
-- Scal_Typ as defined in unit System.Scalar_Values.
function Invalid_Float_Value return Node_Id;
-- Return the invalid value of float type Scal_Typ
function Invalid_Integer_Value return Node_Id;
-- Return the invalid value of integer type Scal_Typ
procedure Set_Invalid_Binder_Values;
-- Set the contents of collection Invalid_Binder_Values
--------------------------
-- Invalid_Binder_Value --
--------------------------
function Invalid_Binder_Value return Node_Id is
Val_Id : Entity_Id;
begin
-- Initialize the collection of invalid binder values the first time
-- around.
Set_Invalid_Binder_Values;
-- Obtain the corresponding variable from System.Scalar_Values which
-- holds the invalid value for this type.
Val_Id := Invalid_Binder_Values (Scal_Typ);
pragma Assert (Present (Val_Id));
return New_Occurrence_Of (Val_Id, Loc);
end Invalid_Binder_Value;
-------------------------
-- Invalid_Float_Value --
-------------------------
function Invalid_Float_Value return Node_Id is
Value : constant Ureal := Invalid_Floats (Scal_Typ);
begin
-- Pragma Invalid_Scalars did not specify an invalid value for this
-- type. Fall back to the value provided by the binder.
if Value = No_Ureal then
return Invalid_Binder_Value;
else
return Make_Real_Literal (Loc, Realval => Value);
end if;
end Invalid_Float_Value;
---------------------------
-- Invalid_Integer_Value --
---------------------------
function Invalid_Integer_Value return Node_Id is
Value : constant Uint := Invalid_Integers (Scal_Typ);
begin
-- Pragma Invalid_Scalars did not specify an invalid value for this
-- type. Fall back to the value provided by the binder.
if No (Value) then
return Invalid_Binder_Value;
else
return Make_Integer_Literal (Loc, Intval => Value);
end if;
end Invalid_Integer_Value;
-------------------------------
-- Set_Invalid_Binder_Values --
-------------------------------
procedure Set_Invalid_Binder_Values is
begin
if not Invalid_Binder_Values_Set then
Invalid_Binder_Values_Set := True;
-- Initialize the contents of the collection once since RTE calls
-- are not cheap.
Invalid_Binder_Values :=
(Name_Short_Float => RTE (RE_IS_Isf),
Name_Float => RTE (RE_IS_Ifl),
Name_Long_Float => RTE (RE_IS_Ilf),
Name_Long_Long_Float => RTE (RE_IS_Ill),
Name_Signed_8 => RTE (RE_IS_Is1),
Name_Signed_16 => RTE (RE_IS_Is2),
Name_Signed_32 => RTE (RE_IS_Is4),
Name_Signed_64 => RTE (RE_IS_Is8),
Name_Signed_128 => Empty,
Name_Unsigned_8 => RTE (RE_IS_Iu1),
Name_Unsigned_16 => RTE (RE_IS_Iu2),
Name_Unsigned_32 => RTE (RE_IS_Iu4),
Name_Unsigned_64 => RTE (RE_IS_Iu8),
Name_Unsigned_128 => Empty);
if System_Max_Integer_Size < 128 then
Invalid_Binder_Values (Name_Signed_128) := RTE (RE_IS_Is8);
Invalid_Binder_Values (Name_Unsigned_128) := RTE (RE_IS_Iu8);
else
Invalid_Binder_Values (Name_Signed_128) := RTE (RE_IS_Is16);
Invalid_Binder_Values (Name_Unsigned_128) := RTE (RE_IS_Iu16);
end if;
end if;
end Set_Invalid_Binder_Values;
-- Start of processing for Invalid_Scalar_Value
begin
if Scal_Typ in Float_Scalar_Id then
return Invalid_Float_Value;
else pragma Assert (Scal_Typ in Integer_Scalar_Id);
return Invalid_Integer_Value;
end if;
end Invalid_Scalar_Value;
--------------------------------
-- Is_Anonymous_Access_Actual --
--------------------------------
function Is_Anonymous_Access_Actual (N : Node_Id) return Boolean is
Par : Node_Id;
begin
if Ekind (Etype (N)) /= E_Anonymous_Access_Type then
return False;
end if;
Par := Parent (N);
while Present (Par)
and then Nkind (Par) in N_Case_Expression
| N_If_Expression
| N_Parameter_Association
loop
Par := Parent (Par);
end loop;
return Nkind (Par) in N_Subprogram_Call;
end Is_Anonymous_Access_Actual;
------------------------
-- Is_Access_Variable --
------------------------
function Is_Access_Variable (E : Entity_Id) return Boolean is
begin
return Is_Access_Type (E)
and then not Is_Access_Constant (E)
and then Ekind (Directly_Designated_Type (E)) /= E_Subprogram_Type;
end Is_Access_Variable;
-----------------------------
-- Is_Actual_Out_Parameter --
-----------------------------
function Is_Actual_Out_Parameter (N : Node_Id) return Boolean is
Formal : Entity_Id;
Call : Node_Id;
begin
Find_Actual (N, Formal, Call);
return Present (Formal) and then Ekind (Formal) = E_Out_Parameter;
end Is_Actual_Out_Parameter;
--------------------------------
-- Is_Actual_In_Out_Parameter --
--------------------------------
function Is_Actual_In_Out_Parameter (N : Node_Id) return Boolean is
Formal : Entity_Id;
Call : Node_Id;
begin
Find_Actual (N, Formal, Call);
return Present (Formal) and then Ekind (Formal) = E_In_Out_Parameter;
end Is_Actual_In_Out_Parameter;
---------------------------------------
-- Is_Actual_Out_Or_In_Out_Parameter --
---------------------------------------
function Is_Actual_Out_Or_In_Out_Parameter (N : Node_Id) return Boolean is
Formal : Entity_Id;
Call : Node_Id;
begin
Find_Actual (N, Formal, Call);
return Present (Formal)
and then Ekind (Formal) in E_Out_Parameter | E_In_Out_Parameter;
end Is_Actual_Out_Or_In_Out_Parameter;
-------------------------
-- Is_Actual_Parameter --
-------------------------
function Is_Actual_Parameter (N : Node_Id) return Boolean is
PK : constant Node_Kind := Nkind (Parent (N));
begin
case PK is
when N_Parameter_Association =>
return N = Explicit_Actual_Parameter (Parent (N));
when N_Entry_Call_Statement
| N_Subprogram_Call
=>
return Is_List_Member (N)
and then
List_Containing (N) = Parameter_Associations (Parent (N));
when others =>
return False;
end case;
end Is_Actual_Parameter;
--------------------------------
-- Is_Actual_Tagged_Parameter --
--------------------------------
function Is_Actual_Tagged_Parameter (N : Node_Id) return Boolean is
Formal : Entity_Id;
Call : Node_Id;
begin
Find_Actual (N, Formal, Call);
return Present (Formal) and then Is_Tagged_Type (Etype (Formal));
end Is_Actual_Tagged_Parameter;
---------------------
-- Is_Aliased_View --
---------------------
function Is_Aliased_View (Obj : Node_Id) return Boolean is
E : Entity_Id;
begin
if Is_Entity_Name (Obj) then
E := Entity (Obj);
return
(Is_Object (E)
and then
(Is_Aliased (E)
or else (Present (Renamed_Object (E))
and then Is_Aliased_View (Renamed_Object (E)))))
or else ((Is_Formal (E) or else Is_Formal_Object (E))
and then Is_Tagged_Type (Etype (E)))
or else (Is_Concurrent_Type (E) and then In_Open_Scopes (E))
-- Current instance of type, either directly or as rewritten
-- reference to the current object.
or else (Is_Entity_Name (Original_Node (Obj))
and then Present (Entity (Original_Node (Obj)))
and then Is_Type (Entity (Original_Node (Obj))))
or else (Is_Type (E) and then E = Current_Scope)
or else (Is_Incomplete_Or_Private_Type (E)
and then Full_View (E) = Current_Scope)
-- Ada 2012 AI05-0053: the return object of an extended return
-- statement is aliased if its type is immutably limited.
or else (Is_Return_Object (E)
and then Is_Limited_View (Etype (E)))
-- The current instance of a limited type is aliased, so
-- we want to allow uses of T'Access in the init proc for
-- a limited type T. However, we don't want to mark the formal
-- parameter as being aliased since that could impact callers.
or else (Is_Formal (E)
and then Chars (E) = Name_uInit
and then Is_Limited_View (Etype (E)));
elsif Nkind (Obj) = N_Selected_Component then
return Is_Aliased (Entity (Selector_Name (Obj)));
elsif Nkind (Obj) = N_Indexed_Component then
return Has_Aliased_Components (Etype (Prefix (Obj)))
or else
(Is_Access_Type (Etype (Prefix (Obj)))
and then Has_Aliased_Components
(Designated_Type (Etype (Prefix (Obj)))));
elsif Nkind (Obj) in N_Unchecked_Type_Conversion | N_Type_Conversion then
return Is_Tagged_Type (Etype (Obj))
and then Is_Aliased_View (Expression (Obj));
-- Ada 2022 AI12-0228
elsif Nkind (Obj) = N_Qualified_Expression
and then Ada_Version >= Ada_2012
then
return Is_Aliased_View (Expression (Obj));
elsif Nkind (Obj) = N_Explicit_Dereference then
return Nkind (Original_Node (Obj)) /= N_Function_Call;
else
return False;
end if;
end Is_Aliased_View;
-------------------------
-- Is_Ancestor_Package --
-------------------------
function Is_Ancestor_Package
(E1 : Entity_Id;
E2 : Entity_Id) return Boolean
is
Par : Entity_Id;
begin
Par := E2;
while Present (Par) and then Par /= Standard_Standard loop
if Par = E1 then
return True;
end if;
Par := Scope (Par);
end loop;
return False;
end Is_Ancestor_Package;
----------------------
-- Is_Atomic_Object --
----------------------
function Is_Atomic_Object (N : Node_Id) return Boolean is
function Prefix_Has_Atomic_Components (P : Node_Id) return Boolean;
-- Determine whether prefix P has atomic components. This requires the
-- presence of an Atomic_Components aspect/pragma.
---------------------------------
-- Prefix_Has_Atomic_Components --
---------------------------------
function Prefix_Has_Atomic_Components (P : Node_Id) return Boolean is
Typ : constant Entity_Id := Etype (P);
begin
if Is_Access_Type (Typ) then
return Has_Atomic_Components (Designated_Type (Typ));
elsif Has_Atomic_Components (Typ) then
return True;
elsif Is_Entity_Name (P)
and then Has_Atomic_Components (Entity (P))
then
return True;
else
return False;
end if;
end Prefix_Has_Atomic_Components;
-- Start of processing for Is_Atomic_Object
begin
if Is_Entity_Name (N) then
return Is_Atomic_Object_Entity (Entity (N));
elsif Is_Atomic (Etype (N)) then
return True;
elsif Nkind (N) = N_Indexed_Component then
return Prefix_Has_Atomic_Components (Prefix (N));
elsif Nkind (N) = N_Selected_Component then
return Is_Atomic (Entity (Selector_Name (N)));
else
return False;
end if;
end Is_Atomic_Object;
-----------------------------
-- Is_Atomic_Object_Entity --
-----------------------------
function Is_Atomic_Object_Entity (Id : Entity_Id) return Boolean is
begin
return
Is_Object (Id)
and then (Is_Atomic (Id) or else Is_Atomic (Etype (Id)));
end Is_Atomic_Object_Entity;
-----------------------------
-- Is_Attribute_Loop_Entry --
-----------------------------
function Is_Attribute_Loop_Entry (N : Node_Id) return Boolean is
begin
return Nkind (N) = N_Attribute_Reference
and then Attribute_Name (N) = Name_Loop_Entry;
end Is_Attribute_Loop_Entry;
----------------------
-- Is_Attribute_Old --
----------------------
function Is_Attribute_Old (N : Node_Id) return Boolean is
begin
return Nkind (N) = N_Attribute_Reference
and then Attribute_Name (N) = Name_Old;
end Is_Attribute_Old;
-------------------------
-- Is_Attribute_Result --
-------------------------
function Is_Attribute_Result (N : Node_Id) return Boolean is
begin
return Nkind (N) = N_Attribute_Reference
and then Attribute_Name (N) = Name_Result;
end Is_Attribute_Result;
-------------------------
-- Is_Attribute_Update --
-------------------------
function Is_Attribute_Update (N : Node_Id) return Boolean is
begin
return Nkind (N) = N_Attribute_Reference
and then Attribute_Name (N) = Name_Update;
end Is_Attribute_Update;
------------------------------------
-- Is_Body_Or_Package_Declaration --
------------------------------------
function Is_Body_Or_Package_Declaration (N : Node_Id) return Boolean is
begin
return Is_Body (N) or else Nkind (N) = N_Package_Declaration;
end Is_Body_Or_Package_Declaration;
-----------------------
-- Is_Bounded_String --
-----------------------
function Is_Bounded_String (T : Entity_Id) return Boolean is
Under : constant Entity_Id := Underlying_Type (Root_Type (T));
begin
-- Check whether T is ultimately derived from Ada.Strings.Superbounded.
-- Super_String, or one of the [Wide_]Wide_ versions. This will
-- be True for all the Bounded_String types in instances of the
-- Generic_Bounded_Length generics, and for types derived from those.
return Present (Under)
and then (Is_RTE (Root_Type (Under), RO_SU_Super_String) or else
Is_RTE (Root_Type (Under), RO_WI_Super_String) or else
Is_RTE (Root_Type (Under), RO_WW_Super_String));
end Is_Bounded_String;
-------------------------------
-- Is_By_Protected_Procedure --
-------------------------------
function Is_By_Protected_Procedure (Id : Entity_Id) return Boolean is
begin
return Ekind (Id) = E_Procedure
and then Present (Get_Rep_Pragma (Id, Name_Implemented))
and then Implementation_Kind (Id) = Name_By_Protected_Procedure;
end Is_By_Protected_Procedure;
---------------------
-- Is_CCT_Instance --
---------------------
function Is_CCT_Instance
(Ref_Id : Entity_Id;
Context_Id : Entity_Id) return Boolean
is
begin
pragma Assert (Ekind (Ref_Id) in E_Protected_Type | E_Task_Type);
if Is_Single_Task_Object (Context_Id) then
return Scope_Within_Or_Same (Etype (Context_Id), Ref_Id);
else
pragma Assert
(Ekind (Context_Id) in
E_Entry | E_Entry_Family | E_Function | E_Package |
E_Procedure | E_Protected_Type | E_Task_Type
or else Is_Record_Type (Context_Id));
return Scope_Within_Or_Same (Context_Id, Ref_Id);
end if;
end Is_CCT_Instance;
-------------------------
-- Is_Child_Or_Sibling --
-------------------------
function Is_Child_Or_Sibling
(Pack_1 : Entity_Id;
Pack_2 : Entity_Id) return Boolean
is
function Distance_From_Standard (Pack : Entity_Id) return Nat;
-- Given an arbitrary package, return the number of "climbs" necessary
-- to reach scope Standard_Standard.
procedure Equalize_Depths
(Pack : in out Entity_Id;
Depth : in out Nat;
Depth_To_Reach : Nat);
-- Given an arbitrary package, its depth and a target depth to reach,
-- climb the scope chain until the said depth is reached. The pointer
-- to the package and its depth a modified during the climb.
----------------------------
-- Distance_From_Standard --
----------------------------
function Distance_From_Standard (Pack : Entity_Id) return Nat is
Dist : Nat;
Scop : Entity_Id;
begin
Dist := 0;
Scop := Pack;
while Present (Scop) and then Scop /= Standard_Standard loop
Dist := Dist + 1;
Scop := Scope (Scop);
end loop;
return Dist;
end Distance_From_Standard;
---------------------
-- Equalize_Depths --
---------------------
procedure Equalize_Depths
(Pack : in out Entity_Id;
Depth : in out Nat;
Depth_To_Reach : Nat)
is
begin
-- The package must be at a greater or equal depth
if Depth < Depth_To_Reach then
raise Program_Error;
end if;
-- Climb the scope chain until the desired depth is reached
while Present (Pack) and then Depth /= Depth_To_Reach loop
Pack := Scope (Pack);
Depth := Depth - 1;
end loop;
end Equalize_Depths;
-- Local variables
P_1 : Entity_Id := Pack_1;
P_1_Child : Boolean := False;
P_1_Depth : Nat := Distance_From_Standard (P_1);
P_2 : Entity_Id := Pack_2;
P_2_Child : Boolean := False;
P_2_Depth : Nat := Distance_From_Standard (P_2);
-- Start of processing for Is_Child_Or_Sibling
begin
pragma Assert
(Ekind (Pack_1) = E_Package and then Ekind (Pack_2) = E_Package);
-- Both packages denote the same entity, therefore they cannot be
-- children or siblings.
if P_1 = P_2 then
return False;
-- One of the packages is at a deeper level than the other. Note that
-- both may still come from different hierarchies.
-- (root) P_2
-- / \ :
-- X P_2 or X
-- : :
-- P_1 P_1
elsif P_1_Depth > P_2_Depth then
Equalize_Depths
(Pack => P_1,
Depth => P_1_Depth,
Depth_To_Reach => P_2_Depth);
P_1_Child := True;
-- (root) P_1
-- / \ :
-- P_1 X or X
-- : :
-- P_2 P_2
elsif P_2_Depth > P_1_Depth then
Equalize_Depths
(Pack => P_2,
Depth => P_2_Depth,
Depth_To_Reach => P_1_Depth);
P_2_Child := True;
end if;
-- At this stage the package pointers have been elevated to the same
-- depth. If the related entities are the same, then one package is a
-- potential child of the other:
-- P_1
-- :
-- X became P_1 P_2 or vice versa
-- :
-- P_2
if P_1 = P_2 then
if P_1_Child then
return Is_Child_Unit (Pack_1);
else pragma Assert (P_2_Child);
return Is_Child_Unit (Pack_2);
end if;
-- The packages may come from the same package chain or from entirely
-- different hierarchies. To determine this, climb the scope stack until
-- a common root is found.
-- (root) (root 1) (root 2)
-- / \ | |
-- P_1 P_2 P_1 P_2
else
while Present (P_1) and then Present (P_2) loop
-- The two packages may be siblings
if P_1 = P_2 then
return Is_Child_Unit (Pack_1) and then Is_Child_Unit (Pack_2);
end if;
P_1 := Scope (P_1);
P_2 := Scope (P_2);
end loop;
end if;
return False;
end Is_Child_Or_Sibling;
-------------------
-- Is_Confirming --
-------------------
function Is_Confirming (Aspect : Nonoverridable_Aspect_Id;
Aspect_Spec_1, Aspect_Spec_2 : Node_Id)
return Boolean is
function Names_Match (Nm1, Nm2 : Node_Id) return Boolean;
-----------------
-- Names_Match --
-----------------
function Names_Match (Nm1, Nm2 : Node_Id) return Boolean is
begin
if Nkind (Nm1) /= Nkind (Nm2) then
return False;
-- This may be too restrictive given that visibility
-- may allow an identifier in one case and an expanded
-- name in the other.
end if;
case Nkind (Nm1) is
when N_Identifier =>
return Name_Equals (Chars (Nm1), Chars (Nm2));
when N_Expanded_Name =>
-- An inherited operation has the same name as its
-- ancestor, but they may have different scopes.
-- This may be too permissive for Iterator_Element, which
-- is intended to be identical in parent and derived type.
return Names_Match (Selector_Name (Nm1),
Selector_Name (Nm2));
when N_Empty =>
return True; -- needed for Aggregate aspect checking
when others =>
-- e.g., 'Class attribute references
if Is_Entity_Name (Nm1) and Is_Entity_Name (Nm2) then
return Entity (Nm1) = Entity (Nm2);
end if;
raise Program_Error;
end case;
end Names_Match;
begin
-- allow users to disable "shall be confirming" check, at least for now
if Relaxed_RM_Semantics then
return True;
end if;
-- ??? Type conversion here (along with "when others =>" below) is a
-- workaround for a bootstrapping problem related to casing on a
-- static-predicate-bearing subtype.
case Aspect_Id (Aspect) is
-- name-valued aspects; compare text of names, not resolution.
when Aspect_Default_Iterator
| Aspect_Iterator_Element
| Aspect_Constant_Indexing
| Aspect_Variable_Indexing =>
declare
Item_1 : constant Node_Id := Aspect_Rep_Item (Aspect_Spec_1);
Item_2 : constant Node_Id := Aspect_Rep_Item (Aspect_Spec_2);
begin
if (Nkind (Item_1) /= N_Attribute_Definition_Clause)
or (Nkind (Item_2) /= N_Attribute_Definition_Clause)
then
pragma Assert (Serious_Errors_Detected > 0);
return True;
end if;
return Names_Match (Expression (Item_1),
Expression (Item_2));
end;
-- A confirming aspect for Implicit_Derenfence on a derived type
-- has already been checked in Analyze_Aspect_Implicit_Dereference,
-- including the presence of renamed discriminants.
when Aspect_Implicit_Dereference =>
return True;
-- one of a kind
when Aspect_Aggregate =>
declare
Empty_1,
Add_Named_1,
Add_Unnamed_1,
New_Indexed_1,
Assign_Indexed_1,
Empty_2,
Add_Named_2,
Add_Unnamed_2,
New_Indexed_2,
Assign_Indexed_2 : Node_Id := Empty;
begin
Parse_Aspect_Aggregate
(N => Expression (Aspect_Spec_1),
Empty_Subp => Empty_1,
Add_Named_Subp => Add_Named_1,
Add_Unnamed_Subp => Add_Unnamed_1,
New_Indexed_Subp => New_Indexed_1,
Assign_Indexed_Subp => Assign_Indexed_1);
Parse_Aspect_Aggregate
(N => Expression (Aspect_Spec_2),
Empty_Subp => Empty_2,
Add_Named_Subp => Add_Named_2,
Add_Unnamed_Subp => Add_Unnamed_2,
New_Indexed_Subp => New_Indexed_2,
Assign_Indexed_Subp => Assign_Indexed_2);
return
Names_Match (Empty_1, Empty_2) and then
Names_Match (Add_Named_1, Add_Named_2) and then
Names_Match (Add_Unnamed_1, Add_Unnamed_2) and then
Names_Match (New_Indexed_1, New_Indexed_2) and then
Names_Match (Assign_Indexed_1, Assign_Indexed_2);
end;
-- Checking for this aspect is performed elsewhere during freezing
when Aspect_No_Controlled_Parts =>
return True;
-- scalar-valued aspects; compare (static) values.
when Aspect_Max_Entry_Queue_Length =>
-- This should be unreachable. Max_Entry_Queue_Length is
-- supported only for protected entries, not for types.
pragma Assert (Serious_Errors_Detected /= 0);
return True;
when others =>
raise Program_Error;
end case;
end Is_Confirming;
-----------------------------
-- Is_Concurrent_Interface --
-----------------------------
function Is_Concurrent_Interface (T : Entity_Id) return Boolean is
begin
return Is_Protected_Interface (T)
or else Is_Synchronized_Interface (T)
or else Is_Task_Interface (T);
end Is_Concurrent_Interface;
------------------------------------------------------
-- Is_Conjunction_Of_Formal_Preelab_Init_Attributes --
------------------------------------------------------
function Is_Conjunction_Of_Formal_Preelab_Init_Attributes
(Expr : Node_Id) return Boolean
is
function Is_Formal_Preelab_Init_Attribute
(N : Node_Id) return Boolean;
-- Returns True if N is a Preelaborable_Initialization attribute
-- applied to a generic formal type, or N's Original_Node is such
-- an attribute.
--------------------------------------
-- Is_Formal_Preelab_Init_Attribute --
--------------------------------------
function Is_Formal_Preelab_Init_Attribute
(N : Node_Id) return Boolean
is
Orig_N : constant Node_Id := Original_Node (N);
begin
return Nkind (Orig_N) = N_Attribute_Reference
and then Attribute_Name (Orig_N) = Name_Preelaborable_Initialization
and then Is_Entity_Name (Prefix (Orig_N))
and then Is_Generic_Type (Entity (Prefix (Orig_N)));
end Is_Formal_Preelab_Init_Attribute;
-- Start of Is_Conjunction_Of_Formal_Preelab_Init_Attributes
begin
return Is_Formal_Preelab_Init_Attribute (Expr)
or else (Nkind (Expr) = N_Op_And
and then
Is_Conjunction_Of_Formal_Preelab_Init_Attributes
(Left_Opnd (Expr))
and then
Is_Conjunction_Of_Formal_Preelab_Init_Attributes
(Right_Opnd (Expr)));
end Is_Conjunction_Of_Formal_Preelab_Init_Attributes;
-----------------------
-- Is_Constant_Bound --
-----------------------
function Is_Constant_Bound (Exp : Node_Id) return Boolean is
begin
if Compile_Time_Known_Value (Exp) then
return True;
elsif Is_Entity_Name (Exp) and then Present (Entity (Exp)) then
return Is_Constant_Object (Entity (Exp))
or else Ekind (Entity (Exp)) = E_Enumeration_Literal;
elsif Nkind (Exp) in N_Binary_Op then
return Is_Constant_Bound (Left_Opnd (Exp))
and then Is_Constant_Bound (Right_Opnd (Exp))
and then Scope (Entity (Exp)) = Standard_Standard;
else
return False;
end if;
end Is_Constant_Bound;
---------------------------
-- Is_Container_Element --
---------------------------
function Is_Container_Element (Exp : Node_Id) return Boolean is
Loc : constant Source_Ptr := Sloc (Exp);
Pref : constant Node_Id := Prefix (Exp);
Call : Node_Id;
-- Call to an indexing aspect
Cont_Typ : Entity_Id;
-- The type of the container being accessed
Elem_Typ : Entity_Id;
-- Its element type
Indexing : Entity_Id;
Is_Const : Boolean;
-- Indicates that constant indexing is used, and the element is thus
-- a constant.
Ref_Typ : Entity_Id;
-- The reference type returned by the indexing operation
begin
-- If C is a container, in a context that imposes the element type of
-- that container, the indexing notation C (X) is rewritten as:
-- Indexing (C, X).Discr.all
-- where Indexing is one of the indexing aspects of the container.
-- If the context does not require a reference, the construct can be
-- rewritten as
-- Element (C, X)
-- First, verify that the construct has the proper form
if not Expander_Active then
return False;
elsif Nkind (Pref) /= N_Selected_Component then
return False;
elsif Nkind (Prefix (Pref)) /= N_Function_Call then
return False;
else
Call := Prefix (Pref);
Ref_Typ := Etype (Call);
end if;
if not Has_Implicit_Dereference (Ref_Typ)
or else No (First (Parameter_Associations (Call)))
or else not Is_Entity_Name (Name (Call))
then
return False;
end if;
-- Retrieve type of container object, and its iterator aspects
Cont_Typ := Etype (First (Parameter_Associations (Call)));
Indexing := Find_Value_Of_Aspect (Cont_Typ, Aspect_Constant_Indexing);
Is_Const := False;
if No (Indexing) then
-- Container should have at least one indexing operation
return False;
elsif Entity (Name (Call)) /= Entity (Indexing) then
-- This may be a variable indexing operation
Indexing := Find_Value_Of_Aspect (Cont_Typ, Aspect_Variable_Indexing);
if No (Indexing)
or else Entity (Name (Call)) /= Entity (Indexing)
then
return False;
end if;
else
Is_Const := True;
end if;
Elem_Typ := Find_Value_Of_Aspect (Cont_Typ, Aspect_Iterator_Element);
if No (Elem_Typ) or else Entity (Elem_Typ) /= Etype (Exp) then
return False;
end if;
-- Check that the expression is not the target of an assignment, in
-- which case the rewriting is not possible.
if not Is_Const then
declare
Par : Node_Id;
begin
Par := Exp;
while Present (Par)
loop
if Nkind (Parent (Par)) = N_Assignment_Statement
and then Par = Name (Parent (Par))
then
return False;
-- A renaming produces a reference, and the transformation
-- does not apply.
elsif Nkind (Parent (Par)) = N_Object_Renaming_Declaration then
return False;
elsif Nkind (Parent (Par)) in
N_Function_Call |
N_Procedure_Call_Statement |
N_Entry_Call_Statement
then
-- Check that the element is not part of an actual for an
-- in-out parameter.
declare
F : Entity_Id;
A : Node_Id;
begin
F := First_Formal (Entity (Name (Parent (Par))));
A := First (Parameter_Associations (Parent (Par)));
while Present (F) loop
if A = Par and then Ekind (F) /= E_In_Parameter then
return False;
end if;
Next_Formal (F);
Next (A);
end loop;
end;
-- E_In_Parameter in a call: element is not modified.
exit;
end if;
Par := Parent (Par);
end loop;
end;
end if;
-- The expression has the proper form and the context requires the
-- element type. Retrieve the Element function of the container and
-- rewrite the construct as a call to it.
declare
Op : Elmt_Id;
begin
Op := First_Elmt (Primitive_Operations (Cont_Typ));
while Present (Op) loop
exit when Chars (Node (Op)) = Name_Element;
Next_Elmt (Op);
end loop;
if No (Op) then
return False;
else
Rewrite (Exp,
Make_Function_Call (Loc,
Name => New_Occurrence_Of (Node (Op), Loc),
Parameter_Associations => Parameter_Associations (Call)));
Analyze_And_Resolve (Exp, Entity (Elem_Typ));
return True;
end if;
end;
end Is_Container_Element;
----------------------------
-- Is_Contract_Annotation --
----------------------------
function Is_Contract_Annotation (Item : Node_Id) return Boolean is
begin
return Is_Package_Contract_Annotation (Item)
or else
Is_Subprogram_Contract_Annotation (Item);
end Is_Contract_Annotation;
--------------------------------------
-- Is_Controlling_Limited_Procedure --
--------------------------------------
function Is_Controlling_Limited_Procedure
(Proc_Nam : Entity_Id) return Boolean
is
Param : Node_Id;
Param_Typ : Entity_Id := Empty;
begin
if Ekind (Proc_Nam) = E_Procedure
and then Present (Parameter_Specifications (Parent (Proc_Nam)))
then
Param :=
Parameter_Type
(First (Parameter_Specifications (Parent (Proc_Nam))));
-- The formal may be an anonymous access type
if Nkind (Param) = N_Access_Definition then
Param_Typ := Entity (Subtype_Mark (Param));
else
Param_Typ := Etype (Param);
end if;
-- In the case where an Itype was created for a dispatchin call, the
-- procedure call has been rewritten. The actual may be an access to
-- interface type in which case it is the designated type that is the
-- controlling type.
elsif Present (Associated_Node_For_Itype (Proc_Nam))
and then Present (Original_Node (Associated_Node_For_Itype (Proc_Nam)))
and then
Present (Parameter_Associations
(Associated_Node_For_Itype (Proc_Nam)))
then
Param_Typ :=
Etype (First (Parameter_Associations
(Associated_Node_For_Itype (Proc_Nam))));
if Ekind (Param_Typ) = E_Anonymous_Access_Type then
Param_Typ := Directly_Designated_Type (Param_Typ);
end if;
end if;
if Present (Param_Typ) then
return
Is_Interface (Param_Typ)
and then Is_Limited_Record (Param_Typ);
end if;
return False;
end Is_Controlling_Limited_Procedure;
-----------------------------
-- Is_CPP_Constructor_Call --
-----------------------------
function Is_CPP_Constructor_Call (N : Node_Id) return Boolean is
begin
return Nkind (N) = N_Function_Call
and then Is_CPP_Class (Etype (Etype (N)))
and then Is_Constructor (Entity (Name (N)))
and then Is_Imported (Entity (Name (N)));
end Is_CPP_Constructor_Call;
-------------------------
-- Is_Current_Instance --
-------------------------
function Is_Current_Instance (N : Node_Id) return Boolean is
Typ : constant Entity_Id := Entity (N);
P : Node_Id;
begin
-- Simplest case: entity is a concurrent type and we are currently
-- inside the body. This will eventually be expanded into a call to
-- Self (for tasks) or _object (for protected objects).
if Is_Concurrent_Type (Typ) and then In_Open_Scopes (Typ) then
return True;
else
-- Check whether the context is a (sub)type declaration for the
-- type entity.
P := Parent (N);
while Present (P) loop
if Nkind (P) in N_Full_Type_Declaration
| N_Private_Type_Declaration
| N_Subtype_Declaration
and then Comes_From_Source (P)
-- If the type has a previous incomplete declaration, the
-- reference in the type definition may have the incomplete
-- view. So, here we detect if this incomplete view is a current
-- instance by checking if its full view is the entity of the
-- full declaration begin analyzed.
and then
(Defining_Entity (P) = Typ
or else
(Ekind (Typ) = E_Incomplete_Type
and then Full_View (Typ) = Defining_Entity (P)))
then
return True;
-- A subtype name may appear in an aspect specification for a
-- Predicate_Failure aspect, for which we do not construct a
-- wrapper procedure. The subtype will be replaced by the
-- expression being tested when the corresponding predicate
-- check is expanded. It may also appear in the pragma Predicate
-- expression during legality checking.
elsif Nkind (P) = N_Aspect_Specification
and then Nkind (Parent (P)) = N_Subtype_Declaration
then
return True;
elsif Nkind (P) = N_Pragma
and then Get_Pragma_Id (P) in Pragma_Predicate
| Pragma_Predicate_Failure
then
return True;
end if;
P := Parent (P);
end loop;
end if;
-- In any other context this is not a current occurrence
return False;
end Is_Current_Instance;
--------------------------------------------------
-- Is_Current_Instance_Reference_In_Type_Aspect --
--------------------------------------------------
function Is_Current_Instance_Reference_In_Type_Aspect
(N : Node_Id) return Boolean
is
begin
-- When a current_instance is referenced within an aspect_specification
-- of a type or subtype, it will show up as a reference to the formal
-- parameter of the aspect's associated subprogram rather than as a
-- reference to the type or subtype itself (in fact, the original name
-- is never even analyzed). We check for predicate, invariant, and
-- Default_Initial_Condition subprograms (in theory there could be
-- other cases added, in which case this function will need updating).
if Is_Entity_Name (N) then
return Present (Entity (N))
and then Ekind (Entity (N)) = E_In_Parameter
and then Ekind (Scope (Entity (N))) in E_Function | E_Procedure
and then
(Is_Predicate_Function (Scope (Entity (N)))
or else Is_Predicate_Function_M (Scope (Entity (N)))
or else Is_Invariant_Procedure (Scope (Entity (N)))
or else Is_Partial_Invariant_Procedure (Scope (Entity (N)))
or else Is_DIC_Procedure (Scope (Entity (N))));
else
case Nkind (N) is
when N_Indexed_Component
| N_Slice
=>
return
Is_Current_Instance_Reference_In_Type_Aspect (Prefix (N));
when N_Selected_Component =>
return
Is_Current_Instance_Reference_In_Type_Aspect (Prefix (N));
when N_Type_Conversion =>
return Is_Current_Instance_Reference_In_Type_Aspect
(Expression (N));
when N_Qualified_Expression =>
return Is_Current_Instance_Reference_In_Type_Aspect
(Expression (N));
when others =>
return False;
end case;
end if;
end Is_Current_Instance_Reference_In_Type_Aspect;
--------------------
-- Is_Declaration --
--------------------
function Is_Declaration
(N : Node_Id;
Body_OK : Boolean := True;
Concurrent_OK : Boolean := True;
Formal_OK : Boolean := True;
Generic_OK : Boolean := True;
Instantiation_OK : Boolean := True;
Renaming_OK : Boolean := True;
Stub_OK : Boolean := True;
Subprogram_OK : Boolean := True;
Type_OK : Boolean := True) return Boolean
is
begin
case Nkind (N) is
-- Body declarations
when N_Proper_Body =>
return Body_OK;
-- Concurrent type declarations
when N_Protected_Type_Declaration
| N_Single_Protected_Declaration
| N_Single_Task_Declaration
| N_Task_Type_Declaration
=>
return Concurrent_OK or Type_OK;
-- Formal declarations
when N_Formal_Abstract_Subprogram_Declaration
| N_Formal_Concrete_Subprogram_Declaration
| N_Formal_Object_Declaration
| N_Formal_Package_Declaration
| N_Formal_Type_Declaration
=>
return Formal_OK;
-- Generic declarations
when N_Generic_Package_Declaration
| N_Generic_Subprogram_Declaration
=>
return Generic_OK;
-- Generic instantiations
when N_Function_Instantiation
| N_Package_Instantiation
| N_Procedure_Instantiation
=>
return Instantiation_OK;
-- Generic renaming declarations
when N_Generic_Renaming_Declaration =>
return Generic_OK or Renaming_OK;
-- Renaming declarations
when N_Exception_Renaming_Declaration
| N_Object_Renaming_Declaration
| N_Package_Renaming_Declaration
| N_Subprogram_Renaming_Declaration
=>
return Renaming_OK;
-- Stub declarations
when N_Body_Stub =>
return Stub_OK;
-- Subprogram declarations
when N_Abstract_Subprogram_Declaration
| N_Entry_Declaration
| N_Expression_Function
| N_Subprogram_Declaration
=>
return Subprogram_OK;
-- Type declarations
when N_Full_Type_Declaration
| N_Incomplete_Type_Declaration
| N_Private_Extension_Declaration
| N_Private_Type_Declaration
| N_Subtype_Declaration
=>
return Type_OK;
-- Miscellaneous
when N_Component_Declaration
| N_Exception_Declaration
| N_Implicit_Label_Declaration
| N_Number_Declaration
| N_Object_Declaration
| N_Package_Declaration
=>
return True;
when others =>
return False;
end case;
end Is_Declaration;
--------------------------------
-- Is_Declared_Within_Variant --
--------------------------------
function Is_Declared_Within_Variant (Comp : Entity_Id) return Boolean is
Comp_Decl : constant Node_Id := Parent (Comp);
Comp_List : constant Node_Id := Parent (Comp_Decl);
begin
return Nkind (Parent (Comp_List)) = N_Variant;
end Is_Declared_Within_Variant;
----------------------------------------------
-- Is_Dependent_Component_Of_Mutable_Object --
----------------------------------------------
function Is_Dependent_Component_Of_Mutable_Object
(Object : Node_Id) return Boolean
is
P : Node_Id;
Prefix_Type : Entity_Id;
P_Aliased : Boolean := False;
Comp : Entity_Id;
Deref : Node_Id := Original_Node (Object);
-- Dereference node, in something like X.all.Y(2)
-- Start of processing for Is_Dependent_Component_Of_Mutable_Object
begin
-- Find the dereference node if any
while Nkind (Deref) in
N_Indexed_Component | N_Selected_Component | N_Slice
loop
Deref := Original_Node (Prefix (Deref));
end loop;
-- If the prefix is a qualified expression of a variable, then function
-- Is_Variable will return False for that because a qualified expression
-- denotes a constant view, so we need to get the name being qualified
-- so we can test below whether that's a variable (or a dereference).
if Nkind (Deref) = N_Qualified_Expression then
Deref := Expression (Deref);
end if;
-- Ada 2005: If we have a component or slice of a dereference, something
-- like X.all.Y (2) and the type of X is access-to-constant, Is_Variable
-- will return False, because it is indeed a constant view. But it might
-- be a view of a variable object, so we want the following condition to
-- be True in that case.
if Is_Variable (Object)
or else Is_Variable (Deref)
or else
(Ada_Version >= Ada_2005
and then (Nkind (Deref) = N_Explicit_Dereference
or else (Present (Etype (Deref))
and then Is_Access_Type (Etype (Deref)))))
then
if Nkind (Object) = N_Selected_Component then
-- If the selector is not a component, then we definitely return
-- False (it could be a function selector in a prefix form call
-- occurring in an iterator specification).
if Ekind (Entity (Selector_Name (Object))) not in
E_Component | E_Discriminant
then
return False;
end if;
-- Get the original node of the prefix in case it has been
-- rewritten, which can occur, for example, in qualified
-- expression cases. Also, a discriminant check on a selected
-- component may be expanded into a dereference when removing
-- side effects, and the subtype of the original node may be
-- unconstrained.
P := Original_Node (Prefix (Object));
Prefix_Type := Etype (P);
-- If the prefix is a qualified expression, we want to look at its
-- operand.
if Nkind (P) = N_Qualified_Expression then
P := Expression (P);
Prefix_Type := Etype (P);
end if;
if Is_Entity_Name (P) then
-- The Etype may not be set on P (which is wrong) in certain
-- corner cases involving the deprecated front-end inlining of
-- subprograms (via -gnatN), so use the Etype set on the
-- the entity for these instances since we know it is present.
if No (Prefix_Type) then
Prefix_Type := Etype (Entity (P));
end if;
if Ekind (Entity (P)) = E_Generic_In_Out_Parameter then
Prefix_Type := Base_Type (Prefix_Type);
end if;
if Is_Aliased (Entity (P)) then
P_Aliased := True;
end if;
-- For explicit dereferences we get the access prefix so we can
-- treat this similarly to implicit dereferences and examine the
-- kind of the access type and its designated subtype further
-- below.
elsif Nkind (P) = N_Explicit_Dereference then
P := Prefix (P);
Prefix_Type := Etype (P);
else
-- Check for prefix being an aliased component???
null;
end if;
-- A heap object is constrained by its initial value
-- Ada 2005 (AI-363): Always assume the object could be mutable in
-- the dereferenced case, since the access value might denote an
-- unconstrained aliased object, whereas in Ada 95 the designated
-- object is guaranteed to be constrained. A worst-case assumption
-- has to apply in Ada 2005 because we can't tell at compile
-- time whether the object is "constrained by its initial value",
-- despite the fact that 3.10.2(26/2) and 8.5.1(5/2) are semantic
-- rules (these rules are acknowledged to need fixing). We don't
-- impose this more stringent checking for earlier Ada versions or
-- when Relaxed_RM_Semantics applies (the latter for CodePeer's
-- benefit, though it's unclear on why using -gnat95 would not be
-- sufficient???).
if Ada_Version < Ada_2005 or else Relaxed_RM_Semantics then
if Is_Access_Type (Prefix_Type)
or else Nkind (P) = N_Explicit_Dereference
then
return False;
end if;
else pragma Assert (Ada_Version >= Ada_2005);
if Is_Access_Type (Prefix_Type) then
-- We need to make sure we have the base subtype, in case
-- this is actually an access subtype (whose Ekind will be
-- E_Access_Subtype).
Prefix_Type := Etype (Prefix_Type);
-- If the access type is pool-specific, and there is no
-- constrained partial view of the designated type, then the
-- designated object is known to be constrained. If it's a
-- formal access type and the renaming is in the generic
-- spec, we also treat it as pool-specific (known to be
-- constrained), but assume the worst if in the generic body
-- (see RM 3.3(23.3/3)).
if Ekind (Prefix_Type) = E_Access_Type
and then (not Is_Generic_Type (Prefix_Type)
or else not In_Generic_Body (Current_Scope))
and then not Object_Type_Has_Constrained_Partial_View
(Typ => Designated_Type (Prefix_Type),
Scop => Current_Scope)
then
return False;
-- Otherwise (general access type, or there is a constrained
-- partial view of the designated type), we need to check
-- based on the designated type.
else
Prefix_Type := Designated_Type (Prefix_Type);
end if;
end if;
end if;
Comp :=
Original_Record_Component (Entity (Selector_Name (Object)));
-- As per AI-0017, the renaming is illegal in a generic body, even
-- if the subtype is indefinite (only applies to prefixes of an
-- untagged formal type, see RM 3.3 (23.11/3)).
-- Ada 2005 (AI-363): In Ada 2005 an aliased object can be mutable
if not Is_Constrained (Prefix_Type)
and then (Is_Definite_Subtype (Prefix_Type)
or else
(not Is_Tagged_Type (Prefix_Type)
and then Is_Generic_Type (Prefix_Type)
and then In_Generic_Body (Current_Scope)))
and then (Is_Declared_Within_Variant (Comp)
or else Has_Discriminant_Dependent_Constraint (Comp))
and then (not P_Aliased or else Ada_Version >= Ada_2005)
then
return True;
-- If the prefix is of an access type at this point, then we want
-- to return False, rather than calling this function recursively
-- on the access object (which itself might be a discriminant-
-- dependent component of some other object, but that isn't
-- relevant to checking the object passed to us). This avoids
-- issuing wrong errors when compiling with -gnatc, where there
-- can be implicit dereferences that have not been expanded.
elsif Is_Access_Type (Etype (Prefix (Object))) then
return False;
else
return
Is_Dependent_Component_Of_Mutable_Object (Prefix (Object));
end if;
elsif Nkind (Object) = N_Indexed_Component
or else Nkind (Object) = N_Slice
then
return Is_Dependent_Component_Of_Mutable_Object
(Original_Node (Prefix (Object)));
-- A type conversion that Is_Variable is a view conversion:
-- go back to the denoted object.
elsif Nkind (Object) = N_Type_Conversion then
return
Is_Dependent_Component_Of_Mutable_Object
(Original_Node (Expression (Object)));
end if;
end if;
return False;
end Is_Dependent_Component_Of_Mutable_Object;
---------------------
-- Is_Dereferenced --
---------------------
function Is_Dereferenced (N : Node_Id) return Boolean is
P : constant Node_Id := Parent (N);
begin
return Nkind (P) in N_Selected_Component
| N_Explicit_Dereference
| N_Indexed_Component
| N_Slice
and then Prefix (P) = N;
end Is_Dereferenced;
----------------------
-- Is_Descendant_Of --
----------------------
function Is_Descendant_Of (T1 : Entity_Id; T2 : Entity_Id) return Boolean is
T : Entity_Id;
Etyp : Entity_Id;
begin
pragma Assert (Nkind (T1) in N_Entity);
pragma Assert (Nkind (T2) in N_Entity);
T := Base_Type (T1);
-- Immediate return if the types match
if T = T2 then
return True;
-- Comment needed here ???
elsif Ekind (T) = E_Class_Wide_Type then
return Etype (T) = T2;
-- All other cases
else
loop
Etyp := Etype (T);
-- Done if we found the type we are looking for
if Etyp = T2 then
return True;
-- Done if no more derivations to check
elsif T = T1
or else T = Etyp
then
return False;
-- Following test catches error cases resulting from prev errors
elsif No (Etyp) then
return False;
elsif Is_Private_Type (T) and then Etyp = Full_View (T) then
return False;
elsif Is_Private_Type (Etyp) and then Full_View (Etyp) = T then
return False;
end if;
T := Base_Type (Etyp);
end loop;
end if;
end Is_Descendant_Of;
----------------------------------------
-- Is_Descendant_Of_Suspension_Object --
----------------------------------------
function Is_Descendant_Of_Suspension_Object
(Typ : Entity_Id) return Boolean
is
Cur_Typ : Entity_Id;
Par_Typ : Entity_Id;
begin
-- Climb the type derivation chain checking each parent type against
-- Suspension_Object.
Cur_Typ := Base_Type (Typ);
while Present (Cur_Typ) loop
Par_Typ := Etype (Cur_Typ);
-- The current type is a match
if Is_RTE (Cur_Typ, RE_Suspension_Object) then
return True;
-- Stop the traversal once the root of the derivation chain has been
-- reached. In that case the current type is its own base type.
elsif Cur_Typ = Par_Typ then
exit;
end if;
Cur_Typ := Base_Type (Par_Typ);
end loop;
return False;
end Is_Descendant_Of_Suspension_Object;
---------------------------------------------
-- Is_Double_Precision_Floating_Point_Type --
---------------------------------------------
function Is_Double_Precision_Floating_Point_Type
(E : Entity_Id) return Boolean is
begin
return Is_Floating_Point_Type (E)
and then Machine_Radix_Value (E) = Uint_2
and then Machine_Mantissa_Value (E) = UI_From_Int (53)
and then Machine_Emax_Value (E) = Uint_2 ** Uint_10
and then Machine_Emin_Value (E) = Uint_3 - (Uint_2 ** Uint_10);
end Is_Double_Precision_Floating_Point_Type;
-----------------------------
-- Is_Effectively_Volatile --
-----------------------------
function Is_Effectively_Volatile
(Id : Entity_Id;
Ignore_Protected : Boolean := False) return Boolean is
begin
if Is_Type (Id) then
-- An arbitrary type is effectively volatile when it is subject to
-- pragma Atomic or Volatile.
if Is_Volatile (Id) then
return True;
-- An array type is effectively volatile when it is subject to pragma
-- Atomic_Components or Volatile_Components or its component type is
-- effectively volatile.
elsif Is_Array_Type (Id) then
if Has_Volatile_Components (Id) then
return True;
else
declare
Anc : Entity_Id := Base_Type (Id);
begin
if Is_Private_Type (Anc) then
Anc := Full_View (Anc);
end if;
-- Test for presence of ancestor, as the full view of a
-- private type may be missing in case of error.
return Present (Anc)
and then Is_Effectively_Volatile
(Component_Type (Anc), Ignore_Protected);
end;
end if;
-- A protected type is always volatile unless Ignore_Protected is
-- True.
elsif Is_Protected_Type (Id) and then not Ignore_Protected then
return True;
-- A descendant of Ada.Synchronous_Task_Control.Suspension_Object is
-- automatically volatile.
elsif Is_Descendant_Of_Suspension_Object (Id) then
return True;
-- Otherwise the type is not effectively volatile
else
return False;
end if;
-- Otherwise Id denotes an object
else pragma Assert (Is_Object (Id));
-- A volatile object for which No_Caching is enabled is not
-- effectively volatile.
return
(Is_Volatile (Id)
and then not
(Ekind (Id) = E_Variable and then No_Caching_Enabled (Id)))
or else Has_Volatile_Components (Id)
or else Is_Effectively_Volatile (Etype (Id), Ignore_Protected);
end if;
end Is_Effectively_Volatile;
-----------------------------------------
-- Is_Effectively_Volatile_For_Reading --
-----------------------------------------
function Is_Effectively_Volatile_For_Reading
(Id : Entity_Id;
Ignore_Protected : Boolean := False) return Boolean
is
begin
-- A concurrent type is effectively volatile for reading, except for a
-- protected type when Ignore_Protected is True.
if Is_Task_Type (Id)
or else (Is_Protected_Type (Id) and then not Ignore_Protected)
then
return True;
elsif Is_Effectively_Volatile (Id, Ignore_Protected) then
-- Other volatile types and objects are effectively volatile for
-- reading when they have property Async_Writers or Effective_Reads
-- set to True. This includes the case of an array type whose
-- Volatile_Components aspect is True (hence it is effectively
-- volatile) which does not have the properties Async_Writers
-- and Effective_Reads set to False.
if Async_Writers_Enabled (Id)
or else Effective_Reads_Enabled (Id)
then
return True;
-- In addition, an array type is effectively volatile for reading
-- when its component type is effectively volatile for reading.
elsif Is_Array_Type (Id) then
declare
Anc : Entity_Id := Base_Type (Id);
begin
if Is_Private_Type (Anc) then
Anc := Full_View (Anc);
end if;
-- Test for presence of ancestor, as the full view of a
-- private type may be missing in case of error.
return Present (Anc)
and then Is_Effectively_Volatile_For_Reading
(Component_Type (Anc), Ignore_Protected);
end;
end if;
end if;
return False;
end Is_Effectively_Volatile_For_Reading;
------------------------------------
-- Is_Effectively_Volatile_Object --
------------------------------------
function Is_Effectively_Volatile_Object (N : Node_Id) return Boolean is
function Is_Effectively_Volatile (E : Entity_Id) return Boolean is
(Is_Effectively_Volatile (E, Ignore_Protected => False));
function Is_Effectively_Volatile_Object_Inst
is new Is_Effectively_Volatile_Object_Shared (Is_Effectively_Volatile);
begin
return Is_Effectively_Volatile_Object_Inst (N);
end Is_Effectively_Volatile_Object;
------------------------------------------------
-- Is_Effectively_Volatile_Object_For_Reading --
------------------------------------------------
function Is_Effectively_Volatile_Object_For_Reading
(N : Node_Id) return Boolean
is
function Is_Effectively_Volatile_For_Reading
(E : Entity_Id) return Boolean
is (Is_Effectively_Volatile_For_Reading (E, Ignore_Protected => False));
function Is_Effectively_Volatile_Object_For_Reading_Inst
is new Is_Effectively_Volatile_Object_Shared
(Is_Effectively_Volatile_For_Reading);
begin
return Is_Effectively_Volatile_Object_For_Reading_Inst (N);
end Is_Effectively_Volatile_Object_For_Reading;
-------------------------------------------
-- Is_Effectively_Volatile_Object_Shared --
-------------------------------------------
function Is_Effectively_Volatile_Object_Shared
(N : Node_Id) return Boolean
is
begin
if Is_Entity_Name (N) then
return Is_Object (Entity (N))
and then Is_Effectively_Volatile_Entity (Entity (N));
elsif Nkind (N) in N_Indexed_Component | N_Slice then
return Is_Effectively_Volatile_Object_Shared (Prefix (N));
elsif Nkind (N) = N_Selected_Component then
return
Is_Effectively_Volatile_Object_Shared (Prefix (N))
or else
Is_Effectively_Volatile_Object_Shared (Selector_Name (N));
elsif Nkind (N) in N_Qualified_Expression
| N_Unchecked_Type_Conversion
| N_Type_Conversion
then
return Is_Effectively_Volatile_Object_Shared (Expression (N));
else
return False;
end if;
end Is_Effectively_Volatile_Object_Shared;
-------------------
-- Is_Entry_Body --
-------------------
function Is_Entry_Body (Id : Entity_Id) return Boolean is
begin
return
Is_Entry (Id)
and then Nkind (Unit_Declaration_Node (Id)) = N_Entry_Body;
end Is_Entry_Body;
--------------------------
-- Is_Entry_Declaration --
--------------------------
function Is_Entry_Declaration (Id : Entity_Id) return Boolean is
begin
return
Is_Entry (Id)
and then Nkind (Unit_Declaration_Node (Id)) = N_Entry_Declaration;
end Is_Entry_Declaration;
------------------------------------
-- Is_Expanded_Priority_Attribute --
------------------------------------
function Is_Expanded_Priority_Attribute (E : Entity_Id) return Boolean is
begin
return
Nkind (E) = N_Function_Call
and then not Configurable_Run_Time_Mode
and then Nkind (Original_Node (E)) = N_Attribute_Reference
and then (Is_RTE (Entity (Name (E)), RE_Get_Ceiling)
or else Is_RTE (Entity (Name (E)), RO_PE_Get_Ceiling));
end Is_Expanded_Priority_Attribute;
----------------------------
-- Is_Expression_Function --
----------------------------
function Is_Expression_Function (Subp : Entity_Id) return Boolean is
begin
if Ekind (Subp) in E_Function | E_Subprogram_Body then
return
Nkind (Original_Node (Unit_Declaration_Node (Subp))) =
N_Expression_Function;
else
return False;
end if;
end Is_Expression_Function;
------------------------------------------
-- Is_Expression_Function_Or_Completion --
------------------------------------------
function Is_Expression_Function_Or_Completion
(Subp : Entity_Id) return Boolean
is
Subp_Decl : Node_Id;
begin
if Ekind (Subp) = E_Function then
Subp_Decl := Unit_Declaration_Node (Subp);
-- The function declaration is either an expression function or is
-- completed by an expression function body.
return
Is_Expression_Function (Subp)
or else (Nkind (Subp_Decl) = N_Subprogram_Declaration
and then Present (Corresponding_Body (Subp_Decl))
and then Is_Expression_Function
(Corresponding_Body (Subp_Decl)));
elsif Ekind (Subp) = E_Subprogram_Body then
return Is_Expression_Function (Subp);
else
return False;
end if;
end Is_Expression_Function_Or_Completion;
-----------------------------------------------
-- Is_Extended_Precision_Floating_Point_Type --
-----------------------------------------------
function Is_Extended_Precision_Floating_Point_Type
(E : Entity_Id) return Boolean is
begin
return Is_Floating_Point_Type (E)
and then Machine_Radix_Value (E) = Uint_2
and then Machine_Mantissa_Value (E) = Uint_64
and then Machine_Emax_Value (E) = Uint_2 ** Uint_14
and then Machine_Emin_Value (E) = Uint_3 - (Uint_2 ** Uint_14);
end Is_Extended_Precision_Floating_Point_Type;
-----------------------
-- Is_EVF_Expression --
-----------------------
function Is_EVF_Expression (N : Node_Id) return Boolean is
Orig_N : constant Node_Id := Original_Node (N);
Alt : Node_Id;
Expr : Node_Id;
Id : Entity_Id;
begin
-- Detect a reference to a formal parameter of a specific tagged type
-- whose related subprogram is subject to pragma Expresions_Visible with
-- value "False".
if Is_Entity_Name (N) and then Present (Entity (N)) then
Id := Entity (N);
return
Is_Formal (Id)
and then Is_Specific_Tagged_Type (Etype (Id))
and then Extensions_Visible_Status (Id) =
Extensions_Visible_False;
-- A case expression is an EVF expression when it contains at least one
-- EVF dependent_expression. Note that a case expression may have been
-- expanded, hence the use of Original_Node.
elsif Nkind (Orig_N) = N_Case_Expression then
Alt := First (Alternatives (Orig_N));
while Present (Alt) loop
if Is_EVF_Expression (Expression (Alt)) then
return True;
end if;
Next (Alt);
end loop;
-- An if expression is an EVF expression when it contains at least one
-- EVF dependent_expression. Note that an if expression may have been
-- expanded, hence the use of Original_Node.
elsif Nkind (Orig_N) = N_If_Expression then
Expr := Next (First (Expressions (Orig_N)));
while Present (Expr) loop
if Is_EVF_Expression (Expr) then
return True;
end if;
Next (Expr);
end loop;
-- A qualified expression or a type conversion is an EVF expression when
-- its operand is an EVF expression.
elsif Nkind (N) in N_Qualified_Expression
| N_Unchecked_Type_Conversion
| N_Type_Conversion
then
return Is_EVF_Expression (Expression (N));
-- Attributes 'Loop_Entry, 'Old, and 'Update are EVF expressions when
-- their prefix denotes an EVF expression.
elsif Nkind (N) = N_Attribute_Reference
and then Attribute_Name (N) in Name_Loop_Entry
| Name_Old
| Name_Update
then
return Is_EVF_Expression (Prefix (N));
end if;
return False;
end Is_EVF_Expression;
--------------
-- Is_False --
--------------
function Is_False (U : Opt_Ubool) return Boolean is
begin
return not Is_True (U);
end Is_False;
---------------------------
-- Is_Fixed_Model_Number --
---------------------------
function Is_Fixed_Model_Number (U : Ureal; T : Entity_Id) return Boolean is
S : constant Ureal := Small_Value (T);
M : Urealp.Save_Mark;
R : Boolean;
begin
M := Urealp.Mark;
R := (U = UR_Trunc (U / S) * S);
Urealp.Release (M);
return R;
end Is_Fixed_Model_Number;
-----------------------------
-- Is_Full_Access_Object --
-----------------------------
function Is_Full_Access_Object (N : Node_Id) return Boolean is
begin
return Is_Atomic_Object (N)
or else Is_Volatile_Full_Access_Object_Ref (N);
end Is_Full_Access_Object;
-------------------------------
-- Is_Fully_Initialized_Type --
-------------------------------
function Is_Fully_Initialized_Type (Typ : Entity_Id) return Boolean is
begin
-- Scalar types
if Is_Scalar_Type (Typ) then
-- A scalar type with an aspect Default_Value is fully initialized
-- Note: Iniitalize/Normalize_Scalars also ensure full initialization
-- of a scalar type, but we don't take that into account here, since
-- we don't want these to affect warnings.
return Has_Default_Aspect (Typ);
elsif Is_Access_Type (Typ) then
return True;
elsif Is_Array_Type (Typ) then
if Is_Fully_Initialized_Type (Component_Type (Typ))
or else (Ada_Version >= Ada_2012 and then Has_Default_Aspect (Typ))
then
return True;
end if;
-- An interesting case, if we have a constrained type one of whose
-- bounds is known to be null, then there are no elements to be
-- initialized, so all the elements are initialized.
if Is_Constrained (Typ) then
declare
Indx : Node_Id;
Indx_Typ : Entity_Id;
Lbd, Hbd : Node_Id;
begin
Indx := First_Index (Typ);
while Present (Indx) loop
if Etype (Indx) = Any_Type then
return False;
-- If index is a range, use directly
elsif Nkind (Indx) = N_Range then
Lbd := Low_Bound (Indx);
Hbd := High_Bound (Indx);
else
Indx_Typ := Etype (Indx);
if Is_Private_Type (Indx_Typ) then
Indx_Typ := Full_View (Indx_Typ);
end if;
if No (Indx_Typ) or else Etype (Indx_Typ) = Any_Type then
return False;
else
Lbd := Type_Low_Bound (Indx_Typ);
Hbd := Type_High_Bound (Indx_Typ);
end if;
end if;
if Compile_Time_Known_Value (Lbd)
and then
Compile_Time_Known_Value (Hbd)
then
if Expr_Value (Hbd) < Expr_Value (Lbd) then
return True;
end if;
end if;
Next_Index (Indx);
end loop;
end;
end if;
-- If no null indexes, then type is not fully initialized
return False;
-- Record types
elsif Is_Record_Type (Typ) then
if Has_Defaulted_Discriminants (Typ)
and then Is_Fully_Initialized_Variant (Typ)
then
return True;
end if;
-- We consider bounded string types to be fully initialized, because
-- otherwise we get false alarms when the Data component is not
-- default-initialized.
if Is_Bounded_String (Typ) then
return True;
end if;
-- Controlled records are considered to be fully initialized if
-- there is a user defined Initialize routine. This may not be
-- entirely correct, but as the spec notes, we are guessing here
-- what is best from the point of view of issuing warnings.
if Is_Controlled (Typ) then
declare
Utyp : constant Entity_Id := Underlying_Type (Typ);
begin
if Present (Utyp) then
declare
Init : constant Entity_Id :=
(Find_Optional_Prim_Op
(Underlying_Type (Typ), Name_Initialize));
begin
if Present (Init)
and then Comes_From_Source (Init)
and then not In_Predefined_Unit (Init)
then
return True;
elsif Has_Null_Extension (Typ)
and then
Is_Fully_Initialized_Type
(Etype (Base_Type (Typ)))
then
return True;
end if;
end;
end if;
end;
end if;
-- Otherwise see if all record components are initialized
declare
Comp : Entity_Id;
begin
Comp := First_Component (Typ);
while Present (Comp) loop
if (No (Parent (Comp))
or else No (Expression (Parent (Comp))))
and then not Is_Fully_Initialized_Type (Etype (Comp))
-- Special VM case for tag components, which need to be
-- defined in this case, but are never initialized as VMs
-- are using other dispatching mechanisms. Ignore this
-- uninitialized case. Note that this applies both to the
-- uTag entry and the main vtable pointer (CPP_Class case).
and then (Tagged_Type_Expansion or else not Is_Tag (Comp))
then
return False;
end if;
Next_Component (Comp);
end loop;
end;
-- No uninitialized components, so type is fully initialized.
-- Note that this catches the case of no components as well.
return True;
elsif Is_Concurrent_Type (Typ) then
return True;
elsif Is_Private_Type (Typ) then
declare
U : constant Entity_Id := Underlying_Type (Typ);
begin
if No (U) then
return False;
else
return Is_Fully_Initialized_Type (U);
end if;
end;
else
return False;
end if;
end Is_Fully_Initialized_Type;
----------------------------------
-- Is_Fully_Initialized_Variant --
----------------------------------
function Is_Fully_Initialized_Variant (Typ : Entity_Id) return Boolean is
Loc : constant Source_Ptr := Sloc (Typ);
Constraints : constant List_Id := New_List;
Components : constant Elist_Id := New_Elmt_List;
Comp_Elmt : Elmt_Id;
Comp_Id : Node_Id;
Comp_List : Node_Id;
Discr : Entity_Id;
Discr_Val : Node_Id;
Report_Errors : Boolean;
pragma Warnings (Off, Report_Errors);
begin
if Serious_Errors_Detected > 0 then
return False;
end if;
if Is_Record_Type (Typ)
and then Nkind (Parent (Typ)) = N_Full_Type_Declaration
and then Nkind (Type_Definition (Parent (Typ))) = N_Record_Definition
then
Comp_List := Component_List (Type_Definition (Parent (Typ)));
Discr := First_Discriminant (Typ);
while Present (Discr) loop
if Nkind (Parent (Discr)) = N_Discriminant_Specification then
Discr_Val := Expression (Parent (Discr));
if Present (Discr_Val)
and then Is_OK_Static_Expression (Discr_Val)
then
Append_To (Constraints,
Make_Component_Association (Loc,
Choices => New_List (New_Occurrence_Of (Discr, Loc)),
Expression => New_Copy (Discr_Val)));
else
return False;
end if;
else
return False;
end if;
Next_Discriminant (Discr);
end loop;
Gather_Components
(Typ => Typ,
Comp_List => Comp_List,
Governed_By => Constraints,
Into => Components,
Report_Errors => Report_Errors);
-- Check that each component present is fully initialized
Comp_Elmt := First_Elmt (Components);
while Present (Comp_Elmt) loop
Comp_Id := Node (Comp_Elmt);
if Ekind (Comp_Id) = E_Component
and then (No (Parent (Comp_Id))
or else No (Expression (Parent (Comp_Id))))
and then not Is_Fully_Initialized_Type (Etype (Comp_Id))
then
return False;
end if;
Next_Elmt (Comp_Elmt);
end loop;
return True;
elsif Is_Private_Type (Typ) then
declare
U : constant Entity_Id := Underlying_Type (Typ);
begin
if No (U) then
return False;
else
return Is_Fully_Initialized_Variant (U);
end if;
end;
else
return False;
end if;
end Is_Fully_Initialized_Variant;
------------------------------------
-- Is_Generic_Declaration_Or_Body --
------------------------------------
function Is_Generic_Declaration_Or_Body (Decl : Node_Id) return Boolean is
Spec_Decl : Node_Id;
begin
-- Package/subprogram body
if Nkind (Decl) in N_Package_Body | N_Subprogram_Body
and then Present (Corresponding_Spec (Decl))
then
Spec_Decl := Unit_Declaration_Node (Corresponding_Spec (Decl));
-- Package/subprogram body stub
elsif Nkind (Decl) in N_Package_Body_Stub | N_Subprogram_Body_Stub
and then Present (Corresponding_Spec_Of_Stub (Decl))
then
Spec_Decl :=
Unit_Declaration_Node (Corresponding_Spec_Of_Stub (Decl));
-- All other cases
else
Spec_Decl := Decl;
end if;
-- Rather than inspecting the defining entity of the spec declaration,
-- look at its Nkind. This takes care of the case where the analysis of
-- a generic body modifies the Ekind of its spec to allow for recursive
-- calls.
return Nkind (Spec_Decl) in N_Generic_Declaration;
end Is_Generic_Declaration_Or_Body;
---------------------------
-- Is_Independent_Object --
---------------------------
function Is_Independent_Object (N : Node_Id) return Boolean is
function Is_Independent_Object_Entity (Id : Entity_Id) return Boolean;
-- Determine whether arbitrary entity Id denotes an object that is
-- Independent.
function Prefix_Has_Independent_Components (P : Node_Id) return Boolean;
-- Determine whether prefix P has independent components. This requires
-- the presence of an Independent_Components aspect/pragma.
------------------------------------
-- Is_Independent_Object_Entity --
------------------------------------
function Is_Independent_Object_Entity (Id : Entity_Id) return Boolean is
begin
return
Is_Object (Id)
and then (Is_Independent (Id)
or else
Is_Independent (Etype (Id)));
end Is_Independent_Object_Entity;
-------------------------------------
-- Prefix_Has_Independent_Components --
-------------------------------------
function Prefix_Has_Independent_Components (P : Node_Id) return Boolean
is
Typ : constant Entity_Id := Etype (P);
begin
if Is_Access_Type (Typ) then
return Has_Independent_Components (Designated_Type (Typ));
elsif Has_Independent_Components (Typ) then
return True;
elsif Is_Entity_Name (P)
and then Has_Independent_Components (Entity (P))
then
return True;
else
return False;
end if;
end Prefix_Has_Independent_Components;
-- Start of processing for Is_Independent_Object
begin
if Is_Entity_Name (N) then
return Is_Independent_Object_Entity (Entity (N));
elsif Is_Independent (Etype (N)) then
return True;
elsif Nkind (N) = N_Indexed_Component then
return Prefix_Has_Independent_Components (Prefix (N));
elsif Nkind (N) = N_Selected_Component then
return Prefix_Has_Independent_Components (Prefix (N))
or else Is_Independent (Entity (Selector_Name (N)));
else
return False;
end if;
end Is_Independent_Object;
----------------------------
-- Is_Inherited_Operation --
----------------------------
function Is_Inherited_Operation (E : Entity_Id) return Boolean is
pragma Assert (Is_Overloadable (E));
Kind : constant Node_Kind := Nkind (Parent (E));
begin
return Kind = N_Full_Type_Declaration
or else Kind = N_Private_Extension_Declaration
or else Kind = N_Subtype_Declaration
or else (Ekind (E) = E_Enumeration_Literal
and then Is_Derived_Type (Etype (E)));
end Is_Inherited_Operation;
-------------------------------------
-- Is_Inherited_Operation_For_Type --
-------------------------------------
function Is_Inherited_Operation_For_Type
(E : Entity_Id;
Typ : Entity_Id) return Boolean
is
begin
-- Check that the operation has been created by the type declaration
return Is_Inherited_Operation (E)
and then Defining_Identifier (Parent (E)) = Typ;
end Is_Inherited_Operation_For_Type;
--------------------------------------
-- Is_Inlinable_Expression_Function --
--------------------------------------
function Is_Inlinable_Expression_Function
(Subp : Entity_Id) return Boolean
is
Return_Expr : Node_Id;
begin
if Is_Expression_Function_Or_Completion (Subp)
and then Has_Pragma_Inline_Always (Subp)
and then Needs_No_Actuals (Subp)
and then No (Contract (Subp))
and then not Is_Dispatching_Operation (Subp)
and then Needs_Finalization (Etype (Subp))
and then not Is_Class_Wide_Type (Etype (Subp))
and then not Has_Invariants (Etype (Subp))
and then Present (Subprogram_Body (Subp))
and then Was_Expression_Function (Subprogram_Body (Subp))
then
Return_Expr := Expression_Of_Expression_Function (Subp);
-- The returned object must not have a qualified expression and its
-- nominal subtype must be statically compatible with the result
-- subtype of the expression function.
return
Nkind (Return_Expr) = N_Identifier
and then Etype (Return_Expr) = Etype (Subp);
end if;
return False;
end Is_Inlinable_Expression_Function;
-----------------
-- Is_Iterator --
-----------------
function Is_Iterator (Typ : Entity_Id) return Boolean is
function Denotes_Iterator (Iter_Typ : Entity_Id) return Boolean;
-- Determine whether type Iter_Typ is a predefined forward or reversible
-- iterator.
----------------------
-- Denotes_Iterator --
----------------------
function Denotes_Iterator (Iter_Typ : Entity_Id) return Boolean is
begin
-- Check that the name matches, and that the ultimate ancestor is in
-- a predefined unit, i.e the one that declares iterator interfaces.
return
Chars (Iter_Typ) in Name_Forward_Iterator | Name_Reversible_Iterator
and then In_Predefined_Unit (Root_Type (Iter_Typ));
end Denotes_Iterator;
-- Local variables
Iface_Elmt : Elmt_Id;
Ifaces : Elist_Id;
-- Start of processing for Is_Iterator
begin
-- The type may be a subtype of a descendant of the proper instance of
-- the predefined interface type, so we must use the root type of the
-- given type. The same is done for Is_Reversible_Iterator.
if Is_Class_Wide_Type (Typ)
and then Denotes_Iterator (Root_Type (Typ))
then
return True;
elsif not Is_Tagged_Type (Typ) or else not Is_Derived_Type (Typ) then
return False;
elsif Present (Find_Value_Of_Aspect (Typ, Aspect_Iterable)) then
return True;
else
Collect_Interfaces (Typ, Ifaces);
Iface_Elmt := First_Elmt (Ifaces);
while Present (Iface_Elmt) loop
if Denotes_Iterator (Node (Iface_Elmt)) then
return True;
end if;
Next_Elmt (Iface_Elmt);
end loop;
return False;
end if;
end Is_Iterator;
----------------------------
-- Is_Iterator_Over_Array --
----------------------------
function Is_Iterator_Over_Array (N : Node_Id) return Boolean is
Container : constant Node_Id := Name (N);
Container_Typ : constant Entity_Id := Base_Type (Etype (Container));
begin
return Is_Array_Type (Container_Typ);
end Is_Iterator_Over_Array;
--------------------------
-- Known_To_Be_Assigned --
--------------------------
function Known_To_Be_Assigned
(N : Node_Id;
Only_LHS : Boolean := False) return Boolean
is
function Known_Assn (N : Node_Id) return Boolean is
(Known_To_Be_Assigned (N, Only_LHS));
-- Local function to simplify the passing of parameters for recursive
-- calls.
P : constant Node_Id := Parent (N);
Form : Entity_Id := Empty;
Call : Node_Id := Empty;
-- Start of processing for Known_To_Be_Assigned
begin
-- Check for out parameters
Find_Actual (N, Form, Call);
if Present (Form) then
return Ekind (Form) /= E_In_Parameter and then not Only_LHS;
end if;
-- Otherwise look at the parent
case Nkind (P) is
-- Test left side of assignment
when N_Assignment_Statement =>
return N = Name (P);
-- Test prefix of component or attribute. Note that the prefix of an
-- explicit or implicit dereference cannot be an l-value. In the case
-- of a 'Read attribute, the reference can be an actual in the
-- argument list of the attribute.
when N_Attribute_Reference =>
return
not Only_LHS and then
((N = Prefix (P)
and then Name_Implies_Lvalue_Prefix (Attribute_Name (P)))
or else
Attribute_Name (P) = Name_Read);
-- For an expanded name, the name is an lvalue if the expanded name
-- is an lvalue, but the prefix is never an lvalue, since it is just
-- the scope where the name is found.
when N_Expanded_Name =>
if N = Prefix (P) then
return Known_Assn (P);
else
return False;
end if;
-- For a selected component A.B, A is certainly an lvalue if A.B is.
-- B is a little interesting, if we have A.B := 3, there is some
-- discussion as to whether B is an lvalue or not, we choose to say
-- it is. Note however that A is not an lvalue if it is of an access
-- type since this is an implicit dereference.
when N_Selected_Component =>
if N = Prefix (P)
and then Present (Etype (N))
and then Is_Access_Type (Etype (N))
then
return False;
else
return Known_Assn (P);
end if;
-- For an indexed component or slice, the index or slice bounds is
-- never an lvalue. The prefix is an lvalue if the indexed component
-- or slice is an lvalue, except if it is an access type, where we
-- have an implicit dereference.
when N_Indexed_Component | N_Slice =>
if N /= Prefix (P)
or else (Present (Etype (N)) and then Is_Access_Type (Etype (N)))
then
return False;
else
return Known_Assn (P);
end if;
-- Prefix of a reference is an lvalue if the reference is an lvalue
when N_Reference =>
return Known_Assn (P);
-- Prefix of explicit dereference is never an lvalue
when N_Explicit_Dereference =>
return False;
-- Test for appearing in a conversion that itself appears in an
-- lvalue context, since this should be an lvalue.
when N_Type_Conversion =>
return Known_Assn (P);
-- Test for appearance in object renaming declaration
when N_Object_Renaming_Declaration =>
return not Only_LHS;
-- All other references are definitely not lvalues
when others =>
return False;
end case;
end Known_To_Be_Assigned;
-----------------------------
-- Is_Library_Level_Entity --
-----------------------------
function Is_Library_Level_Entity (E : Entity_Id) return Boolean is
begin
-- The following is a small optimization, and it also properly handles
-- discriminals, which in task bodies might appear in expressions before
-- the corresponding procedure has been created, and which therefore do
-- not have an assigned scope.
if Is_Formal (E) then
return False;
-- If we somehow got an empty value for Scope, the tree must be
-- malformed. Rather than blow up we return True in this case.
elsif No (Scope (E)) then
return True;
-- Handle loops since Enclosing_Dynamic_Scope skips them; required to
-- properly handle entities local to quantified expressions in library
-- level specifications.
elsif Ekind (Scope (E)) = E_Loop then
return False;
end if;
-- Normal test is simply that the enclosing dynamic scope is Standard
return Enclosing_Dynamic_Scope (E) = Standard_Standard;
end Is_Library_Level_Entity;
--------------------------------
-- Is_Limited_Class_Wide_Type --
--------------------------------
function Is_Limited_Class_Wide_Type (Typ : Entity_Id) return Boolean is
begin
return
Is_Class_Wide_Type (Typ)
and then (Is_Limited_Type (Typ) or else From_Limited_With (Typ));
end Is_Limited_Class_Wide_Type;
---------------------------------
-- Is_Local_Variable_Reference --
---------------------------------
function Is_Local_Variable_Reference (Expr : Node_Id) return Boolean is
begin
if not Is_Entity_Name (Expr) then
return False;
else
declare
Ent : constant Entity_Id := Entity (Expr);
Sub : constant Entity_Id := Enclosing_Subprogram (Ent);
begin
if Ekind (Ent)
not in E_Variable | E_In_Out_Parameter | E_Out_Parameter
then
return False;
else
return Present (Sub) and then Sub = Current_Subprogram;
end if;
end;
end if;
end Is_Local_Variable_Reference;
---------------
-- Is_Master --
---------------
function Is_Master (N : Node_Id) return Boolean is
Disable_Subexpression_Masters : constant Boolean := True;
begin
if Nkind (N) in N_Subprogram_Body | N_Task_Body | N_Entry_Body
or else Is_Statement (N)
then
return True;
end if;
-- We avoid returning True when the master is a subexpression described
-- in RM 7.6.1(3/2) for the proposes of accessibility level calculation
-- in Accessibility_Level_Helper.Innermost_Master_Scope_Depth ???
if not Disable_Subexpression_Masters
and then Nkind (N) in N_Subexpr
then
declare
Par : Node_Id := N;
subtype N_Simple_Statement_Other_Than_Simple_Return
is Node_Kind with Static_Predicate =>
N_Simple_Statement_Other_Than_Simple_Return
in N_Abort_Statement
| N_Assignment_Statement
| N_Code_Statement
| N_Delay_Statement
| N_Entry_Call_Statement
| N_Free_Statement
| N_Goto_Statement
| N_Null_Statement
| N_Raise_Statement
| N_Requeue_Statement
| N_Exit_Statement
| N_Procedure_Call_Statement;
begin
while Present (Par) loop
Par := Parent (Par);
if Nkind (Par) in N_Subexpr |
N_Simple_Statement_Other_Than_Simple_Return
then
return False;
end if;
end loop;
return True;
end;
end if;
return False;
end Is_Master;
-----------------------
-- Is_Name_Reference --
-----------------------
function Is_Name_Reference (N : Node_Id) return Boolean is
begin
if Is_Entity_Name (N) then
return Present (Entity (N)) and then Is_Object (Entity (N));
end if;
case Nkind (N) is
when N_Indexed_Component
| N_Slice
=>
return
Is_Name_Reference (Prefix (N))
or else Is_Access_Type (Etype (Prefix (N)));
-- Attributes 'Input, 'Old and 'Result produce objects
when N_Attribute_Reference =>
return Attribute_Name (N) in Name_Input | Name_Old | Name_Result;
when N_Selected_Component =>
return
Is_Name_Reference (Selector_Name (N))
and then
(Is_Name_Reference (Prefix (N))
or else Is_Access_Type (Etype (Prefix (N))));
when N_Explicit_Dereference =>
return True;
-- A view conversion of a tagged name is a name reference
when N_Type_Conversion =>
return
Is_Tagged_Type (Etype (Subtype_Mark (N)))
and then Is_Tagged_Type (Etype (Expression (N)))
and then Is_Name_Reference (Expression (N));
-- An unchecked type conversion is considered to be a name if the
-- operand is a name (this construction arises only as a result of
-- expansion activities).
when N_Unchecked_Type_Conversion =>
return Is_Name_Reference (Expression (N));
when others =>
return False;
end case;
end Is_Name_Reference;
--------------------------
-- Is_Newly_Constructed --
--------------------------
function Is_Newly_Constructed
(Exp : Node_Id; Context_Requires_NC : Boolean) return Boolean
is
Original_Exp : constant Node_Id := Original_Node (Exp);
function Is_NC (Exp : Node_Id) return Boolean is
(Is_Newly_Constructed (Exp, Context_Requires_NC));
-- If the context requires that the expression shall be newly
-- constructed, then "True" is a good result in the sense that the
-- expression satisfies the requirements of the context (and "False"
-- is analogously a bad result). If the context requires that the
-- expression shall *not* be newly constructed, then things are
-- reversed: "False" is the good value and "True" is the bad value.
Good_Result : constant Boolean := Context_Requires_NC;
Bad_Result : constant Boolean := not Good_Result;
begin
case Nkind (Original_Exp) is
when N_Aggregate
| N_Extension_Aggregate
| N_Function_Call
| N_Op
=>
return True;
when N_Identifier =>
return Present (Entity (Original_Exp))
and then Ekind (Entity (Original_Exp)) = E_Function;
when N_Qualified_Expression =>
return Is_NC (Expression (Original_Exp));
when N_Type_Conversion
| N_Unchecked_Type_Conversion
=>
if Is_View_Conversion (Original_Exp) then
return Is_NC (Expression (Original_Exp));
elsif not Comes_From_Source (Exp) then
if Exp /= Original_Exp then
return Is_NC (Original_Exp);
else
return Is_NC (Expression (Original_Exp));
end if;
else
return False;
end if;
when N_Explicit_Dereference
| N_Indexed_Component
| N_Selected_Component
=>
return Nkind (Exp) = N_Function_Call;
-- A use of 'Input is a function call, hence allowed. Normally the
-- attribute will be changed to a call, but the attribute by itself
-- can occur with -gnatc.
when N_Attribute_Reference =>
return Attribute_Name (Original_Exp) = Name_Input;
-- "return raise ..." is OK
when N_Raise_Expression =>
return Good_Result;
-- For a case expression, all dependent expressions must be legal
when N_Case_Expression =>
declare
Alt : Node_Id;
begin
Alt := First (Alternatives (Original_Exp));
while Present (Alt) loop
if Is_NC (Expression (Alt)) = Bad_Result then
return Bad_Result;
end if;
Next (Alt);
end loop;
return Good_Result;
end;
-- For an if expression, all dependent expressions must be legal
when N_If_Expression =>
declare
Then_Expr : constant Node_Id :=
Next (First (Expressions (Original_Exp)));
Else_Expr : constant Node_Id := Next (Then_Expr);
begin
if (Is_NC (Then_Expr) = Bad_Result)
or else (Is_NC (Else_Expr) = Bad_Result)
then
return Bad_Result;
else
return Good_Result;
end if;
end;
when others =>
return False;
end case;
end Is_Newly_Constructed;
------------------------------------
-- Is_Non_Preelaborable_Construct --
------------------------------------
function Is_Non_Preelaborable_Construct (N : Node_Id) return Boolean is
-- NOTE: the routines within Is_Non_Preelaborable_Construct are
-- intentionally unnested to avoid deep indentation of code.
Non_Preelaborable : exception;
-- This exception is raised when the construct violates preelaborability
-- to terminate the recursion.
procedure Visit (Nod : Node_Id);
-- Semantically inspect construct Nod to determine whether it violates
-- preelaborability. This routine raises Non_Preelaborable.
procedure Visit_List (List : List_Id);
pragma Inline (Visit_List);
-- Invoke Visit on each element of list List. This routine raises
-- Non_Preelaborable.
procedure Visit_Pragma (Prag : Node_Id);
pragma Inline (Visit_Pragma);
-- Semantically inspect pragma Prag to determine whether it violates
-- preelaborability. This routine raises Non_Preelaborable.
procedure Visit_Subexpression (Expr : Node_Id);
pragma Inline (Visit_Subexpression);
-- Semantically inspect expression Expr to determine whether it violates
-- preelaborability. This routine raises Non_Preelaborable.
-----------
-- Visit --
-----------
procedure Visit (Nod : Node_Id) is
begin
case Nkind (Nod) is
-- Declarations
when N_Component_Declaration =>
-- Defining_Identifier is left out because it is not relevant
-- for preelaborability.
Visit (Component_Definition (Nod));
Visit (Expression (Nod));
when N_Derived_Type_Definition =>
-- Interface_List is left out because it is not relevant for
-- preelaborability.
Visit (Record_Extension_Part (Nod));
Visit (Subtype_Indication (Nod));
when N_Entry_Declaration =>
-- A protected type with at leat one entry is not preelaborable
-- while task types are never preelaborable. This renders entry
-- declarations non-preelaborable.
raise Non_Preelaborable;
when N_Full_Type_Declaration =>
-- Defining_Identifier and Discriminant_Specifications are left
-- out because they are not relevant for preelaborability.
Visit (Type_Definition (Nod));
when N_Function_Instantiation
| N_Package_Instantiation
| N_Procedure_Instantiation
=>
-- Defining_Unit_Name and Name are left out because they are
-- not relevant for preelaborability.
Visit_List (Generic_Associations (Nod));
when N_Object_Declaration =>
-- Defining_Identifier is left out because it is not relevant
-- for preelaborability.
Visit (Object_Definition (Nod));
if Has_Init_Expression (Nod) then
Visit (Expression (Nod));
elsif not Has_Preelaborable_Initialization
(Etype (Defining_Entity (Nod)))
then
raise Non_Preelaborable;
end if;
when N_Private_Extension_Declaration
| N_Subtype_Declaration
=>
-- Defining_Identifier, Discriminant_Specifications, and
-- Interface_List are left out because they are not relevant
-- for preelaborability.
Visit (Subtype_Indication (Nod));
when N_Protected_Type_Declaration
| N_Single_Protected_Declaration
=>
-- Defining_Identifier, Discriminant_Specifications, and
-- Interface_List are left out because they are not relevant
-- for preelaborability.
Visit (Protected_Definition (Nod));
-- A [single] task type is never preelaborable
when N_Single_Task_Declaration
| N_Task_Type_Declaration
=>
raise Non_Preelaborable;
-- Pragmas
when N_Pragma =>
Visit_Pragma (Nod);
-- Statements
when N_Statement_Other_Than_Procedure_Call =>
if Nkind (Nod) /= N_Null_Statement then
raise Non_Preelaborable;
end if;
-- Subexpressions
when N_Subexpr =>
Visit_Subexpression (Nod);
-- Special
when N_Access_To_Object_Definition =>
Visit (Subtype_Indication (Nod));
when N_Case_Expression_Alternative =>
Visit (Expression (Nod));
Visit_List (Discrete_Choices (Nod));
when N_Component_Definition =>
Visit (Access_Definition (Nod));
Visit (Subtype_Indication (Nod));
when N_Component_List =>
Visit_List (Component_Items (Nod));
Visit (Variant_Part (Nod));
when N_Constrained_Array_Definition =>
Visit_List (Discrete_Subtype_Definitions (Nod));
Visit (Component_Definition (Nod));
when N_Delta_Constraint
| N_Digits_Constraint
=>
-- Delta_Expression and Digits_Expression are left out because
-- they are not relevant for preelaborability.
Visit (Range_Constraint (Nod));
when N_Discriminant_Specification =>
-- Defining_Identifier and Expression are left out because they
-- are not relevant for preelaborability.
Visit (Discriminant_Type (Nod));
when N_Generic_Association =>
-- Selector_Name is left out because it is not relevant for
-- preelaborability.
Visit (Explicit_Generic_Actual_Parameter (Nod));
when N_Index_Or_Discriminant_Constraint =>
Visit_List (Constraints (Nod));
when N_Iterator_Specification =>
-- Defining_Identifier is left out because it is not relevant
-- for preelaborability.
Visit (Name (Nod));
Visit (Subtype_Indication (Nod));
when N_Loop_Parameter_Specification =>
-- Defining_Identifier is left out because it is not relevant
-- for preelaborability.
Visit (Discrete_Subtype_Definition (Nod));
when N_Parameter_Association =>
Visit (Explicit_Actual_Parameter (N));
when N_Protected_Definition =>
-- End_Label is left out because it is not relevant for
-- preelaborability.
Visit_List (Private_Declarations (Nod));
Visit_List (Visible_Declarations (Nod));
when N_Range_Constraint =>
Visit (Range_Expression (Nod));
when N_Record_Definition
| N_Variant
=>
-- End_Label, Discrete_Choices, and Interface_List are left out
-- because they are not relevant for preelaborability.
Visit (Component_List (Nod));
when N_Subtype_Indication =>
-- Subtype_Mark is left out because it is not relevant for
-- preelaborability.
Visit (Constraint (Nod));
when N_Unconstrained_Array_Definition =>
-- Subtype_Marks is left out because it is not relevant for
-- preelaborability.
Visit (Component_Definition (Nod));
when N_Variant_Part =>
-- Name is left out because it is not relevant for
-- preelaborability.
Visit_List (Variants (Nod));
-- Default
when others =>
null;
end case;
end Visit;
----------------
-- Visit_List --
----------------
procedure Visit_List (List : List_Id) is
Nod : Node_Id;
begin
if Present (List) then
Nod := First (List);
while Present (Nod) loop
Visit (Nod);
Next (Nod);
end loop;
end if;
end Visit_List;
------------------
-- Visit_Pragma --
------------------
procedure Visit_Pragma (Prag : Node_Id) is
begin
case Get_Pragma_Id (Prag) is
when Pragma_Assert
| Pragma_Assert_And_Cut
| Pragma_Assume
| Pragma_Async_Readers
| Pragma_Async_Writers
| Pragma_Attribute_Definition
| Pragma_Check
| Pragma_Constant_After_Elaboration
| Pragma_CPU
| Pragma_Deadline_Floor
| Pragma_Dispatching_Domain
| Pragma_Effective_Reads
| Pragma_Effective_Writes
| Pragma_Extensions_Visible
| Pragma_Ghost
| Pragma_Secondary_Stack_Size
| Pragma_Task_Name
| Pragma_Volatile_Function
=>
Visit_List (Pragma_Argument_Associations (Prag));
-- Default
when others =>
null;
end case;
end Visit_Pragma;
-------------------------
-- Visit_Subexpression --
-------------------------
procedure Visit_Subexpression (Expr : Node_Id) is
procedure Visit_Aggregate (Aggr : Node_Id);
pragma Inline (Visit_Aggregate);
-- Semantically inspect aggregate Aggr to determine whether it
-- violates preelaborability.
---------------------
-- Visit_Aggregate --
---------------------
procedure Visit_Aggregate (Aggr : Node_Id) is
begin
if not Is_Preelaborable_Aggregate (Aggr) then
raise Non_Preelaborable;
end if;
end Visit_Aggregate;
-- Start of processing for Visit_Subexpression
begin
case Nkind (Expr) is
when N_Allocator
| N_Qualified_Expression
| N_Type_Conversion
| N_Unchecked_Expression
| N_Unchecked_Type_Conversion
=>
-- Subpool_Handle_Name and Subtype_Mark are left out because
-- they are not relevant for preelaborability.
Visit (Expression (Expr));
when N_Aggregate
| N_Extension_Aggregate
=>
Visit_Aggregate (Expr);
when N_Attribute_Reference
| N_Explicit_Dereference
| N_Reference
=>
-- Attribute_Name and Expressions are left out because they are
-- not relevant for preelaborability.
Visit (Prefix (Expr));
when N_Case_Expression =>
-- End_Span is left out because it is not relevant for
-- preelaborability.
Visit_List (Alternatives (Expr));
Visit (Expression (Expr));
when N_Delta_Aggregate =>
Visit_Aggregate (Expr);
Visit (Expression (Expr));
when N_Expression_With_Actions =>
Visit_List (Actions (Expr));
Visit (Expression (Expr));
when N_Function_Call =>
-- Ada 2022 (AI12-0175): Calls to certain functions that are
-- essentially unchecked conversions are preelaborable.
if Ada_Version >= Ada_2022
and then Nkind (Expr) = N_Function_Call
and then Is_Entity_Name (Name (Expr))
and then Is_Preelaborable_Function (Entity (Name (Expr)))
then
Visit_List (Parameter_Associations (Expr));
else
raise Non_Preelaborable;
end if;
when N_If_Expression =>
Visit_List (Expressions (Expr));
when N_Quantified_Expression =>
Visit (Condition (Expr));
Visit (Iterator_Specification (Expr));
Visit (Loop_Parameter_Specification (Expr));
when N_Range =>
Visit (High_Bound (Expr));
Visit (Low_Bound (Expr));
when N_Slice =>
Visit (Discrete_Range (Expr));
Visit (Prefix (Expr));
-- Default
when others =>
-- The evaluation of an object name is not preelaborable,
-- unless the name is a static expression (checked further
-- below), or statically denotes a discriminant.
if Is_Entity_Name (Expr) then
Object_Name : declare
Id : constant Entity_Id := Entity (Expr);
begin
if Is_Object (Id) then
if Ekind (Id) = E_Discriminant then
null;
elsif Ekind (Id) in E_Constant | E_In_Parameter
and then Present (Discriminal_Link (Id))
then
null;
else
raise Non_Preelaborable;
end if;
end if;
end Object_Name;
-- A non-static expression is not preelaborable
elsif not Is_OK_Static_Expression (Expr) then
raise Non_Preelaborable;
end if;
end case;
end Visit_Subexpression;
-- Start of processing for Is_Non_Preelaborable_Construct
begin
Visit (N);
-- At this point it is known that the construct is preelaborable
return False;
exception
-- The elaboration of the construct performs an action which violates
-- preelaborability.
when Non_Preelaborable =>
return True;
end Is_Non_Preelaborable_Construct;
---------------------------------
-- Is_Nontrivial_DIC_Procedure --
---------------------------------
function Is_Nontrivial_DIC_Procedure (Id : Entity_Id) return Boolean is
Body_Decl : Node_Id;
Stmt : Node_Id;
begin
if Ekind (Id) = E_Procedure and then Is_DIC_Procedure (Id) then
Body_Decl :=
Unit_Declaration_Node
(Corresponding_Body (Unit_Declaration_Node (Id)));
-- The body of the Default_Initial_Condition procedure must contain
-- at least one statement, otherwise the generation of the subprogram
-- body failed.
pragma Assert (Present (Handled_Statement_Sequence (Body_Decl)));
-- To qualify as nontrivial, the first statement of the procedure
-- must be a check in the form of an if statement. If the original
-- Default_Initial_Condition expression was folded, then the first
-- statement is not a check.
Stmt := First (Statements (Handled_Statement_Sequence (Body_Decl)));
return
Nkind (Stmt) = N_If_Statement
and then Nkind (Original_Node (Stmt)) = N_Pragma;
end if;
return False;
end Is_Nontrivial_DIC_Procedure;
-----------------------
-- Is_Null_Extension --
-----------------------
function Is_Null_Extension
(T : Entity_Id; Ignore_Privacy : Boolean := False) return Boolean
is
Type_Decl : Node_Id;
Type_Def : Node_Id;
begin
if Ignore_Privacy then
Type_Decl := Parent (Underlying_Type (Base_Type (T)));
else
Type_Decl := Parent (Base_Type (T));
if Nkind (Type_Decl) /= N_Full_Type_Declaration then
return False;
end if;
end if;
pragma Assert (Nkind (Type_Decl) = N_Full_Type_Declaration);
Type_Def := Type_Definition (Type_Decl);
if Present (Discriminant_Specifications (Type_Decl))
or else Nkind (Type_Def) /= N_Derived_Type_Definition
or else not Is_Tagged_Type (T)
or else No (Record_Extension_Part (Type_Def))
then
return False;
end if;
return Is_Null_Record_Definition (Record_Extension_Part (Type_Def));
end Is_Null_Extension;
--------------------------
-- Is_Null_Extension_Of --
--------------------------
function Is_Null_Extension_Of
(Descendant, Ancestor : Entity_Id) return Boolean
is
Ancestor_Type : constant Entity_Id
:= Underlying_Type (Base_Type (Ancestor));
Descendant_Type : Entity_Id := Underlying_Type (Base_Type (Descendant));
begin
pragma Assert (Descendant_Type /= Ancestor_Type);
while Descendant_Type /= Ancestor_Type loop
if not Is_Null_Extension
(Descendant_Type, Ignore_Privacy => True)
then
return False;
end if;
Descendant_Type := Etype (Subtype_Indication
(Type_Definition (Parent (Descendant_Type))));
Descendant_Type := Underlying_Type (Base_Type (Descendant_Type));
end loop;
return True;
end Is_Null_Extension_Of;
-------------------------------
-- Is_Null_Record_Definition --
-------------------------------
function Is_Null_Record_Definition (Record_Def : Node_Id) return Boolean is
Item : Node_Id;
begin
-- Testing Null_Present is just an optimization, not required.
if Null_Present (Record_Def) then
return True;
elsif Present (Variant_Part (Component_List (Record_Def))) then
return False;
elsif not Present (Component_List (Record_Def)) then
return True;
end if;
Item := First (Component_Items (Component_List (Record_Def)));
while Present (Item) loop
if Nkind (Item) = N_Component_Declaration
and then Is_Internal_Name (Chars (Defining_Identifier (Item)))
then
null;
elsif Nkind (Item) = N_Pragma then
null;
else
return False;
end if;
Item := Next (Item);
end loop;
return True;
end Is_Null_Record_Definition;
-------------------------
-- Is_Null_Record_Type --
-------------------------
function Is_Null_Record_Type
(T : Entity_Id; Ignore_Privacy : Boolean := False) return Boolean
is
Decl : Node_Id;
Type_Def : Node_Id;
begin
if not Is_Record_Type (T) then
return False;
end if;
if Ignore_Privacy then
Decl := Parent (Underlying_Type (Base_Type (T)));
else
Decl := Parent (Base_Type (T));
if Nkind (Decl) /= N_Full_Type_Declaration then
return False;
end if;
end if;
pragma Assert (Nkind (Decl) = N_Full_Type_Declaration);
Type_Def := Type_Definition (Decl);
if Has_Discriminants (Defining_Identifier (Decl)) then
return False;
end if;
case Nkind (Type_Def) is
when N_Record_Definition =>
return Is_Null_Record_Definition (Type_Def);
when N_Derived_Type_Definition =>
if not Is_Null_Record_Type
(Etype (Subtype_Indication (Type_Def)),
Ignore_Privacy => Ignore_Privacy)
then
return False;
elsif not Is_Tagged_Type (T) then
return True;
else
return Is_Null_Extension (T, Ignore_Privacy => Ignore_Privacy);
end if;
when others =>
return False;
end case;
end Is_Null_Record_Type;
---------------------
-- Is_Object_Image --
---------------------
function Is_Object_Image (Prefix : Node_Id) return Boolean is
begin
-- Here we test for the case that the prefix is not a type and assume
-- if it is not then it must be a named value or an object reference.
-- This is because the parser always checks that prefixes of attributes
-- are named.
return not (Is_Entity_Name (Prefix)
and then Is_Type (Entity (Prefix))
and then not Is_Current_Instance (Prefix));
end Is_Object_Image;
-------------------------
-- Is_Object_Reference --
-------------------------
function Is_Object_Reference (N : Node_Id) return Boolean is
function Safe_Prefix (N : Node_Id) return Node_Id;
-- Return Prefix (N) unless it has been rewritten as an
-- N_Raise_xxx_Error node, in which case return its original node.
-----------------
-- Safe_Prefix --
-----------------
function Safe_Prefix (N : Node_Id) return Node_Id is
begin
if Nkind (Prefix (N)) in N_Raise_xxx_Error then
return Original_Node (Prefix (N));
else
return Prefix (N);
end if;
end Safe_Prefix;
begin
-- AI12-0068: Note that a current instance reference in a type or
-- subtype's aspect_specification is considered a value, not an object
-- (see RM 8.6(18/5)).
if Is_Entity_Name (N) then
return Present (Entity (N)) and then Is_Object (Entity (N))
and then not Is_Current_Instance_Reference_In_Type_Aspect (N);
else
case Nkind (N) is
when N_Indexed_Component
| N_Slice
=>
return
Is_Object_Reference (Safe_Prefix (N))
or else Is_Access_Type (Etype (Safe_Prefix (N)));
-- In Ada 95, a function call is a constant object; a procedure
-- call is not.
-- Note that predefined operators are functions as well, and so
-- are attributes that are (can be renamed as) functions.
when N_Function_Call
| N_Op
=>
return Etype (N) /= Standard_Void_Type;
-- Attributes references 'Loop_Entry, 'Old, 'Priority and 'Result
-- yield objects, even though they are not functions.
when N_Attribute_Reference =>
return
Attribute_Name (N) in Name_Loop_Entry
| Name_Old
| Name_Priority
| Name_Result
or else Is_Function_Attribute_Name (Attribute_Name (N));
when N_Selected_Component =>
return
Is_Object_Reference (Selector_Name (N))
and then
(Is_Object_Reference (Safe_Prefix (N))
or else Is_Access_Type (Etype (Safe_Prefix (N))));
-- An explicit dereference denotes an object, except that a
-- conditional expression gets turned into an explicit dereference
-- in some cases, and conditional expressions are not object
-- names.
when N_Explicit_Dereference =>
return Nkind (Original_Node (N)) not in
N_Case_Expression | N_If_Expression;
-- A view conversion of a tagged object is an object reference
when N_Type_Conversion =>
if Ada_Version <= Ada_2012 then
-- A view conversion of a tagged object is an object
-- reference.
return Is_Tagged_Type (Etype (Subtype_Mark (N)))
and then Is_Tagged_Type (Etype (Expression (N)))
and then Is_Object_Reference (Expression (N));
else
-- AI12-0226: In Ada 2022 a value conversion of an object is
-- an object.
return Is_Object_Reference (Expression (N));
end if;
-- An unchecked type conversion is considered to be an object if
-- the operand is an object (this construction arises only as a
-- result of expansion activities).
when N_Unchecked_Type_Conversion =>
return True;
-- AI05-0003: In Ada 2012 a qualified expression is a name.
-- This allows disambiguation of function calls and the use
-- of aggregates in more contexts.
when N_Qualified_Expression =>
return Ada_Version >= Ada_2012
and then Is_Object_Reference (Expression (N));
-- In Ada 95 an aggregate is an object reference
when N_Aggregate
| N_Delta_Aggregate
| N_Extension_Aggregate
=>
return Ada_Version >= Ada_95;
-- A string literal is not an object reference, but it might come
-- from rewriting of an object reference, e.g. from folding of an
-- aggregate.
when N_String_Literal =>
return Is_Rewrite_Substitution (N)
and then Is_Object_Reference (Original_Node (N));
-- AI12-0125: Target name represents a constant object
when N_Target_Name =>
return True;
when others =>
return False;
end case;
end if;
end Is_Object_Reference;
-----------------------------------
-- Is_OK_Variable_For_Out_Formal --
-----------------------------------
function Is_OK_Variable_For_Out_Formal (AV : Node_Id) return Boolean is
begin
Note_Possible_Modification (AV, Sure => True);
-- We must reject parenthesized variable names. Comes_From_Source is
-- checked because there are currently cases where the compiler violates
-- this rule (e.g. passing a task object to its controlled Initialize
-- routine). This should be properly documented in sinfo???
if Paren_Count (AV) > 0 and then Comes_From_Source (AV) then
return False;
-- A variable is always allowed
elsif Is_Variable (AV) then
return True;
-- Generalized indexing operations are rewritten as explicit
-- dereferences, and it is only during resolution that we can
-- check whether the context requires an access_to_variable type.
elsif Nkind (AV) = N_Explicit_Dereference
and then Present (Etype (Original_Node (AV)))
and then Has_Implicit_Dereference (Etype (Original_Node (AV)))
and then Ada_Version >= Ada_2012
then
return not Is_Access_Constant (Etype (Prefix (AV)));
-- Unchecked conversions are allowed only if they come from the
-- generated code, which sometimes uses unchecked conversions for out
-- parameters in cases where code generation is unaffected. We tell
-- source unchecked conversions by seeing if they are rewrites of
-- an original Unchecked_Conversion function call, or of an explicit
-- conversion of a function call or an aggregate (as may happen in the
-- expansion of a packed array aggregate).
elsif Nkind (AV) = N_Unchecked_Type_Conversion then
if Nkind (Original_Node (AV)) in N_Function_Call | N_Aggregate then
return False;
elsif Comes_From_Source (AV)
and then Nkind (Original_Node (Expression (AV))) = N_Function_Call
then
return False;
elsif Nkind (Original_Node (AV)) = N_Type_Conversion then
return Is_OK_Variable_For_Out_Formal (Expression (AV));
else
return True;
end if;
-- Normal type conversions are allowed if argument is a variable
elsif Nkind (AV) = N_Type_Conversion then
if Is_Variable (Expression (AV))
and then Paren_Count (Expression (AV)) = 0
then
Note_Possible_Modification (Expression (AV), Sure => True);
return True;
-- We also allow a non-parenthesized expression that raises
-- constraint error if it rewrites what used to be a variable
elsif Raises_Constraint_Error (Expression (AV))
and then Paren_Count (Expression (AV)) = 0
and then Is_Variable (Original_Node (Expression (AV)))
then
return True;
-- Type conversion of something other than a variable
else
return False;
end if;
-- If this node is rewritten, then test the original form, if that is
-- OK, then we consider the rewritten node OK (for example, if the
-- original node is a conversion, then Is_Variable will not be true
-- but we still want to allow the conversion if it converts a variable).
elsif Is_Rewrite_Substitution (AV) then
return Is_OK_Variable_For_Out_Formal (Original_Node (AV));
-- All other non-variables are rejected
else
return False;
end if;
end Is_OK_Variable_For_Out_Formal;
----------------------------
-- Is_OK_Volatile_Context --
----------------------------
function Is_OK_Volatile_Context
(Context : Node_Id;
Obj_Ref : Node_Id;
Check_Actuals : Boolean) return Boolean
is
function Is_Protected_Operation_Call (Nod : Node_Id) return Boolean;
-- Determine whether an arbitrary node denotes a call to a protected
-- entry, function, or procedure in prefixed form where the prefix is
-- Obj_Ref.
function Within_Check (Nod : Node_Id) return Boolean;
-- Determine whether an arbitrary node appears in a check node
function Within_Volatile_Function (Id : Entity_Id) return Boolean;
-- Determine whether an arbitrary entity appears in a volatile function
---------------------------------
-- Is_Protected_Operation_Call --
---------------------------------
function Is_Protected_Operation_Call (Nod : Node_Id) return Boolean is
Pref : Node_Id;
Subp : Node_Id;
begin
-- A call to a protected operations retains its selected component
-- form as opposed to other prefixed calls that are transformed in
-- expanded names.
if Nkind (Nod) = N_Selected_Component then
Pref := Prefix (Nod);
Subp := Selector_Name (Nod);
return
Pref = Obj_Ref
and then Present (Etype (Pref))
and then Is_Protected_Type (Etype (Pref))
and then Is_Entity_Name (Subp)
and then Present (Entity (Subp))
and then Ekind (Entity (Subp)) in
E_Entry | E_Entry_Family | E_Function | E_Procedure;
else
return False;
end if;
end Is_Protected_Operation_Call;
------------------
-- Within_Check --
------------------
function Within_Check (Nod : Node_Id) return Boolean is
Par : Node_Id;
begin
-- Climb the parent chain looking for a check node
Par := Nod;
while Present (Par) loop
if Nkind (Par) in N_Raise_xxx_Error then
return True;
-- Prevent the search from going too far
elsif Is_Body_Or_Package_Declaration (Par) then
exit;
end if;
Par := Parent (Par);
end loop;
return False;
end Within_Check;
------------------------------
-- Within_Volatile_Function --
------------------------------
function Within_Volatile_Function (Id : Entity_Id) return Boolean is
pragma Assert (Ekind (Id) = E_Return_Statement);
Func_Id : constant Entity_Id := Return_Applies_To (Id);
begin
pragma Assert (Ekind (Func_Id) in E_Function | E_Generic_Function);
return Is_Volatile_Function (Func_Id);
end Within_Volatile_Function;
-- Local variables
Obj_Id : Entity_Id;
-- Start of processing for Is_OK_Volatile_Context
begin
-- Ignore context restriction when doing preanalysis, e.g. on a copy of
-- an expression function, because this copy is not fully decorated and
-- it is not possible to reliably decide the legality of the context.
-- Any violations will be reported anyway when doing the full analysis.
if not Full_Analysis then
return True;
end if;
-- For actual parameters within explicit parameter associations switch
-- the context to the corresponding subprogram call.
if Nkind (Context) = N_Parameter_Association then
return Is_OK_Volatile_Context (Context => Parent (Context),
Obj_Ref => Obj_Ref,
Check_Actuals => Check_Actuals);
-- The volatile object appears on either side of an assignment
elsif Nkind (Context) = N_Assignment_Statement then
return True;
-- The volatile object is part of the initialization expression of
-- another object.
elsif Nkind (Context) = N_Object_Declaration
and then Present (Expression (Context))
and then Expression (Context) = Obj_Ref
and then Nkind (Parent (Context)) /= N_Expression_With_Actions
then
Obj_Id := Defining_Entity (Context);
-- The volatile object acts as the initialization expression of an
-- extended return statement. This is valid context as long as the
-- function is volatile.
if Is_Return_Object (Obj_Id) then
return Within_Volatile_Function (Scope (Obj_Id));
-- Otherwise this is a normal object initialization
else
return True;
end if;
-- The volatile object acts as the name of a renaming declaration
elsif Nkind (Context) = N_Object_Renaming_Declaration
and then Name (Context) = Obj_Ref
then
return True;
-- The volatile object appears as an actual parameter in a call to an
-- instance of Unchecked_Conversion whose result is renamed.
elsif Nkind (Context) = N_Function_Call
and then Is_Entity_Name (Name (Context))
and then Is_Unchecked_Conversion_Instance (Entity (Name (Context)))
and then Nkind (Parent (Context)) = N_Object_Renaming_Declaration
then
return True;
-- The volatile object is actually the prefix in a protected entry,
-- function, or procedure call.
elsif Is_Protected_Operation_Call (Context) then
return True;
-- The volatile object appears as the expression of a simple return
-- statement that applies to a volatile function.
elsif Nkind (Context) = N_Simple_Return_Statement
and then Expression (Context) = Obj_Ref
then
return
Within_Volatile_Function (Return_Statement_Entity (Context));
-- The volatile object appears as the prefix of a name occurring in a
-- non-interfering context.
elsif Nkind (Context) in
N_Attribute_Reference |
N_Explicit_Dereference |
N_Indexed_Component |
N_Selected_Component |
N_Slice
and then Prefix (Context) = Obj_Ref
and then Is_OK_Volatile_Context
(Context => Parent (Context),
Obj_Ref => Context,
Check_Actuals => Check_Actuals)
then
return True;
-- The volatile object appears as the prefix of attributes Address,
-- Alignment, Component_Size, First, First_Bit, Last, Last_Bit, Length,
-- Position, Size, Storage_Size.
elsif Nkind (Context) = N_Attribute_Reference
and then Prefix (Context) = Obj_Ref
and then Attribute_Name (Context) in Name_Address
| Name_Alignment
| Name_Component_Size
| Name_First
| Name_First_Bit
| Name_Last
| Name_Last_Bit
| Name_Length
| Name_Position
| Name_Size
| Name_Storage_Size
then
return True;
-- The volatile object appears as the expression of a type conversion
-- occurring in a non-interfering context.
elsif Nkind (Context) in N_Qualified_Expression
| N_Type_Conversion
| N_Unchecked_Type_Conversion
and then Expression (Context) = Obj_Ref
and then Is_OK_Volatile_Context
(Context => Parent (Context),
Obj_Ref => Context,
Check_Actuals => Check_Actuals)
then
return True;
-- The volatile object appears as the expression in a delay statement
elsif Nkind (Context) in N_Delay_Statement then
return True;
-- Allow references to volatile objects in various checks. This is not a
-- direct SPARK 2014 requirement.
elsif Within_Check (Context) then
return True;
-- References to effectively volatile objects that appear as actual
-- parameters in subprogram calls can be examined only after call itself
-- has been resolved. Before that, assume such references to be legal.
elsif Nkind (Context) in N_Subprogram_Call | N_Entry_Call_Statement then
if Check_Actuals then
declare
Call : Node_Id;
Formal : Entity_Id;
Subp : constant Entity_Id := Get_Called_Entity (Context);
begin
Find_Actual (Obj_Ref, Formal, Call);
pragma Assert (Call = Context);
-- An effectively volatile object may act as an actual when the
-- corresponding formal is of a non-scalar effectively volatile
-- type (SPARK RM 7.1.3(10)).
if not Is_Scalar_Type (Etype (Formal))
and then Is_Effectively_Volatile_For_Reading (Etype (Formal))
then
return True;
-- An effectively volatile object may act as an actual in a
-- call to an instance of Unchecked_Conversion. (SPARK RM
-- 7.1.3(10)).
elsif Is_Unchecked_Conversion_Instance (Subp) then
return True;
else
return False;
end if;
end;
else
return True;
end if;
else
return False;
end if;
end Is_OK_Volatile_Context;
------------------------------------
-- Is_Package_Contract_Annotation --
------------------------------------
function Is_Package_Contract_Annotation (Item : Node_Id) return Boolean is
Nam : Name_Id;
begin
if Nkind (Item) = N_Aspect_Specification then
Nam := Chars (Identifier (Item));
else pragma Assert (Nkind (Item) = N_Pragma);
Nam := Pragma_Name (Item);
end if;
return Nam = Name_Abstract_State
or else Nam = Name_Initial_Condition
or else Nam = Name_Initializes
or else Nam = Name_Refined_State;
end Is_Package_Contract_Annotation;
-----------------------------------
-- Is_Partially_Initialized_Type --
-----------------------------------
function Is_Partially_Initialized_Type
(Typ : Entity_Id;
Include_Implicit : Boolean := True) return Boolean
is
begin
if Is_Scalar_Type (Typ) then
return Has_Default_Aspect (Base_Type (Typ));
elsif Is_Access_Type (Typ) then
return Include_Implicit;
elsif Is_Array_Type (Typ) then
-- If component type is partially initialized, so is array type
if Has_Default_Aspect (Base_Type (Typ))
or else Is_Partially_Initialized_Type
(Component_Type (Typ), Include_Implicit)
then
return True;
-- Otherwise we are only partially initialized if we are fully
-- initialized (this is the empty array case, no point in us
-- duplicating that code here).
else
return Is_Fully_Initialized_Type (Typ);
end if;
elsif Is_Record_Type (Typ) then
-- A discriminated type is always partially initialized if in
-- all mode
if Has_Discriminants (Typ) and then Include_Implicit then
return True;
-- A tagged type is always partially initialized
elsif Is_Tagged_Type (Typ) then
return True;
-- Case of nondiscriminated record
else
declare
Comp : Entity_Id;
Component_Present : Boolean := False;
-- Set True if at least one component is present. If no
-- components are present, then record type is fully
-- initialized (another odd case, like the null array).
begin
-- Loop through components
Comp := First_Component (Typ);
while Present (Comp) loop
Component_Present := True;
-- If a component has an initialization expression then the
-- enclosing record type is partially initialized
if Present (Parent (Comp))
and then Present (Expression (Parent (Comp)))
then
return True;
-- If a component is of a type which is itself partially
-- initialized, then the enclosing record type is also.
elsif Is_Partially_Initialized_Type
(Etype (Comp), Include_Implicit)
then
return True;
end if;
Next_Component (Comp);
end loop;
-- No initialized components found. If we found any components
-- they were all uninitialized so the result is false.
if Component_Present then
return False;
-- But if we found no components, then all the components are
-- initialized so we consider the type to be initialized.
else
return True;
end if;
end;
end if;
-- Concurrent types are always fully initialized
elsif Is_Concurrent_Type (Typ) then
return True;
-- For a private type, go to underlying type. If there is no underlying
-- type then just assume this partially initialized. Not clear if this
-- can happen in a non-error case, but no harm in testing for this.
elsif Is_Private_Type (Typ) then
declare
U : constant Entity_Id := Underlying_Type (Typ);
begin
if No (U) then
return True;
else
return Is_Partially_Initialized_Type (U, Include_Implicit);
end if;
end;
-- For any other type (are there any?) assume partially initialized
else
return True;
end if;
end Is_Partially_Initialized_Type;
------------------------------------
-- Is_Potentially_Persistent_Type --
------------------------------------
function Is_Potentially_Persistent_Type (T : Entity_Id) return Boolean is
Comp : Entity_Id;
Indx : Node_Id;
begin
-- For private type, test corresponding full type
if Is_Private_Type (T) then
return Is_Potentially_Persistent_Type (Full_View (T));
-- Scalar types are potentially persistent
elsif Is_Scalar_Type (T) then
return True;
-- Record type is potentially persistent if not tagged and the types of
-- all it components are potentially persistent, and no component has
-- an initialization expression.
elsif Is_Record_Type (T)
and then not Is_Tagged_Type (T)
and then not Is_Partially_Initialized_Type (T)
then
Comp := First_Component (T);
while Present (Comp) loop
if not Is_Potentially_Persistent_Type (Etype (Comp)) then
return False;
else
Next_Entity (Comp);
end if;
end loop;
return True;
-- Array type is potentially persistent if its component type is
-- potentially persistent and if all its constraints are static.
elsif Is_Array_Type (T) then
if not Is_Potentially_Persistent_Type (Component_Type (T)) then
return False;
end if;
Indx := First_Index (T);
while Present (Indx) loop
if not Is_OK_Static_Subtype (Etype (Indx)) then
return False;
else
Next_Index (Indx);
end if;
end loop;
return True;
-- All other types are not potentially persistent
else
return False;
end if;
end Is_Potentially_Persistent_Type;
--------------------------------
-- Is_Potentially_Unevaluated --
--------------------------------
function Is_Potentially_Unevaluated (N : Node_Id) return Boolean is
function Has_Null_Others_Choice (Aggr : Node_Id) return Boolean;
-- Aggr is an array aggregate with static bounds and an others clause;
-- return True if the others choice of the given array aggregate does
-- not cover any component (i.e. is null).
function Immediate_Context_Implies_Is_Potentially_Unevaluated
(Expr : Node_Id) return Boolean;
-- Return True if the *immediate* context of this expression tells us
-- that it is potentially unevaluated; return False if the *immediate*
-- context doesn't provide an answer to this question and we need to
-- keep looking.
function Non_Static_Or_Null_Range (N : Node_Id) return Boolean;
-- Return True if the given range is nonstatic or null
----------------------------
-- Has_Null_Others_Choice --
----------------------------
function Has_Null_Others_Choice (Aggr : Node_Id) return Boolean is
Idx : constant Node_Id := First_Index (Etype (Aggr));
Hiv : constant Uint := Expr_Value (Type_High_Bound (Etype (Idx)));
Lov : constant Uint := Expr_Value (Type_Low_Bound (Etype (Idx)));
begin
declare
Intervals : constant Interval_Lists.Discrete_Interval_List :=
Interval_Lists.Aggregate_Intervals (Aggr);
begin
-- The others choice is null if, after normalization, we
-- have a single interval covering the whole aggregate.
return Intervals'Length = 1
and then
Intervals (Intervals'First).Low = Lov
and then
Intervals (Intervals'First).High = Hiv;
end;
-- If the aggregate is malformed (that is, indexes are not disjoint)
-- then no action is needed at this stage; the error will be reported
-- later by the frontend.
exception
when Interval_Lists.Intervals_Error =>
return False;
end Has_Null_Others_Choice;
----------------------------------------------------------
-- Immediate_Context_Implies_Is_Potentially_Unevaluated --
----------------------------------------------------------
function Immediate_Context_Implies_Is_Potentially_Unevaluated
(Expr : Node_Id) return Boolean
is
Par : constant Node_Id := Parent (Expr);
function Aggregate_Type return Node_Id is (Etype (Parent (Par)));
begin
if Nkind (Par) = N_If_Expression then
return Is_Elsif (Par) or else Expr /= First (Expressions (Par));
elsif Nkind (Par) = N_Case_Expression then
return Expr /= Expression (Par);
elsif Nkind (Par) in N_And_Then | N_Or_Else then
return Expr = Right_Opnd (Par);
elsif Nkind (Par) in N_In | N_Not_In then
-- If the membership includes several alternatives, only the first
-- is definitely evaluated.
if Present (Alternatives (Par)) then
return Expr /= First (Alternatives (Par));
-- If this is a range membership both bounds are evaluated
else
return False;
end if;
elsif Nkind (Par) = N_Quantified_Expression then
return Expr = Condition (Par);
elsif Nkind (Par) = N_Component_Association
and then Expr = Expression (Par)
and then Nkind (Parent (Par))
in N_Aggregate | N_Delta_Aggregate | N_Extension_Aggregate
and then Present (Aggregate_Type)
and then Aggregate_Type /= Any_Composite
then
if Is_Array_Type (Aggregate_Type) then
if Ada_Version >= Ada_2022 then
-- For Ada 2022, this predicate returns True for
-- any "repeatedly evaluated" expression.
return True;
end if;
declare
Choice : Node_Id;
In_Others_Choice : Boolean := False;
Array_Agg : constant Node_Id := Parent (Par);
begin
-- The expression of an array_component_association is
-- potentially unevaluated if the associated choice is a
-- subtype_indication or range that defines a nonstatic or
-- null range.
Choice := First (Choices (Par));
while Present (Choice) loop
if Nkind (Choice) = N_Range
and then Non_Static_Or_Null_Range (Choice)
then
return True;
elsif Nkind (Choice) = N_Identifier
and then Present (Scalar_Range (Etype (Choice)))
and then
Non_Static_Or_Null_Range
(Scalar_Range (Etype (Choice)))
then
return True;
elsif Nkind (Choice) = N_Others_Choice then
In_Others_Choice := True;
end if;
Next (Choice);
end loop;
-- It is also potentially unevaluated if the associated
-- choice is an others choice and the applicable index
-- constraint is nonstatic or null.
if In_Others_Choice then
if not Compile_Time_Known_Bounds (Aggregate_Type) then
return True;
else
return Has_Null_Others_Choice (Array_Agg);
end if;
end if;
end;
elsif Is_Container_Aggregate (Parent (Par)) then
-- a component of a container aggregate
return True;
end if;
return False;
else
return False;
end if;
end Immediate_Context_Implies_Is_Potentially_Unevaluated;
------------------------------
-- Non_Static_Or_Null_Range --
------------------------------
function Non_Static_Or_Null_Range (N : Node_Id) return Boolean is
Low, High : Node_Id;
begin
Get_Index_Bounds (N, Low, High);
-- Check static bounds
if not Compile_Time_Known_Value (Low)
or else not Compile_Time_Known_Value (High)
then
return True;
-- Check null range
elsif Expr_Value (High) < Expr_Value (Low) then
return True;
end if;
return False;
end Non_Static_Or_Null_Range;
-- Local variables
Par : Node_Id;
Expr : Node_Id;
-- Start of processing for Is_Potentially_Unevaluated
begin
Expr := N;
Par := N;
-- A postcondition whose expression is a short-circuit is broken down
-- into individual aspects for better exception reporting. The original
-- short-circuit expression is rewritten as the second operand, and an
-- occurrence of 'Old in that operand is potentially unevaluated.
-- See sem_ch13.adb for details of this transformation. The reference
-- to 'Old may appear within an expression, so we must look for the
-- enclosing pragma argument in the tree that contains the reference.
while Present (Par)
and then Nkind (Par) /= N_Pragma_Argument_Association
loop
if Is_Rewrite_Substitution (Par)
and then Nkind (Original_Node (Par)) = N_And_Then
then
return True;
end if;
Par := Parent (Par);
end loop;
-- Other cases; 'Old appears within other expression (not the top-level
-- conjunct in a postcondition) with a potentially unevaluated operand.
Par := Parent (Expr);
while Present (Par)
and then Nkind (Par) /= N_Pragma_Argument_Association
loop
if Comes_From_Source (Par)
and then
Immediate_Context_Implies_Is_Potentially_Unevaluated (Expr)
then
return True;
-- For component associations continue climbing; it may be part of
-- an array aggregate.
elsif Nkind (Par) = N_Component_Association then
null;
-- If the context is not an expression, or if is the result of
-- expansion of an enclosing construct (such as another attribute)
-- the predicate does not apply.
elsif Nkind (Par) = N_Case_Expression_Alternative then
null;
elsif Nkind (Par) not in N_Subexpr
or else not Comes_From_Source (Par)
then
return False;
end if;
Expr := Par;
Par := Parent (Par);
end loop;
return False;
end Is_Potentially_Unevaluated;
-----------------------------------------
-- Is_Predefined_Dispatching_Operation --
-----------------------------------------
function Is_Predefined_Dispatching_Operation
(E : Entity_Id) return Boolean
is
TSS_Name : TSS_Name_Type;
begin
if not Is_Dispatching_Operation (E) then
return False;
end if;
Get_Name_String (Chars (E));
-- Most predefined primitives have internally generated names. Equality
-- must be treated differently; the predefined operation is recognized
-- as a homogeneous binary operator that returns Boolean.
if Name_Len > TSS_Name_Type'Last then
TSS_Name :=
TSS_Name_Type
(Name_Buffer (Name_Len - TSS_Name'Length + 1 .. Name_Len));
if Chars (E) in Name_uAssign | Name_uSize
or else
(Chars (E) = Name_Op_Eq
and then Etype (First_Formal (E)) = Etype (Last_Formal (E)))
or else TSS_Name = TSS_Deep_Adjust
or else TSS_Name = TSS_Deep_Finalize
or else TSS_Name = TSS_Stream_Input
or else TSS_Name = TSS_Stream_Output
or else TSS_Name = TSS_Stream_Read
or else TSS_Name = TSS_Stream_Write
or else TSS_Name = TSS_Put_Image
or else Is_Predefined_Interface_Primitive (E)
then
return True;
end if;
end if;
return False;
end Is_Predefined_Dispatching_Operation;
---------------------------------------
-- Is_Predefined_Interface_Primitive --
---------------------------------------
function Is_Predefined_Interface_Primitive (E : Entity_Id) return Boolean is
begin
-- In VM targets we don't restrict the functionality of this test to
-- compiling in Ada 2005 mode since in VM targets any tagged type has
-- these primitives.
return (Ada_Version >= Ada_2005 or else not Tagged_Type_Expansion)
and then Chars (E) in Name_uDisp_Asynchronous_Select
| Name_uDisp_Conditional_Select
| Name_uDisp_Get_Prim_Op_Kind
| Name_uDisp_Get_Task_Id
| Name_uDisp_Requeue
| Name_uDisp_Timed_Select;
end Is_Predefined_Interface_Primitive;
---------------------------------------
-- Is_Predefined_Internal_Operation --
---------------------------------------
function Is_Predefined_Internal_Operation
(E : Entity_Id) return Boolean
is
TSS_Name : TSS_Name_Type;
begin
if not Is_Dispatching_Operation (E) then
return False;
end if;
Get_Name_String (Chars (E));
-- Most predefined primitives have internally generated names. Equality
-- must be treated differently; the predefined operation is recognized
-- as a homogeneous binary operator that returns Boolean.
if Name_Len > TSS_Name_Type'Last then
TSS_Name :=
TSS_Name_Type
(Name_Buffer (Name_Len - TSS_Name'Length + 1 .. Name_Len));
if Chars (E) in Name_uSize | Name_uAssign
or else
(Chars (E) = Name_Op_Eq
and then Etype (First_Formal (E)) = Etype (Last_Formal (E)))
or else TSS_Name = TSS_Deep_Adjust
or else TSS_Name = TSS_Deep_Finalize
or else Is_Predefined_Interface_Primitive (E)
then
return True;
end if;
end if;
return False;
end Is_Predefined_Internal_Operation;
--------------------------------
-- Is_Preelaborable_Aggregate --
--------------------------------
function Is_Preelaborable_Aggregate (Aggr : Node_Id) return Boolean is
Aggr_Typ : constant Entity_Id := Etype (Aggr);
Array_Aggr : constant Boolean := Is_Array_Type (Aggr_Typ);
Anc_Part : Node_Id;
Assoc : Node_Id;
Choice : Node_Id;
Comp_Typ : Entity_Id := Empty; -- init to avoid warning
Expr : Node_Id;
begin
if Array_Aggr then
Comp_Typ := Component_Type (Aggr_Typ);
end if;
-- Inspect the ancestor part
if Nkind (Aggr) = N_Extension_Aggregate then
Anc_Part := Ancestor_Part (Aggr);
-- The ancestor denotes a subtype mark
if Is_Entity_Name (Anc_Part)
and then Is_Type (Entity (Anc_Part))
then
if not Has_Preelaborable_Initialization (Entity (Anc_Part)) then
return False;
end if;
-- Otherwise the ancestor denotes an expression
elsif not Is_Preelaborable_Construct (Anc_Part) then
return False;
end if;
end if;
-- Inspect the positional associations
Expr := First (Expressions (Aggr));
while Present (Expr) loop
if not Is_Preelaborable_Construct (Expr) then
return False;
end if;
Next (Expr);
end loop;
-- Inspect the named associations
Assoc := First (Component_Associations (Aggr));
while Present (Assoc) loop
-- Inspect the choices of the current named association
Choice := First (Choices (Assoc));
while Present (Choice) loop
if Array_Aggr then
-- For a choice to be preelaborable, it must denote either a
-- static range or a static expression.
if Nkind (Choice) = N_Others_Choice then
null;
elsif Nkind (Choice) = N_Range then
if not Is_OK_Static_Range (Choice) then
return False;
end if;
elsif not Is_OK_Static_Expression (Choice) then
return False;
end if;
else
Comp_Typ := Etype (Choice);
end if;
Next (Choice);
end loop;
-- The type of the choice must have preelaborable initialization if
-- the association carries a <>.
pragma Assert (Present (Comp_Typ));
if Box_Present (Assoc) then
if not Has_Preelaborable_Initialization (Comp_Typ) then
return False;
end if;
-- The type of the expression must have preelaborable initialization
elsif not Is_Preelaborable_Construct (Expression (Assoc)) then
return False;
end if;
Next (Assoc);
end loop;
-- At this point the aggregate is preelaborable
return True;
end Is_Preelaborable_Aggregate;
--------------------------------
-- Is_Preelaborable_Construct --
--------------------------------
function Is_Preelaborable_Construct (N : Node_Id) return Boolean is
begin
-- Aggregates
if Nkind (N) in N_Aggregate | N_Extension_Aggregate then
return Is_Preelaborable_Aggregate (N);
-- Attributes are allowed in general, even if their prefix is a formal
-- type. It seems that certain attributes known not to be static might
-- not be allowed, but there are no rules to prevent them.
elsif Nkind (N) = N_Attribute_Reference then
return True;
-- Expressions
elsif Nkind (N) in N_Subexpr and then Is_OK_Static_Expression (N) then
return True;
elsif Nkind (N) = N_Qualified_Expression then
return Is_Preelaborable_Construct (Expression (N));
-- Names are preelaborable when they denote a discriminant of an
-- enclosing type. Discriminals are also considered for this check.
elsif Is_Entity_Name (N)
and then Present (Entity (N))
and then
(Ekind (Entity (N)) = E_Discriminant
or else (Ekind (Entity (N)) in E_Constant | E_In_Parameter
and then Present (Discriminal_Link (Entity (N)))))
then
return True;
-- Statements
elsif Nkind (N) = N_Null then
return True;
-- Ada 2022 (AI12-0175): Calls to certain functions that are essentially
-- unchecked conversions are preelaborable.
elsif Ada_Version >= Ada_2022
and then Nkind (N) = N_Function_Call
and then Is_Entity_Name (Name (N))
and then Is_Preelaborable_Function (Entity (Name (N)))
then
declare
A : Node_Id;
begin
A := First_Actual (N);
while Present (A) loop
if not Is_Preelaborable_Construct (A) then
return False;
end if;
Next_Actual (A);
end loop;
end;
return True;
-- Otherwise the construct is not preelaborable
else
return False;
end if;
end Is_Preelaborable_Construct;
-------------------------------
-- Is_Preelaborable_Function --
-------------------------------
function Is_Preelaborable_Function (Id : Entity_Id) return Boolean is
SATAC : constant Rtsfind.RTU_Id := System_Address_To_Access_Conversions;
Scop : constant Entity_Id := Scope (Id);
begin
-- Small optimization: every allowed function has convention Intrinsic
-- (see Analyze_Subprogram_Instantiation for the subtlety in the test).
if not Is_Intrinsic_Subprogram (Id)
and then Convention (Id) /= Convention_Intrinsic
then
return False;
end if;
-- An instance of Unchecked_Conversion
if Is_Unchecked_Conversion_Instance (Id) then
return True;
end if;
-- A function declared in System.Storage_Elements
if Is_RTU (Scop, System_Storage_Elements) then
return True;
end if;
-- The functions To_Pointer and To_Address declared in an instance of
-- System.Address_To_Access_Conversions (they are the only ones).
if Ekind (Scop) = E_Package
and then Nkind (Parent (Scop)) = N_Package_Specification
and then Present (Generic_Parent (Parent (Scop)))
and then Is_RTU (Generic_Parent (Parent (Scop)), SATAC)
then
return True;
end if;
return False;
end Is_Preelaborable_Function;
-----------------------------
-- Is_Private_Library_Unit --
-----------------------------
function Is_Private_Library_Unit (Unit : Entity_Id) return Boolean is
Comp_Unit : constant Node_Id := Parent (Unit_Declaration_Node (Unit));
begin
return Nkind (Comp_Unit) = N_Compilation_Unit
and then Private_Present (Comp_Unit);
end Is_Private_Library_Unit;
---------------------------------
-- Is_Protected_Self_Reference --
---------------------------------
function Is_Protected_Self_Reference (N : Node_Id) return Boolean is
function In_Access_Definition (N : Node_Id) return Boolean;
-- Returns true if N belongs to an access definition
--------------------------
-- In_Access_Definition --
--------------------------
function In_Access_Definition (N : Node_Id) return Boolean is
P : Node_Id;
begin
P := Parent (N);
while Present (P) loop
if Nkind (P) = N_Access_Definition then
return True;
end if;
P := Parent (P);
end loop;
return False;
end In_Access_Definition;
-- Start of processing for Is_Protected_Self_Reference
begin
-- Verify that prefix is analyzed and has the proper form. Note that
-- the attributes Elab_Spec, Elab_Body, and Elab_Subp_Body, which also
-- produce the address of an entity, do not analyze their prefix
-- because they denote entities that are not necessarily visible.
-- Neither of them can apply to a protected type.
return Ada_Version >= Ada_2005
and then Is_Entity_Name (N)
and then Present (Entity (N))
and then Is_Protected_Type (Entity (N))
and then In_Open_Scopes (Entity (N))
and then not In_Access_Definition (N);
end Is_Protected_Self_Reference;
-----------------------------
-- Is_RCI_Pkg_Spec_Or_Body --
-----------------------------
function Is_RCI_Pkg_Spec_Or_Body (Cunit : Node_Id) return Boolean is
function Is_RCI_Pkg_Decl_Cunit (Cunit : Node_Id) return Boolean;
-- Return True if the unit of Cunit is an RCI package declaration
---------------------------
-- Is_RCI_Pkg_Decl_Cunit --
---------------------------
function Is_RCI_Pkg_Decl_Cunit (Cunit : Node_Id) return Boolean is
The_Unit : constant Node_Id := Unit (Cunit);
begin
if Nkind (The_Unit) /= N_Package_Declaration then
return False;
end if;
return Is_Remote_Call_Interface (Defining_Entity (The_Unit));
end Is_RCI_Pkg_Decl_Cunit;
-- Start of processing for Is_RCI_Pkg_Spec_Or_Body
begin
return Is_RCI_Pkg_Decl_Cunit (Cunit)
or else
(Nkind (Unit (Cunit)) = N_Package_Body
and then Is_RCI_Pkg_Decl_Cunit (Library_Unit (Cunit)));
end Is_RCI_Pkg_Spec_Or_Body;
-----------------------------------------
-- Is_Remote_Access_To_Class_Wide_Type --
-----------------------------------------
function Is_Remote_Access_To_Class_Wide_Type
(E : Entity_Id) return Boolean
is
begin
-- A remote access to class-wide type is a general access to object type
-- declared in the visible part of a Remote_Types or Remote_Call_
-- Interface unit.
return Ekind (E) = E_General_Access_Type
and then (Is_Remote_Call_Interface (E) or else Is_Remote_Types (E));
end Is_Remote_Access_To_Class_Wide_Type;
-----------------------------------------
-- Is_Remote_Access_To_Subprogram_Type --
-----------------------------------------
function Is_Remote_Access_To_Subprogram_Type
(E : Entity_Id) return Boolean
is
begin
return (Ekind (E) = E_Access_Subprogram_Type
or else (Ekind (E) = E_Record_Type
and then Present (Corresponding_Remote_Type (E))))
and then (Is_Remote_Call_Interface (E) or else Is_Remote_Types (E));
end Is_Remote_Access_To_Subprogram_Type;
--------------------
-- Is_Remote_Call --
--------------------
function Is_Remote_Call (N : Node_Id) return Boolean is
begin
if Nkind (N) not in N_Subprogram_Call then
-- An entry call cannot be remote
return False;
elsif Nkind (Name (N)) in N_Has_Entity
and then Is_Remote_Call_Interface (Entity (Name (N)))
then
-- A subprogram declared in the spec of a RCI package is remote
return True;
elsif Nkind (Name (N)) = N_Explicit_Dereference
and then Is_Remote_Access_To_Subprogram_Type
(Etype (Prefix (Name (N))))
then
-- The dereference of a RAS is a remote call
return True;
elsif Present (Controlling_Argument (N))
and then Is_Remote_Access_To_Class_Wide_Type
(Etype (Controlling_Argument (N)))
then
-- Any primitive operation call with a controlling argument of
-- a RACW type is a remote call.
return True;
end if;
-- All other calls are local calls
return False;
end Is_Remote_Call;
----------------------
-- Is_Renamed_Entry --
----------------------
function Is_Renamed_Entry (Proc_Nam : Entity_Id) return Boolean is
Orig_Node : Node_Id := Empty;
Subp_Decl : Node_Id :=
(if No (Parent (Proc_Nam)) then Empty else Parent (Parent (Proc_Nam)));
function Is_Entry (Nam : Node_Id) return Boolean;
-- Determine whether Nam is an entry. Traverse selectors if there are
-- nested selected components.
--------------
-- Is_Entry --
--------------
function Is_Entry (Nam : Node_Id) return Boolean is
begin
if Nkind (Nam) = N_Selected_Component then
return Is_Entry (Selector_Name (Nam));
end if;
return Ekind (Entity (Nam)) = E_Entry;
end Is_Entry;
-- Start of processing for Is_Renamed_Entry
begin
if Present (Alias (Proc_Nam)) then
Subp_Decl := Parent (Parent (Alias (Proc_Nam)));
end if;
-- Look for a rewritten subprogram renaming declaration
if Nkind (Subp_Decl) = N_Subprogram_Declaration
and then Present (Original_Node (Subp_Decl))
then
Orig_Node := Original_Node (Subp_Decl);
end if;
-- The rewritten subprogram is actually an entry
if Present (Orig_Node)
and then Nkind (Orig_Node) = N_Subprogram_Renaming_Declaration
and then Is_Entry (Name (Orig_Node))
then
return True;
end if;
return False;
end Is_Renamed_Entry;
----------------------------
-- Is_Reversible_Iterator --
----------------------------
function Is_Reversible_Iterator (Typ : Entity_Id) return Boolean is
Ifaces_List : Elist_Id;
Iface_Elmt : Elmt_Id;
Iface : Entity_Id;
begin
if Is_Class_Wide_Type (Typ)
and then Chars (Root_Type (Typ)) = Name_Reversible_Iterator
and then In_Predefined_Unit (Root_Type (Typ))
then
return True;
elsif not Is_Tagged_Type (Typ) or else not Is_Derived_Type (Typ) then
return False;
else
Collect_Interfaces (Typ, Ifaces_List);
Iface_Elmt := First_Elmt (Ifaces_List);
while Present (Iface_Elmt) loop
Iface := Node (Iface_Elmt);
if Chars (Iface) = Name_Reversible_Iterator
and then In_Predefined_Unit (Iface)
then
return True;
end if;
Next_Elmt (Iface_Elmt);
end loop;
end if;
return False;
end Is_Reversible_Iterator;
----------------------
-- Is_Selector_Name --
----------------------
function Is_Selector_Name (N : Node_Id) return Boolean is
begin
if not Is_List_Member (N) then
declare
P : constant Node_Id := Parent (N);
begin
return Nkind (P) in N_Expanded_Name
| N_Generic_Association
| N_Parameter_Association
| N_Selected_Component
and then Selector_Name (P) = N;
end;
else
declare
L : constant List_Id := List_Containing (N);
P : constant Node_Id := Parent (L);
begin
return (Nkind (P) = N_Discriminant_Association
and then Selector_Names (P) = L)
or else
(Nkind (P) = N_Component_Association
and then Choices (P) = L);
end;
end if;
end Is_Selector_Name;
---------------------------------
-- Is_Single_Concurrent_Object --
---------------------------------
function Is_Single_Concurrent_Object (Id : Entity_Id) return Boolean is
begin
return
Is_Single_Protected_Object (Id) or else Is_Single_Task_Object (Id);
end Is_Single_Concurrent_Object;
-------------------------------
-- Is_Single_Concurrent_Type --
-------------------------------
function Is_Single_Concurrent_Type (Id : Entity_Id) return Boolean is
begin
return
Ekind (Id) in E_Protected_Type | E_Task_Type
and then Is_Single_Concurrent_Type_Declaration
(Declaration_Node (Id));
end Is_Single_Concurrent_Type;
-------------------------------------------
-- Is_Single_Concurrent_Type_Declaration --
-------------------------------------------
function Is_Single_Concurrent_Type_Declaration
(N : Node_Id) return Boolean
is
begin
return Nkind (Original_Node (N)) in
N_Single_Protected_Declaration | N_Single_Task_Declaration;
end Is_Single_Concurrent_Type_Declaration;
---------------------------------------------
-- Is_Single_Precision_Floating_Point_Type --
---------------------------------------------
function Is_Single_Precision_Floating_Point_Type
(E : Entity_Id) return Boolean is
begin
return Is_Floating_Point_Type (E)
and then Machine_Radix_Value (E) = Uint_2
and then Machine_Mantissa_Value (E) = Uint_24
and then Machine_Emax_Value (E) = Uint_2 ** Uint_7
and then Machine_Emin_Value (E) = Uint_3 - (Uint_2 ** Uint_7);
end Is_Single_Precision_Floating_Point_Type;
--------------------------------
-- Is_Single_Protected_Object --
--------------------------------
function Is_Single_Protected_Object (Id : Entity_Id) return Boolean is
begin
return
Ekind (Id) = E_Variable
and then Ekind (Etype (Id)) = E_Protected_Type
and then Is_Single_Concurrent_Type (Etype (Id));
end Is_Single_Protected_Object;
---------------------------
-- Is_Single_Task_Object --
---------------------------
function Is_Single_Task_Object (Id : Entity_Id) return Boolean is
begin
return
Ekind (Id) = E_Variable
and then Ekind (Etype (Id)) = E_Task_Type
and then Is_Single_Concurrent_Type (Etype (Id));
end Is_Single_Task_Object;
--------------------------------------
-- Is_Special_Aliased_Formal_Access --
--------------------------------------
function Is_Special_Aliased_Formal_Access
(Exp : Node_Id;
In_Return_Context : Boolean := False) return Boolean
is
Scop : constant Entity_Id := Current_Subprogram;
begin
-- Verify the expression is an access reference to 'Access within a
-- return statement as this is the only time an explicitly aliased
-- formal has different semantics.
if Nkind (Exp) /= N_Attribute_Reference
or else Get_Attribute_Id (Attribute_Name (Exp)) /= Attribute_Access
or else not (In_Return_Value (Exp)
or else In_Return_Context)
or else not Needs_Result_Accessibility_Level (Scop)
then
return False;
end if;
-- Check if the prefix of the reference is indeed an explicitly aliased
-- formal parameter for the function Scop. Additionally, we must check
-- that Scop returns an anonymous access type, otherwise the special
-- rules dictating a need for a dynamic check are not in effect.
return Is_Entity_Name (Prefix (Exp))
and then Is_Explicitly_Aliased (Entity (Prefix (Exp)));
end Is_Special_Aliased_Formal_Access;
-----------------------------
-- Is_Specific_Tagged_Type --
-----------------------------
function Is_Specific_Tagged_Type (Typ : Entity_Id) return Boolean is
Full_Typ : Entity_Id;
begin
-- Handle private types
if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
Full_Typ := Full_View (Typ);
else
Full_Typ := Typ;
end if;
-- A specific tagged type is a non-class-wide tagged type
return Is_Tagged_Type (Full_Typ) and not Is_Class_Wide_Type (Full_Typ);
end Is_Specific_Tagged_Type;
------------------
-- Is_Statement --
------------------
function Is_Statement (N : Node_Id) return Boolean is
begin
return
Nkind (N) in N_Statement_Other_Than_Procedure_Call
or else Nkind (N) = N_Procedure_Call_Statement;
end Is_Statement;
--------------------------------------
-- Is_Static_Discriminant_Component --
--------------------------------------
function Is_Static_Discriminant_Component (N : Node_Id) return Boolean is
begin
return Nkind (N) = N_Selected_Component
and then not Is_In_Discriminant_Check (N)
and then Present (Etype (Prefix (N)))
and then Ekind (Etype (Prefix (N))) = E_Record_Subtype
and then Has_Static_Discriminants (Etype (Prefix (N)))
and then Present (Entity (Selector_Name (N)))
and then Ekind (Entity (Selector_Name (N))) = E_Discriminant
and then not In_Check_Node (N);
end Is_Static_Discriminant_Component;
------------------------
-- Is_Static_Function --
------------------------
function Is_Static_Function (Subp : Entity_Id) return Boolean is
begin
-- Always return False for pre Ada 2022 to e.g. ignore the Static
-- aspect in package Interfaces for Ada_Version < 2022 and also
-- for efficiency.
return Ada_Version >= Ada_2022
and then Has_Aspect (Subp, Aspect_Static)
and then
(No (Find_Value_Of_Aspect (Subp, Aspect_Static))
or else Is_True (Static_Boolean
(Find_Value_Of_Aspect (Subp, Aspect_Static))));
end Is_Static_Function;
-----------------------------
-- Is_Static_Function_Call --
-----------------------------
function Is_Static_Function_Call (Call : Node_Id) return Boolean is
function Has_All_Static_Actuals (Call : Node_Id) return Boolean;
-- Return whether all actual parameters of Call are static expressions
----------------------------
-- Has_All_Static_Actuals --
----------------------------
function Has_All_Static_Actuals (Call : Node_Id) return Boolean is
Actual : Node_Id := First_Actual (Call);
String_Result : constant Boolean :=
Is_String_Type (Etype (Entity (Name (Call))));
begin
while Present (Actual) loop
if not Is_Static_Expression (Actual) then
-- ??? In the string-returning case we want to avoid a call
-- being made to Establish_Transient_Scope in Resolve_Call,
-- but at the point where that's tested for (which now includes
-- a call to test Is_Static_Function_Call), the actuals of the
-- call haven't been resolved, so expressions of the actuals
-- may not have been marked Is_Static_Expression yet, so we
-- force them to be resolved here, so we can tell if they're
-- static. Calling Resolve here is admittedly a kludge, and we
-- limit this call to string-returning cases.
if String_Result then
Resolve (Actual);
end if;
-- Test flag again in case it's now True due to above Resolve
if not Is_Static_Expression (Actual) then
return False;
end if;
end if;
Next_Actual (Actual);
end loop;
return True;
end Has_All_Static_Actuals;
begin
return Nkind (Call) = N_Function_Call
and then Is_Entity_Name (Name (Call))
and then Is_Static_Function (Entity (Name (Call)))
and then Has_All_Static_Actuals (Call);
end Is_Static_Function_Call;
-------------------------------------------
-- Is_Subcomponent_Of_Full_Access_Object --
-------------------------------------------
function Is_Subcomponent_Of_Full_Access_Object (N : Node_Id) return Boolean
is
R : Node_Id;
begin
R := Get_Referenced_Object (N);
while Nkind (R) in N_Indexed_Component | N_Selected_Component | N_Slice
loop
R := Get_Referenced_Object (Prefix (R));
-- If the prefix is an access value, only the designated type matters
if Is_Access_Type (Etype (R)) then
if Is_Full_Access (Designated_Type (Etype (R))) then
return True;
end if;
else
if Is_Full_Access_Object (R) then
return True;
end if;
end if;
end loop;
return False;
end Is_Subcomponent_Of_Full_Access_Object;
---------------------------------------
-- Is_Subprogram_Contract_Annotation --
---------------------------------------
function Is_Subprogram_Contract_Annotation
(Item : Node_Id) return Boolean
is
Nam : Name_Id;
begin
if Nkind (Item) = N_Aspect_Specification then
Nam := Chars (Identifier (Item));
else pragma Assert (Nkind (Item) = N_Pragma);
Nam := Pragma_Name (Item);
end if;
return Nam = Name_Contract_Cases
or else Nam = Name_Depends
or else Nam = Name_Extensions_Visible
or else Nam = Name_Global
or else Nam = Name_Post
or else Nam = Name_Post_Class
or else Nam = Name_Postcondition
or else Nam = Name_Pre
or else Nam = Name_Pre_Class
or else Nam = Name_Precondition
or else Nam = Name_Refined_Depends
or else Nam = Name_Refined_Global
or else Nam = Name_Refined_Post
or else Nam = Name_Subprogram_Variant
or else Nam = Name_Test_Case;
end Is_Subprogram_Contract_Annotation;
--------------------------------------------------
-- Is_Subprogram_Stub_Without_Prior_Declaration --
--------------------------------------------------
function Is_Subprogram_Stub_Without_Prior_Declaration
(N : Node_Id) return Boolean
is
begin
pragma Assert (Nkind (N) = N_Subprogram_Body_Stub);
case Ekind (Defining_Entity (N)) is
-- A subprogram stub without prior declaration serves as declaration
-- for the actual subprogram body. As such, it has an attached
-- defining entity of E_Function or E_Procedure.
when E_Function
| E_Procedure
=>
return True;
-- Otherwise, it is completes a [generic] subprogram declaration
when E_Generic_Function
| E_Generic_Procedure
| E_Subprogram_Body
=>
return False;
when others =>
raise Program_Error;
end case;
end Is_Subprogram_Stub_Without_Prior_Declaration;
---------------------------
-- Is_Suitable_Primitive --
---------------------------
function Is_Suitable_Primitive (Subp_Id : Entity_Id) return Boolean is
begin
-- The Default_Initial_Condition and invariant procedures must not be
-- treated as primitive operations even when they apply to a tagged
-- type. These routines must not act as targets of dispatching calls
-- because they already utilize class-wide-precondition semantics to
-- handle inheritance and overriding.
if Ekind (Subp_Id) = E_Procedure
and then (Is_DIC_Procedure (Subp_Id)
or else
Is_Invariant_Procedure (Subp_Id))
then
return False;
end if;
return True;
end Is_Suitable_Primitive;
----------------------------
-- Is_Synchronized_Object --
----------------------------
function Is_Synchronized_Object (Id : Entity_Id) return Boolean is
Prag : Node_Id;
begin
if Is_Object (Id) then
-- The object is synchronized if it is of a type that yields a
-- synchronized object.
if Yields_Synchronized_Object (Etype (Id)) then
return True;
-- The object is synchronized if it is atomic and Async_Writers is
-- enabled.
elsif Is_Atomic_Object_Entity (Id)
and then Async_Writers_Enabled (Id)
then
return True;
-- A constant is a synchronized object by default, unless its type is
-- access-to-variable type.
elsif Ekind (Id) = E_Constant
and then not Is_Access_Variable (Etype (Id))
then
return True;
-- A variable is a synchronized object if it is subject to pragma
-- Constant_After_Elaboration.
elsif Ekind (Id) = E_Variable then
Prag := Get_Pragma (Id, Pragma_Constant_After_Elaboration);
return Present (Prag) and then Is_Enabled_Pragma (Prag);
end if;
end if;
-- Otherwise the input is not an object or it does not qualify as a
-- synchronized object.
return False;
end Is_Synchronized_Object;
---------------------------------
-- Is_Synchronized_Tagged_Type --
---------------------------------
function Is_Synchronized_Tagged_Type (E : Entity_Id) return Boolean is
Kind : constant Entity_Kind := Ekind (Base_Type (E));
begin
-- A task or protected type derived from an interface is a tagged type.
-- Such a tagged type is called a synchronized tagged type, as are
-- synchronized interfaces and private extensions whose declaration
-- includes the reserved word synchronized.
return (Is_Tagged_Type (E)
and then (Kind = E_Task_Type
or else
Kind = E_Protected_Type))
or else
(Is_Interface (E)
and then Is_Synchronized_Interface (E))
or else
(Ekind (E) = E_Record_Type_With_Private
and then Nkind (Parent (E)) = N_Private_Extension_Declaration
and then (Synchronized_Present (Parent (E))
or else Is_Synchronized_Interface (Etype (E))));
end Is_Synchronized_Tagged_Type;
-----------------
-- Is_Transfer --
-----------------
function Is_Transfer (N : Node_Id) return Boolean is
Kind : constant Node_Kind := Nkind (N);
begin
if Kind = N_Simple_Return_Statement
or else
Kind = N_Extended_Return_Statement
or else
Kind = N_Goto_Statement
or else
Kind = N_Raise_Statement
or else
Kind = N_Requeue_Statement
then
return True;
elsif (Kind = N_Exit_Statement or else Kind in N_Raise_xxx_Error)
and then No (Condition (N))
then
return True;
elsif Kind = N_Procedure_Call_Statement
and then Is_Entity_Name (Name (N))
and then Present (Entity (Name (N)))
and then No_Return (Entity (Name (N)))
then
return True;
elsif Nkind (Original_Node (N)) = N_Raise_Statement then
return True;
else
return False;
end if;
end Is_Transfer;
-------------
-- Is_True --
-------------
function Is_True (U : Opt_Ubool) return Boolean is
begin
return No (U) or else U = Uint_1;
end Is_True;
--------------------------------------
-- Is_Unchecked_Conversion_Instance --
--------------------------------------
function Is_Unchecked_Conversion_Instance (Id : Entity_Id) return Boolean is
Par : Node_Id;
begin
-- Look for a function whose generic parent is the predefined intrinsic
-- function Unchecked_Conversion, or for one that renames such an
-- instance.
if Ekind (Id) = E_Function then
Par := Parent (Id);
if Nkind (Par) = N_Function_Specification then
Par := Generic_Parent (Par);
if Present (Par) then
return
Chars (Par) = Name_Unchecked_Conversion
and then Is_Intrinsic_Subprogram (Par)
and then In_Predefined_Unit (Par);
else
return
Present (Alias (Id))
and then Is_Unchecked_Conversion_Instance (Alias (Id));
end if;
end if;
end if;
return False;
end Is_Unchecked_Conversion_Instance;
-------------------------------
-- Is_Universal_Numeric_Type --
-------------------------------
function Is_Universal_Numeric_Type (T : Entity_Id) return Boolean is
begin
return T = Universal_Integer or else T = Universal_Real;
end Is_Universal_Numeric_Type;
------------------------------
-- Is_User_Defined_Equality --
------------------------------
function Is_User_Defined_Equality (Id : Entity_Id) return Boolean is
begin
return Ekind (Id) = E_Function
and then Chars (Id) = Name_Op_Eq
and then Comes_From_Source (Id)
-- Internally generated equalities have a full type declaration
-- as their parent.
and then Nkind (Parent (Id)) = N_Function_Specification;
end Is_User_Defined_Equality;
--------------------------------------
-- Is_Validation_Variable_Reference --
--------------------------------------
function Is_Validation_Variable_Reference (N : Node_Id) return Boolean is
Var : constant Node_Id := Unqual_Conv (N);
Var_Id : Entity_Id;
begin
Var_Id := Empty;
if Is_Entity_Name (Var) then
Var_Id := Entity (Var);
end if;
return
Present (Var_Id)
and then Ekind (Var_Id) = E_Variable
and then Present (Validated_Object (Var_Id));
end Is_Validation_Variable_Reference;
----------------------------
-- Is_Variable_Size_Array --
----------------------------
function Is_Variable_Size_Array (E : Entity_Id) return Boolean is
Idx : Node_Id;
begin
pragma Assert (Is_Array_Type (E));
-- Check if some index is initialized with a non-constant value
Idx := First_Index (E);
while Present (Idx) loop
if Nkind (Idx) = N_Range then
if not Is_Constant_Bound (Low_Bound (Idx))
or else not Is_Constant_Bound (High_Bound (Idx))
then
return True;
end if;
end if;
Next_Index (Idx);
end loop;
return False;
end Is_Variable_Size_Array;
-----------------------------
-- Is_Variable_Size_Record --
-----------------------------
function Is_Variable_Size_Record (E : Entity_Id) return Boolean is
Comp : Entity_Id;
Comp_Typ : Entity_Id;
begin
pragma Assert (Is_Record_Type (E));
Comp := First_Component (E);
while Present (Comp) loop
Comp_Typ := Underlying_Type (Etype (Comp));
-- Recursive call if the record type has discriminants
if Is_Record_Type (Comp_Typ)
and then Has_Discriminants (Comp_Typ)
and then Is_Variable_Size_Record (Comp_Typ)
then
return True;
elsif Is_Array_Type (Comp_Typ)
and then Is_Variable_Size_Array (Comp_Typ)
then
return True;
end if;
Next_Component (Comp);
end loop;
return False;
end Is_Variable_Size_Record;
-----------------
-- Is_Variable --
-----------------
-- Should Is_Variable be refactored to better handle dereferences and
-- technical debt ???
function Is_Variable
(N : Node_Id;
Use_Original_Node : Boolean := True) return Boolean
is
Orig_Node : Node_Id;
function In_Protected_Function (E : Entity_Id) return Boolean;
-- Within a protected function, the private components of the enclosing
-- protected type are constants. A function nested within a (protected)
-- procedure is not itself protected. Within the body of a protected
-- function the current instance of the protected type is a constant.
function Is_Variable_Prefix (P : Node_Id) return Boolean;
-- Prefixes can involve implicit dereferences, in which case we must
-- test for the case of a reference of a constant access type, which can
-- can never be a variable.
---------------------------
-- In_Protected_Function --
---------------------------
function In_Protected_Function (E : Entity_Id) return Boolean is
Prot : Entity_Id;
S : Entity_Id;
begin
-- E is the current instance of a type
if Is_Type (E) then
Prot := E;
-- E is an object
else
Prot := Scope (E);
end if;
if not Is_Protected_Type (Prot) then
return False;
else
S := Current_Scope;
while Present (S) and then S /= Prot loop
if Ekind (S) = E_Function and then Scope (S) = Prot then
return True;
end if;
S := Scope (S);
end loop;
return False;
end if;
end In_Protected_Function;
------------------------
-- Is_Variable_Prefix --
------------------------
function Is_Variable_Prefix (P : Node_Id) return Boolean is
begin
if Is_Access_Type (Etype (P)) then
return not Is_Access_Constant (Root_Type (Etype (P)));
-- For the case of an indexed component whose prefix has a packed
-- array type, the prefix has been rewritten into a type conversion.
-- Determine variable-ness from the converted expression.
elsif Nkind (P) = N_Type_Conversion
and then not Comes_From_Source (P)
and then Is_Packed_Array (Etype (P))
then
return Is_Variable (Expression (P));
else
return Is_Variable (P);
end if;
end Is_Variable_Prefix;
-- Start of processing for Is_Variable
begin
-- Special check, allow x'Deref(expr) as a variable
if Nkind (N) = N_Attribute_Reference
and then Attribute_Name (N) = Name_Deref
then
return True;
end if;
-- Check if we perform the test on the original node since this may be a
-- test of syntactic categories which must not be disturbed by whatever
-- rewriting might have occurred. For example, an aggregate, which is
-- certainly NOT a variable, could be turned into a variable by
-- expansion.
if Use_Original_Node then
Orig_Node := Original_Node (N);
else
Orig_Node := N;
end if;
-- Definitely OK if Assignment_OK is set. Since this is something that
-- only gets set for expanded nodes, the test is on N, not Orig_Node.
if Nkind (N) in N_Subexpr and then Assignment_OK (N) then
return True;
-- Normally we go to the original node, but there is one exception where
-- we use the rewritten node, namely when it is an explicit dereference.
-- The generated code may rewrite a prefix which is an access type with
-- an explicit dereference. The dereference is a variable, even though
-- the original node may not be (since it could be a constant of the
-- access type).
-- In Ada 2005 we have a further case to consider: the prefix may be a
-- function call given in prefix notation. The original node appears to
-- be a selected component, but we need to examine the call.
elsif Nkind (N) = N_Explicit_Dereference
and then Nkind (Orig_Node) /= N_Explicit_Dereference
and then Present (Etype (Orig_Node))
and then Is_Access_Type (Etype (Orig_Node))
then
-- Note that if the prefix is an explicit dereference that does not
-- come from source, we must check for a rewritten function call in