Converted from .HLP to .HTML by HLPTOHTML.

fortran .HLP

ADJARRBOU

SEVERITY: F

MESSAGE TEXT: Adjustable array bound contains invalid data item

EXPLANATION: An adjustable array dimension declarator expression contained an operand that was not one of the following:

o A constant

o A variable in a common block

o A variable associated with a subprogram dummy argument

ADJARRUSE

SEVERITY: F

MESSAGE TEXT: Adjustable array used in invalid context

EXPLANATION: A reference to an adjustable array was made in a context where such a reference is not allowed.

ADJLENUSE

SEVERITY: F

MESSAGE TEXT: Passed-length character name used in invalid context

EXPLANATION: A reference to a passed-length character array or variable was made in a context where such a reference is not allowed.

AGGREFSIZ

SEVERITY: F

MESSAGE TEXT: Aggregate reference exceeds 65535 bytes per element

EXPLANATION: Any aggregate reference larger than 65535 bytes cannot be used in an I/O list or as an actual or dummy argument.

ALTRETLAB

SEVERITY: F

MESSAGE TEXT: Alternate return label used in invalid context

EXPLANATION: An alternate return argument cannot be used in a function reference.

ALTRETOMI

SEVERITY: E

MESSAGE TEXT: Alternate return omitted in SUBROUTINE or ENTRY statement

EXPLANATION: An asterisk is missing in the argument list of a subroutine for which an alternate return is specified. Examples:

1. SUBROUTINE XYZ(A,B) . . . RETURN 1

2. ENTRY ABC(Q,R) . . .

RETURN I+4

ALTRETSPE

SEVERITY: F

MESSAGE TEXT: Alternate return specifier invalid in FUNCTION subprogram

EXPLANATION: The argument list of a FUNCTION declaration contains an asterisk or a RETURN statement in a function subprogram specifies an alternate return. Examples:

1. INTEGER FUNCTION TCB(ARG,*,X)

2. FUNCTION IMAX . . . RETURN I+J END

ARGLISEXE

SEVERITY: F

MESSAGE TEXT: IARGCOUNT/IARGPTR used in non-executable statement

EXPLANATION: One of the argument list inquiry functions, IARGCOUNT or IARGPTR, was used in a non-executable statement such as a statement function declaration.

ARIVALREQ

SEVERITY: F

MESSAGE TEXT: Character expression where arithmetic value required

EXPLANATION: An expression that must be arithmetic (INTEGER, REAL, LOGICAL, or COMPLEX) was of type CHARACTER.

ASFUNUSED

SEVERITY: I

MESSAGE TEXT: Statement function was defined but not used

EXPLANATION: The specified statement function was defined but never used.

This message can be suppressed with /WARNINGS=NOUNCALLED.

ASSARRUSE

SEVERITY: F

MESSAGE TEXT: Assumed size array name used in invalid context

EXPLANATION: An assumed size array name was used where the size of the array was also required, for example, in an I/O list.

ASSDOVAR

SEVERITY: W

MESSAGE TEXT: Assignment to DO variable within loop

EXPLANATION: The control variable of a DO loop has been altered within the range of the DO statement.

ATTRIERR

SEVERITY: I

MESSAGE TEXT: COMMON attributes conflict, using the default attribute

EXPLANATION: This error only occurs with the CDEC$ PSECT compiler directive statement and under any of the following circumstances:

o A common block is declared as both GBL (global) and LCL (local), both WRT (write) and NOWRT (nowrite), or both SHR (shared) and NOSHR (noshared).

o More than one alignment (ALIGN=) to the COMMON block is specified.

o The following combination of compiler directive statements occurs:

CPAR$ SHARED com_blk and CDEC$ PSECT /com_blk/ ATTRI=something-not-page-alignment

o An alignment value exceeding the legal range is specified. The alignment attribute can only take the value of 0 through 9.

AUTDATINI

SEVERITY: W

MESSAGE TEXT: Variable is data-initialized; AUTOMATIC ignored

EXPLANATION: A variable was declared as AUTOMATIC but was also data-initialized in a DATA or type-specification statement. AUTOMATIC variables cannot be data-initialized. The AUTOMATIC attribute was ignored.

AUTSAVALL

SEVERITY: W

MESSAGE TEXT: SAVE of all variables specified; AUTOMATIC ignored

EXPLANATION: A variable was declared as AUTOMATIC in a program unit which contained a SAVE statement that, by omitting a list of names of variables to be SAVEd, specified that all variables should be SAVEd. The AUTOMATIC attribute was ignored.

BADALIGN

SEVERITY: W

MESSAGE TEXT: Variable not naturally aligned

EXPLANATION: A variable or array was declared in such a way that it crossed a natural boundary for its data size.

BADEND

SEVERITY: F

MESSAGE TEXT: END [STRUCTURE|UNION|MAP] must match top

EXPLANATION: A STRUCTURE, UNION, or MAP statement did not have a corresponding END STRUCTURE, END UNION, or END MAP statement, respectively.

BADFIELD

SEVERITY: F

MESSAGE TEXT: Field name not defined for this structure

EXPLANATION: A field name not defined in a record structure was used in a record reference.

BADRECREF

SEVERITY: F

MESSAGE TEXT: Aggregate reference where scalar reference required

EXPLANATION: An aggregate record reference was used where a scalar record reference was required.

BADVALUE

SEVERITY: F

MESSAGE TEXT: "keyword-value" is an invalid keyword value

EXPLANATION: The specified FORTRAN command line contained a keyword "keyword-value" that is not recognized as a valid keyword value.

BUGCHECK

SEVERITY: F

MESSAGE TEXT: Internal consistency failure

EXPLANATION: The compiler detected an internal error and the compilation was terminated. Please report the problem to Digital (by means of a Software Performance Report (SPR)) and include all information necessary to reproduce the error, including sources and a compiler listing, if possible.

BRNCHINTOBLK

SEVERITY: I

MESSAGE TEXT: Questionable branch into loop or block

EXPLANATION: A branch into a DO loop or IF block was detected. Although this might be valid if the FORTRAN 66 "extended range of a DO loop" feature was being used, it generally indicates a programming error. A common case involves two or more DO loops which share a common termination. In such cases, the shared termination statement is considered to belong to the innermost DO loop.

This message can be suppressed with /WARNINGS=NOUSAGE.

CDDALNARY

SEVERITY: I

MESSAGE TEXT: CDD description specifies an aligned array (unsupported)

EXPLANATION: The CDD description contained an array field whose elements have an alignment that DEC Fortran cannot accommodate.

When this error is encountered, the array is replaced by a structure of the appropriate size.

CDDBITSIZ

SEVERITY: F

MESSAGE TEXT: CDD field specifies a bit size or alignment.

EXPLANATION: The CDD's bit datatype and bit alignment are not supported by DEC Fortran.

CDDERROR

SEVERITY: I

MESSAGE TEXT: CDD description extraction condition

EXPLANATION: The DEC Fortran compiler encountered an error while extracting a structure definition from the Common Data Dictionary (CDD). See the accompanying messages for more information.

CDDINIVAL

SEVERITY: I

MESSAGE TEXT: CDD description contains Initial Value attribute (ignored)

EXPLANATION: A field that specified an initial value was present in the CDD description being expanded.

When this error is encountered, the initial value is ignored.

CDDNOTSTR

SEVERITY: F

MESSAGE TEXT: CDD record is not a structure

EXPLANATION: DEC Fortran requires structure definitions (elementary field descriptions in CDDL). The data described by the CDD is not a structure.

CDDRECDIM

SEVERITY: F

MESSAGE TEXT: CDD record is dimensioned

EXPLANATION: DEC Fortran does not support dimensioned structures, for example, arrays of structures.

CDDSCALED

SEVERITY: W

MESSAGE TEXT: CDD description specifies a scaled data type

EXPLANATION: DEC Fortran does not support scaled data types. The data described by the CDD specifies a scaled component.

CDDTOOBIG

SEVERITY: F

MESSAGE TEXT: Attributes for some member of CDD record description exceed implementation's limit for member complexity

EXPLANATION: Some member of the Common Data Dictionary record description had too many attributes and created a program that was too large. Change the CDD description to make the field description smaller.

CDDTOODEEP

SEVERITY: F

MESSAGE TEXT: Attributes for CDD record description exceed implementation's limit for record complexity

EXPLANATION: The CDD record description contained structures that were nested too deeply. Modify the CDD description to reduce the level of nesting in the record description.

CHANAMINC

SEVERITY: E

MESSAGE TEXT: Character name incorrectly initialized with numeric value

EXPLANATION: Character data with a length greater than one was initialized with a numeric value in a DATA statement. Example: CHARACTER*4 A DATA A/14/

CHASBSLIM

SEVERITY: F

MESSAGE TEXT: Character substring limits out of order

EXPLANATION: The first character position of a substring expression was greater than the last character position. Example:

C(5:3)

CHAVALREQ

SEVERITY: F

MESSAGE TEXT: Arithmetic expression where character value required

EXPLANATION: An expression that must be of type CHARACTER was of another data type.

CLOSEIN

SEVERITY: F

MESSAGE TEXT: Error closing "file-spec" as input

EXPLANATION: Unable to close the file "file-spec".

