HP 3000 Manuals

List of Messages (0540 - 0733) [ Micro Focus COBOL Error Messages ] MPE/iX 5.0 Documentation


Micro Focus COBOL Error Messages

List of Messages (0540 - 0733) 

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 VS COBOL II 
            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 OS/VS COBOL, VS COBOL II, Micro
                   Focus, or other 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, more than one separate, not nested,
                   program exists.

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 

               *   You do not have sufficient 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 might become
                   corrupted.

0571        Mixed literal is continued 

0572        INITIALIZE operand does not have fixed location 

0573        More than one REPLACING phrase 

0574        Conditional statement not terminated by its scope-delimiter 

0575        Zero suppression follows floating insertion 

0576        Preceding statement is not imperative 

0577        Group level USAGE does not match PICTURE type--USAGE ignored 

               *   You have declared a PICTURE clause but the group USAGE
                   does not match this type.

               *   Either delete the USAGE clause or change the PICTURE
                   clause.

0578        PROGRAM-ID specified as literal 

0579        PROGRAM-ID is DBCS name 

0580        User-defined word as DBCS name 

0581        END-SEARCH used with NEXT SENTENCE 

0582        Redefined item has OCCURS phrase 

0583        EXIT PROGRAM in GLOBAL declarative 

0584        Inline PERFORM statement not terminated by END-PERFORM 

0585        Imperative statement missing 

               *   You have failed to specify an imperative statement.

               *   Include an imperative statement.

0586        Smallest record size size1 > minimum in RECORD clause size2 

               *   You have specified a minimum size for your record
                   definitions, but none of the records you have defined
                   is that small.

               *   Revise your code so that the minimum size specified is
                   equal to your smallest data record.

0587        Largest record size size1 <maximum in RECORD clause  size2 

               *   You have specified a maximum size for your record
                   definitions, but none of the records you have defined
                   is that large.

               *   Revise your code so that the maximum size specified is
                   equal to your largest data record.

0588        Operand does not have USAGE DISPLAY 

0589        Procedure Division does not finish with complete sentence 

0590        USING/GIVING file does not have ORGANIZATION SEQUENTIAL 

0591        USING/GIVING file has ACCESS RANDOM 

0592        USING/GIVING file has ACCESS DYNAMIC 

0593        Sequence number contains nonnumeric characters 

0594        Variable length group is operand of INITIALIZE statement 

0595        SORT file has FILE STATUS clause 

0596        01 level record in Report Section is elementary 

0597        Object of SUM clause belongs to different report 

0598        Assignment-name is alphanumeric literal 

0599        Literal form of CODE phrase 

0600        Name is implicitly qualified 

0601        USE BEFORE REPORTING on DETAIL group 

0602        Neither LINE nor LINES specified 

0603        SIGN phrase in Report Section 

0604        GLOBAL specified for entry without data-name 

0605        More than one SUM for single item 

0606        Program does not contain PROCEDURE DIVISION 

0607        PROCEDURE DIVISION header missing 

0608        Pseudo-text delimiter preceded / followed by illegal 
            character 

               *   The pseudo text delimiters used in COPY...REPLACING
                   and REPLACE must be preceded by a space and followed
                   by a separator.  The system assumes one was present.

0609        Apostrophe found with QUOTE directive (future occurrences not 
            flagged)  

0610        Quote found with APOST directive (future occurrences not 
            flagged)  

0611        Line:  line-no Column:  column-no 

0612        EXIT PROGRAM not in separate paragraph 

0613        Invalid program name 

0614        Previous LINE clause specified same number 

0615        Floating point data item 

0616        This EXIT statement format defined in Codasyl JOD 

0617        Data item is defined at level 66 

0618        Data item is not declared in Linkage Section 

0619        User-name mixes single-byte and double-byte characters 

0620        DBCS user-name exceeds 14 characters in length 

0621        DBCS user-name begins with DBCS equivalent of SBCS "-" 
            character 

0622        DBCS name contains illegal character 

0623        DBCS name contains only DBCS characters equivalent to SBCS 
            characters 

