The following are error messages:
   - Variable or array "#1" cannot be assigned an expression
   of this type. The type of the expression cannot be coerced to
   the type of the target variable or array.
   
 - A .NOT. cannot be applied to an expression of type
   "#1." The logical operator .NOT. cannot be applied to
   expressions of the given type. Some Fortran dialects allow mixing
   of logical and other types in expressions, others do not.
   
 - A closing Parallel directive must be preceded by an
   opening Parallel directive.
   
 - All parameters to the indicated intrinsic function must
   have the same shape (or be conformable).
   
 - An arithmetic expression was expected but not
   found.
   
 - Arithmetic operations are not allowed between these
   types of operands. The arithmetic operator at the position
   given cannot be applied to the mentioned types.
   
 - Array "#1" must be explicitly typed. IMPLICIT NONE
   or UNDEFINED disables automatic typing. All variables occurring
   within the scope of IMPLICIT NONE or UNDEFINED must be explicitly
   typed.
 
   
 - Array bound "#1" is neither a formal parameter nor in
   a COMMON block. A symbol was used in a place where only a
   formal parameter or a variable specified as being in a COMMON
   block is allowed.
   
 - Array declared and referenced with different number of
   subscripts. The array reference has more or less subscripts
   than the number of dimensions in the declaration of this
   variable.
   
 - Array not declared or statement function declared after
   executable statements. A statement function declaration must
   appear before any executable statements.
   
 
   - ASSIGN statement must include the word TO before the
   integer variable name. The format of an ASSIGN statement is
   ASSIGN s TO i, where s is a statement label and i is the name of
   a scalar integer variable. The word TO is missing in this case.
   
 - Assign variable "#1" was never assigned a label.
   The label assign variable has never been assigned.
   
 - Assigned GOTO variable "#1" is not a scalar. The
   variable used to select a branch address must be a scalar (not an
   array element).
   
 - Assigned GOTO variable "#1" is not an integer. The
   variable used to select a branch address must be of type integer.
   
 - ASSIGNed variable "#1" is not a scalar. The
   variable used to store a statement label must be a scalar (not
   an array element).
   
 - ASSIGNed variable "#1" is not an integer. The
   variable used to hold a statement label must be of type integer.
   
 
 
   - Assumed size arrays must specify the upper bound of
   the assumed size dimension. Assumed size arrays may be used
   in array assignments, but the upper bound of the assumed size
   dimension must be specified.
   
 - Asterisk (*) as a dimension bound was specified for an
   invalid dimension. Asterisk may be specified in a dimension
   bound only as the upper bound of the final dimension.
   
 - At least one parameter is required to this intrinsic
   function. At least one parameter must appear in the
   invocation of this intrinsic function. Lookup the intrinsic
   function and code the correct number of parameters.
   
 
   - At least two MAP/ENDMAP statements must appear within a
   UNION/ENDUNION. At least two map declaration constructs must
   appear within any UNION/ENDUNION declaration.
 
   
 - Bit constant is too long or contains characters that
   are not 0 or 1. A bit constant may contain only the digits
   0 or 1. The specified constant contained one or more characters
   that were not 0 or 1.
   
 - Bit operations are only valid on operands of type
   bit. One or more of the operands found were not of type bit.
   
 - Block IF or block WHERE has not been closed. During
   label resolution (after examining the entire program), a block
   construct has been discovered that has not been closed. The
   message is attached to the block IF, ELSEIF, ELSE, block WHERE,
   or OTHERWISE that begins the block that is not closed. Check the
   structure of the program to determine where the error lies.
   
 - Cannot associate entire equivalence group with the
   same storage unit. An EQUIVALENCE statement must not specify
   that the same storage unit is to occur more than once in a
   storage sequence, or that consecutive storage units are to be
   nonconsecutive.
 
   
 - Cannot reference format label here. The label used
   in the format statement is a target of a branch statement.
   
 - Character variable must have a length of one
   character. The character entity must have a length of
   one character if the entity is being initialized by a numeric
   constant.
   
 
   - Closing > is missing from this format expression.
   Expressions within a FORMAT must be enclosed by angle brackets.
   
 
   - Colon in this key specification is missing. Colon
   separating first and last byte position is missing.
   
 - Colon in this substring reference is missing. Colon
   separating lower and upper bounds in a substring reference is
   missing.
 
   
 - Comma was expected here but not found. A comma was
   expected in the indicated column, but another symbol was found
   instead.
   
 - Comparisons are not allowed between these types of
   operands. The comparison operator at position given cannot be
   applied to the mentioned types.
   
 - Compiler directive does not have correct syntax.
   This line seems to have a c*kap* compiler directive on it, but it
   contains a syntax error.
   
 - Concatenation is valid only on character strings.
   Concatenation can only be applied to character strings. One of
   the operands in this concatenation is not a string.
   
 - Constant must have a value in the range 0 through
   255. The constant used to initialize a character entity must
   have a value less than 255.
   
 - Definition of the label "#1" is not unique. An earlier
   definition exists. Each statement label must be unique within
   a program unit. This statement has a label that has been defined
   earlier.
 
   
 - Dimension must be a constant. The dimension in
   question must be a compile-time constant.
   
 
   - DO loop ends on a nonexecutable statement. A
   DO loop ends on a statement that is non-executable. Insert a
   CONTINUE or renumber the DO.
   
 - DO loop has not been closed. The end of a DO loop
   has not been found within this program unit. Find the mismatched
   DO and correct.
   
 - DO loop is improperly nested. This DO loop does not
   begin and end in the same block.
   
 - DO-variable "#1" is not a scalar variable. The
   format of the DO statement is DO [,] i = e1, e2 [,e3]. The "i"
   is the name of an integer, real, or double precision variable,
   called the DO-variable. In this statement, "i" is the name of a
   nonscalar variable, such as an array. Check your array names, or
   change the name of the DO-variable.
   
 - DO-variable "#1" is not a variable. The format of
   the DO statement is DO [,] i = e1, e2 [,e3]. The i is the name
   of an integer, real, or double precision variable, called the
   DO-variable. In this statement, 1 is the name of an entity that
   cannot be used as a variable. Check your SUBROUTINE and FUNCTION
   names.
 
   
 - DO-variable "#1" is not INTEGER, REAL, or DOUBLE
   PRECISION. The format of the DO statement is DO [,] i
   = e1, e2 [,e3]. The i is the name of an integer, real or
   double precision variable, called the DO-variable. In this
   statement, i is not INTEGER, REAL, or DOUBLE PRECISION. Check
   your specification statements or IMPLICIT statements, or change
   the name of the DO-variable.
   
 
   - DO-variable is being assigned within the DO loop.
   The format of the DO statement is DO s [,] i = e1, e2 [,e3]. The
   i is the name of an integer, real, or double precision variable,
   called the DO-variable. It is being assigned within this loop.
   
 
   - Each DO-WHILE DO-loop must be terminated by a separate
   ENDDO statement. A DO-WHILE loop must be terminated by a
   unique ENDDO statement. The label on the DO-WHILE is optional,
   but if it is specified, the terminating ENDDO must be labeled
   accordingly.
 
   
 - Elements in named COMMON blocks must be initialized
   within a block data subprogram. Entities in a named COMMON
   block must be initialized only within a block data subprogram.
   
 - Elements in unnamed COMMON blocks must not be
   initialized by DATA statements. Variables and arrays that
   are contained in unnamed COMMON blocks must not be initialized by
   data statements or by type specification statements.
   
 - ELSE IF statement must be followed by the keyword
   THEN. The format of the ELSE IF statement is ELSE IF (e)
   THEN. A statement other than "THEN" was found after the right
   parenthesis.
   
 - ELSE occurred with no matching Block IF. Every ELSE
   statement must be lexically preceded by a Block IF statement that
   has not been closed with an ENDIF. This ELSE is not preceded by
   an "open" Block IF structure.
 
   
 - ELSEIF occurred with no matching Block IF. Every
   ELSEIF statement must be lexically preceded by a Block IF
   statement that has not been closed with an ENDIF. This ELSEIF
   is not preceded by an "open" Block IF structure.
   
 
   - END MAP statement must be used inside a STRUCTURE
   declaration block. The END MAP statement must be used inside
   a STRUCTURE declaration block.
   
 - End of this statement was encountered unexpectedly.
   The end of this statement was encountered where more characters
   were expected.
   
 - END STRUCTURE statement found unexpectedly. The END
   STRUCTURE statement was scanned during a parse state where KAP
   was expecting another declaration type for the present structure
   declaration block.
 
   
 - END STRUCTURE statement must be preceded by a STRUCTURE
   declaration. The END STRUCTURE statement must be preceded by
   a STRUCTURE declaration statement.
   
 - END UNION statement must be preceded by a UNION
   statement. The END UNION statement was scanned during a parse
   state where KAP was expecting another declaration type for the
   present structure declaration block.
   
 - END UNION statement must be used inside a STRUCTURE
   declaration block.
   
 - ENDDO occurred with no matching DO or DO-WHILE.
   Every ENDDO statement must be lexically preceded by a DO or DO-
   WHILE. If the DO or DO-WHILE statement specifies a label, the
   corresponding ENDDO must have a matching label.
   
 
 
   - ENDIF occurred with no matching Block IF. Every
   ENDIF statement must be lexically preceded by a Block IF
   statement that has not been closed with an ENDIF. This ENDIF
   is not preceded by an "open" Block IF structure.
   
 - ENTRY statement may appear only within a SUBROUTINE or
   a FUNCTION. This compilation unit is a BLOCK DATA, PROGRAM,
   or untyped (and hence a main program). The current statement is
   an ENTRY statement, and an ENTRY statement can appear only inside
   compilation units of type SUBROUTINE or FUNCTION.
   
 - Equals sign is not at the expected column in this
   assignment statement. The format of an assignment statement
   is V=E. Either the specification of V was in error (there should
   be a previous message for this statement), or the equals sign was
   missing or misplaced.
 
   
 - Equivalence would cause leftward extension of a COMMON
   block. Equivalence association must not cause a COMMON block
   storage sequence to be extended by adding storage units preceding
   the first storage unit of the first entity specified in a COMMON
   statement for the COMMON block.
   
 
   - Error in array reference. An illegal array
   reference has been detected. A variable may not have been
   declared as an array, or the array reference may be incorrectly
   constructed.
   
 - Error in intrinsic function parameter. An intrinsic
   function has been specified, but there is an error in one or more
   of its parameters.
   
 - Executable statement found inside a block data
   subprogram. Executable statements are not allowed inside a
   block data subprogram.
   
 
   - Expected type name for this IMPLICIT statement is
   missing or in error. The format of the IMPLICIT statement
   is IMPLICIT typ (a [,a]...) [,typ(a[,a])]... "typ" must be a
   legal Fortran type name (for example, INTEGER, REAL, LOGICAL, and
   so on). The type name was either missing or was not one of the
   allowed names.
   
 - Expression given in a RETURN statement is not scalar
   arithmetic. The format of the RETURN statement is RETURN [e],
   where e is a scalar arithmetic expression. The expression given
   in this statement was not arithmetic type and shape scalar.
   
 - Expression given in a RETURN statement is not scalar
   integer. The format of the RETURN statement is RETURN [e],
   where e is a scalar integer expression. The expression given in
   this statement was not of type integer and shape scalar.
 
   
 - Expression in a logical, block, or ELSE IF must be of
   type logical. The expression tested by a logical or block
   IF or by an ELSE IF statement must be of type logical. The
   expression given in this statement evaluates to a different type.
   
 - Expression in a subarray must be scalar. The
   expression in a subarray specifier must have shape scalar.
   
 - Expression in a subarray must have type integer.
   
 
   - Expression in an arithmetic IF is not of an allowed
   type. The expression in an arithmetic IF must be of type
   integer, real, or double precision. The expression given in this
   statement evaluates to a different type.
   
 - Expression in this statement is too complicated for
   KAP to handle. The expression in this statement is too
   complicated to be parsed by KAP. This could be either because
   a function call has too many parameters, or because an expression
   has too many operators and operands, or a combination of the two.
   
 - Expression or variable value of this I/O control
   element is invalid. The expression or variable that is at
   the current column is not well formed. The I/O control specifier
   in error is somewhere to the left of the current column.
 
   
 - Extended operator/operand is missing the last
   period. An extended operator (like .LE.) or operand (like
   .TRUE.) was coded, but the rightmost period was missing.
   
 
   - Extra text encountered after this statement is
   ignored. After this statement was parsed, more text was found
   that was not recognizable as part of the statement, starting in
   the given column.
   
 - Field names cannot be defined more than once within
   a STRUCTURE. A field name cannot be defined more than once
   within a STRUCTURE declaration block.
   
 - File already being included. An include directive
   specifies a file that is already open as an include file.
   Recursive includes are not allowed.
   
 - FORALL index "#1" is not used in the assignment part
   of this statement. All indices must be used in the array
   reference on the left side of the forall assignment.
   
 
   - Forall statement ends on a non-executable
   statement. A forall statement has been improperly
   constructed.
   
 - Form of record specification used is not valid
   here. The apostrophe form of the record specification can
   only come after a nonkeyword unit without a comma.
   
 - Formal parameter cannot be in a SAVE statement. A
   subroutine or function parameter cannot be an argument in a SAVE
   statement.
   
 - Formal parameter or allocatable array "#1" in COMMON
   block. Formal parameters or allocatable array may not be
   in a COMMON statement. The mentioned symbol is the name of a
   formal parameter or allocatable array that appears in a COMMON
   statement.
 
   
 - Formal parameter or allocatable array "#1" may not be
   equivalenced. Formal parameters or allocatable array may not
   be equivalenced. The mentioned symbol is the name of a formal
   parameter or allocatable array that appears in an EQUIVALENCE
   statement.
   
 - Format item is not repeatable. A format item
   preceded by an integer was encountered. The ANSI standard
   specifies that this particular item cannot be repeated.
   
 - Format item requires a leading integer. The ANSI
   standard requires that certain format items be preceded by an
   integer.
   
 - Format specifier is not a statement label, asterisk,
   or other legal form. The format specifier must be a statement
   label, integer variable name, character array name, character
   expression, or an asterisk. The format specifier to the left of
   the current column is none of these.
 
   
 - Function reference must include a parameter list.
   A function call must include a parameter list. The list can be
   empty, specified by "( )."
   
 - FUNCTION/ENTRY name "#1" may not be equivalenced.
   A variable name that is also a function name may not be
   equivalenced. The mentioned symbol is the name of a FUNCTION
   subprogram, or the name specified as an ENTRY name in a function
   subprogram.
   
 
   - Group name in this NAMELIST statement was previously
   defined. The group name specified in this statement was used
   previously.
   
 - Hex constant contains characters that are not 0-
   9 or A-F. A hex constant may contain only the digits
   0,1,2,3,4,5,6,7,8,9 or the letters a,b,c,d,e,f (case does not
   matter). The specified constant contained one or more characters
   that were not 0-9 or A-F.
   
 - Hex constant too long. Only 32 digits are allowed.
   A hex constant can only be 128 bits long. The specified constant
   contained more than 32 digits.
   
 - Hollerith with
   invalid length encountered. Hollerith with an invalid length
   ( <= 0) or longer than the remaining card  was encountered.
   
 - I/O control entry's operand is not a specific type.
   The I/O control entry requires the operand to be a specific type.
   It was not. The I/O control entry to the left of the current
   column is in error. Each I/O control entry requires that its
   operand be of a specific type (character, logical, or integer).
   The type of the expression or variable that was the operand to
   this I/O control entry does not match the required type.
   
 - Identifier "#1" already used as name of function.
   The symbolic name of an external function is a global name and
   must not be the same as any other global or local name except a
   variable name in the function subprogram.
   
 - Identifier "#1" being ASSIGNed must be a variable
   name. The identifier used to hold a statement label must
   be the name of a variable.
   
 - Identifier "#1" following GOTO in an assigned goto must
   be a variable name. The identifier used to select a branch
   address must be the name of a variable.
   
 
   - Identifier "#1" in SAVE statement is not a
   variable. The form of the SAVE statement is SAVE [a [,
   a]...], where each a is a named COMMON block name preceded and
   followed by a slash, a variable name, or an array name. The
   indicated identifier was previously used in a context such that
   it may not also be a variable.
   
 - Identifier "#1" is not the name of subroutine.
   
 - Identifier was expected here but not found. An
   identifier was expected in the indicated column, but another
   symbol was found instead.
   
 - IF block is improperly nested. This IF block does
   not begin and end in the same block.
 
   
 - Illegal escape sequence. An escape sequence
   consists of the escape character and two hexadecimal digits.
   The escape character was found, but not the proper digits.
   
 - Illegal expression for special call parameter.
   An illegal expression was detected in a special subroutine call
   (Fortran extension).
   
 - Illegal index expression. Array reference has an
   incorrect subscript expression, possibly an illegal subarray
   reference.
   
 - Illegal number of subscripts in ARRAY. Some
   products put restrictions on the number of subscripts allowed
   in arrays.
   
 - Illegal statement label. The indicated token is an
   illegal statement label because it is not an integer, or because
   it is more than 5 digits long.
   
 - IMPLICIT NONE must be the only IMPLICIT statement in
   the program unit. If you specify IMPLICIT NONE, no other
   IMPLICIT statements can be included in the program unit.
   
 
   - Implied DO list in this I/O statement is not terminated
   by a right parenthesis. The implied DO list that should have
   ended with a right parenthesis in the current column did not. A
   right parenthesis is assumed.
   
 - Improper DO or WHILE statement. The DO or WHILE
   statement was improperly typed.
   
 - Include file "#1" not found. A file specified in an
   INCLUDE statement was not in the directory specified. Either the
   file does not exist or it is not in the correct directory.
   
 - Include nesting level has been exceeded. The number
   of nested includes allowed has been exceeded.
   
 - Incompatible storage class for "#1". Incompatible
   storage class(PRIVATE,STATIC,AUTOMATIC,SHARED) for the specified
   variable/COMMON block.
 
   
 - Increment expression of the DO statement has an
   error. The format of the DO statement is DO s [,] i = e1, e2
   [,e3]. The expressions "e1," "e2," and "e3" are each an INTEGER,
   REAL, or DOUBLE PRECISION expression. In this statement, "e3" has
   a syntax error.
   
 - Increment of the DO statement must not be zero.
   The format of the DO statement is DO s [,] i = e1, e2 [,e3].
   The expressions "e1," "e2," and "e3" are each an INTEGER, REAL,
   or DOUBLE PRECISION expression. "e3" must not be zero, when
   evaluated and converted to the type of the DO index variable.
   
 - Individual parts of a COMMON block cannot be in a
   SAVE statement. A variable in a COMMON block cannot be saved
   without the rest of the COMMON block.
   
 
   - Initialization of "#1" by this constant is not
   allowed. A type mismatch has been found between the variable
   being initialized and the constant being used for initialization.
   
 - Integer encountered was too large to represent
   internally. The scanner encountered and tried to convert
   an integer too large to represent internally. This normally is a
   semantic error.
   
 - Integer was expected here but not found. An integer
   was expected in the indicated column.
   
 - Intrinsic function call has the wrong number of
   parameters. An incorrect number of parameters (usually too
   few) was coded in the invocation of this intrinsic function.
   Look up the intrinsic function and code the correct number of
   parameters.
   
 - Intrinsic function is not allowed in a constant
   expression. The constant expression required here may not
   contain the given intrinsic function.
   
 - Intrinsic function parameter has the wrong
   dimensionality. The indicated parameter to this intrinsic
   function has the wrong number of dimensions. Either an array was
   specified where a scalar is required, or a scalar was specified
   where an array is required.
 
   
 - Intrinsic function parameter has the wrong type.
   The indicated parameter to this intrinsic function has the wrong
   type. Check your system's Fortran user guide to find the correct
   intrinsic to use.
   
 - Intrinsic function requires at least two
   parameters. This intrinsic function requires at least two
   parameters. Check your system's Fortran user guide for details.
   
 - Intrinsic functions not allowed here. The constant
   expression required here may not contain intrinsic functions.
   
 
   - Intrinsic may not be used as an actual parameter.
   Some intrinsic functions may not be used as actual parameters.
   These include type conversion intrinsics, lexical relationship
   intrinsics, and max/min variations.
   
 - Intrinsic parameter cannot have this value. A
   constant value has been specified for an intrinsic function that
   only allows a specified range of legal values. The constant is
   not in this range.
   
 - Invalid character found in this constant. The
   character was not expected to occur in this constant. The
   constant may be hex, octal, bit, or hollerith.
   
 - Invalid syntax for the INQUIRE statement. The
   INQUIRE statement may have either FILE and DEFAULTFILE or UNIT,
   but not both.
   
 - Invalid unit specifier. The unit specifier must
   be one of: an integer expression, a character expression, or
   an asterisk. Which of these is allowed varies depending on the
   specific type of I/O statement.
 
   
 - Item involved in the transfer is incorrectly
   specified. The I/O list parser expected a comma to be at the
   current column, and a valid I/O list element to be to the left.
   This error can result from using an expression in a READ I/O
   list, or from an incorrectly formed expression in WRITE, PRINT,
   or PUNCH I/O lists.
   
 - Keyword parameter not allowed at this point in call
   to this intrinsic function. Keyword parameters are not
   allowed at this position in the parameter list of this intrinsic
   function. Check your system's Fortran user guide for details.
   
 - Label "#1" is not the label of a format statement.
   The mentioned statement label was used as a format specifier
   in this statement. The mentioned label is a label used in the
   program, but is not the label on a format statement.
   
 - Label "#1" on non-executable statement cannot
   be branched to. The mentioned label is the label on a
   nonexecutable statement. The current statement attempts to branch
   to that statement. Only executable statements can be branched
   to.
   
 
   - Label of the terminator statement is missing from the
   DO statement. The format of the DO statement is DO s [,] i
   = e1, e2 [,e3]. The "s" is the statement label of an executable
   statement, called with terminal statement. In this statement,
   the statement label is missing or it has an illegal format for a
   Fortran statement label. The label need not appear if the DO is
   terminated by an ENDDO in Digital Fortran.
   
 - Left and right sides have different number of
   dimensions in array assignment. The left and right sides
   of an array assignment must have the same number of array
   section selectors or the right side must be a scalar. Check the
   declarations of each variable appearing in the statement.
   
 - Left parenthesis was expected here but not found.
   A left parenthesis was expected in the indicated column, but
   another symbol was found instead.
 
   
 - Left side of an assignment is not a scalar or array
   shape. The shape of the left side expression could not be
   determined. If other errors have not been noted with an earlier
   column number for this same statement, then there is a translator
   error.
   
 - Length field must be an integer constant or enclosed in
   parentheses. If a length is given for a type and the length
   is not enclosed in parentheses, that length must be an unsigned,
   nonzero integer constant. A more general expression is allowed
   for type Character if the expression is enclosed in parentheses.
   
 - Length given is not valid for type character. The
   length of a character variable must be an unsigned, nonzero
   integer constant, an integer constant expression enclosed in
   parentheses with a positive value, or an asterisk in parentheses.
   
 - Length specified for this data type is illegal. An
   incorrect explicit length has been specified for a noncharacter
   type.
   
 - List directed or namelist formatting not allowed
   for an internal file. If the unit_specifier specifies an
   internal file, the control information list must contain a format
   identifier other than an asterisk or a namelist group name.
   
 - Logical IF ends on a non-executable statement. The
   statement part of a logical IF must be executable.
   
 - Logical operations are invalid between these types of
   operands. The logical operator at the position given cannot
   be applied to types of operands it is between.
   
 
   - Lower bound expression of the DO statement has an
   error. The format of the DO statement is DO s [,] i = e1, e2
   [,e3]. The expressions "e1," "e2," and "e3" are each an INTEGER,
   REAL, or DOUBLE PRECISION expression. In this statement, "e3" has
   a syntax error.
   
 - MAP statement must be preceded by a UNION
   statement. The MAP statement was scanned during a parse
   state where KAP was not expecting a MAP declaration type for
   the present structure declaration block.
   
 - MAP statement must be used inside a STRUCTURE
   declaration block.
   
 - MAP/ENDMAP statements must have at least one field-
   declaration.
   
 - Missing operand. An operator has been found that
   does not have enough operands.
   
 - Multiple declaration of variable. Variable has been
   declared in previous type declaration statement.
 
   
 - Multiple initialization of the same variable is not
   allowed. Variable has been initialized previously.
   
 - Name enclosed in slashes "#1" is not the name of a
   named COMMON block. In a save statement, a COMMON block
   name is specified by enclosing it in slashes. The name found
   between the slashes has not been used as the name of a COMMON
   block previously in this compilation unit.
   
 - Name is not a legal external identifier. The
   indicated name is not a legal external name for the target
   language. It either has too many characters or contains a
   character that is not allowed in external names.
   
 - Name was previously used in a conflicting way.
   The name was used previously in a declaration statement, an
   expression, or other manner such that the current use is no
   longer legal. For example, a name may not be dimensioned more
   than once.
   
 
   - Negation cannot be applied to an expression of type
   "#1". Negation "-" cannot be applied to expressions of the
   given type.
   
 - Nested loops with same variable "#1". The index
   variable for nested loops should not be the same.
   
 - Number of items in the variable list is not the same
   as in the constant list. The number of items specified in
   the variable list must be the same number in its corresponding
   constant list.
   
 - Number of places in edit descriptor must not exceed
   field width. The number of places (m) required in Iw.m edit
   descriptor must not exceed the field width (w).
   
 - Octal constant contains characters that are not
   0-7. An octal constant may contain only the digits
   0,1,2,3,4,5,6, or 7. The specified constant contained one or
   more digits that were 8 or 9.
 
   
 - Octal constant too long. Only 43 digits are
   allowed. An octal constant can only be 128 bits long. The
   specified constant contained more than 43 digits.
   
 - Only constants are allowed in this expression. The
   indicated expression element is illegal in this context.
   
 - Only equality comparisons can be made on complex
   values. Logical operators .GT., .GE., .LT., .LE. cannot be
   applied to complex values.
   
 - Only formal parameters and constants are allowed in
   this expression.
   
 - Only simple parameters and constants are allowed
   in this expression. Only scalar variable parameters and
   constants are allowed in this expression.
   
 - Operands are not conformable. The operands involved
   must have the same number of array section selectors.
   
 
   - Operator was not expected here. An operator was
   found in the wrong place.
   
 - Parameter U is required but was not found. The
   letter U is required as the third parameter for DEFINE FILE.
   
 - Parallel constructs are not contained in the same
   statement flow-control block. Currently, KAP only allows each
   Parallel construct to be started and ended in the same statement
   flow-control block.
   
 - Periods can only be used to form numbers or extended
   operators/operands. A period was encountered, but it was not
   part of a number or part of an extended operator/operand.
   
 - Preceding EQUIVALENCE group must have more than one
   entry. A single name was specified inside an EQUIVALENCE
   group. At least two names must be specified in each group.
 
   
 - Previous I/O control entry has already been
   specified. Each type of I/O control entry can be specified
   at most once. The I/O control entry that was specified just prior
   to the current column had been specified earlier.
   
 - Previous I/O control entry may not be specified in
   this type of I/O statement. Each type of I/O statement allows
   certain I/O control entries to be specified. The I/O control
   entry that was specified just prior to the current column may not
   be specified with this I/O statement.
   
 - Range of first letters specified in this IMPLICIT
   statement is invalid. An IMPLICIT statement must specify
   either a single letter or two letters separated by a dash, with
   the first letter preceding the second in the alphabet. The range
   of letters specified must not overlap any other ranges specified
   in this or other IMPLICIT statements.
   
 - Record name "#1" cannot be used in an EQUIVALENCE
   statement.
   
 - Repetition factor must be greater than zero.
   Repetition factors for repeatable format items must be greater
   than zero.
   
 
   - Right parenthesis that matches this left parenthesis is
   missing. The indicated left parenthesis has no corresponding
   right parenthesis.
   
 - Right parenthesis was expected here but not found.
   A right parenthesis was expected in the indicated column, but
   another symbol was found instead.
   
 - Scalar expression expected. A scalar expression was
   expected but not found, for example in the logical expression of
   an if statement.
   
 - Scalar integer expression must follow the label list in
   a computed GOTO. The format of a computed GOTO requires that
   an integer expression follow the list of statement labels. This
   expression can be an integer constant, an integer variable, an
   integer array element, or any form of scalar integer expression.
   
 - Semicolon vector syntax not accepted by this
   product. This product does not accept semicolon vector
   notation. Use some other notation such as Fortran 8X triplets.
   
 - Shape mismatch: Shape of left side is "#1" and shape
   of right side is not. The shape of the left and right sides
   of an assignment statement must be the same or conformable. The
   shape of the left side (mentioned in the message) and the shape
   of the right side do not agree.
   
 - Size of hollerith constant exceeds remaining statement
   length. A hollerith constant was specified with a length
   that is longer than the number of characters that are left in the
   statement.
   
 - Statement contains too many continuation lines.
   KAP expects a maximum number of continuation lines per statement.
   This maximum is product-dependent. When the maximum is exceeded,
   no further tokenization takes place until a noncontinuation line
   is encountered.
 
   
 - Statement is not any of the possible GOTO
   statements. The syntax of this statement is so confused
   that KAP could not decide what type of statement it is. It
   appears to be some type of GOTO statement, but little else can
   be determined.
   
 - Statement label "#1" was referenced, but never defined
   in this program unit.
   
 - Statement must occur earlier in the program unit.
   The definition of the version of Fortran being accepted
   gives the restrictions on statement ordering within a single
   compilation unit. The statement being scanned violates this order
   requirement. Check the Fortran user guide or Fortran reference
   manual.
   
 
   - Statement unrecognizable as any known statement
   type. The given statement contains errors that make it
   impossible to tell what type of statement it was intended to
   be. The keyword at the beginning of the statement (if any) did
   not match any of the known statement keywords. The statement also
   did not contain any equals signs at parenthesis nest level 0,
   necessary for the statement to be an assignment statement. This
   error may be caused by incorrect parenthesis nesting, or by a
   misspelled keyword.
   
 - String constant was not closed by end of statement.
   A string constant was begun by an apostrophe or double quote, but
   no trailing delimiter was encountered before the end of statement
   was reached.
   
 - Structure name of a record is the same as the defining
   STRUCTURE. A structure name of a record cannot be used within
   the defining declaration for that structure name.
   
 -  Structure references must be defined prior to use in a
   RECORD statement.
   
 - Structure-name has been used previously in a STRUCTURE
   declaration.
 
   
 - Structure-name is missing from the STRUCTURE
   declaration. Structure names are required on the structure
   declaration at the outermost level of nesting.
   
 - Substring denoted by this expression is not within
   declared length of string. The starting position of a
   substring specification must be at least 1, and the ending
   position must be at most the length of the string.
   
 - Symbolic constant must be a simple scalar entity.
   The name of a symbolic constant must not be dimensioned, or in
   any way appear different than that of a scalar variable.
   
 - Symbolic constant must not be defined more than once
   in a program unit. The symbolic constant that is defined to
   the left of the current column has been either in an earlier
   PARAMETER statement in this program unit, or in an earlier
   portion of this PARAMETER statement. Each symbolic constant in
   a program unit can be defined only once.
   
 
   - Text "#1" following a STOP or PAUSE is not an integer
   or string constant. The format of the STOP statement is STOP
   [n]. The format of the PAUSE statement is PAUSE [n]. In either
   case, "n" must be either a string of not more than 5 digits or a
   character constant.
   
 - The %FILL pseudo-name cannot be dimensioned.
   
 - The array "#1" has adjustable dimension and must appear
   in dummy argument list. At least one dummy argument list of
   the subprogram must contain the name of the adjustable array.
   
 - The field name "#1" has an illegal adjustable
   dimension. Adjustable or assumed sized arrays and passed
   length CHARACTER declarations are not allowed in field
   declarations.
   
 - The field-name has not been defined in the associated
   structure.
   
 - The preceding Parallel parallel and/or synchronization
   region/section is not closed. The present Parallel directive
   was scanned or the end of the program was reached where KAP was
   expecting a closing parallel directive for the preceding parallel
   region/section block.
 
   
 - This declaration type is not allowed in structure
   declaration blocks. During the scanning process, a
   declaration type has been detected within a STRUCTURE declaration
   block that is not allowed.
   
 - This directive is not adjacent to the loop it applies
   to. KAP recognizes directives in a file only if they are
   placed immediately before the loop that they are to affect.
   
 - This Parallel directive should be inside a Parallel
   PARALLEL REGION. Work-sharing or synchronization Parallel
   constructs should be used inside a Parallel fork/join construct,
   that is, a PARALLEL REGION.
   
 - Too many arguments in FUNCTION/SUBROUTINE. Some
   products put restrictions on the number of arguments allowed in
   SUBROUTINE/ FUNCTION.
   
 - Too many labels in computed GOTO. Some products put
   restrictions on the number of labels allowed in a computed GOTO
   statement.
   
 - Too many parameters are specified to this intrinsic
   function. Too many parameters appear in the invocation of the
   indicated intrinsic function. Check the intrinsic function and
   code the correct number of parameters.
   
 
   - Transfer into IF or DO block from outside the IF or DO
   block is prohibited. Transfer of control into an IF-block or
   DO-block from outside the block is not allowed.
   
 - Type conversion not supported for this product.
   This message is issued if the type conversion did not exist to
   type cast the statement function expression to the type of the
   statement function.
   
 - Unary operator has more than one operand. A unary
   operator was found that has an operator on the left side.
   
 - Unexpected character. In processing a statement,
   a character was encountered that was not allowed at the place
   it was found. Check the syntax of the statement where the error
   occurred.
   
 - Unexpected symbol. The indicated symbol is not
   legal at this point in the statement.
 
   
 - UNION statement must be used inside a STRUCTURE
   declaration block.
   
 - UNION statement must not be preceded by a UNION
   statement. The UNION statement was scanned during a parse
   state where KAP was expecting a MAP declaration type for the
   present structure declaration block.
   
 - Unknown I/O control entry begins at the current
   column. An I/O control entry that is not in the table of
   all possible I/O control entries begins at the current column.
   This I/O control entry is not the first or second entry in this
   control list, because those two can be positional (unit and
   format).
   
 - Unrecognized .xxx. operator. A token was recognized
   as having the format of an extended operator/operand (period
   identifier period), but the extended operator/operand was not in
   the table of known extended operators/operands. Check the system
   Fortran user guide.
 
   
 - Unsubscripted arrays not permitted in expressions and
   assignment statements. An array name without a subscript is
   not allowed in expressions and assignment statements.
   
 
   - Upper bound expression of the DO statement has an
   error. The format of the DO statement is DO [,] i = e1, e2
   [,e3]. The expressions "e1," "e2," and "e3" are each an INTEGER,
   REAL, or DOUBLE PRECISION expression. In this statement, "e2" has
   a syntax error.
   
 - Variable "#1" has no dimension bounds specified.
   Variables declared in a dimension statement must have at least
   one dimension bound, enclosed in parentheses, specified.
   
 - Variable "#1" must be explicitly typed. IMPLICIT
   NONE and UNDEFINED ( for few dialects ) disables automatic
   typing. All variables occurring within the scope of IMPLICIT
   NONE or UNDEFINED must be explicitly typed.
   
 - Variable already occurred in a DATA statement. The
   variable is declared after it has already been used in a data
   statement.
   
 - Variable list is missing from this list-directed I/O
   statement. The comma after the format in a list-directed
   READ, PRINT, or PUNCH statement was present, but the variable
   list following the comma was missing.
 
   
 - Variable must be an array. The simple variable in
   question is used in a context requiring an array.
   
 - Variable name "#1" is too long. The given variable
   name is too long for the target language.
   
 - Variable name is required at this point. Only a
   variable can be used at this point.
   
 - Variables from different COMMON blocks may not be
   equivalenced. An EQUIVALENCE statement must not cause the
   storage sequences of two different COMMON blocks in the same
   program unit to be associated.
   
 
Previous Page | Next Page | Contents | Index | 
Command-Line Qualifiers