CLOSEOUT

SEVERITY: F

MESSAGE TEXT: Error closing "file-spec" as output

EXPLANATION: Unable to close the file "file-spec".

COMVARDECL

SEVERITY: F

MESSAGE TEXT: Common variable cannot be declared SHARED or PRIVATE

EXPLANATION: A variable within a common block cannot be specified in a CONTEXT_SHARED or PRIVATE compiler directive statement. Entire common blocks can be declared shared or private, but individual elements within them cannot be declared context-shared or private.

CONMEMEQV

SEVERITY: E

MESSAGE TEXT: Conflicting memory attributes in an equivalenced group

EXPLANATION: By means of an EQUIVALENCE statement, certain memory locations were given conflicting memory attributes (shared or context-shared and private).

CONSIZEXC

SEVERITY: E

MESSAGE TEXT: Constant size exceeds variable size in data initialization

EXPLANATION: A constant used for data initialization is larger than its corresponding variable.

DBGOPT

SEVERITY: I

MESSAGE TEXT: The NOOPTIMIZE qualifier is recommended with the DEBUG qualifier

EXPLANATION: Optimizations performed by the compiler can cause several different kinds of unexpected behavior when using VAX DEBUG. For more information about compiler optimizations, see the DEC Fortran Performance Guide for OpenVMS VAX Systems.

DEFSTAUNK

SEVERITY: I

MESSAGE TEXT: Default STATUS='UNKNOWN' used in OPEN statement

EXPLANATION: The OPEN statement default STATUS='UNKNOWN' can cause an old file to be inadvertently modified.

DEPENDITEM

SEVERITY: I

MESSAGE TEXT: CDD description contains Depends Item attribute (ignored)

EXPLANATION: Fortran does not support the Common Data Dictionary Depend Item attribute.

DESCOMABORT

SEVERITY: F

MESSAGE TEXT: /DESIGN=COMMENTS processing has been aborted due to an internal error

EXPLANATION: The design processing routines have detected an internal error; subsequent messages provide more detail. Please report the problem to Digital.

DESCOMERR

SEVERITY: W

MESSAGE TEXT: Error in processing design information

EXPLANATION: The comment analysis routines have detected an error in the text of a comment, such as an undefined keyword in a structured tag. Additional messages relating to the error are also displayed.

DESCOMNOLSE

SEVERITY: F

MESSAGE TEXT: /DESIGN=COMMENTS requires installation of VAX Language Sensitive Editor

EXPLANATION: To use /DESIGN=COMMENTS, the Language Sensitive Editor (part of DECset) needs to be installed on this system. Omit /DESIGN=COMMENTS, attempt the compilation on another system where the Language Sensitive Editor is installed, or install the Language Sensitive Editor and retry.

DESCOMSEVERR

SEVERITY: F

MESSAGE TEXT: A serious error has occurred processing /DESIGN=COMMENTS

EXPLANATION: The comment analysis routines have detected a severe error that prevents further comment analysis in the current compilation. Additional messages relating to the error are also displayed. The compilation is aborted.

DESIGNTOOOLD

SEVERITY: F

MESSAGE TEXT: /DESIGN=COMMENTS processing routines are too old for the compiler

EXPLANATION: The version of the comment analysis routines present on the system is not supported by this version of DEC Fortran. Install a newer version of the Language Sensitive Editor to obtain the newer comment analysis routines.

DICTABORT

SEVERITY: F

MESSAGE TEXT: DICTIONARY processing of CDD record description aborted

EXPLANATION: The DEC Fortran compiler is unable to process the Common Data Dictionary record description. See the accompanying messages for further information.

DIRSTRREQ

SEVERITY: I

MESSAGE TEXT: Directive requires string constant, directive ignored

EXPLANATION: This error only occurs with the use of the CDEC$ compiler directive statements: TITLE, SUBTITLE, and IDENT.

String values for the TITLE, SUBTITLE, and IDENT directives cannot be more than 31 characters. Any other values, including PARAMETER statement constants that are defined to be strings, are invalid on these directives.

ENTDUMVAR

SEVERITY: F

MESSAGE TEXT: ENTRY dummy variable previously used in executable statement

EXPLANATION: The dummy arguments of an ENTRY statement must not have been used previously in an executable statement in the same program unit.

ERRLIMEXC

SEVERITY: F

MESSAGE TEXT: Error limit exceeded; compilation terminated

EXPLANATION: The limit on the number of E or F level errors specified by the /ERROR_LIMIT qualifer was exceeded for this compilation unit. Compilation of this unit was terminated, but compilation continued for other units, if any.

EQVEXPCOM

SEVERITY: F

MESSAGE TEXT: EQUIVALENCE statement incorrectly expands a common block

EXPLANATION: A common block cannot be extended beyond its beginning by an EQUIVALENCE statement.

EQVSAVCOM

SEVERITY: E

MESSAGE TEXT: EQUIVALENCE may not be used to put a SAVE variable into COMMON

EXPLANATION: An EQUIVALENCE group was found which included a COMMON variable and a variable named in a SAVE statement. SAVE variables may not be placed in COMMON, although an entire COMMON block may be named in a SAVE statement.

EXCCHATRU

SEVERITY: E

MESSAGE TEXT: Non-blank characters truncated in string constant

EXPLANATION: A character constant or Hollerith constant was converted to a data type that was not large enough to contain all the significant characters.

EXCDIGTRU

SEVERITY: E

MESSAGE TEXT: Non-zero digits truncated in constant

EXPLANATION: A Hollerith, character literal or typeless constant was converted to a data type that was not large enough to contain all the significant digits.

EXCNAMDAT

SEVERITY: E

MESSAGE TEXT: Number of names exceeds number of values in data initialization

EXPLANATION: The number of constants specified in a DATA statement must match the number of variables or array elements to be initialized. When a mismatch occurs, any extra variables or array elements are not initialized.

EXCVALDAT

SEVERITY: E

MESSAGE TEXT: Number of values exceeds number of names in data initialization

EXPLANATION: The number of variables or array elements to be initialized must match the number of constants specified in data initialization. When a mismatch occurs, any extra constant values are ignored.

EXPSTAOVE

SEVERITY: F

MESSAGE TEXT: Compiler expression stack overflow

EXPLANATION: An expression was too complex or there were too many actual arguments in a subprogram reference. A maximum of 255 actual arguments can be compiled. You can subdivide a complex expression or reduce the number of arguments.

EXTARYUSE

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Nonstandard use of array

EXPLANATION: One of the following extensions was detected:

o An array was used as a FILE specification in an OPEN statement.

o The file name of an INQUIRE statement was a numeric scalar reference or a numeric array name reference

EXTBADCONT

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: nonstandard continuation character

EXPLANATION: A nonstandard character was used as a continuation indicator.

EXTCATDARG

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Concatenation of dummy argument

EXPLANATION: A character dummy argument appeared as an operand in a concatenation operation.

EXTCHAFOL

SEVERITY: E

MESSAGE TEXT: Extra characters following a valid statement

EXPLANATION: Superfluous text was found at the end of a syntactically correct statement. Check for typing or syntax errors.

EXTCHARREQ

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Character required

EXPLANATION: A character variable was initialized with a noncharacter value by means of a DATA statement.

EXTCHASOU

SEVERITY: W

MESSAGE TEXT: Extra characters in source line were truncated

EXPLANATION: A source line was read that was longer than the statement field width and /WARNINGS=TRUNCATED_SOURCE was specified. The source line was truncated to the statement field width; 72 or 132 characters, depending on the value of the /EXTEND_SOURCE command or OPTIONS statement qualifier in effect.

EXTCHRARG

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: CHARACTER*(*) argument used as function

EXPLANATION: A formal argument used as a function was declared CHARACTER*(*). The FORTRAN-77 standard requires the length to be an integer constant.

EXTCOMPARNAM

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: COMMON block has same name as PARAMETER constant

EXPLANATION: A COMMON blocks was declared to have the same name as a PARAMETER constant, a PARAMETER constant was declared to have the same name as a previously declared COMMON block.

EXTCONT19

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: more than 19 continuation lines

EXPLANATION: More than 19 continuation lines were defined for the statement.

EXTDATACOM

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Nonstandard DATA initialization

EXPLANATION: One of the following extensions occurred:

o An element in a blank common block was data initialized.

o An element of a named common block was data initialized outside of the BLOCK DATA program unit.

EXTDATORD

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: DATA statement out of order

EXPLANATION: A DATA statement occurred before a declaration statement. All DATA statements must occur after the declaration section of a program.

EXTILDOCNT

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Negative implied-Do iteration count

EXPLANATION: The iteration count of an implied DO was negative.

EXTINTRIN

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: nonstandard intrinsic function

EXPLANATION: A nonstandard intrinsic function was used.

EXTLSTINF

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: nonstandard list directed internal

EXPLANATION: A nonstandard list directed internal read or write statement was used.

EXTMISSUB

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Missing array subscripts

EXPLANATION: Only one subscript was used to reference a multi-dimensional array in an EQUIVALENCE statement.

EXTMIXCOM

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Mixed numeric and character elements in COMMON

EXPLANATION: A common block must not contain both numeric and character data.

EXTMIXEQV

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Mixed numeric and character elements in EQUIVALENCE

