|
|
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: 11567 (0x2d2f)
Types: TextFile
Names: »V«
└─⟦149519bd4⟧ Bits:30000546 8mm tape, Rational 1000, !projects 93-07-13
└─⟦124ff5788⟧ »DATA«
└─⟦this⟧
└─⟦f64eaa120⟧ Bits:30000752 8mm tape, Rational 1000, !projects 93 02 16
└─⟦6f12a12be⟧ »DATA«
└─⟦this⟧
WITH Calendar;
WITH Byte_Defs;
WITH Interchange_Defs;
PACKAGE Interchange IS
-- This package defines a collection of types for data interchange.
-- Each type has some local representation, which is dependent on
-- the characteristics of the local architecture/compiler; and also
-- an interchange representation (a canonical byte sequence), which
-- is machine-independent. This package provides operations for
-- converting between the local and interchange representations.
-- The types provided are similar to types in the Ada predefined
-- language environment, i.e. packages STANDARD and CALENDAR.
-- The conversion operations are generic on a procedural byte
-- stream, so that they may be used on a variety of interchange
-- media, e.g. communication channels, tapes, and disks.
-- The algorithms for conversion to and from the interchange form
-- are extensible to any Ada type except access values and task
-- types. The rules for forming new type conversion algorithms
-- are given below.
-- The interchange representation does not carry type information,
-- i.e. the types of the interchanged data must be known a priori
-- in order to convert them back to the local representation.
-- The interchange representation mostly follows the rules of
-- Courier, the Xerox System Integration Standard for a remote
-- procedure call protocol. In particular, all interchange
-- values are a multiple of two bytes (16 bits) in length.
Constraint_Error : EXCEPTION;
-- Raised when an interchange conversion procedure encounters
-- an out-of-range value.
SUBTYPE Byte IS Byte_Defs.Byte;
SUBTYPE Byte_String IS Byte_Defs.Byte_String;
TYPE Short_Integer IS RANGE -(2 ** 14) - (2 ** 14) ..
(2 ** 14) + ((2 ** 14) - 1);
SUBTYPE Short_Natural IS Short_Integer RANGE 0 .. Short_Integer'Last;
SUBTYPE Short_Positive IS Short_Integer RANGE 1 .. Short_Integer'Last;
TYPE Integer IS NEW Interchange_Defs.Longest_Integer
RANGE -(2 ** 30) - (2 ** 30) ..
(2 ** 30) + ((2 ** 30) - 1);
SUBTYPE Natural IS Integer RANGE 0 .. Integer'Last;
SUBTYPE Positive IS Integer RANGE 1 .. Integer'Last;
TYPE Long_Integer IS NEW Interchange_Defs.Longest_Integer;
SUBTYPE Long_Natural IS Long_Integer RANGE 0 .. Long_Integer'Last;
SUBTYPE Long_Positive IS Long_Integer RANGE 1 .. Long_Integer'Last;
-- The range of long_integer is machine-dependent. Each
-- implementation should choose the largest possible range.
-- The interchange form (which is machine-independent),
-- can express values up to +- 2 ** (2 ** 16 - 1) - 1.
TYPE Float IS NEW Interchange_Defs.Float;
TYPE Long_Float IS NEW Interchange_Defs.Long_Float;
SUBTYPE Nanosecond_Count IS Interchange.Natural RANGE 0 .. 10 ** 9 - 1;
TYPE Duration IS
RECORD
Seconds : Interchange.Integer;
Nanoseconds : Interchange.Nanosecond_Count;
END RECORD;
FUNCTION Convert (X : Standard.Duration) RETURN Interchange.Duration;
FUNCTION Convert (X : Interchange.Duration) RETURN Standard.Duration;
SUBTYPE Year_Number IS Interchange.Short_Integer;
SUBTYPE Month_Number IS Interchange.Short_Integer RANGE 1 .. 12;
SUBTYPE Day_Number IS Interchange.Short_Integer RANGE 1 .. 31;
SUBTYPE Day_Duration IS Interchange.Duration;
TYPE Time IS
RECORD
Year : Year_Number;
Month : Month_Number;
Day : Day_Number;
Seconds : Day_Duration;
END RECORD;
FUNCTION Convert (X : Calendar.Time) RETURN Interchange.Time;
FUNCTION Convert (X : Interchange.Time) RETURN Calendar.Time;
GENERIC
TYPE Stream_Id IS LIMITED PRIVATE;
-- Identifies an interchange medium.
WITH PROCEDURE Put (Into : Stream_Id; Data : Byte_String) IS <>;
-- Put the given DATA into the given stream.
WITH PROCEDURE Get (From : Stream_Id; Data : OUT Byte_String) IS <>;
-- Get the first DATA'LENGTH bytes from the given stream.
-- The interchange medium must not lose bytes, and must
-- preserve byte ordering. Also, it must fragment and
-- reassemble. That is, the sequence of calls:
--
-- PUT (STREAM, DATA (1 .. N));
-- PUT (STREAM, DATA (N + 1 .. LAST));
--
-- must have the same effect as the single call
--
-- PUT (STREAM, DATA (1 .. LAST));
--
-- for all values of N in the range 1 .. LAST.
-- Similarly, the sequence of calls
--
-- GET (STREAM, DATA (1 .. N));
-- GET (STREAM, DATA (N + 1 .. LAST));
--
-- must have the same effect as the single call
--
-- GET (STREAM, DATA (1 .. LAST));
--
-- for all values of N in the range 1 .. LAST.
-- Note that a STREAM_ID is passed as an 'in' parameter.
-- This simplifies the interchange of unconstrained types
-- (since they can be returned as the value of a function),
-- but may require the instantiator to invent a level of
-- indirection.
PACKAGE Operations IS
-- Given a facility for interchanging bytes, this package
-- provides a facility for interchanging values of other
-- types. For each type, PUT and GET operations are
-- defined: PUT converts any value to a sequence of
-- bytes, and GET reconstructs the original value.
-- Exceptions raised by the primitive operations are
-- propagated to the caller of the derived operations.
-- A short_integer is represented in 16-bit two's complement,
-- split into two bytes, most significant byte first.
PROCEDURE Put (Into : Stream_Id; Data : Interchange.Short_Integer);
PROCEDURE Get (From : Stream_Id; Data : OUT Interchange.Short_Integer);
-- An integer is represented in 32-bit two's complement,
-- split into four bytes, most significant byte first.
PROCEDURE Put (Into : Stream_Id; Data : Interchange.Integer);
PROCEDURE Get (From : Stream_Id; Data : OUT Interchange.Integer);
-- A long_integer is represented in arbitrary
-- precision two's complement, that is, the two's
-- complement representation, split into as many bytes as
-- needed, represented as a BYTE_STRING, most significant
-- byte first. See the Put & Get routines for
-- BYTE_STRINGs, below.
-- GET may raise CONSTRAINT_ERROR if the local implementation
-- of long_integer cannot represent a gotten value.
PROCEDURE Put (Into : Stream_Id; Data : Interchange.Long_Integer);
PROCEDURE Get (From : Stream_Id; Data : OUT Interchange.Long_Integer);
-- Floating point types are represented in IEEE format.
-- A Float (single-precision) occupies 4 bytes, and
-- a Long_Float (double-precision) occupies 8 bytes.
-- The sign bit goes in the MSB of the first byte, followed by
-- the exponent, followed by the fraction, with the LSB of the
-- fraction going in the LSB of the last byte.
PROCEDURE Put (Into : Stream_Id; Data : Interchange.Float);
PROCEDURE Get (From : Stream_Id; Data : OUT Interchange.Float);
PROCEDURE Put (Into : Stream_Id; Data : Interchange.Long_Float);
PROCEDURE Get (From : Stream_Id; Data : OUT Interchange.Long_Float);
-- The types for time are represented using the rules
-- for records, described below.
PROCEDURE Put (Into : Stream_Id; Data : Interchange.Time);
PROCEDURE Get (From : Stream_Id; Data : OUT Interchange.Time);
PROCEDURE Put (Into : Stream_Id; Data : Interchange.Duration);
PROCEDURE Get (From : Stream_Id; Data : OUT Interchange.Duration);
-- A Boolean is represented by the value 0 for false and
-- 1 for true, converted to an interchange.short_natural.
PROCEDURE Put (Into : Stream_Id; Data : Standard.Boolean);
PROCEDURE Get (From : Stream_Id; Data : OUT Standard.Boolean);
-- A BYTE is represented by its 'pos, converted to an
-- interchange.short_natural (or, if you like, padded
-- on the left with a 0 byte).
PROCEDURE Put (Into : Stream_Id; Data : Byte);
PROCEDURE Get (From : Stream_Id; Data : OUT Byte);
-- A CHARACTER is represented like a byte.
PROCEDURE Put (Into : Stream_Id; Data : Standard.Character);
PROCEDURE Get (From : Stream_Id; Data : OUT Standard.Character);
-- The GET operation for an unconstrained type is a function,
-- rather than a procedure. This is because Ada rules don't
-- allow the caller of GET to declare an unconstrained
-- variable of the type. Casting GET as a function allows
-- the caller to declare a constant of the type, and
-- initialize it with the value of the GET function, e.g.:
--
-- declare
-- S : constant STRING := GET_STRING (STREAM);
-- begin
-- ...
-- A STRING is represented by its 'LENGTH, followed by the
-- 'POS of each of its elements (in ascending index order),
-- followed by a 0 byte if required to pad the whole thing to
-- an even number of bytes. The 'LENGTH is represented as a
-- INTERCHANGE.NATURAL. Each element is represented as one
-- byte. This representation loses the 'FIRST of the STRING,
-- much as does slice assignment.
PROCEDURE Put_String (Into : Stream_Id; Data : Standard.String);
FUNCTION Get_String (From : Stream_Id) RETURN Standard.String;
-- A BYTE_STRING is represented like a STRING.
PROCEDURE Put_Byte_String (Into : Stream_Id; Data : Byte_String);
FUNCTION Get_Byte_String (From : Stream_Id) RETURN Byte_String;
-- Interchange forms for other types may be defined using the
-- following rules. In some cases, the rules are implemented
-- by generics.
-- A record type is represented by the sequence of its fields,
-- in the order of their declaration. In discriminated records,
-- fields which are inaccessible are omitted.
-- A discrete type (integer subtype or enumeration type)
-- is represented by its 'POS, converted to a short_integer.
GENERIC
TYPE Discrete_Type IS (<>);
PACKAGE Discrete IS
PROCEDURE Put (Into : Stream_Id; Data : Discrete_Type);
PROCEDURE Get (From : Stream_Id; Data : OUT Discrete_Type);
END Discrete;
-- A vector (one-dimensional array) is represented by its
-- 'LENGTH, followed by its elements in index order. The
-- 'LENGTH is represented as an Interchange.Natural. This
-- representation loses information about the 'FIRST of the
-- vector, much like slice assignment.
GENERIC
TYPE Element_Type IS PRIVATE;
WITH PROCEDURE Put (Into : Stream_Id; Data : Element_Type) IS <>;
WITH PROCEDURE Get (From : Stream_Id; Data : OUT Element_Type) IS <>;
TYPE Index_Type IS (<>);
WITH PROCEDURE Put (Into : Stream_Id; Data : Index_Type) IS <>;
WITH PROCEDURE Get (From : Stream_Id; Data : OUT Index_Type) IS <>;
TYPE Vector_Type IS ARRAY (Index_Type RANGE <>) OF Element_Type;
PACKAGE Vector IS
PROCEDURE Put (Into : Stream_Id; Data : Vector_Type);
FUNCTION Get (From : Stream_Id) RETURN Vector_Type;
END Vector;
END Operations;
END Interchange;