HP 3000 Manuals

Disastrous Errors [ HP COBOL II/XL Reference Manual ] MPE/iX 5.0 Documentation


HP COBOL II/XL Reference Manual

Disastrous Errors 

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

450      ERROR      USL FILE OVERFLOW.
         MESSAGE

         CAUSE      The USL file may overflow under the following conditions:  A
                    $CONTROL USLINIT command may be missing, the default size of 1023
                    records may be too small, or there may not be enough records left
                    in the usl file.

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

451      ERROR      PARSE STACK OVERFLOW; POSSIBLE LIMIT EXCEEDED.
         MESSAGE

         CAUSE      [REV BEG]The parse stack in compiler overflowed.  This may have
                    been caused by too many levels of nesting of IF...THEN...ELSE
                    statements.  This could also be caused by error 410.  This could
                    occur instead of error 423.[REV END]

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

452      ERROR      EARLY END OF FILE ON COBOL SOURCE.
         MESSAGE

         CAUSE      This could occur with the following errors:

                       1.  The syntax of a COPY or REPLACE statement is incorrect.
                       2.  A syntax error in the program.  For example, a period may be
                           missing making the IDENTIFICATION DIVISION paragraph
                           incorrect.

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

453      ERROR      BAD INTRINSIC FILE.
         MESSAGE

         CAUSE      The system intrinsic file (SYSINTR.PUB.SYS) is not in the proper
                    format.

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

454      ERROR      READ ERROR ON IDS FILE.
         MESSAGE

         CAUSE      An error has occurred while trying to do a read on the IDS file (an
                    internal temporary file).  The most likely cause is a serious
                    compiler problem.  See directions on line .4 of the file
                    COBCAT.PUB.SYS.

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

455      ERROR      WRITE ERROR ON IDS FILE.
         MESSAGE

         CAUSE      An error has occurred while trying to do a write to the IDS file
                    (an internal temporary file).  See line .4 of the file
                    COBCAT.PUB.SYS, if compiler problem.  This can be caused by a
                    serious compiler problem, an excessively large source file, or a
                    lack of disk space.

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

456      ERROR      OPEN ERROR ON IDS FILE.
         MESSAGE

         CAUSE      An error has occurred while trying to open the IDS file (an
                    internal temporary file).  The most likely cause of this is lack of
                    disk space.

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

457      ERROR      COMPILER ERROR:  OUT OF IDS FILE BUFFERS.
         MESSAGE

         CAUSE      This can be caused by a compiler problem or by statements too
                    complex or with too many operands.

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

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

458      ERROR      COMPILER ERROR:  INVALID INTERNAL LABEL.
         MESSAGE

         CAUSE      The compiler has generated or referenced an invalid internal label
                    number.  This could also be caused by too many VALUE clauses on
                    table elements.  If the error is not in the DATA DIVISION or it is
                    the only error, then see directions on line .3 of the file
                    COBCAT.PUB.SYS.

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

459      ERROR      TOO MANY VALUE CLAUSES.
         MESSAGE

         CAUSE      USL entry overflows maximum size.  Reduce the number of VALUE
                    clauses, for example, by combining at group level.

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

460      ERROR      MISSING IDENTIFICATION DIVISION, COMPILATION TERMINATED.
         MESSAGE

         CAUSE

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

461      ERROR      DYNAMIC ARRAY ERROR, OUT OF SPACE.
         MESSAGE

         CAUSE      The number of macros, size of one macro or copylib member is too
                    big.  May be caused instead of 417 and 418.

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

462      ERROR      AVAILABLE MEMORY INSUFFICIENT FOR COMPILATION.
         MESSAGE

         CAUSE      Refer to error 471 for possible problem cause.  If not applicable,
                    see directions on line .3 of the file COBCAT.PUB.SYS.

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