0624        Belongs to Linkage record not specified in PROCEDURE DIVISION 
            header 

0625        Alphabetic edited item treated as alphabetic 

0626        Edited field not allowed 

0627        Section header not followed by paragraph name or other 
            Section header 

0628        Use of symbolic literal defined in level 78 or CONSTANT 
            directive 

0629        Use of signed or non-integer numeric literal 

0630        INTO not legal for this file 

0631        GLOBAL specified in Linkage Section 

0632        A FUNCTION cannot be a receiving item 

0633        REPORT HEADING extends beyond first detail.  NEXT GROUP NEXT 
            PAGE assumed 

0634        Feature not supported in selected dialect 

0635        VALUE specified for external floating point data item 

0636        Level 88 defined on external floating point data item 

0637        ACCEPT references internal floating point data item 

0638        Floating point data illegal in DIVIDE with REMAINDER clause 

0639        Reserved word OR missing 

0640        Floating point data item used in SEARCH ALL statement 

0641        '.'  missing following procedure name declaration, or 
            unrecognized verb 

0642        Source and target start at same location 

0643        Source and target overlap, and source is at a higher address 
            than target 

               *   If the source and target items in a move overlap, the
                   result of the move is undefined.

0644        Mantissa has more than 16 numeric positions 

0645        Floating-point value out of range 

0646        ODO item for non-Local-Storage item cannot be in 
            Local-Storage 

0647        CURSOR data item cannot be in Local-Storage 

0648        Illegal use of Local-Storage item 

0649        Record length exceeds system limit 

0650        No matching $IF--ignored 

               *   A $END or $ELSE conditional compilation statement has
                   been found without a preceding $IF. The line was
                   ignored.

0651        SORT key cannot have, or be subsidiary to item with, OCCURS 
            clause 

0653        COMP-1 support not implemented in SQL--recode using COMP-2 

0654        NEXT GROUP specified for group with no LINE NUMBER clause 

0655        NEXT GROUP NEXT PAGE specified for report without PAGE 
            description 

0656        Source and target overlap, and source is at lower address 
            than target 

0657        Should be declared in Linkage Section 

0658        NUMERIC class test on ALPHABETIC item 

0659        Screen name mandatory at 01 level in Screen Section 

0660        Positive signed integer used in relative subscripting 

0661        Superfluous TO found in MOVE statement.  Ignored 

0662        Figurative constant or ALL not allowed here 

0663        LENGTH function in non-standard context 

0664        INPUT-OUTPUT Section precedes CONFIGURATION Section 

0665        Communications syntax incorrect 

0666        Reserved word used as data-name or unknown data description 
            qualifier 

0667        ODO object object must have fixed location 

0668        JUSTIFIED specified on edited field 

0669        EVALUATE statement using partial conditional expressions 

0670        Selection object does not correspond to selection subject 

0671        PERFORM UNTIL EXIT 

0672        COPY nested in COPY REPLACING 

0673        Incompatible options specified 

0674        Subscripting and indexing used for the same identifier 

0675        Numeric FUNCTION used as source of MOVE statement 

0676        THEN used instead of THAN 

0677        Value of previous expression cannot be the same under OSVS/ 
            VSC2 

0678        Too many CONTROLS specified for report 

0679        QUOTE character must be double in an N literal 

0680        N" format literal 

0681        Function argument must be positive 

0682        Function argument must be positive or zero 

0683        Function argument must be nonzero 

0684        Function argument must be between -1 and +1 

0685        Function argument must be greater than -1 

0686        Function argument must be between 1 and collating sequence 
            length 

0687        Use of PROCEDURE-POINTER data item 

0688        Use of "C" or "R" as currency sign 

0689        Condition-name cannot be set to FALSE (no FALSE value 
            specified)  

               *   You have tried to set a level-88 item to FALSE without
                   having specified the WHEN SET TO FALSE clause in the
                   item's data description.

0690        Illegal use of floating-point literal 

0691        Simple COPY and qualified COPY both used in the same program 

               *   You have mixed two different copies of copylbr in the
                   same program.  You must not use COPY statements if
                   some have qualification and some have not.

