|
|
DataMuseum.dkPresents historical artifacts from the history of: Rational R1000/400 Tapes |
This is an automatic "excavation" of a thematic subset of
See our Wiki for more about Rational R1000/400 Tapes Excavated with: AutoArchaeologist - Free & Open Source Software. |
top - metrics - downloadIndex: T V
Length: 50629 (0xc5c5)
Types: TextFile
Names: »V«
└─⟦afbc8121e⟧ Bits:30000532 8mm tape, Rational 1000, MC68020_OS2000 7_2_2
└─⟦77aa8350c⟧ »DATA«
└─⟦f794ecd1d⟧
└─⟦this⟧
---------------------------------------------------------------------------
-- Proprietary and confidential information of Rational; use or copying --
-- without express written authorization is strictly prohibited. This --
-- material is protected as an unpublished work under the U.S. Copyright --
-- Act of 1976. Created 1981 - 1987. All rights reserved. --
---------------------------------------------------------------------------
with Action;
with Calendar;
with Device_Independent_Io;
with Directory;
with Job_Segment;
with System;
package Object_Module_Support is
pragma Open_Private_Part;
--
-- This package is provided to assist in the generation and
-- manipulation of Object Modules used by Rational's CDFs.
-- Most users of this package are really concerned with one
-- or more of the packages exported. These are:
--
-- Package Cross_Referencing;
-- Facilities are provided here for generating cross reference
-- information of the form required by the Symbol_Table package.
-- These cross references may be used to provide either diagnostic
-- or statistic information about symbol usage.
--
-- Package Expression_Evaluation;
-- Facilities are provided here for the generation, manipulation,
-- and traversal of expressions. Expressions are used to denote
-- values which cannot be expressed in numeric representation
-- such as the value of an external symbol.
--
-- Package Symbol_Table;
-- The Symbol_Table package is used to map symbolic names to
-- their values. These values are represented as Expressions.
-- Operations are exported to define, reference, manipulate,
-- and traverse the properties of symbols. Symbol_Table also
-- enforces the semantics required for most assembly level
-- programming such as detection of multiply defined symbols,
-- etc.
--
-- Package Object_Module_Format;
-- This package exports the format of object modules via visible
-- types. Additionally, operations are provided to store and
-- retrieve objects of these types in files.
--
type State_Info is private;
type Cross_Reference is private;
type Expression is private;
type Symbol is private;
type Symbol_List is private;
type Expression_Kinds is (Absolute,
Relocatable, Symbolic,
Unary_Op, Binary_Op, Extended,
Characters, Conditional,
On_Free_List);
subtype Address is Long_Integer range 0 .. 16#FFFF_FFFF#;
subtype Natural32 is Long_Integer range 0 .. 16#FFFF_FFFF#;
subtype Section_Number is System.Byte;
subtype Subsection_Number is Natural range 0 .. 16#FFFF#;
subtype Alignment_Info is Natural range 0 .. 16#FFFF#;
type Unary_Operators is (Negate_Op, Complement_Op, Abs_Op);
type Binary_Operators is (Eq_Op, Ne_Op, Gt_Op, Lt_Op, Ge_Op, Le_Op,
And_Op, Or_Op, Xor_Op,
Add_Op, Subtract_Op,
Multiply_Op, Divide_Op, Mod_Op, Rem_Op,
Exponentiate_Op, Lshift_Op, Rshift_Op,
Assert_Op);
subtype Symbol_Name_Length is Positive range 1 .. 32;
type Numbers is (Signed, Unsigned, Number);
--
-- The legal range of a value is based on its kind and the number of bits
-- which are allocated to it as follows:
-- Kind 'First 'Last
-- ________ ________ ________
-- Signed -(2**(N-1)) (2**(N-1)) - 1
-- Unsigned 0 2**N - 1
-- Number -(2**(N-1)) 2**N - 1
--
-- Where N is the number of bits allocated. For N = 8 ( a byte)
-- the ranges are:
--
-- Signed -128 .. 127
-- Unsigned 0 .. 255
-- Number -128 .. 255
--
package Cross_Referencing is
--
-- A general purpose cross referencing facility which is used
-- in association with the Symbol_Table package to produce symbol
-- usage information. Cross-References consist of two portions;
-- the At_Position, and the Is_Definition. At_Position may be
-- either a String or an Integer and objects of either type may
-- be added to any given list of other cross-references using
-- the function Add. The Is_Definition boolean is simply provided
-- as a means to distinguish definition references from usage
-- references and is not interpreted by this package. A list
-- of cross-references may include any number of references
-- which are definitions.
--
function No_References return Cross_Reference;
--
-- This value may be used in most cases when a Cross_Reference
-- parameter is required but no record of the reference is
-- desired.
--
function Make (At_Position : Integer;
Defining_Occurance : Boolean;
State : State_Info) return Cross_Reference;
--
-- Used to generate a cross-reference to a numeric position. This
-- might be used in an assembler to generate cross-references to
-- source line numbers or in conjunction with a Map to create
-- cross-references of symbols to arbitrary items.
--
function Make (At_Position : String;
Defining_Occurance : Boolean;
State : State_Info) return Cross_Reference;
--
-- Used to generate a cross-reference to a string position.
-- This might be used in a linker to generate cross-references
-- to object module names.
--
function Add (Item : Cross_Reference;
To_List : Cross_Reference) return Cross_Reference;
--
-- Item is placed on To_List in some order not defined.
-- Program_Error will be raised if Item is already on To_List.
-- Adding the value returned by No_References to a list will
-- not alter the list.
--
function Next (List : Cross_Reference) return Cross_Reference;
function Done (List : Cross_Reference) return Boolean;
function Value (Item : Cross_Reference) return Integer;
--
-- If the item was not an Integer cross-reference Program_Error
-- will be raised.
--
function Value (Item : Cross_Reference) return String;
--
-- The image is either the exact string passed to Make for a
-- literal cross-reference or the value returned by Integer'Image
-- for a numeric cross-reference. In either case the low bound
-- of the result is 1.
--
function Is_Definition (Item : Cross_Reference) return Boolean;
end Cross_Referencing;
package Expression_Evaluation is
Divide_By_Zero : exception;
Negative_Exponent : exception;
Mod_By_Zero : exception;
Rem_By_Zero : exception;
Assert_Failure : exception;
type Extensions is new System.Byte;
Reserved : constant Extensions := 0;
Section_Size : constant Extensions := 1;
Section_Low_Address : constant Extensions := 2;
Section_High_Address : constant Extensions := 3;
Segment_Size : constant Extensions := 4;
Segment_Low_Address : constant Extensions := 5;
Segment_High_Address : constant Extensions := 6;
Time_Of_Link : constant Extensions := 7;
Linker_1 : constant Extensions := 8;
Linker_2 : constant Extensions := 9;
Linker_3 : constant Extensions := 10;
Linker_4 : constant Extensions := 11;
Segment_Of : constant Extensions := 12;
Toc_Of : constant Extensions := 13;
Section_Offset : constant Extensions := 14;
Segment_Offset : constant Extensions := 15;
Sibling_Count : constant Extensions := 16;
Dead_Code : constant Extensions := 255;
function Image (E : Extensions) return String;
--
-- Extensions are just that; they allow various item of
-- interest to be expressed within expressions. The above
-- extensions are defined as follows:
--
-- Section_Size -
-- Results in the size of the program section in which
-- the associated value is located. If the value is not
-- relocatable the result is zero. Sizes are always in
-- storage units.
--
-- Section_Low_Address -
-- Results in the lowest address of the program section.
--
-- Section_High_Address -
-- Results in the higest address of the program section.
--
-- Segment_Size - Similiar to Section_Size
-- Segment_Low_Address - Similiar to Section_Low_Address
-- Segment_High_Address - Similiar to Section_High_Address
--
-- Time_Of_Link -
-- The associated value determines the value of these
-- expressions. The associated value must be absolute
-- or is presumed to be zero.
--
-- 0 - A 32 bit number which indicates the date of linking.
-- 1 signifies 01-Jan-1901.
-- 1 - A 32 bit number which indicates the time of linking.
-- This is the time since midnight in units of 1/16384
-- seconds.
--
-- Linker1 - Linker4
-- Reserved for internal use by the linker. These extensions
-- must never be stored in object modules.
--
-- Segment_Of -
-- Results in the segment number assigned by the linker
-- to the relocatable section of the associated value.
--
-- Toc_of -
-- Similar in spirit to section_low_address; results in the
-- base address of the TOC containing the symbol; peculiar
-- to the RS6000 and AIX.
--
-- Section_Offset -
-- Offset from the beginning of the enclosing section of the
-- referenced relocatable expression.
--
-- Segment_Offset -
-- Offset from the beginning of the enclosing segment of the
-- referenced relocatable expression.
--
-- Dead_Code -
-- Usually found only in debug tables of linked programs,
-- this value indicates that the real value cannot be
-- obtained because it designated object which was deleted
-- via Link-Time-Dead-Code-Elimination. The value is not
-- defined.
--
-- These conventions are followed by Rational produced software
-- through careful use of the generic Simplify procedure provided
-- below. Future use of these and other extension values cannot
-- be guaranteed. Contact your Rational representative if you
-- encounter problems with Extended expressions.
--
function Make (N : Long_Integer; State : State_Info) return Expression;
function Make (S : String; State : State_Info) return Expression;
function Make (Section : Section_Number;
Subsection : Subsection_Number;
Offset : Long_Integer;
State : State_Info) return Expression;
function Make (Extension : Extensions;
Value : Expression) return Expression;
function Make (S : Symbol;
See_Through : Boolean := True) return Expression;
--
-- Used to construct an expression with the corresponding
-- value. In the last case, if Symbol_Table.Is_Defined (S) is True
-- and See_Through is True then the result of Make is the same as the
-- result of Symbol_Table.Value (S). In either case, no sharing of
-- subexpressions occurs between the in and out parameters,
-- thus resulting expression may be transformed freely
-- with no side effects whatsoever (i.e., Make_Copy => True where
-- applicable).
--
function Copy (E : Expression) return Expression;
--
-- A complete copy of the entire expression is returned.
--
function Evaluate (L, R : Expression;
Op : Binary_Operators) return Expression;
--
-- In general a new expression is generated of the form:
--
-- Op
-- /\
-- / \
-- L R
--
-- However if the form of the operands is such that the result
-- may be calculated then a simpler result may be returned.
--
-- For example:
--
-- Evalute (L => Make (3), R => Make (4), Op => Plus_Op)
--
-- will return the same values as returned by:
--
-- Make (7)
--
function Evaluate (A : Expression;
Op : Unary_Operators) return Expression;
--
-- Similar to the above form for Binary_Operators.
--
function Evaluate (Cond : Expression; L : Expression; R : Expression)
return Expression;
-- returns an expression which evaluates to L if Cond is true (not 0)
-- and to R if it is false (0).
--
-- In general returns an expr of the form
-- if (cond) then L else R
--
-- If cond evaluates to a constant then a simpler expression (either
-- L or R) may be returned.
--
function Is_Constant (E : Expression) return Boolean;
--
-- Returns true IFF the value designated by E contains no
-- symbolic or relocatable values and no operators. No
-- attempt is made to simplify the expression designated by
-- E so the results are not always what you might expect.
--
function Value (E : Expression;
Consume : Boolean) return Long_Integer;
--
-- Returns the value of an absolute expression or the offset
-- part of a relocatable expression. If the expression E is
-- neither absolute nor relocatable Program_Error is raised.
--
function Unsigned_Value (E : Expression;
Consume : Boolean) return Long_Integer;
--
-- Has the same semantics as Value except that the result is
-- returned as an unsigned value. That is to say that the value
-- returned by:
-- Unsigned_Value (Make (-1))
-- will be 16#0000_0000_FFFF_FFFF#.
--
type Expression_Status is (Simple, Simple_Relocatable,
Complex_Relocatable, Extended, Undefined);
procedure Simplify (E : in out Expression;
S : out Expression_Status;
U : out Symbol_List);
--
-- Used to reduce the complexity of expressions. The algorithim
-- works bottom up and results in a possibly smaller expression
-- which has the same value. The Status applies to the most
-- complex subexpression. The list U designates all of the
-- undefined symbols on which this expression depends.
--
generic
with procedure Extension_Simplifier (E : in out Expression);
procedure Simplify_Extended (E : in out Expression;
S : out Expression_Status;
U : out Symbol_List);
--
-- Like Simplify but calls Extension_Simplifier passing the
-- extension. Extension Simplifier may transform the tree
-- or do nothing; the subtree of the extension tree will have
-- been previously Simplified. Extension_Simplifier should be
-- certain to Free any subtrees which are not returned.
--
procedure Free_Single_Node (E : Expression);
--
-- The expression E is placed into the free list for further
-- reuse. The subexpressions of E are unaffected. Use this
-- with care.
--
procedure Free (E : Expression);
--
-- The expression E and all of its subexpressions are placed into
-- the free list for further reuse. Use this with extreme care.
--
function Null_Expression return Expression;
procedure Check_Fit (Kind : Numbers;
Bit_Length : Natural;
Value : Long_Integer;
Fits : out Boolean);
function Kind (E : Expression) return Expression_Kinds;
function Section (E : Expression) return Section_Number;
function Subsection (E : Expression) return Subsection_Number;
function Relocatable_Offset (E : Expression) return Long_Integer;
function Referenced_Symbol (E : Expression) return Symbol;
function Unary_Operator (E : Expression) return Unary_Operators;
function Unary_Operand (E : Expression) return Expression;
function Binary_Operator (E : Expression) return Binary_Operators;
function Left_Operand (E : Expression) return Expression;
function Right_Operand (E : Expression) return Expression;
function Condition (E : Expression) return Expression;
function Then_Part (E : Expression) return Expression;
function Else_Part (E : Expression) return Expression;
function Extension (E : Expression) return Extensions;
function Extension_Value (E : Expression) return Expression;
function Characters (E : Expression) return String;
function Image (E : Expression) return String;
--
-- May be used to traverse expressions. Constraint_Error (Variant)
-- will be raised if an inappropriate selector is applied to a
-- given expression.
--
function Explanation (State : State_Info) return Expression;
--
-- If the first argument to ASSERT_OP evaluates to false (i.e., 0)
-- during simplification or evaluation, the second argument
-- (presumably the explanation) is cached in the state variable and
-- ASSERT_FAILURE raised.
--
type Expression_Seq is array (Positive range <>) of Expression;
type Expression_Sequence is access Expression_Seq;
pragma Segmented_Heap (Expression_Sequence);
type Expression_List is private;
function Empty_List return Expression_List;
procedure Initialize (List : out Expression_List);
-- Must be called prior to any other actions
function Length (List : Expression_List) return Natural;
-- Takes linear time
procedure Append (E : Expression;
To_List : in out Expression_List);
procedure Prepend (E : Expression;
To_List : in out Expression_List);
-- Perform the obvious catenation operations
procedure Reset (List : in out Expression_List);
procedure Next (List : in out Expression_List);
function Value (List : Expression_List) return Expression;
function Done (List : Expression_List) return Boolean;
-- Perform the obvious traversal operations
procedure Set_Value (List : Expression_List; Item : Expression);
-- Alters the value of the current list element
procedure Release (List : in out Expression_List;
State : State_Info);
-- Releases all storage related to the list but not the
-- designated Expressions.
private
type List_Element;
type E_List_Element is access List_Element;
pragma Segmented_Heap (E_List_Element);
type Expression_List is
record
Head : E_List_Element;
Tail : E_List_Element;
Iter : E_List_Element;
end record;
end Expression_Evaluation;
package Object_Module_Format is
------------------------------------------------------------
--
-- This package allows one to read and write object modules
-- and linked programs. All information contained within
-- these files should be accessed through this package. All
-- types are visible to allow maximum flexibility when
-- managing object. In particular the cross-assemblers,
-- linker, and load module conversion programs all deal with
-- certain conventions based upon these definitions. Be
-- sure you understand those tools before changing this
-- interface.
--
------------------------------------------------------------
type Object_Module_Version is private;
type Targets is new System.Byte;
M68000 : constant Targets := 0;
Milstd1750a : constant Targets := 1;
Ibm370 : constant Targets := 2;
Intel_X86 : constant Targets := 3;
Vax_Vms : constant Targets := 4;
Ibm_6000 : constant Targets := 5;
function Image (Target : Targets) return String;
subtype Machine_Id is Long_Integer range 0 .. 16#FFFF_FFFF#;
------------------------------------------------------------
--
-- Each entity has a header. All text strings are for
-- informational purposes only. Sections may be used
-- to indicate orthoganal memory spaces in the case of
-- targets with physically distinct code and data.
--
-- Modules count is the count of object modules linked in
-- to form this object module - defaults to 1 when a new object
-- module is created. The linker sets it correctly when it links
-- modules.
--
------------------------------------------------------------
type Object_Module_Header is
record
Name_Length : Natural;
Name : String (1 .. 128);
Target : Targets;
Has_Errors : Boolean;
Date : Calendar.Time;
Rev_Length : Natural;
Rev : String (1 .. 128);
Produced_Length : Natural;
Produced_By : String (1 .. 128);
Module_Machine_Id : Machine_Id;
Module_Instance_Name : Natural;
Globals : Natural;
Externals : Natural;
Has_Starting_Address : Boolean;
Starting_Address : Expression;
Modules_Count : Natural := 1;
end record;
------------------------------------------------------------
--
-- Each section is comprised of one or more subsections.
-- Within a given section, a subsection may be deleted as
-- long as the relative ordering of the other subsections is
-- maintained.
--
------------------------------------------------------------
type Subsection_Info (Name_Length : Natural := 0) is
record
Name : String (1 .. Name_Length);
Align_Div : Alignment_Info;
Align_Mod : Alignment_Info;
end record;
type Subsection_Info_Ptr is access Subsection_Info;
pragma Segmented_Heap (Subsection_Info_Ptr);
type Subsection_Information is
array (Subsection_Number range <>) of Subsection_Info_Ptr;
------------------------------------------------------------
--
-- Each Object_Module is comprised of one or more Sections.
-- A section simply designates a vector of bytes which are
-- to be maintained contiguously throughout the program generation
-- process. The vector of bytes designated by a given program
-- section within a given module is described by the Section_Info
-- record.
--
-- The MISC field of section_info can be used to 'tag' a
-- section, thereby possibly aiding the linker & object converter.
--
-- Note: Only the lower 32 bits of MISC are stored in the
-- object file (as a signed int). The upper 32 bits are
-- available for local use, and are not stored.
--
------------------------------------------------------------
type Section_Info (Last_Subsection : Subsection_Number := 0) is
record
Name : String (Symbol_Name_Length);
Name_Length : Symbol_Name_Length;
Is_Code : Boolean;
Is_Readwrite : Boolean;
Is_Concatenate : Boolean;
Is_Absolute : Boolean;
Base_Rel_Labels : Boolean;
Pool : Boolean;
Starts_At : Address;
Align_Div : Alignment_Info;
Align_Mod : Alignment_Info;
Fixup_Count : Natural;
Byte_Count : Natural32;
Misc : Long_Integer;
Subsection_Dictionary :
Subsection_Information (0 .. Last_Subsection);
end record;
type Section_Info_Ptr is access Section_Info;
pragma Segmented_Heap (Section_Info_Ptr);
type Section_Information is
array (Section_Number range <>) of Section_Info_Ptr;
------------------------------------------------------------
--
-- Normalization is performed by the assemblers during the
-- second pass (back-patching) and by the linker. These
-- indications allow more semantic content to be expressed
-- than the underlying expression tree contains.
--
-- No_Normalization - Just what it means.
--
-- Normalize_By_One - Used to encode N bit fields which
-- represent the values 1..2**N. If
-- the target is 1750A or 370 the
-- encoded value is one less than then
-- value supplied; if the target is
-- MC68000 the encoded value is the
-- supplied value MOD 2**N.
--
-- M68000_Short_Branch -
-- Used for conditional branches in
-- which the branch displacement may
-- not be zero.
--
-- Align_On_Longword -
-- Used to assure that the expression
-- resolves to a longword-aligned value.
--
------------------------------------------------------------
type Normalization is new System.Byte;
No_Normalization : constant Normalization := 0;
Normalize_By_One : constant Normalization := 1;
M68000_Short_Branch : constant Normalization := 2;
Align_On_Longword : constant Normalization := 3;
function Image (N : Normalization) return String;
------------------------------------------------------------
--
-- Fixups are the mechanism which describe how to modify
-- a given program section's contents to incorporate values
-- which could not be computed at the time the object module
-- was initially generated. These values include symbolic
-- references to external symbols and references to relocatable
-- values at assembly time.
--
-- A fixup consists of two portions: the destination and the
-- value. The destination is comprised of three portions:
-- 1.) The byte displacement from the beginning of the
-- program section.
-- 2.) The Bit offset from that byte.
-- 3.) The Bit length of the field affected by the fixup.
-- The value of fixup is designated by an Expression.
--
-- It is usually the responsiblity of the linker to resolve
-- the values designated by a given Fixup and update the
-- destination with that value.
--
-- The Is_Benign bit indicates that, for the purpose of
-- Link-Time-Dead-Code-Elimination, the given fixup should
-- not be considered to be a reference to the value.
--
-- The order of a list of fixups associated with a program
-- section will be in ascending order by Displacement. This
-- ordering is insured during the processing done at the time
-- a module is stored with one of the write_module subprograms.
-- Furthermore, the Displacement and Bit_Offset fields are
-- normalized so that Bit_Offset is always in the range 0..7.
--
-- Fixups of zero length are permissible and are used to indicate
-- various information about the destination/value pair.
--
------------------------------------------------------------
type Fixup;
type Fixup_Ptr is access Fixup;
pragma Segmented_Heap (Fixup_Ptr);
type Fixup is
record
Displacement : Address;
Subsection : Subsection_Number;
Bit_Offset : System.Byte;
Bit_Length : System.Byte;
Normalize : Normalization;
Kind : Numbers;
Is_Benign : Boolean;
Value : Expression;
Link : Fixup_Ptr;
end record;
type Fixup_Information is array (Section_Number range <>) of Fixup_Ptr;
------------------------------------------------------------
--
-- All data is represented as byte strings. A list of data may
-- have holes. This notion is captured by a data record with
-- Max_Length < 0 and Length indicating the size of the hole.
--
-- A hole is used to explicitly represent uninitialized data.
--
-- The Length field is the actual count of used bytes and may
-- exceed Max_Length by one.
--
------------------------------------------------------------
type Data (Max_Length : Integer := 255);
type Data_Ptr is access Data;
pragma Segmented_Heap (Data_Ptr);
type Data (Max_Length : Integer := 255) is
record
Length : Natural32;
Starting_Offset : Address;
Subsection : Subsection_Number;
Data : System.Byte_String (0 .. Max_Length);
Link : Data_Ptr;
end record;
type Data_Information is array (Section_Number range <>) of Data_Ptr;
------------------------------------------------------------
--
-- A real object module
--
------------------------------------------------------------
type Object_Module_Information (Sections : Section_Number) is
record
Version : Object_Module_Version;
Header : Object_Module_Header;
Section_Dictionary : Section_Information (1 .. Sections);
Globals : Symbol_List;
Externals : Symbol_List;
Data : Data_Information (1 .. Sections);
Fixups : Fixup_Information (1 .. Sections);
end record;
type Object_Module is access Object_Module_Information;
pragma Segmented_Heap (Object_Module);
Object_Module_Read_Error : exception;
Object_Module_Write_Error : exception;
Object_Module_Version_Error : exception;
function Current_Object_Module_Version return Object_Module_Version;
generic
with function External (Module_Name : in String;
Sym_Name : in String;
Misc : in Long_Integer) return Symbol;
with function Global (Module_Name : in String;
Sym_Name : in String;
Value : in Expression;
Misc : in Long_Integer) return Symbol;
function Read_Module (Channel : Device_Independent_Io.File_Type;
State : State_Info) return Object_Module;
generic
with function External (Module_Name : in String;
Sym_Name : in String;
Misc : in Long_Integer) return Symbol;
with function Global (Module_Name : in String;
Sym_Name : in String;
Value : in Expression;
Misc : in Long_Integer) return Symbol;
function Read_Object_Module (File : Directory.Version;
Action_Id : Action.Id := Action.Null_Id;
State : State_Info) return Object_Module;
function Read_Just_The_Version_Number
(File : Directory.Version;
Action_Id : Action.Id := Action.Null_Id;
State : State_Info) return Object_Module_Version;
--
-- These generic functions are used to retrieve the contents
-- of an object module.
--
-- The generic formal subprograms are expected to be used
-- by the client to add the encountered global/externals to
-- the symbol table as required.
--
-- For externals, the object module file contains not only the
-- name of the symbol, but also a miscellaneous field defined
-- by the object writer.
--
-- Similarly, for globals, the object module file contains not
-- only the name of the symbol, but the defined value, and again
-- a miscellaneous field defined by the object writer.
--
-- Cross references should added for both global and external
-- symbols. In each case the literal form of a reference should be
-- generated with Module.Header.Name used as the At_Position
-- of the reference. Global symbols should be considered as the
-- Defining_Occurance.
--
-- If the file contents are of a revision which is no longer
-- supported the exception Object_Module_Version_Error is
-- raised; any other error will result in Object_Module_Read_Error.
-- Attempts to retrieve modules which were not produced with
-- one of the write operations provided below may produce either
-- exception or may succeed. In any case use of such modules
-- is not recommended.
--
type Symbol_Name_List_Element (Length : Symbol_Name_Length);
type Symbol_Name_List is access Symbol_Name_List_Element;
pragma Segmented_Heap (Symbol_Name_List);
type Symbol_Name_List_Element (Length : Symbol_Name_Length) is
record
Name : String (1 .. Length);
Misc : Long_Integer;
Link : Symbol_Name_List;
end record;
function Read_Object_Module_Globals
(File : Directory.Version;
Action_Id : Action.Id := Action.Null_Id;
State : State_Info) return Symbol_Name_List;
--
-- These functions may be used to obtain a list of symbols which
-- are exported by the designated object module. Use of these
-- operations does not affect the Symbol_Table in any way.
--
procedure Write_Object_Module (Filename : in String;
Action_Id : Action.Id := Action.Null_Id;
Module : Object_Module);
procedure Write_Object_Module (File : Directory.Version;
Action_Id : Action.Id := Action.Null_Id;
Module : Object_Module);
--
-- The object module Module is stored in the designated file. Any
-- errors encountered result in Object_Module_Write_Error. These
-- usually are associated with:
--
-- File access errors while opening or writing to the
-- designated file.
--
-- Malformed object modules such as modules with symbols
-- mentioned in the global symbol list which have not been
-- defined or with fixups which designate expressions which
-- reference symbols which are not mentioned in the external
-- symbol list.
--
function Is_Debug_Table_Section (S : Section_Info_Ptr) return Boolean;
-- Returns true if this is a section for the debug table.
-- A section is a debug table section if it's name begins with "debug".
procedure Write_Debug_Tables (File : Directory.Version;
Action_Id : Action.Id := Action.Null_Id;
Module : Object_Module);
-- writes out only the debug table portion of the object module.
-- WARNING: This changes the in memory image of the object module.
generic
with procedure Put (S : String; Nl : Boolean := True);
procedure Display (Module : Object_Module;
Display_Header : Boolean := True;
Display_Section_Dictionary : Boolean := True;
Display_Global_Symbols : Boolean := True;
Display_External_Symbols : Boolean := True;
Display_Data : Boolean := False;
Display_Fixups : Boolean := False);
procedure Normalize (Method : Normalization;
Target : Targets;
Bit_Length : Natural;
Value : in out Long_Integer;
Legal : out Boolean);
function Bytes_Per_Addressing_Unit (Target : Targets) return Positive;
function Bytes_Are_Backwards (Target : Targets) return Boolean;
function Image (V : in Object_Module_Version) return String;
private
type Object_Module_Version is new System.Byte;
end Object_Module_Format;
package Symbol_Table is
type Symbol_Status is (Successful,
Multiply_Defined,
Was_Temporary,
Had_References,
Is_External,
Is_Circular);
--
-- The status of attempts to Define a symbol. The meanings are
-- as follows:
-- Successful - The operation was successful.
-- Multiply_Defined- The symbol was already defined.
-- Was_Temporary - The symbol was previously defined as
-- temporary but is now being defined as
-- permanent.
-- Had_References - The symbol was previously undefined but
-- had references and is now being defined
-- as a temporary symbol.
-- Is_External - The symbol has been referenced and has
-- been made External. External symbols
-- may not be Defined.
-- Is_Circular - The Value used in the definition of
-- the symbol references the symbol itself.
procedure Define (Spelling : in String;
Value : in Expression;
Is_Temporary : in Boolean;
Xref : in Cross_Reference;
Status : out Symbol_Status);
procedure Define (Spelling : in String;
Value : in Expression;
Is_Temporary : in Boolean;
Xref : in Cross_Reference;
Sym : out Symbol;
Status : out Symbol_Status);
--
-- Associates the value with the symbol. The symbol table entry is
-- created if it did not already exist. If the returned status is
-- other than Successful, the call to Define has no effect.
--
function Reference (Spelling : in String;
Xref : Cross_Reference;
State : State_Info) return Symbol;
--
-- Creates a reference to the symbol. The symbol table entry is
-- created if the designated symbol has been neither Defined nor
-- Referenced.
--
function Lookup
(Spelling : in String; State : State_Info) return Symbol;
--
-- See if an entry exists already for this symbol. If not,
-- null_symbol will be returned.
--
function Needs_Definition (Spelling : in String;
State : State_Info) return Boolean;
--
-- Returns true iff the symbol has been Referenced but not
-- Defined.
--
procedure New_Local_Symbol_Table (Too_Many : out Boolean;
State : State_Info);
--
-- Conceptually flushes all local symbols from the symbol table.
-- A limit of about 2**16 symbol tables may exist before Too_Many
-- will be returned true.
--
procedure Make_External (S : Symbol);
--
-- The symbol is made External and is added to the Symbol_List
-- returned by Externals. Program_Error is raised if the
-- symbol is:
--
-- a local symbol
-- a temporary symbol
-- has been Made_Global
-- has been previously Defined
--
procedure Make_Global (S : Symbol);
--
-- The symbol is made Global and is added to the Symbol_List
-- returned by Globals. Program_Error is raised if the
-- symbol is:
--
-- a local symbol
-- a temporary symbol
-- has been Made_External
-- has been previously Defined
--
function Globals (State : State_Info) return Symbol_List;
--
-- Returns a list of all symbols which have been made global.
--
function Global_Count (State : State_Info) return Natural;
--
-- Returns the number of symbols which have been made global.
--
function Externals (State : State_Info) return Symbol_List;
--
-- Returns a list of all symbols which have been made external.
--
function External_Count (State : State_Info) return Natural;
--
-- Returns the number of symbols which have been made external.
--
function Value (S : Symbol; Make_Copy : Boolean) return Expression;
--
-- Returns either the actual expression denoted by the symbol
-- or a complete copy of the expression. If the symbol has not
-- been Defined a Null_Expression is returned.
--
procedure Set_Misc (S : Symbol; N : Long_Integer);
function Get_Misc (S : Symbol) return Long_Integer;
--
-- Allow storage and retrieval of user information for each
-- symbol. This field is initialized to zero when the symbol
-- is created and is not otherwise modified internally.
--
-- The lower 32 bits of this value is stored for globals ONLY.
--
function Is_Defined (S : Symbol) return Boolean;
function Is_External (S : Symbol) return Boolean;
function Is_Global (S : Symbol) return Boolean;
function Is_Temporary (S : Symbol) return Boolean;
function Is_Local (S : Symbol) return Boolean;
function Name (S : Symbol) return String;
function Cross_References (S : Symbol) return Cross_Reference;
--
-- Various selectors for querying attributes of Symbols.
--
procedure Force_Value (S : Symbol; Value : Expression);
--
-- If the symbol has been Defined the value associated is freed.
-- The Value provided is associated with the symbol and the
-- symbol becomes Defined. No cross reference is generated and the
-- previous cross references associated with the symbol are not
-- altered.
--
type Global_Status is (Legal, Is_Undefined, References_Undefineds);
--
-- Status values returned by Check_Global have the following
-- meaning:
--
-- Legal - The symbol is an acceptable Global
-- symbol.
-- Is_Undefined - The symbol has never been defined.
-- References_Undefineds- The symbol has been defined in terms
-- of other symbols which are undefined.
--
procedure Check_Global (G : Symbol;
S : out Global_Status;
U : out Symbol_List);
--
-- Checks a given symbol to insure that it conforms to the
-- requirements of a global symbol. This procedure should be
-- called for each symbol in the Symbol_List returned by
-- Globals prior to construction of an object module. The list
-- U includes all of the undefined or external symbols referenced
-- by the value of G. It is an empty list if S is either Legal
-- or Is_Undefined.
--
function Is_Null (Sym : in Symbol) return Boolean;
function Null_Symbol return Symbol;
function Null_List return Symbol_List;
procedure Add_To_List (S : in out Symbol_List;
Sym : Symbol);
function Get_Symbol (S : Symbol_List) return Symbol;
function Done (S : Symbol_List) return Boolean;
function Next (S : Symbol_List;
Consume : Boolean) return Symbol_List;
procedure Free (S : Symbol_List);
--
-- Each perform the obvious.
-- Add_To_List adds the given symbol to the list in some order
-- not defined.
-- Free deallocates the storage associated with a single list
-- element, not the entire list.
function First (State : State_Info) return Symbol;
function Next (S : Symbol) return Symbol;
function Done (S : Symbol) return Boolean;
--
-- Symbol Table Traversal
--
end Symbol_Table;
function Initialize
(Heap : System.Segment := Job_Segment.Get) return State_Info;
--
-- Initialize create and initialize the state variable. This
-- package has no internal state and is completely reentrant.
--
generic
with procedure Put (S : String);
procedure Statistics (State : State_Info);
--
-- Displays statisitcs about the number of allocations, the
-- number of free elements, and the size of various types of
-- objects. Objects include Expressions, Symbols, and Symbol_Lists.
--
private
type State_Information;
type Xref_Kind is (Numeric, Literal);
subtype Xref_Literal_Index is Natural range 0 .. 1024;
type Xref_Info (Kind : Xref_Kind; Lit_Size : Xref_Literal_Index);
type Expression_Node;
type Symbol_Table_Entry (Name_Length : Symbol_Name_Length);
type Symbol_List_Element;
type State_Info is access State_Information;
type Cross_Reference is access Xref_Info;
type Expression is access Expression_Node;
type Symbol is access Symbol_Table_Entry;
type Symbol_List is access Symbol_List_Element;
pragma Segmented_Heap (State_Info);
pragma Segmented_Heap (Cross_Reference);
pragma Segmented_Heap (Expression);
pragma Segmented_Heap (Symbol);
pragma Segmented_Heap (Symbol_List);
end Object_Module_Support;