[an error occurred while processing this directive]

HP OpenVMS Systems

Content starts here

DEC Ada
Technical Overview and Comparison on DIGITAL Platforms


Previous Contents Index


Appendix B
Extended Float Package for OpenVMS Alpha Systems

The following is a suggested and unsupported Ada package previously given out to support long floating-point types on OpenVMS Alpha.


----------------------------------

--   (C) Digital Equipment Corporation 1996. All rights reserved.
--
--   Restricted Rights: Use, duplication, or disclosure by the U.S.
--   Government is subject to restrictions as set forth in subparagraph
--   (c) (1) (ii) of DFARS 252.227-7013, or in FAR 52.227-19, or in FAR
--   52.227-14 Alt. III, as applicable.
--
--   This software is proprietary to and embodies the confidential
--   technology of Digital Equipment Corporation. Possession, use, or
--   copying of this software and media is authorized only pursuant to a
--   valid written license from DIGITAL or an authorized sublicensor.

package X_Float_Package is
    -- Defines 128 bit IEEE Extended floating point type, and associated
    -- operations.

    type X_Float is private;

-- Unary ops
    function "+"(Right: X_Float) return X_Float;
    function "-"(Right: X_Float) return X_Float;
    function "abs"(Right: X_Float) return X_Float;

-- Binary ops
    function "+"(Left, Right: X_Float) return X_Float;
    function "-"(Left, Right: X_Float) return X_Float;
    function "*"(Left, Right: X_Float) return X_Float;
    function "/"(Left, Right: X_Float) return X_Float;

-- Comparison ops ("=" and "/=" are already defined)
    function "<"(Left, Right: X_Float) return Boolean;

    -- Conversions, specified as the unary "+" operator so they are
    -- Convenient to use, as in:
    --
    --    xf := + "1234.5678e+5";
    --    xf := + 1234.5678e+5;    -- literal is long_float

    function "+"(Right: String) return X_Float;
    function "+"(Right: Long_Float) return X_Float;

    function Image(Right: X_Float) return String;
    function Image(Right: X_Float; Format: String) return String;

    function To_Long_Float(Right: X_Float) return Long_Float;

    pragma inline("+", "-", "*", "/", "abs", "<", Image, To_Long_Float);

private

    type X_Float is
        record
            Low,High: Long_Float;
        end record;
    -- We will never manipulate the individual components of an X_Float;
    -- that will be done in the support routines.  An X_Float only has to
    -- be 128 bits long, and aligned on a quad-word boundary.

    for X_Float'size use 128;

end;

