HP 3000 Manuals

List of Messages 0379 - 0573 [ COBOL/HP-UX Error Messages for the Series 700 and 800 ] MPE/iX 5.0 Documentation


COBOL/HP-UX Error Messages for the Series 700 and 800

List of Messages 0379 - 0573 

0379     Non-DISPLAY numeric data cannot be compared with alphanumeric 
         literal 

0380     Parameter count in CALL different from that in PROCEDURE 
         DIVISION header 

0381     TALLYING option has ALL etc.  distributed over multiple 
         identifiers 

0382     Only one Procedure-name in GO TO ...  DEPENDING 

0383     Missing ALSO 

            *   You have omitted the word ALSO.

            *   Add the word ALSO.

0384     NEXT SENTENCE does not follow IF, ELSE or SEARCH WHEN 

            *   NEXT SENTENCE should be used only in either branch of an
                IF statement or the WHEN branch of a SEARCH statement.

            *   Revise your code to ensure that you have obeyed these
                rules.

0385     Order of initialization changed 

0386     No section or paragraph at start of PROCEDURE DIVISION 

0387     AFTER and BEFORE options used together 

0388     Key is right hand side of condition 

0389     EXIT not in separate paragraph 

0390     OPEN EXTEND on non-sequential file 

0391     MF format Accept/Display 

0392     More than two AFTER phrases 

            *   You have included more than the maximum of two AFTER
                phrases in your program.

            *   Delete any extra AFTER phrases.

0393     In-line PERFORM 

0394     No section header after END DECLARATIVES 

0395     FROM literal 

0396     No suitable conditional phrase and no applicable declarative 

0397     No preceding section 

0398     Offset only allowed with Index-names 

0399     Index-name data-name belongs to different table 

0400     Cannot use index data-item as subscript 

            *   You have used an index data-item as a subscript within
                your program.

0401     Limit exceeded - number of source statements > limit 

0402     Limit exceeded - number of files > limit 

0404     Limit exceeded - number of pairs of REPLACING operands > limit 

0406     Limit exceeded - length of file/copy/library name > limit 

0409     Limit exceeded - number of SELECT filenames > limit 

0410     Limit exceeded - number of SAME RECORD AREA clauses > limit 

0411     Limit exceeded - number of MULTIPLE FILE filenames > limit 

0412     Limit exceeded - number of ALTERNATE RECORD KEY clauses in a 
         file > limit 

0413     Limit exceeded - length of RECORD KEY > limit characters 

0414     Limit exceeded - length of DATA DIVISION > limit 

0415     Limit exceeded - length of data SECTION > limit 

0419     Limit exceeded - BLOCK size > limit characters 

0420     Limit exceeded - RECORD length > limit characters 

0421     Limit exceeded - number of FD filenames > limit 

0422     Limit exceeded - number of SD filenames > limit 

0424     Limit exceeded - number of 01 & 77 items in LINKAGE SECTION > 
         limit 

0425     Limit exceeded - length of FILE SECTION group item > limit 
         characters 

0426     Limit exceeded - length of group item > limit characters 

0427     Limit exceeded - length of data item > limit characters 

0428     Limit exceeded - length of edited item > limit characters 

0429     Limit exceeded - length of variable length table > limit 
         characters 

0430     Limit exceeded - total length of VALUE literals > limit
         characters 

0431     Limit exceeded - length of PICTURE string > limit characters 

0432     Limit exceeded - length of PICTURE replication > limit 

0433     Limit exceeded - length of sort record > limit characters 

0434     Limit exceeded - length of table > limit characters 

0435     Limit exceeded - length of table element > limit characters 

0436     Limit exceeded - number of ASC/DESC KEY clauses > limit 

0437     Limit exceeded at data-name - length of ASC/DESC KEYs > limit 
         characters 

0438     Limit exceeded - number of INDEXED BY clauses > limit 

0440     Limit exceeded - number of paragraph labels > limit 

0441     Limit exceeded - number of PERFORMs > limit 

0442     Limit exceeded - OCCURS nesting > limit 

0443     Limit exceeded - number of GO TO DEPENDING ON names > limit 

0444     Limit exceeded - number of IF nesting levels > limit 

0445     Limit exceeded - number of CALL parameters > limit 

0446     Limit exceeded - number of SORT/MERGE input files > limit 

0447     Limit exceeded - number of SORT/MERGE keys > limit 

0448     Limit exceeded - number of conditions in a SEARCH ALL > limit 

0449     Limit exceeded - number of UNSTRING delimiters > limit 

0450     Limit exceeded - number of operands in INSPECT 
         TALLYING/REPLACING > limit 

0451     Limit exceeded - length of SORT/MERGE keys > limit characters 

0452     Limit exceeded - number of PROCEDURE DIVISION USING parameters > 
         limit 

0460     Previous item crosses 64K boundary.  Segment checking code 
         produced 

0461     Table crosses 64K boundary.  Segment checking code produced 

0462     Parameter crosses 64K boundary.  Use NOSMALLDD when compiling 
         subprogram 

0463     Parameter to call-by-number routine not contained in first 64K 
         of WS 

            *   Parameters for call-by-number routines must be defined in
                the first 64K of Working-Storage if the CHIP(16)
                directive is set.  See your COBOL System Reference for
                details.

0501     Feature is part of an optional module - module-name 

0502     This entire section is part of an optional module - module-name 

0504     ORGANIZATION clause in SELECT statement of sort file 

0505     VALUE OF clause in SD or CD 

0506     REDEFINES does not immediately follow data-name 

            *   The REDEFINES clause does not immediately follow
                data-name in your program.

            *   Revise your program so that REDEFINES immediately follows
                data-name.