EXPLANATION: A numeric variable or numeric array element cannot be equivalenced to a character variable or character array element.

EXTOPERAT

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Nonstandard operation

EXPLANATION: One of the following operations was detected:

o A logical operand and a nonlogical operand were used in the same operation.

o A real type expression and a complex type expression were used in the same statement.

o A character operand and a noncharacter operand were used in the same operation.

o A nonlogical expression was assigned to a logical variable.

o A noncharacter expression was assigned to a character variable.

o A character dummy argument appeared in a concatenation operation and the result of the expression was not assigned to a character variable.

o Logical operators were used with nonlogical operands.

o Arithmetic operators were used with nonnumeric operands.

EXTRECUSE

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Nonstandard use of field reference

EXPLANATION: A record reference (for example, record-name.field-name) was used in a program compiled with the /STANDARD=[SYNTAX|ALL] qualifier in the FORTRAN command.

EXTUSECCON

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Nonstandard use of character constant

EXPLANATION: A character constant was used in an assignment statement where a numeric value is required.

EXT_ARIREQ

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Arithmetic expression required

EXPLANATION: A logical expression was used in an arithmetic IF statement.

EXT_ASFARGNAM

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Statement function argument name same as non-variable

EXPLANATION: A statement function dummy argument had the same name as an entity other than a variable or a common block (for example, a PARAMETER constant).

EXT_COM

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: nonstandard comment

EXPLANATION: FORTRAN-77 allows only the characters "C" and "*" to begin a comment line; "c", "D", "d", and "!" are extensions to FORTRAN-77.

EXT_CONST

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: nonstandard constant

EXPLANATION: The following constant forms are extensions to FORTRAN-77:

Form Example --------- ------------------ Hollerith nH..... Typeless 'nnnn'B, B'nnnn', 'nnnn'X, X'nnnn', 'nnnn'O, O'nnnn', 'nnnn'Z, Z'nnnn' Binary B'nn' Octal "oooo or Ooooo Hexadecimal Znnnn Radix-50 nR..... Complex with PARAMETER components COMPLEX*16 (www.xxxDn, yyy.zzzDn) REAL*16 yyy.zzzQn

EXT_DOEXPR

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Nonstandard loop expression

EXPLANATION: The upper bound expression, lower bound expression, or increment expression of a DO loop was not of type integer, real, or double precision.

EXT_FMT

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: nonstandard FORMAT statement item

EXPLANATION: The following format field descriptors are extensions to FORTRAN-77:

$,O,Z All forms A,L,I,F,E,G,D Default field width forms P Without scale factor

EXT_INTREQ

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Integer expression required

EXPLANATION: One of the following items was not of type integer:

o A logical unit number

o The record specifier, REC=recspec

o The arithmetic expression of a computed GOTO statement

o The RETURN [I]

o A subscript expression

o Array dimension bounds

o Character substring bounds expressions

EXT_INVINTARG

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Nonstandard use of intrinsic function as actual argument

EXPLANATION: The FORTRAN-77 standard does not permit the use of the type conversion (INT, DBLE, etc.), lexical relationship (LGE, LGT, etc.) or minimum or maximum functions (MIN, MAX, etc.) as actual arguments.

EXT_KEY

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: nonstandard keyword

EXPLANATION: A nonstandard keyword was used.

EXT_LEX

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: nonstandard lexical item

EXPLANATION: One of the following nonstandard lexical items was used:

o An alternate return specifier with an ampersand (&) in a CALL statement

