procedure Set_Original_Node (N : Node_Id; Val : Node_Id);
pragma Inline (Set_Original_Node);
-- Note that this routine is used only in very peculiar cases. In normal
- -- cases, the Original_Node link is set by calls to Rewrite. We currently
- -- use it in ASIS mode to manually set the link from pragma expressions to
- -- their aspect original source expressions, so that the original source
- -- expressions accessed by ASIS are also semantically analyzed.
+ -- cases, the Original_Node link is set by calls to Rewrite.
procedure Set_Parent (N : Node_Id; Val : Node_Id);
pragma Inline (Set_Parent);
function Original_Node (Node : Node_Id) return Node_Id;
pragma Inline (Original_Node);
-- If Node has not been rewritten, then returns its input argument
- -- unchanged, else returns the Node for the original subtree. Note that
- -- this is used extensively by ASIS on the trees constructed in ASIS mode
- -- to reconstruct the original semantic tree. See section in sinfo.ads
- -- for requirements on original nodes returned by this function.
+ -- unchanged, else returns the Node for the original subtree. See section
+ -- in sinfo.ads for requirements on original nodes returned by this
+ -- function.
--
-- Note: Parents are not preserved in original tree nodes that are
-- retrieved in this way (i.e. their children may have children whose
-- Do not generate an elaboration check in compilation modes where
-- expansion is not desirable.
- if ASIS_Mode or GNATprove_Mode then
+ if GNATprove_Mode then
return;
-- Do not generate an elaboration check if all checks have been
Skip_Assert_Exprs : constant Boolean :=
Ekind_In (Subp_Id, E_Entry, E_Entry_Family)
- and then not ASIS_Mode
and then not GNATprove_Mode;
Depends : Node_Id := Empty;
if not Expander_Active then
return;
- -- ASIS requires an unaltered tree
-
- elsif ASIS_Mode then
- return;
-
-- GNATprove does not need the executable semantics of a contract
elsif GNATprove_Mode then
-- d.E Turn selected errors into warnings
-- d.F Debug mode for GNATprove
-- d.G Ignore calls through generic formal parameters for elaboration
- -- d.H GNSA mode for ASIS
+ -- d.H
-- d.I Do not ignore enum representation clauses in CodePeer mode
-- d.J Relaxed rules for pragma No_Return
-- d.K
-- now fixed, but we provide this debug flag to revert to the previous
-- situation of ignoring such calls to aid in transition.
- -- d.H Sets ASIS_GNSA_Mode to True. This signals the front end to suppress
- -- the call to gigi in ASIS_Mode.
-
-- d.I Do not ignore enum representation clauses in CodePeer mode.
-- The default of ignoring representation clauses for enumeration
-- types in CodePeer is good for the majority of Ada code, but in some
-- list is always empty.
-- When expansion is disabled the corresponding record type of a
-- synchronized type is not constructed. In that case, such types
--- carry this attribute directly, for ASIS use.
+-- carry this attribute directly.
-- Directly_Designated_Type (Node20)
-- Defined in access types. This field points to the type that is
begin
-- Build equality code with a user-defined operator, if
-- available, and with the predefined "=" otherwise. For
- -- compatibility with older Ada versions, and preserve the
- -- workings of some ASIS tools, we also use the predefined
- -- operation if the component-type equality is abstract,
- -- rather than raising Program_Error.
+ -- compatibility with older Ada versions, we also use the
+ -- predefined operation if the component-type equality is
+ -- abstract, rather than raising Program_Error.
if Ada_Version < Ada_2012 then
Next_Test := Make_Op_Ne (Loc, Lhs, Rhs);
New_Ref : Node_Id;
begin
- -- This expansion activity is called during analysis, but cannot
- -- be applied in ASIS mode when other expansion is disabled.
+ -- This expansion activity is called during analysis.
if Is_Tagged_Type (Typ)
and then not Is_Class_Wide_Type (Typ)
and then not Is_CPP_Class (Typ)
and then Tagged_Type_Expansion
and then Nkind (Expr) /= N_Aggregate
- and then not ASIS_Mode
and then (Nkind (Expr) /= N_Qualified_Expression
or else Nkind (Expression (Expr)) /= N_Aggregate)
then
DIC_Proc : constant Entity_Id := DIC_Procedure (DIC_Typ);
Obj_Id : constant Entity_Id := First_Formal (DIC_Proc);
- procedure Preanalyze_Own_DIC_For_ASIS;
- -- Preanalyze the original DIC expression of an aspect or a source
- -- pragma for ASIS.
-
- ---------------------------------
- -- Preanalyze_Own_DIC_For_ASIS --
- ---------------------------------
-
- procedure Preanalyze_Own_DIC_For_ASIS is
- Expr : Node_Id := Empty;
-
- begin
- -- The DIC pragma is a source construct, preanalyze the original
- -- expression of the pragma.
-
- if Comes_From_Source (DIC_Prag) then
- Expr := DIC_Expr;
-
- -- Otherwise preanalyze the expression of the corresponding aspect
-
- elsif Present (DIC_Asp) then
- Expr := Expression (DIC_Asp);
- end if;
-
- -- The expression must be subjected to the same substitutions as
- -- the copy used in the generation of the runtime check.
-
- if Present (Expr) then
- Replace_Type_References
- (Expr => Expr,
- Typ => DIC_Typ,
- Obj_Id => Obj_Id);
-
- Preanalyze_Assert_Expression (Expr, Any_Boolean);
- end if;
- end Preanalyze_Own_DIC_For_ASIS;
-
-- Local variables
Typ_Decl : constant Node_Id := Declaration_Node (DIC_Typ);
Set_Entity (Identifier (DIC_Asp), New_Copy_Tree (Expr));
end if;
- -- Preanalyze the original DIC expression for ASIS
-
- if ASIS_Mode then
- Preanalyze_Own_DIC_For_ASIS;
- end if;
-
-- Once the DIC assertion expression is fully processed, add a check
-- to the statements of the DIC procedure.
Set_Corresponding_Spec (Proc_Body, Proc_Id);
-- The body should not be inserted into the tree when the context
- -- is ASIS or a generic unit because it is not part of the template.
+ -- is a generic unit because it is not part of the template.
-- Note that the body must still be generated in order to resolve the
-- DIC assertion expression.
- if ASIS_Mode or Inside_A_Generic then
+ if Inside_A_Generic then
null;
-- Semi-insert the body into the tree for GNATprove by setting its
New_Occurrence_Of (Work_Typ, Loc)))));
-- The declaration should not be inserted into the tree when the context
- -- is ASIS or a generic unit because it is not part of the template.
+ -- is a generic unit because it is not part of the template.
- if ASIS_Mode or Inside_A_Generic then
+ if Inside_A_Generic then
null;
-- Semi-insert the declaration into the tree for GNATprove by setting
Checks : in out List_Id;
Priv_Item : Node_Id := Empty)
is
- ASIS_Expr : Node_Id;
Expr : Node_Id;
Prag : Node_Id;
Prag_Asp : Node_Id;
Set_Entity (Identifier (Prag_Asp), New_Copy_Tree (Expr));
end if;
- -- Analyze the original invariant expression for ASIS
-
- if ASIS_Mode then
- ASIS_Expr := Empty;
-
- if Comes_From_Source (Prag) then
- ASIS_Expr := Prag_Expr;
- elsif Present (Prag_Asp) then
- ASIS_Expr := Expression (Prag_Asp);
- end if;
-
- if Present (ASIS_Expr) then
- Replace_Type_References (ASIS_Expr, T, Obj_Id);
- Preanalyze_Assert_Expression (ASIS_Expr, Any_Boolean);
- end if;
- end if;
-
Add_Invariant_Check (Prag, Expr, Checks);
end if;
Set_Corresponding_Spec (Proc_Body, Proc_Id);
-- The body should not be inserted into the tree when the context is
- -- ASIS or a generic unit because it is not part of the template. Note
+ -- a generic unit because it is not part of the template. Note
-- that the body must still be generated in order to resolve the
-- invariants.
- if ASIS_Mode or Inside_A_Generic then
+ if Inside_A_Generic then
null;
-- Semi-insert the body into the tree for GNATprove by setting its
Parameter_Type => New_Occurrence_Of (Obj_Typ, Loc)))));
-- The declaration should not be inserted into the tree when the context
- -- is ASIS or a generic unit because it is not part of the template.
+ -- is a generic unit because it is not part of the template.
- if ASIS_Mode or Inside_A_Generic then
+ if Inside_A_Generic then
null;
-- Semi-insert the declaration into the tree for GNATprove by setting
procedure Replace_Subtype_Reference (N : Node_Id) is
begin
Rewrite (N, New_Copy_Tree (Expr));
-
- -- We want to treat the node as if it comes from source, so that
- -- ASIS will not ignore it.
-
- Set_Comes_From_Source (N, True);
end Replace_Subtype_Reference;
procedure Replace_Subtype_References is
procedure Replace_Type_Ref (N : Node_Id) is
begin
-- Decorate the reference to Typ even though it may be rewritten
- -- further down. This is done for two reasons:
-
- -- * ASIS has all necessary semantic information in the original
- -- tree.
-
- -- * Routines which examine properties of the Original_Node have
- -- some semantic information.
+ -- further down. This is done so that routines which examine
+ -- properties of the Original_Node have some semantic information.
if Nkind (N) = N_Identifier then
Set_Entity (N, Typ);
procedure Expander_Mode_Restore is
begin
- -- Not active (has no effect) in ASIS and GNATprove modes (see comments
+ -- Not active (has no effect) in GNATprove mode (see comments
-- in spec of Expander_Mode_Save_And_Set).
- if ASIS_Mode or GNATprove_Mode then
+ if GNATprove_Mode then
return;
end if;
procedure Expander_Mode_Save_And_Set (Status : Boolean) is
begin
- -- Not active (has no effect) in ASIS and GNATprove modes (see comments
+ -- Not active (has no effect) in GNATprove modes (see comments
-- in spec of Expander_Mode_Save_And_Set).
- if ASIS_Mode or GNATprove_Mode then
+ if GNATprove_Mode then
return;
end if;
-- For nodes other than subexpressions, it is not necessary to preserve the
-- original tree in the Expand routines, unlike the case for modifications
-- to the tree made in the semantic analyzer. This is because anyone who is
--- interested in working with the original tree (like ASIS) is required to
--- compile in semantics checks only mode. Thus Replace may be freely used
--- in such instances.
+-- interested in working with the original tree is required to compile in
+-- semantics checks only mode. Thus Replace may be freely used in such
+-- instances.
-- For subexpressions, preservation of the original tree is required because
-- of the need for conformance checking of default expressions, which occurs
-- Saves the current setting of the Expander_Active flag on an internal
-- stack and then sets the flag to the given value.
--
- -- Note: this routine has no effect in ASIS and GNATprove modes. In ASIS
- -- mode, all expansion activity is always off, since we want the original
- -- semantic tree for ASIS purposes without any expansion. In GNATprove
- -- mode, a very light expansion is performed on specific nodes. Both are
- -- achieved by setting Expander_Active False in ASIS and GNATprove modes.
+ -- Note: this routine has no effect in GNATprove mode. In this mode,
+ -- a very light expansion is performed on specific nodes and
+ -- Expander_Active is set to False.
-- In situations such as the call to Instantiate_Bodies in Frontend,
-- Expander_Mode_Save_And_Set may be called to temporarily turn the
- -- expander on, but this will have no effect in ASIS and GNATprove modes.
+ -- expander on, but this will have no effect in GNATprove mode.
procedure Expander_Mode_Restore;
-- Restores the setting of the Expander_Active flag using the top entry
-- pushed onto the stack by Expander_Mode_Save_And_Reset, popping the
-- stack, except that if any errors have been detected, then the state of
- -- the flag is left set to False. Disabled for ASIS and GNATprove modes
- -- (see above).
+ -- the flag is left set to False. Disabled for GNATprove mode (see above).
end Expander;
-- Cleanup processing after completing main analysis
- -- Comment needed for ASIS mode test and GNATprove mode test???
+ -- In GNATprove_Mode we do not perform most expansions but body
+ -- instantiation is needed.
pragma Assert
(Operating_Mode = Generate_Code
or else Operating_Mode = Check_Semantics);
if Operating_Mode = Generate_Code
- or else (ASIS_Mode or GNATprove_Mode)
+ or else GNATprove_Mode
then
Instantiate_Bodies;
end if;
CodePeer_Mode := False;
end if;
- -- Set ASIS mode if -gnatt and -gnatc are set
-
- if Operating_Mode = Check_Semantics and then Tree_Output then
- ASIS_Mode := True;
-
- -- Set ASIS GNSA mode if -gnatd.H is set
-
- if Debug_Flag_Dot_HH then
- ASIS_GNSA_Mode := True;
- end if;
-
- -- Turn off inlining in ASIS mode, since ASIS cannot handle the extra
- -- information in the trees caused by inlining being active.
-
- -- More specifically, the tree seems to be malformed from the ASIS
- -- point of view if -gnatc and -gnatn appear together???
-
- Inline_Active := False;
-
- -- Turn off SCIL generation and CodePeer mode in semantics mode,
- -- since SCIL requires front-end expansion.
-
- Generate_SCIL := False;
- CodePeer_Mode := False;
- end if;
-
-- SCIL mode needs to disable front-end inlining since the generated
-- trees (in particular order and consistency between specs compiled
-- as part of a main unit or as part of a with-clause) are causing
-- Set and check exception mechanism. This is only meaningful when
-- compiling, and in particular not meaningful for special modes used
- -- for program analysis rather than compilation: ASIS mode, CodePeer
- -- mode and GNATprove mode.
+ -- for program analysis rather than compilation: CodePeer mode and
+ -- GNATprove mode.
if Operating_Mode = Generate_Code
- and then not (ASIS_Mode or CodePeer_Mode or GNATprove_Mode)
+ and then not (CodePeer_Mode or GNATprove_Mode)
then
case Targparm.Frontend_Exceptions_On_Target is
when True =>
not Generate_C_Code
- -- No back-end inlining available in ASIS mode
-
- and then not ASIS_Mode
-
-- No back-end inlining in GNATprove mode, since it just confuses
-- the formal verification process.
-- Annotation is suppressed for targets where front-end layout is
-- enabled, because the front end determines representations.
- -- The back end is not invoked in ASIS mode with GNSA because all type
- -- representation information will be provided by the GNSA back end, not
- -- gigi.
-
-- A special back end is always called in CodePeer and GNATprove modes,
-- unless this is a subunit.
if Back_End_Mode = Declarations_Only
and then
(not (Back_Annotate_Rep_Info or Generate_SCIL or GNATprove_Mode)
- or else Main_Unit_Kind = N_Subunit
- or else ASIS_GNSA_Mode)
+ or else Main_Unit_Kind = N_Subunit)
then
Post_Compilation_Validation_Checks;
Errout.Finalize (Last_Call => True);
Back_End.Gen_Or_Update_Object_File;
end if;
- -- Generate ASIS tree after writing the ALI file, since in ASIS mode,
- -- Write_ALI may in fact result in further tree decoration from the
- -- original tree file. Note that we dump the tree just before generating
- -- it, so that the dump will exactly reflect what is written out.
+ -- Generate tree after writing the ALI file, since Write_ALI may in
+ -- fact result in further tree decoration from the original tree file.
+ -- Note that we dump the tree just before generating it, so that the
+ -- dump will exactly reflect what is written out.
+ -- Should we remove Tree_Dump completely now that ASIS is no longer
+ -- supported???
Treepr.Tree_Dump;
Tree_Gen;
------------------------------------------------------------------------------
with Atree; use Atree;
-with Opt; use Opt;
with Sem; use Sem;
with Sinfo; use Sinfo;
with Stand; use Stand;
Set_Is_Itype (Typ);
Set_Associated_Node_For_Itype (Typ, Related_Nod);
- if In_Deleted_Code
- and then not ASIS_Mode
- then
+ if In_Deleted_Code then
Set_Is_Frozen (Typ);
end if;
function Get_Compilation_Switch (N : Pos) return String_Ptr;
-- Return the Nth stored compilation switch, or null if less than N
- -- switches have been stored. Used by ASIS and back ends written in Ada.
+ -- switches have been stored. Used by back ends written in Ada.
function Generic_May_Lack_ALI (Unum : Unit_Number_Type) return Boolean;
-- Generic units must be separately compiled. Since we always use
-- This table is set as part of the compiler argument scanning in
-- Back_End. It can also be reset in -gnatc mode from the data in an
-- existing ali file, and is read and written by the Tree_Read and
- -- Tree_Write routines for ASIS.
+ -- Tree_Write routines.
package Compilation_Switches is new Table.Table (
Table_Component_Type => String_Ptr,
-- also the suffixes used to indicate package body entities and to
-- distinguish between overloaded entities). Note that names are not
-- qualified until just before the call to gigi, so this routine is only
- -- needed by processing that occurs after gigi has been called. This
- -- includes all ASIS processing, since ASIS works on the tree written
- -- after gigi has been called.
+ -- needed by processing that occurs after gigi has been called.
procedure Append_Unqualified_Decoded
(Buf : in out Bounded_String;
Assertions_Enabled_Config_Val : Nat;
begin
- Tree_Read_Int (Tree_ASIS_Version_Number);
-
Tree_Read_Bool (Address_Is_Private);
Tree_Read_Bool (Brief_Output);
Tree_Read_Bool (GNAT_Mode);
Version_String : String := Gnat_Version_String;
begin
- Tree_Write_Int (ASIS_Version_Number);
-
Tree_Write_Bool (Address_Is_Private);
Tree_Write_Bool (Brief_Output);
Tree_Write_Bool (GNAT_Mode);
-- Set to non-null when Bind_Alternate_Main_Name is True. This value
-- is modified as needed by Gnatbind.Scan_Bind_Arg.
- ASIS_GNSA_Mode : Boolean := False;
- -- GNAT
- -- Enable GNSA back-end processing assuming ASIS_Mode is already set to
- -- True. ASIS_GNSA mode suppresses the call to gigi.
-
- ASIS_Mode : Boolean := False;
- -- GNAT
- -- Enable semantic checks and tree transformations that are important
- -- for ASIS but that are usually skipped if Operating_Mode is set to
- -- Check_Semantics. This flag does not have the corresponding option to set
- -- it ON. It is set ON when Tree_Output is set ON, it can also be set ON
- -- from the code of GNSA-based tool (a client may need to set ON the
- -- Back_Annotate_Rep_Info flag in this case. At the moment this does not
- -- make very much sense, because GNSA cannot do back annotation).
-
Assertions_Enabled : Boolean := False;
-- GNAT
-- Indicates default policy (True = Check, False = Ignore) to be applied
Ignore_Rep_Clauses : Boolean := False;
-- GNAT
-- Set True to ignore all representation clauses. Useful when compiling
- -- code from foreign compilers for checking or ASIS purposes. Can be
+ -- code from foreign compilers for checking purposes. Can be
-- set True by use of -gnatI.
Ignore_SPARK_Mode_Pragmas_In_Instance : Boolean := False;
-- to the three corresponding procedures in Osint-C. The reason for this
-- slightly strange interface is to stop Repinfo from dragging in Osint in
-- ASIS mode, which would include lots of unwanted units in the ASIS build.
+ -- ??? Revisit this now that ASIS mode is gone.
type Create_List_File_Proc is access procedure (S : String);
type Write_List_Info_Proc is access procedure (S : String);
procedure Tree_Write;
-- Writes out switch settings to current tree file using Tree_Write
- --------------------------
- -- ASIS Version Control --
- --------------------------
-
- -- These two variables (Tree_Version_String and Tree_ASIS_Version_Number)
- -- are supposed to be used in the GNAT/ASIS version check performed in
- -- the ASIS code (this package is also a part of the ASIS implementation).
- -- They are set by Tree_Read procedure, so they represent the version
- -- number (and the version string) of the compiler which has created the
- -- tree, and they are supposed to be compared with the corresponding values
- -- from the Tree_IO and Gnatvsn packages which also are a part of ASIS
- -- implementation.
-
Tree_Version_String : String_Access;
-- Used to store the compiler version string read from a tree file to check
-- if it is from the same date as stored in the version string in Gnatvsn.
- -- We require that ASIS Pro can be used only with GNAT Pro, but we allow
- -- non-Pro ASIS and ASIS-based tools to be used with any version of the
- -- GNAT compiler. Therefore, we need the possibility to compare the dates
- -- of the corresponding source sets, using version strings that may be
- -- of different lengths.
-
- Tree_ASIS_Version_Number : Int;
- -- Used to store the ASIS version number read from a tree file to check if
- -- it is the same as stored in the ASIS version number in Tree_IO.
-----------------------------------
-- Modes for Formal Verification --
return Nkind (Arg1) = N_Identifier
-- Return True if the tool name is GNAT, and we're not in
- -- GNATprove or CodePeer or ASIS mode...
+ -- GNATprove or CodePeer mode...
and then ((Chars (Arg1) = Name_Gnat
and then not
- (CodePeer_Mode or GNATprove_Mode or ASIS_Mode))
+ (CodePeer_Mode or GNATprove_Mode))
-- or if the tool name is GNATprove, and we're in GNATprove
-- mode.
-- This package contains the routines to handle back annotation of the
-- tree to fill in representation information, and also the routines used
--- by -gnatR to output this information. This unit is used both in the
--- compiler and in ASIS (it is used in ASIS as part of the implementation
--- of the Data Decomposition Annex).
+-- by -gnatR to output this information.
-- WARNING: There is a C version of this package. Any changes to this
-- source file must be properly reflected in the C header file repinfo.h
-- in terms of the variables represented symbolically.
-- Note: the extended back annotation for the dynamic case is needed only
- -- for -gnatR3 output, and for proper operation of the ASIS DDA. Since it
- -- can be expensive to do this back annotation (for discriminated records
- -- with many variable-length arrays), we only do the full back annotation
- -- in -gnatR3 mode, or ASIS mode. In any other mode, the back-end just sets
- -- the value to Uint_Minus_1, indicating that the value of the attribute
- -- depends on discriminant information, but not giving further details.
+ -- for -gnatR3 output. Since it can be expensive to do this back annotation
+ -- (for discriminated records with many variable-length arrays), we only do
+ -- the full back annotation in -gnatR3 mode. In any other mode, the
+ -- back-end just sets the value to Uint_Minus_1, indicating that the value
+ -- of the attribute depends on discriminant information, but not giving
+ -- further details.
-- GCC expressions are represented with a Uint value that is negative.
-- See the body of this package for details on the representation used.
-- with a given set of discriminant values, indicates whether the variant
-- is present for that set of values (result is True, i.e. non-zero) or
-- not present (result is False, i.e. zero). Again, the full annotation of
- -- this field is done only in -gnatR3 mode or in ASIS mode, and in other
- -- modes, the value is set to Uint_Minus_1.
+ -- this field is done only in -gnatR3 mode, and in other modes, the value
+ -- is set to Uint_Minus_1.
subtype Node_Ref is Uint;
-- Subtype used for negative Uint values used to represent nodes
-- number of elements of the value of "operands" is specified by the
-- operands column in the line associated with the symbol in the table.
- -- As documented above, the full back annotation is only done in -gnatR3
- -- or ASIS mode. In the other cases, if the numerical expression is not
- -- a number, then it is replaced with the "??" string.
+ -- As documented above, the full back annotation is only done in -gnatR3.
+ -- In the other cases, if the numerical expression is not a number, then
+ -- it is replaced with the "??" string.
------------------------
-- The gigi Interface --
-- and entity id values and the back end makes Get_Dynamic_SO_Ref
-- calls to retrieve them.
- --------------------
- -- ASIS_Interface --
- --------------------
+ ------------------------------
+ -- External tools Interface --
+ ------------------------------
type Discrim_List is array (Pos range <>) of Uint;
-- Type used to represent list of discriminant values
-- If the subtype has a static predicate, replace the
-- original choice with the list of individual values
- -- covered by the predicate. Do not perform this
- -- transformation if we need to preserve the source
- -- for ASIS use.
+ -- covered by the predicate.
-- This should be deferred to expansion time ???
- if Present (Static_Discrete_Predicate (E))
- and then not ASIS_Mode
- then
+ if Present (Static_Discrete_Predicate (E)) then
Delete_Choice := True;
New_Cs := New_List;
if Lo_Dup > Hi_Dup then
null;
- -- Otherwise place proper message. Because
- -- of the missing expansion of subtypes with
- -- predicates in ASIS mode, do not report
- -- spurious overlap errors.
-
- elsif ASIS_Mode
- and then
- ((Is_Type (Entity (Table (J).Choice))
- and then Has_Predicates
- (Entity (Table (J).Choice)))
- or else
- (Is_Type (Entity (Table (K).Choice))
- and then Has_Predicates
- (Entity (Table (K).Choice))))
- then
- null;
+ -- Otherwise place proper message
else
-- We place message on later choice, with a
-- access types, even in compile_only mode.
if not Inside_A_Generic then
-
- -- In ASIS mode, preanalyze the expression in an
- -- others association before making copies for
- -- separate resolution and accessibility checks.
- -- This ensures that the type of the expression is
- -- available to ASIS in all cases, in particular if
- -- the expression is itself an aggregate.
-
- if ASIS_Mode then
- Preanalyze_And_Resolve (Expression (Assoc), Typ);
- end if;
-
return
New_Copy_Tree_And_Copy_Dimensions
(Expression (Assoc));
-
else
return Expression (Assoc);
end if;
-- --
------------------------------------------------------------------------------
--- Package containing utility procedures used throughout the compiler,
--- and also by ASIS so dependencies are limited to ASIS included packages.
+-- Package containing utility procedures used throughout the compiler.
-- Historical note. Many of the routines here were originally in Einfo, but
-- Einfo is supposed to be a relatively low level package dealing with the
-- 4. In the case of static predicates, we need to expand out choices that
-- correspond to the predicate for the back end. This expansion destroys
--- the list of choices, so it should be delayed to expansion time. We do
--- not want to mess up the -gnatct ASIS tree, which needs to be able to
+-- the list of choices, so it should be delayed to expansion time.
-- Step 1 is performed by the generic procedure Analyze_Choices, which is
-- called when the variant record or case statement/expression is first
-- for predicated subtypes to accurately construct this.
-- Step 4 is performed by the procedure Expand_Static_Predicates_In_Choices.
--- For case statements, this call only happens during expansion, so the tree
--- generated for ASIS does not have this expansion. For the Variant case, the
--- expansion is done in the ASIS -gnatct case, but with a proper Rewrite call
--- on the N_Variant node, so ASIS can retrieve the original. The reason we do
--- the expansion unconditionally for variants is that other processing, for
--- example for aggregates, relies on having a complete list of choices.
+-- For case statements, this call only happens during expansion. The reason
+-- we do the expansion unconditionally for variants is that other processing,
+-- for example for aggregates, relies on having a complete list of choices.
-- Historical note: We used to perform all four of these functions at once in
-- a single procedure called Analyze_Choices. This routine was called at the
procedure Optional_Subunit;
-- This procedure is called when the main unit is a stub, or when we
-- are not generating code. In such a case, we analyze the subunit if
- -- present, which is user-friendly and in fact required for ASIS, but we
- -- don't complain if the subunit is missing. In GNATprove_Mode, we issue
- -- an error to avoid formal verification of a partial unit.
+ -- present, which is user-friendly, but we don't complain if the subunit
+ -- is missing. In GNATprove_Mode, we issue an error to avoid formal
+ -- verification of a partial unit.
----------------------
-- Optional_Subunit --
-- ignore all errors. Note that Fatal_Error will still be set, so we
-- will be able to check for this case below.
- if not (ASIS_Mode or GNATprove_Mode) then
+ if not GNATprove_Mode then
Ignore_Errors_Enable := Ignore_Errors_Enable + 1;
end if;
Subunit => True,
Error_Node => N);
- if not (ASIS_Mode or GNATprove_Mode) then
+ if not GNATprove_Mode then
Ignore_Errors_Enable := Ignore_Errors_Enable - 1;
end if;
-- If the main unit is a subunit, then we are just performing semantic
-- analysis on that subunit, and any other subunits of any parent unit
- -- should be ignored, except that if we are building trees for ASIS
- -- usage we want to annotate the stub properly. If the main unit is
- -- itself a subunit, another subunit is irrelevant unless it is a
- -- subunit of the current one, that is to say appears in the current
- -- source tree.
+ -- should be ignored. If the main unit is itself a subunit, another
+ -- subunit is irrelevant unless it is a subunit of the current one, that
+ -- is to say appears in the current source tree.
elsif Nkind (Unit (Cunit (Main_Unit))) = N_Subunit
and then Subunit_Name /= Unit_Name (Main_Unit)
then
- if ASIS_Mode then
- declare
- PB : constant Node_Id := Proper_Body (Unit (Cunit (Main_Unit)));
- begin
- if Nkind_In (PB, N_Package_Body, N_Subprogram_Body)
- and then List_Containing (N) = Declarations (PB)
- then
- Optional_Subunit;
- end if;
- end;
- end if;
-
-- But before we return, set the flag for unloaded subunits. This
-- will suppress junk warnings of variables in the same declarative
-- part (or a higher level one) that are in danger of looking unused
-- clauses into regular with clauses.
if Sloc (U) /= No_Location then
- if In_Predefined_Unit (U)
-
- -- In ASIS mode the rtsfind mechanism plays no role, and
- -- we need to maintain the original tree structure, so
- -- this transformation is not performed in this case.
-
- and then not ASIS_Mode
- then
+ if In_Predefined_Unit (U) then
Set_Limited_Present (N, False);
Analyze_With_Clause (N);
else
-- Set entity of parent identifiers if the unit is a child
-- unit. This ensures that the tree is properly formed from
- -- semantic point of view (e.g. for ASIS queries). The unit
- -- entities are not fully analyzed, so we need to follow unit
- -- links in the tree.
+ -- semantic point of view. The unit entities are not fully
+ -- analyzed, so we need to follow unit links in the tree.
Set_Entity (Nam, Ent);
-- clauses in other nested packages. We replace the clause with
-- a null statement, which is otherwise ignored by the rest of
-- the compiler, so that ASIS tools can reconstruct the source.
+ -- Is this still needed now that ASIS mode is removed???
if In_Regular_With_Clause (Entity (Name (Item))) then
declare
-- actuals are positional, return the next one, if any. If the actuals
-- are named, scan the parameter associations to find the right one.
-- A_F is the corresponding entity in the analyzed generic, which is
- -- placed on the selector name for ASIS use.
+ -- placed on the selector name.
--
-- In Ada 2005, a named association may be given with a box, in which
-- case Matching_Actual sets Found_Assoc to the generic association,
Set_Has_Completion (Formal, True);
- -- Add semantic information to the original defining identifier for ASIS
- -- use.
+ -- Add semantic information to the original defining identifier.
Set_Ekind (Pack_Id, E_Package);
Set_Etype (Pack_Id, Standard_Void_Type);
-- body if there is one and it needs to be instantiated here.
-- We instantiate the body only if we are generating code, or if we
- -- are generating cross-reference information, or if we are building
- -- trees for ASIS use or GNATprove use.
+ -- are generating cross-reference information, or for GNATprove use.
declare
Enclosing_Body_Present : Boolean := False;
and then not Inline_Now
and then (Operating_Mode = Generate_Code
or else (Operating_Mode = Check_Semantics
- and then (ASIS_Mode or GNATprove_Mode)));
+ and then GNATprove_Mode));
-- If front-end inlining is enabled or there are any subprograms
-- marked with Inline_Always, do not instantiate body when within
Inline_Instance_Body (N, Gen_Unit, Act_Decl);
end if;
- -- The following is a tree patch for ASIS: ASIS needs separate nodes to
- -- be used as defining identifiers for a formal package and for the
- -- corresponding expanded package.
-
- if Nkind (N) = N_Formal_Package_Declaration then
- Act_Decl_Id := New_Copy (Defining_Entity (N));
- Set_Comes_From_Source (Act_Decl_Id, True);
- Set_Is_Generic_Instance (Act_Decl_Id, False);
- Set_Defining_Identifier (N, Act_Decl_Id);
- end if;
-
-- Check that if N is an instantiation of System.Dim_Float_IO or
-- System.Dim_Integer_IO, the formal type has a dimension system.
if (Is_In_Main_Unit (N) or else Is_Inlined_Or_Child_Of_Inlined (Subp))
- -- Must be generating code or analyzing code in ASIS/GNATprove mode
+ -- Must be generating code or analyzing code in GNATprove mode
and then (Operating_Mode = Generate_Code
or else (Operating_Mode = Check_Semantics
- and then (ASIS_Mode or GNATprove_Mode)))
+ and then GNATprove_Mode))
- -- The body is needed when generating code (full expansion), in ASIS
- -- mode for other tools, and in GNATprove mode (special expansion) for
- -- formal verification of the body itself.
+ -- The body is needed when generating code (full expansion) and in
+ -- in GNATprove mode (special expansion) for formal verification of
+ -- the body itself.
- and then (Expander_Active or ASIS_Mode or GNATprove_Mode)
+ and then (Expander_Active or GNATprove_Mode)
-- No point in inlining if ABE is inevitable
-- constitute a freeze point, but to insure that the freeze node
-- is placed properly, it is created directly when instantiating
-- the body (otherwise the freeze node might appear to early for
- -- nested instantiations). For ASIS purposes, indicate that the
- -- wrapper package has replaced the instantiation node.
+ -- nested instantiations).
elsif Nkind (Parent (N)) = N_Compilation_Unit then
Rewrite (N, Unit (Parent (N)));
end if;
-- Replace instance node for library-level instantiations of
- -- intrinsic subprograms, for ASIS use.
+ -- intrinsic subprograms.
elsif Nkind (Parent (N)) = N_Compilation_Unit then
Rewrite (N, Unit (Parent (N)));
function In_Defining_Unit_Name (Nam : Node_Id) return Boolean;
-- True if an identifier is part of the defining program unit name of
- -- a child unit. The entity of such an identifier must be kept (for
- -- ASIS use) even though as the name of an enclosing generic it would
- -- otherwise not be preserved in the generic tree.
+ -- a child unit.
+ -- Consider removing this subprogram now that ASIS no longer uses it.
----------------------
-- Copy_Descendants --
-- The entities for parent units in the defining_program_unit of a
-- generic child unit are established when the context of the unit
-- is first analyzed, before the generic copy is made. They are
- -- preserved in the copy for use in ASIS queries.
+ -- preserved in the copy for use in e.g. ASIS queries.
Ent := Entity (New_N);
Subt_Decl : Node_Id := Empty;
Subt_Mark : Node_Id := Empty;
- function Copy_Access_Def return Node_Id;
- -- If formal is an anonymous access, copy access definition of formal
- -- for generated object declaration.
-
- ---------------------
- -- Copy_Access_Def --
- ---------------------
-
- function Copy_Access_Def return Node_Id is
- begin
- Def := New_Copy_Tree (Acc_Def);
-
- -- In addition, if formal is an access to subprogram we need to
- -- generate new formals for the signature of the default, so that
- -- the tree is properly formatted for ASIS use.
-
- if Present (Access_To_Subprogram_Definition (Acc_Def)) then
- declare
- Par_Spec : Node_Id;
- begin
- Par_Spec :=
- First (Parameter_Specifications
- (Access_To_Subprogram_Definition (Def)));
- while Present (Par_Spec) loop
- Set_Defining_Identifier (Par_Spec,
- Make_Defining_Identifier (Sloc (Acc_Def),
- Chars => Chars (Defining_Identifier (Par_Spec))));
- Next (Par_Spec);
- end loop;
- end;
- end if;
-
- return Def;
- end Copy_Access_Def;
-
-- Start of processing for Instantiate_Object
begin
-- use the actual directly, rather than a copy, because it is not
-- used further in the list of actuals, and because a copy or a use
-- of relocate_node is incorrect if the instance is nested within a
- -- generic. In order to simplify ASIS searches, the Generic_Parent
- -- field links the declaration to the generic association.
+ -- generic. In order to simplify e.g. ASIS queries, the
+ -- Generic_Parent field links the declaration to the generic
+ -- association.
if No (Actual) then
Error_Msg_NE
if Present (Actual) then
if Present (Subt_Mark) then
Def := New_Copy_Tree (Subt_Mark);
- else pragma Assert (Present (Acc_Def));
- Def := Copy_Access_Def;
+ else
+ pragma Assert (Present (Acc_Def));
+ Def := New_Copy_Tree (Acc_Def);
end if;
Decl_Node :=
if Present (Subt_Mark) then
Def := New_Copy (Subt_Mark);
- else pragma Assert (Present (Acc_Def));
- Def := Copy_Access_Def;
+ else
+ pragma Assert (Present (Acc_Def));
+ Def := New_Copy_Tree (Acc_Def);
end if;
Decl_Node :=
end if;
if Is_Global (E) then
-
- -- If the entity is a package renaming that is the prefix of
- -- an expanded name, it has been rewritten as the renamed
- -- package, which is necessary semantically but complicates
- -- ASIS tree traversal, so we recover the original entity to
- -- expose the renaming. Take into account that the context may
- -- be a nested generic, that the original node may itself have
- -- an associated node that had better be an entity, and that
- -- the current node is still a selected component.
-
- if Ekind (E) = E_Package
- and then Nkind (N) = N_Selected_Component
- and then Nkind (Parent (N)) = N_Expanded_Name
- and then Present (Original_Node (N2))
- and then Is_Entity_Name (Original_Node (N2))
- and then Present (Entity (Original_Node (N2)))
- then
- if Is_Global (Entity (Original_Node (N2))) then
- N2 := Original_Node (N2);
- Set_Associated_Node (N, N2);
- Set_Global_Type (N, N2);
-
- -- Renaming is local, and will be resolved in instance
-
- else
- Set_Associated_Node (N, Empty);
- Set_Etype (N, Empty);
- end if;
-
- else
- Set_Global_Type (N, N2);
- end if;
+ Set_Global_Type (N, N2);
elsif Nkind (N) = N_Op_Concat
and then Is_Generic_Type (Etype (N2))
-- The node did not undergo a transformation
if Nkind (N) = Nkind (Get_Associated_Node (N)) then
- declare
- Aux_N2 : constant Node_Id := Get_Associated_Node (N);
- Orig_N2_Parent : constant Node_Id :=
- Original_Node (Parent (Aux_N2));
- begin
- -- The parent of this identifier is a selected component
- -- which denotes a named number that was constant folded.
- -- Preserve the original name for ASIS and link the parent
- -- with its expanded name. The constant folding will be
- -- repeated in the instance.
-
- if Nkind (Parent (N)) = N_Selected_Component
- and then Nkind_In (Parent (Aux_N2), N_Integer_Literal,
- N_Real_Literal)
- and then Is_Entity_Name (Orig_N2_Parent)
- and then Ekind (Entity (Orig_N2_Parent)) in Named_Kind
- and then Is_Global (Entity (Orig_N2_Parent))
- then
- N2 := Aux_N2;
- Set_Associated_Node
- (Parent (N), Original_Node (Parent (N2)));
-
- -- Common case
-
- else
- -- If this is a discriminant reference, always save it.
- -- It is used in the instance to find the corresponding
- -- discriminant positionally rather than by name.
+ -- If this is a discriminant reference, always save it.
+ -- It is used in the instance to find the corresponding
+ -- discriminant positionally rather than by name.
- Set_Original_Discriminant
- (N, Original_Discriminant (Get_Associated_Node (N)));
- end if;
+ Set_Original_Discriminant
+ (N, Original_Discriminant (Get_Associated_Node (N)));
- Reset_Entity (N);
- end;
+ Reset_Entity (N);
-- The analysis of the generic copy transformed the identifier
-- into another construct. Propagate the changes to the template.
-- The identifier denotes a named number that was constant
-- folded. Preserve the original name for ASIS and undo the
-- constant folding which will be repeated in the instance.
+ -- Is this still needed???
elsif Nkind_In (N2, N_Integer_Literal, N_Real_Literal)
and then Is_Entity_Name (Original_Node (N2))
and then Nkind (Original_Node (N2)) = Nkind (N)
then
-- Operation was constant-folded. Whenever possible,
- -- recover semantic information from unfolded node,
- -- for ASIS use.
+ -- recover semantic information from unfolded node.
+ -- This was initially done for ASIS but is apparently
+ -- needed also for e.g. compiling a-nbnbin.adb.
Set_Associated_Node (N, Original_Node (N2));
-- Construct the attribute_definition_clause. The expression
-- in the aspect specification is simply shared with the
-- constructed attribute, because it will be fully analyzed
- -- when the attribute is processed. However, in ASIS mode
- -- the aspect expression itself is preanalyzed and resolved
- -- to catch visibility errors that are otherwise caught
- -- later, and we create a separate copy of the expression
- -- to prevent analysis of a malformed tree (e.g. a function
- -- call with parameter associations).
-
- if ASIS_Mode then
- Aitem :=
- Make_Attribute_Definition_Clause (Loc,
- Name => Ent,
- Chars => Chars (Id),
- Expression => New_Copy_Tree (Expr));
- else
- Aitem :=
- Make_Attribute_Definition_Clause (Loc,
- Name => Ent,
- Chars => Chars (Id),
- Expression => Relocate_Node (Expr));
- end if;
+ -- when the attribute is processed.
+
+ 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
-- 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. Also, we
- -- don't do this in GNATprove mode, because it brings no
- -- benefit for proof and causes annoynace for flow analysis,
+ -- We don't do this in GNATprove mode, because it brings no
+ -- benefit for proof and causes annoyance for flow analysis,
-- which prefers to be as close to the original source code
-- as possible. Also we don't do this when analyzing generic
-- units since it causes spurious visibility errors in the
-- preanalysis of instantiations.
- if not (ASIS_Mode or GNATprove_Mode)
+ if not GNATprove_Mode
and then (Pname = Name_Postcondition
or else not Class_Present (Aspect))
and then not Inside_A_Generic
-- because subsequent visibility analysis of the aspect
-- depends on this sharing. This should be cleaned up???
- -- If the context is generic or involves ASIS, we want
- -- to preserve the original tree, and simply share it
- -- between aspect and generated attribute. This parallels
- -- what is done in sem_prag.adb (see Get_Argument).
+ -- If the context is generic, we want to preserve the
+ -- original tree, and simply share it between aspect and
+ -- generated attribute. This parallels what is done in
+ -- sem_prag.adb (see Get_Argument).
declare
New_Expr : Node_Id;
begin
- if ASIS_Mode or else Inside_A_Generic then
+ if Inside_A_Generic then
New_Expr := Expr;
else
New_Expr := Relocate_Node (Expr);
-- expressions through the Original_Node link. This is used
-- in semantic analysis for ASIS mode, so that the original
-- expression also gets analyzed.
+ -- Is this still needed???
Comp_Expr := First (Expressions (Expr));
while Present (Comp_Expr) loop
Set_Has_Alignment_Clause (U_Ent);
-- Tagged type case, check for attempt to set alignment to a
- -- value greater than Max_Align, and reset if so. This error
- -- is suppressed in ASIS mode to allow for different ASIS
- -- back ends or ASIS-based tools to query the illegal clause.
+ -- value greater than Max_Align, and reset if so.
- if Is_Tagged_Type (U_Ent)
- and then Align > Max_Align
- and then not ASIS_Mode
- then
+ if Is_Tagged_Type (U_Ent) and then Align > Max_Align then
Error_Msg_N
("alignment for & set to Maximum_Aligment??", Nam);
Set_Alignment (U_Ent, Max_Align);
elsif Radix = 10 then
Set_Machine_Radix_10 (U_Ent);
- -- The following error is suppressed in ASIS mode to allow for
- -- different ASIS back ends or ASIS-based tools to query the
- -- illegal clause.
-
- elsif not ASIS_Mode then
+ else
Error_Msg_N ("machine radix value must be 2 or 10", Expr);
end if;
end if;
else
Check_Size (Expr, U_Ent, Size, Biased);
- -- The following errors are suppressed in ASIS mode to allow
- -- for different ASIS back ends or ASIS-based tools to query
- -- the illegal clause.
-
- if ASIS_Mode then
- null;
-
- elsif Size <= 0 then
+ if Size <= 0 then
Error_Msg_N ("Object_Size must be positive", Expr);
elsif Is_Scalar_Type (U_Ent) then
-- For objects, set Esize only
else
- -- The following error is suppressed in ASIS mode to allow
- -- for different ASIS back ends or ASIS-based tools to query
- -- the illegal clause.
-
if Is_Elementary_Type (Etyp)
and then Size /= System_Storage_Unit
and then Size /= System_Storage_Unit * 2
and then Size /= System_Storage_Unit * 4
and then Size /= System_Storage_Unit * 8
- and then not ASIS_Mode
then
Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
Error_Msg_Uint_2 := Error_Msg_Uint_1 * 8;
null;
elsif Is_Elementary_Type (U_Ent) then
-
- -- The following errors are suppressed in ASIS mode to allow
- -- for different ASIS back ends or ASIS-based tools to query
- -- the illegal clause.
-
- if ASIS_Mode then
- null;
-
- elsif Size /= System_Storage_Unit
+ if Size /= System_Storage_Unit
and then Size /= System_Storage_Unit * 2
and then Size /= System_Storage_Unit * 4
and then Size /= System_Storage_Unit * 8
if Present (Mod_Clause (N)) then
declare
- Loc : constant Source_Ptr := Sloc (N);
- M : constant Node_Id := Mod_Clause (N);
- P : constant List_Id := Pragmas_Before (M);
- AtM_Nod : Node_Id;
-
- Mod_Val : Uint;
- pragma Warnings (Off, Mod_Val);
+ M : constant Node_Id := Mod_Clause (N);
+ P : constant List_Id := Pragmas_Before (M);
+ Ignore : Uint;
begin
Check_Restriction (No_Obsolescent_Features, Mod_Clause (N));
Analyze_List (P);
end if;
- -- In ASIS_Mode mode, expansion is disabled, but we must convert
- -- the Mod clause into an alignment clause anyway, so that the
- -- back end can compute and back-annotate properly the size and
- -- alignment of types that may include this record.
+ -- Get the alignment value to perform error checking
- -- This seems dubious, this destroys the source tree in a manner
- -- not detectable by ASIS ???
-
- if Operating_Mode = Check_Semantics and then ASIS_Mode then
- AtM_Nod :=
- Make_Attribute_Definition_Clause (Loc,
- Name => New_Occurrence_Of (Base_Type (Rectype), Loc),
- Chars => Name_Alignment,
- Expression => Relocate_Node (Expression (M)));
-
- Set_From_At_Mod (AtM_Nod);
- Insert_After (N, AtM_Nod);
- Mod_Val := Get_Alignment_Value (Expression (AtM_Nod));
- Set_Mod_Clause (N, Empty);
-
- else
- -- Get the alignment value to perform error checking
-
- Mod_Val := Get_Alignment_Value (Expression (M));
- end if;
+ Ignore := Get_Alignment_Value (Expression (M));
end;
end if;
Set_Etype (N, Typ);
Set_Entity (N, Object_Entity);
-
- -- We want to treat the node as if it comes from source, so
- -- that ASIS will not ignore it.
-
- Set_Comes_From_Source (N, True);
end Replace_Type_Reference;
-- Local variables
-- Extract the arguments of the pragma. The expression itself
-- is copied for use in the predicate function, to preserve the
-- original version for ASIS use.
+ -- Is this still needed???
Arg1 := First (Pragma_Argument_Associations (Prag));
Arg2 := Next (Arg1);
procedure Size_Too_Small_Error (Min_Siz : Uint) is
begin
- -- This error is suppressed in ASIS mode to allow for different ASIS
- -- back ends or ASIS-based tools to query the illegal clause.
-
- if not ASIS_Mode then
- Error_Msg_Uint_1 := Min_Siz;
- Error_Msg_NE (Size_Too_Small_Message, N, T);
- end if;
+ Error_Msg_Uint_1 := Min_Siz;
+ Error_Msg_NE (Size_Too_Small_Message, N, T);
end Size_Too_Small_Error;
-- Local variables
-- between interface primitives and tagged type primitives. They are
-- also used to locate primitives covering interfaces when processing
-- generics (see Derive_Subprograms).
+ -- ??? Revisit now that ASIS mode is gone.
-- This is not needed in the generic case
-- for aggregates, requires the expanded list of choices.
-- If the expander is not active, then we can't just clobber
- -- the list since it would invalidate the ASIS -gnatct tree.
+ -- the list since it would invalidate the tree.
-- So we have to rewrite the variant part with a Rewrite
-- call that replaces it with a copy and clobber the copy.
+ -- This is no longer needed for ASIS, but possibly for
+ -- GNATprove???
if not Expander_Active then
declare
-- to the others choice (it's the list we're replacing).
-- We only want to do this if the expander is active, since
- -- we do not want to clobber the ASIS tree.
+ -- we do not want to clobber the tree.
+ -- This is no longer needed for ASIS, is this needed for
+ -- GNATprove_Mode???
if Expander_Active then
declare
return No_Uint;
elsif Align < 0 then
-
- -- This error is suppressed in ASIS mode to allow for different ASIS
- -- back ends or ASIS-based tools to query the illegal clause.
-
- if not ASIS_Mode then
- Error_Msg_N ("alignment value must be positive", Expr);
- end if;
-
+ Error_Msg_N ("alignment value must be positive", Expr);
return No_Uint;
-- If Alignment is specified to be 0, we treat it the same as 1
exit when M = Align;
if M > Align then
-
- -- This error is suppressed in ASIS mode to allow for
- -- different ASIS back ends or ASIS-based tools to query the
- -- illegal clause.
-
- if not ASIS_Mode then
- Error_Msg_N ("alignment value must be power of 2", Expr);
- end if;
-
+ Error_Msg_N ("alignment value must be power of 2", Expr);
return No_Uint;
end if;
end;
pragma Assert (Ignore_Rep_Clauses);
-- Note: we use Replace rather than Rewrite, because we don't want
- -- ASIS to be able to use Original_Node to dig out the (undecorated)
+ -- tools to be able to use Original_Node to dig out the (undecorated)
-- rep clause that is being replaced.
Replace (N, Make_Null_Statement (Sloc (N)));
-- The null statement must be marked as not coming from source. This is
- -- so that ASIS ignores it, and also the back end does not expect bogus
+ -- so that tools ignore it, and also the back end does not expect bogus
-- "from source" null statements in weird places (e.g. in declarative
-- regions where such null statements are not allowed).
-- introduce a local identifier that would require proper expansion to
-- handle properly.
- -- In ASIS_Mode we preserve the entity in the source because there is
- -- no subsequent expansion to decorate the tree.
-
------------------
-- Resolve_Name --
------------------
or else N /= Selector_Name (Parent (N)))
then
Find_Direct_Name (N);
-
- -- In ASIS mode we must analyze overloaded identifiers to ensure
- -- their correct decoration because expansion is disabled (and
- -- the expansion of freeze nodes takes care of resolving aspect
- -- expressions).
-
- if ASIS_Mode then
- if Is_Overloaded (N) then
- Analyze (Parent (N));
- end if;
- else
- Set_Entity (N, Empty);
- end if;
+ Set_Entity (N, Empty);
-- The name is component association needs no resolution.
begin
F := First (Formals);
- -- In ASIS mode, the access_to_subprogram may be analyzed twice,
- -- when it is part of an unconstrained type and subtype expansion
- -- is disabled. To avoid back-end problems with shared profiles,
- -- use previous subprogram type as the designated type, and then
- -- remove scope added above.
-
- if ASIS_Mode and then Present (Scope (Defining_Identifier (F)))
- then
- Set_Etype (T_Name, T_Name);
- Init_Size_Align (T_Name);
- Set_Directly_Designated_Type (T_Name,
- Scope (Defining_Identifier (F)));
- End_Scope;
- return;
- end if;
-
while Present (F) loop
if No (Parent (Defining_Identifier (F))) then
Set_Parent (Defining_Identifier (F), F);
-- of locally defined tagged types (or compiling with static
-- dispatch tables generation disabled) the corresponding
-- entry of the secondary dispatch table is filled when such
- -- an entity is frozen. This is an expansion activity that must
- -- be suppressed for ASIS because it leads to gigi elaboration
- -- issues in annotate mode.
+ -- an entity is frozen.
- if not ASIS_Mode then
- Set_Has_Delayed_Freeze (New_Subp);
- end if;
+ Set_Has_Delayed_Freeze (New_Subp);
end if;
<<Continue>>
else
-- For declarations in a subprogram body there is no issue
- -- with name resolution in aspect specifications, but in
- -- ASIS mode we need to preanalyze aspect specifications
- -- that may otherwise only be analyzed during expansion
- -- (e.g. during generation of a related subprogram).
-
- if ASIS_Mode then
- Resolve_Aspects;
- end if;
+ -- with name resolution in aspect specifications.
Freeze_All (First_Entity (Current_Scope), Decl);
Freeze_From := Last_Entity (Current_Scope);
-- End of a package declaration
- -- In compilation mode the expansion of freeze node takes care
- -- of resolving expressions of all aspects in the list. In ASIS
- -- mode this must be done explicitly.
-
- if ASIS_Mode
- and then Scope (Current_Scope) = Standard_Standard
- then
- Resolve_Aspects;
- end if;
-
-- This is a freeze point because it is the end of a
-- compilation unit.
-- to examine Next_Decl as the late primitive idiom can only apply
-- to the first encountered body.
- -- The spec of the late primitive is not generated in ASIS mode to
- -- ensure a consistent list of primitives that indicates the true
- -- semantic structure of the program (which is not relevant when
- -- generating executable code).
-
-- ??? A cleaner approach may be possible and/or this solution
-- could be extended to general-purpose late primitives, TBD.
- if not ASIS_Mode
- and then not Body_Seen
- and then not Is_Body (Decl)
- then
+ if not Body_Seen and then not Is_Body (Decl) then
Body_Seen := True;
if Nkind (Next_Decl) = N_Subprogram_Body then
else
-- In ASIS mode, if the next declaration is a body, complete
-- the analysis of declarations so far.
+ -- Is this still needed???
Resolve_Aspects;
end if;
Mark_Rewrite_Insertion (Decl);
- -- In ASIS mode, analyze the profile on the original node, because
- -- the separate copy does not provide enough links to recover the
- -- original tree. Analysis is limited to type annotations, within
- -- a temporary scope that serves as an anonymous subprogram to collect
- -- otherwise useless temporaries and itypes.
-
- if ASIS_Mode then
- declare
- Typ : constant Entity_Id := Make_Temporary (Loc, 'S');
-
- begin
- if Nkind (Spec) = N_Access_Function_Definition then
- Set_Ekind (Typ, E_Function);
- else
- Set_Ekind (Typ, E_Procedure);
- end if;
-
- Set_Parent (Typ, N);
- Set_Scope (Typ, Current_Scope);
- Push_Scope (Typ);
-
- -- Nothing to do if procedure is parameterless
-
- if Present (Parameter_Specifications (Spec)) then
- Process_Formals (Parameter_Specifications (Spec), Spec);
- end if;
-
- if Nkind (Spec) = N_Access_Function_Definition then
- declare
- Def : constant Node_Id := Result_Definition (Spec);
-
- begin
- -- The result might itself be an anonymous access type, so
- -- have to recurse.
-
- if Nkind (Def) = N_Access_Definition then
- if Present (Access_To_Subprogram_Definition (Def)) then
- Set_Etype
- (Def,
- Replace_Anonymous_Access_To_Protected_Subprogram
- (Spec));
- else
- Find_Type (Subtype_Mark (Def));
- end if;
-
- else
- Find_Type (Def);
- end if;
- end;
- end if;
-
- End_Scope;
- end;
- end if;
-
-- Insert the new declaration in the nearest enclosing scope. If the
-- parent is a body and N is its return type, the declaration belongs
-- in the enclosing scope. Likewise if N is the type of a parameter.
elsif not Private_Extension then
Expand_Record_Extension (Derived_Type, Type_Def);
- -- Note : previously in ASIS mode we set the Parent_Subtype of the
- -- derived type to propagate some semantic information. This led
- -- to other ASIS failures and has been removed.
-
-- Ada 2005 (AI-251): Addition of the Tag corresponding to all the
-- implemented interfaces if we are in expansion mode
-- If an access to object, preserve entity of designated type,
-- for ASIS use, before rewriting the component definition.
+ -- Is this still needed???
else
declare
begin
Desig := Entity (Subtype_Indication (Type_Def));
- -- If the access definition is to the current record,
- -- the visible entity at this point is an incomplete
- -- type. Retrieve the full view to simplify ASIS queries
+ -- If the access definition is to the current record,
+ -- the visible entity at this point is an incomplete
+ -- type. Retrieve the full view to simplify ASIS queries
if Ekind (Desig) = E_Incomplete_Type then
Desig := Full_View (Desig);
end if;
Set_Entity
- (Subtype_Mark (Access_Definition (Comp_Def)), Desig);
+ (Subtype_Mark (Access_Definition (Comp_Def)), Desig);
end;
end if;
else
T := Process_Subtype (Obj_Def, Related_Nod);
-
- -- If expansion is disabled an object definition that is an aggregate
- -- will not get expanded and may lead to scoping problems in the back
- -- end, if the object is referenced in an inner scope. In that case
- -- create an itype reference for the object definition now. This
- -- may be redundant in some cases, but harmless.
-
- if Is_Itype (T)
- and then Nkind (Related_Nod) = N_Object_Declaration
- and then ASIS_Mode
- then
- Build_Itype_Reference (T, Related_Nod);
- end if;
end if;
return T;
and then Is_Overloadable (Entity (Selector_Name (P)))
then
Process_Function_Call;
-
- -- In ASIS mode within a generic, a prefixed call is analyzed and
- -- partially rewritten but the original indexed component has not
- -- yet been rewritten as a call. Perform the replacement now.
-
- elsif Nkind (P) = N_Selected_Component
- and then Nkind (Parent (P)) = N_Function_Call
- and then ASIS_Mode
- then
- Rewrite (N, Parent (P));
- Analyze (N);
-
else
-- Indexed component, slice, or a call to a member of a family
-- entry, which will be converted to an entry call later.
-- reflect the right kind. This is needed for proper ASIS
-- navigation. If expansion is enabled, the transformation is
-- performed when the expression is rewritten as a loop.
+ -- Is this still needed???
Set_Iterator_Specification (N,
New_Copy_Tree (Iterator_Specification (Parent (Loop_Par))));
-- In ASIS mode the generic parent type may be absent. Examine
-- the parent type directly for a component that may have been
-- visible in a parent generic unit.
+ -- ??? Revisit now that ASIS mode is gone
elsif Is_Derived_Type (Prefix_Type) then
Par := Etype (Prefix_Type);
-- in Standard to be chosen, and the "/=" will be rewritten as a
-- negation of "=" (see the end of Analyze_Equality_Op). This ensures
-- that rewriting happens during analysis rather than being
- -- delayed until expansion (this is needed for ASIS, which only sees
- -- the unexpanded tree). Note that if the node is N_Op_Ne, but Op_Id
+ -- delayed until expansion (is this still needed now that ASIS mode
+ -- is gone???). Note that if the node is N_Op_Ne, but Op_Id
-- is Name_Op_Eq then we still proceed with the interpretation,
-- because that indicates the potential rewriting case where the
-- interpretation to consider is actually "=" and the node may be
Actuals : List_Id;
begin
- -- Obj may already have been rewritten if it involves an implicit
- -- dereference (e.g. if it is an access to a limited view). Preserve
- -- a link to the original node for ASIS use.
-
- if not Comes_From_Source (Obj) then
- Set_Original_Node (Dummy, Original_Node (Obj));
- end if;
-
-- Common case covering 1) Call to a procedure and 2) Call to a
-- function that has some additional actuals.
-- Once the aspects of the generated body have been analyzed, create
-- a copy for ASIS purposes and associate it with the original node.
+ -- Is this still needed???
if Has_Aspects (N) then
Set_Aspect_Specifications (Orig_N,
-- Once the aspects of the generated spec have been analyzed, create
-- a copy for ASIS purposes and associate it with the original node.
+ -- Is this still needed???
if Has_Aspects (N) then
Set_Aspect_Specifications (Orig_N,
-- the freeze actions that include the bodies. In particular, extra
-- formals for accessibility or for return-in-place may need to be
-- generated. Freeze nodes, if any, are inserted before the current
- -- body. These freeze actions are also needed in ASIS mode and in
- -- Compile_Only mode to enable the proper back-end type annotations.
+ -- body. These freeze actions are also needed in Compile_Only mode to
+ -- enable the proper back-end type annotations.
-- They are necessary in any case to ensure proper elaboration order
-- in gigi.
and then not Has_Completion (Spec_Id)
and then Serious_Errors_Detected = 0
and then (Expander_Active
- or else ASIS_Mode
or else Operating_Mode = Check_Semantics
or else Is_Ignored_Ghost_Entity (Spec_Id))
then
-- Within an instance, add local renaming declarations so that
-- gdb can retrieve the values of actuals more easily. This is
- -- only relevant if generating code (and indeed we definitely
- -- do not want these definitions -gnatc mode, because that would
- -- confuse ASIS).
+ -- only relevant if generating code.
if Is_Generic_Instance (Spec_Id)
and then Is_Wrapper_Package (Current_Scope)
Result := No_Rational;
end if;
- -- Provide minimal semantic information on dimension expressions,
- -- even though they have no run-time existence. This is for use by
- -- ASIS tools, in particular pretty-printing. If generating code
- -- standard operator resolution will take place.
-
- if ASIS_Mode then
- Set_Entity (N, Standard_Op_Minus);
- Set_Etype (N, Standard_Integer);
- end if;
-
return Result;
end Process_Minus;
Result := Left_Rat / Right_Rat;
end if;
- -- Provide minimal semantic information on dimension expressions,
- -- even though they have no run-time existence. This is for use by
- -- ASIS tools, in particular pretty-printing. If generating code
- -- standard operator resolution will take place.
-
- if ASIS_Mode then
- Set_Entity (N, Standard_Op_Divide);
- Set_Etype (N, Standard_Integer);
- end if;
-
return Result;
end Process_Divide;
if Legacy_Elaboration_Checks then
return;
- -- Nothing to do for ASIS because ABE checks and diagnostics are not
- -- performed in this mode.
-
- elsif ASIS_Mode then
- return;
-
-- Nothing to do when the call is being preanalyzed as the marker will
-- be inserted in the wrong place.
Finalize_All_Data_Structures;
return;
- -- Nothing to do for ASIS because ABE checks and diagnostics are not
- -- performed in this mode.
-
- elsif ASIS_Mode then
- Finalize_All_Data_Structures;
- return;
-
-- Nothing to do when the elaboration phase of the compiler is not
-- active.
if Legacy_Elaboration_Checks then
return;
- -- Nothing to do for ASIS because ABE checks and diagnostics are not
- -- performed in this mode.
-
- elsif ASIS_Mode then
- return;
-
-- Nothing to do when the scenario is being preanalyzed
elsif Preanalysis_Active then
-- Do not normalize a clause if errors were detected (count
-- of Serious_Errors has increased) because the inputs and/or
- -- outputs may denote illegal items. Normalization is disabled
- -- in ASIS mode as it alters the tree by introducing new nodes
- -- similar to expansion.
+ -- outputs may denote illegal items.
- if Serious_Errors_Detected = Errors and then not ASIS_Mode then
+ if Serious_Errors_Detected = Errors then
Normalize_Clause (Clause);
end if;
Set_Mechanism_Value
(Formal, Expression (Massoc));
- -- Set entity on identifier (needed by ASIS)
+ -- Set entity on identifier for proper tree
+ -- structure.
Set_Entity (Choice, Formal);
then
Error_Msg_N
("Inline cannot apply to a formal subprogram", N);
-
- -- If Subp is a renaming, it is the renamed entity that
- -- will appear in any call, and be inlined. However, for
- -- ASIS uses it is convenient to indicate that the renaming
- -- itself is an inlined subprogram, so that some gnatcheck
- -- rules can be applied in the absence of expansion.
-
- elsif Nkind (Decl) = N_Subprogram_Renaming_Declaration then
- Set_Inline_Flags (Subp);
end if;
end if;
if Arg_Count > 1 then
Check_Optional_Identifier (Arg2, Name_Message);
- -- Provide semantic annnotations for optional argument, for
+ -- Provide semantic annotations for optional argument, for
-- ASIS use, before rewriting.
+ -- Is this still needed???
Preanalyze_And_Resolve (Expression (Arg2), Standard_String);
Append_To (New_Args, New_Copy_Tree (Arg2));
if Present (CS) then
- -- If we have multiple instances, concatenate them, but
- -- not in ASIS, where we want the original tree.
+ -- If we have multiple instances, concatenate them.
- if not ASIS_Mode then
- Start_String (Strval (CS));
- Store_String_Char (' ');
- Store_String_Chars (Strval (Str));
- Set_Strval (CS, End_String);
- end if;
+ Start_String (Strval (CS));
+ Store_String_Char (' ');
+ Store_String_Chars (Strval (Str));
+ Set_Strval (CS, End_String);
else
Set_Ident_String (Current_Sem_Unit, Str);
if Present (Ename) then
- -- If entity name matches, we are fine. Save entity in
- -- pragma argument, for ASIS use.
+ -- If entity name matches, we are fine.
if Chars (Ename) = Chars (Ent) then
Set_Entity (Ename, Ent);
-- Now declare the operators. We do this during analysis rather
-- than expansion, since we want the operators available if we
- -- are operating in -gnatc or ASIS mode.
+ -- are operating in -gnatc mode.
Declare_Shift_Operator (Name_Rotate_Left);
Declare_Shift_Operator (Name_Rotate_Right);
Add_Contract_Item (N, Subp_Id);
- -- Preanalyze the original aspect argument "Name" for ASIS or for
- -- a generic subprogram to properly capture global references.
+ -- Preanalyze the original aspect argument "Name" for a generic
+ -- subprogram to properly capture global references.
- if ASIS_Mode or else Is_Generic_Subprogram (Subp_Id) then
+ if Is_Generic_Subprogram (Subp_Id) then
Asp_Arg := Test_Case_Arg (N, Name_Name, From_Aspect => True);
if Present (Asp_Arg) then
and then Nam_In (Chars (Argx), Name_Gnat, Name_Gnatprove)
then
if Chars (Argx) = Name_Gnat then
- if CodePeer_Mode or GNATprove_Mode or ASIS_Mode then
+ if CodePeer_Mode or GNATprove_Mode then
Rewrite (N, Make_Null_Statement (Loc));
Analyze (N);
raise Pragma_Exit;
Body_Outputs => Body_Outputs);
end if;
- -- Matching is disabled in ASIS because clauses are not normalized as
- -- this is a tree altering activity similar to expansion.
-
- if ASIS_Mode then
- goto Leave;
- end if;
-
-- Multiple dependency clauses appear as component associations of an
-- aggregate. Note that the clauses are copied because the algorithm
-- modifies them and this should not be visible in Depends.
Arg : Node_Id;
begin
- -- Preanalyze the original aspect argument for ASIS or for a generic
- -- subprogram to properly capture global references.
+ -- Preanalyze the original aspect argument for a generic subprogram
+ -- to properly capture global references.
- if ASIS_Mode or else Is_Generic_Subprogram (Spec_Id) then
+ if Is_Generic_Subprogram (Spec_Id) then
Arg :=
Test_Case_Arg
(Prag => N,
Args : constant List_Id := Pragma_Argument_Associations (Prag);
begin
- -- Use the expression of the original aspect when compiling for ASIS or
- -- when analyzing the template of a generic unit. In both cases the
- -- aspect's tree must be decorated to allow for ASIS queries or to save
- -- the global references in the generic context.
+ -- Use the expression of the original aspect when analyzing the template
+ -- of a generic unit. In both cases the aspect's tree must be decorated
+ -- to allow for ASIS queries or to save the global references in the
+ -- generic context.
if From_Aspect_Specification (Prag)
- and then (ASIS_Mode or else (Present (Context_Id)
- and then Is_Generic_Unit (Context_Id)))
+ and then (Present (Context_Id) and then Is_Generic_Unit (Context_Id))
then
return Corresponding_Aspect (Prag);
elsif Nkind (N) = N_Identifier
and then From_Policy
and then Serious_Errors_Detected = 0
- and then not ASIS_Mode
then
if Chars (N) = Name_Precondition
or else Chars (N) = Name_Postcondition
-- of the pragma. The argument is extracted in the following manner:
--
-- When the pragma is generated from an aspect, return the corresponding
- -- aspect for ASIS or when Context_Id denotes a generic unit.
+ -- aspect when Context_Id denotes a generic unit.
--
-- Otherwise return the first argument of Prag
--
else
Resolve (N, Typ);
end if;
-
- -- If in ASIS_Mode, propagate operand types to original actuals of
- -- function call, which would otherwise not be fully resolved. If
- -- the call has already been constant-folded, nothing to do. We
- -- relocate the operand nodes rather than copy them, to preserve
- -- original_node pointers, given that the operands themselves may
- -- have been rewritten. If the call was itself a rewriting of an
- -- operator node, nothing to do.
-
- if ASIS_Mode
- and then Nkind (N) in N_Op
- and then Nkind (Original_Node (N)) = N_Function_Call
- then
- declare
- L : Node_Id;
- R : constant Node_Id := Right_Opnd (N);
-
- Old_First : constant Node_Id :=
- First (Parameter_Associations (Original_Node (N)));
- Old_Sec : Node_Id;
-
- begin
- if Is_Binary then
- L := Left_Opnd (N);
- Old_Sec := Next (Old_First);
-
- -- If the original call has named associations, replace the
- -- explicit actual parameter in the association with the proper
- -- resolved operand.
-
- if Nkind (Old_First) = N_Parameter_Association then
- if Chars (Selector_Name (Old_First)) =
- Chars (First_Entity (Op_Id))
- then
- Rewrite (Explicit_Actual_Parameter (Old_First),
- Relocate_Node (L));
- else
- Rewrite (Explicit_Actual_Parameter (Old_First),
- Relocate_Node (R));
- end if;
-
- else
- Rewrite (Old_First, Relocate_Node (L));
- end if;
-
- if Nkind (Old_Sec) = N_Parameter_Association then
- if Chars (Selector_Name (Old_Sec)) =
- Chars (First_Entity (Op_Id))
- then
- Rewrite (Explicit_Actual_Parameter (Old_Sec),
- Relocate_Node (L));
- else
- Rewrite (Explicit_Actual_Parameter (Old_Sec),
- Relocate_Node (R));
- end if;
-
- else
- Rewrite (Old_Sec, Relocate_Node (R));
- end if;
-
- else
- if Nkind (Old_First) = N_Parameter_Association then
- Rewrite (Explicit_Actual_Parameter (Old_First),
- Relocate_Node (R));
- else
- Rewrite (Old_First, Relocate_Node (R));
- end if;
- end if;
- end;
-
- Set_Parent (Original_Node (N), Parent (N));
- end if;
end Make_Call_Into_Operator;
-------------------
procedure Resolve_Generalized_Indexing (N : Node_Id; Typ : Entity_Id) is
Indexing : constant Node_Id := Generalized_Indexing (N);
- Call : Node_Id;
- Indexes : List_Id;
- Pref : Node_Id;
-
begin
- -- In ASIS mode, propagate the information about the indexes back to
- -- to the original indexing node. The generalized indexing is either
- -- a function call, or a dereference of one. The actuals include the
- -- prefix of the original node, which is the container expression.
-
- if ASIS_Mode then
- Resolve (Indexing, Typ);
- Set_Etype (N, Etype (Indexing));
- Set_Is_Overloaded (N, False);
-
- Call := Indexing;
- while Nkind_In (Call, N_Explicit_Dereference, N_Selected_Component)
- loop
- Call := Prefix (Call);
- end loop;
-
- if Nkind (Call) = N_Function_Call then
- Indexes := New_Copy_List (Parameter_Associations (Call));
- Pref := Remove_Head (Indexes);
- Set_Expressions (N, Indexes);
-
- -- If expression is to be reanalyzed, reset Generalized_Indexing
- -- to recreate call node, as is the case when the expression is
- -- part of an expression function.
-
- if In_Spec_Expression then
- Set_Generalized_Indexing (N, Empty);
- end if;
-
- Set_Prefix (N, Pref);
- end if;
-
- else
- Rewrite (N, Indexing);
- Resolve (N, Typ);
- end if;
+ Rewrite (N, Indexing);
+ Resolve (N, Typ);
end Resolve_Generalized_Indexing;
---------------------------
-- Note: test for presence of E is defense against previous error.
if No (E) then
-
- -- If expansion is disabled the Corresponding_Record_Type may
- -- not be available yet, so use the interface list in the
- -- declaration directly.
-
- if ASIS_Mode
- and then Nkind (Parent (BT2)) = N_Protected_Type_Declaration
- and then Present (Interface_List (Parent (BT2)))
- then
- declare
- Intf : Node_Id := First (Interface_List (Parent (BT2)));
- begin
- while Present (Intf) loop
- if Is_Ancestor (Etype (T1), Entity (Intf)) then
- return True;
- else
- Next (Intf);
- end if;
- end loop;
- end;
-
- return False;
-
- else
- Check_Error_Detected;
- end if;
+ Check_Error_Detected;
-- Here we have a corresponding record type
if Present (Elaboration_Entity (Spec_Id)) then
return;
- -- Ignore in ASIS mode, elaboration entity is not in source and plays
- -- no role in analysis.
-
- elsif ASIS_Mode then
- return;
-
-- Do not generate an elaboration entity in GNATprove move because the
-- elaboration counter is a form of expansion.
if Legacy_Elaboration_Checks then
return False;
- -- No marker needs to be created for ASIS because ABE diagnostics and
- -- checks are not performed in this mode.
-
- elsif ASIS_Mode then
- return False;
-
-- No marker needs to be created when the reference is preanalyzed
-- because the marker will be inserted in the wrong place.
-- subprogram instance, and the other is an anonymous subprogram nested
-- within a wrapper package that contains the renamings for the actuals.
-- Both of these entities have the Sloc of the defining entity in the
- -- instantiation node. This simplifies some ASIS queries.
+ -- instantiation node. This simplified for instance in the past some ASIS
+ -- queries.
-----------------------
-- Field Definitions --
-- code is being generated, since they involved expander actions that
-- destroy the tree.
- ---------------
- -- ASIS Mode --
- ---------------
-
- -- When a file is compiled in ASIS mode (-gnatct), expansion is skipped,
- -- and the analysis must generate a tree in a form that meets all ASIS
- -- requirements.
-
- -- ASIS must be able to recover the original tree that corresponds to the
- -- source. It relies heavily on Original_Node for this purpose, which as
- -- described in Atree, records the history when a node is rewritten. ASIS
- -- uses Original_Node to recover the original node before the Rewrite.
-
- -- At least in ASIS mode (not really important in non-ASIS mode), when
- -- N1 is rewritten as N2:
-
- -- The subtree rooted by the original node N1 should be fully decorated,
- -- i.e. all semantic fields noted in sinfo.ads should be set properly
- -- and any referenced entities should be complete (with exceptions for
- -- representation information, noted below).
-
- -- For all the direct descendants of N1 (original node) their Parent
- -- links should point not to N1, but to N2 (rewriting node).
-
- -- The Parent links of rewritten nodes (N1 in this example) are set in
- -- some cases (to point to the rewritten parent), but in other cases
- -- they are set to Empty. This needs sorting out ??? It would be much
- -- cleaner if they could always be set in the original node ???
-
- -- There are a few cases when ASIS has to use not the original, but the
- -- rewritten tree structures. This happens when because of some important
- -- technical reasons it is impossible or very hard to have the original
- -- structure properly decorated by semantic information, and the rewritten
- -- structure fully reproduces the original source. Below is the (incomplete
- -- for the moment???) list of such exceptions:
- --
- -- Generic specifications and generic bodies
- -- Function calls that use prefixed notation (Operand.Operation [(...)])
-
- -- Representation Information
-
- -- For the purposes of the data description annex, the representation
- -- information for source declared entities must be complete in the
- -- ASIS tree.
-
- -- This requires that the front end call the back end (gigi/gcc) in
- -- a special "back annotate only" mode to obtain information on layout
- -- from the back end.
-
- -- For the purposes of this special "back annotate only" mode, the
- -- requirements that would normally need to be met to generate code
- -- are relaxed as follows:
-
- -- Anonymous types need not have full representation information (e.g.
- -- sizes need not be set for types where the front end would normally
- -- set the sizes), since anonymous types can be ignored in this mode.
-
- -- In this mode, gigi will see at least fragments of a fully annotated
- -- unexpanded tree. This means that it will encounter nodes it does
- -- not normally handle (such as stubs, task bodies etc). It should
- -- simply ignore these nodes, since they are not relevant to the task
- -- of back annotating representation information.
-
- -- Some other ASIS-specific issues are covered in specific comments in
- -- sections for particular nodes or flags.
-
----------------
-- Ghost Mode --
----------------
-- These three flags are always set by the front end during semantic
-- analysis, on expression nodes that may trigger the corresponding
-- check. The front end then inserts or not the check during expansion. In
- -- particular, these flags should also be correctly set in ASIS mode and
- -- GNATprove mode. As a special case, the front end does not insert a
- -- Do_Division_Check flag on float exponentiation expressions, for the case
- -- where the value is 0.0 and the exponent is negative, although this case
- -- does lead to a division check failure. As another special case,
- -- the front end does not insert a Do_Range_Check on an allocator where
- -- the designated type is scalar, and the designated type is more
- -- constrained than the type of the initialized allocator value or the type
- -- of the default value for an uninitialized allocator.
+ -- particular, these flags should also be correctly set in GNATprove mode.
+ -- As a special case, the front end does not insert a Do_Division_Check
+ -- flag on float exponentiation expressions, for the case where the value
+ -- is 0.0 and the exponent is negative, although this case does lead to a
+ -- division check failure. As another special case, the front end does not
+ -- insert a Do_Range_Check on an allocator where the designated type is
+ -- scalar, and the designated type is more constrained than the type of the
+ -- initialized allocator value or the type of the default value for an
+ -- uninitialized allocator.
-- Note that the expander always takes care of the Do_Range_Check case, so
-- this flag will never be set in the expanded tree passed to the back end.
-- map generic formals to their actuals. If set, the field points either
-- to a copy of a default expression for an actual of mode IN or to a
-- generic_association which is the original parent of the expression or
- -- name appearing in the declaration. This simplifies ASIS and GNATprove
- -- queries.
+ -- name appearing in the declaration. This simplifies GNATprove queries.
-- Corresponding_Integer_Value (Uint4-Sem)
-- This field is set in real literals of fixed-point types (it is not
-- attribute is a function call (possibly dereferenced) that corresponds
-- to the proper expansion of the source indexing operation. Before
-- expansion, the source node is rewritten as the resolved generalized
- -- indexing. In ASIS mode, the expansion does not take place, so that
- -- the source is preserved and properly annotated with types.
+ -- indexing.
-- Generic_Parent (Node5-Sem)
-- Generic_Parent is defined on declaration nodes that are instances. The
-- Label_Construct (Node2-Sem)
-- Used in an N_Implicit_Label_Declaration node. Refers to an N_Label,
-- N_Block_Statement or N_Loop_Statement node to which the label
- -- declaration applies. This attribute is used both in the compiler and
- -- in the implementation of ASIS queries. The field is left empty for the
- -- special labels generated as part of expanding raise statements with a
- -- local exception handler.
+ -- declaration applies. The field is left empty for the special labels
+ -- generated as part of expanding raise statements with a local exception
+ -- handler.
-- Library_Unit (Node4-Sem)
-- In a stub node, Library_Unit points to the compilation unit node of
-- Original_Entity is empty. This field is needed to handle properly
-- named numbers in generic units, where the Associated_Node field
-- interferes with the Entity field, making it impossible to preserve the
- -- original entity at the point of instantiation (ASIS problem).
+ -- original entity at the point of instantiation.
-- Others_Discrete_Choices (List1-Sem)
-- When a case statement or variant is analyzed, the semantic checks
-- values, this expression evaluates to False (zero) if variant is not
-- present, and True (non-zero) if it is present. See unit Repinfo for
-- further details on gigi back annotation. This field is used during
- -- ASIS processing (data decomposition annex) to determine if a field is
- -- present or not.
+ -- back-annotation processing (for -gnatR -gnatc) to determine if a field
+ -- is present or not.
-- Prev_Use_Clause (Node1-Sem)
-- Present in both N_Use_Package_Clause and N_Use_Type_Clause. Used in
-- Was_Expression_Function (Flag18-Sem)
-- Present in N_Subprogram_Body. True if the original source had an
-- N_Expression_Function, which was converted to the N_Subprogram_Body
- -- by Analyze_Expression_Function. This is needed by ASIS to correctly
- -- recreate the expression function (for the instance body) when the
- -- completion of a generic function declaration is an expression
- -- function.
+ -- by Analyze_Expression_Function.
-- Was_Originally_Stub (Flag13-Sem)
-- This flag is set in the node for a proper body that replaces stub.
-- Note: in the list of Discrete_Choices, the tree passed to the back
-- end does not have choice entries corresponding to names of statically
-- predicated subtypes. Such entries are always expanded out to the list
- -- of equivalent values or ranges. The ASIS tree generated in -gnatct
- -- mode also has this expansion, but done with a proper Rewrite call on
- -- the N_Variant node so that ASIS can properly retrieve the original.
+ -- of equivalent values or ranges.
---------------------------------
-- 3.8.1 Discrete Choice List --
-- Note: in the list of Discrete_Choices, the tree passed to the back
-- end does not have choice entries corresponding to names of statically
-- predicated subtypes. Such entries are always expanded out to the list
- -- of equivalent values or ranges. The ASIS tree generated in -gnatct
- -- mode does not have this expansion, and has the original choices.
+ -- of equivalent values or ranges.
-------------------------
-- 5.5 Loop Statement --
-- limited with clause is changed into a normal with clause, because we
-- are not prepared to deal with limited with in the context of Rtsfind.
-- So in this case, the Limited_Present flag will be False in the final
- -- tree. However, we do NOT do this transformation in ASIS mode, so for
- -- ASIS the flag will remain set in this situation.
+ -- tree.
----------------------
-- With_Type clause --
-- Types and subtypes defined in package Standard (in the order in which
-- they appear in the RM, so that the declarations are in the right
- -- order for the purposes of ASIS traversals
+ -- order for the purposes of e.g. ASIS traversals
S_Boolean,
-- create and close routines are elsewhere (in Osint in the compiler, and in
-- the tree read driver for the tree read interface).
+-- Should we remove this package altogether???
+
with Types; use Types;
with System; use System;
Tree_Format_Error : exception;
-- Raised if a format error is detected in the input file
- ASIS_Version_Number : constant := 34;
- -- ASIS Version. This is used to check for consistency between the compiler
- -- used to generate trees and an ASIS application that is reading the
- -- trees. It must be incremented whenever a change is made to the tree
- -- format that would result in the compiler being incompatible with an
- -- older version of ASIS.
- --
- -- 27 Changes in the tree structures for expression functions
- -- 28 Changes in Snames
- -- 29 Changes in Sem_Ch3 (tree copying in case of discriminant constraint
- -- for concurrent types).
- -- 30 Add Check_Float_Overflow boolean to tree file
- -- 31 Remove read/write of Debug_Pragmas_Disabled/Debug_Pragmas_Enabled
- -- 32 Change the way entities are changed through Next_Entity field in
- -- the hierarchy of child units
- -- 33 Add copying subtrees for rewriting infix calls of operator
- -- functions for the corresponding original nodes.
- -- 34 Add read/write of Address_Is_Private, Ignore_Rep_Clauses,
- -- Ignore_Style_Check_Pragmas, Multiple_Unit_Index. Also this
- -- is the version where rep clauses are removed by -gnatI.
-
procedure Tree_Read_Initialize (Desc : File_Descriptor);
-- Called to initialize reading of a tree file. This call must be made
-- before calls to Tree_Read_xx. No calls to Tree_Write_xx are permitted