HP 3000 Manuals

Extensions to the Standard [ HP FORTRAN 77/iX Reference ] MPE/iX 5.0 Documentation


HP FORTRAN 77/iX Reference

Extensions to the Standard 

HP FORTRAN 77 fully implements the ANSI 77 standard for FORTRAN. HP
FORTRAN 77 also contains many extensions to this standard.  This appendix
categorizes and lists these extensions.  Complete descriptions are given
at the point in the manual where each topic is found.

MIL-STD-1753 Extensions 

The HP FORTRAN 77 compiler fully implements the Military Standard
Definition (MIL-STD-1753) of extensions to the ANSI 77 standard.  These
extensions are as follows:

   *   DO WHILE loops.

   *   INCLUDE statement (also INCLUDE directive).

   *   IMPLICIT NONE statement.

   *   The following bit manipulation intrinsic functions:

 BTEST      IBCLR      IBSET      IOR        ISHFTC     NOT
 IAND       IBITS      IEOR       ISHFT      MVBITS

   *   Octal and hexadecimal constants in DATA and PARAMETER statements.
       A further extension of MIL-STD-1753 is the ability to include
       octal and hexadecimal constants in expressions within assignments
       and to use them as actual parameters.

   *   READ and WRITE past end-of-file.

Other Extensions 

These are the system dependent and all other extensions to the ANSI 77
standard. 

   *   Block DO loops.

   *   Extended range DO loops.

   *   Label omitted in block Do loop.

   *   128-bit complex data type (COMPLEX*16), as approved by the IFIP WG
       2.5 Numerical Software Group.

   *   8-bit integer data type (BYTE or LOGICAL*1).

   *   16-bit integer data type (INTEGER*2).

   *   16-bit logical data type (LOGICAL*2).

   *   Underscores and dollar signs in symbolic names.

   *   Lower case letters as part of FORTRAN character set.

   *   Symbolic names greater than six characters.

   *   Equivalence of character and noncharacter items.

   *   Character and noncharacter items can be mixed in same common
       block.

   *   Exclamation point (!)  at the beginning of an embedded comment.

   *   Byte length specified in numeric type statements, for example,
       INTEGER*4.  (Including the byte length in CHARACTER type
       statements is part of the ANSI 77 standard).

   *   Compiler directives.

   *   Integer intrinsic functions cover both two-byte (INTEGER*2) and
       four-byte (INTEGER*4) integers.

   *   Concatenation of an item of type CHARACTER*(*).

   *   Mixed lengths among character-typed entries.

   *   Unlimited number of array dimensions (the ANSI 77 standard
       specifies only seven).

   *   The logical operators--.AND., .EQV., .NEQV., .NOT., .OR., and
       .XOR.--can be applied to integer data to perform bit masking and
       bit manipulation.

   *   A numeric array can be used as a format specifier in an
       input/output statement.

   *   Formal parameters can be specified for a program and can be passed
       as values from the run string.

   *   Recursion is permitted.

   *   Hollerith, octal, and hexadecimal typeless constants.

   *   The letter J appended to an integer constant to explicitly specify
       type INTEGER*4.

   *   The letter I appended to an integer constant to explicitly specify
       type INTEGER*2.

   *   Logical operands can be intermixed with numeric operands.

   *   Length specification can be a variable enclosed in parentheses.

   *   A length specifier can follow the item being declared.

   *   Quotation marks used as string delimiters.

   *   Integer values can be input or output in octal or hexadecimal
       format.

   *   The SYSTEM INTRINSIC statement (from FORTRAN 66/V).

   *   The ON statement (from FORTRAN 66/V).

   *   Additional format specifications:  @, K, O, Q, R, Z.

   *   Variable format descriptors.

   *   VOLATILE statement.

   *   List-directed I/O transfers can be made on internal files.

   *   Data initialization can be performed in type declaration
       statements by enclosing the initialization value in slashes (/ /).

   *   A COMMON statement can contain a name that has been initialized in
       a DATA statement or type declaration statement.

   *   A variable of type integer can be used as a character length
       specifier.

   *   Dynamic arrays.

   *   Optional label in an Arithmetic IF.

   *   A tab in column 1-6 immediately followed by a digit from 1-9, and
       blanks or nothing before the tab character, is a line
       continuation.

   *   Consecutive operators are allowed if the second operator is either
       a unary plus (+) or minus (-).

   *   Multi-dimensioned EQUIVALENCE.

   *   A CALL can have missing arguments, which are replaced by a zero
       passed by value.

   *   An optional comma (,) is allowed to precede the I/O list within a
       WRITE statement.

   *   Null strings are allowed in the same context where other strings
       are allowed.

   *   The use of & instead of * for alternate return arguments is
       allowed.

   *   Keyword statements:  ACCEPT, DECODE, DOUBLE COMPLEX, ENCODE,
       NAMELIST, TYPE, VIRTUAL.

   *   PROGRAM statement allows the declaration of parameters for the
       main program unit.

   *   Use of noninteger expressions in computed GOTO statements.

   *   Allows blank commons to be initialized by block data subprograms.

   *   REAL*16.

   *   Support of user defined structure types (records).

   *   The following intrinsic functions are included:

