Trailing-Edge
-
PDP-10 Archives
-
BB-H506E-SM
-
cobol/source/diags.mac
There are 23 other files named diags.mac in the archive. Click here to see a list.
; UPD ID= 3535 on 5/8/81 at 12:09 PM by NIXON
TITLE DIAGS FOR COBOL V12C
SUBTTL DIAGNOSTIC MESSAGES AL BLACKINGTON/CAM
SEARCH COPYRT
SALL
;COPYRIGHT (C) DIGITAL EQUIPMENT CORPORATION 1974, 1985
;ALL RIGHTS RESERVED.
;
;THIS SOFTWARE IS FURNISHED UNDER A LICENSE AND MAY BE USED AND COPIED
;ONLY IN ACCORDANCE WITH THE TERMS OF SUCH LICENSE.
SEARCH P
%%P==:%%P
RPW==:RPW
DBMS==:DBMS
MCS==:MCS
TCS==:TCS
;EDITS
;NAME DATE COMMENTS
;JEH 07-JUN-84 [1537] Change message for E.654
;JEH 24-OCT-83 [1502] Warning if record size < max record size
;JEH 10-OCT-83 [1500] Warnings on HIGH/LOW VALUES with numeric fields
;JEH 02-MAY-83 [1466] Change message 365 to include POSITIONING
;RLF 19-APR-83 [1460] Gives error message when key is subscripted
;RLF 27-JAN-83 [1450] Gives error message on FREE syntax
;DMN 09-NOV-82 [1431] Fix error message added by edit 1046
;JEH 26-OCT-82 [1424] Add error for non-DISPLAY data in ASCII file
;SMI 08-OCT-82 [1416] 68274 Generate warning for size differences
;SMI 08-OCT-82 [1415] Add 68274 message for generating SET TALLY
;SMI 25-AUG-82 [1401] Fatal if statements in EXIT paragraph
;JEH 05-MAY-82 [1353] Fatal if operand too large for literal compare
;DMN 07-APR-82 [1350] Add 68274 message for DISPLAY or STOP signed integer.
;JEH 30-MAR-82 [1346] Fatal on data key conv rtn, nbr of table keys
;DMN 12-MAR-82 [1340] Add 68274 message for Abbrev. Combined Relation
; Condition with NOT and JUSTIFIED clause in VALUE
;JEH 01-JAN-82 [1330] Warning for invalid memory size
;WTK/JM 30-Sep-81 [1312] Add Diag 651 for -,---... and +,+++...
;V12B**********************
;V12*****************
;JSM 2-Feb-81 [1116] Add diag 648 for UNSTRING.
;DAW 12-Dec-80 [1102] Make diag 64 more accurate.
;DMN 14-NOV-80 [1071] GIVE ERROR MESSAGE IF VARIABLE PART IS NOT LAST THING IN RECORD.
;CLRH 12-AUG-80 [1046] IN FIND RSE3, ID MUST BE 1-WORD COMP.
;DMN 22-APR-80 [1013] ADD ERROR FOR MISSING == ON COPY REPLACING.
;JSM 2-APR-80 [1005] ADD ERROR FOR ILLEGAL IF OR SEARCH IN WHEN CLAUSE OF SEARCH.
;DMN 26-MAR-80 [1002] ADD ERRORS 629 & 630 FOR ILLEGAL CALL/ENTER ARG.
;JSM 29-JAN-80 [761] MAKE MESSAGES 117, 148, 154, 264, 414, AND 419
; MORE EXPLICIT FOR DML COMPILES
;CLRH 3-MAY-79 [706] ADD 622 RECORD SIZE SHOULD MATCH FD
;DMN 5-JAN-78 [624] RECORD SIZE DOES NOT MATCH FD IN "F" MODE FILE
;DMN 29-DEC-78 [623] ADD ERROR MESSAGE FOR SORT KEY CONTAINING OCCURS CLAUSE
;DMN 19-SEP-78 [557] VARIOUS COPY REPLACING BUGS
;EHM 17-SEP-78 [554] ADD 610 FOR SORT KEY NOT IN SORT FILE
;EHM 17-SEP-78 [553] ADD 609 FOR MAX NUM RECORDS/RERUN EXCEEDED
;EHM 17-SEP-78 [552] ADD 608 FOR NO END DECLARATIVES IF DECLARATIVES
;V10*****************
;SSC 28-SEPT-77 ADDED 594 FOR OPEN TRANSACTION STATEMENT
;EHM 19-SEP-77 [511] CHANGE 323 TO INDICATE THAT SEARCH USES
; THE SAME PATHS AND ADDRESS TABLE.
;MDL 28-JUL-77 [505] ADDED #595 - GIVE FATAL MESSAGE WHEN MODE AND KEY TYPE CONFLICT
;MDL 26-APR-77 [471] ADDED 593 - GIVE FATAL MESSAGE WHEN AN
; "OCCURS" EXCEEDS MAXIMUM OF 32,767.
;EHM 28-DEC-76 [456] ADDED 591 - GIVE WARNING OF INVALID ROUNDING
;MDL 04-NOV-76 [447] ADDED 590 - GIVE WARNING IF ATTEMPTING TO 'ACCEPT' MORE
; THAN 1023 CHARACTERS INTO AN AREA.
; 21-SEP-76 [444] ADDED 568 - COMPARE LENGTH FOR 'IF' STATEMENT EXCEEDED
; 30-JAN-76 [405] FIX END OF 1ST TABLE AND TYPE OUT OF UNDEFINED DIAG NUMBERS
;GPS 12/23/74 ADD DIAGNOSTICS FOR SIMULTANEOUS UPDATE
;ACK 12-JAN-75 ADD CAPABILITY OF HAVING DIAGNOSTICS UP TO 1023.
;DBT 1/24/75 MESSAGE 565 - CANCEL OF CURRENT SUBROUTINE
;********************
; EDIT 355 ADDED 587
; EDIT 342 USE ERROR MSG 497 FOR REPORT LINE CODE MISSING
;EDIT 331 ADD ERROR MSG FOR SECTIONS OUT OF ORDER CAUSED BY MIS-
; PLACED SCHEMA SECTION
; EDIT 315 ADD MORE REPORT WRITER ERROR CODES.
; EDIT 312 MAKE ERROR 410 INDEPENDENT OF DBMS ASSY SWITCH
; EDIT 257 ADDED 488
; EDIT 253 CHANGE RENAMES MSG
;[237] /JEF COBOLC.MAC, DIAGS.MAC QAR-2918
; IDENTIFIERS GIVEN IN THE CONTROL CLAUSE MUST BE DEFINED
; ONLY IN THE FILE OR WORKING STORAGE SECTIONS.
;[220] /ACK GENERATE AN ERROR IF A MINOR KEY IS THE SUBJECT OF AN OCCURS.
;EDIT 215 COBOLC, DIAGS -- REPORT WRITER BUG
; ERROR IF HEADING < FIRST-DETAIL < LAST-DETAIL < FOOTING
; EDIT 213 ADD COPY WITHIN LIBARY ERROR MSG # 492
;EDIT 212 "CANCEL IS NOT IMPLEMENTED YET..."
;EDIT 162 "NOT ALLOWED IN LINKAGE SECTION"
;EDIT 137 GIVE ERROR MESSAGE IF SUBSCRIPT IS IN LINKAGE SECTION
;EDIT 110 NO MULTIPLE WORKING STORAGE
; RESERVE ALTERNATE AREAS GIVES TOO MANY BUFFERS
; ALTER STATEMENT GETS ERROR IF PRG COMPILED WITH /A
; LAST STATEMENT IN PARA IS AN OPEN NOT TERMINATED BY A
; PERIOD GETS NO WARNING.
TWOSEG
.COPYRIGHT ;Put COPYRIGHT statement in .REL file.
RELOC 400000
XALL
ENTRY SETDN
INTERNAL SETFAK
EXTERNAL FAKERA
;THIS ROUTINE SETS UP "TE" TO POINT TO THE MESSAGE
; WHOSE NUMBER IS IN "TB"
SETDN: LDB TE, TBNUM ;GET THE DIAG NUMBER.
CAIG TE, LASTLO ; [405] POINTER IN THE FIRST TABLE?
JRST SETDN1 ;YES.
CAIGE TE, FRSTB2 ;BETWEEN FIRST AND SECOND TABLES?
JRST SETDN3 ;YES, FAKE IT.
CAIG TE, RLSTHI ;SECOND TABLE?
JRST SETDN2 ;YES.
CAIG TE, LASTHI ;BETWEEN SECOND AND THIRD TABLES?
JRST SETDN3 ;YES, FAKE IT.
CAILE TE, LSTDIG ;IN THE THIRD TABLE?
JRST SETDN3 ;NO, FAKE IT.
MOVE TE, TABLE3-<LASTHI+1>(TE) ;GET THE POINTER.
JRST .+3 ;GO SEE IF THERE REALLY IS A MSG.
SETDN1: SKIPA TE, TABLE1(TE) ;GET IT FROM THE FIRST TABLE.
SETDN2: SKIPE TE, TABLE2-FRSTB2(TE) ;GET IT FROM THE SECOND TABLE.
JUMPN TE, CPOPJ ;IF THERE REALLY WAS A POINTER
; RETURN, OTHERWISE FAKE IT.
;FAKE DIAGNOSTIC REQUIRED
SETDN3: LDB TE,TBNUM ;CONVERT DIAG # TO DECIMAL
IDIVI TE,12
LSHC TD,-7
IDIVI TE,12
LSHC TD,-7
IDIVI TE,^D10
LSHC TD,^D14+^D15
LSHC TE,^D21
ADD TE, ["0000"]
DPB TE,[POINT 28,FAKERA+3,34]; STASH # IN MESSAGE
LDB TE,TBFAZE
DPB TE,[POINT 4,FAKERA+6,20]
MOVE TE,[POINT 7,FAKERA,6]
CPOPJ: POPJ PP,
SETFAK: XWD .+1,7
ASCIZ /FDiagnostic no. XXXX from phase A/
;IF THE FIRST CHARACTER OF A DIAGNOSTIC MESSAGE IS "A", THAT
; MESSAGE WILL APPEAR AT THE END OF THE SOURCE LISTING.
;IF THE CHARACTER IS "F", THE DIAG IS FATAL.
;IF ANY OTHER CHARACTER (SPECIFICALLY "W"),
; THE DIAG IS A WARNING IMBEDDED IN SOURCE LISTING.
DEFINE ERROR (X,Y),<
XLIST
.XCREF
ERA'X: ASCIZ $'Y'$
IFG ^D'X-LASTLO,<
IFL ^D'X-FRSTB2,<LASTLO==^D'X>>
IFG ^D'X-RLSTHI,<
IFL ^D'X-LASTHI,<RLSTHI==^D'X>>
IFG ^D'X-LSTDIG,<LSTDIG==^D'X>
.CREF
LIST
>
INTERNAL FRSTHI
INTERNAL LASTHI
LASTLO==0
LASTHI==0 ;LAST MESSAGE IN TABLE 1.
RLSTHI==0 ;LAST MESSAGE IN TABLE 2.
LSTDIG==0 ;LAST MESSAGE IN TABLE 3.
FRSTHI==^D500 ;FIRST MESSAGE REQUIRING
; ADDITIONAL DATA.
FRSTB2==FRSTHI-4 ;FIRST MESSAGE IN TABLE 2.
LASTHI==^D550 ;LAST POSSIBLE MESSAGE IN TABLE 2.
; NOTE: TABLE 3 STARTS AT 551.
ERROR 1,<FFirst word not IDENTIFICATION.>
ERROR 2,<FBlocking factor greater than 4095.>
ERROR 3,<FMore than one PROGRAM-ID.>
ERROR 4,<FImproper PROGRAM-ID.>
IFE TOPS20,<
ERROR 5,<WDECsystem-10 assumed.>
>
IFN TOPS20,<
ERROR 5,<WDECSYSTEM-20 assumed.>
>
ERROR 6,<FMore than one OBJECT-COMPUTER paragraph.>
ERROR 7,<FImproper paragraph name.>
ERROR 8,<FThe word SELECT expected.>
ERROR 9,<FFile SELECTed more than once.>
ERROR 10,<FASSIGN is the only allowed word here.>
ERROR 11,<FNo device name specified.>
ERROR 12,<FOnly one device of this type allowed.>
ERROR 13,<FNo file name given.>
ERROR 14,<FProcessing mode must be SEQUENTIAL.>
ERROR 15,<FImproper ACCESS mode.>
ERROR 16,<FClause duplicated.>
ERROR 17,<FThis cannot be a data name.>
ERROR 18,<FImproper clause.>
ERROR 19,<FImproper SEGMENT-LIMIT.>
ERROR 20,<FThis file not SELECTed.>
ERROR 21,<FThis cannot be a file-name.>
ERROR 22,<FPosition number required.>
ERROR 23,<FNot on same device as previous file listed.>
ERROR 24,<FCannot be used as a mnemonic name.>
ERROR 25,<FPositive integer required.>
ERROR 26,<FCannot be used as a condition name.>
ERROR 27,<FMust be a single-character non-numeric literal.>
ERROR 28,<FAlready in use as a mnemonic name.>
ERROR 29,<FMore than one RERUN clause for this file.>
ERROR 30,<FParagraph appears more than once.>
ERROR 31,<FNo DATA DIVISION.>
ERROR 32,<FNo PROCEDURE DIVISION.>
ERROR 33,<FAll records for this file must have same usage.>
ERROR 34,<FThis file already defined.>
ERROR 35,<FRecord name not unique within this file.>
ERROR 36,<FThis is a multi-device file.>
ERROR 37,<WThis record not mentioned in DATA RECORDS clause.>
ERROR 38,<FNo record name given.>
ERROR 39,<FThis is not previous item at this level.>
ERROR 40,<FThis is not a numeric item.>
ERROR 41,<FUsage conflicts with group item.>
ERROR 42,<FThis clause not valid for group item.>
ERROR 43,<FImproper section name.>
ERROR 44,<FNot a SORT file.>
ERROR 45,<FThis must be a literal.>
ERROR 46,<FNot allowed in this section.>
ERROR 47,<FData name not defined in this record.>
ERROR 48,<FNew record expected here.>
ERROR 49,<FNo value given.>
;MESSAGE 50 SEEMS TO DUPLICATE MESSAGE 171
; ERROR 50,<FSection duplicated.>
ERROR 51,<FImproper PICTURE - this character invalid.>
ERROR 52,<FImproper PICTURE - this character not
allowed in combination with preceding characters.>
ERROR 53,<FA word may not begin with a hyphen.>
ERROR 54,<FA word may not end with a hyphen.>
ERROR 55,<FToo many characters in the word.>
ERROR 56,<FToo many characters in the literal.>
ERROR 57,<FInvalid character.>
ERROR 58,<FCannot be used as an index name.>
ERROR 59,<FThis item does not have usage INDEX.>
ERROR 60,<FNot uniquely defined.>
ERROR 61,<FMore than three levels of OCCURS.>
ERROR 62,<FVALUE OF ID must be a DISPLAY field of 9 characters.>
ERROR 63,<FVALUE OF DATE-WRITTEN must be a DISPLAY field of 6 characters.>
ERROR 64,<FLevel numbers must be in range 01-49.> ;[1102]
ERROR 65,<FInvalid clauses for group item.>
ERROR 66,<FREDEFINES not valid at record level in FILE SECTION.>
ERROR 67,<FFOR expected.>
ERROR 68,<FINDEX USAGE items may not have a PICTURE.>
ERROR 69,<WJUSTIFIED clause invalid with numeric items.>
ERROR 70,<WNo ending quote on this literal.>
ERROR 71,<WNo leading quote on continued literal.>
ERROR 72,<FToo many characters in PICTURE.>
ERROR 73,<FImproper continuation character.>
ERROR 74,<FLibrary routine not found.>
ERROR 75,<FNo library specified in command string.>
ERROR 76,<FImproper character for numeric literal.>
ERROR 77,<FMore than one decimal point.>
ERROR 78,<WShould not be preceded by a space.>
ERROR 79,<WShould be followed by a space.>
ERROR 80,<FFile descriptor expected.>
ERROR 81,<WPreceding space assumed.>
ERROR 82,<FSource line too long.>
ERROR 83,<FImproper device name.>
ERROR 84,<FRight parenthesis expected.>
ERROR 85,<FAlready in use as a condition name.>
ERROR 86,<FRelational operator expected.>
ERROR 87,<FON or OFF expected.>
ERROR 88,<FIntermediate result too large.>
ERROR 89,<FValues not allowed in LINKAGE SECTION.>
ERROR 90,<FAltering independent segment from another segment.>
ERROR 91,<FNot implemented in this version of COBOL.>
ERROR 92,<FExternal program name expected.>
ERROR 93,<FDummy argument must be an 01 LINKAGE SECTION item.>
ERROR 94,<WThis paragraph is never ALTERed.>
ERROR 95,<FIllegal entry name.>
ERROR 96,<FDecimal places not allowed.>
ERROR 97,<FNo file-descriptor for this file.>
ERROR 98,<FMust be an integer in the range 0 - 66.>
ERROR 99,<FMust be a printer channel.>
ERROR 100,<FNot yet implemented.>
ERROR 101,<FIdentifier expected.>
ERROR 102,<WNot a device name -- TTY assumed.>
ERROR 103,<FCannot be a data-name.>
ERROR 104,<FNot defined.>
ERROR 105,<WNo CORRESPONDING elements.>
ERROR 106,<FNot a group name.>
ERROR 107,<FERROR expected.>
ERROR 108,<FSIZE ERROR assumed.>
ERROR 109,<FSIZE ERROR clause incorrect.>
ERROR 110,<FNumeric literal or identifier expected.>
;NOTE THERE IS NO MESSAGE 111. INSTEAD MESSAGE 111 CAUSES
;EITHER 103 OR 104 DEPENDING ON THE SITUATION.
ERROR 112,<FAt least two items must appear before GIVING.>
ERROR 113,<FCannot be ALTERed.>
ERROR 114,<FPROCEED expected.>
ERROR 115,<FParagraph name expected.>
ERROR 116,<WALTERed to proceed to itself.>
ERROR 117,<FFile name or AREA expected.>
ERROR 118,<FNO REWIND or LOCK expected.>
ERROR 119,<FNO REWIND expected.>
ERROR 120,<FBY or INTO expected.>
ERROR 121,<FGIVING clause required.>
ERROR 122,<FALL, LEADING, or UNTIL FIRST expected.>
ERROR 123,<F1-character non-numeric literal expected.>
ERROR 124,<FBY expected.>
ERROR 125,<WPeriod assumed.>
ERROR 126,<FDEPENDING ON clause expected.>
ERROR 127,<FTIMES expected.>
ERROR 128,<FEND expected.>
ERROR 129,<FAT END or INVALID KEY clause missing.>
ERROR 130,<FIdentifier, index, or TO expected.>
ERROR 131,<FIdentifier, index, or literal expected.>
ERROR 132,<FIdentifier, index, TO, UP, or DOWN expected.>
ERROR 133,<FIndex or identifier expected.>
ERROR 134,<FIllegal item in expression: compiler error.>
ERROR 135,<FUnbalanced parenthesis in expression.>
ERROR 136,<FTO expected.>
ERROR 137,<WDIVISION expected.>
ERROR 138,<FParagraph or section name expected.>
ERROR 139,<FSection name expected.>
ERROR 140,<WSECTION expected.>
IFN ANS68,< ;[1401]
ERROR 141,<FOnly notes may appear in remainder of this paragraph.>
> ;[1401]
IFN ANS74,< ;[1401]
ERROR 141,<FOnly comments may appear in remainder of this paragraph.> ;[1401]
> ;[1401]
ERROR 142,<FNot a declarative sentence.>
ERROR 143,<FBEFORE or AFTER expected.>
ERROR 144,<FBEGINNING, ENDING, or ERROR expected.>
ERROR 145,<FREEL, FILE, or UNIT expected.>
ERROR 146,<FLABEL expected.>
ERROR 147,<FPROCEDURE expected.>
ERROR 148,<FStatement expected, or invalid identifier or keyword.>
ERROR 149,<F'=' Expected.>
ERROR 150,<FTALLYING or REPLACING expected.>
ERROR 151,<FA group item may not be a minor key.> ;[220]
ERROR 152,<F'.' or ELSE expected.>
ERROR 153,<FSENTENCE expected.>
ERROR 154,<FINPUT, OUTPUT, I-O, or AREA expected.>
ERROR 155,<FProcedure name expected.>
ERROR 156,<FToo many levels of VARYING.>
ERROR 157,<FFROM expected.>
ERROR 158,<FUNTIL expected.>
ERROR 159,<FRecord name expected.>
ERROR 160,<WThis statement does nothing.>
ERROR 161,<FKEY expected.>
ERROR 162,<FDECLARATIVES expected.>
ERROR 163,<FExternal name expected.>
IFN ANS68,<
ERROR 164,<FMACRO, FORTRAN, or FORTRAN-IV expected.>
>
IFN ANS74,<
ERROR 164,<FMACRO, or FORTRAN expected.>
>
ERROR 165,<FFIRST expected.>
ERROR 166,<FALL, LEADING, FIRST, or UNTIL FIRST expected.>
ERROR 167,<FIllegal sequence of priorities.>
ERROR 168,<FNull PROCEDURE DIVISION.>
ERROR 169,<FNull DECLARATIVES.>
ERROR 170,<FRUN or literal expected.>
ERROR 171,<FDuplicate section name.>
ERROR 172,<FDuplicate paragraph in this section.>
ERROR 173,<FThis file already appears in a SAME RECORD AREA clause.>
ERROR 174,<FThis file already appears in a SAME AREA clause.>
ERROR 175,<FImproper character for CURRENCY SIGN.>
ERROR 176,<FFD expected.>
ERROR 177,<FLABEL RECORDS clause required.>
ERROR 178,<FTwo sections have this name.>
ERROR 179,<FThis paragraph name must be qualified.>
ERROR 180,<FA section, as well as a paragraph in the current section,
has this name.>
ERROR 181,<FThis procedure name is not defined.>
ERROR 182,<FNot a PICTURE.>
ERROR 183,<FNull literal.>
ERROR 184,<FIllegal use of figurative constant.>
ERROR 185,<FImproper reference of procedure name in or out of DECLARATIVES.>
ERROR 186,<FFigurative constant or non-numeric literal must follow ALL.>
ERROR 187,<FThis procedure name is multiply defined.>
ERROR 188,<WThis statement cannot be reached.>
ERROR 189,<FToo many levels of qualification.>
ERROR 190,<FImproper qualification.>
ERROR 191,<FThis file is never OPENed.>
IFN ANS68,<
ERROR 192,<fBLOCK CONTAINS n RECORDS must be specified for RANDOM access files.>
ERROR 193,<FFILE-LIMITS required.>
>
; ERROR 194,<FVariable length records not allowed.>
; ERROR 195,<FFILE-LIMITS not allowed.>
IFN ANS68,<
ERROR 196,<FMultiple REEL/UNIT not allowed.>
>
ERROR 197,<FOnly one device allowed.>
ERROR 198,<FLABELS must be STANDARD.>
ERROR 199,<FVALUE OF ID required.>
; ERROR 200,<FVALUE OF ID & VALUE OF DATE-WRITTEN not allowed.>
ERROR 201,<FNo data record specified.>
ERROR 202,<FNo devices specified.>
ERROR 203,<FThe word DATA expected.>
ERROR 204,<WFile never OPENed.>
IFN ANS68,<
ERROR 205,<FAccess mode must be RANDOM.>
>
IFN ANS74,<
ERROR 205,<FORGANIZATION must be RELATIVE or INDEXED.>
>
ERROR 206,<FNot a record in the FILE SECTION.>
ERROR 207,<FMust contain an integer.>
ERROR 208,<WAT END assumed.>
ERROR 209,<WINVALID KEY assumed.>
ERROR 210,<FThis literal may contain only DISPLAY-6 characters.>
ERROR 211,<FImproper class.>
ERROR 212,<WCondition always true.>
ERROR 213,<WCondition always false.>
ERROR 214,<FWrong number of operands passed from PHASE D: compiler error.>
ERROR 215,<FFound outside an expression: compiler error.>
ERROR 216,<FExpression generator confused: compiler error.>
ERROR 217,<WImpossible to get SIZE ERROR.>
ERROR 218,<WRounding not necessary.>
ERROR 219,<FImproper range of PERFORM.>
ERROR 220,<FPICTURE required.>
ERROR 221,<FPICTURE not permitted.>
ERROR 222,<FBLANK WHEN ZERO not allowed at group level.>
ERROR 223,<FBLANK WHEN ZERO allowed only on numeric display items.>
ERROR 224,<FJUSTIFIED clause not allowed at group level.>
ERROR 225,<FSYNCHRONIZED clause not allowed at group level.>
COMMENT \ ALLOW USAGE INDEX AT GROUP LEVEL 21-MAR-75 /ACK
ERROR 226,<FUSAGE INDEX clause not allowed at group level.>
\
ERROR 227,<WAt least one and no more than eight data names must
be given in a FILE STATUS clause.>
ERROR 228,<WThis record not mentioned in DATA RECORDS or
LABEL RECORDS clause -- DATA RECORD assumed
.>
ERROR 229,<FA maximum of 4095 occurrences allowed.>
ERROR 230,<FCondition-name multiply defined for this item.>
IFN RPW,<
ERROR 231,<FCONTROL identifier or FINAL expected.>
>
ERROR 232,<WEXIT for this procedure cannot be reached.>
ERROR 233,<WOTHERS expected.>
ERROR 234,<FVALUE clause at higher level supersedes VALUE
clause at this level.>
ERROR 235,<FVALUE clause may not appear in a data description containing,
or subordinate to an entry containing, an OCCURS clause.>
ERROR 236,<FGroup items may have only figurative constants or non-numeric
literals as values.>
ERROR 237,<FVALUE clause not permitted in FILE SECTION.>
ERROR 238,<WNon-numeric literal in value clause truncated to size of item.>
ERROR 239,<FDivision by zero not permitted.> ;
ERROR 240,<FACTUAL KEY must be a COMPUTATIONAL item of ten or fewer digits.>
ERROR 241,<FClass of data item inconsistent with VALUE.>
ERROR 242,<FNon-standard characters in VALUE clause.>
ERROR 243,<FSwitch numbers must be in the range 0 through 35.>
ERROR 244,<FUSAGE conflicts with PICTURE.>
ERROR 245,<FToo many digits to left of decimal point in VALUE clause.>
ERROR 246,<FToo many digits to right of decimal point in VALUE clause.>
ERROR 247,<FAn item subordinate to one containing a VALUE clause must not
be JUSTIFIED or SYNCHRONIZED, and must have USAGE DISPLAY-6, DISPLAY-7
OR DISPLAY-9.>
ERROR 248,<FVALUE not in range described by PICTURE.>
ERROR 249,<WVALUE may not be signed.>
ERROR 250,<FWrong number of subscripts.>
ERROR 251,<FImproper subscript.>
ERROR 252,<FVALUE greater than number of occurrences.>
ERROR 253,<FData items with levels of 01, 66, or 77 may not appear in
a RENAMES clause.> ; [253]
ERROR 254,<FData items requiring subscripting may not appear in a
RENAMES clause.> ; [253]
ERROR 255,<FData items appearing in a RENAMES ... THRU ... clause must
belong to the same record.>
ERROR 256,<FData items appearing in a RENAMES ... THRU ... clause may neither be
subordinate to the other.>
ERROR 257,<FThe area defined by the second data item in a RENAMES ... THRU ...
clause must follow the area defined by the first.>
ERROR 258,<FLiteral or figurative constant expected.>
ERROR 259,<FAnother independent item has this name.>
ERROR 260,<FIF syntax scan error -- improper unnesting--compiler error.>
ERROR 261,<FUnbalanced parentheses.>
ERROR 262,<FNo current paragraph - compiler error.>
ERROR 263,<FNull table link - compiler error.>
ERROR 264,<FInteger literal or identifier expected, or NEXT/PRIOR/FIRST/LAST.>
; ERROR 264,<FMust be numeric, and have no decimal places.>
ERROR 265,<FOnly group items allowed in CORRESPONDING.>
ERROR 266,<FMay redefine only the current data item.>
IFN RPW,<
ERROR 267,<FMust be an 01-level report group item.>
>
ERROR 268,<FMore than 12 nested redefinitions.>
ERROR 269,<FAn item containing, or subordinate to an item
containing, an OCCURS clause may not be redefined>
ERROR 270,<FVALUE clause is not permitted in a redefinition.>
ERROR 271,<ARedefinition is not the same size as the redefined item.>
ERROR 272,<FThis must be greater than the first integer.>
ERROR 273,<FImproper use of ALL.>
ERROR 274,<FMust be subscripted.>
ERROR 275,<FMay not be subscripted.>
ERROR 276,<FBad USAGE -- compiler error.>
ERROR 277,<FToo many levels of subscripting.>
ERROR 278,<FMust have a size of 10 digits or less.>
ERROR 279,<FCannot continue after an empty or comment line.>
ERROR 280,<FASCENDING or DESCENDING expected.>
ERROR 281,<FRENAMES expected.>
ERROR 282,<FSORT generator confused -- compiler error.>
ERROR 283,<FImproper name for independent item.>
ERROR 284,<FA record containing DISPLAY-7 items may not
contain items of any other usage.>
ERROR 285,<FThis cannot be a library-name.>
ERROR 286,<FCOPY statement must be terminated by a period.>
ERROR 287,<FLeft parenthesis expected.>
ERROR 288,<FIdentifier, numeric literal, or mnemonic-name expected.>
ERROR 289,<FFILLER may not be referenced directly.>
ERROR 290,<FThis must be a SWITCH ON or OFF STATUS.>
ERROR 291,<FThis file must not appear in an SD.>
ERROR 292,<FCannot have both USING and INPUT PROCEDURE.>
ERROR 293,<FMust have either USING or INPUT PROCEDURE.>
ERROR 294,<FCannot have both GIVING and OUTPUT PROCEDURE.>
ERROR 295,<FMust have either GIVING or OUTPUT PROCEDURE.>
ERROR 296,<FVALUE expected.>
ERROR 297,<FThere is an independent item of this name.>
ERROR 298,<FImproper figurative constant in VALUE clause.>
ERROR 299,<FNo result found -- compiler error.>
ERROR 300,<WRounding not done with COMP-1 fields.>
ERROR 301,<FBLOCK CONTAINS must be specified for a file opened for
INPUT-OUTPUT.>
ERROR 302,<WOnly eight significant places used for COMP-1.>
ERROR 303,<FTHRU expected.>
ERROR 304,<FAt least 3 devices must be assigned to a SORT file.>
REPEAT 0,<
Error 305,<FA file opened for INPUT-OUTPUT or RANDOM access
must have a BLOCK CONTAINS 1 RECORD clause if it is explicitly or
implicitly DISPLAY-7.>
>
ERROR 306,<WSyntax scan suspended at this character.>
ERROR 307,<WSyntax scan resumed at this character.>
ERROR 308,<FThis procedure-name must be in DECLARATIVES.>
ERROR 309,<FThis procedure-name must not be in DECLARATIVES.>
ERROR 310,<FThis procedure-name must be in an INPUT PROCEDURE.>
ERROR 311,<FThis procedure-name is in an INPUT PROCEDURE.>
ERROR 312,<FThis procedure-name must be in an OUTPUT PROCEDURE.>
ERROR 313,<FThis procedure-name is in an OUTPUT PROCEDURE.>
ERROR 314,<FLiterals and reserved words may not be replaced.>
ERROR 315,<FA word may not be replaced by a reserved word.>
ERROR 316,<FAn item may not exceed 262,143 characters.>
ERROR 317,<FThis is neither a data-name nor a procedure-name.>
ERROR 318,<FAT END clause required.>
ERROR 319,<FINVALID KEY clause required.>
ERROR 320,<FAT END and INVALID KEY not allowed.>
ERROR 321,<FThis item must not be COMPUTATIONAL-1.>
ERROR 322,<FA record in the FILE SECTION may not exceed 4095 characters.>
IFN ANS68,<
ERROR 323,<FMore than 12 nested IF/SEARCH statements.>
ERROR 324,<FMore than 12 conditions nested in IF statement.>
>
IFN ANS74,<
ERROR 323,<FMore than 24 nested IF/SEARCH statements.>
ERROR 324,<FMore than 24 conditions nested in IF statement.>
>
ERROR 325,<FOCCURS is illegal at 01 level in FILE SECTION.>
ERROR 326,<FVerb name expected.>
ERROR 327,<FInvalid DENSITY.>
ERROR 328,<FODD or EVEN required.>
ERROR 329,<FNon-sixbit character in VALUE of DISPLAY-6 item.>
ERROR 330,<FA numeric item may not exceed 18 digits.>
ERROR 331,<FTwo literals may not be compared.>
ERROR 332,<FInsufficient qualification.>
ERROR 333,<FFewer than 6 characters in DATE-WRITTEN.>
ERROR 334,<WFewer than 9 characters in IDENTIFICATION.>
ERROR 335,<FSecond half of project-programmer number missing.>
ERROR 336,<FMust be an octal integer of 6 digits or less.>
ERROR 337,<FImproper mode.>
IFN RPW,<
ERROR 338,<FREPORT name must be unique.>
ERROR 339,<FFILE SECTION must precede REPORT SECTION.> ;
>
ERROR 340,<FData item has improper size for this use.>
ERROR 341,<WShould begin in A-margin.>
IFN RPW,<
ERROR 342,<FREPORT not specified in a REPORT clause in FILE SECTION.>
ERROR 343,<FLine number greater than PAGE LIMIT.>
ERROR 344,<FPAGE LIMIT must be positive and less than 512.>
ERROR 345,<FCONTROL identifier expected.>
ERROR 346,<FIf used, FINAL must be the first CONTROL.>
>
ERROR 347,<FDEPENDING variables must be COMP and 10 digits or less.>
IFN RPW,<
ERROR 348,<FClause not legal in report group.>
ERROR 349,<FUSAGE not legal in REPORT SECTION.>
ERROR 350,<FClause legal only in report group.>
ERROR 351,<FPAGE expected.>
ERROR 352,<FMust be less than PAGE LIMIT.>
ERROR 353,<FNot a CONTROL identifier.>
ERROR 354,<FOnly one GROUP of this type allowed per report.>
ERROR 355,<FHEADING or FOOTING required.>
ERROR 356,<FReport item type required.>
ERROR 357,<FNot declared as a CONTROL.>
ERROR 358,<FItem referenced by a SUM clause must be source item in
TYPE DETAIL or item in TYPE CONTROL FOOTING which has
a SUM clause.>
ERROR 359,<FReport-name expected.>
ERROR 360,<FItem will not fit in print line.>
ERROR 361,<FNot a TYPE DETAIL item.>
ERROR 362,<FItem is SUMmed in REPORT SECTION, therefore it must be numeric.>
ERROR 363,<FOnly a CONTROL FOOTING GROUP may have a SUM.>
ERROR 364,<FItem referenced by a SUM UPON clause must be TYPE DETAIL.>
>;END OF RPW
ERROR 365,<FADVANCING/POSITIONING clause illegal with RECORDING MODE other
than ASCII.> ;[1466]
ERROR 366,<FVALUE OF USER-NUMBER must be a COMP item with
fewer than 11 digits.>
IFN RPW,<
ERROR 367,<FMust be defined in either the FILE or WORKING-STORAGE SECTION.>
ERROR 368,<FRESET may be used only with CONTROL-FOOTING items.>
ERROR 369,<FMust be a CONTROL.>
ERROR 370,<FMust be a higher level CONTROL than that of this GROUP.>
>
ERROR 371,<FValid only for files with ACCESS MODE INDEXED.>
ERROR 372,<FADVANCING allowed only on SEQUENTIAL files.>
ERROR 373,<FImproper usage.>
IFN ISAM,<
IFN ANS68,<
ERROR 374,<FRECORD KEY and SYMBOLIC KEY must be same class.>
ERROR 375,<FRECORD KEY and SYMBOLIC KEY must be same USAGE.>
ERROR 376,<FRECORD KEY and SYMBOLIC KEY must be same size.>
ERROR 377,<FRECORD KEY and SYMBOLIC KEY must have the same
number of decimal places.>
>;END IFN ANS68
ERROR 378,<FINDEXED files must not be BINARY.>
ERROR 379,<FRECORD KEY must be in appropriate record.>
>;END IFN ISAM
ERROR 380,<FREDEFINES nesting confused -- compiler error.>
ERROR 381,<FSearched items must have OCCURS clause with INDEXED option.>
ERROR 382,<FA key of more major priority than this was not specified.>
ERROR 383,<FOne operand in every WHEN condition must be a search key.>
ERROR 384,<FAssociated data item must be a search key.>
ERROR 385,<FCondition name must have only a single value.>
ERROR 386,<FSEARCH ALL requires KEY clause in table definition.>
IFN RPW,<
Error 387,<FCODE must not contain non-sixbit characters.>
>
ERROR 388,<WON/OFF expected - ON assumed.>
ERROR 389,<FOnly equality conditions allowed in SEARCH ALL.>
ERROR 390,<FWHEN expected.>
ERROR 391,<FThe only connective in WHEN clause is AND.>
;DONT BELIEVE 392 IS EVER USED
;BUT IF IT IS IT SHOULD BE CHANGED TO 329
; ERROR 392,<FNon-sixbit character in literal.>
IFN ISAM,<
IFN ANS68,<
ERROR 393,<FSYMBOLIC KEY required.>
>
ERROR 394,<FRECORD KEY required.>
>
ERROR 395,<FRECORDS or CHARACTERS required.>
ERROR 396,<FCALL argument must be word-aligned.>
ERROR 397,<FDuplicate ENTRY definition.>
ERROR 398,<FIllegal to call internal ENTRY.>
IFN RPW,<
ERROR 399,<FPAGE-COUNTER and LINE-COUNTER may not be independently defined when report writer features are used.>
>
ERROR 400,<FImproper punctuation.>
ERROR 401,<FNot declared in an ENTRY or PD USING clause.>
ERROR 402,<FDuplicate WORKING-STORAGE SECTION.>
IFN DBMS,<
ERROR 403,<FSet-name or ANY expected.>
ERROR 404,<FSET expected.>
ERROR 405,<FERROR-STATUS expected.>
ERROR 406,<FIllegal combination of ERROR-STATUS USE PROCEDURES.>
ERROR 407,<FArea-name expected.>
ERROR 408,<FDuplicate SCHEMA SECTION.>
ERROR 409,<FALL, RECORD, AREA, SET, or set-name expected.>
> ; [312] END IFN DBMS
ERROR 410,<WThis name shouldn't be more than 6 characters.>
IFN DBMS,<
Error 411,<FINTO expected.>
ERROR 412,<FALL or set-name expected.>
ERROR 413,<FCOMPILE expected.>
ERROR 414,<FINVALID, ONLY, SELECTIVE, ALL or no qualification expected.>
ERROR 415,<FSELECTIVE, ONLY, ALL, or record-name expected.>
ERROR 416,<FRecord-name, set-name, area-name, or RUN-UNIT expected.>
ERROR 417,<FRECORD expected.>
ERROR 418,<FFOR expected.>
ERROR 419,<FAREA or SET expected, or invalid previous identifier.>
ERROR 420,<FSUB-SCHEMA or sub-schema name expected.>
ERROR 421,<FINVOKE statement must follow SCHEMA SECTION.>
ERROR 422,<FSet-name expected.>
ERROR 423,<FCURRENT expected.>
ERROR 424,<FAmbiguous or incorrect RSE specification.>
ERROR 425,<FEXCLUSIVE, PROTECTED, or RETRIEVAL expected.>
ERROR 426,<FSet-name or area-name expected.>
ERROR 427,<FRECORD or record-name expected.>
ERROR 428,<FNo more than 10 area-names allowed per OPEN statement.>
ERROR 429,<FIncorrect privacy key.>
ERROR 430,<FUPDATE expected.>
ERROR 431,<FDECLARATIVES must immediately follow PROCEDURE DIVISION.>
>
IFN MCS!TCS,<
Error 432,<FDuplicate COMMUNICATION SECTION.>
ERROR 433,<FCOMMUNICATION SECTION must precede REPORT SECTION.>
ERROR 434,<FMore than 11 data items in input CD.>
ERROR 435,<FCD-name expected.>
ERROR 436,<FINITIAL, INPUT or OUTPUT expected.>
ERROR 437,<FINPUT expected.>
ERROR 438,<FInvalid queue specification.>
ERROR 439,<FDATE, TIME or COUNT expected.>
ERROR 440,<FLENGTH expected.>
ERROR 441,<FIS or data-name expected.>
ERROR 442,<FOCCURS expected.>
ERROR 443,<FDESTINATION expected.>
ERROR 444,<FCLASS expected.>
>
IFN MCS!TCS,<
ERROR 445,<FNumber of occurences in destination table must be less than 51.>
; ERROR 445,<FNumber of occurences in destination table must be equal to 1.>
ERROR 446,<FMore than one INITIAL input CD.>
ERROR 447,<WClause previously used.>
ERROR 448,<FINPUT or OUTPUT expected.>
ERROR 449,<FTERMINAL or cd-name expected.>
ERROR 450,<FInvalid password.>
ERROR 451,<FMESSAGE or COUNT expected.>
ERROR 452,<FCOUNT expected.>
ERROR 453,<FMust be an output CD.>
ERROR 454,<FMust be alphanumeric.>
ERROR 455,<FInvalid end indicator.>
ERROR 456,<FDuplicate cd-name.>
ERROR 457,<FFROM or WITH expected.>
ERROR 458,<FMust be an input CD.>
>
IFN MCS!TCS,<
ERROR 459,<FMESSAGE or SEGMENT expected.>
; ERROR 459,<FMESSAGE expected.>
>
ERROR 460,<FPOINTER expected.>
ERROR 461,<FOVERFLOW expected.>
ERROR 462,<FDELIMITED BY clause required.>
IFN MCS!TCS,<
ERROR 463,<FMust be a channel number.>
>
ERROR 464,<FCannot be an edited item.>
ERROR 465,<WPointer, counter or tallying item may have too few digits.>
IFN MCS!TCS,<
ERROR 466,<FReceiving item contained in cd-record.>
>
IFN DBMS,<
ERROR 467,<FSTATUS expected.>
>
ERROR 468,<FOR or INTO expected.>
ERROR 469,<WCANCEL is not implemented yet -- this sentence ignored.>
IFN DBMS!MCS!TCS,<
ERROR 470,<FThis section is out of order.> ;[%331]
ERROR 471,<FSchema name may not also be a reserved word or data name or PROGRAM ID.> ;[sc]
>
IFN RPW,<
ERROR 472,<FDuplicate CONTROL HEADING GROUP for this identifier.> ; [315]
ERROR 473,<FDuplicate CONTROL FOOTING GROUP for this identifier.> ; [315]
ERROR 474,<FColumn number must be greater than previous one in report line.> ; [315]
ERROR 475,<FSOURCE or VALUE or (for CONTROL FOOTING only) SUM clause required.> ; [315]
ERROR 476,<FRESET clause not allowed at GROUP level.> ; [315]
ERROR 477,<FGROUP INDICATE clause not allowed at GROUP level.> ; [315]
ERROR 478,<FCOLUMN NUMBER illegal at GROUP level.> ; [315]
ERROR 479,<FSOURCE or SUM or VALUE clause not allowed at GROUP level.> ; [315]
ERROR 480,<FNEXT GROUP clause allowed only at an 01 GROUP level.> ; [315]
ERROR 481,<FRESET FINAL clause allowed only if there is a CONTROL FINAL.> ; [315]
ERROR 482,<FGROUP INDICATE clause allowed only for TYPE DETAIL.> ; [315]
ERROR 483,<FCONTROL FOOTING line number must be from FIRST DETAIL to FOOTING inclusive.> ; [315]
ERROR 484,<FCONTROL HEADING or DETAIL line number must be from FIRST DETAIL to LAST DETAIL inclusive.> ; [315]
ERROR 485,<FPAGE HEADING line number must be from HEADING to FIRST DETAIL inclusive.> ; [315]
ERROR 486,<FREPORT HEADING or REPORT FOOTING line number must be from HEADING to PAGE-LIMIT inclusive.> ; [315]
ERROR 487,<FPAGE FOOTING line number must be from FOOTING to PAGE-LIMIT inclusive.> ; [315]
>
ERROR 488,<FRecord must be in a SORT FILE.> ; [257]
IFN RPW,<
ERROR 489,<FHEADING must be .le. to FIRST DETAIL.> ;[215]
ERROR 490,<FFIRST DETAIL must be .le. to LAST DETAIL.> ;[215]
ERROR 491,<FLAST DETAIL must be .le. to FOOTING.> ;[215]
>
ERROR 492,<FCOPY not allowed within a library.> ; [213]
ERROR 493,<FNot allowed in LINKAGE SECTION.>
ERROR 494,<FSubscript may not be in LINKAGE SECTION.>
ERROR 495,<FSubscripted subscript not allowed.>
ERROR 496,<WLeft-most truncation.>
IFN RPW,<
ERROR 497,<FThere must be a LINE clause with or before the FIRST COLUMN clause in a report group.>
>
ERROR 498,<WMost significant digits truncated.>
ERROR 499,<WLeast significant digits truncated.>
;WARNING:
; MESSAGES BETWEEN 500 AND 550 HAVE ADDED DATA
; (SEE COBOLF AND USE OF FRSTHI IN SRTERA (IN SRTTAB)
; (TO FIND OUT WHAT IS GOING ON)
ERROR 500,<ALeft-most truncation on>
ERROR 501,<ARight-most truncation on>
ERROR 502,<AMost significant digits truncated on>
ERROR 503,<ALeast significant digits truncated on>
ERROR 504,<AZeroes put into>
ERROR 505,<FConflicts with a USE procedure in SECTION>
ERROR 506,<FClass conflicts with class of literal specified as
VALUE for condition name>
IFN ANS74,<
ERROR 507,<W> ;syntax exceeds requested level.
>
ERROR 551,<FUSAGE must be INDEX.>
ERROR 552,<FClass must be alphanumeric.>
ERROR 553,<FWrong size for this item.>
ERROR 554,<FUsage must be DISPLAY.>
ERROR 555,<FClass must be numeric.>
ERROR 556,<FCan not have any decimal places.>
ERROR 557,<FCan not be in the LINKAGE SECTION.>
ERROR 558,<FCan not be in the FILE SECTION.>
ERROR 559,<FCan not have a JUSTIFIED clause.>
ERROR 560,<FCan not be edited.>
ERROR 561,<FCan not be subscripted.>
ERROR 562,<FBLANK WHEN ZERO not allowed.>
ERROR 563,<FMust not be signed.>
ERROR 564,<FMay not be used as a FILE STATUS item.>
ERROR 565,<FIllegal CANCEL of internal ENTRY.>
ERROR 566,<FEBCDIC files may not have non-standard LABELS.>
ERROR 567,<WCan not follow a level 77 item - assuming level 01.>
ERROR 568,<WMaximum compare length of 2047 characters is exceeded.>
ERROR 570,<FNeither a non-numeric literal nor a long numeric literal nor a figurative constant may be used to identify a record to be retained.>
ERROR 571,<FA COMP value must be used when identifying a record of a SEQUENTIAL or RANDOM file to be RETAINed.>
ERROR 572,<FA data name or literal used to identify a record of an INDEXED file to be RETAINed must match the SYMBOLIC KEY of the file in usage and size.>
ERROR 573,<FOnly sixteen files may be opened by a single OPEN statement.>
ERROR 574,<FFiles being opened for simultaneous update must be opened for INPUT-OUTPUT (I-O).>
ERROR 575,<WThe presence of a FOR clause alone does not open a file for simultaneous update; an OTHERS clause is required.>
; ERROR 576,<FRelative indexing is not allowed on dynamicly subscripted STRING/UNSTRING items.>
ERROR 577,<FReceiving item may not be edited or justified.>
ERROR 578,<FInvalid RECORDING MODE.>
ERROR 579,<FBoth WRITE ADVANCING and WRITE POSITIONING clauses are used on this file.>
ERROR 580,<FIdentifier or numeric literal expected.>
ERROR 581,<FOnly AFTER POSITIONING is allowed.>
ERROR 582,<FPositioning item must be described by PIC X.>
ERROR 583,<FMust be an integer in the range 0 - 3.>
ERROR 584,<FAll records in a file whose recording mode is F must be the same size.>
ERROR 585,<FOnly densities of 800 or 1600 BPI are allowed with STANDARD ASCII.>
ERROR 586,<WThis report group will cause blank lines to be printed since it contains a LINE clause but no COLUMN clauses.>
ERROR 587,<WMaximum ALTERNATE AREAS exceeded; set to maximum value of 62.>
IFN DBMS4,<
ERROR 588,<FVariable in this context must be defined in SUB-SCHEMA.>
>
; ERROR 589,<WDECSYSTEM-20 assumed.>
ERROR 590,<WMaximum of 1023 characters will be accepted.> ;[447]
ERROR 591,<WRounding ignored.> ;[456]
ERROR 592,<FWITH SEQUENCE CHECK expected.>
ERROR 593,<FOCCURS maximum of 32,767 exceeded.>
ERROR 594,<FTransaction-name expected.>
IFN ANS68,<
ERROR 595,<FACTUAL KEY required only for RANDOM files.>
>
IFN ANS74,<
ERROR 595,<FRELATIVE KEY required only for RELATIVE files.>
>
ERROR 596,<FBYTE and BINARY mode not both allowed.>
ERROR 597,<FHas a DEPENDING variable not declared in an ENTRY or PD USING clause.>
ERROR 598,<FLINKAGE subscripts must be usage COMP with fewer than 11 digits, and may not have an additive.>
IFN CSTATS,<
ERROR 599,<FWITH METER--ING must be specified in ENVIRONMENT DIVISION.>
ERROR 600,<FMust be less than 2500.>
>;END IFN CSTATS
ERROR 601,<WSequenced (/S) source file assumed.>
ERROR 602,<FMaximum of 18 decimal places exceeded.>
; ERROR 603,<FWITH EMI or EGI expected.>
ERROR 604,<FIllegal for this dataname to have a scaling factor.>
ERROR 605,<F'==' Expected.> ;[557]
ERROR 606,<WDevice missing -- TTY assumed.>
ERROR 607,<FLibrary file not found.> ;[557]
ERROR 608,<FCorresponding END DECLARATIVES not seen.> ;[552]
ERROR 609,<WRERUN count maximum of 65535 assumed.> ;[553]
ERROR 610,<FKey not contained in sort-file.> ;[554]
ERROR 611,<WDISPLAY-6, DISPLAY-7 or DISPLAY-9 expected -- DISPLAY-6 assumed.>
ERROR 612,<FThis item may not have a DEPENDING variable.>
ERROR 613,<FSort key must not contain an OCCURS clause.> ;[623]
ERROR 614,<FRecord size must match RECORD CONTAINS clause in FD of file whose RECORDING MODE is F.> ;[624]
ERROR 615,<FIdentifier or non-numeric literal expected.>
ERROR 616,<FIdentifier, non-numeric literal, or SIZE expected.>
ERROR 617,<FALTERNATE RECORD KEY not supported.>
ERROR 618,<F.> ;unused diag slot
ERROR 619,<FMust be a key or subordinate item with the same starting position.>
ERROR 620,<WIncorrect and ambiguous syntax.>
ERROR 621,<WPeriod ignored.>
ERROR 622,<WRECORD CONTAINS clause does not match max. record size, RECORD CONTAINS clause ignored.> ;[706]
ERROR 623,<FBLOCK CONTAINS character count too small, file is unblocked.>
ERROR 624,<FALTERNATE KEY may only be specified for INDEXED files.>
ERROR 625,<FSimultaneous update not supported for RMS files.>
ERROR 626,<FKEY IS allowed only when file is INDEXED.>
ERROR 627,<FKey must be DISPLAY mode.>
ERROR 628,<FKey size must be less than 256 characters.>
ERROR 629,<FCALL/ENTER arg expected.> ;[1002]
ERROR 630,<FIllegal CALL/ENTER arg.> ;[1002]
ERROR 631,<FOPEN EXTEND may only be specified for sequential files.>
ERROR 632,<FIF or SEARCH not allowed in WHEN clause of SEARCH> ;[1005]
ERROR 633,<FEnding == not found.> ;[1013]
ERROR 634,<FMust be an integer in the range 0 - 255.>
ERROR 635,<FThis data item must be described as an integer.>
ERROR 636,<FMay only appear in a USE BEFORE REPORTING procedure.>
ERROR 637,<FSUPPRESS not allowed for DETAIL lines - use GENERATE <rdname>.>
ERROR 638,<FZERO is the only figurative constant allowed.>
ERROR 639,<FIdentifier must be one-word computational or index> ;[1431] [1046]
ERROR 640,<FREDEFINES not allowed at 01 level in COMMUNICATION SECTION.>
ERROR 641,<WDISPLAY-7 assumed - it is the only usage allowed here.>
ERROR 642,<WSize of user-defined CD entry is not equal to the default size.>
IFN ANS74,<
ERROR 643,<FPositive integer expected.>
>
IFN ANS68,<
ERROR 643,<FNO or integer expected.>
>
ERROR 644,<FMay not reference a report in a USE BEFORE REPORTING
procedure which uses the same file as the USE report group.>
ERROR 645,<FData-name illegal at this point, statement or paragraph name expected.>
IFN ANS74,<
ERROR 646,<FOnly the last part of a record can have a variable number of occurances.> ;[1071]
>
IFN ANS68,<
ERROR 646,<WUnexpected results may occur when the variable part is not the last part of the record.> ;[1071]
>
ERROR 647,<FMissing 9 in PICTURE clause after S.>
ERROR 648,<FReserved word BY allowed only once in UNSTRING> ;[1116]
ERROR 649,<WLibrary module name too long - truncated to 8 characters.>
ERROR 650,<WLibrary file-name.ext too long - truncated to 9 characters.>
ERROR 651,<WNo room for significant digit before first comma> ;[1312]
ERROR 652,<WMEMORY SIZE too large, maximum assumed> ;[133]
ERROR 653,<FOperand too large to use in literal compare> ;[1353]
ERROR 654,<FUsage must be DISPLAY to write from an ASCII record> ;[1424][1537]
ERROR 655,<ADEC extension - HIGH-VALUES is highest collating sequence value, not the highest numeric value> ;[1500][1547]
ERROR 656,<ADEC extension - Highest numerical value used> ;[1500][1547]
ERROR 657,<ADEC extension - ZERO is only FIGURATIVE CONSTANT allowed for numeric fields by ANSI Standard> ;[1500][1547]
ERROR 660,<WRecord size is less than maximum computed size.> ;[1502]
;ANS-74 ERRORS START AT 700
IFN ANS74,<
ERROR 700,<FContinuation of comment-entry by '-' is not permitted.>
ERROR 701,<FBLANK WHEN ZERO and '*' not allowed together.>
ERROR 702,<FNumeric literal must be unsigned integer.>
ERROR 703,<FERROR or EXCEPTION expected.>
ERROR 704,<FSEQUENTIAL, RANDOM or DYNAMIC expected.>
ERROR 705,<FData-name or integer expected.>
ERROR 706,<FLINES expected.>
ERROR 707,<FFOOTING expected.>
ERROR 708,<FTOP or BOTTOM expected.>
ERROR 709,<FIllegal alphabet-name.>
ERROR 710,<FItem must be signed numeric display.>
ERROR 711,<FSEQUENCE expected.>
ERROR 712,<FTHRU or ALSO requires a one character nonnumeric literal.>
ERROR 713,<FAlphabet-name expected.>
ERROR 714,<FKEY IS not allowed when READ file NEXT is specified.>
ERROR 715,<FCOBOL-74 syntax is DELETE file-name INVALID KEY.>
ERROR 716,<FNon-standard labels are illegal in COBOL-74.>
; ERROR 717,<WDEBUG module is not implemented.>
ERROR 718,<FAlphabet-name is not defined.>
ERROR 719,<WDuplicate character(s) in this collating sequence.>
ERROR 720,<FValue must not exceed number of characters in the character set.>
ERROR 721,<WAll items which are immediately subordinate to a group item must have the same level-number.>
; ERROR 722,<ADEC extension to ANSI-74 standard.> ;[1547]
ERROR 723,<WShould be unsigned integer.>
ERROR 724,<FOnly one BEFORE or AFTER clause allowed per INSPECT argument.>
ERROR 725,<FItem must have the same size as the item being replaced.>
ERROR 726,<FThis item must be smaller than 4096 characters.>
ERROR 727,<FRELATIVE KEY must be specified for this file.>
ERROR 728,<FDEBUGGING expected.>
ERROR 729,<FDELETE not allowed for SEQUENTIAL files.>
ERROR 730,<FReserved word in COBOL-74: may not be used as a paragraph name.>
ERROR 731,<FDEBUG-ITEM is a reserved word in COBOL-74.>
ERROR 732,<FNot implemented on TOPS10.>
ERROR 733,<WBLOCK CONTAINS 1 RECORD assumed.>
ERROR 734,<W"RESERVE 2 AREAS" assumed.>
ERROR 735,<FINVALID KEY clause must not be specified for SEQUENTIAL access files.>
ERROR 736,<FALL, cd-name, file-name, identifier, or procedure-name expected.>
ERROR 737,<FIdentifier or PROCEDURES expected.>
ERROR 738,<FMay not RETAIN or FREE records in more than one file that has a non-COMP key.> ;DMN design flaw restriction
ERROR 739,<FWhen the KEY clause is used for relative files, this item must be the RELATIVE KEY.>
ERROR 740,<FKEY clause not allowed when file access mode is SEQUENTIAL.>
ERROR 741,<FThis item must be defined in a record of the file.>
ERROR 742,<WRecord size not the same as SD file as required by 74 standard.>
ERROR 743,<FORGANIZATION must be RELATIVE if RELATIVE KEY is specified.>
ERROR 744,<FORGANIZATION must be INDEXED if RECORD KEY is specified.>
ERROR 745,<FNo more than 255 keys allowed> ;[1345]
ERROR 746,<FCan't store key conversion address - compiler failure> ;[1346]
ERROR 747,<FKey name or EVERY expected after FREE> ;[1450]
ERROR 750,<FKey name can't be subscripted> ;[1460]
ERROR 777,<WSyntax has been changed to ORGANIZATION IS RMS INDEXED>
>
;COBOL-68 TO COBOL-74 CONVERSION WARNINGS
IFN FT68274,<
ERROR 700,<WContinuation of comment-entry by '-' is not permitted in COBOL-74.>
ERROR 701,<WBLANK WHEN ZERO and '*' not allowed together in COBOL-74.>
ERROR 702,<WNumeric literal must be unsigned integer in COBOL-74.> ;[1350]
ERROR 715,<WCOBOL-74 syntax is DELETE file-name INVALID KEY.>
ERROR 716,<WNon-standard labels are illegal in COBOL-74.>
ERROR 721,<WAll items which are immediately subordinate to a group item must have the same level-number in COBOL-74.>
ERROR 723,<WShould be unsigned integer in COBOL-74.>
ERROR 742,<WRecord size not the same as SD file as required by 74 standard.>
ERROR 765,<WComparing different size items may be different in COBOL-74.> ;[1416]
ERROR 767,<WSET TALLY TO 0 generated here but not required.> ;[1415]
ERROR 768,<WThe VALUE clause is initialized independent of the JUSTIFIED clause in COBOL-74.> ;[1340]
ERROR 769,<WNot in abbreviated combined relation conditions may generate different code> ;[1340]
ERROR 770,<WReplace by ACCEPT cd-name MESSAGE COUNT.>
ERROR 771,<WContents of DELIMITER may be different in COBOL-74.>
ERROR 772,<WImproper character for CURRENCY SIGN in COBOL-74.>
ERROR 773,<WTALLY generated here but not required.>
ERROR 774,<WReplace LOW-VALUE hack with appropriate COBOL-74 syntax.>
ERROR 775,<WReplace TODAY with ACCEPT FROM DAY, DATE, or TIME as appropriate.>
ERROR 776,<WSWITCHes are defined differently in COBOL-74.>
ERROR 777,<WThis is a new reserved word in COBOL-74.>
>
;MISCELLANEOUS CONSTANTS
TBNUM:: POINT 10,TB,35 ;DIAG NUMBER FIELD IN TB
TBFAZE: POINT 3,TB,24 ;PHASE NUMBER FIELD IN TB
;TABLES OF POINTERS TO MESSAGES
DEFINE TABLE (A) <
IFDEF ERA'A <POINT 7,ERA'A,6>
IFNDEF ERA'A <0>
>
Radix 10
DEFINE TABLEA (A,B),<
XLIST
.XCREF
I==A
REPEAT B-A+1,<TABLE \I
I==I+1>
.CREF
LIST>
TABLE1: TABLEA 0,LASTLO;
TABLE2: TABLEA FRSTB2,RLSTHI;
TABLE3: TABLEA LASTHI+1,LSTDIG;
RADIX 8
END