463      ERROR      READ ERROR ON SYMBOL TABLE FILE.
         MESSAGE

         CAUSE      An error has occurred while trying to read from the symbol table
                    file (an internal temporary file).  See directions on line .4 of
                    the file COBCAT.PUB.SYS. The most likely cause of this is a serious
                    compiler error.

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

464      ERROR      READ ERROR ON DATA TABLE FILE.
         MESSAGE

         CAUSE      An error occurred while trying to read from the data table file (an
                    internal temporary file).  See directions on line .4 of the file
                    COBCAT.PUB.SYS. The most likely cause of this is a serious compiler
                    error.

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

465      ERROR      WRITE ERROR ON SYMBOL TABLE FILE.
         MESSAGE

         CAUSE      An error has occurred while trying to write to the symbol table
                    file (an internal temporary file).  See directions on line .4 of
                    the file COBCAT.PUB.SYS. This can be caused by a compiler error or
                    by a lack of disk space.

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

466      ERROR      WRITE ERROR ON DATA TABLE FILE.
         MESSAGE

         CAUSE      An error has occurred while trying to write to the data table file
                    (an internal temporary file).  See directions on line .4 of the
                    file COBCAT.PUB.SYS. This can be caused by a compiler error or by a
                    lack of disk space.

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

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

467      ERROR      OPEN ERROR ON SYMBOL TABLE FILE.
         MESSAGE

         CAUSE      An error has occurred while trying to open the symbol table file
                    (an internal temporary file).  See directions on line .4 of the
                    file COBCAT.PUB.SYS. The most likely cause of this is a lack of
                    disk space.

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

468      ERROR      OPEN ERROR ON DATA TABLE FILE.
         MESSAGE

         CAUSE      An error has occurred while trying to open the data table file (an
                    internal temporary file).  See directions on line .4 of the file
                    COBCAT.PUB.SYS. The most likely cause of this is a lack of disk
                    space.

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

470      ERROR      USL FILE (DIRECTORY) OVERFLOW.
         MESSAGE

         CAUSE      The directory area of the USL file does not have enough space for
                    the current entry.

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

471      ERROR      CODE SEGMENT EXCEEDS 16 K.
         MESSAGE

         CAUSE      A compiled code segment is too large.  Use COBOL SECTION entries to
                    break up the code segments.  (If not in initialization section,
                    that is, for VALUE clauses.)

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

491      ERROR      UNABLE TO OPEN FILE !.
         MESSAGE

         CAUSE

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

492      ERROR      UNABLE TO USE FILE !.
         MESSAGE

         CAUSE

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

493      ERROR      READ FAILURE ON FILE !.
         MESSAGE

         CAUSE
---------------------------------------------------------------------------------------

494      ERROR      WRITE FAILURE ON FILE !.
         MESSAGE

         CAUSE      [REV BEG]This could occur on writes to COBXREF. The disc file is
                    not big enough to contain all of its data.  The filesize can be
                    increased with the file equation

                    :FILE COBXREF;DISC=nnnnn[REV END]

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

495      ERROR      UNABLE TO CLOSE FILE !.
         MESSAGE

         CAUSE

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

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

         496      ERROR      EARLY END OF FILE ON FILE !.
                  MESSAGE

                  CAUSE      This could occur with the following errors:

                                *   Syntax of COPY or REPLACE statement is bad.
                                *   Syntax in program, such as a period is missing.
                                *   IDENTIFICATION DIVISION paragraph is incorrect.
                             [REV BEG]

                             This could occur on writes to COBLIST, COBTEMP, COBMAC, or COBXDB.
                             The disc file is not big enough to contain all of its data.  The
                             filesize can be increased with a file equation

                             :FILE COBTEMP;DISC=nnnnn[REV END]

------------------------------------------------------------------------------------------------
[REV BEG]

         498      ERROR      UNABLE TO SAVE FILE !.
                  MESSAGE

                  CAUSE      [REV END]

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



MPE/iX 5.0 Documentation