%LOC          BTEST         HBITS         IISIGN        JISHFTC       QEXTD
%REF          CDABS         HBSET         IIXOR         JISIGN        QINT
%VAL          CDCOS         HDIM          IMAG          JIXOR         QLOG
ACOSD         CDEXP         HIAND         IMAX0         JMAX0         QLOG10
ACOSH         CDLOG         HIEOR         IMAX1         JMAX1         QMAX1
AIMAX0        CDSIN         HIOR          IMIN0         JMIN0         QMIN1
AIMIN0        CDSQRT        HMOD          IMIN1         JMIN1         QMOD
AJMAX0        COSD          HMVBITS       IMOD          JMOD          QNINT
AJMIN0        DACOSD        HNOT          ININT         JNINT         QNUM
ASIND         DACOSH        HSHFT         INOT          JNOT          QPROD
ASINH         DASIND        HSHFTC        INUM          JNUM          QSIGN
ATAN2D        DASINH        HSIGN         IOR           JZEXT         QSIN
ATAND         DATAN2D       HTEST         IQINT         MVBITS        QSIND
ATANH         DATAND        IAND          IQNINT        NOT           QSINH
BABS          DATANH        IBCLR         IRAND         QABS          QSQRT
BADDRESS      DBLEQ         IBITS         ISHFT         QACOS         QTAN
BBCLR         DCMPLX        IBSET         ISHFTC        QACOSD        QTAND
BBITS         DCONJG        IEOR          IXOR          QACOSH        QTANH
BBSET         DCOSD         IIABS         IZEXT         QASIN         RAND
BBTEST        DDINT         IIAND         JIABS         QASIND        RNUM
BDIM          DFLOAT        IIBCLR        JIAND         QASINH        SIND
BIAND         DFLOTI        IIBITS        JIBCLR        QATAN         SNGLQ
MIEOR         DFLOTJ        IIBSET        JIBITS        QATAN2        TAND
BIOR          DIMAG         IIDIM         JIBSET        QATAN2D       ZABS
BITEST        DNUM          IIDINT        JIDIM         QATAND        ZCOS
BIXOR         DREAL         IIDNNT        JIDINT        QATANH        ZEXP
BJTEST        DSIND         IIEOR         JIDNNT        QCOS          ZEXT
BMOD          DTAND         IIFIX         JIEOR         QCOSD         ZLOG
BMVBITS       FLOATI        IINT          JIFIX         QCOSH         ZSIN
BNOT          FLOATJ        IIOR          JINT          QDIM          ZSQRT
BSHFT         HABS          IISHFT        JIOR          QEXP          ZTAN
BSHFTC        HBCLR         IISHFTC       JISHFT        QEXT
BSIGN



MPE/iX 5.0 Documentation