0692        REPORT specified in more than two FDs 

0693        Cannot be an external item 

0694        Identifier is reference modified 

0695        EXTERNAL program 

0696        Data-name must be specified with TYPEDEF 

0697        Data item is redefinition of KEY, rather than the key  itself

0698        Use of positive literal in AFTER ADVANCING phrase 

0699        ADVANCING PAGE and END-OF-PAGE used in same WRITE statement 

               *   Under ANS85 and VSC2, ADVANCING PAGE and END-OF-PAGE
                   are not allowed in the same WRITE statement.

0700        Function argument is wrong format 

               *   You have supplied an argument to an intrinsic function
                   which is of the wrong format, for example
                   INTEGER-OF-DAY requires a date of a certain format.

               *   Check the format of your argument against the
                   documentation and recode.

0701        Alphabet-name must be preceded by ALPHABET 

0702        Alphabetic class expanded to include lower-case letters 

0703        ON OVERFLOW will execute under more conditions 

0704        Comparison between scaled integer and nonnumeric is different 

               *   You are trying to compare a scaled integer with a
                   numeric edited or alphanumeric item.

0705        ":" treated as a separator 

0706        Non-COBOL character character found.  Results might be 
            different 

               *   Your COBOL system has found non-COBOL characters when
                   trying a COPY REPLACING BY operation.  The results
                   might be different on other environments.

0707        An implicit EXIT PROGRAM will be executed at end of program 

0708        PICTURE consists of A's and B's.  Treated as 
            alphanumeric-edited 

0709        Order of initialization different for PERFORM...  VARYING..
            .  AFTER 

0710        The maximum length of receiver receiver will be used 

0711        RECORD CONTAINS with one integer is supported differently 

               *   The behavior of the RECORD CONTAINS clause differs
                   between OSVS and VS COBOL II.

0712        The file status values are different 

               *   The file status values for file operations differ
                   between environments.

0713        Subscripting and ODO for UNSTRING evaluated at start of 
            statement 

0714        Non-space characters following "." are ignored 

0715        EXIT not followed by "." 

0716        EXIT PROGRAM not followed by "." 

0717        Shift out character not followed by valid DBCS character 

0718        Shift out character not matched with shift in, or vice versa 

0719        I-O CONTROL paragraph contains multiple sentences 

0720        SEQUENTIAL file used as CALL parameter 

0721        Non-SEQUENTIAL file used as CALL parameter 

0722        Data item too small (must be at least 16 characters long)  

0723        USE...GIVING option 

0724        Period follows SKIP1/ 2/ 3 or EJECT 

0725        Function argument invalid, year must be greater than 1600 

               *   See the section Intrinsic Functions in the chapter
                   Program Definition in your Language Reference.

0726        Function argument invalid, month must be an integer between 1 
            and 12 

0727        Function argument invalid, day must be an integer between 1 
            and 31 

0728        Function argument invalid, day must be an integer between 1 
            and 366 

0729        OO: Use skeleton parameter parameter-name not specified in 
            USING 

               *   Parameters to user defined syntax must be listed in
                   the PROCEDURE DIVISION USING clause of the program.

0730        OO: Use skeleton definition too long 

               *   The definitions of user defined syntax are restricted
                   in size.

               *   Shorten your syntax definition, for example, by
                   omitting optional noise words.

0731        OO: Syntax matches more than one use skeleton--first assumed 

               *   The syntax defined in the program matches more than
                   one user defined syntax definition.  The code could be
                   ambiguous.  However, in many cases the definitions
                   resolve to the same method.  The Compiler uses the
                   first matching definition.

0732        OO: Syntax options do not match any use skeleton 

               *   The code in the program does not match any user
                   defined syntax definition.

0733        OO: FUNCTION skeleton not permitted--no RETURNING/GIVING 
            phrase specified 

               *   User-defined syntax FUNCTIONs can only be defined for
                   methods which have a RETURNING or GIVING phrase on the
                   PROCEDURE DIVISION.



MPE/iX 5.0 Documentation