o The apostrophe (') form of record specifier in a direct access I/O statement

o A variable format expression

EXT_LOGREQ

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Logical expression required

EXPLANATION: One of the following syntax extensions was detected:

o A numeric expression was used in a logical IF statement.

o A numeric expression was used in a block IF statement.

o A value other than .TRUE. or .FALSE. was assigned to a logical variable.

o A logical variable was initialized with a nonlogical value by means of a DATA statement.

EXT_NAME

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: nonstandard name

EXPLANATION: A name longer than six characters or containing a dollar sign ($) or an underscore (_) was used.

EXT_OPER

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: nonstandard operator

EXPLANATION: The operators .XOR., %VAL, %REF, %DESCR, and %LOC are extensions to FORTRAN-77. The standard form of .XOR. is .NEQV. The % operators are extensions provided to allow access to non-Fortran parts of the VMS environment.

EXT_RETTYP

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: Nonstandard function return type

EXPLANATION: One of the following conditions was detected:

o The function was not declared with a standard data type.

o The entry point was not declared with a standard data type.

EXT_SOURC

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: tab indentation or lowercase source

EXPLANATION: The use of tab indention or lowercase letters in source code is an extension to FORTRAN-77.

EXT_STMT

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: nonstandard statement type

EXPLANATION: A nonstandard statement type was used.

EXT_SYN

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77: nonstandard syntax

EXPLANATION: One of the following syntax extensions was specified:

o PARAMETER name = value Error: Typeless syntax without parentheses

o type name/value/ Error: Data initialization in type declaration

o DATA (ch(exp:exp),v=e2)/values/ Error: Substring initialization with implied-DO in DATA statement

o CHARACTER FUNCTION NAME*n Error: Character function length after name

o INCLUDE '(module)' Error: Library-based INCLUDE (only if /STANDARD=MIA)

o CALL name(arg2,,arg3) Error: Null actual argument

o READ (...),iolist Error: Comma between I/O control and element lists

o PARAMETER (name2=ABS(name1)) Error: Function use in PARAMETER

o e1 ** -e2 Error: Two consecutive operators

EXT_TYPE

SEVERITY: I

MESSAGE TEXT: Extension to FORTRAN-77; nonstandard data type specification

EXPLANATION: The following DATA type specifications are extensions to FORTRAN-77. The FORTRAN-77 equivalent is given where available. This message is issued when these types are used in the IMPLICIT statement or in a numeric type statement.

Extension Standard --------- -------- BYTE - LOGICAL*1 - LOGICAL*2 LOGICAL (with /NOI4 specified only) LOGICAL*4 LOGICAL INTEGER*1 - INTEGER*2 INTEGER (with /NOI4 specified only) INTEGER*4 INTEGER REAL*4 REAL REAL*8 DOUBLE PRECISION REAL*16 - COMPLEX*8 COMPLEX COMPLEX*16 - DOUBLE COMPLEX -

FEANOTSUP

SEVERITY: E

MESSAGE TEXT: Feature not supported on this platform

EXPLANATION: Detected a language feature supported on other DEC Fortran platforms that is not suported on this platform.

FEAUNSAXP

SEVERITY: W

MESSAGE TEXT: Feature not supported on Alpha AXP systems

EXPLANATION: Detected a language feature supported on the DEC Fortran for AXP platforms that is not suported on this platform.

FLDNAME

SEVERITY: F

MESSAGE TEXT: Structure field is missing a field name

EXPLANATION: Unnamed fields are not allowed. The effect of an unnamed field can be achieved by using %FILL in place of a field name in a typed data declaration.

FMTEXTCOM

SEVERITY: W

MESSAGE TEXT: Extra comma in format list

EXPLANATION: A format list contained an extra comma.

Example: FORMAT(I4,)

FMTEXTNUM

SEVERITY: E

MESSAGE TEXT: Extra number in format list

EXPLANATION: A format list contained an extraneous number.

Example: FORMAT (I4,3)

FMTINVCHA

SEVERITY: E

MESSAGE TEXT: Format item contains meaningless character

EXPLANATION: An invalid character or a syntax error was detected in a FORMAT statement.

FMTINVCON

SEVERITY: E

MESSAGE TEXT: Constant in format item out of range

EXPLANATION: A numeric value in a FORMAT statement exceeds the allowable range. For information about range limits, see the DEC Fortran Language Reference Manual.

FMTMISNUM

SEVERITY: E

MESSAGE TEXT: Missing number in format list

EXPLANATION: An expected number was missing from a format list.

Example: FORMAT (F6.)

FMTMISSEP

SEVERITY: E

MESSAGE TEXT: Missing separator between format items

EXPLANATION: A required separator character was omitted between fields in a FORMAT statement.

FMTNEST

SEVERITY: E

MESSAGE TEXT: Format groups nested too deeply

EXPLANATION: Format groups cannot be nested beyond eight levels.

FMTPAREN

SEVERITY: E

MESSAGE TEXT: Unbalanced parentheses in format list

EXPLANATION: The number of right parentheses does not match the number of left parentheses.

FMTSIGN

SEVERITY: E

MESSAGE TEXT: Format item cannot be signed

EXPLANATION: A signed constant is valid only with the P format code.

FUNVALUND

SEVERITY: W

MESSAGE TEXT: Function value undefined at end of routine

EXPLANATION: A function did not have its return value defined at the end of the routine.

HOLCOURED

SEVERITY: E

MESSAGE TEXT: Count of Hollerith or Radix-50 constant too large, reduced

EXPLANATION: The value specified by the integer preceding the H or R was greater than the number of characters remaining in the source statement.

IDOINVOP

SEVERITY: F

MESSAGE TEXT: Invalid operation in implied-DO list

EXPLANATION: An invalid operation was attempted in an implied-DO list in a DATA statement; for example, a function reference in the subscript or substring expression of an array or character substring reference.

Example:

DATA (A(SIN(REAL(I))), I=1,10) /101./

IDOINVPAR

SEVERITY: F

MESSAGE TEXT: Invalid DO parameters in implied-DO list

EXPLANATION: An invalid control parameter was detected in an implied-DO list in a DATA statement; for example, an increment of zero.

IDOINVREF

SEVERITY: F

MESSAGE TEXT: Invalid reference to name in implied-DO list

EXPLANATION: A control parameter expression in an implied-DO list in a DATA statement contained a name that was not the name of a control variable within the scope of any implied-DO list. Example:

DATA (A(J), J=1,10),(B(I), I=J,K) /1001./

Both J and K in the second implied-DO list are invalid names.

IDOSYNERR

SEVERITY: F

MESSAGE TEXT: Syntax error in implied-DO list in data initialization

EXPLANATION: Improper syntax was detected in an implied-DO list in data initialization; for example, improperly nested parentheses.

ILDIRSPEC

SEVERITY: I

MESSAGE TEXT: Unrecognized directive ignored

EXPLANATION: A directive with a valid DEC Fortran prefix was encountered in the first 5 columns of a source code statement (such as a DEC Fortran vector directive), but its presence in the context of the specified command qualifiers is inconsistent or the keyword following the prefix (such as CDEC$ or CPAR$) was not recognized.

ILDOPARCTL

SEVERITY: F

MESSAGE TEXT: Illegal parallel DO-loop, control variable must be declared INTEGER

EXPLANATION: Only integer control variables can be used with parallel DO loops.

ILDOPARDIR

SEVERITY: E

MESSAGE TEXT: DO_PARALLEL directive must be followed by DO statement, directive ignored

EXPLANATION: The first executable statement after a DO_PARALLEL compiler directive statement (CPAR$ DO_PARALLEL) must be a DO statement.

ILIDFDIR

SEVERITY: W

MESSAGE TEXT: Loop directive must be followed by DO statement

EXPLANATION: A CDEC$ directive that applies to DO loops was found but no DO loop was found within its range.

ILLBRANCH

SEVERITY: E

MESSAGE TEXT: Illegal branch into or out of parallel DO-loop

EXPLANATION: A branch into or out of a parallel DO loop is not allowed.

ILPARSTMT

SEVERITY: E

MESSAGE TEXT: Statement not permitted inside parallel DO-loop

EXPLANATION: I/O statements and RETURN, STOP, and PAUSE statements are not permitted inside a parallel DO-loop.

IMPDECLAR

SEVERITY: W

MESSAGE TEXT: Use of implicit with declaration warnings

EXPLANATION: An IMPLICIT statement was used in a program compiled with the /WARNINGS=DECLARATIONS qualifier on the FORTRAN command line.

IMPMULTYP

SEVERITY: E

MESSAGE TEXT: Letter mentioned twice in IMPLICIT statement, last type used

EXPLANATION: A letter was given an implicit data type more than once. The last data type given is used.

IMPNONE

SEVERITY: E

MESSAGE TEXT: Untyped name, must be explicitly typed

EXPLANATION: The displayed name was not defined in any data type declaration statement, and an IMPLICIT NONE statement was specified. Check that the name was not accidentally created by an undetected syntax error. Example:

DO 10 I = 1.10

The apparent DO statement is really an assignment to the accidentally created variable DO10I.

IMPSYNERR

SEVERITY: E

MESSAGE TEXT: Syntax error in IMPLICIT statement

EXPLANATION: Improper syntax was used in an IMPLICIT statement.

INCDONEST

SEVERITY: F

MESSAGE TEXT: DO or IF statement incorrectly nested

EXPLANATION: One of the following conditions occurred:

o A statement label specified in a DO statement was used previously. Example:

10 I = I + 1 J = J + 1 DO 10 K=1,10

o A DO loop contains an incomplete DO loop or IF block. Examples:

1. DO 10 I=1,10 J = J + 1 DO 20 K=1,10 J = J + K 10 CONTINUE

The start of the incomplete IF block can be a block IF, ELSE IF, or ELSE statement.

2. DO 10 I=1,10 J = J + I IF (J .GT. 20) THEN J = J - 1 ELSE J = J + 1 10 CONTINUE END IF

INCFILNES

SEVERITY: F

MESSAGE TEXT: INCLUDE files and/or DICTIONARY statements nested too deeply

EXPLANATION: Up to 10 levels of nested INCLUDE files and DICTIONARY statements are permitted.

INCFUNTYP

SEVERITY: F

MESSAGE TEXT: Inconsistent function data types

EXPLANATION: The function name and entry points in a function subprogram must be consistent within one of three groups of data types:

Group 1: All numeric types except REAL*16 and COMPLEX*16 Group 2: REAL*16 and COMPLEX*16 Group 3: Character

Example:

CHARACTER*15 FUNCTION I REAL*4 G ENTRY G

INCLABUSE

SEVERITY: F

MESSAGE TEXT: Inconsistent usage of statement label

EXPLANATION: Labels of executable statements were confused with labels of FORMAT statements or with labels of nonexecutable statements. Example:

GO TO 10 10 FORMAT (I5)

INCLENMOD

SEVERITY: F

MESSAGE TEXT: Incorrect length modifier in declaration

EXPLANATION: An unacceptable length was specified in a data type declaration. For example:

INTEGER PIPES*8

INCMODNAM

SEVERITY: F

MESSAGE TEXT: Module name not found in library

EXPLANATION: When an INCLUDE statement of the form INCLUDE '(module)' is used, several text libraries are searched for the specified module name. These are, in order:

1. Libraries specified on the FORTRAN command line with the /LIBRARY qualifier

2. The library specified using the logical name FORT$LIBRARY

3. The DEC Fortran system text library, SYS$LIBRARY:FORSYSDEF.

The INCMODNAM message is issued when the specified module name cannot be found in any of the libraries. Note that one of the causes of this search failure may be an open failure on one of the libraries. If a "$LIBRARY/LIST" command shows the module to be present in the library, check to ensure that the library itself can be read by the compiler.

INCNOTSUP

SEVERITY: F

MESSAGE TEXT: INCLUDE not supported for current source file device

EXPLANATION: An INCLUDE statement was found while the current source device was not random-access, for example a tape drive or a terminal. The compiler requires that it be able to close and later reopen and reposition the source file before processing an INCLUDE statement.

INCOPEFAI

SEVERITY: F

MESSAGE TEXT: Open failure on INCLUDE file

EXPLANATION: The specified file could not be opened, possibly because of an incorrect file specification, nonexistent file, unmounted volume, or protection violation.

INCOPNFORT

SEVERITY: W

MESSAGE TEXT: Unable to open text library defined by FORT$LIBRARY

EXPLANATION: In an attempt to include a text library, the compiler was unable to open the text library defined by the logical name FORT$LIBRARY.

INCOPNSYSL

SEVERITY: W

MESSAGE TEXT: Open error opening include file SYS$LIBRARY:FORSYSDEF.TLB

EXPLANATION: In an attempt to include a module from DEC Fortran's symbolic definition library (FORSYSDEF), the compiler was unable to locate the library. (FORSYSDEF contains DEC Fortran source definitions for related groups of system symbols.)

INCSTAFUN

SEVERITY: W

MESSAGE TEXT: Inconsistent statement function reference

EXPLANATION: The actual arguments in a statement function reference did not agree in either order, number, or data type with the formal arguments declared.

INCSYNERR

SEVERITY: F

MESSAGE TEXT: Syntax error in INCLUDE file specification

EXPLANATION: The file-name string was not acceptable (invalid syntax, invalid qualifier, undefined device, and so on).

INQUNIT

SEVERITY: F

MESSAGE TEXT: Missing or invalid use of UNIT or FILE specifier in INQUIRE statement

EXPLANATION: An INQUIRE statement must have a UNIT specifier or a FILE specifier, but not both.

INSVIRMEM

SEVERITY: F

MESSAGE TEXT: Insufficient virtual memory to complete compilation

EXPLANATION: The compiler was not able to acquire sufficient virtual memory in order to complete the compilation.

USER ACTION: Increase your process page file quota (AUTHORIZE quota PGFLQUO) and/or the system virtual page count limit (SYSGEN parameter VIRTUALPAGECNT), specify the /NOOPTIMIZE compile command qualifier or reduce the size or complexity of the compilation unit.

INTACTARG

SEVERITY: W

MESSAGE TEXT: Intrinsic routine used as actual argument should be named in INTRINSIC statement

EXPLANATION: An identifier which had been previously used as an intrinsic routine was used as an actual argument, but was not named in an INTRINSIC statement. The compiler assumed that the intrinsic routine of that name was intended.

USER ACTION: If the identifier is intended to be a routine name, declare it in an EXTERNAL or INTRINSIC statement as appropriate.

This message can be suppressed with /WARNINGS=NOUSAGE.

INTFUNARG

SEVERITY: E

MESSAGE TEXT: Arguments incompatible with intrinsic function, assumed EXTERNAL

EXPLANATION: A function reference was made using an intrinsic function name, but the argument list does not agree in order, number, or type with the intrinsic function requirements. When this error occurs, the function is assumed to be supplied by you as an EXTERNAL function.

INTVALREQ

SEVERITY: F

MESSAGE TEXT: Non-integer expression where integer value required

EXPLANATION: An expression that must be of type integer was another data type.

INVACTARG

SEVERITY: E

MESSAGE TEXT: Invalid use of intrinsic function name as actual argument

EXPLANATION: A generic name of an intrinsic function was used as an actual argument.

INVASSVAR

SEVERITY: E

MESSAGE TEXT: Invalid ASSOCIATEVARIABLE specification

EXPLANATION: An ASSOCIATEVARIABLE specification in an OPEN or DEFINE FILE statement was a dummy argument or an array element.

INVCHASOU

SEVERITY: W

MESSAGE TEXT: Invalid character treated as blank

EXPLANATION: A nonprinting character was found in a source line and was replaced by a space (blank) character. The value of the last nonprinting character found in a source line appears within the message in the form [CHAR(nnn)], where nnn is the decimal value of the nonprinting character.

For more information on valid nonprinting characters in source files, see your user manual.

INVCHAUSE

SEVERITY: E

MESSAGE TEXT: Invalid character used in constant

EXPLANATION: An invalid character was used in a constant. Valid characters are:

Hexadecimal: 0 - 9, A - F, a - f Octal: 0 - 7 Binary: 0 - 1 Radix-50: A - Z, 0 - 9, $, period, or space

For Radix-50, a space is substituted for the invalid character. For hexadecimal and octal, the entire constant is set to zero.

INVCONST

SEVERITY: E

MESSAGE TEXT: Arithmetic error while evaluating constant or constant expression

EXPLANATION: The specified value of a constant was too large or too small to be represented.

INVCONSTR

SEVERITY: F

MESSAGE TEXT: Invalid control structure using ELSE IF, ELSE, or END IF

EXPLANATION: The order of ELSE IF, ELSE, or END IF statements is incorrect.

ELSE IF, ELSE, and END IF statements cannot stand alone. ELSE IF and ELSE must be preceded by either a block IF statement or an ELSE IF statement. END IF must be preceded by either a block IF, ELSE IF, or ELSE statement. Examples:

1. DO 10 I=1,10 J = J + I ELSE IF (J .LE. K) THEN

Error: ELSE IF preceded by a DO statement.

2. IF (J .LT. K) THEN J = I + J ELSE J = I - J ELSE IF (J .EQ. K) THEN END IF

Error: ELSE IF preceded by an ELSE statement.

INVDEVSPE

SEVERITY: E

MESSAGE TEXT: Invalid device specified, analysis data file not produced

EXPLANATION: The file specified by the /ANALYSIS_DATA qualifier could not be written because it was not a random access file.

INVDOTERM

SEVERITY: W

MESSAGE TEXT: Statement cannot terminate a DO loop

EXPLANATION: The terminal statement of a DO loop cannot be a GO TO, arithmetic IF, block IF, RETURN, ELSE, ELSE IF, END IF, DO, or END statement.

INVDUMARG

SEVERITY: E

MESSAGE TEXT: Dummy argument invalid in parallel memory directive

EXPLANATION: Dummy arguments cannot be specified on a parallel memory directive.

INVENDKEY

SEVERITY: W

MESSAGE TEXT: Invalid END= keyword, ignored

EXPLANATION: The END keyword was used illegally in a WRITE, REWRITE, direct access READ, or keyed access READ statement.

INVENTRY

SEVERITY: E

MESSAGE TEXT: ENTRY within DO loop or IF block, statement ignored

EXPLANATION: An ENTRY statement is not allowed within the range of a DO loop or IF block.

INVEQVCOM

SEVERITY: F

MESSAGE TEXT: Invalid equivalence of two variables in common

EXPLANATION: Variables in common blocks cannot be equivalenced to each other.

INVFUNUSE

SEVERITY: F

MESSAGE TEXT: Invalid use of function name in CALL statement

EXPLANATION: A CALL statement referred to a subprogram name that was used as a CHARACTER, REAL*16, or COMPLEX*16 function. Example:

IMPLICIT CHARACTER*10(C) CSCAL = CFUNC(X) CALL CFUNC(X)

INVINIVAR

SEVERITY: E

MESSAGE TEXT: Invalid initialization of variable not in common

EXPLANATION: An attempt was made in a BLOCK DATA subprogram to initialize a variable that was not in a common block.

INVINTFUN

SEVERITY: E

MESSAGE TEXT: Name used in INTRINSIC statement is not an intrinsic function

EXPLANATION: A function name which appeared in the INTRINSIC statement was not an intrinsic function.

INVIOSPEC

SEVERITY: F

MESSAGE TEXT: Invalid I/O specification for this type of I/O statement

EXPLANATION: A syntax error occurred in the portion of an I/O statement that precedes the I/O list. Examples:

1. TYPE (6), J

2. WRITE 100, J

INVKEYOPE

SEVERITY: F

MESSAGE TEXT: Incorrect keyword in OPEN, CLOSE, or INQUIRE statement

EXPLANATION: An OPEN, CLOSE, or INQUIRE statement contained an invalid keyword.

INVLEFSID

SEVERITY: F

MESSAGE TEXT: Left side of assignment must be variable or array element

EXPLANATION: The symbolic name to which the value of an expression is assigned must be a variable, array element, or character substring reference.

INVLEXEME

SEVERITY: F

MESSAGE TEXT: Variable name, constant, or expression invalid in this context

EXPLANATION: An entity was used incorrectly; for example, the name of a subprogram was used where an arithmetic expression was required.

INVLOGIF

SEVERITY: F

MESSAGE TEXT: Statement cannot appear in logical IF statement

EXPLANATION: A logical IF statement must not contain a DO statement or another logical IF, IF THEN, ELSE IF, ELSE, END IF, or END statement.

INVNMLELE

SEVERITY: F

MESSAGE TEXT: Invalid namelist element

EXPLANATION: An element other than a variable or array name appeared in a namelist declaration.

INVNUMSUB

SEVERITY: F

MESSAGE TEXT: Number of subscripts does not match array declaration

EXPLANATION: More or fewer dimensions than were declared for the array were referenced.

INVPERARG

SEVERITY: F

MESSAGE TEXT: Invalid argument to %VAL, %REF, %DESCR, or %LOC

EXPLANATION: The argument specified for one of the built-in functions was not valid. Examples:

%VAL (3.5D0) Error: Argument cannot be REAL*8, REAL*16, character, or complex. %LOC (X+Y) Error: Argument must not be an expression.

INVPERUSE

SEVERITY: E

MESSAGE TEXT: %VAL, %REF, or %DESCR used in invalid context

EXPLANATION: The argument list built-in functions (%VAL, %REF, and %DESCR) cannot be used outside an actual argument list. Example:

X = %REF(Y)

INVQUAL

SEVERITY: I

MESSAGE TEXT: Invalid qualifier or qualifier value in OPTIONS statement

EXPLANATION: An invalid qualifier or qualifier value was specified in the OPTIONS statement. When this error occurs, the qualifier is ignored.

INVRECUSE

SEVERITY: F

MESSAGE TEXT: Invalid use of record or array name

EXPLANATION: A statement in the program violated one of the following rules:

o An aggregate cannot be assigned to a nonaggregate or to an aggregate with a structure that is not the same.

o An array name reference cannot be qualified.

o Aggregate references cannot be used in I/O lists of formatted I/O statements.

o An aggregate or array cannot be passed as an expression in an actual argument list.

INVREPCOU

SEVERITY: E

MESSAGE TEXT: Invalid repeat count in data initialization, count ignored

EXPLANATION: The repeat count in a data initialization was not an unsigned, nonzero integer constant. When this error occurs, the count is ignored.

INVSBSREF

SEVERITY: E

MESSAGE TEXT: Substring reference used in invalid context

EXPLANATION: A substring reference was made to a variable or array that is not of type CHARACTER. Example:

REAL X(10) Y = X(J:K)

INVSTALAB

SEVERITY: W

MESSAGE TEXT: Invalid statement label ignored

EXPLANATION: An improperly formed statement label (namely, a label containing letters) appeared in columns 1 to 5 of an initial line. When this error occurs, the statement label is ignored.

INVSUBREF

SEVERITY: F

MESSAGE TEXT: Subscripted reference to non-array variable

EXPLANATION: A variable that is not defined as an array cannot appear with subscripts.

INVTYPUSE

SEVERITY: F

MESSAGE TEXT: Name previously used with conflicting data type

EXPLANATION: A data type was assigned to a name that had already been used in a context that required a different data type.

IODUPKEY

SEVERITY: F

MESSAGE TEXT: Duplicated keyword in I/O statement

EXPLANATION: Each keyword subparameter in an I/O statement or auxiliary I/O statement can be specified only once.

IOINVFMT

SEVERITY: F

MESSAGE TEXT: Format specifier in error

EXPLANATION: The format specifier in an I/O statement is invalid. It must be one of the following:

o The label of a FORMAT statement.

o An asterisk (*) in a list-directed I/O statement.

o A run-time format specifier: a variable, array element, or character substring reference.

o An integer variable that was assigned a FORMAT label by an ASSIGN statement.

IOINVKEY

SEVERITY: F

MESSAGE TEXT: Invalid keyword for this type of I/O statement

EXPLANATION: An I/O statement contained a keyword that cannot be used with that type of I/O statement.

IOINVLIST

SEVERITY: F

MESSAGE TEXT: Invalid I/O list element for input statement

EXPLANATION: An input statement I/O list contained an invalid element, such as an expression or a constant.

IOSYNERR

SEVERITY: F

MESSAGE TEXT: Syntax error in I/O list

EXPLANATION: Improper syntax was detected in an I/O list.

LABASSIGN

SEVERITY: F

MESSAGE TEXT: Label in ASSIGN statement exceeds INTEGER*2 range

EXPLANATION: A label whose value is assigned to an INTEGER*2 variable by an ASSIGN statement must not be separated by more than 32K bytes from the beginning of the code for the program unit.

LENCHAFUN

SEVERITY: E

MESSAGE TEXT: Length specified must match CHARACTER FUNCTION declaration

EXPLANATION: The length specifications for all ENTRY names in a character function subprogram must be the same. Example:

CHARACTER*15 FUNCTION F CHARACTER*20 G ENTRY G

LOGVALREQ

SEVERITY: F

MESSAGE TEXT: Non-logical expression where logical value required

EXPLANATION: An expression that must be of type LOGICAL was of another data type.

LOG4LCKREQ

SEVERITY: E

MESSAGE TEXT: Lock variable must be declared LOGICAL*4

EXPLANATION: The lock entity used in a LOCKON or LOCKOFF directive must be declared to be LOGICAL*4.

LOWBOUGRE

SEVERITY: E

MESSAGE TEXT: Lower bound greater than upper bound in array declaration

EXPLANATION: The upper bound of a dimension declarator must be equal to or greater than the lower bound.

LSEDIAGS

SEVERITY: I

MESSAGE TEXT: Additional diagnostics written to LSE diagnostics file

EXPLANATION: Additional data dependence diagnostics were written to the VAX Language-Sensitive Editor diagnostics file and can be reviewed in the editor.

MINDIGITS

SEVERITY: I

MESSAGE TEXT: CDD description specifies precision less than allowed for data type. Minimum precision is supplied.

EXPLANATION: Some Common Data Dictionary data types specified a number of digits that is incompatible with DEC Fortran data types. When this error occurs, the DEC Fortran compiler expands the data type to conform to a DEC Fortran data type.

MINOCCURS

SEVERITY: I

MESSAGE TEXT: CDD description contains Minimum Occurs attribute (ignored)

EXPLANATION: DEC Fortran does not support the Common Data Dictionary Minimum Occurs attribute.

MISSAPOS

SEVERITY: E

MESSAGE TEXT: Missing apostrophe in character constant

EXPLANATION: A character constant must be enclosed by apostrophes.

MISSCOM

SEVERITY: F

MESSAGE TEXT: Missing common block name

EXPLANATION: A common block name was omitted or specified improperly on a SHARED directive.

MISSCONST

SEVERITY: F

MESSAGE TEXT: Missing constant

EXPLANATION: A required constant was not found.

MISSDEL

SEVERITY: F

MESSAGE TEXT: Missing operator or delimiter symbol

EXPLANATION: Two terms of an expression were not separated by an operator, or a punctuation mark (such as a comma) was omitted. Examples:

CIRCUM = 3.14 DIAM IF (I 10,20,30

MISSEND

SEVERITY: E

MESSAGE TEXT: Missing END statement, END is assumed

EXPLANATION: An END statement was missing at the end of the last input file. When this error occurs, an END statement is inserted.

MISSEXPO

SEVERITY: E

MESSAGE TEXT: Missing exponent after E, D, or Q

EXPLANATION: A floating-point constant was specified in E, D, or Q notation, but the exponent was omitted.

MISSKEY

SEVERITY: F

MESSAGE TEXT: Missing keyword

EXPLANATION: A required keyword, such as TO, was omitted from a statement such as ASSIGN 10 TO I.

MISSLABEL

SEVERITY: F

MESSAGE TEXT: Missing statement label

EXPLANATION: A required statement label reference was omitted.

MISSNAME

SEVERITY: F

MESSAGE TEXT: Missing variable or subprogram name

EXPLANATION: A required variable name or subprogram name was not found.

MISSUNIT

SEVERITY: F

MESSAGE TEXT: Unit specifier keyword missing in I/O statement

EXPLANATION: An I/O statement must include a unit specifier subparameter.

MISSVAR

SEVERITY: F

MESSAGE TEXT: Missing variable or constant

EXPLANATION: An expression, or a term of an expression, was omitted. Examples:

WRITE ( ) DIST = *TIME

MISSVARCOM

SEVERITY: E

MESSAGE TEXT: Missing variable or common name

EXPLANATION: A name of a variable or a common block that is required by a compiler directive statement or a VOLATILE statement was omitted.

MULDECNAM

SEVERITY: F

MESSAGE TEXT: Multiple declaration of name

EXPLANATION: A name appeared in two or more inconsistent declaration statements or a dummy argument was specified in an EQUIVALENCE statement.

MULDECTYP

SEVERITY: E

MESSAGE TEXT: Multiple declaration of data type for variable, first type used

EXPLANATION: A variable appeared in more than one data type declaration statement. When this error occurs, the first type declaration is used.

MULDEFLAB

SEVERITY: E

MESSAGE TEXT: Multiple definition of statement label, second ignored

EXPLANATION: The same label appeared on more than one statement. When this error occurs, the first occurrence of the label is used.

MULFLDNAM

SEVERITY: F

MESSAGE TEXT: Multiply defined field name

EXPLANATION: Each field name within the same level of a given structure declaration must be unique.

MULSPEPAR

SEVERITY: E

MESSAGE TEXT: Multiple specification of parallel memory attributes, first specification used

EXPLANATION: A variable, array, record, or COMMON block was a given memory attributes (shared and private or context-shared and private) in a parallel directive. When this error occurs, the first attribute specified is the one that is used.

MULSTRNAM

SEVERITY: F

MESSAGE TEXT: Multiply defined STRUCTURE name

EXPLANATION: A STRUCTURE name must be unique among STRUCTURE names.

NAMTOOLON

SEVERITY: W

MESSAGE TEXT: Name longer than 31 characters

EXPLANATION: A symbolic name cannot exceed 31 characters. When this error occurs, the symbolic name is truncated to 31 characters.

NESTPARDO

SEVERITY: E

MESSAGE TEXT: Nested parallel DO-loops not permitted, directive ignored

EXPLANATION: A parallel DO-loop directive (CPAR$ DO_PARALLEL) was detected within a DO-loop that was already marked as parallel. Nested parallel DO-loop directives are not supported.

NMLIOLIST

SEVERITY: E

MESSAGE TEXT: I/O list not permitted with namelist I/O

EXPLANATION: An I/O statement with a namelist specifier incorrectly contained an I/O list.

NODEPCOMMN

SEVERITY: I

MESSAGE TEXT: Dependence analysis inhibited due to call in DO-loop and COMMON loop control variable

EXPLANATION: Dependence analysis is not performed on DO-loops that have a control variable specified within a COMMON block and a reference to an external routine. The analysis is not done because of the potential for changing the control variable in the external routine.

NODEPDEEP

SEVERITY: I

MESSAGE TEXT: Dependence analysis inhibited due to more than 7 loops nested inside DO-loop

EXPLANATION: Dependence analysis is not performed on DO-loops that have more than seven levels of nesting.

NODEPEQUIV

SEVERITY: I

MESSAGE TEXT: Dependence analysis inhibited due to EQUIVALENCEd loop control variable

EXPLANATION: Dependence analysis is not performed on DO-loops that have a control variable that is also specified in an EQUIVALENCE statement.

NODEPFLOW

SEVERITY: I

MESSAGE TEXT: Dependence analysis inhibited due to transfer into or out of DO-loop

EXPLANATION: Dependence analysis is not performed on DO-loops that contain transfers into or out of the loop. A STOP or RETURN is considered as a transfer out of a DO-loop.

NODEPINT4

SEVERITY: I

MESSAGE TEXT: Dependence analysis inhibited due to non-integer control variable

EXPLANATION: Dependence analysis is not performed on DO-loops that have a non-integer control variable. (Note - INTEGER*2 is now allowed.)

NODEPNEST

SEVERITY: I

MESSAGE TEXT: Dependence analysis inhibited due to inhibitor in loop nested inside DO-loop

EXPLANATION: Dependence analysis is not performed on DO-loops that contain a nested DO-loop with inhibitors.

NODEPOVLP

SEVERITY: I

MESSAGE TEXT: Dependence analysis inhibited due to potential overlap dummy arguments and common variables in DO-loop

EXPLANATION: Dependence analysis is not performed on DO-loops that contain references and stores into dummy arguments and variables in a common block. The potential for dummy arguments and variables in common blocks being aliased is the reason for this inhibitor. This error is partially controlled by the setting of the /ASSUME=[NO]DUMMY_ALIASES qualifier.

NODEPPAR

SEVERITY: I

MESSAGE TEXT: Dependence analysis inhibited due to parallel loop nested inside DO-loop

EXPLANATION: Dependence analysis is not performed on DO-loops that contain a nested parallel DO-loop that was established by a compiler directive statement (directed decomposition).

NODEPSTMT

SEVERITY: I

MESSAGE TEXT: Dependence analysis inhibited due to use of inhibitor statement inside DO-loop

EXPLANATION: Dependence analysis is not performed on DO-loops that contain any of the following statements:

o An assigned GOTO

o A computed GOTO

o A character function invocation

o A LOCKON or LOCKOFF directive

o A format containing a variable format expression was referenced in an I/O statement within the DO-loop

NODEPVOLAT

SEVERITY: I

MESSAGE TEXT: Dependence analysis inhibited due to volatile control variable

EXPLANATION: Dependence analysis is not performed on DO-loops that have a control variable that is declared volatile.

NODFLOAT

SEVERITY: W

MESSAGE TEXT: CDD description specifies the D_floating data type. The data cannot be represented when compiling /G_FLOAT.

EXPLANATION: A D_floating data type was specified when compiling with the /G_FLOATING qualifier. Ignore the warning message or recompile the program using the /NOG_FLOATING qualifier.

NOGFLOAT

SEVERITY: W

MESSAGE TEXT: CDD description specifies G_floating data type. The data cannot be represented when compiling /NOG_FLOAT.

EXPLANATION: A G_floating data type was specified when compiling with the /NOG_FLOATING qualifier. Ignore the warning message or recompile the program using the /G_FLOAT qualifier.

NONCONSUB

SEVERITY: F

MESSAGE TEXT: Nonconstant subscript where constant required

EXPLANATION: Subscript and substring expressions used in DATA and EQUIVALENCE statements must be constants.

NOPATH

SEVERITY: W

MESSAGE TEXT: No path to this statement

EXPLANATION: Program control cannot reach this statement. When this error occurs, the statement is deleted. Example:

10 I = I + 1 GO TO 10 STOP

NOPPARVEC

SEVERITY: W

MESSAGE TEXT: /NOOPTIMIZE conflicts /PARALLEL=AUTOMATIC or /VECTOR

EXPLANATION: When you specify /PARALLEL=AUTOMATIC or /VECTOR, you must omit /NOOPTIMIZE.

NOSOUFILE

SEVERITY: F

MESSAGE TEXT: No source file specified

EXPLANATION: A command line was entered that specified only library file names and no source files to compile.

NOTINLINED

SEVERITY: I

MESSAGE TEXT: Intrinsic reference was not expanded inline

EXPLANATION: The reference to a BLAS intrinsic routine could not be expanded into inline code.

NOVECACCU

SEVERITY: I

MESSAGE TEXT: Vectorization inhibition: Qualifier /ASSUME=ACCURACY prevents recurrence vectorization

EXPLANATION: Vectorization is not performed. The /ASSUME=ACCURACY_SENSITIVE option prevents recurrence vectorization.

NOVECALIGN

SEVERITY: I

MESSAGE TEXT: Vectorization inhibition: Misaligned array

EXPLANATION: Vectorization is not performed. Data for vector instructions must be aligned on natural boundaries, based on the data type. An array is aligned on natural boundaries if all its elements are so aligned.

NOVECDTARR

SEVERITY: I

MESSAGE TEXT: Vectorization inhibition: Data type not supported for array

EXPLANATION: Vectorization is not performed because the data type is not supported for the array.

NOVECDTIND

SEVERITY: I

MESSAGE TEXT: Vectorization inhibition: Use of unsupported data type in array index

EXPLANATION: Vectorization is not performed because an unsupported data type is used in the array index.

NOVECSUBP

SEVERITY: I

MESSAGE TEXT: Vectorization inhibition: Reference to subprogram

EXPLANATION: Vectorization is not performed for data that can be modified in the subprogram.

NOVECVOLARR

SEVERITY: I

MESSAGE TEXT: Vectorization inhibition: Use of volatile array

EXPLANATION: Vectorization is not performed. Volatile arrays have dependences the compiler is unaware of; thus, they cannot be vectorized.

NOVECVOLIND

SEVERITY: I

MESSAGE TEXT: Vectorization inhibition: Use of volatile array index

EXPLANATION: Vectorization is not performed. The compiler cannot identify all dependences for volatile array indexes; thus, they cannot be vectorized.

OPEDOLOOP

SEVERITY: F

MESSAGE TEXT: Unclosed DO loop or IF block

EXPLANATION: The terminal statement of a DO loop or the END IF statement of an IF block was not found. Example:

DO 20 I=1,10 X = Y END

OPENIN

SEVERITY: F

MESSAGE TEXT: Error opening "file-spec" as input

EXPLANATION: Unable to open the file "file-spec".

OPENOTPER

SEVERITY: F

MESSAGE TEXT: Operation not permissible on these data types

EXPLANATION: An invalid operation was specified, such as an .AND. of two real variables.

OPENOUT

SEVERITY: F

MESSAGE TEXT: Error opening "file-spec" as output

EXPLANATION: Unable to open the file "file-spec".

OPTLV4CHK

SEVERITY: W

MESSAGE TEXT: /OPTIMIZE=LEVEL=4 conflicts with /CHECK=BOUNDS; /OPTIMIZE=LEVEL=4 ignored

EXPLANATION: When you specify /CHECK=BOUNDS, you cannot use /OPTIMIZE=LEVEL=4. A lower level of optimization has been used.

PARCHKCON

SEVERITY: W

MESSAGE TEXT: /PARALLEL=AUTOMATIC conflicts with /CHECK=BOUNDS

EXPLANATION: When you specify /CHECK=BOUNDS, you cannot use /PARALLEL=AUTOMATIC. /PARALLEL=NOAUTOMATIC was used.

PLACEEOL

SEVERITY: F

MESSAGE TEXT: Placeholder not terminated before end of line

EXPLANATION: The closing delimiter of a placeholder was not found before the end of the line.

PLACENODESIGN

SEVERITY: E

MESSAGE TEXT: Placeholder not valid without /DESIGN=PLACEHOLDERS

EXPLANATION: A placeholder was found but /DESIGN=PLACEHOLDERS was not specified on the compile command line.

PLACENODOT

SEVERITY: E

MESSAGE TEXT: Repetition of pseudocode placeholder not allowed

EXPLANATION: A pseudocode placeholder was found with three dots after it, indicating a list placeholder, which is not supported.

PLACENOOBJ

SEVERITY: I

MESSAGE TEXT: Placeholders detected - no object code generated

EXPLANATION: One or more placeholders were found in the current compilation unit and so no object code was generated for that unit.

PLACENOTVAL

SEVERITY: E

MESSAGE TEXT: Placeholder not valid in this context

EXPLANATION: A placeholder was found in a context that is not supported.

PROSTOREQ

SEVERITY: F

MESSAGE TEXT: Program storage requirements exceed addressable memory

EXPLANATION: The storage space allocated to the variables and arrays of the program unit exceeded the addressing range of the machine.

PRVCTLVAR

SEVERITY: I

MESSAGE TEXT: Control variable for parallel loop defaulting to PRIVATE

EXPLANATION: The control variable for a parallel DO loop was not explicitly declared private.

PRVSYMIL

SEVERITY: E

MESSAGE TEXT: PRIVATE symbol invalid in routine without parallel DO-loop

EXPLANATION: Symbols declared within a routine that does not contain a parallel DO loop cannot be listed in a PRIVATE directive.

READERR

SEVERITY: F

MESSAGE TEXT: Error reading "file-spec"

EXPLANATION: Unable to read from file "file-spec".

RECPARCON

SEVERITY: W

MESSAGE TEXT: /RECURSIVE conflicts with /PARALLEL; /RECURSIVE ignored

EXPLANATION: If you specify /PARALLEL, you must omit /RECURSIVE. Compilation uses /PARALLEL but ignores /RECURSIVE.

REDCONMAR

SEVERITY: W

MESSAGE TEXT: Redundant continuation mark ignored

EXPLANATION: A continuation mark was used where an initial line is required. When this error occurs, the continuation mark is ignored.

REFERENCE

SEVERITY: I

MESSAGE TEXT: CDD description contains Reference attribute (ignored)

EXPLANATION: Fortran does not support the CDD Reference attribute.

ROUREFREC

SEVERITY: F

MESSAGE TEXT: Routine referenced recursively; /RECURSIVE required

EXPLANATION: A subroutine, function or entry name was referenced recursively in the same program unit, but the /RECURSIVE command or OPTIONS statement qualifier was not specified.

ROWMAJOR

SEVERITY: I

MESSAGE TEXT: Bounds reversed for CDD member row-major array

EXPLANATION: A row-major multi-dimensioned array was found in a CDD record. The bounds were reversed to allow for Fortran column-major array addressing.

SAVPRICONF

SEVERITY: E

MESSAGE TEXT: PRIVATE variable or common block must not be declared SAVE

EXPLANATION: Symbols cannot be declared in both a SAVE statement and a PRIVATE directive or common block.

SHRCTLVAR

SEVERITY: E

MESSAGE TEXT: Control variable for parallel DO-loops must be declared PRIVATE

EXPLANATION: The control variable for a parallel DO-loop was explicitly declared SHARED. Control variables for parallel DO-loops must be explicitly declared PRIVATE.

SHRNAMLON

SEVERITY: E

MESSAGE TEXT: Shared COMMON name too long, limited to 26 characters

EXPLANATION: The maximum length of a COMMON block name specified in a SHARED compiler directive statement is 26 characters.

SOURCETYPE

SEVERITY: I

MESSAGE TEXT: CDD description contains Source Type attribute (ignored)

EXPLANATION: DEC Fortran does not support the CDD Source Type attribute.

STAENDSTR

SEVERITY: F

MESSAGE TEXT: Statement not allowed within structure; structure definition closed

EXPLANATION: A statement not allowed in a structure declaration block was encountered. When this error occurs, the compiler assumes that you omitted one or more END STRUCTURE statements.

STAINVSTR

SEVERITY: E

MESSAGE TEXT: Statement not allowed within structure definition; statement ignored

EXPLANATION: A statement not allowed in a structure declaration block was encountered. Structure declaration blocks can only include the following statements: typed data declaration statements, RECORD statements, UNION/END UNION statements, MAP/END MAP statements, and STRUCTURE/END STRUCTURE statements.

STANOTVAL

SEVERITY: E

MESSAGE TEXT: Statement not valid in this program unit, statement ignored

EXPLANATION: A program unit contained a statement that is not allowed; for example, a BLOCK DATA subprogram containing an executable statement.

STAOUTORD

SEVERITY: E

MESSAGE TEXT: Statement out of order, statement ignored

EXPLANATION: A statement was used in a place where it does not belong. When this error occurs, the statement is ignored.

STATOOCOM

SEVERITY: F

MESSAGE TEXT: Statement too complex

EXPLANATION: A statement was too complex to be compiled. It must be subdivided into two or more statements.

STRCONTRU

SEVERITY: E

MESSAGE TEXT: String constant truncated to maximum length

EXPLANATION: A character constant or Hollerith constant can contain up to 2000 characters. A Radix-50 constant can contain up to 12 characters.

STRDEPTH

SEVERITY: F

MESSAGE TEXT: STRUCTUREs/UNIONs/MAPs nested too deeply

EXPLANATION: The combined nesting level limit for structures, unions, and maps is 20 levels.

STRNAME

SEVERITY: E

MESSAGE TEXT: Outer level structure is missing a structure name

EXPLANATION: An outer level STRUCTURE statement must have a structure name in order for a RECORD statement to be able to reference the structure declaration.

STRNOTDEF

SEVERITY: F

MESSAGE TEXT: Structure name in RECORD statement not defined

EXPLANATION: Either a RECORD statement did not contain a structure name enclosed within slashes or the structure name contained in a RECORD statement was not defined in a structure declaration.

SUBEXPVAL

SEVERITY: E

MESSAGE TEXT: Subscript or substring expression value out of bounds

EXPLANATION: A reference was made to either an array element beyond the specified dimensions or a character substring outside the specified bounds.

SUBNOTALL

SEVERITY: F

MESSAGE TEXT: Subqualifier not allowed with negated qualifier

EXPLANATION: A negated qualifier specified on the command line also specified subqualifier values.

For example: /NOCHECK=UNDERFLOW

TAGVARIAB

SEVERITY: I

MESSAGE TEXT: CDD description contains Tag Variable attribute (ignored)

EXPLANATION: DEC Fortran does not support the Common Data Dictionary Tag Variable attribute.

TOOMANCOM

SEVERITY: F

MESSAGE TEXT: Too many named common blocks

EXPLANATION: DEC Fortran allows a maximun of 508 named common blocks. You must reduce the number of named common blocks.

TOOMANCON

SEVERITY: E

MESSAGE TEXT: Too many continuation lines, remainder ignored

EXPLANATION: Up to 99 continuation lines are permitted.

TOOMANDIM

SEVERITY: E

MESSAGE TEXT: More than 7 dimensions specified, remainder ignored

EXPLANATION: An array cannot have more than seven dimensions.

TOOMANYDO

SEVERITY: F

MESSAGE TEXT: DO and IF statements nested too deeply

EXPLANATION: DO loops and block IF statements cannot be nested beyond 128 levels.

UNDARR

SEVERITY: F

MESSAGE TEXT: Undimensioned array or statement function definition out of order

EXPLANATION: Either a statement function definition was found among executable statements or an assignment statement involving an undimensioned array was found.

UNDSTALAB

SEVERITY: F

MESSAGE TEXT: Undefined statement label

EXPLANATION: A reference was made to a statement label that is not defined in the program unit.

UNRECSTMT

SEVERITY: F

MESSAGE TEXT: Unrecognized statement

EXPLANATION: The statement encountered was not recognized as valid.

UNSUPPTYPE

SEVERITY: I

MESSAGE TEXT: CDD description specifies an unsupported data type

EXPLANATION: The Common Data Dictionary description for a structure item attempted to use a data type that is not supported by DEC Fortran.

The DEC Fortran compiler makes the data type accessible by declaring it as an inner structure containing a single unnamed field (%FILL field) that is a LOGICAL*1 array with an appropriate dimension. Change the data type to one that is supported by DEC Fortran or use the DEC Fortran built-in functions to manipulate the contents of the field.

USEUNIVAR

SEVERITY: W

MESSAGE TEXT: Use of initialized variable

EXPLANATION: A variable was used before it was initialized. Initialize the variable before using it.

This message can be suppressed with /WARNINGS=NOUNINITIALIZED.

VARINCEQV

SEVERITY: F

MESSAGE TEXT: Variable inconsistently equivalenced to itself

EXPLANATION: EQUIVALENCE statements specified inconsistent relationships between variables or array elements. Example:

EQUIVALENCE (A(1), A(2))

VARNOTASS

SEVERITY: E

MESSAGE TEXT: Variable not assigned label by ASSIGN statement

EXPLANATION: A variable was found in a context that required an assigned label (such as in an assigned GOTO statement or as the format specifier of an I/O statement), but no ASSIGN statement was found that assigned a label to that variable.

This error commonly occurs if you use an arithmetic assignment statement instead of the ASSIGN statement. If the program executes, the result is unpredictable.

VARUNUSED

SEVERITY: I

EXPLANATION: The specified variable was declared but never used.

This message can be suppressed with /WARNINGS=NOUNUSED.

VAXELNUNS

SEVERITY: W

MESSAGE TEXT: This feature is unsupported on VAXELN

EXPLANATION: The specified DEC Fortran feature is not supported on a VAXELN system.

VECCHKCON

SEVERITY: W

MESSAGE TEXT: /VECTOR conflicts with /CHECK=BOUNDS; /VECTOR ignored

EXPLANATION: When you specify /CHECK=BOUNDS, you cannot use /VECTOR. The /VECTOR qualifier is ignored.

VFUFEANEX

SEVERITY: W

MESSAGE TEXT: This feature is unsupported and non-executable on ULTRIX

EXPLANATION: The program attempted to use a DEC Fortran I/O feature that is not available on ULTRIX systems. If the resulting program is run on an ULTRIX system, a run-time error will be issued if this statement is executed. Major DEC Fortran features not available on ULTRIX include the following:

o OPEN and INQUIRE options:

- ORGANIZATION= 'RELATIVE' or 'INDEXED'

- ACCESS='KEYED'

- RECORDTYPE= 'STREAM' or 'STREAM_CR'

- KEY

- DEFAULTFILE

- USEROPEN

o I/O statements DELETE, REWRITE, and UNLOCK

o Read statement keyword attributes: KEY, KEYEQ, KEYGE, KEYGT, and KEYID

VFUFEAUNS

SEVERITY: W

MESSAGE TEXT: This feature is unsupported on ULTRIX-32

EXPLANATION: The program attempted to use a DEC Fortran I/O feature that is not available on ULTRIX systems. If the resulting program is run on an ULTRIX system, this construct will be ignored. Major DEC Fortran features not available on ULTRIX include the following:

o OPEN statement keywords (and attributes):

- DISPOSE= 'PRINT', 'PRINT/DELETE', 'SUBMIT', 'SUBMIT/DELETE'

- BUFFERCOUNT

- EXTENDSIZE

- INITIALSIZE

- NOSPANBLOCKS

- SHARED

o CLOSE statement keywords (and attributes):

- DISPOSE= 'PRINT', 'PRINT/DELETE', 'SUBMIT', 'SUBMIT/DELETE'

- STATUS

VFUSRCUNA

SEVERITY: W

MESSAGE TEXT: Requested source is not available on ULTRIX

EXPLANATION: The program attempted to use one of the following DEC Fortran I/O features that are not available on ULTRIX systems:

o The DICTIONARY statement

o The INCLUDE statement for a text module from a library file

WRITEERR

SEVERITY: F

MESSAGE TEXT: Error writing "file-spec"

EXPLANATION: Unable to write to file "file-spec".

WRONGCLD

SEVERITY: F

MESSAGE TEXT: Wrong command definition installed - please see your system manager

EXPLANATION: The current command tables do not include the proper definition of the FORTRAN command. This may be due to having installed an older version of the command definition, or the system command tables were updated but a user process is still using an older version.

ZERLENSTR

SEVERITY: E

MESSAGE TEXT: Zero-length string

EXPLANATION: The length specified for a character, Hollerith, hexadecimal, octal, or Radix-50 constant must not be zero.