0507     Numeric literal VALUE on edited item 

0508     NEXT used in READ of sequential file 

0509     SET operation on non-index data item 

0510     ZEROS or ZEROES in BLANK WHEN clause.  Treated as ZERO 

0511     FILE STATUS data-name is not alphanumeric 

            *   You have specified a nonalphanumeric data item in your
                FILE STATUS.

            *   Amend your code to make the data item alphanumeric.

0512     Data name is qualified 

0513     Flag refers to entire section 

0514     "CHANGED" and/or "NAMED" missing 

            *   You have omitted at least one of CHANGED or NAMED.

            *   Add CHANGED and/or NAMED to your program.

0515     Phrases repeated 

0516     Only 1 file specified in SAME AREA clause 

0517     Jump out of inline PERFORM 

0518     > or < followed by THAN, or = followed by TO 

            *   You have included the noise words THAN and TO
                unnecessarily in your code.

            *   Delete these words.

0519     More than 5 levels of qualification 

0520     "INVALID KEY" phrase used with sequential file 

0521     USING literal/LENGTH OF identifier.  (BY CONTENT implied for 
         this item) 

0522     BY CONTENT literal/LENGTH OF identifier 

0523     DECLARATIVE SECTION without USE statement 

0524     ALPHABET IS ASCII 

0525     EOP or END-OF-PAGE used on file which has no LINAGE 

            *   You have specified EOP, which is invalid for a file which
                has no LINAGE.

            *   Delete EOP.

0526     Phrases are not in the correct order 

0527     REDEFINES at 01 in FILE SECTION 

0528     Data-name data-name in ASC/DESC key is not uniquely identified 

0529     Clause treated as documentary 

0530     Data item used as index file key is not alphanumeric 

            *   The data item you have specified as an index file key is
                not alphanumeric.

            *   Revise your code to make the data item alphanumeric.

0531     Too many subscripts 

0532     INTO data-name is group item 

0533     START ...  LESS/NOT GREATER THAN ... 

0534     Entry treated as documentary 

0535     ALPHABET is EBCDIC 

0536     CICS LINKAGE items generated 

0537     BASIS mechanism (BASIS, DELETE or INSERT) 

0538     Picture string is continued 

0539     This item is obsolete in 1985 standard 

            *   The syntax you have used is not supported under ANSI'85.

            *   Delete this syntax.

0540     Source field is edited 

0541     Comparison between edited field and COMP field 

0542     VALUE clause on group COMP 

0543     VALUE clause on variable length group 

0544     VALUE clause with OCCURS or subsidiary to group OCCURS 

0545     ALTERNATE RECORD KEY is not in SAA 

0546     PICTURE symbol P not allowed in RELATIVE KEY 

            *   You have included the PICTURE symbol P in a Relative Key.

            *   Delete P.

0547     END-IF used with NEXT SENTENCE 

0548     Program is nested 

0549     USING identifier must not be a redefinition 

0550     Pseudo-text consists entirely of a separator comma or semicolon 

0551     Second status field does not comply with VSC2 specifications 

0552     Comment lines precede IDENTIFICATION DIVISION 

0553     syntax :  non-conforming standard ANS85 

            *   The language element is part of the ANSI'85 standard but
                above the flagging level selected.

0554     Syntax is non-conforming non-standard ANS85 

            *   The language element is not part of the ANSI'85 standard.
                It is an OSVS, VSC2, MF, et cetera extension.

0555     syntax :  marked as obsolete in the ANS85 standard 

            *   The ANSI'85 standard has defined this language element as
                obsolete.  It will be removed from the next ANSI
                standard.

            *   Delete this syntax.

0556     Multiple program source 

            *   Source file contains more than one source program.  In
                this situation there is more than one separate, not
                nested, program.

0557     Multiple GIVING files 

            *   A SORT or MERGE statement contains multiple files in the
                GIVING clause

0558     Comparison between index-name and arithmetic expression 

0559     Statement cannot be reached 

0560     Alphabet declared without ALPHABET keyword 

0561     A "NOT" phrase did not have a matching verb and was discarded 

            *   You declared a NOT phrase but failed to declare a
                matching verb.

            *   Add the appropriate verb.

0562     An "ELSE" phrase did not have a matching IF and was discarded 

            *   You declared an ELSE phrase but failed to declare a
                matching IF.

            *   Resolve the mismatch between the conditional verbs.

0563     A "WHEN" phrase did not have a matching verb and was discarded 

            *   You declared a WHEN phrase but failed to declare a
                matching verb.

            *   Add the appropriate verb.

0564     A scope-delimiter did not have a matching verb and was discarded 

            *   You declared a scope-delimiter but failed to declare a
                matching verb.

            *   Resolve the mismatch between the conditional verbs.

0565     RECORDING MODE used with INDEXED or RELATIVE file 

0566     This release does not support floating point in this context 

0567     USAGE DISPLAY-1 missing 

            *   You have omitted the words USAGE DISPLAY-1.

            *   Add USAGE DISPLAY-1.

0568     Sign condition in EVALUATE statement 

0569     Data item does not have fixed location 

0570     Insufficient space in area B for SO/SI insertion 

            *   There is insufficient space in area B for SO/SI
                characters to be inserted for the DBCS items.  If the
                source program is ported to an environment requiring
                SO/SI characters the source line may become corrupted.

0571     Mixed literal is continued 

0572     INITIALIZE operand does not have fixed location 

0573     More than one REPLACING phrase 



MPE/iX 5.0 Documentation