blob: 6f68e9afbfbfd12437b92916e7b3fc720b589d64 [file] [log] [blame]
------------------------------------------------------------------------------
-- --
-- GNAT COMPILER COMPONENTS --
-- --
-- S E M _ C H 1 3 --
-- --
-- B o d y --
-- --
-- Copyright (C) 1992-2015, Free Software Foundation, Inc. --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
-- ware Foundation; either version 3, or (at your option) any later ver- --
-- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
-- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
-- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
-- for more details. You should have received a copy of the GNU General --
-- Public License distributed with GNAT; see file COPYING3. If not, go to --
-- http://www.gnu.org/licenses for a complete copy of the license. --
-- --
-- GNAT was originally developed by the GNAT team at New York University. --
-- Extensive contributions were provided by Ada Core Technologies Inc. --
-- --
------------------------------------------------------------------------------
with Aspects; use Aspects;
with Atree; use Atree;
with Checks; use Checks;
with Debug; use Debug;
with Einfo; use Einfo;
with Elists; use Elists;
with Errout; use Errout;
with Exp_Disp; use Exp_Disp;
with Exp_Tss; use Exp_Tss;
with Exp_Util; use Exp_Util;
with Freeze; use Freeze;
with Lib; use Lib;
with Lib.Xref; use Lib.Xref;
with Namet; use Namet;
with Nlists; use Nlists;
with Nmake; use Nmake;
with Opt; use Opt;
with Restrict; use Restrict;
with Rident; use Rident;
with Rtsfind; use Rtsfind;
with Sem; use Sem;
with Sem_Aux; use Sem_Aux;
with Sem_Case; use Sem_Case;
with Sem_Ch3; use Sem_Ch3;
with Sem_Ch6; use Sem_Ch6;
with Sem_Ch8; use Sem_Ch8;
with Sem_Dim; use Sem_Dim;
with Sem_Disp; use Sem_Disp;
with Sem_Eval; use Sem_Eval;
with Sem_Prag; use Sem_Prag;
with Sem_Res; use Sem_Res;
with Sem_Type; use Sem_Type;
with Sem_Util; use Sem_Util;
with Sem_Warn; use Sem_Warn;
with Sinput; use Sinput;
with Snames; use Snames;
with Stand; use Stand;
with Sinfo; use Sinfo;
with Stringt; use Stringt;
with Targparm; use Targparm;
with Ttypes; use Ttypes;
with Tbuild; use Tbuild;
with Urealp; use Urealp;
with Warnsw; use Warnsw;
with GNAT.Heap_Sort_G;
package body Sem_Ch13 is
SSU : constant Pos := System_Storage_Unit;
-- Convenient short hand for commonly used constant
-----------------------
-- Local Subprograms --
-----------------------
procedure Alignment_Check_For_Size_Change (Typ : Entity_Id; Size : Uint);
-- This routine is called after setting one of the sizes of type entity
-- Typ to Size. The purpose is to deal with the situation of a derived
-- type whose inherited alignment is no longer appropriate for the new
-- size value. In this case, we reset the Alignment to unknown.
procedure Build_Discrete_Static_Predicate
(Typ : Entity_Id;
Expr : Node_Id;
Nam : Name_Id);
-- Given a predicated type Typ, where Typ is a discrete static subtype,
-- whose predicate expression is Expr, tests if Expr is a static predicate,
-- and if so, builds the predicate range list. Nam is the name of the one
-- argument to the predicate function. Occurrences of the type name in the
-- predicate expression have been replaced by identifier references to this
-- name, which is unique, so any identifier with Chars matching Nam must be
-- a reference to the type. If the predicate is non-static, this procedure
-- returns doing nothing. If the predicate is static, then the predicate
-- list is stored in Static_Discrete_Predicate (Typ), and the Expr is
-- rewritten as a canonicalized membership operation.
procedure Build_Predicate_Functions (Typ : Entity_Id; N : Node_Id);
-- If Typ has predicates (indicated by Has_Predicates being set for Typ),
-- then either there are pragma Predicate entries on the rep chain for the
-- type (note that Predicate aspects are converted to pragma Predicate), or
-- there are inherited aspects from a parent type, or ancestor subtypes.
-- This procedure builds the spec and body for the Predicate function that
-- tests these predicates. N is the freeze node for the type. The spec of
-- the function is inserted before the freeze node, and the body of the
-- function is inserted after the freeze node. If the predicate expression
-- has at least one Raise_Expression, then this procedure also builds the
-- M version of the predicate function for use in membership tests.
procedure Check_Pool_Size_Clash (Ent : Entity_Id; SP, SS : Node_Id);
-- Called if both Storage_Pool and Storage_Size attribute definition
-- clauses (SP and SS) are present for entity Ent. Issue error message.
procedure Freeze_Entity_Checks (N : Node_Id);
-- Called from Analyze_Freeze_Entity and Analyze_Generic_Freeze Entity
-- to generate appropriate semantic checks that are delayed until this
-- point (they had to be delayed this long for cases of delayed aspects,
-- e.g. analysis of statically predicated subtypes in choices, for which
-- we have to be sure the subtypes in question are frozen before checking.
function Get_Alignment_Value (Expr : Node_Id) return Uint;
-- Given the expression for an alignment value, returns the corresponding
-- Uint value. If the value is inappropriate, then error messages are
-- posted as required, and a value of No_Uint is returned.
function Is_Operational_Item (N : Node_Id) return Boolean;
-- A specification for a stream attribute is allowed before the full type
-- is declared, as explained in AI-00137 and the corrigendum. Attributes
-- that do not specify a representation characteristic are operational
-- attributes.
function Is_Predicate_Static
(Expr : Node_Id;
Nam : Name_Id) return Boolean;
-- Given predicate expression Expr, tests if Expr is predicate-static in
-- the sense of the rules in (RM 3.2.4 (15-24)). Occurrences of the type
-- name in the predicate expression have been replaced by references to
-- an identifier whose Chars field is Nam. This name is unique, so any
-- identifier with Chars matching Nam must be a reference to the type.
-- Returns True if the expression is predicate-static and False otherwise,
-- but is not in the business of setting flags or issuing error messages.
--
-- Only scalar types can have static predicates, so False is always
-- returned for non-scalar types.
--
-- Note: the RM seems to suggest that string types can also have static
-- predicates. But that really makes lttle sense as very few useful
-- predicates can be constructed for strings. Remember that:
--
-- "ABC" < "DEF"
--
-- is not a static expression. So even though the clearly faulty RM wording
-- allows the following:
--
-- subtype S is String with Static_Predicate => S < "DEF"
--
-- We can't allow this, otherwise we have predicate-static applying to a
-- larger class than static expressions, which was never intended.
procedure New_Stream_Subprogram
(N : Node_Id;
Ent : Entity_Id;
Subp : Entity_Id;
Nam : TSS_Name_Type);
-- Create a subprogram renaming of a given stream attribute to the
-- designated subprogram and then in the tagged case, provide this as a
-- primitive operation, or in the untagged case make an appropriate TSS
-- entry. This is more properly an expansion activity than just semantics,
-- but the presence of user-defined stream functions for limited types
-- is a legality check, which is why this takes place here rather than in
-- exp_ch13, where it was previously. Nam indicates the name of the TSS
-- function to be generated.
--
-- To avoid elaboration anomalies with freeze nodes, for untagged types
-- we generate both a subprogram declaration and a subprogram renaming
-- declaration, so that the attribute specification is handled as a
-- renaming_as_body. For tagged types, the specification is one of the
-- primitive specs.
procedure Resolve_Iterable_Operation
(N : Node_Id;
Cursor : Entity_Id;
Typ : Entity_Id;
Nam : Name_Id);
-- If the name of a primitive operation for an Iterable aspect is
-- overloaded, resolve according to required signature.
procedure Set_Biased
(E : Entity_Id;
N : Node_Id;
Msg : String;
Biased : Boolean := True);
-- If Biased is True, sets Has_Biased_Representation flag for E, and
-- outputs a warning message at node N if Warn_On_Biased_Representation is
-- is True. This warning inserts the string Msg to describe the construct
-- causing biasing.
----------------------------------------------
-- Table for Validate_Unchecked_Conversions --
----------------------------------------------
-- The following table collects unchecked conversions for validation.
-- Entries are made by Validate_Unchecked_Conversion and then the call
-- to Validate_Unchecked_Conversions does the actual error checking and
-- posting of warnings. The reason for this delayed processing is to take
-- advantage of back-annotations of size and alignment values performed by
-- the back end.
-- Note: the reason we store a Source_Ptr value instead of a Node_Id is
-- that by the time Validate_Unchecked_Conversions is called, Sprint will
-- already have modified all Sloc values if the -gnatD option is set.
type UC_Entry is record
Eloc : Source_Ptr; -- node used for posting warnings
Source : Entity_Id; -- source type for unchecked conversion
Target : Entity_Id; -- target type for unchecked conversion
Act_Unit : Entity_Id; -- actual function instantiated
end record;
package Unchecked_Conversions is new Table.Table (
Table_Component_Type => UC_Entry,
Table_Index_Type => Int,
Table_Low_Bound => 1,
Table_Initial => 50,
Table_Increment => 200,
Table_Name => "Unchecked_Conversions");
----------------------------------------
-- Table for Validate_Address_Clauses --
----------------------------------------
-- If an address clause has the form
-- for X'Address use Expr
-- where Expr is of the form Y'Address or recursively is a reference to a
-- constant of either of these forms, and X and Y are entities of objects,
-- then if Y has a smaller alignment than X, that merits a warning about
-- possible bad alignment. The following table collects address clauses of
-- this kind. We put these in a table so that they can be checked after the
-- back end has completed annotation of the alignments of objects, since we
-- can catch more cases that way.
type Address_Clause_Check_Record is record
N : Node_Id;
-- The address clause
X : Entity_Id;
-- The entity of the object overlaying Y
Y : Entity_Id;
-- The entity of the object being overlaid
Off : Boolean;
-- Whether the address is offset within Y
end record;
package Address_Clause_Checks is new Table.Table (
Table_Component_Type => Address_Clause_Check_Record,
Table_Index_Type => Int,
Table_Low_Bound => 1,
Table_Initial => 20,
Table_Increment => 200,
Table_Name => "Address_Clause_Checks");
-----------------------------------------
-- Adjust_Record_For_Reverse_Bit_Order --
-----------------------------------------
procedure Adjust_Record_For_Reverse_Bit_Order (R : Entity_Id) is
Comp : Node_Id;
CC : Node_Id;
begin
-- Processing depends on version of Ada
-- For Ada 95, we just renumber bits within a storage unit. We do the
-- same for Ada 83 mode, since we recognize the Bit_Order attribute in
-- Ada 83, and are free to add this extension.
if Ada_Version < Ada_2005 then
Comp := First_Component_Or_Discriminant (R);
while Present (Comp) loop
CC := Component_Clause (Comp);
-- If component clause is present, then deal with the non-default
-- bit order case for Ada 95 mode.
-- We only do this processing for the base type, and in fact that
-- is important, since otherwise if there are record subtypes, we
-- could reverse the bits once for each subtype, which is wrong.
if Present (CC) and then Ekind (R) = E_Record_Type then
declare
CFB : constant Uint := Component_Bit_Offset (Comp);
CSZ : constant Uint := Esize (Comp);
CLC : constant Node_Id := Component_Clause (Comp);
Pos : constant Node_Id := Position (CLC);
FB : constant Node_Id := First_Bit (CLC);
Storage_Unit_Offset : constant Uint :=
CFB / System_Storage_Unit;
Start_Bit : constant Uint :=
CFB mod System_Storage_Unit;
begin
-- Cases where field goes over storage unit boundary
if Start_Bit + CSZ > System_Storage_Unit then
-- Allow multi-byte field but generate warning
if Start_Bit mod System_Storage_Unit = 0
and then CSZ mod System_Storage_Unit = 0
then
Error_Msg_N
("info: multi-byte field specified with "
& "non-standard Bit_Order?V?", CLC);
if Bytes_Big_Endian then
Error_Msg_N
("\bytes are not reversed "
& "(component is big-endian)?V?", CLC);
else
Error_Msg_N
("\bytes are not reversed "
& "(component is little-endian)?V?", CLC);
end if;
-- Do not allow non-contiguous field
else
Error_Msg_N
("attempt to specify non-contiguous field "
& "not permitted", CLC);
Error_Msg_N
("\caused by non-standard Bit_Order "
& "specified", CLC);
Error_Msg_N
("\consider possibility of using "
& "Ada 2005 mode here", CLC);
end if;
-- Case where field fits in one storage unit
else
-- Give warning if suspicious component clause
if Intval (FB) >= System_Storage_Unit
and then Warn_On_Reverse_Bit_Order
then
Error_Msg_N
("info: Bit_Order clause does not affect " &
"byte ordering?V?", Pos);
Error_Msg_Uint_1 :=
Intval (Pos) + Intval (FB) /
System_Storage_Unit;
Error_Msg_N
("info: position normalized to ^ before bit " &
"order interpreted?V?", Pos);
end if;
-- Here is where we fix up the Component_Bit_Offset value
-- to account for the reverse bit order. Some examples of
-- what needs to be done are:
-- First_Bit .. Last_Bit Component_Bit_Offset
-- old new old new
-- 0 .. 0 7 .. 7 0 7
-- 0 .. 1 6 .. 7 0 6
-- 0 .. 2 5 .. 7 0 5
-- 0 .. 7 0 .. 7 0 4
-- 1 .. 1 6 .. 6 1 6
-- 1 .. 4 3 .. 6 1 3
-- 4 .. 7 0 .. 3 4 0
-- The rule is that the first bit is is obtained by
-- subtracting the old ending bit from storage_unit - 1.
Set_Component_Bit_Offset
(Comp,
(Storage_Unit_Offset * System_Storage_Unit) +
(System_Storage_Unit - 1) -
(Start_Bit + CSZ - 1));
Set_Normalized_First_Bit
(Comp,
Component_Bit_Offset (Comp) mod
System_Storage_Unit);
end if;
end;
end if;
Next_Component_Or_Discriminant (Comp);
end loop;
-- For Ada 2005, we do machine scalar processing, as fully described In
-- AI-133. This involves gathering all components which start at the
-- same byte offset and processing them together. Same approach is still
-- valid in later versions including Ada 2012.
else
declare
Max_Machine_Scalar_Size : constant Uint :=
UI_From_Int
(Standard_Long_Long_Integer_Size);
-- We use this as the maximum machine scalar size
Num_CC : Natural;
SSU : constant Uint := UI_From_Int (System_Storage_Unit);
begin
-- This first loop through components does two things. First it
-- deals with the case of components with component clauses whose
-- length is greater than the maximum machine scalar size (either
-- accepting them or rejecting as needed). Second, it counts the
-- number of components with component clauses whose length does
-- not exceed this maximum for later processing.
Num_CC := 0;
Comp := First_Component_Or_Discriminant (R);
while Present (Comp) loop
CC := Component_Clause (Comp);
if Present (CC) then
declare
Fbit : constant Uint := Static_Integer (First_Bit (CC));
Lbit : constant Uint := Static_Integer (Last_Bit (CC));
begin
-- Case of component with last bit >= max machine scalar
if Lbit >= Max_Machine_Scalar_Size then
-- This is allowed only if first bit is zero, and
-- last bit + 1 is a multiple of storage unit size.
if Fbit = 0 and then (Lbit + 1) mod SSU = 0 then
-- This is the case to give a warning if enabled
if Warn_On_Reverse_Bit_Order then
Error_Msg_N
("info: multi-byte field specified with "
& " non-standard Bit_Order?V?", CC);
if Bytes_Big_Endian then
Error_Msg_N
("\bytes are not reversed "
& "(component is big-endian)?V?", CC);
else
Error_Msg_N
("\bytes are not reversed "
& "(component is little-endian)?V?", CC);
end if;
end if;
-- Give error message for RM 13.5.1(10) violation
else
Error_Msg_FE
("machine scalar rules not followed for&",
First_Bit (CC), Comp);
Error_Msg_Uint_1 := Lbit;
Error_Msg_Uint_2 := Max_Machine_Scalar_Size;
Error_Msg_F
("\last bit (^) exceeds maximum machine "
& "scalar size (^)",
First_Bit (CC));
if (Lbit + 1) mod SSU /= 0 then
Error_Msg_Uint_1 := SSU;
Error_Msg_F
("\and is not a multiple of Storage_Unit (^) "
& "(RM 13.4.1(10))",
First_Bit (CC));
else
Error_Msg_Uint_1 := Fbit;
Error_Msg_F
("\and first bit (^) is non-zero "
& "(RM 13.4.1(10))",
First_Bit (CC));
end if;
end if;
-- OK case of machine scalar related component clause,
-- For now, just count them.
else
Num_CC := Num_CC + 1;
end if;
end;
end if;
Next_Component_Or_Discriminant (Comp);
end loop;
-- We need to sort the component clauses on the basis of the
-- Position values in the clause, so we can group clauses with
-- the same Position together to determine the relevant machine
-- scalar size.
Sort_CC : declare
Comps : array (0 .. Num_CC) of Entity_Id;
-- Array to collect component and discriminant entities. The
-- data starts at index 1, the 0'th entry is for the sort
-- routine.
function CP_Lt (Op1, Op2 : Natural) return Boolean;
-- Compare routine for Sort
procedure CP_Move (From : Natural; To : Natural);
-- Move routine for Sort
package Sorting is new GNAT.Heap_Sort_G (CP_Move, CP_Lt);
Start : Natural;
Stop : Natural;
-- Start and stop positions in the component list of the set of
-- components with the same starting position (that constitute
-- components in a single machine scalar).
MaxL : Uint;
-- Maximum last bit value of any component in this set
MSS : Uint;
-- Corresponding machine scalar size
-----------
-- CP_Lt --
-----------
function CP_Lt (Op1, Op2 : Natural) return Boolean is
begin
return Position (Component_Clause (Comps (Op1))) <
Position (Component_Clause (Comps (Op2)));
end CP_Lt;
-------------
-- CP_Move --
-------------
procedure CP_Move (From : Natural; To : Natural) is
begin
Comps (To) := Comps (From);
end CP_Move;
-- Start of processing for Sort_CC
begin
-- Collect the machine scalar relevant component clauses
Num_CC := 0;
Comp := First_Component_Or_Discriminant (R);
while Present (Comp) loop
declare
CC : constant Node_Id := Component_Clause (Comp);
begin
-- Collect only component clauses whose last bit is less
-- than machine scalar size. Any component clause whose
-- last bit exceeds this value does not take part in
-- machine scalar layout considerations. The test for
-- Error_Posted makes sure we exclude component clauses
-- for which we already posted an error.
if Present (CC)
and then not Error_Posted (Last_Bit (CC))
and then Static_Integer (Last_Bit (CC)) <
Max_Machine_Scalar_Size
then
Num_CC := Num_CC + 1;
Comps (Num_CC) := Comp;
end if;
end;
Next_Component_Or_Discriminant (Comp);
end loop;
-- Sort by ascending position number
Sorting.Sort (Num_CC);
-- We now have all the components whose size does not exceed
-- the max machine scalar value, sorted by starting position.
-- In this loop we gather groups of clauses starting at the
-- same position, to process them in accordance with AI-133.
Stop := 0;
while Stop < Num_CC loop
Start := Stop + 1;
Stop := Start;
MaxL :=
Static_Integer
(Last_Bit (Component_Clause (Comps (Start))));
while Stop < Num_CC loop
if Static_Integer
(Position (Component_Clause (Comps (Stop + 1)))) =
Static_Integer
(Position (Component_Clause (Comps (Stop))))
then
Stop := Stop + 1;
MaxL :=
UI_Max
(MaxL,
Static_Integer
(Last_Bit
(Component_Clause (Comps (Stop)))));
else
exit;
end if;
end loop;
-- Now we have a group of component clauses from Start to
-- Stop whose positions are identical, and MaxL is the
-- maximum last bit value of any of these components.
-- We need to determine the corresponding machine scalar
-- size. This loop assumes that machine scalar sizes are
-- even, and that each possible machine scalar has twice
-- as many bits as the next smaller one.
MSS := Max_Machine_Scalar_Size;
while MSS mod 2 = 0
and then (MSS / 2) >= SSU
and then (MSS / 2) > MaxL
loop
MSS := MSS / 2;
end loop;
-- Here is where we fix up the Component_Bit_Offset value
-- to account for the reverse bit order. Some examples of
-- what needs to be done for the case of a machine scalar
-- size of 8 are:
-- First_Bit .. Last_Bit Component_Bit_Offset
-- old new old new
-- 0 .. 0 7 .. 7 0 7
-- 0 .. 1 6 .. 7 0 6
-- 0 .. 2 5 .. 7 0 5
-- 0 .. 7 0 .. 7 0 4
-- 1 .. 1 6 .. 6 1 6
-- 1 .. 4 3 .. 6 1 3
-- 4 .. 7 0 .. 3 4 0
-- The rule is that the first bit is obtained by subtracting
-- the old ending bit from machine scalar size - 1.
for C in Start .. Stop loop
declare
Comp : constant Entity_Id := Comps (C);
CC : constant Node_Id := Component_Clause (Comp);
LB : constant Uint := Static_Integer (Last_Bit (CC));
NFB : constant Uint := MSS - Uint_1 - LB;
NLB : constant Uint := NFB + Esize (Comp) - 1;
Pos : constant Uint := Static_Integer (Position (CC));
begin
if Warn_On_Reverse_Bit_Order then
Error_Msg_Uint_1 := MSS;
Error_Msg_N
("info: reverse bit order in machine " &
"scalar of length^?V?", First_Bit (CC));
Error_Msg_Uint_1 := NFB;
Error_Msg_Uint_2 := NLB;
if Bytes_Big_Endian then
Error_Msg_NE
("\big-endian range for component "
& "& is ^ .. ^?V?", First_Bit (CC), Comp);
else
Error_Msg_NE
("\little-endian range for component"
& "& is ^ .. ^?V?", First_Bit (CC), Comp);
end if;
end if;
Set_Component_Bit_Offset (Comp, Pos * SSU + NFB);
Set_Normalized_First_Bit (Comp, NFB mod SSU);
end;
end loop;
end loop;
end Sort_CC;
end;
end if;
end Adjust_Record_For_Reverse_Bit_Order;
-------------------------------------
-- Alignment_Check_For_Size_Change --
-------------------------------------
procedure Alignment_Check_For_Size_Change (Typ : Entity_Id; Size : Uint) is
begin
-- If the alignment is known, and not set by a rep clause, and is
-- inconsistent with the size being set, then reset it to unknown,
-- we assume in this case that the size overrides the inherited
-- alignment, and that the alignment must be recomputed.
if Known_Alignment (Typ)
and then not Has_Alignment_Clause (Typ)
and then Size mod (Alignment (Typ) * SSU) /= 0
then
Init_Alignment (Typ);
end if;
end Alignment_Check_For_Size_Change;
-------------------------------------
-- Analyze_Aspects_At_Freeze_Point --
-------------------------------------
procedure Analyze_Aspects_At_Freeze_Point (E : Entity_Id) is
ASN : Node_Id;
A_Id : Aspect_Id;
Ritem : Node_Id;
procedure Analyze_Aspect_Default_Value (ASN : Node_Id);
-- This routine analyzes an Aspect_Default_[Component_]Value denoted by
-- the aspect specification node ASN.
procedure Inherit_Delayed_Rep_Aspects (ASN : Node_Id);
-- As discussed in the spec of Aspects (see Aspect_Delay declaration),
-- a derived type can inherit aspects from its parent which have been
-- specified at the time of the derivation using an aspect, as in:
--
-- type A is range 1 .. 10
-- with Size => Not_Defined_Yet;
-- ..
-- type B is new A;
-- ..
-- Not_Defined_Yet : constant := 64;
--
-- In this example, the Size of A is considered to be specified prior
-- to the derivation, and thus inherited, even though the value is not
-- known at the time of derivation. To deal with this, we use two entity
-- flags. The flag Has_Derived_Rep_Aspects is set in the parent type (A
-- here), and then the flag May_Inherit_Delayed_Rep_Aspects is set in
-- the derived type (B here). If this flag is set when the derived type
-- is frozen, then this procedure is called to ensure proper inheritance
-- of all delayed aspects from the parent type. The derived type is E,
-- the argument to Analyze_Aspects_At_Freeze_Point. ASN is the first
-- aspect specification node in the Rep_Item chain for the parent type.
procedure Make_Pragma_From_Boolean_Aspect (ASN : Node_Id);
-- Given an aspect specification node ASN whose expression is an
-- optional Boolean, this routines creates the corresponding pragma
-- at the freezing point.
----------------------------------
-- Analyze_Aspect_Default_Value --
----------------------------------
procedure Analyze_Aspect_Default_Value (ASN : Node_Id) is
Ent : constant Entity_Id := Entity (ASN);
Expr : constant Node_Id := Expression (ASN);
Id : constant Node_Id := Identifier (ASN);
begin
Error_Msg_Name_1 := Chars (Id);
if not Is_Type (Ent) then
Error_Msg_N ("aspect% can only apply to a type", Id);
return;
elsif not Is_First_Subtype (Ent) then
Error_Msg_N ("aspect% cannot apply to subtype", Id);
return;
elsif A_Id = Aspect_Default_Value
and then not Is_Scalar_Type (Ent)
then
Error_Msg_N ("aspect% can only be applied to scalar type", Id);
return;
elsif A_Id = Aspect_Default_Component_Value then
if not Is_Array_Type (Ent) then
Error_Msg_N ("aspect% can only be applied to array type", Id);
return;
elsif not Is_Scalar_Type (Component_Type (Ent)) then
Error_Msg_N ("aspect% requires scalar components", Id);
return;
end if;
end if;
Set_Has_Default_Aspect (Base_Type (Ent));
if Is_Scalar_Type (Ent) then
Set_Default_Aspect_Value (Base_Type (Ent), Expr);
else
Set_Default_Aspect_Component_Value (Base_Type (Ent), Expr);
end if;
end Analyze_Aspect_Default_Value;
---------------------------------
-- Inherit_Delayed_Rep_Aspects --
---------------------------------
procedure Inherit_Delayed_Rep_Aspects (ASN : Node_Id) is
P : constant Entity_Id := Entity (ASN);
-- Entithy for parent type
N : Node_Id;
-- Item from Rep_Item chain
A : Aspect_Id;
begin
-- Loop through delayed aspects for the parent type
N := ASN;
while Present (N) loop
if Nkind (N) = N_Aspect_Specification then
exit when Entity (N) /= P;
if Is_Delayed_Aspect (N) then
A := Get_Aspect_Id (Chars (Identifier (N)));
-- Process delayed rep aspect. For Boolean attributes it is
-- not possible to cancel an attribute once set (the attempt
-- to use an aspect with xxx => False is an error) for a
-- derived type. So for those cases, we do not have to check
-- if a clause has been given for the derived type, since it
-- is harmless to set it again if it is already set.
case A is
-- Alignment
when Aspect_Alignment =>
if not Has_Alignment_Clause (E) then
Set_Alignment (E, Alignment (P));
end if;
-- Atomic
when Aspect_Atomic =>
if Is_Atomic (P) then
Set_Is_Atomic (E);
end if;
-- Atomic_Components
when Aspect_Atomic_Components =>
if Has_Atomic_Components (P) then
Set_Has_Atomic_Components (Base_Type (E));
end if;
-- Bit_Order
when Aspect_Bit_Order =>
if Is_Record_Type (E)
and then No (Get_Attribute_Definition_Clause
(E, Attribute_Bit_Order))
and then Reverse_Bit_Order (P)
then
Set_Reverse_Bit_Order (Base_Type (E));
end if;
-- Component_Size
when Aspect_Component_Size =>
if Is_Array_Type (E)
and then not Has_Component_Size_Clause (E)
then
Set_Component_Size
(Base_Type (E), Component_Size (P));
end if;
-- Machine_Radix
when Aspect_Machine_Radix =>
if Is_Decimal_Fixed_Point_Type (E)
and then not Has_Machine_Radix_Clause (E)
then
Set_Machine_Radix_10 (E, Machine_Radix_10 (P));
end if;
-- Object_Size (also Size which also sets Object_Size)
when Aspect_Object_Size | Aspect_Size =>
if not Has_Size_Clause (E)
and then
No (Get_Attribute_Definition_Clause
(E, Attribute_Object_Size))
then
Set_Esize (E, Esize (P));
end if;
-- Pack
when Aspect_Pack =>
if not Is_Packed (E) then
Set_Is_Packed (Base_Type (E));
if Is_Bit_Packed_Array (P) then
Set_Is_Bit_Packed_Array (Base_Type (E));
Set_Packed_Array_Impl_Type
(E, Packed_Array_Impl_Type (P));
end if;
end if;
-- Scalar_Storage_Order
when Aspect_Scalar_Storage_Order =>
if (Is_Record_Type (E) or else Is_Array_Type (E))
and then No (Get_Attribute_Definition_Clause
(E, Attribute_Scalar_Storage_Order))
and then Reverse_Storage_Order (P)
then
Set_Reverse_Storage_Order (Base_Type (E));
-- Clear default SSO indications, since the aspect
-- overrides the default.
Set_SSO_Set_Low_By_Default (Base_Type (E), False);
Set_SSO_Set_High_By_Default (Base_Type (E), False);
end if;
-- Small
when Aspect_Small =>
if Is_Fixed_Point_Type (E)
and then not Has_Small_Clause (E)
then
Set_Small_Value (E, Small_Value (P));
end if;
-- Storage_Size
when Aspect_Storage_Size =>
if (Is_Access_Type (E) or else Is_Task_Type (E))
and then not Has_Storage_Size_Clause (E)
then
Set_Storage_Size_Variable
(Base_Type (E), Storage_Size_Variable (P));
end if;
-- Value_Size
when Aspect_Value_Size =>
-- Value_Size is never inherited, it is either set by
-- default, or it is explicitly set for the derived
-- type. So nothing to do here.
null;
-- Volatile
when Aspect_Volatile =>
if Is_Volatile (P) then
Set_Is_Volatile (E);
end if;
-- Volatile_Components
when Aspect_Volatile_Components =>
if Has_Volatile_Components (P) then
Set_Has_Volatile_Components (Base_Type (E));
end if;
-- That should be all the Rep Aspects
when others =>
pragma Assert (Aspect_Delay (A_Id) /= Rep_Aspect);
null;
end case;
end if;
end if;
N := Next_Rep_Item (N);
end loop;
end Inherit_Delayed_Rep_Aspects;
-------------------------------------
-- Make_Pragma_From_Boolean_Aspect --
-------------------------------------
procedure Make_Pragma_From_Boolean_Aspect (ASN : Node_Id) is
Ident : constant Node_Id := Identifier (ASN);
A_Name : constant Name_Id := Chars (Ident);
A_Id : constant Aspect_Id := Get_Aspect_Id (A_Name);
Ent : constant Entity_Id := Entity (ASN);
Expr : constant Node_Id := Expression (ASN);
Loc : constant Source_Ptr := Sloc (ASN);
Prag : Node_Id;
procedure Check_False_Aspect_For_Derived_Type;
-- This procedure checks for the case of a false aspect for a derived
-- type, which improperly tries to cancel an aspect inherited from
-- the parent.
-----------------------------------------
-- Check_False_Aspect_For_Derived_Type --
-----------------------------------------
procedure Check_False_Aspect_For_Derived_Type is
Par : Node_Id;
begin
-- We are only checking derived types
if not Is_Derived_Type (E) then
return;
end if;
Par := Nearest_Ancestor (E);
case A_Id is
when Aspect_Atomic | Aspect_Shared =>
if not Is_Atomic (Par) then
return;
end if;
when Aspect_Atomic_Components =>
if not Has_Atomic_Components (Par) then
return;
end if;
when Aspect_Discard_Names =>
if not Discard_Names (Par) then
return;
end if;
when Aspect_Pack =>
if not Is_Packed (Par) then
return;
end if;
when Aspect_Unchecked_Union =>
if not Is_Unchecked_Union (Par) then
return;
end if;
when Aspect_Volatile =>
if not Is_Volatile (Par) then
return;
end if;
when Aspect_Volatile_Components =>
if not Has_Volatile_Components (Par) then
return;
end if;
when others =>
return;
end case;
-- Fall through means we are canceling an inherited aspect
Error_Msg_Name_1 := A_Name;
Error_Msg_NE
("derived type& inherits aspect%, cannot cancel", Expr, E);
end Check_False_Aspect_For_Derived_Type;
-- Start of processing for Make_Pragma_From_Boolean_Aspect
begin
-- Note that we know Expr is present, because for a missing Expr
-- argument, we knew it was True and did not need to delay the
-- evaluation to the freeze point.
if Is_False (Static_Boolean (Expr)) then
Check_False_Aspect_For_Derived_Type;
else
Prag :=
Make_Pragma (Loc,
Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Sloc (Ident),
Expression => New_Occurrence_Of (Ent, Sloc (Ident)))),
Pragma_Identifier =>
Make_Identifier (Sloc (Ident), Chars (Ident)));
Set_From_Aspect_Specification (Prag, True);
Set_Corresponding_Aspect (Prag, ASN);
Set_Aspect_Rep_Item (ASN, Prag);
Set_Is_Delayed_Aspect (Prag);
Set_Parent (Prag, ASN);
end if;
end Make_Pragma_From_Boolean_Aspect;
-- Start of processing for Analyze_Aspects_At_Freeze_Point
begin
-- Must be visible in current scope
if not Scope_Within_Or_Same (Current_Scope, Scope (E)) then
return;
end if;
-- Look for aspect specification entries for this entity
ASN := First_Rep_Item (E);
while Present (ASN) loop
if Nkind (ASN) = N_Aspect_Specification then
exit when Entity (ASN) /= E;
if Is_Delayed_Aspect (ASN) then
A_Id := Get_Aspect_Id (ASN);
case A_Id is
-- For aspects whose expression is an optional Boolean, make
-- the corresponding pragma at the freeze point.
when Boolean_Aspects |
Library_Unit_Aspects =>
Make_Pragma_From_Boolean_Aspect (ASN);
-- Special handling for aspects that don't correspond to
-- pragmas/attributes.
when Aspect_Default_Value |
Aspect_Default_Component_Value =>
Analyze_Aspect_Default_Value (ASN);
-- Ditto for iterator aspects, because the corresponding
-- attributes may not have been analyzed yet.
when Aspect_Constant_Indexing |
Aspect_Variable_Indexing |
Aspect_Default_Iterator |
Aspect_Iterator_Element =>
Analyze (Expression (ASN));
if Etype (Expression (ASN)) = Any_Type then
Error_Msg_NE
("\aspect must be fully defined before & is frozen",
ASN, E);
end if;
when Aspect_Iterable =>
Validate_Iterable_Aspect (E, ASN);
when others =>
null;
end case;
Ritem := Aspect_Rep_Item (ASN);
if Present (Ritem) then
Analyze (Ritem);
end if;
end if;
end if;
Next_Rep_Item (ASN);
end loop;
-- This is where we inherit delayed rep aspects from our parent. Note
-- that if we fell out of the above loop with ASN non-empty, it means
-- we hit an aspect for an entity other than E, and it must be the
-- type from which we were derived.
if May_Inherit_Delayed_Rep_Aspects (E) then
Inherit_Delayed_Rep_Aspects (ASN);
end if;
end Analyze_Aspects_At_Freeze_Point;
-----------------------------------
-- Analyze_Aspect_Specifications --
-----------------------------------
procedure Analyze_Aspect_Specifications (N : Node_Id; E : Entity_Id) is
procedure Decorate (Asp : Node_Id; Prag : Node_Id);
-- Establish linkages between an aspect and its corresponding
-- pragma.
procedure Insert_After_SPARK_Mode
(Prag : Node_Id;
Ins_Nod : Node_Id;
Decls : List_Id);
-- Subsidiary to the analysis of aspects Abstract_State, Ghost,
-- Initializes, Initial_Condition and Refined_State. Insert node Prag
-- before node Ins_Nod. If Ins_Nod is for pragma SPARK_Mode, then skip
-- SPARK_Mode. Decls is the associated declarative list where Prag is to
-- reside.
procedure Insert_Pragma (Prag : Node_Id);
-- Subsidiary to the analysis of aspects Attach_Handler, Contract_Cases,
-- Depends, Global, Post, Pre, Refined_Depends and Refined_Global.
-- Insert pragma Prag such that it mimics the placement of a source
-- pragma of the same kind.
--
-- procedure Proc (Formal : ...) with Global => ...;
--
-- procedure Proc (Formal : ...);
-- pragma Global (...);
--------------
-- Decorate --
--------------
procedure Decorate (Asp : Node_Id; Prag : Node_Id) is
begin
Set_Aspect_Rep_Item (Asp, Prag);
Set_Corresponding_Aspect (Prag, Asp);
Set_From_Aspect_Specification (Prag);
Set_Parent (Prag, Asp);
end Decorate;
-----------------------------
-- Insert_After_SPARK_Mode --
-----------------------------
procedure Insert_After_SPARK_Mode
(Prag : Node_Id;
Ins_Nod : Node_Id;
Decls : List_Id)
is
Decl : Node_Id := Ins_Nod;
begin
-- Skip SPARK_Mode
if Present (Decl)
and then Nkind (Decl) = N_Pragma
and then Pragma_Name (Decl) = Name_SPARK_Mode
then
Decl := Next (Decl);
end if;
if Present (Decl) then
Insert_Before (Decl, Prag);
-- Aitem acts as the last declaration
else
Append_To (Decls, Prag);
end if;
end Insert_After_SPARK_Mode;
-------------------
-- Insert_Pragma --
-------------------
procedure Insert_Pragma (Prag : Node_Id) is
Aux : Node_Id;
Decl : Node_Id;
begin
if Nkind (N) = N_Subprogram_Body then
if Present (Declarations (N)) then
-- Skip other internally generated pragmas from aspects to find
-- the proper insertion point. As a result the order of pragmas
-- is the same as the order of aspects.
-- As precondition pragmas generated from conjuncts in the
-- precondition aspect are presented in reverse order to
-- Insert_Pragma, insert them in the correct order here by not
-- skipping previously inserted precondition pragmas when the
-- current pragma is a precondition.
Decl := First (Declarations (N));
while Present (Decl) loop
if Nkind (Decl) = N_Pragma
and then From_Aspect_Specification (Decl)
and then not (Get_Pragma_Id (Decl) = Pragma_Precondition
and then
Get_Pragma_Id (Prag) = Pragma_Precondition)
then
Next (Decl);
else
exit;
end if;
end loop;
if Present (Decl) then
Insert_Before (Decl, Prag);
else
Append (Prag, Declarations (N));
end if;
else
Set_Declarations (N, New_List (Prag));
end if;
-- When the context is a library unit, the pragma is added to the
-- Pragmas_After list.
elsif Nkind (Parent (N)) = N_Compilation_Unit then
Aux := Aux_Decls_Node (Parent (N));
if No (Pragmas_After (Aux)) then
Set_Pragmas_After (Aux, New_List);
end if;
Prepend (Prag, Pragmas_After (Aux));
-- Default
else
Insert_After (N, Prag);
end if;
end Insert_Pragma;
-- Local variables
Aspect : Node_Id;
Aitem : Node_Id;
Ent : Node_Id;
L : constant List_Id := Aspect_Specifications (N);
Ins_Node : Node_Id := N;
-- Insert pragmas/attribute definition clause after this node when no
-- delayed analysis is required.
-- Start of processing for Analyze_Aspect_Specifications
-- The general processing involves building an attribute definition
-- clause or a pragma node that corresponds to the aspect. Then in order
-- to delay the evaluation of this aspect to the freeze point, we attach
-- the corresponding pragma/attribute definition clause to the aspect
-- specification node, which is then placed in the Rep Item chain. In
-- this case we mark the entity by setting the flag Has_Delayed_Aspects
-- and we evaluate the rep item at the freeze point. When the aspect
-- doesn't have a corresponding pragma/attribute definition clause, then
-- its analysis is simply delayed at the freeze point.
-- Some special cases don't require delay analysis, thus the aspect is
-- analyzed right now.
-- Note that there is a special handling for Pre, Post, Test_Case,
-- Contract_Cases aspects. In these cases, we do not have to worry
-- about delay issues, since the pragmas themselves deal with delay
-- of visibility for the expression analysis. Thus, we just insert
-- the pragma after the node N.
begin
pragma Assert (Present (L));
-- Loop through aspects
Aspect := First (L);
Aspect_Loop : while Present (Aspect) loop
Analyze_One_Aspect : declare
Expr : constant Node_Id := Expression (Aspect);
Id : constant Node_Id := Identifier (Aspect);
Loc : constant Source_Ptr := Sloc (Aspect);
Nam : constant Name_Id := Chars (Id);
A_Id : constant Aspect_Id := Get_Aspect_Id (Nam);
Anod : Node_Id;
Delay_Required : Boolean;
-- Set False if delay is not required
Eloc : Source_Ptr := No_Location;
-- Source location of expression, modified when we split PPC's. It
-- is set below when Expr is present.
procedure Analyze_Aspect_External_Or_Link_Name;
-- Perform analysis of the External_Name or Link_Name aspects
procedure Analyze_Aspect_Implicit_Dereference;
-- Perform analysis of the Implicit_Dereference aspects
procedure Make_Aitem_Pragma
(Pragma_Argument_Associations : List_Id;
Pragma_Name : Name_Id);
-- This is a wrapper for Make_Pragma used for converting aspects
-- to pragmas. It takes care of Sloc (set from Loc) and building
-- the pragma identifier from the given name. In addition the
-- flags Class_Present and Split_PPC are set from the aspect
-- node, as well as Is_Ignored. This routine also sets the
-- From_Aspect_Specification in the resulting pragma node to
-- True, and sets Corresponding_Aspect to point to the aspect.
-- The resulting pragma is assigned to Aitem.
------------------------------------------
-- Analyze_Aspect_External_Or_Link_Name --
------------------------------------------
procedure Analyze_Aspect_External_Or_Link_Name is
begin
-- Verify that there is an Import/Export aspect defined for the
-- entity. The processing of that aspect in turn checks that
-- there is a Convention aspect declared. The pragma is
-- constructed when processing the Convention aspect.
declare
A : Node_Id;
begin
A := First (L);
while Present (A) loop
exit when Nam_In (Chars (Identifier (A)), Name_Export,
Name_Import);
Next (A);
end loop;
if No (A) then
Error_Msg_N
("missing Import/Export for Link/External name",
Aspect);
end if;
end;
end Analyze_Aspect_External_Or_Link_Name;
-----------------------------------------
-- Analyze_Aspect_Implicit_Dereference --
-----------------------------------------
procedure Analyze_Aspect_Implicit_Dereference is
begin
if not Is_Type (E) or else not Has_Discriminants (E) then
Error_Msg_N
("aspect must apply to a type with discriminants", N);
else
declare
Disc : Entity_Id;
begin
Disc := First_Discriminant (E);
while Present (Disc) loop
if Chars (Expr) = Chars (Disc)
and then Ekind (Etype (Disc)) =
E_Anonymous_Access_Type
then
Set_Has_Implicit_Dereference (E);
Set_Has_Implicit_Dereference (Disc);
return;
end if;
Next_Discriminant (Disc);
end loop;
-- Error if no proper access discriminant.
Error_Msg_NE
("not an access discriminant of&", Expr, E);
end;
end if;
end Analyze_Aspect_Implicit_Dereference;
-----------------------
-- Make_Aitem_Pragma --
-----------------------
procedure Make_Aitem_Pragma
(Pragma_Argument_Associations : List_Id;
Pragma_Name : Name_Id)
is
Args : List_Id := Pragma_Argument_Associations;
begin
-- We should never get here if aspect was disabled
pragma Assert (not Is_Disabled (Aspect));
-- Certain aspects allow for an optional name or expression. Do
-- not generate a pragma with empty argument association list.
if No (Args) or else No (Expression (First (Args))) then
Args := No_List;
end if;
-- Build the pragma
Aitem :=
Make_Pragma (Loc,
Pragma_Argument_Associations => Args,
Pragma_Identifier =>
Make_Identifier (Sloc (Id), Pragma_Name),
Class_Present => Class_Present (Aspect),
Split_PPC => Split_PPC (Aspect));
-- Set additional semantic fields
if Is_Ignored (Aspect) then
Set_Is_Ignored (Aitem);
elsif Is_Checked (Aspect) then
Set_Is_Checked (Aitem);
end if;
Set_Corresponding_Aspect (Aitem, Aspect);
Set_From_Aspect_Specification (Aitem, True);
end Make_Aitem_Pragma;
-- Start of processing for Analyze_One_Aspect
begin
-- Skip aspect if already analyzed, to avoid looping in some cases
if Analyzed (Aspect) then
goto Continue;
end if;
-- Skip looking at aspect if it is totally disabled. Just mark it
-- as such for later reference in the tree. This also sets the
-- Is_Ignored and Is_Checked flags appropriately.
Check_Applicable_Policy (Aspect);
if Is_Disabled (Aspect) then
goto Continue;
end if;
-- Set the source location of expression, used in the case of
-- a failed precondition/postcondition or invariant. Note that
-- the source location of the expression is not usually the best
-- choice here. For example, it gets located on the last AND
-- keyword in a chain of boolean expressiond AND'ed together.
-- It is best to put the message on the first character of the
-- assertion, which is the effect of the First_Node call here.
if Present (Expr) then
Eloc := Sloc (First_Node (Expr));
end if;
-- Check restriction No_Implementation_Aspect_Specifications
if Implementation_Defined_Aspect (A_Id) then
Check_Restriction
(No_Implementation_Aspect_Specifications, Aspect);
end if;
-- Check restriction No_Specification_Of_Aspect
Check_Restriction_No_Specification_Of_Aspect (Aspect);
-- Mark aspect analyzed (actual analysis is delayed till later)
Set_Analyzed (Aspect);
Set_Entity (Aspect, E);
Ent := New_Occurrence_Of (E, Sloc (Id));
-- Check for duplicate aspect. Note that the Comes_From_Source
-- test allows duplicate Pre/Post's that we generate internally
-- to escape being flagged here.
if No_Duplicates_Allowed (A_Id) then
Anod := First (L);
while Anod /= Aspect loop
if Comes_From_Source (Aspect)
and then Same_Aspect (A_Id, Get_Aspect_Id (Anod))
then
Error_Msg_Name_1 := Nam;
Error_Msg_Sloc := Sloc (Anod);
-- Case of same aspect specified twice
if Class_Present (Anod) = Class_Present (Aspect) then
if not Class_Present (Anod) then
Error_Msg_NE
("aspect% for & previously given#",
Id, E);
else
Error_Msg_NE
("aspect `%''Class` for & previously given#",
Id, E);
end if;
end if;
end if;
Next (Anod);
end loop;
end if;
-- Check some general restrictions on language defined aspects
if not Implementation_Defined_Aspect (A_Id) then
Error_Msg_Name_1 := Nam;
-- Not allowed for renaming declarations
if Nkind (N) in N_Renaming_Declaration then
Error_Msg_N
("aspect % not allowed for renaming declaration",
Aspect);
end if;
-- Not allowed for formal type declarations
if Nkind (N) = N_Formal_Type_Declaration then
Error_Msg_N
("aspect % not allowed for formal type declaration",
Aspect);
end if;
end if;
-- Copy expression for later processing by the procedures
-- Check_Aspect_At_[Freeze_Point | End_Of_Declarations]
Set_Entity (Id, New_Copy_Tree (Expr));
-- Set Delay_Required as appropriate to aspect
case Aspect_Delay (A_Id) is
when Always_Delay =>
Delay_Required := True;
when Never_Delay =>
Delay_Required := False;
when Rep_Aspect =>
-- If expression has the form of an integer literal, then
-- do not delay, since we know the value cannot change.
-- This optimization catches most rep clause cases.
-- For Boolean aspects, don't delay if no expression
if A_Id in Boolean_Aspects and then No (Expr) then
Delay_Required := False;
-- For non-Boolean aspects, don't delay if integer literal
elsif A_Id not in Boolean_Aspects
and then Present (Expr)
and then Nkind (Expr) = N_Integer_Literal
then
Delay_Required := False;
-- All other cases are delayed
else
Delay_Required := True;
Set_Has_Delayed_Rep_Aspects (E);
end if;
end case;
-- Processing based on specific aspect
case A_Id is
when Aspect_Unimplemented =>
null; -- ??? temp for now
-- No_Aspect should be impossible
when No_Aspect =>
raise Program_Error;
-- Case 1: Aspects corresponding to attribute definition
-- clauses.
when Aspect_Address |
Aspect_Alignment |
Aspect_Bit_Order |
Aspect_Component_Size |
Aspect_Constant_Indexing |
Aspect_Default_Iterator |
Aspect_Dispatching_Domain |
Aspect_External_Tag |
Aspect_Input |
Aspect_Iterable |
Aspect_Iterator_Element |
Aspect_Machine_Radix |
Aspect_Object_Size |
Aspect_Output |
Aspect_Read |
Aspect_Scalar_Storage_Order |
Aspect_Size |
Aspect_Small |
Aspect_Simple_Storage_Pool |
Aspect_Storage_Pool |
Aspect_Stream_Size |
Aspect_Value_Size |
Aspect_Variable_Indexing |
Aspect_Write =>
-- Indexing aspects apply only to tagged type
if (A_Id = Aspect_Constant_Indexing
or else
A_Id = Aspect_Variable_Indexing)
and then not (Is_Type (E)
and then Is_Tagged_Type (E))
then
Error_Msg_N
("indexing aspect can only apply to a tagged type",
Aspect);
goto Continue;
end if;
-- For the case of aspect Address, we don't consider that we
-- know the entity is never set in the source, since it is
-- is likely aliasing is occurring.
-- Note: one might think that the analysis of the resulting
-- attribute definition clause would take care of that, but
-- that's not the case since it won't be from source.
if A_Id = Aspect_Address then
Set_Never_Set_In_Source (E, False);
end if;
-- Correctness of the profile of a stream operation is
-- verified at the freeze point, but we must detect the
-- illegal specification of this aspect for a subtype now,
-- to prevent malformed rep_item chains.
if A_Id = Aspect_Input or else
A_Id = Aspect_Output or else
A_Id = Aspect_Read or else
A_Id = Aspect_Write
then
if not Is_First_Subtype (E) then
Error_Msg_N
("local name must be a first subtype", Aspect);
goto Continue;
-- If stream aspect applies to the class-wide type,
-- the generated attribute definition applies to the
-- class-wide type as well.
elsif Class_Present (Aspect) then
Ent :=
Make_Attribute_Reference (Loc,
Prefix => Ent,
Attribute_Name => Name_Class);
end if;
end if;
-- Construct the attribute definition clause
Aitem :=
Make_Attribute_Definition_Clause (Loc,
Name => Ent,
Chars => Chars (Id),
Expression => Relocate_Node (Expr));
-- If the address is specified, then we treat the entity as
-- referenced, to avoid spurious warnings. This is analogous
-- to what is done with an attribute definition clause, but
-- here we don't want to generate a reference because this
-- is the point of definition of the entity.
if A_Id = Aspect_Address then
Set_Referenced (E);
end if;
-- Case 2: Aspects corresponding to pragmas
-- Case 2a: Aspects corresponding to pragmas with two
-- arguments, where the first argument is a local name
-- referring to the entity, and the second argument is the
-- aspect definition expression.
-- Linker_Section/Suppress/Unsuppress
when Aspect_Linker_Section |
Aspect_Suppress |
Aspect_Unsuppress =>
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => New_Occurrence_Of (E, Loc)),
Make_Pragma_Argument_Association (Sloc (Expr),
Expression => Relocate_Node (Expr))),
Pragma_Name => Chars (Id));
-- Synchronization
-- Corresponds to pragma Implemented, construct the pragma
when Aspect_Synchronization =>
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => New_Occurrence_Of (E, Loc)),
Make_Pragma_Argument_Association (Sloc (Expr),
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Implemented);
-- Attach_Handler
when Aspect_Attach_Handler =>
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Sloc (Ent),
Expression => Ent),
Make_Pragma_Argument_Association (Sloc (Expr),
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Attach_Handler);
-- We need to insert this pragma into the tree to get proper
-- processing and to look valid from a placement viewpoint.
Insert_Pragma (Aitem);
goto Continue;
-- Dynamic_Predicate, Predicate, Static_Predicate
when Aspect_Dynamic_Predicate |
Aspect_Predicate |
Aspect_Static_Predicate =>
-- These aspects apply only to subtypes
if not Is_Type (E) then
Error_Msg_N
("predicate can only be specified for a subtype",
Aspect);
goto Continue;
elsif Is_Incomplete_Type (E) then
Error_Msg_N
("predicate cannot apply to incomplete view", Aspect);
goto Continue;
end if;
-- Construct the pragma (always a pragma Predicate, with
-- flags recording whether it is static/dynamic). We also
-- set flags recording this in the type itself.
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Sloc (Ent),
Expression => Ent),
Make_Pragma_Argument_Association (Sloc (Expr),
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Predicate);
-- Mark type has predicates, and remember what kind of
-- aspect lead to this predicate (we need this to access
-- the right set of check policies later on).
Set_Has_Predicates (E);
if A_Id = Aspect_Dynamic_Predicate then
Set_Has_Dynamic_Predicate_Aspect (E);
elsif A_Id = Aspect_Static_Predicate then
Set_Has_Static_Predicate_Aspect (E);
end if;
-- If the type is private, indicate that its completion
-- has a freeze node, because that is the one that will
-- be visible at freeze time.
if Is_Private_Type (E) and then Present (Full_View (E)) then
Set_Has_Predicates (Full_View (E));
if A_Id = Aspect_Dynamic_Predicate then
Set_Has_Dynamic_Predicate_Aspect (Full_View (E));
elsif A_Id = Aspect_Static_Predicate then
Set_Has_Static_Predicate_Aspect (Full_View (E));
end if;
Set_Has_Delayed_Aspects (Full_View (E));
Ensure_Freeze_Node (Full_View (E));
end if;
-- Case 2b: Aspects corresponding to pragmas with two
-- arguments, where the second argument is a local name
-- referring to the entity, and the first argument is the
-- aspect definition expression.
-- Convention
when Aspect_Convention =>
-- The aspect may be part of the specification of an import
-- or export pragma. Scan the aspect list to gather the
-- other components, if any. The name of the generated
-- pragma is one of Convention/Import/Export.
declare
Args : constant List_Id := New_List (
Make_Pragma_Argument_Association (Sloc (Expr),
Expression => Relocate_Node (Expr)),
Make_Pragma_Argument_Association (Sloc (Ent),
Expression => Ent));
Imp_Exp_Seen : Boolean := False;
-- Flag set when aspect Import or Export has been seen
Imp_Seen : Boolean := False;
-- Flag set when aspect Import has been seen
Asp : Node_Id;
Asp_Nam : Name_Id;
Extern_Arg : Node_Id;
Link_Arg : Node_Id;
Prag_Nam : Name_Id;
begin
Extern_Arg := Empty;
Link_Arg := Empty;
Prag_Nam := Chars (Id);
Asp := First (L);
while Present (Asp) loop
Asp_Nam := Chars (Identifier (Asp));
-- Aspects Import and Export take precedence over
-- aspect Convention. As a result the generated pragma
-- must carry the proper interfacing aspect's name.
if Nam_In (Asp_Nam, Name_Import, Name_Export) then
if Imp_Exp_Seen then
Error_Msg_N ("conflicting", Asp);
else
Imp_Exp_Seen := True;
if Asp_Nam = Name_Import then
Imp_Seen := True;
end if;
end if;
Prag_Nam := Asp_Nam;
-- Aspect External_Name adds an extra argument to the
-- generated pragma.
elsif Asp_Nam = Name_External_Name then
Extern_Arg :=
Make_Pragma_Argument_Association (Loc,
Chars => Asp_Nam,
Expression => Relocate_Node (Expression (Asp)));
-- Aspect Link_Name adds an extra argument to the
-- generated pragma.
elsif Asp_Nam = Name_Link_Name then
Link_Arg :=
Make_Pragma_Argument_Association (Loc,
Chars => Asp_Nam,
Expression => Relocate_Node (Expression (Asp)));
end if;
Next (Asp);
end loop;
-- Assemble the full argument list
if Present (Extern_Arg) then
Append_To (Args, Extern_Arg);
end if;
if Present (Link_Arg) then
Append_To (Args, Link_Arg);
end if;
Make_Aitem_Pragma
(Pragma_Argument_Associations => Args,
Pragma_Name => Prag_Nam);
-- Store the generated pragma Import in the related
-- subprogram.
if Imp_Seen and then Is_Subprogram (E) then
Set_Import_Pragma (E, Aitem);
end if;
end;
-- CPU, Interrupt_Priority, Priority
-- These three aspects can be specified for a subprogram spec
-- or body, in which case we analyze the expression and export
-- the value of the aspect.
-- Previously, we generated an equivalent pragma for bodies
-- (note that the specs cannot contain these pragmas). The
-- pragma was inserted ahead of local declarations, rather than
-- after the body. This leads to a certain duplication between
-- the processing performed for the aspect and the pragma, but
-- given the straightforward handling required it is simpler
-- to duplicate than to translate the aspect in the spec into
-- a pragma in the declarative part of the body.
when Aspect_CPU |
Aspect_Interrupt_Priority |
Aspect_Priority =>
if Nkind_In (N, N_Subprogram_Body,
N_Subprogram_Declaration)
then
-- Analyze the aspect expression
Analyze_And_Resolve (Expr, Standard_Integer);
-- Interrupt_Priority aspect not allowed for main
-- subprograms. ARM D.1 does not forbid this explicitly,
-- but ARM J.15.11 (6/3) does not permit pragma
-- Interrupt_Priority for subprograms.
if A_Id = Aspect_Interrupt_Priority then
Error_Msg_N
("Interrupt_Priority aspect cannot apply to "
& "subprogram", Expr);
-- The expression must be static
elsif not Is_OK_Static_Expression (Expr) then
Flag_Non_Static_Expr
("aspect requires static expression!", Expr);
-- Check whether this is the main subprogram. Issue a
-- warning only if it is obviously not a main program
-- (when it has parameters or when the subprogram is
-- within a package).
elsif Present (Parameter_Specifications
(Specification (N)))
or else not Is_Compilation_Unit (Defining_Entity (N))
then
-- See ARM D.1 (14/3) and D.16 (12/3)
Error_Msg_N
("aspect applied to subprogram other than the "
& "main subprogram has no effect??", Expr);
-- Otherwise check in range and export the value
-- For the CPU aspect
elsif A_Id = Aspect_CPU then
if Is_In_Range (Expr, RTE (RE_CPU_Range)) then
-- Value is correct so we export the value to make
-- it available at execution time.
Set_Main_CPU
(Main_Unit, UI_To_Int (Expr_Value (Expr)));
else
Error_Msg_N
("main subprogram CPU is out of range", Expr);
end if;
-- For the Priority aspect
elsif A_Id = Aspect_Priority then
if Is_In_Range (Expr, RTE (RE_Priority)) then
-- Value is correct so we export the value to make
-- it available at execution time.
Set_Main_Priority
(Main_Unit, UI_To_Int (Expr_Value (Expr)));
-- Ignore pragma if Relaxed_RM_Semantics to support
-- other targets/non GNAT compilers.
elsif not Relaxed_RM_Semantics then
Error_Msg_N
("main subprogram priority is out of range",
Expr);
end if;
end if;
-- Load an arbitrary entity from System.Tasking.Stages
-- or System.Tasking.Restricted.Stages (depending on
-- the supported profile) to make sure that one of these
-- packages is implicitly with'ed, since we need to have
-- the tasking run time active for the pragma Priority to
-- have any effect. Previously we with'ed the package
-- System.Tasking, but this package does not trigger the
-- required initialization of the run-time library.
declare
Discard : Entity_Id;
begin
if Restricted_Profile then
Discard := RTE (RE_Activate_Restricted_Tasks);
else
Discard := RTE (RE_Activate_Tasks);
end if;
end;
-- Handling for these Aspects in subprograms is complete
goto Continue;
-- For tasks
else
-- Pass the aspect as an attribute
Aitem :=
Make_Attribute_Definition_Clause (Loc,
Name => Ent,
Chars => Chars (Id),
Expression => Relocate_Node (Expr));
end if;
-- Warnings
when Aspect_Warnings =>
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Sloc (Expr),
Expression => Relocate_Node (Expr)),
Make_Pragma_Argument_Association (Loc,
Expression => New_Occurrence_Of (E, Loc))),
Pragma_Name => Chars (Id));
-- Case 2c: Aspects corresponding to pragmas with three
-- arguments.
-- Invariant aspects have a first argument that references the
-- entity, a second argument that is the expression and a third
-- argument that is an appropriate message.
-- Invariant, Type_Invariant
when Aspect_Invariant |
Aspect_Type_Invariant =>
-- Analysis of the pragma will verify placement legality:
-- an invariant must apply to a private type, or appear in
-- the private part of a spec and apply to a completion.
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Sloc (Ent),
Expression => Ent),
Make_Pragma_Argument_Association (Sloc (Expr),
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Invariant);
-- Add message unless exception messages are suppressed
if not Opt.Exception_Locations_Suppressed then
Append_To (Pragma_Argument_Associations (Aitem),
Make_Pragma_Argument_Association (Eloc,
Chars => Name_Message,
Expression =>
Make_String_Literal (Eloc,
Strval => "failed invariant from "
& Build_Location_String (Eloc))));
end if;
-- For Invariant case, insert immediately after the entity
-- declaration. We do not have to worry about delay issues
-- since the pragma processing takes care of this.
Delay_Required := False;
-- Case 2d : Aspects that correspond to a pragma with one
-- argument.
-- Abstract_State
-- Aspect Abstract_State introduces implicit declarations for
-- all state abstraction entities it defines. To emulate this
-- behavior, insert the pragma at the beginning of the visible
-- declarations of the related package so that it is analyzed
-- immediately.
when Aspect_Abstract_State => Abstract_State : declare
Context : Node_Id := N;
Decl : Node_Id;
Decls : List_Id;
begin
-- When aspect Abstract_State appears on a generic package,
-- it is propageted to the package instance. The context in
-- this case is the instance spec.
if Nkind (Context) = N_Package_Instantiation then
Context := Instance_Spec (Context);
end if;
if Nkind_In (Context, N_Generic_Package_Declaration,
N_Package_Declaration)
then
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Abstract_State);
Decorate (Aspect, Aitem);
Decls := Visible_Declarations (Specification (Context));
-- In general pragma Abstract_State must be at the top
-- of the existing visible declarations to emulate its
-- source counterpart. The only exception to this is a
-- generic instance in which case the pragma must be
-- inserted after the association renamings.
if Present (Decls) then
Decl := First (Decls);
-- The visible declarations of a generic instance have
-- the following structure:
-- <renamings of generic formals>
-- <renamings of internally-generated spec and body>
-- <first source declaration>
-- The pragma must be inserted before the first source
-- declaration, skip the instance "header".
if Is_Generic_Instance (Defining_Entity (Context)) then
while Present (Decl)
and then not Comes_From_Source (Decl)
loop
Decl := Next (Decl);
end loop;
end if;
-- When aspects Abstract_State, Ghost,
-- Initial_Condition and Initializes are out of order,
-- ensure that pragma SPARK_Mode is always at the top
-- of the declarations to properly enabled/suppress
-- errors.
Insert_After_SPARK_Mode
(Prag => Aitem,
Ins_Nod => Decl,
Decls => Decls);
-- Otherwise the pragma forms a new declarative list
else
Set_Visible_Declarations
(Specification (Context), New_List (Aitem));
end if;
else
Error_Msg_NE
("aspect & must apply to a package declaration",
Aspect, Id);
end if;
goto Continue;
end Abstract_State;
-- Aspect Default_Internal_Condition is never delayed because
-- it is equivalent to a source pragma which appears after the
-- related private type. To deal with forward references, the
-- generated pragma is stored in the rep chain of the related
-- private type as types do not carry contracts. The pragma is
-- wrapped inside of a procedure at the freeze point of the
-- private type's full view.
when Aspect_Default_Initial_Condition =>
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name =>
Name_Default_Initial_Condition);
Decorate (Aspect, Aitem);
Insert_Pragma (Aitem);
goto Continue;
-- Default_Storage_Pool
when Aspect_Default_Storage_Pool =>
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name =>
Name_Default_Storage_Pool);
Decorate (Aspect, Aitem);
Insert_Pragma (Aitem);
goto Continue;
-- Depends
-- Aspect Depends is never delayed because it is equivalent to
-- a source pragma which appears after the related subprogram.
-- To deal with forward references, the generated pragma is
-- stored in the contract of the related subprogram and later
-- analyzed at the end of the declarative region. See routine
-- Analyze_Depends_In_Decl_Part for details.
when Aspect_Depends =>
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Depends);
Decorate (Aspect, Aitem);
Insert_Pragma (Aitem);
goto Continue;
-- Aspect Extensions_Visible is never delayed because it is
-- equivalent to a source pragma which appears after the
-- related subprogram.
when Aspect_Extensions_Visible =>
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Extensions_Visible);
Decorate (Aspect, Aitem);
Insert_Pragma (Aitem);
goto Continue;
-- Aspect Ghost is never delayed because it is equivalent to a
-- source pragma which appears at the top of [generic] package
-- declarations or after an object, a [generic] subprogram, or
-- a type declaration.
when Aspect_Ghost => Ghost : declare
Decls : List_Id;
begin
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Ghost);
Decorate (Aspect, Aitem);
-- When the aspect applies to a [generic] package, insert
-- the pragma at the top of the visible declarations. This
-- emulates the placement of a source pragma.
if Nkind_In (N, N_Generic_Package_Declaration,
N_Package_Declaration)
then
Decls := Visible_Declarations (Specification (N));
if No (Decls) then
Decls := New_List;
Set_Visible_Declarations (N, Decls);
end if;
-- When aspects Abstract_State, Ghost, Initial_Condition
-- and Initializes are out of order, ensure that pragma
-- SPARK_Mode is always at the top of the declarations to
-- properly enabled/suppress errors.
Insert_After_SPARK_Mode
(Prag => Aitem,
Ins_Nod => First (Decls),
Decls => Decls);
-- Otherwise the context is an object, [generic] subprogram
-- or type declaration.
else
Insert_Pragma (Aitem);
end if;
goto Continue;
end Ghost;
-- Global
-- Aspect Global is never delayed because it is equivalent to
-- a source pragma which appears after the related subprogram.
-- To deal with forward references, the generated pragma is
-- stored in the contract of the related subprogram and later
-- analyzed at the end of the declarative region. See routine
-- Analyze_Global_In_Decl_Part for details.
when Aspect_Global =>
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Global);
Decorate (Aspect, Aitem);
Insert_Pragma (Aitem);
goto Continue;
-- Initial_Condition
-- Aspect Initial_Condition is never delayed because it is
-- equivalent to a source pragma which appears after the
-- related package. To deal with forward references, the
-- generated pragma is stored in the contract of the related
-- package and later analyzed at the end of the declarative
-- region. See routine Analyze_Initial_Condition_In_Decl_Part
-- for details.
when Aspect_Initial_Condition => Initial_Condition : declare
Context : Node_Id := N;
Decls : List_Id;
begin
-- When aspect Initial_Condition appears on a generic
-- package, it is propageted to the package instance. The
-- context in this case is the instance spec.
if Nkind (Context) = N_Package_Instantiation then
Context := Instance_Spec (Context);
end if;
if Nkind_In (Context, N_Generic_Package_Declaration,
N_Package_Declaration)
then
Decls := Visible_Declarations (Specification (Context));
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name =>
Name_Initial_Condition);
Decorate (Aspect, Aitem);
if No (Decls) then
Decls := New_List;
Set_Visible_Declarations (Context, Decls);
end if;
-- When aspects Abstract_State, Ghost, Initial_Condition
-- and Initializes are out of order, ensure that pragma
-- SPARK_Mode is always at the top of the declarations to
-- properly enabled/suppress errors.
Insert_After_SPARK_Mode
(Prag => Aitem,
Ins_Nod => First (Decls),
Decls => Decls);
else
Error_Msg_NE
("aspect & must apply to a package declaration",
Aspect, Id);
end if;
goto Continue;
end Initial_Condition;
-- Initializes
-- Aspect Initializes is never delayed because it is equivalent
-- to a source pragma appearing after the related package. To
-- deal with forward references, the generated pragma is stored
-- in the contract of the related package and later analyzed at
-- the end of the declarative region. For details, see routine
-- Analyze_Initializes_In_Decl_Part.
when Aspect_Initializes => Initializes : declare
Context : Node_Id := N;
Decls : List_Id;
begin
-- When aspect Initializes appears on a generic package,
-- it is propageted to the package instance. The context
-- in this case is the instance spec.
if Nkind (Context) = N_Package_Instantiation then
Context := Instance_Spec (Context);
end if;
if Nkind_In (Context, N_Generic_Package_Declaration,
N_Package_Declaration)
then
Decls := Visible_Declarations (Specification (Context));
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Initializes);
Decorate (Aspect, Aitem);
if No (Decls) then
Decls := New_List;
Set_Visible_Declarations (Context, Decls);
end if;
-- When aspects Abstract_State, Ghost, Initial_Condition
-- and Initializes are out of order, ensure that pragma
-- SPARK_Mode is always at the top of the declarations to
-- properly enabled/suppress errors.
Insert_After_SPARK_Mode
(Prag => Aitem,
Ins_Nod => First (Decls),
Decls => Decls);
else
Error_Msg_NE
("aspect & must apply to a package declaration",
Aspect, Id);
end if;
goto Continue;
end Initializes;
-- Obsolescent
when Aspect_Obsolescent => declare
Args : List_Id;
begin
if No (Expr) then
Args := No_List;
else
Args := New_List (
Make_Pragma_Argument_Association (Sloc (Expr),
Expression => Relocate_Node (Expr)));
end if;
Make_Aitem_Pragma
(Pragma_Argument_Associations => Args,
Pragma_Name => Chars (Id));
end;
-- Part_Of
when Aspect_Part_Of =>
if Nkind_In (N, N_Object_Declaration,
N_Package_Instantiation)
then
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Part_Of);
else
Error_Msg_NE
("aspect & must apply to a variable or package "
& "instantiation", Aspect, Id);
end if;
-- SPARK_Mode
when Aspect_SPARK_Mode => SPARK_Mode : declare
Decls : List_Id;
begin
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_SPARK_Mode);
-- When the aspect appears on a package or a subprogram
-- body, insert the generated pragma at the top of the body
-- declarations to emulate the behavior of a source pragma.
if Nkind_In (N, N_Package_Body, N_Subprogram_Body) then
Decorate (Aspect, Aitem);
Decls := Declarations (N);
if No (Decls) then
Decls := New_List;
Set_Declarations (N, Decls);
end if;
Prepend_To (Decls, Aitem);
goto Continue;
-- When the aspect is associated with a [generic] package
-- declaration, insert the generated pragma at the top of
-- the visible declarations to emulate the behavior of a
-- source pragma.
elsif Nkind_In (N, N_Generic_Package_Declaration,
N_Package_Declaration)
then
Decorate (Aspect, Aitem);
Decls := Visible_Declarations (Specification (N));
if No (Decls) then
Decls := New_List;
Set_Visible_Declarations (Specification (N), Decls);
end if;
Prepend_To (Decls, Aitem);
goto Continue;
end if;
end SPARK_Mode;
-- Refined_Depends
-- Aspect Refined_Depends is never delayed because it is
-- equivalent to a source pragma which appears in the
-- declarations of the related subprogram body. To deal with
-- forward references, the generated pragma is stored in the
-- contract of the related subprogram body and later analyzed
-- at the end of the declarative region. For details, see
-- routine Analyze_Refined_Depends_In_Decl_Part.
when Aspect_Refined_Depends =>
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Refined_Depends);
Decorate (Aspect, Aitem);
Insert_Pragma (Aitem);
goto Continue;
-- Refined_Global
-- Aspect Refined_Global is never delayed because it is
-- equivalent to a source pragma which appears in the
-- declarations of the related subprogram body. To deal with
-- forward references, the generated pragma is stored in the
-- contract of the related subprogram body and later analyzed
-- at the end of the declarative region. For details, see
-- routine Analyze_Refined_Global_In_Decl_Part.
when Aspect_Refined_Global =>
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Refined_Global);
Decorate (Aspect, Aitem);
Insert_Pragma (Aitem);
goto Continue;
-- Refined_Post
when Aspect_Refined_Post =>
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Refined_Post);
-- Refined_State
when Aspect_Refined_State => Refined_State : declare
Decls : List_Id;
begin
-- The corresponding pragma for Refined_State is inserted in
-- the declarations of the related package body. This action
-- synchronizes both the source and from-aspect versions of
-- the pragma.
if Nkind (N) = N_Package_Body then
Decls := Declarations (N);
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Refined_State);
Decorate (Aspect, Aitem);
if No (Decls) then
Decls := New_List;
Set_Declarations (N, Decls);
end if;
-- Pragma Refined_State must be inserted after pragma
-- SPARK_Mode in the tree. This ensures that any error
-- messages dependent on SPARK_Mode will be properly
-- enabled/suppressed.
Insert_After_SPARK_Mode
(Prag => Aitem,
Ins_Nod => First (Decls),
Decls => Decls);
else
Error_Msg_NE
("aspect & must apply to a package body", Aspect, Id);
end if;
goto Continue;
end Refined_State;
-- Relative_Deadline
when Aspect_Relative_Deadline =>
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Relative_Deadline);
-- If the aspect applies to a task, the corresponding pragma
-- must appear within its declarations, not after.
if Nkind (N) = N_Task_Type_Declaration then
declare
Def : Node_Id;
V : List_Id;
begin
if No (Task_Definition (N)) then
Set_Task_Definition (N,
Make_Task_Definition (Loc,
Visible_Declarations => New_List,
End_Label => Empty));
end if;
Def := Task_Definition (N);
V := Visible_Declarations (Def);
if not Is_Empty_List (V) then
Insert_Before (First (V), Aitem);
else
Set_Visible_Declarations (Def, New_List (Aitem));
end if;
goto Continue;
end;
end if;
-- Case 2e: Annotate aspect
when Aspect_Annotate =>
declare
Args : List_Id;
Pargs : List_Id;
Arg : Node_Id;
begin
-- The argument can be a single identifier
if Nkind (Expr) = N_Identifier then
-- One level of parens is allowed
if Paren_Count (Expr) > 1 then
Error_Msg_F ("extra parentheses ignored", Expr);
end if;
Set_Paren_Count (Expr, 0);
-- Add the single item to the list
Args := New_List (Expr);
-- Otherwise we must have an aggregate
elsif Nkind (Expr) = N_Aggregate then
-- Must be positional
if Present (Component_Associations (Expr)) then
Error_Msg_F
("purely positional aggregate required", Expr);
goto Continue;
end if;
-- Must not be parenthesized
if Paren_Count (Expr) /= 0 then
Error_Msg_F ("extra parentheses ignored", Expr);
end if;
-- List of arguments is list of aggregate expressions
Args := Expressions (Expr);
-- Anything else is illegal
else
Error_Msg_F ("wrong form for Annotate aspect", Expr);
goto Continue;
end if;
-- Prepare pragma arguments
Pargs := New_List;
Arg := First (Args);
while Present (Arg) loop
Append_To (Pargs,
Make_Pragma_Argument_Association (Sloc (Arg),
Expression => Relocate_Node (Arg)));
Next (Arg);
end loop;
Append_To (Pargs,
Make_Pragma_Argument_Association (Sloc (Ent),
Chars => Name_Entity,
Expression => Ent));
Make_Aitem_Pragma
(Pragma_Argument_Associations => Pargs,
Pragma_Name => Name_Annotate);
end;
-- Case 3 : Aspects that don't correspond to pragma/attribute
-- definition clause.
-- Case 3a: The aspects listed below don't correspond to
-- pragmas/attributes but do require delayed analysis.
-- Default_Value can only apply to a scalar type
when Aspect_Default_Value =>
if not Is_Scalar_Type (E) then
Error_Msg_N
("aspect Default_Value must apply to a scalar type", N);
end if;
Aitem := Empty;
-- Default_Component_Value can only apply to an array type
-- with scalar components.
when Aspect_Default_Component_Value =>
if not (Is_Array_Type (E)
and then Is_Scalar_Type (Component_Type (E)))
then
Error_Msg_N ("aspect Default_Component_Value can only "
& "apply to an array of scalar components", N);
end if;
Aitem := Empty;
-- Case 3b: The aspects listed below don't correspond to
-- pragmas/attributes and don't need delayed analysis.
-- Implicit_Dereference
-- For Implicit_Dereference, External_Name and Link_Name, only
-- the legality checks are done during the analysis, thus no
-- delay is required.
when Aspect_Implicit_Dereference =>
Analyze_Aspect_Implicit_Dereference;
goto Continue;
-- External_Name, Link_Name
when Aspect_External_Name |
Aspect_Link_Name =>
Analyze_Aspect_External_Or_Link_Name;
goto Continue;
-- Dimension
when Aspect_Dimension =>
Analyze_Aspect_Dimension (N, Id, Expr);
goto Continue;
-- Dimension_System
when Aspect_Dimension_System =>
Analyze_Aspect_Dimension_System (N, Id, Expr);
goto Continue;
-- Case 4: Aspects requiring special handling
-- Pre/Post/Test_Case/Contract_Cases whose corresponding
-- pragmas take care of the delay.
-- Pre/Post
-- Aspects Pre/Post generate Precondition/Postcondition pragmas
-- with a first argument that is the expression, and a second
-- argument that is an informative message if the test fails.
-- This is inserted right after the declaration, to get the
-- required pragma placement. The processing for the pragmas
-- takes care of the required delay.
when Pre_Post_Aspects => Pre_Post : declare
Pname : Name_Id;
begin
if A_Id = Aspect_Pre or else A_Id = Aspect_Precondition then
Pname := Name_Precondition;
else
Pname := Name_Postcondition;
end if;
-- If the expressions is of the form A and then B, then
-- we generate separate Pre/Post aspects for the separate
-- clauses. Since we allow multiple pragmas, there is no
-- problem in allowing multiple Pre/Post aspects internally.
-- These should be treated in reverse order (B first and
-- A second) since they are later inserted just after N in
-- the order they are treated. This way, the pragma for A
-- ends up preceding the pragma for B, which may have an
-- importance for the error raised (either constraint error
-- or precondition error).
-- We do not do this for Pre'Class, since we have to put
-- these conditions together in a complex OR expression.
-- We do not do this in ASIS mode, as ASIS relies on the
-- original node representing the complete expression, when
-- retrieving it through the source aspect table.
if not ASIS_Mode
and then (Pname = Name_Postcondition
or else not Class_Present (Aspect))
then
while Nkind (Expr) = N_And_Then loop
Insert_After (Aspect,
Make_Aspect_Specification (Sloc (Left_Opnd (Expr)),
Identifier => Identifier (Aspect),
Expression => Relocate_Node (Left_Opnd (Expr)),
Class_Present => Class_Present (Aspect),
Split_PPC => True));
Rewrite (Expr, Relocate_Node (Right_Opnd (Expr)));
Eloc := Sloc (Expr);
end loop;
end if;
-- Build the precondition/postcondition pragma
-- Add note about why we do NOT need Copy_Tree here???
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Eloc,
Chars => Name_Check,
Expression => Relocate_Node (Expr))),
Pragma_Name => Pname);
-- Add message unless exception messages are suppressed
if not Opt.Exception_Locations_Suppressed then
Append_To (Pragma_Argument_Associations (Aitem),
Make_Pragma_Argument_Association (Eloc,
Chars => Name_Message,
Expression =>
Make_String_Literal (Eloc,
Strval => "failed "
& Get_Name_String (Pname)
& " from "
& Build_Location_String (Eloc))));
end if;
Set_Is_Delayed_Aspect (Aspect);
-- For Pre/Post cases, insert immediately after the entity
-- declaration, since that is the required pragma placement.
-- Note that for these aspects, we do not have to worry
-- about delay issues, since the pragmas themselves deal
-- with delay of visibility for the expression analysis.
Insert_Pragma (Aitem);
goto Continue;
end Pre_Post;
-- Test_Case
when Aspect_Test_Case => Test_Case : declare
Args : List_Id;
Comp_Expr : Node_Id;
Comp_Assn : Node_Id;
New_Expr : Node_Id;
begin
Args := New_List;
if Nkind (Parent (N)) = N_Compilation_Unit then
Error_Msg_Name_1 := Nam;
Error_Msg_N ("incorrect placement of aspect `%`", E);
goto Continue;
end if;
if Nkind (Expr) /= N_Aggregate then
Error_Msg_Name_1 := Nam;
Error_Msg_NE
("wrong syntax for aspect `%` for &", Id, E);
goto Continue;
end if;
-- Make pragma expressions refer to the original aspect
-- expressions through the Original_Node link. This is used
-- in semantic analysis for ASIS mode, so that the original
-- expression also gets analyzed.
Comp_Expr := First (Expressions (Expr));
while Present (Comp_Expr) loop
New_Expr := Relocate_Node (Comp_Expr);
Append_To (Args,
Make_Pragma_Argument_Association (Sloc (Comp_Expr),
Expression => New_Expr));
Next (Comp_Expr);
end loop;
Comp_Assn := First (Component_Associations (Expr));
while Present (Comp_Assn) loop
if List_Length (Choices (Comp_Assn)) /= 1
or else
Nkind (First (Choices (Comp_Assn))) /= N_Identifier
then
Error_Msg_Name_1 := Nam;
Error_Msg_NE
("wrong syntax for aspect `%` for &", Id, E);
goto Continue;
end if;
Append_To (Args,
Make_Pragma_Argument_Association (Sloc (Comp_Assn),
Chars => Chars (First (Choices (Comp_Assn))),
Expression =>
Relocate_Node (Expression (Comp_Assn))));
Next (Comp_Assn);
end loop;
-- Build the test-case pragma
Make_Aitem_Pragma
(Pragma_Argument_Associations => Args,
Pragma_Name => Nam);
end Test_Case;
-- Contract_Cases
when Aspect_Contract_Cases =>
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name => Nam);
Decorate (Aspect, Aitem);
Insert_Pragma (Aitem);
goto Continue;
-- Case 5: Special handling for aspects with an optional
-- boolean argument.
-- In the general case, the corresponding pragma cannot be
-- generated yet because the evaluation of the boolean needs
-- to be delayed till the freeze point.
when Boolean_Aspects |
Library_Unit_Aspects =>
Set_Is_Boolean_Aspect (Aspect);
-- Lock_Free aspect only apply to protected objects
if A_Id = Aspect_Lock_Free then
if Ekind (E) /= E_Protected_Type then
Error_Msg_Name_1 := Nam;
Error_Msg_N
("aspect % only applies to a protected object",
Aspect);
else
-- Set the Uses_Lock_Free flag to True if there is no
-- expression or if the expression is True. The
-- evaluation of this aspect should be delayed to the
-- freeze point (why???)
if No (Expr)
or else Is_True (Static_Boolean (Expr))
then
Set_Uses_Lock_Free (E);
end if;
Record_Rep_Item (E, Aspect);
end if;
goto Continue;
elsif A_Id = Aspect_Import or else A_Id = Aspect_Export then
-- For the case of aspects Import and Export, we don't
-- consider that we know the entity is never set in the
-- source, since it is is likely modified outside the
-- program.
-- Note: one might think that the analysis of the
-- resulting pragma would take care of that, but
-- that's not the case since it won't be from source.
if Ekind (E) = E_Variable then
Set_Never_Set_In_Source (E, False);
end if;
-- In older versions of Ada the corresponding pragmas
-- specified a Convention. In Ada 2012 the convention is
-- specified as a separate aspect, and it is optional,
-- given that it defaults to Convention_Ada. The code
-- that verifed that there was a matching convention
-- is now obsolete.
-- Resolve the expression of an Import or Export here,
-- and require it to be of type Boolean and static. This
-- is not quite right, because in general this should be
-- delayed, but that seems tricky for these, because
-- normally Boolean aspects are replaced with pragmas at
-- the freeze point (in Make_Pragma_From_Boolean_Aspect),
-- but in the case of these aspects we can't generate
-- a simple pragma with just the entity name. ???
if not Present (Expr)
or else Is_True (Static_Boolean (Expr))
then
if A_Id = Aspect_Import then
Set_Is_Imported (E);
-- An imported entity cannot have an explicit
-- initialization.
if Nkind (N) = N_Object_Declaration
and then Present (Expression (N))
then
Error_Msg_N
("imported entities cannot be initialized "
& "(RM B.1(24))", Expression (N));
end if;
elsif A_Id = Aspect_Export then
Set_Is_Exported (E);
end if;
end if;
goto Continue;
end if;
-- Library unit aspects require special handling in the case
-- of a package declaration, the pragma needs to be inserted
-- in the list of declarations for the associated package.
-- There is no issue of visibility delay for these aspects.
if A_Id in Library_Unit_Aspects
and then
Nkind_In (N, N_Package_Declaration,
N_Generic_Package_Declaration)
and then Nkind (Parent (N)) /= N_Compilation_Unit
-- Aspect is legal on a local instantiation of a library-
-- level generic unit.
and then not Is_Generic_Instance (Defining_Entity (N))
then
Error_Msg_N
("incorrect context for library unit aspect&", Id);
goto Continue;
end if;
-- External property aspects are Boolean by nature, but
-- their pragmas must contain two arguments, the second
-- being the optional Boolean expression.
if A_Id = Aspect_Async_Readers or else
A_Id = Aspect_Async_Writers or else
A_Id = Aspect_Effective_Reads or else
A_Id = Aspect_Effective_Writes
then
declare
Args : List_Id;
begin
-- The first argument of the external property pragma
-- is the related object.
Args :=
New_List (
Make_Pragma_Argument_Association (Sloc (Ent),
Expression => Ent));
-- The second argument is the optional Boolean
-- expression which must be propagated even if it
-- evaluates to False as this has special semantic
-- meaning.
if Present (Expr) then
Append_To (Args,
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr)));
end if;
Make_Aitem_Pragma
(Pragma_Argument_Associations => Args,
Pragma_Name => Nam);
end;
-- Cases where we do not delay, includes all cases where the
-- expression is missing other than the above cases.
elsif not Delay_Required or else No (Expr) then
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Sloc (Ent),
Expression => Ent)),
Pragma_Name => Chars (Id));
Delay_Required := False;
-- In general cases, the corresponding pragma/attribute
-- definition clause will be inserted later at the freezing
-- point, and we do not need to build it now.
else
Aitem := Empty;
end if;
-- Storage_Size
-- This is special because for access types we need to generate
-- an attribute definition clause. This also works for single
-- task declarations, but it does not work for task type
-- declarations, because we have the case where the expression
-- references a discriminant of the task type. That can't use
-- an attribute definition clause because we would not have
-- visibility on the discriminant. For that case we must
-- generate a pragma in the task definition.
when Aspect_Storage_Size =>
-- Task type case
if Ekind (E) = E_Task_Type then
declare
Decl : constant Node_Id := Declaration_Node (E);
begin
pragma Assert (Nkind (Decl) = N_Task_Type_Declaration);
-- If no task definition, create one
if No (Task_Definition (Decl)) then
Set_Task_Definition (Decl,
Make_Task_Definition (Loc,
Visible_Declarations => Empty_List,
End_Label => Empty));
end if;
-- Create a pragma and put it at the start of the task
-- definition for the task type declaration.
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Loc,
Expression => Relocate_Node (Expr))),
Pragma_Name => Name_Storage_Size);
Prepend
(Aitem,
Visible_Declarations (Task_Definition (Decl)));
goto Continue;
end;
-- All other cases, generate attribute definition
else
Aitem :=
Make_Attribute_Definition_Clause (Loc,
Name => Ent,
Chars => Chars (Id),
Expression => Relocate_Node (Expr));
end if;
end case;
-- Attach the corresponding pragma/attribute definition clause to
-- the aspect specification node.
if Present (Aitem) then
Set_From_Aspect_Specification (Aitem);
end if;
-- In the context of a compilation unit, we directly put the
-- pragma in the Pragmas_After list of the N_Compilation_Unit_Aux
-- node (no delay is required here) except for aspects on a
-- subprogram body (see below) and a generic package, for which we
-- need to introduce the pragma before building the generic copy
-- (see sem_ch12), and for package instantiations, where the
-- library unit pragmas are better handled early.
if Nkind (Parent (N)) = N_Compilation_Unit
and then (Present (Aitem) or else Is_Boolean_Aspect (Aspect))
then
declare
Aux : constant Node_Id := Aux_Decls_Node (Parent (N));
begin
pragma Assert (Nkind (Aux) = N_Compilation_Unit_Aux);
-- For a Boolean aspect, create the corresponding pragma if
-- no expression or if the value is True.
if Is_Boolean_Aspect (Aspect) and then No (Aitem) then
if Is_True (Static_Boolean (Expr)) then
Make_Aitem_Pragma
(Pragma_Argument_Associations => New_List (
Make_Pragma_Argument_Association (Sloc (Ent),
Expression => Ent)),
Pragma_Name => Chars (Id));
Set_From_Aspect_Specification (Aitem, True);
Set_Corresponding_Aspect (Aitem, Aspect);
else
goto Continue;
end if;
end if;
-- If the aspect is on a subprogram body (relevant aspect
-- is Inline), add the pragma in front of the declarations.
if Nkind (N) = N_Subprogram_Body then
if No (Declarations (N)) then
Set_Declarations (N, New_List);
end if;
Prepend (Aitem, Declarations (N));
elsif Nkind (N) = N_Generic_Package_Declaration then
if No (Visible_Declarations (Specification (N))) then
Set_Visible_Declarations (Specification (N), New_List);
end if;
Prepend (Aitem,
Visible_Declarations (Specification (N)));
elsif Nkind (N) = N_Package_Instantiation then
declare
Spec : constant Node_Id :=
Specification (Instance_Spec (N));
begin
if No (Visible_Declarations (Spec)) then
Set_Visible_Declarations (Spec, New_List);
end if;
Prepend (Aitem, Visible_Declarations (Spec));
end;
else
if No (Pragmas_After (Aux)) then
Set_Pragmas_After (Aux, New_List);
end if;
Append (Aitem, Pragmas_After (Aux));
end if;
goto Continue;
end;
end if;
-- The evaluation of the aspect is delayed to the freezing point.
-- The pragma or attribute clause if there is one is then attached
-- to the aspect specification which is put in the rep item list.
if Delay_Required then
if Present (Aitem) then
Set_Is_Delayed_Aspect (Aitem);
Set_Aspect_Rep_Item (Aspect, Aitem);
Set_Parent (Aitem, Aspect);
end if;
Set_Is_Delayed_Aspect (Aspect);
-- In the case of Default_Value, link the aspect to base type
-- as well, even though it appears on a first subtype. This is
-- mandated by the semantics of the aspect. Do not establish
-- the link when processing the base type itself as this leads
-- to a rep item circularity. Verify that we are dealing with
-- a scalar type to prevent cascaded errors.
if A_Id = Aspect_Default_Value
and then Is_Scalar_Type (E)
and then Base_Type (E) /= E
then
Set_Has_Delayed_Aspects (Base_Type (E));
Record_Rep_Item (Base_Type (E), Aspect);
end if;
Set_Has_Delayed_Aspects (E);
Record_Rep_Item (E, Aspect);
-- When delay is not required and the context is a package or a
-- subprogram body, insert the pragma in the body declarations.
elsif Nkind_In (N, N_Package_Body, N_Subprogram_Body) then
if No (Declarations (N)) then
Set_Declarations (N, New_List);
end if;
-- The pragma is added before source declarations
Prepend_To (Declarations (N), Aitem);
-- When delay is not required and the context is not a compilation
-- unit, we simply insert the pragma/attribute definition clause
-- in sequence.
else
Insert_After (Ins_Node, Aitem);
Ins_Node := Aitem;
end if;
end Analyze_One_Aspect;
<<Continue>>
Next (Aspect);
end loop Aspect_Loop;
if Has_Delayed_Aspects (E) then
Ensure_Freeze_Node (E);
end if;
end Analyze_Aspect_Specifications;
-----------------------
-- Analyze_At_Clause --
-----------------------
-- An at clause is replaced by the corresponding Address attribute
-- definition clause that is the preferred approach in Ada 95.
procedure Analyze_At_Clause (N : Node_Id) is
CS : constant Boolean := Comes_From_Source (N);
begin
-- This is an obsolescent feature
Check_Restriction (No_Obsolescent_Features, N);
if Warn_On_Obsolescent_Feature then
Error_Msg_N
("?j?at clause is an obsolescent feature (RM J.7(2))", N);
Error_Msg_N
("\?j?use address attribute definition clause instead", N);
end if;
-- Rewrite as address clause
Rewrite (N,
Make_Attribute_Definition_Clause (Sloc (N),
Name => Identifier (N),
Chars => Name_Address,
Expression => Expression (N)));
-- We preserve Comes_From_Source, since logically the clause still comes
-- from the source program even though it is changed in form.
Set_Comes_From_Source (N, CS);
-- Analyze rewritten clause
Analyze_Attribute_Definition_Clause (N);
end Analyze_At_Clause;
-----------------------------------------
-- Analyze_Attribute_Definition_Clause --
-----------------------------------------
procedure Analyze_Attribute_Definition_Clause (N : Node_Id) is
Loc : constant Source_Ptr := Sloc (N);
Nam : constant Node_Id := Name (N);
Attr : constant Name_Id := Chars (N);
Expr : constant Node_Id := Expression (N);
Id : constant Attribute_Id := Get_Attribute_Id (Attr);
Ent : Entity_Id;
-- The entity of Nam after it is analyzed. In the case of an incomplete
-- type, this is the underlying type.
U_Ent : Entity_Id;
-- The underlying entity to which the attribute applies. Generally this
-- is the Underlying_Type of Ent, except in the case where the clause
-- applies to full view of incomplete type or private type in which case
-- U_Ent is just a copy of Ent.
FOnly : Boolean := False;
-- Reset to True for subtype specific attribute (Alignment, Size)
-- and for stream attributes, i.e. those cases where in the call to
-- Rep_Item_Too_Late, FOnly is set True so that only the freezing rules
-- are checked. Note that the case of stream attributes is not clear
-- from the RM, but see AI95-00137. Also, the RM seems to disallow
-- Storage_Size for derived task types, but that is also clearly
-- unintentional.
procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type);
-- Common processing for 'Read, 'Write, 'Input and 'Output attribute
-- definition clauses.
function Duplicate_Clause return Boolean;
-- This routine checks if the aspect for U_Ent being given by attribute
-- definition clause N is for an aspect that has already been specified,
-- and if so gives an error message. If there is a duplicate, True is
-- returned, otherwise if there is no error, False is returned.
procedure Check_Indexing_Functions;
-- Check that the function in Constant_Indexing or Variable_Indexing
-- attribute has the proper type structure. If the name is overloaded,
-- check that some interpretation is legal.
procedure Check_Iterator_Functions;
-- Check that there is a single function in Default_Iterator attribute
-- has the proper type structure.
function Check_Primitive_Function (Subp : Entity_Id) return Boolean;
-- Common legality check for the previous two
-----------------------------------
-- Analyze_Stream_TSS_Definition --
-----------------------------------
procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type) is
Subp : Entity_Id := Empty;
I : Interp_Index;
It : Interp;
Pnam : Entity_Id;
Is_Read : constant Boolean := (TSS_Nam = TSS_Stream_Read);
-- True for Read attribute, false for other attributes
function Has_Good_Profile (Subp : Entity_Id) return Boolean;
-- Return true if the entity is a subprogram with an appropriate
-- profile for the attribute being defined.
----------------------
-- Has_Good_Profile --
----------------------
function Has_Good_Profile (Subp : Entity_Id) return Boolean is
F : Entity_Id;
Is_Function : constant Boolean := (TSS_Nam = TSS_Stream_Input);
Expected_Ekind : constant array (Boolean) of Entity_Kind :=
(False => E_Procedure, True => E_Function);
Typ : Entity_Id;
begin
if Ekind (Subp) /= Expected_Ekind (Is_Function) then
return False;
end if;
F := First_Formal (Subp);
if No (F)
or else Ekind (Etype (F)) /= E_Anonymous_Access_Type
or else Designated_Type (Etype (F)) /=
Class_Wide_Type (RTE (RE_Root_Stream_Type))
then
return False;
end if;
if not Is_Function then
Next_Formal (F);
declare
Expected_Mode : constant array (Boolean) of Entity_Kind :=
(False => E_In_Parameter,
True => E_Out_Parameter);
begin
if Parameter_Mode (F) /= Expected_Mode (Is_Read) then
return False;
end if;
end;
Typ := Etype (F);
-- If the attribute specification comes from an aspect
-- specification for a class-wide stream, the parameter must be
-- a class-wide type of the entity to which the aspect applies.
if From_Aspect_Specification (N)
and then Class_Present (Parent (N))
and then Is_Class_Wide_Type (Typ)
then
Typ := Etype (Typ);
end if;
else
Typ := Etype (Subp);
end if;
-- Verify that the prefix of the attribute and the local name for
-- the type of the formal match, or one is the class-wide of the
-- other, in the case of a class-wide stream operation.
if Base_Type (Typ) = Base_Type (Ent)
or else (Is_Class_Wide_Type (Typ)
and then Typ = Class_Wide_Type (Base_Type (Ent)))
or else (Is_Class_Wide_Type (Ent)
and then Ent = Class_Wide_Type (Base_Type (Typ)))
then
null;
else
return False;
end if;
if Present ((Next_Formal (F)))
then
return False;
elsif not Is_Scalar_Type (Typ)
and then not Is_First_Subtype (Typ)
and then not Is_Class_Wide_Type (Typ)
then
return False;
else
return True;
end if;
end Has_Good_Profile;
-- Start of processing for Analyze_Stream_TSS_Definition
begin
FOnly := True;
if not Is_Type (U_Ent) then
Error_Msg_N ("local name must be a subtype", Nam);
return;
elsif not Is_First_Subtype (U_Ent) then
Error_Msg_N ("local name must be a first subtype", Nam);
return;
end if;
Pnam := TSS (Base_Type (U_Ent), TSS_Nam);
-- If Pnam is present, it can be either inherited from an ancestor
-- type (in which case it is legal to redefine it for this type), or
-- be a previous definition of the attribute for the same type (in
-- which case it is illegal).
-- In the first case, it will have been analyzed already, and we
-- can check that its profile does not match the expected profile
-- for a stream attribute of U_Ent. In the second case, either Pnam
-- has been analyzed (and has the expected profile), or it has not
-- been analyzed yet (case of a type that has not been frozen yet
-- and for which the stream attribute has been set using Set_TSS).
if Present (Pnam)
and then (No (First_Entity (Pnam)) or else Has_Good_Profile (Pnam))
then
Error_Msg_Sloc := Sloc (Pnam);
Error_Msg_Name_1 := Attr;
Error_Msg_N ("% attribute already defined #", Nam);
return;
end if;
Analyze (Expr);
if Is_Entity_Name (Expr) then
if not Is_Overloaded (Expr) then
if Has_Good_Profile (Entity (Expr)) then
Subp := Entity (Expr);
end if;
else
Get_First_Interp (Expr, I, It);
while Present (It.Nam) loop
if Has_Good_Profile (It.Nam) then
Subp := It.Nam;
exit;
end if;
Get_Next_Interp (I, It);
end loop;
end if;
end if;
if Present (Subp) then
if Is_Abstract_Subprogram (Subp) then
Error_Msg_N ("stream subprogram must not be abstract", Expr);
return;
-- A stream subprogram for an interface type must be a null
-- procedure (RM 13.13.2 (38/3)).
elsif Is_Interface (U_Ent)
and then not Is_Class_Wide_Type (U_Ent)
and then not Inside_A_Generic
and then
(Ekind (Subp) = E_Function
or else
not Null_Present
(Specification
(Unit_Declaration_Node (Ultimate_Alias (Subp)))))
then
Error_Msg_N
("stream subprogram for interface type "
& "must be null procedure", Expr);
end if;
Set_Entity (Expr, Subp);
Set_Etype (Expr, Etype (Subp));
New_Stream_Subprogram (N, U_Ent, Subp, TSS_Nam);
else
Error_Msg_Name_1 := Attr;
Error_Msg_N ("incorrect expression for% attribute", Expr);
end if;
end Analyze_Stream_TSS_Definition;
------------------------------
-- Check_Indexing_Functions --
------------------------------
procedure Check_Indexing_Functions is
Indexing_Found : Boolean := False;
procedure Check_One_Function (Subp : Entity_Id);
-- Check one possible interpretation. Sets Indexing_Found True if a
-- legal indexing function is found.
procedure Illegal_Indexing (Msg : String);
-- Diagnose illegal indexing function if not overloaded. In the
-- overloaded case indicate that no legal interpretation exists.
------------------------
-- Check_One_Function --
------------------------
procedure Check_One_Function (Subp : Entity_Id) is
Default_Element : Node_Id;
Ret_Type : constant Entity_Id := Etype (Subp);
begin
if not Is_Overloadable (Subp) then
Illegal_Indexing ("illegal indexing function for type&");
return;
elsif Scope (Subp) /= Scope (Ent) then
if Nkind (Expr) = N_Expanded_Name then
-- Indexing function can't be declared elsewhere
Illegal_Indexing
("indexing function must be declared in scope of type&");
end if;
return;
elsif No (First_Formal (Subp)) then
Illegal_Indexing
("Indexing requires a function that applies to type&");
return;
elsif No (Next_Formal (First_Formal (Subp))) then
Illegal_Indexing
("indexing function must have at least two parameters");
return;
elsif Is_Derived_Type (Ent) then
if (Attr = Name_Constant_Indexing
and then Present
(Find_Aspect (Etype (Ent), Aspect_Constant_Indexing)))
or else
(Attr = Name_Variable_Indexing
and then Present
(Find_Aspect (Etype (Ent), Aspect_Variable_Indexing)))
then
if Debug_Flag_Dot_XX then
null;
else
Illegal_Indexing
("indexing function already inherited "
& "from parent type");
return;
end if;
end if;
end if;
if not Check_Primitive_Function (Subp) then
Illegal_Indexing
("Indexing aspect requires a function that applies to type&");
return;
end if;
-- If partial declaration exists, verify that it is not tagged.
if Ekind (Current_Scope) = E_Package
and then Has_Private_Declaration (Ent)
and then From_Aspect_Specification (N)
and then
List_Containing (Parent (Ent)) =
Private_Declarations
(Specification (Unit_Declaration_Node (Current_Scope)))
and then Nkind (N) = N_Attribute_Definition_Clause
then
declare
Decl : Node_Id;
begin
Decl :=
First (Visible_Declarations
(Specification
(Unit_Declaration_Node (Current_Scope))));
while Present (Decl) loop
if Nkind (Decl) = N_Private_Type_Declaration
and then Ent = Full_View (Defining_Identifier (Decl))
and then Tagged_Present (Decl)
and then No (Aspect_Specifications (Decl))
then
Illegal_Indexing
("Indexing aspect cannot be specified on full view "
& "if partial view is tagged");
return;
end if;
Next (Decl);
end loop;
end;
end if;
-- An indexing function must return either the default element of
-- the container, or a reference type. For variable indexing it
-- must be the latter.
Default_Element :=
Find_Value_Of_Aspect
(Etype (First_Formal (Subp)), Aspect_Iterator_Element);
if Present (Default_Element) then
Analyze (Default_Element);
if Is_Entity_Name (Default_Element)
and then not Covers (Entity (Default_Element), Ret_Type)
and then False
then
Illegal_Indexing
("wrong return type for indexing function");
return;
end if;
end if;
-- For variable_indexing the return type must be a reference type
if Attr = Name_Variable_Indexing then
if not Has_Implicit_Dereference (Ret_Type) then
Illegal_Indexing
("variable indexing must return a reference type");
return;
elsif Is_Access_Constant
(Etype (First_Discriminant (Ret_Type)))
then
Illegal_Indexing
("variable indexing must return an access to variable");
return;
end if;
else
if Has_Implicit_Dereference (Ret_Type)
and then not
Is_Access_Constant (Etype (First_Discriminant (Ret_Type)))
then
Illegal_Indexing
("constant indexing must return an access to constant");
return;
elsif Is_Access_Type (Etype (First_Formal (Subp)))
and then not Is_Access_Constant (Etype (First_Formal (Subp)))
then
Illegal_Indexing
("constant indexing must apply to an access to constant");
return;
end if;
end if;
-- All checks succeeded.
Indexing_Found := True;
end Check_One_Function;
-----------------------
-- Illegal_Indexing --
-----------------------
procedure Illegal_Indexing (Msg : String) is
begin
Error_Msg_NE (Msg, N, Ent);
end Illegal_Indexing;
-- Start of processing for Check_Indexing_Functions
begin
if In_Instance then
return;
end if;
Analyze (Expr);
if not Is_Overloaded (Expr) then
Check_One_Function (Entity (Expr));
else
declare
I : Interp_Index;
It : Interp;
begin
Indexing_Found := False;
Get_First_Interp (Expr, I, It);
while Present (It.Nam) loop
-- Note that analysis will have added the interpretation
-- that corresponds to the dereference. We only check the
-- subprogram itself.
if Is_Overloadable (It.Nam) then
Check_One_Function (It.Nam);
end if;
Get_Next_Interp (I, It);
end loop;
end;
end if;
if not Indexing_Found and then not Error_Posted (N) then
Error_Msg_NE
("aspect Indexing requires a local function that "
& "applies to type&", Expr, Ent);
end if;
end Check_Indexing_Functions;
------------------------------
-- Check_Iterator_Functions --
------------------------------
procedure Check_Iterator_Functions is
Default : Entity_Id;
function Valid_Default_Iterator (Subp : Entity_Id) return Boolean;
-- Check one possible interpretation for validity
----------------------------
-- Valid_Default_Iterator --
----------------------------
function Valid_Default_Iterator (Subp : Entity_Id) return Boolean is
Formal : Entity_Id;
begin
if not Check_Primitive_Function (Subp) then
return False;
else
Formal := First_Formal (Subp);
end if;
-- False if any subsequent formal has no default expression
Formal := Next_Formal (Formal);
while Present (Formal) loop
if No (Expression (Parent (Formal))) then
return False;
end if;
Next_Formal (Formal);
end loop;
-- True if all subsequent formals have default expressions
return True;
end Valid_Default_Iterator;
-- Start of processing for Check_Iterator_Functions
begin
Analyze (Expr);
if not Is_Entity_Name (Expr) then
Error_Msg_N ("aspect Iterator must be a function name", Expr);
end if;
if not Is_Overloaded (Expr) then
if not Check_Primitive_Function (Entity (Expr)) then
Error_Msg_NE
("aspect Indexing requires a function that applies to type&",
Entity (Expr), Ent);
end if;
if not Valid_Default_Iterator (Entity (Expr)) then
Error_Msg_N ("improper function for default iterator", Expr);
end if;
else
Default := Empty;
declare
I : Interp_Index;
It : Interp;
begin
Get_First_Interp (Expr, I, It);
while Present (It.Nam) loop
if not Check_Primitive_Function (It.Nam)
or else not Valid_Default_Iterator (It.Nam)
then
Remove_Interp (I);
elsif Present (Default) then
Error_Msg_N ("default iterator must be unique", Expr);
else
Default := It.Nam;
end if;
Get_Next_Interp (I, It);
end loop;
end;
if Present (Default) then
Set_Entity (Expr, Default);
Set_Is_Overloaded (Expr, False);
end if;
end if;
end Check_Iterator_Functions;
-------------------------------
-- Check_Primitive_Function --
-------------------------------
function Check_Primitive_Function (Subp : Entity_Id) return Boolean is
Ctrl : Entity_Id;
begin
if Ekind (Subp) /= E_Function then
return False;
end if;
if No (First_Formal (Subp)) then
return False;
else
Ctrl := Etype (First_Formal (Subp));
end if;
-- Type of formal may be the class-wide type, an access to such,
-- or an incomplete view.
if Ctrl = Ent
or else Ctrl = Class_Wide_Type (Ent)
or else
(Ekind (Ctrl) = E_Anonymous_Access_Type
and then (Designated_Type (Ctrl) = Ent
or else
Designated_Type (Ctrl) = Class_Wide_Type (Ent)))
or else
(Ekind (Ctrl) = E_Incomplete_Type
and then Full_View (Ctrl) = Ent)
then
null;
else
return False;
end if;
return True;
end Check_Primitive_Function;
----------------------
-- Duplicate_Clause --
----------------------
function Duplicate_Clause return Boolean is
A : Node_Id;
begin
-- Nothing to do if this attribute definition clause comes from
-- an aspect specification, since we could not be duplicating an
-- explicit clause, and we dealt with the case of duplicated aspects
-- in Analyze_Aspect_Specifications.
if From_Aspect_Specification (N) then
return False;
end if;
-- Otherwise current clause may duplicate previous clause, or a
-- previously given pragma or aspect specification for the same
-- aspect.
A := Get_Rep_Item (U_Ent, Chars (N), Check_Parents => False);
if Present (A) then
Error_Msg_Name_1 := Chars (N);
Error_Msg_Sloc := Sloc (A);
Error_Msg_NE ("aspect% for & previously given#", N, U_Ent);
return True;
end if;
return False;
end Duplicate_Clause;
-- Start of processing for Analyze_Attribute_Definition_Clause
begin
-- The following code is a defense against recursion. Not clear that
-- this can happen legitimately, but perhaps some error situations can
-- cause it, and we did see this recursion during testing.
if Analyzed (N) then
return;
else
Set_Analyzed (N, True);
end if;
-- Ignore some selected attributes in CodePeer mode since they are not
-- relevant in this context.
if CodePeer_Mode then
case Id is
-- Ignore Component_Size in CodePeer mode, to avoid changing the
-- internal representation of types by implicitly packing them.
when Attribute_Component_Size =>
Rewrite (N, Make_Null_Statement (Sloc (N)));
return;
when others =>
null;
end case;
end if;
-- Process Ignore_Rep_Clauses option
if Ignore_Rep_Clauses then
case Id is
-- The following should be ignored. They do not affect legality
-- and may be target dependent. The basic idea of -gnatI is to
-- ignore any rep clauses that may be target dependent but do not
-- affect legality (except possibly to be rejected because they
-- are incompatible with the compilation target).
when Attribute_Alignment |
Attribute_Bit_Order |
Attribute_Component_Size |
Attribute_Machine_Radix |
Attribute_Object_Size |
Attribute_Size |
Attribute_Small |
Attribute_Stream_Size |
Attribute_Value_Size =>
Kill_Rep_Clause (N);
return;
-- The following should not be ignored, because in the first place
-- they are reasonably portable, and should not cause problems
-- in compiling code from another target, and also they do affect
-- legality, e.g. failing to provide a stream attribute for a type
-- may make a program illegal.
when Attribute_External_Tag |
Attribute_Input |
Attribute_Output |
Attribute_Read |
Attribute_Simple_Storage_Pool |
Attribute_Storage_Pool |
Attribute_Storage_Size |
Attribute_Write =>
null;
-- We do not do anything here with address clauses, they will be
-- removed by Freeze later on, but for now, it works better to
-- keep then in the tree.
when Attribute_Address =>
null;
-- Other cases are errors ("attribute& cannot be set with
-- definition clause"), which will be caught below.
when others =>
null;
end case;
end if;
Analyze (Nam);
Ent := Entity (Nam);
if Rep_Item_Too_Early (Ent, N) then
return;
end if;
-- Rep clause applies to full view of incomplete type or private type if
-- we have one (if not, this is a premature use of the type). However,
-- certain semantic checks need to be done on the specified entity (i.e.
-- the private view), so we save it in Ent.
if Is_Private_Type (Ent)
and then Is_Derived_Type (Ent)
and then not Is_Tagged_Type (Ent)
and then No (Full_View (Ent))
then
-- If this is a private type whose completion is a derivation from
-- another private type, there is no full view, and the attribute
-- belongs to the type itself, not its underlying parent.
U_Ent := Ent;
elsif Ekind (Ent) = E_Incomplete_Type then
-- The attribute applies to the full view, set the entity of the
-- attribute definition accordingly.
Ent := Underlying_Type (Ent);
U_Ent := Ent;
Set_Entity (Nam, Ent);
else
U_Ent := Underlying_Type (Ent);
end if;
-- Avoid cascaded error
if Etype (Nam) = Any_Type then
return;
-- Must be declared in current scope or in case of an aspect
-- specification, must be visible in current scope.
elsif Scope (Ent) /= Current_Scope
and then
not (From_Aspect_Specification (N)
and then Scope_Within_Or_Same (Current_Scope, Scope (Ent)))
then
Error_Msg_N ("entity must be declared in this scope", Nam);
return;
-- Must not be a source renaming (we do have some cases where the
-- expander generates a renaming, and those cases are OK, in such
-- cases any attribute applies to the renamed object as well).
elsif Is_Object (Ent)
and then Present (Renamed_Object (Ent))