package body X_Float_Package is

    function "+"(Right: X_Float) return X_Float is
    begin
        return Right;
    end;

    function "-"(Right: X_Float) return X_Float is
        Result: X_Float;
        procedure uminusx(X: X_Float; R: out X_Float);
        pragma Interface(Fortran, uminusx);
    begin
        uminusx(Right, Result);
        return Result;
    end;

    function "abs"(Right: X_Float) return X_Float is
        Result: X_Float;
        procedure uabsx(X: X_Float; R: out X_Float);
        pragma Interface(Fortran, uabsx);
    begin
        uabsx(Right, Result);
        return Result;
    end;

    function "+"(Left, Right: X_Float) return X_Float is
        Result: X_Float;
        procedure plusx(X, Y: X_Float; R: out X_Float);
        pragma Interface(Fortran, plusx);
    begin
        plusx(Left, Right, Result);
        return Result;
    end;

    function "-"(Left, Right: X_Float) return X_Float is
        Result: X_Float;
        procedure minusx(X, Y: X_Float; R: out X_Float);
        pragma Interface(Fortran, minusx);
    begin
        minusx(Left, Right, Result);
        return Result;
    end;

    function "*"(Left, Right: X_Float) return X_Float is
        Result: X_Float;
        procedure mulx(X, Y: X_Float; R: out X_Float);
        pragma Interface(Fortran, mulx);
    begin
        mulx(Left, Right, Result);
        return Result;
    end;

    function "/"(Left, Right: X_Float) return X_Float is
        Result: X_Float;
        procedure divx(X, Y: X_Float; R: out X_Float);
        pragma Interface(Fortran, divx);
    begin
        divx(Left, Right, Result);
        return Result;
    end;

    function "<"(Left, Right: X_Float) return Boolean is
        Result: Integer;
        procedure ltx(X, Y: X_Float; R: out Integer);
        pragma Interface(Fortran, ltx);
    begin
        ltx(Left, Right, Result);
        return Result /= 0 ;
    end;

    function "+"(Right: String) return X_Float is
        Result: X_Float;
        OK: Boolean;

        procedure cvtsx(X: String; R: out X_Float; OK: out Boolean;
            XLen: Integer);
            -- For OSF, need to pass string length by value.  On VMS, this is
            -- (probably) not needed 'cause descriptors are used.
        pragma Interface(Fortran, cvtsx);
        pragma Import_Procedure(cvtsx,mechanism=>(XLen=>Value));
    begin
        cvtsx(Right, Result, OK, Right'Length);
        if OK then
            return Result;
        else
            raise CONSTRAINT_ERROR;
        end if;
    end;

    function "+"(Right: Long_Float) return X_Float is
        Result: X_Float;
        procedure cvtlx(X: Long_Float; R: out X_Float);
        pragma Interface(Fortran, cvtlx);
    begin
        cvtlx(Right, Result);
        return Result;
    end;

    function Image(Right: X_Float) return String is
        subtype Str100 is String(1..100);
        Result: Str100 := (others => ' ');
        procedure imagex(X: X_Float; R: out Str100);
        pragma Interface(Fortran, imagex);
    begin
        imagex(Right, Result);
        return Result;
    end;

    function Image(Right: X_Float; Format: String) return String is
        subtype Str100 is String(1..100);
        Result: Str100 := (others => ' ');
        procedure imagefx(X: X_Float; F: String; R: out Str100;
            FLen: integer);
            -- For OSF, need to pass string length, by value.  On VMS, this is
            -- (probably) not needed 'cause descriptors are used.
        pragma Interface(Fortran, imagefx);
        pragma Import_Procedure(imagefx,mechanism=>(FLen=>Value));
    begin
        imagefx(Right, Format, Result, Format'Length);
        return Result;
    end;

    function To_Long_Float(Right: X_Float) return Long_Float is
        Result: Long_Float;
        OK: Boolean;
        procedure cvtxl(X: X_Float; R: out Long_Float; OK: out Boolean);
        pragma Interface(Fortran, cvtxl);
    begin
        cvtxl(Right, Result, OK);
        if OK then
            return Result;
        else
            raise CONSTRAINT_ERROR;
        end if;
    end;

end;

      subroutine uminusx(x,r)
      real*16 x,r
      r = - x
      end

      subroutine uabsx(x,r)
      real*16 x,r
      r = abs(x)
      end

      subroutine plusx(x,y,r)
      real*16 x,y,r
      r = x + y
      end

      subroutine minusx(x,y,r)
      real*16 x,y,r
      r = x - y
      end

      subroutine mulx(x,y,r)
      real*16 x,y,r
      r = x * y
      end

      subroutine divx(x,y,r)
      real*16 x,y,r
      r = x / y
      end

      subroutine ltx(x,y,r)
      real*16 x,y
      integer*4 r
      r = x .lt. y
      end

      subroutine cvtsx(x,r,ok)
      real*16 r
      character*(*) x
      integer*4 ok
c     use internal read to cvt string to x_float. on error, goto 100
      read (x,*, err=100) r
      ok = 1
      return
 100  ok = 0
      end

      subroutine cvtlx(x,r)
      real*16 r
      real*8 x
      r = x
      end

      subroutine imagex(x,r)
      real*16 x
      character*100 r
c     use internal write to translate x_float to string
      write (r,*) x
      end

      subroutine imagefx(x,f,r)
      real*16 x
      character*100 r
      character*(*) f
c     use internal write to translate x_float to string, using passed
c     in format:f
      write (r,f) x
      end

      subroutine cvtxl(x,r,ok)
      real*16 x
      real*8 r
      integer*4 ok
c     Check that x doesn't have too large an absolute value for
c     converting to real*8.
      if(x.gt. 1.797693134623d+308.or.x.lt. -1.797693134623d+308)then
          ok = 0
      else
          ok = 1
          r = x
      endif
      end

with x_float_package, text_io;
use x_float_package, text_io;
pragma Elaborate(x_float_package);    -- makes inlining more efficient
procedure x_float_use is
    a,b,c,d,e: x_float;
    x,y,z:long_float;
    s:string(1..100);
begin
    a := + 1.0;        -- The + should cause the float literal to implicitly
                    -- become Long_Float; the + then explicitly converts
                    -- it to X_Float.
    b := a + (+2.0);
    c := b * b;
    d := + long_float'large;
    e := d * d;
    put_line(image(c));
    put_line(image(d));
    put_line(image(e));
    a := + "1234567890.12345678901234567890";
    a := a + (+1.0);
    put_line(image(a));
end;

-- Here's the output from running this on Alpha OSF
--   9.00000000000000000000000000000000
--  2.571100870814383299068985182977955E+0061
--  6.610559687902480118162696145745944E+0122
--   1234567891.12345678901234567890000


Appendix C
A Comparison of Rational's VADS for DIGITAL UNIX with DEC Ada for DIGITAL UNIX Systems

This appendix compares Rational's Ada 83 compiler, VADS for DEC Alpha AXP OSF/1 (DIGITAL UNIX) and DEC Ada on DIGITAL UNIX systems, including differences in the implementation or interpretation of the Ada standard.

Note

In this guide, VADS refers to the VADS product line from Rational Software Corporation, an extensive family of mature, production-quality, optimizing Ada compilers, cross-compilers, and related tools.

This appendix discusses the following topics:

  • Language-related features
  • Representation clauses
  • Dope vectors
  • Package STANDARD
  • Package SYSTEM
  • Tasking and task-related features
  • Pragmas and pragma-related features
  • Library of predefined units
  • Bindings
  • Implementation-defined attributes
  • Compiler and run-time interfacing
  • User interface
  • Input-output
  • Implementation limits

Note that VADS can be cross-compiled and downloaded to other systems. DEC Ada was not intended for such use. As a result, VADS contains functions that handle cross-compiling and downloading and DEC Ada does not. On DEC Ada, cross-compiling is available only with the use of XD Ada.

C.1 Language-Related Features

The following sections highlight differences in types, representations of types, operations, alignment, and related topics.

C.1.1 Integer Types

VADS provides the following integer types:

  • TINY_INTEGER
  • SHORT_INTEGER
  • INTEGER
  • LONG_INTEGER

Table C-1 lists the integer types provided by VADS and first and last values.

Table C-1 Range of Values for VADS Predefined Integer Types
Type T'FIRST T'LAST T'SIZE
TINY_INTEGER --2 7 2 7--1 8
SHORT_INTEGER --2 15 2 15--1 16
INTEGER --2 31 2 31--1 32
LONG_INTEGER --2 31 2 63--1 64

DEC Ada provides the following integer types:

  • SHORT_SHORT_INTEGER
  • SHORT_INTEGER
  • INTEGER
  • LONG_INTEGER

Table C-2 lists the predefined integer types provided by DEC Ada and first and last values.

Table C-2 Range of Values for DEC Ada Predefined Integer Types
Type T'FIRST T'LAST T'SIZE
SHORT_SHORT_INTEGER --2 7 2 7--1 8
SHORT_INTEGER --2 15 2 15--1 16
INTEGER --2 31 2 31--1 32
LONG_INTEGER --2 63 2 63--1 64

DEC Ada has defined the following additional integer types:

  • INTEGER_8
  • INTEGER_16
  • INTEGER_32
  • INTEGER_64
  • LARGEST_INTEGER

On DEC Ada, the maximum integer size is 64 bits.

C.1.2 Floating-Point Numbers and Representations

VADS provides the following floating-point types:

  • SHORT_FLOAT
  • FLOAT
  • LONG_FLOAT

The predefined attributes and their values that yield the characteristics of each floating-point type are described in Appendix F of the VADSself DEC Alpha AXP DIGITAL UNIX Programmer's Guide.

DEC Ada on DIGITAL UNIX systems implements the following floating-point numbers:

  • IEEE_SINGLE_FLOAT
  • IEEE_DOUBLE_FLOAT

Table C-3 lists the floating-point types declared in the package STANDARD and their default representations.

Table C-3 Floating-Point Types and Default Representations
Predefined Type Default
Representation
Size (bits) Digits of Precision
FLOAT IEEE single float 32 6
LONG_FLOAT IEEE double float 64 15
LONG_LONG_FLOAT IEEE double float 64 15

The predefined attributes that yield the characteristics of each floating-point type are described in the DEC Ada Language Reference Manual. Values of these attributes for the DEC Ada floating-point data representations are listed in Appendix F of the DEC Ada Language Reference Manual. The DEC Ada run-time reference manuals also give information on the internal representation of the DEC Ada floating-point types.

On DIGITAL UNIX, DEC Ada provides the pragma FLOAT_REPRESENTATION, which acts as a program library switch to allow control over the internal representation chosen for the predefined floating-point types declared in the packages STANDARD and SYSTEM. On DIGITAL UNIX, the value of this pragma must be IEEE_FLOAT.

C.1.3 Record Representation Clause Maximum Alignment

On VADS implementations, the record representation clause maximum alignment is 16. On DEC Ada implementations, the maximum alignment is 23.

C.1.4 Record and Array Component Alignment

On VADS, if the component does not start on a storage unit boundary, then it must be possible to store the component in a register with one move instruction (4 bytes on an Intel 80386 processor).

On DEC Ada, all noncomposite components are aligned on natural boundaries (unless otherwise specified with the pragma COMPONENT_ALIGNMENT). For example, 1-byte components are aligned on byte boundaries, 2-byte components on 2-byte boundaries, 4-byte components on 4-byte boundaries, and so on.

The Alpha hardware runs more efficiently with naturally aligned data.

On DIGITAL UNIX systems, DEC Ada allows the simple expression in an alignment clause to have a value between 20 and 216 (inclusive).

In other words, the simple expression must be an integer in the range 1 .. 512, 1 .. 65536, or 1 .. 8 that is also a power of 2. The allocations then occur at addresses that are a multiple of the simple expression (a value of 2 aligns the data on a 2-byte boundary, a value of 4 aligns the data on a 4-byte boundary, and so on).

C.1.5 Type DURATION

The type DURATION has different ranges on VADS and DEC Ada. Table C-4 shows these ranges as well as other attributes of the type DURATION and their values on the two platforms.

Table C-4 Properties of the Type DURATION
Attribute Value on VADS Value on DEC Ada
DURATION'DELTA 1.00000000000000E--09 0.0001
DURATION'SMALL 1.00000000000000E--09 2.0 -14
DURATION'FIRST --9799832789.158200441 --131072.0000
DURATION'LAST 9223372036.854778244 131071.9999
DURATION'LARGE 9.22337203685478E+09 131071.9999

C.1.6 Other VADS-Specific Type Information

The following lists implementation-defined type information:

  • Maximum ARRAY and RECORD type size limits are increased to 256_000_000 bits.
  • VADS uses unlimited precision arithmetic for computation with numeric literals.
  • VADS allows an unlimited number of literals within an enumeration type.
  • VADS defines the image of a character that is not a graphic character as the corresponding 2- or 3-character identifier from package ASCII. The identifier is in uppercase without enclosing apostrophes.
  • Except for memory size, VADS places no specific limit on the length of the predefined type STRING. Any type derived from STRING is similarly unlimited.
  • VADS provides fixed-point types mapped to the supported integer sizes.

C.2 Representation Clauses

Representation clauses are based on the target machine's word, byte, and bit order numbering. VADS is consistent with machine architecture manuals for both "big-endian" and "little-endian" machines. Bits within a STORAGE_UNIT are numbered according to the target machine manuals. It is not necessary for a user to understand the default layout for records and other aggregates because fine control over the layout is obtained by the use of record representation clauses. It is possible to align fields correctly with structures and other aggregates from other languages by specifying the location of each element explicitly. The FIRST_BIT and LAST_BIT attributes can be used to construct bit manipulation code applicable to differently bit-numbered systems.

The only restriction on record representation clauses is that if a component does not start and end on a storage unit boundary, it must be possible to get it into a register with one move instruction.

The size of object modules is aligned. It is assumed that "mod 2" is a worst case restriction, assuming that even the C compiler aligns to a 2-byte boundary.

The alignment clause portion of a record representation must be a power of 2. The alignment is obeyed for all allocations of the record type with the following exceptions:

  • Object declared within a procedure
  • Objects created by an allocator

For these two exceptions, the maximum alignment obeyed is the default stack and heap alignment.

If a record is given a representation clause but no alignment clause, the compiler assumes that the record may be arbitrarily aligned (at an arbitrary bit offset within another structure, for example).

C.2.1 ADDRESS Attribute---VADS Implementations

The ADDRESS attribute is supported for the following entities:

  • Variables
  • Constants
  • Procedures
  • Functions

If the prefix of an address attribute is an object that is not aligned on a storage unit boundary, the attribute yields the address of the storage unit containing the first bit of the object. This is consistent with the definition of the FIRST_BIT attribute.

C.2.2 Restrictions on Unchecked Type Conversions

VADS implementations provide both UNCHECKED_DEALLOCATION and UNCHECKED_CONVERSION.

VADS supports the generic function UNCHECKED_CONVERSION with the following restrictions on the class of types involved:

  • The actual subtype corresponding to the formal type TARGET must not be an unconstrained array type.
  • The actual subtype corresponding to the formal type TARGET must not be an unconstrained type with discriminants.

If the size of the source differs from the size of the target subtype, a warning is issued by the compiler and results may be unpredictable.

Any object allocated can be deallocated. Currently, VADS performs no checks on release objects. However, when an object is deallocated, its access variable is set to null. Subsequent deallocations using the null access variable are ignored.

DEC Ada supports the generic function UNCHECKED_CONVERSION with the following restrictions on the class of types involved:

  • The actual subtype corresponding to the formal type TARGET must not be an unconstrained array type.
  • The actual subtype corresponding to the formal type TARGET must not be an unconstrained type with discriminants.

When the target type is a type with discriminants, the value resulting from a call of the conversion function resulting from an instantiation of UNCHECKED_CONVERSION is checked to ensure that the discriminants satisfy the constraints of the actual subtype.

If the size of the source value is greater than the size of the target subtype, the high order of bits of the value is ignored (truncated). If the size of the source value is less than the size of the target subtype, the value is extended with zero bits to form the result value.

C.2.3 Additional Representation Clause Information---VADS Implementations

VADS supports the following:

  • Bit-level representation clauses
  • Enumeration representation clauses
  • Change of representation
  • Representation attributes of real types
  • Machine code insertions

VADS does not define any additional representation pragmas.

C.2.4 Restrictions on Representation Clauses---DEC Ada Implementations

The representation clauses allowed in VADS are length, enumeration, record representation, and address clauses.

A representation clause is not allowed for a generic formal type.

The representation clauses allowed in DEC Ada are length, enumeration, record representation, and address clauses.

In DEC Ada, a representation clause is not allowed for:

  • A generic formal type
  • A type that depends on a generic formal type
  • A composite type that has a component or subcomponent of a generic formal type
  • A type derived from a generic formal type

C.3 Dope Vectors

In VADS, an array dope vector is a sequence of quadwords (64 bits) containing precomputed offset expressions used for indexing arrays.

An array subtype is completely static if its bounds are all static and its component subtype is static sized. The dope vector for a completely static array subtype is initialized statically. All other dope vectors are initialized by generated inline code.

Dope vectors are allocated in different ways as shown in the following table:

Static Allocation If the array subtype is completely static or declared within a library level package spec or body, then the dope vector is allocated statically.
Stack Allocation If the array subtype is dynamic and declared within a task, declare block, or subprogram body, the dope vector is allocated on the stack.
Heap Allocation If the array subtype is declared in an allocator for an unconstrained array type, the dope vector is allocated in the words immediately preceding the allocated array object.
Record Allocation If the array subtype is a dependent array subtype (for example, one of its bounds is a discriminant of an enclosing record), the dope vector is allocated in the static part of the record. The dope vector is initialized by record initialization code.

In DEC Ada, dope vectors are special descriptors that are used in some cases to pass record and array parameters between Ada subprograms or to return record and array function results. They are never used in calls to and from subprograms that are specified in an import, export, or INTERFACE pragma.

DEC Ada uses two kinds of dope vectors:

  • Dope vectors that describe a byte-aligned data element
  • Bit dope vectors that describe a bit-aligned data element

For more information on DEC Ada dope vectors, see the DEC Ada Run--Time Reference Manual for DEC OSF/1 Systems.

C.4 Parameter Passing

VADS passes the first six scalar parameters in registers. The remaining scalar parameters are passed by pushing values (or addresses) on the stack.

Small results are returned in registers. Large results with known targets are passed by reference. Large results of anonymous target and known size are passed by reference to a temporary created on the caller's stack. Large results of anonymous target and unknown size are returned by copying the value down from a temporary in the callee so the space used by the temporary can be reclaimed.

VADS passes up to six parameters in registers, the remaining parameters are passed on the stack. The MACHINE_CODE package requires the usage of parameters as operands be consistent with the type of operand expected by the MACHINE_CODE instruction, given that the parameters can be in registers or on the stack.

In DEC Ada when importing or exporting routines from other languages or when exporting Ada subprogram, you can explicitly specify the passing mechanisms for one or more parameters or function results.

Before deciding to explicitly specify the passing mechanisms, the compiler compilation notes can be used to determine which default mechanisms the compiler chooses for certain parameters or function results.

Once the parameter-passing mechanisms are explicitly specified, the MECHANISM option can be used in DEC Ada import or export pragmas to specify one of two values for each parameter. Similarly, the RESULT_MECHANISM option can be used to specify one of the same two values for each function result. The two mechanisms are as follows:

  • VALUE. Causes the value of the actual parameter or function result to be passed or returned.
  • REFERENCE. Causes an address of the value of the actual parameter to be passed; causes the address of the function result to be returned by the extra parameter method.

C.5 Package STANDARD

The package STANDARD is fully described in the Reference Manual for the Ada Programming Language (ANSI/MIL-STD-1815A-1983) and the the implementation of the package in DEC Ada is fully described in DEC Ada Language Reference Manual.

For a discussion of the predefined types in this appendix, see Section C.1.

The following list compares the differences between implementations of the package STANDARD on VADS and on DEC Ada:

  • DEC Ada supports the Latin-1 character set in the type CHARACTER. VADS supports a 7-bit character set.
  • VADS supports the type TINY_INTEGER, and DEC Ada supports the type SHORT_SHORT_INTEGER. These two types have identical attribute values.
  • VADS supports the type SHORT_FLOAT, which is the same size as the DEC Ada type FLOAT.
  • VADS supports the type FLOAT, which is the same size as the DEC Ada tyep LONG_FLOAT.
  • By default, VADS has representation of a string with 1 byte per character. By default, DEC Ada has 1 byte per character.

Table C-5 compares the sizes of integer and floating-point types between the package STANDARD on VADS and on DEC Ada.

Table C-5 Comparison of Type Sizes in the Package STANDARD
Type VADS Size DEC Ada Size
SHORT_FLOAT 32 bits N/A
FLOAT 64 bits 32 bits
LONG_FLOAT 64 bits 64 bits
LONG_LONG_FLOAT N/A 64 bits
SHORT_SHORT_INTEGER N/A 8 bits
TINY_INTEGER 8 bits N/A
SHORT_INTEGER 16 bits 16 bits
INTEGER 32 bits 32 bits
LONG_INTEGER 64 bits 64 bits


Previous Next Contents Index