Source Code Management Topics
Free Source Format
Free source format, or “terminal format” applies different rules for establishing the location of the Area A, the Indicator Area, Area B, and the Identification Area, as specified below.
COBOL-IT source programs that are written in Terminal Format must be compiled with the –free
compiler flag.
Example:
>cobc –free hello.cbl
General Rules:
- Area A may start in column 1, 2, or 3, and extends for 4 characters. Most commonly, Area A begins in column 1.
- The Indicator Area is optional, and can be used to mark a comment line with a “
*
” character. The Indicator Area must start in column 1. Note that both Area A and the Indicator Area may start in Column 1. - Area B starts after the last character in Area A. In the most common case, where Area A begins in column 1 and extends for 4 characters, Area B would start in column 5. Area B extends to the end of the line, or to the beginning of the Identification Area.
- Identification Area holds in-line comments. In a program written in Terminal Format, the beginning of the Identification Area is marked with “
*>
” (without the quotes). Note that when contained within quotation marks, the “*>
” mark is not interpreted as the beginning of the Identification Area. - The Identification Area extends to the end of the line.
Code Sample:
IDENTIFICATION DIVISION.
PROGRAM-ID. HELLO.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
77 WS-DUMMY PIC X.
PROCEDURE DIVISION.
DISPLAY "HELLO WORLD" LINE 10 COL 10.
ACCEPT WS-DUMMY.
STOP RUN.
- Note that COBOL IT’s default behavior is to assume an ANSI format, and the compiler
will flag a terminal format source file with an error such as the following:
C: COBOL CobolIT>cobc hello.cbl
C:/COBOL/CobolIT/hello.cbl:1: Error: Invalid indicator 'f' at column 7
- To correct this error, compile with the
free
compiler flag:C: COBOL CobolIT>cobc free hello.cbl
cob44D4.c
Creatinglibrary hello.lib
and objecthello.exp
Line Continuations
A line continuation condition exists when a clause continues in Area B of the next line (excluding comment lines).
General Rules:
- A continuation line is marked by placing a hyphen “-“ in the indicator area.
- On a continuation line:
- If the continued line ends in a literal without a closing quotation mark, then the first non-blank character of the continuation line must be a quotation mark.
- In all other cases, the first non-blank character of the continuation line is interpreted as following the last non-blank character in the previous line.
Code Sample:
IDENTIFICATION DIVISION.
PROGRAM-ID. LINECONTINUE.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
77 WS-LITERAL PIC X(75) VALUE "THIS IS A LONG LITERAL THAT IS US
- "EFUL IN DEMONSTRATING LINE CONTINUATIONS.".
77 WS-DUMMY PIC X.
PROCEDURE DIVISION.
DISPLAY WS-LITERAL LINE 10 COL 1.
ACCEPT WS-DUMMY.
STOP RUN.
Blank Lines and Comment Lines
A blank line is a line that contains only spaces in Area A and Area B. A comment line is a line that contains an asterisk “*
”in the indicator area. Blank lines and comment lines can appear anywhere in a source file. Blank lines and comment lines are preserved in source listings, but have no effect on the behavior of the compiled code.
The “*>
” notation may be used anywhere in a source line to designate a comment and both single-quote, and double-quote notations may be used in the comment.
Conditional Compilation
$END Statement
The $END
Statement terminates the conditional compile construct.
General Format:
$END
General rules:
The $END
statement must appear on a single line.
$ELSE Statement
The $ELSE
Statement indicates a branch that should be executed if the $IF
condition does not test true
.
General Format:
$ELSE
General rules:
The $ELSE
statement must appear on a single line.
$IF Statement
The $IF
Statement provides the ability to conditionally include or exclude text based on the truth test of the if-condition
. There are two formats:
Format 1:
$IF constant-name-1 [NOT] = literal-1
Format 2:
$IF [X0 - X9] [NOT][=]{ON }
{OFF }
Syntax:
Constant-name-1
is named in the compiler flag–constant
“constant-name-1=value
”.Literal-1
may be a numeric or alphanumeric literal.- The
$IF
/$ELSE
/$END
/$SET
directive must not be terminated by a period.
General rules:
- If the condition evaluates "
true
", the source lines following the $IF statement are processed. If the condition evaluates "false
", COBOL source lines are ignored until the next conditional compilation line is encountered. $IF
/$ELSE
/$END
conditional compilation directives may be nested to 99 levels.
$SET Statement
The Format 1 $SET
Statement is used to set one of the X0-X5
switches to ON
or OFF
.
Format 1:
$SET [X0-X9]= {ON }
{OFF}
The Format 2 $SET
Statement provides a way to dynamically create a constant with a value, which may be used programmatically like a level-78 constant.
Format 2:
$SET [constant-1] = [constant-value ]
Code Sample:
. . .
$SET MYCONSTANT = 50
. . .
01 MY-BUFFER PIC X(MYCONSTANT).
78 NUMBER-STATES VALUE MYCONSTANT.
$SET
Statement provices a way to set compiler configuration flag within the COBOL source file.
Format 3:
$SET compiler-configuration-flag = [value]
General rules:
The $SET
statement must appear on a single line.
Format 1 Code Sample:
IDENTIFICATION DIVISION.
PROGRAM-ID. CONDCOMPILE.
* COMPILE WITH
* >COBC -CONSTANT "C1="USA"" -CONSTANT "C2=100" CONDCOMPILE.CBL
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
77 WS-DUMMY PIC X.
PROCEDURE DIVISION.
MAIN.
* FORMAT 1
* $IF CONSTANT-1 [NOT] = LITERAL-1
$IF C1 = "USA"
DISPLAY "C1 = USA" LINE 6 COL 10.
$ELSE
DISPLAY "C1 NOT = USA" LINE 6 COL 10.
$END
$IF C2 = 100
DISPLAY "C2 = 100" LINE 8 COL 10.
$ELSE
DISPLAY "C2 NOT = 100" LINE 8 COL 10.
$END
* FORMAT 2
* $SET X0=ON
$SET X0=ON
$IF X0=ON
DISPLAY "X0 SET!" LINE 10 COL 10.
$ELSE
DISPLAY "X0 NOT SET!" LINE 10 COL 10.
$END
ACCEPT WS-DUMMY.
STOP RUN.
Format 3 provides a mechanism to supply compiler configuration within the COBOL source file. In the COBOL-IT Compiler & Runtime Reference Manual, see the Compiler Configuration File section for more details.
Use of Figurative Constants
Figurative Constants are reserved words with equivalent values.
The Figurative Constants recognized by COBOL-IT and their equivalent values are listed below:
Figurative Constant | Equivalent Value |
---|---|
HIGH-VALUE, HIGH-VALUES | Hex “FF” |
LOW-VALUE, LOW-VALUES | Hex “00” |
NULL | Hex “00” |
QUOTE, QUOTES | Double-quote character ( “ ) |
SPACE, SPACES | The Space character |
ZERO, ZEROS, ZEROES | The 0 character |
General Rules:
- With the exception of
ZERO
,ZEROS
,ZEROES
, which are considered numeric, all of the figurative constants are considered to be alphanumeric literals. - Figurative constants can be used in any statement that their equivalent value can be used.
COPY Statement
The COPY
statement names a file copy-lib
that is to be copied into the source at the location of the COPY
statement prior to compilation.
General Format:
COPY copy-lib
[ REPLACING { { old-text BY new-text } } ... ]
{ { {LEADING } literal-1 BY {literal-2} } }
{ { {TRAILING} {SPACE } } }
{ { {SPACES } } }.
Syntax:
- The
COPY
statement may appear in Area A or Area B. Old-text
requires that at least one word be specified.Old-text
andnew-text
may be any of the following:- A word or series of text words placed between “
= =
”` delimiters. - A numeric or non numeric literal
- A data name, including qualifiers, subscripts, and reference modification.
- A word or series of text words placed between “
Old-text
may not be any of the following- A space
- The “
= =
” delimiter - The quote character
- The word “
COPY
” designating aCOPY
statement
Literal-1
andliteral-2
are nonnumeric literals.
General Rules:
-
copy-lib
may be entered in quotes, as inCOPY “copy-lib”
or not, as inCOPY copy-lib
. The internal rules applied for locating the copy file and resolving the copyfile name are the same. For details about rules used to locate copy books and resolve copy book names, see Copy Book Handling. -
The
REPLACING
clause indicates text replacements to be made prior to compiling the source. -
When
old-text
is identified incopy-lib,
it is replaced bynew-text
, at the former starting position ofold-text
. -
The
LEADING
/TRAILING
phrase indicates that only theLEADING
orTRAILING
characters identified will be replaced if they match text incopy-lib
. -
The
SPACE
orSPACES
phrase indicates thatold-text
should be removed. -
SPACE
andSPACES
are synonyms. -
A period “
.
” At the end of aCOPY
statement is not required. -
++COPY
and++INCLUDE
are synonyms ofCOPY
. -
COBOL-IT recognizes the following delimiters:
= = old-text = =
= = : old-text : = =
- Note that spaces between
old-text
and the delimiter are ignored.
Compiler flags related to locating copy files and resolving copy file name:
Compiler Flag | Description |
---|---|
-I <path>[,ext1,ext2,.,extn][@<LibName>] |
<command-file> Searches <path> for copy files, including files with extensions of ext1 , ext2 , ... extn , and located in directory named by <LibName> . |
–ext <extension> |
Includes <extension> along with default extensions. |
-fcopy-mark |
Adds mark for begin/end of COPY In listing and preprocessed file.The copy marks are: *++SCOPY [ COPY file is listed here ] *--SCOPY |
-fcurdir-include |
Causes COPY file search to begin in current directory. |
-ffold-copy-lower |
Fold COPY subject to lower case looking for match. |
-ffold-copy-upper |
Fold COPY subject to upper case looking for match. |
Environment variables related to locating copy files:
Environment Variable | Description |
---|---|
COB_COPY_DIR=<path> |
Searches <path> for copy files. |
COBCPY=<path> |
Searches <path> for copy files. |
REPLACE Statement
The REPLACE
Statement allows the user to direct the compiler to replace selected strings or numbers in source text with alternative strings or numbers.
General Format:
Format 1:
The Format 1 REPLACE
statement indicates text replacements to be made prior to compiling the source until another Format 1 REPLACE
statement is encountered, or until the REPLACE OFF
statement is encountered.
REPLACE { { old-text BY new-text } } ... ]
{ { {LEADING } literal-1 BY {literal-2} } }
{ { {TRAILING} {SPACE } } }
{ { {SPACES } } }.
Syntax Rules:
-
old-text
requires that at least one word must be specified. -
old-text
andnew-text
may be any of the following:- A word or series of series of text words placed between “
==
” delimiters. - A numeric or nonnumeric literal.
- A data name, including qualifiers, subscripts, and reference modification.
- A word or series of series of text words placed between “
-
old-text
may not be any of the following:- A space
- The “
= =
” delimiter - The quote character
- The word “
COPY
” designating aCOPY
statement.
-
literal-1
andliteral-2
are nonnumeric literals.
General Rules:
-
The
REPLACE
statement must be terminated by a period. -
The
REPLACE
Statement may appear anywhere in the COBOL source text, in Area A or Area B. -
Text replacement described by a
REPLACE
statement is done prior to compilation, after the processing of theCOPY
statement. -
The
REPLACE
statement specifies conversion of source statements containingold-text
intonew-text
. -
Text replacement uses the following rules:
- The leftmost source text word is
old-text
. Old-text
is matched when an identical word or sequence of words is encountered within the scope of theREPLACE
statement. When matching, multiple spaces match a single space. Lower case and upper case characters match, except in quoted literals.
- The leftmost source text word is
-
When
old-text
is matched with existing source code, it is replaced bynew-text
in the source program, in the same location. -
When you are using the
LEADING
/TRAILING
option, a match betweenold-text
and matched source code can be made with a substring in an element in the source code. -
When
SPACE
, orSPACES
are indicated asnew-text
, matchedold-text
characters are deleted.
Format 2:
The Format 2 REPLACE
statement removes the existing REPLACE
statement directive.
REPLACE OFF.
Format 3:
The Format 3 REPLACE ADD
nests a REPLACE
statement inside an existing REPLACE
statement.
REPLACE ADD.
General Rules continued:
- Support for the
REPLACE ADD
statement requires that thereplace-additive
compiler configuration file variable be set toon
.
The replace additive compiler configuration file variable allows for the use of theREPLACE ADD
verb, which has the effect of nesting aREPLACE
statement inside an existingREPLACE
statement. NestedREPLACE
statements are executed before outerREPLACE
statements in COBOL-IT’s precompile phase. Note that aREPLACE
stack can be cleared with theREPLACE OFF
statement.
Code Sample:
IDENTIFICATION DIVISION.
PROGRAM-ID. REPLACE1.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
REPLACE LEADING ==WS== BY ==W==.
77 WS-DUMMY PIC X.
PROCEDURE DIVISION.
REPLACE "HELLO WORLD" BY "ENJOY COBOL-IT" 10 BY 20.
DISPLAY "HELLO WORLD" LINE 10 COL 10.
REPLACE OFF.
REPLACE ==LINE 10== BY ==LINE 22==
==COL 10== BY ==COL 20==
=="HELLO WORLD"== BY =="GOODBYE FRIEND"==.
DISPLAY "HELLO WORLD" LINE 10 COL 10.
ACCEPT W-DUMMY.
STOP RUN.
Produces the following screen output:
ENJOY COBOL-IT
GOODBYE FRIEND
Special Registers
Tally Register
The TALLY
register is used during TALLYING
operations.
The predefined register TALLY is defined as:
01 TALLY GLOBAL PICTURE S 9(9) USAGE COMP-5 VALUE ZERO.
The configuration file flag tally-register
, when set to NO
, disables the creation of the
predefined register TALLY
, for example:
tally-register:no
Return-Code Register
The RETURN-CODE
register is used by a number internal library routines, and can also be set by the STOP
statement to return a value after the run unit has terminated.
The predefined register RETURN CODE
is defined as:
01 RETURN-CODE EXTERNAL USAGE BINARY-LONG.
Sort-Return Register
The SORT-RETURN
register is set to “0
” following a successful SORT
, and to a non-zero value if the SORT
is unsuccessful.
The predefined register SORT-RETURN
is defined as:
01 SORT-RETURN USAGE BINARY-LONG.
Number-of-Call-Parameters Register
The NUMBER-OF-CALL-PARAMETERS
stores the number of parameters with which the program was CALL
’ed.
The predefined register NUMBER OF CALL PARAMETERS
is defined as:
01 NUMBER-OF-CALL-PARAMETERS USAGE BINARY LONG.