List of Messages 0574 - 1231 [ 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 0574 - 1231
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 within GLOBAL declarative
0584 In-line 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 data record is larger than minimum specified in RECORD
CONTAINS
* 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 data record is smaller than maximum specified in RECORD
CONTAINS
* 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 non-numeric 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 when compiling with QUOTE directive
0610 Quote found when compiling with APOST directive
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 may not be in LOCAL-STORAGE
0647 CURSOR data item may not 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
0652 Directive setting incompatible with selected flagging dialect
* The directive setting will cause behavior different from
that of the dialect for which flagging was selected. It
is processed as requested.
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 ALPHANUMERIC item
* The numeric test cannot be used with an item whose data
description describes the item as alphabetic.
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 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 within 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 may not be the same under OSVS/
VSC2
0678 Too many CONTROLS specified for report
0679 QUOTE character must be double within 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 non-zero
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
1001 Character other than *, D, /, -, or $ found in column 7. Blank
assumed
* You may have mistyped one of the characters allowed in
column 7. Your COBOL system cannot interpret the
character in column 7, and has treated it as a space.
1002 Continuation character invalid at this point. Blank assumed
* You have placed a hyphen in column 7, though your COBOL
system is not expecting the syntax to be continued at
this point. The continuation character is ignored.
1003 First character of a continued literal not a quote. Quote
assumed
* You have included a continuation character in column 7,
but you have forgotten to start the continuation of the
literal with a quotation mark. Your COBOL system assumes
that the quotation mark is included.
1004 Continuation character expected. End of literal assumed
* The literal in the previous line of source code is not
delimited by quotation marks, so your COBOL system is
expecting a continuation character in column 7, and a
continuation of the literal. Your COBOL system has
assumed that you meant to end the literal on the previous
line.
1005 Name ends in hyphen. Processed as written
* You have used a hyphen as the last character in a
user-defined name, which is against the rules of COBOL
syntax. Your COBOL system has accepted this as a valid
name, however, and has not changed the name in any way.
1006 COBOL word contains more than 30 characters. Word truncated
* The name that you have specified is longer than 30
characters. Your COBOL system treats this as a name
consisting of the first 30 characters of your original
name.
1007 VALUE literal too large. Literal truncated
* The literal you have specified in the VALUE clause is too
long to fit into the data item. Your COBOL system
inserts characters from the literal into the data item,
until the data item is full.
1008 DBCS literal must contain an even number of characters. Literal
truncated
* All Double Byte Character Set (DBCS) symbols are two
bytes (two characters) long. You have specified a
literal that consists of an odd number of characters.
Your COBOL system ignores the last, single character of
the literal.
1009 Closing delimiter for DBCS literal not found. Delimiter assumed
* You have not included the quotation mark to show the end
of the Double Byte Character Set (DBCS) literal. Your
COBOL system has assumed that you intended to end the
literal at this point.
1010 Nonnumeric literal has length of zero. One SPACE assumed
* The alphabetic or alphanumeric literal you have defined
in your source code is empty, that is, you have a pair of
quotation marks with no character between them. Your
COBOL system has assumed that the literal contains one
space character.
1011 DBCS literal has length of zero. Length of one DBCS character
assumed
* The Double Byte Character Set (DBCS) literal you have
defined in your source code is empty, that is, you have a
pair of quotation marks with no DBCS character between
them. Your COBOL system has assumed that the literal is
two characters long, and that it has a value of spaces.
1012 DIVISION missing or misspelled. DIVISION assumed
* You have omitted the word DIVISION from a division
header, or you have spelled it incorrectly. Your COBOL
system has assumed that DIVISION is what was meant.
1013 SECTION missing or misspelled. SECTION assumed
* You have omitted the word SECTION from a section header,
or you have spelled it incorrectly. Your COBOL system
has assumed that SECTION is what was meant.
1014 Period missing. Period assumed
* You have omitted a period in a place where one is
expected by the rules of COBOL syntax. Your COBOL system
has assumed the period is present.
1015 OCCURS integer-1 exceeds OCCURS integer-2. 0 is assumed for
integer-1
* You have included the OCCURS integer-1 TO integer-2
DEPENDING clause in your source code, but the value given
for integer-1 is greater than that for integer-2, which
is against the rules of COBOL syntax. Your COBOL system
has effectively changed the value of integer-1 to 0.
1016 Expected SEPARATE before CHARACTER in SIGN clause. SEPARATE
assumed
* You have incorrectly coded the SIGN clause because you
have included the word CHARACTER, which is not required,
but you have omitted the required word SEPARATE. Your
COBOL system has assumed that you intended the clause to
be SIGN IS LEADING (or TRAILING) SEPARATE CHARACTER.
1017 REDEFINES ignored for 01 level item in FILE or COMMUNICATION
SECTION
* You have tried to REDEFINE a data item in the File or
Communication Section, but the data item is an 01 level
item. Level 01 items for the same FD or CD automatically
redefine one another anyway.
1018 VALUE clause not allowed here. Clause processed as comment
* You have tried to assign a value to a data item defined
in the File Section or the Linkage Section. The VALUE
clause is ignored.
1019 Unsigned numeric literal expected. Sign ignored
* You have specified a sign where one is not expected, for
example, you have used the AFTER ADVANCING +1 or BEFORE
ADVANCING -2 clause to the WRITE statement. Your COBOL
system ignores the sign, and treats the digits as a
positive value.
1020 Unsigned numeric field. Sign in VALUE clause ignored
* You have defined a numeric data item, that is, PIC 9, and
you have tried to assign a signed number as its value.
Your COBOL system ignores the sign you have specified.
Where you are attempting to move a number with a negative
sign into a numeric field, the result will not be as
expected.
1021 Slack bytes added in conversion of COMP-6 to COMP
* You are using a program converted from RM/COBOL that
contains
a COMP-6 numeric data item which has been converted to a
COMP numeric data item. As a result of this conversion,
less data space may have been allocated to the numeric
data item and, therefore, your COBOL system adds leading
binary zeros to pad the space, if required.
1022 Table item not subscripted or indexed. First occurrence assumed
1023 WORKING-STORAGE SECTION expected. Start of WORKING-STORAGE
assumed
* Your program begins with an 01 level entry. It is
assumed that this is the first item of Working Storage.
1024 VALUE clause literal does not conform to PICTURE. Changed to
blanks
* A numeric value has been specified for a nonnumeric data
item. The data item will be filled with spaces.
1025 MOVE edited field to edited field - treated as alphanumeric move
* A move of one edited field to another is treated as an
alphanumeric move.
1026 Source literal is non-numeric - substituting zero
* A MOVE statement is trying to MOVE a nonnumeric literal
to a numeric data item. This cannot be done. To avoid
undefined results, ZERO will be moved to the target data
item.
1027 Literal is numeric - treated as non-numeric
* A numeric literal is being used in relation to a
nonnumeric data item; for example, as the VALUE of an 88
level entry attached to a nonnumeric data item. The
literal will be converted to an alphanumeric literal.
1028 Statement should not reference an alphabetic data item
* A statement would cause invalid data to be contained in
an alphabetic data item. Your COBOL system will execute
the statement as written.
1029 A non-integer is being moved to an alphanumeric data item
* A MOVE statement is trying to move a noninteger item to
an alphanumeric data item. The decimal point will be
ignored and all the digits moved as if they constituted
an integer.
1030 Cannot SORT or MERGE USING or GIVING two files with SAME AREA
* Two files specified in a SORT or MERGE statement are
defined as sharing the same area. The files will be
allocated different areas.
1031 SORT file appears in more than one SAME SORT (-MERGE) AREA
clause
* A SORT file has been referenced in more than one SAME
SORT (-MERGE) AREA clause. The files will be allocated
different areas.
1032 File-names illegally specified in same SAME RECORD AREA clause
* Two files in a SORT or MERGE statement are defined as
sharing the same record area. The files will be
allocated different record areas.
1033 File-names illegally specified in same SAME SORT (-MERGE) AREA
clause
* Two files in a SORT or MERGE statement are defined as
sharing the same sort (-merge) area. The files will be
allocated different sort-merge areas.
1034 Source item is ALPHABETIC or ALPHANUMERIC-EDITED - treated as
alphanumeric
* You have moved either an alphabetic, alphabetic
justified, edited alphabetic or edited alphanumeric field
to a numeric display field. The source field has been
treated as though it were a numeric field.
1035 Key is not wholly contained within minimum record length
* The specified key is greater in length than the minimum
size of the record.
1036 Entry name illegal
1037 Data-name must be specified for an EXTERNAL record - EXTERNAL
ignored
1038 RECORD key or ALTERNATE key has same starting position as
another key
* The specified key has the same starting position in the
file's record as a previously defined key.
1039 Error in structure information. No structure diagram created
* You are trying to perform structure animation of a
program in which a PERFORM THRU statement performs
sections in the Declaratives.
* Normal animation can be performed, but not structure
animation.
1040 ALL not allowed here - ALL ignored
1041 Data item has zero size, or group not yet completed. Value of 0
assumed
1042 A numeric item is being moved to an ALPHABETIC data item
1043 PERFORM may be recursive
1044 Load failure on SLOAD - STRUCT ignored
1045 Capacity of POINTER may be exceeded
1046 Host variable name may cause problems if not unique, even if
qualified
1047 Phrase ignored - unsuccessful chain will cause program
termination
1048 DBCS literal includes invalid data
1049 KEY clause not allowed with sequential READ - clause ignored
1101 No COBOL statement between periods
* You have placed one period immediately following another
period. This is not against the rules of COBOL syntax,
but it may indicate a fault in your program, for example,
you may have wanted to include a line of source code
here.
1102 Blank continuation source line. Line ignored
* You have placed a hyphen in column 7, but the rest of the
line contains no other code. The next line should also
contain a hyphen in column 7, to continue correctly.
1103 Sequence number out of order or missing
1104 77 level item in FILE SECTION. Processed as 01 level
* You have assigned a level of 77 to a data item in the
File Section, which is against the rules of COBOL syntax.
Your COBOL system assumes that you had intended to code
this as an 01 level item, and processes it as such.
1105 No CORRESPONDING items were found. Statement has no effect
* Your COBOL system found no matching data items for the
CORRESPONDING clause, so no intermediate code is produced
for this statement.
1106 ZERO value for BY operand. Statement processed as written
* You have used the BY operand to the verb PERFORM, but the
value you have specified for the increment is zero. Your
COBOL system will produce code to execute this statement,
but the value is never incremented.
1107 Statement exceeds COMP subset
* The COMP subset code you have written could be rewritten
to execute more efficiently. Refer to your COBOL System
Reference for information on writing efficient code.
1108 Signed numeric compared with group. Processed as alphanumeric
compare
* You have written your code so that a signed numeric field
is compared with a group item. Your COBOL system has
treated the signed numeric field as an alphanumeric field
for the comparison. There are no problems with comparing
a signed numeric field with an elementary item.
1109 WITH DEBUGGING MODE not specified. Section ignored
* Your program includes the USE FOR DEBUGGING statement in
a section in the Declaratives of your Procedure Division,
but you have not included the WITH DEBUGGING MODE clause
in the Source-Computer paragraph. Your COBOL system
ignores all code in this section.
1110 First literal is greater than second. Processed as written
* In the ALPHABET clause the first literal that is
specified has a value greater than that of the second,
for example, P THRU D. Your COBOL system accepts this as
written, that is, the characters are processed in reverse
order.
1111 Boundary violation. Processed as written
* You have attempted to access an item beyond the end of a
table. Your COBOL system will generate code to access
the appropriate line of code beyond the end of the table,
but the result of this is undefined.
1112 Compatibility directive forcing non standard behavior
* When the RM directive is set and an alphanumeric data
item is MOVEd to a numeric data item which is defined as
larger, your COBOL system adds space characters to the
front of the MOVEd data item. Under the RM/COBOL system,
however, leading zeros are added to the front of the
alphanumeric data item when it is MOVEd to a numeric data
item which is defined as larger.
1113 Imperative statement missing - CONTINUE assumed
* Your program contains a conditional statement which has
not been followed by an imperative statement. Your COBOL
system will execute the code, but the result of this may
be undefined.
1114 Clause treated as documentary
* You have assigned more than one external file reference
to a SELECT ... ASSIGN clause. Your COBOL system will
accept the first external file reference, but will treat
all remaining external file references in that clause as
documentary.
1115 SAME AREA treated as SAME RECORD AREA
* You are using a program converted from DG Interactive
COBOL to this COBOL that contains a SAME AREA clause.
Your COBOL system has assumed that the SAME RECORD AREA
clause is what was meant.
1116 ACCEPT qualifier used with display-only field - qualifier
ignored
* The qualifier used with a DISPLAY only field, or in a
DISPLAY statement, can be used only with an ACCEPT. It is
ignored.
1117 Zero suppression follows floating insertion - treated as
floating insertion
* As an example, PIC ++Z.ZZ is treated as PIC +++.++.
1118 Index-name belongs to different table
* The index used to subscript a table item is not one used
in the INDEXED BY clause for this table. The results
will be unpredictable.
1119 Record < minimum size given in FD statement
* The definition of a record following an FD clause is
smaller than the minimum size specified in the RECORD
CONTAINS phrase of that FD clause.
1120 Record > maximum size given in FD statement
* The definition of a record following an FD clause is
larger than the maximum size specified in the RECORD
CONTAINS phrase of that FD clause.
1121 VALUE in FILE, LINKAGE, or LOCAL-STORAGE SECTION -processed as
comment
* A data item in the File or Linkage Section cannot be
given a value. The VALUE clause specified will be
ignored.
1122 Period must be followed by a space
* In all cases a period must be followed by a space.
1123 Neither NAMED nor CHANGED specified. Will be treated as
formatted DISPLAY.
* An EXHIBIT statement has been used without the NAMED or
CHANGED phrase. The resulting display will be formatted
by separating each item with a space.
1124 CALL parameter is literal (or LENGTH OF) BY CONTENT assumed
* You are using a program converted from RM/COBOL to this
COBOL that contains a CALL ... USING literal statement.
Your COBOL system has assumed that CALL
1125 Punctuation character not followed by a space. Assume space
* A punctuation character should be followed by a space.
1126 Punctuation character not preceded by a space. Assume space
* A punctuation character should be preceded by a space.
1127 Double-Byte character(s) may be corrupted by use of this move
* This MOVE statement may cause a double-byte data item to
be corrupted by changing one byte of a double-byte pair.
1128 No STOP RUN, GOBACK, or EXIT PROGRAM statements encountered in
source
* The source has no STOP RUN, GOBACK or EXIT PROGRAM
statement. The COBOL system will automatically insert an
EXIT statement followed by a STOP RUN statement following
the last line in the program. However, this may not have
the effect you desire.
1129 Statement cannot be reached
* The program flow will prevent the statement flagged from
being executed.
1130 Prefix of filename treated as documentary
1131 Statement generated no executable code
* This error may be produced when, for example, an
INITIALIZE statement does not cause any code to be
created. It is an indication that the statement may be
removed from the program. If the error is ignored the
effect is as if the statement were removed.
1132 Unable to validate contents of DBCS literals
* Your COBOL system is unable to check that the contents of
a DBCS literal are valid. If the contents are invalid
the results will be unpredictable.
1133 SQL warning/ recoverable error
* The SQL processor generated a warning. Check your SQL
documentation for further details.
1134 Entry name has been converted following OS/VS COBOL and VS COBOL
II rules
* The name you specified for an ENTRY statement would be
altered if your source program were processed by an IBM
OS/VS COBOL or VS COBOL II compiler.
1135 No OPEN statement was found for file
1136 No CLOSE statement was found for file
1137 `KEPT' omitted for file with multiple record locking
* The KEPT phrase has not been included in your multiple
record locked file.
1138 Name truncated to 8 characters
1139 SQL host variable does not have suitable data type
1140 SQL host variable not enclosed with BEGIN DECLARE and END
DECLARE
1141 Name longer than 8 characters
1142 Name includes characters that would be changed by OS/VS COBOL
and VS COBOL II
1143 Name includes characters that would be illegal for OS/VS COBOL
and VS COBOL II
1144 String will be null terminated when returned by SQL
1145 DUPLICATES phrase with keys generates slower sort; remove if
possible
1146 procedure-name lies in more than one PERFORM THRU range
1147 End precedes start in PERFORM procedure-name THRU procedure-name
* The procedure-name after the THRU comes earlier in the
source program than the one before the THRU.
1148 Segmentation specified in nested program - ignored
1149 Operand data-name ambiguous in corresponding target
* In a MOVE, ADD or SUBTRACT CORRESPONDING, the sending
group contains an item, data-name, which is ambiguous in
the receiving group.
* Although data-name occurs in both the sending and
receiving groups, no relevant MOVE, ADD or SUBTRACT is
generated: this is in accordance with ANSI defined
behavior.
1150 Redefinition of internal floating-point item. May not be
portable
1151 Forwards overlapping move may produce unpredictable results
1152 Comparison involving floating point data may not be portable
1153 Some mainframe values for this data type cannot be handled on PC
1154 PC allows values for this data type that cannot be handled on
mainframes
1155 Both PANVALET and LIBRARIAN specified - not mainframe compatible
1156 BLOCK or LABEL clause in SD not allowed. Ignored
1157 JUSTIFIED specified on edited field
1201 Zero suppression PICTURE string overrides the BLANK WHEN ZERO
clause
1202 Original item is larger than redefinition
1203 LABEL clause processed as comment
1204 BLOCK CONTAINS clause processed as comment
1205 Previous paragraph or SECTION contains no statements
1206 PROCEDURE DIVISION does not start with a SECTION
1207 Original item is smaller than redefinition
1208 USE clause omitted
1209 COMP-5 is machine specific format. (Future occurrences not
indicated)
1210 COMP processed as DISPLAY (future occurrences not indicated)
1211 COMP-6 processed as COMP (future occurrences not indicated)
1212 COMP-1 processed as PIC S9(4) COMP (future occurrences not
indicated)
1213 COMP-0 field exceeds PIC S9(5), converted to USAGE DISPLAY
1214 COMP-0 processed as PIC S9(4) COMP (future occurrences not
indicated)
1215 UNIT phrase processed as comment
1216 Literal exceeds 160 characters
1217 Procedure name same as data name
1218 RERUN clause processed as comment
1219 No REPLACE currently in effect
1220 COMP-4 processed as PIC S9(9) COMP (future occurrences not
indicated)
1221 COMP-4 field exceeds S9(10), converted to USAGE DISPLAY
1222 COMP-3 unsigned, converted to signed COMP-3
1223 BLANK WHEN ZERO clause overrides the zero suppression PICTURE
string
1224 MEMORY SIZE clause processed as comment
* The MEMORY SIZE clause is treated as documentary.
1225 MULTIPLE FILE TAPE clause processed as comment
* The MULTIPLE FILE TAPE clause is treated as documentary.
1226 COMMON can only be used in nested program - processed as comment
* The program defined as COMMON is a main program, not a
nested program.
1227 An implicit scope terminator was generated
1228 Word non-portable; reserved in OS/400
1229 Word non-portable; reserved in VSC2(3)
1230 Word non-portable; reserved in OS/2 COBOL
1231 Syntax is non-conforming SAA
MPE/iX 5.0 Documentation