Vous êtes sur la page 1sur 33

COBOL STANDARDS AND CONVENTIONS

1.

COBOL CODING STANDARDS.............................................................................2


1.1
IDENTIFICATION DIVISION...........................................................................2
1.1.1 PROGRAM-ID.................................................................................................2
1.1.2 AUTHOR...........................................................................................................2
1.1.3 INSTALLATION................................................................................................2
1.1.4 DATE-WRITTEN.............................................................................................2
1.1.5 DATE-COMPILED...........................................................................................3
1.1.6 REMARKS........................................................................................................3
1.2 ENVIRONMENT DIVISION...................................................................................4
1.2.1 Configuration Section.....................................................................................4
1.2.2 Input-Output Section.......................................................................................4
1.3 DATA DIVISION......................................................................................................6
1.3.1 FILE SECTION................................................................................................6
1.3.2 WORKING-STORAGE SECTION................................................................7
1.3.3 LINKAGE SECTION.....................................................................................14
1.4 PROCEDURE DIVISION....................................................................................15
1.4.1 Program Structure.........................................................................................15
1.4.2 Coding Structure...............................................................................................17
1.4.3 CALL Statement................................................................................................18
1.4.4 COMMENTS..................................................................................................19
1.4.5 Compound Conditions..................................................................................19
1.4.6 COMPUTE Statement..................................................................................20
1.4.7 Condition Names...........................................................................................21
1.4.8 Conditional Tests...........................................................................................22
1.4.9 DISPLAY Statement.....................................................................................22
1.4.10 GO TO Statement.......................................................................................22
1.4.11 IF Statement.................................................................................................23
1.4.12 Logical Comparisons..................................................................................25
1.4.13 MOVE Statement........................................................................................25
1.4.14 ON Condition...............................................................................................26
1.4.15 OPEN/CLOSE Statements........................................................................27
1.4.16 PERFORM Statement................................................................................27
1.4.17 Program Switches.......................................................................................27
1.4.19 Program Audit Control................................................................................28
1.4.20 Program Constants.....................................................................................29
1.4.21 Prohibited Or Restricted Verbs.................................................................29
1.4.22 READ Statement.........................................................................................29
1.4.23 Record Counts............................................................................................30
1.4.24 REPORT WRITER Feature.......................................................................30
1.4.25 SEARCH Statement...................................................................................30
1.4.26 Sequence Check.........................................................................................31
1.4.27 SORT Feature.............................................................................................31
1.4.28 STRING/UNSTRING..................................................................................31

1.4.29 SUBSCRIPT AND INDEX..........................................................................32


1.4.30 Tables............................................................................................................32
1.4.31 Termination Processing..............................................................................33
1.4.32 TRACE Verb................................................................................................33
1.4.33 WRITE Statement.......................................................................................33

1. COBOL CODING STANDARDS


These COBOL coding standards and conventions are meant to serve as a directive to improve application program quality
and computer programmer productivity. Prime consideration is given to the issues of program readability, understanding,
ease of development and maintenance, ease of debugging, and program efficiency.
Good programming practices and established conventions and standards should always be followed. Changes to improve
machine efficiency should never obscure organized structured program logic.
These standards, conventions, and guidelines will provide for uniformity in the development, construction, and installation
of reliable COBOL application programs.

1.1 IDENTIFICATION DIVISION


This division provides for the capture of all pertinent information concerning the program.
1.1.1 PROGRAM-ID
The eight character assigned mnemonic conforming to the statewide standard naming conventions will be provided by
the data processing system analyst.
A one liner comment statement summarizing the major purpose or function of the program follows this line.
Example:
PROGRAM-ID. XLSA1A1L.

EXTRACT LAST YEARS TRAINING TRANSACTIONS.


1.1.2 AUTHOR
Both the data processing systems analyst and computer programmer's names will be included here. In
addition to the application designer's name and the computer program coder's names, any vendor,
consultant or contractor will also indicate the firm's name here.

1.1.3 INSTALLATION
The use of the INSTALLATION paragraph name is optional.
1.1.4 DATE-WRITTEN

Use the format of "January 31, 2002" to reflect the date when the coding was originally developed by the
computer program coder.
1.1.5 DATE-COMPILED
Enter only the paragraph name, DATE-COMPILED, because the operating system will insert the current
system date after this paragraph name when the COBOL program source code is actually compiled.
1.1.6 REMARKS
This section will provide a brief narrative of the program function or purpose, and a summary of any revision
made to the source code subsequent to the initial program implementation. This section will contain the
following subsections:
a. Program Abstract
A brief description of the main program purpose, function, or control logic, in 3 to 5 sentences. If the
program is part of a system of programs, then explain how the program fits into the system. The following
should also be included:
If the SPECIAL NAMES paragraph (except for top of page) or I O control paragraph is used, it should be
mentioned here to draw attention to its presence.
If subroutine calls are used in the program, list the names and functions of subroutines.
Example. External subroutines called: "CANCEL", "GREGRN".
Explain the organization, structure and use of any table.
Explain when and how the application program should be used.
b. File Descriptions
Enter the name of each file used by the program indicating whether it is input, output or work-file (I/O) and
its file organization (Physically Sequential, VSAM, etc.)
Indicate sort sequence, starting field position, field length, field descriptive name, and a brief description of
internal and external sort files.
c.

Program Modification

Any revision or modification to the program should be noted and dated. Data should include change request
number, date change implemented, programmer's name, and summary description of the change.
Example of a completed "IDENTIFICATION DIVISION":
IDENTIFICATION DIVISION.
PROGRAM ID.
XASA1C1L.
DAGS/ICSD TRAINING EVALUATION REPORTS
INSTALLATION. STATE OF HAWAII, DAGS/ICS DIVISION.
AUTHOR.
PROGRAMMER:
JANE Q. DOE;
ANALYST:
JOHN R. SMITH.

DATE WRITTEN. MARCH 3, 2001.


DATE COMPILED.
REMARKS.
1) GENERATES ANNUAL TRAINING STATISTICS
FROM MASTER STUDENT ATTENDANCE.
2) PRODUCES THE FOLLOWING REPORTS:
a) XASA1C1R
DETAIL COURSE STATS.
b) XASA1C2R
SUMMARY BY COURSES.
c) XASA1C3R
DETAIL DEPT. STATISTICS.
d) XASA1C4R
DETAIL STUDENT STATS.
3) TERMINATE JOB IF INPUT OUT OF SEQUENCE.
SORT ORDER:
01,41,CH,A
SORT KEY
66,04,CH,A
TRAN YEAR
62,04,CH,A
TRAN MON-DAY
4) COURSE CODES AND DESCRIPTIVE NAMES,
FOR MAXIMUM OF 90 COURSES.
5) DEPT CODE AND NAME FOR 30 AGENCIES.
MODIFIED DECEMBER 2001 BY P. POTTER TO ADD SPECIAL
STUDENT PORTFOLIO REPORT XASA1C5R.

1.2 ENVIRONMENT DIVISION


The function of this division is to define and specify the hardware configuration and requirements used by the program.
1.2.1 Configuration Section
The SOURCE COMPUTER and OBJECT COMPUTER paragraph names are optional. If these paragraph
names are coded, enter the phrase: IBM OS/390.
The use of the SPECIAL NAMES paragraph for any purpose other than to specify "TOP-OF-PAGE" or "NEWPAGE", is discouraged.
Do not use the SPECIAL-NAMES paragraph to rename an input/output device, because the I/O functional
name must already be as explicit as any mnemonic.

1.2.2 Input-Output Section


a) No program will use more than three (3) magnetic tape cartridge or reel drives concurrently
for any length of time.
b) No program will use the computer console typewriter for I/O (input-output) message that
requires a computer operator's response.
c) EXAMPLE: 'ACCEPT ..... FROM CONSOLE'
d) All batch programs will print computer operator console status messages:
EXAMPLE:

'DISPLAY ..... UPON CONSOLE'

The 'DISPLAY ..... UPON CONSOLE' sentence is primarily used to send messages to indicate the beginning
and ending status of a program.
EXAMPLE:
DISPLAY ' ' PROG ID ' '
'NORMAL TERMINATION ' UPON CONSOLE.

FILE-CONTROL PARAGRAPH
a. SELECT Statements
For readability, and to allow the flexibility for name changes, each SELECT statement will begin on a new line
with the ASSIGN and other options indented on the following line under the file name.
EXAMPLE:SELECT PAY XTRACT FILE
ASSIGN TO XLSA1A1D
KEY IS XTRT ID KEY
PASSWORD IS OPEN OKAY.
b. File names.
All file names will be descriptive ending with the word "FILE" and indicate the file's primary purpose or
function, such as, input, extract, output, work, sort, or the project's PMS code.
EXAMPLE:
OLD-MSTR FILE (Sample Input File Name)
NEW-MSTR FILE (Sample Output File Name)
TRAN DUP FILE (Sample Output File Name)
TRAN ERR FILE (Sample Output File Name)
OAB XTRACT FILE(Sample PMS File Name)
c. ASSIGN clause.
Device independence is encouraged. Programmers will not assign a data set to a particular storage device.
d. RESERVE clause.
Reserve clause should not be specified but instead assigned at execution time via DD statements.
e. FILE STATUS clause.
File status must be defined in the Data Division for all VSAM files. It is used to monitor the successful
execution of each I/O request of the VSAM file.

I-O-CONTROL PARAGRAPH
a. The RERUN paragraph must not be used.
b. The APPLY clause is discouraged except for use with OCCURS....DEPENDING. It may only be used with
the approval of the project leader.

1.3 DATA DIVISION


This division describes each file, record, and data element used in the program.
1.3.1 FILE SECTION
The File Section contains a description of all externally stored data as well as each Sort / Merge File used in
the program.
File Description Entries
1.The file name is the computer programmer's descriptive mnemonic name for the data file. The file-name
identifies the major function and purpose for the file. DO NOT associate the file-name to a physical
storage device.
EXAMPLE: MSTR TAPE FILE.
2.The file-name should have at least three portions. The last suffix word must be "-FILE". The other words
must describe or identify the application data's purpose, primary function, activity, or data source.
EXAMPLE:
PAYROLL MASTER FILE
OAB XTRACT MSTR FILE

Record Description Entries


Each record description will contain the following entries:
BLOCK CONTAINS.
Use the phrase, BLOCK CONTAINS 0 RECORDS, for sequential files. The value for this parameter will be
determined by the JCL at execution time. For keyed-sequenced randomly accessed files, the actual number
of records per block may be specified. For VSAM files, this statement is treated as a comment.
RECORD CONTAINS.
This entry is optional. If the actual record size is larger than the total specified record length description, only
the 01-level specified data length is made available to the computer operating system.
LABEL RECORD.
This statement definition comes through JCL parameter. The omission of this phrase currently results in a
compiler warning message, so it is recommended to add the phrase: "LABEL RECORD IS STANDARD".
DATA RECORD.
The record description names must be related to the given file name for ease of program maintenance. The
only difference in the names is the suffix name, "-FILE" is changed to "-RECORD" OR "-RECD".
EXAMPLE:

FD MSTR XTRT FILE


BLOCK CONTAINS 0 RECORDS
.
.
.
DATA RECORD IS MSTR XTRT RECD.
IMPORTANT NOTES:
1.The data record picture description will have one "FILLER" statement to reflect the total logical record
length. The exception is when a keyed-definition record is being defined, then appropriate field names for
the key data field(s) and the record status field should be specified in this section.
2.Sequential files should have fairly large block sizes.
The COBOL compiler's de-blocking routine to get logical records from the physical block-size record is
fast and does not require the massive number of housekeeping instructions required to get a new
physical record of data.
Large blocks save I/O channel time and improves peripheral storage capacity, but requires more Virtual
Storage for Buffer Management. The large physical block-size record may substantially increase the total
region size for the program execution.
3.Specify "S" (synchronized) in PICTURE for COMP, COMP-3 and COMP-4 items to align data item on
"word" storage boundaries for efficient arithmetic operations, otherwise an extra instruction is needed to
remove the sign whenever the value of a data element is modified. Specify an odd number of digits for a
data field length.
1.3.2 WORKING-STORAGE SECTION
This section contains data description entries for temporary or non contiguous data items and/or records.
1.3.2.1 WORKING-STORAGE CONVENTIONS
Rules for recording data as stated in the FILE SECTION apply here unless specifically restricted.
a.77 level entries must be removed. Elementary items such as counters, indicators, subscripts, switches, etc.,
should be grouped together under 01, 05, or 10 levels.
b.88 level condition names should be used to describe and test conditions. Names should be descriptive and
meaningful. See switches examples in WORKING STORAGE ORGANIZATION. Section 1.3.2.2
c. All data items including constants, should be initialized with a VALUE clause wherever a value is needed.
d.Continuation of literals is not allowed. The entire literal should be coded on one line, or split into two or more
FILLER-VALUE lines. Careful and consistent alignment helps reduce desk-checking time and produces
preferable documentation.
e.All fields to be used in numerical calculations should be signed, (packed decimal) COMP-3, and have an
odd number of digits
f. Numerical data that will not be used in calculations should be defined as Alphanumeric, for example: ZIPCODE PIC X(05).
g.Arithmetic fields for computations must not be in display mode unless it is part of an I/O record.
h.Eliminate any record, field, or independent data item defined in Working Storage that are not referenced in
the cross reference listing (of compile listing ).
i. Try to specify the same usage (COMP or COMP-3) for numeric items that interact in moves, compares, and
arithmetic statements.
j. For added and subtracted items, specify the same number of decimal places when possible.

k. Use the variable definition, "FILLER PIC X(99)", to define any unreferenced data field areas in a record.
1.3.2.2 WORKING-STORAGE ORGANIZATION
a.The first and last entry for the Working Storage Section must contain a descriptive literal message to define
where the WORKING STORAGE area begins and ends in the nucleus, to provide the programmer with a
debugging aid to locate data assigned to variables within the WORKING STORAGE.
b.
EXAMPLE: WORKING STORAGE SECTION.
c.
01
FILLER
PIC X(32)
VALUE
d.
'PGM=XLSA1A1L, WS BEGINS HERE'.
e.
.
f.
01
FILLER
PIC X(32)
VALUE
g.
'PGM=XLSA1A1L, WS ENDS HERE'.
h.Place the high activity data elements at the beginning of each group of the WORKING STORAGE
SECTION variables.
i. If possible, start all PICTURE clauses in column 40; long VALUE clauses of more than 12 characters or
attribute continuations necessitated by a very long PICTURE expansion in column 30; and for short
PICTUREs, place COMP-3, COMP, SOURCE or short VALUES in column 51. However, the main point
here is consistency.
j. For the ease of program checkout and maintenance, it is suggested that WORKING STORAGE data entries
be categorized into major groupings (01, 05, or 10 levels) whenever possible or practical.
The names assigned to the fields within a major grouping should all begin with the same functional
descriptive prefix. The fields within each major group should be alphabetized. But fields within major
groups that may be printed should be listed in the same order as the output.
EXAMPLE:

Counters or accumulators layout structures:

01
05
05
05
05
05

COUNTERS.
CNT-CLIENTS
CNT-MASTER
CNT-REJECT
CNT-SELECT
CNT-TRANSACT

COMP-3
COMP-3
COMP-3
COMP-3
COMP-3

PIC
PIC
PIC
PIC
PIC

S9(7)
S9(7)
S9(7)
S9(7)
S9(7)

VALUE
VALUE
VALUE
VALUE
VALUE

ZERO.
ZERO.
ZERO.
ZERO.
ZERO.

01
05
05
05
05

ACCUMULATORS.
CUM-AMT-PAID
CUM-INTEREST
CUM-SUBTOTAL
CUM-MON-TOTAL

COMP-3
COMP-3
COMP-3
COMP-3

PIC
PIC
PIC
PIC

S9(7)
S9(7)
S9(9)
S9(9)

VALUE
VALUE
VALUE
VALUE

ZERO.
ZERO.
ZERO.
ZERO.

Some recommended major groupings are as follows:


Input/Output Areas.
This entry would include the Working Storage copies of records from files being processed.
Control Fields.
These areas used for data being sequenced or for processing logic controls.
Constants.

Any elemental data name used to minimize compiler conversions of literals to internal temporary storage
target attributes. Avoid the use of literals in the body of the program.
Counters.
These include all accumulators and audit counters used for numeric operations.
Literals.
These are variable names assigned to literal values. The use of the literal value in the procedure division
is easily located in the cross reference listing. Also, changes to a literal value can easily be made in a
centralized location (DATA DIVISION) and thus eliminates the need to change the literal value in the
PROCEDURE DIVISION.
EXAMPLE:
05
05

ONE
COMP-3
FICA-RATE COMP-3

PIC S9(05)
VALUE +00001.
PIC S9(01)V9(04) VALUE +.0585.

Messages.
These variables are used to simplify changes for program status descriptors; or to define program logic
error messages and their literal text. A control number and a consistent label should be assigned to any
error message and any other status message.
EXAMPLE:
05
MSG14 ERR IN SEQUENCE
PIC X(42) VALUE
'TRANSACTION OUT OF SEQUENCE-ABORT JOB'.
Switches.
The use of switches and flags will be kept at a minimum. Decision switches should have the value of "0"
or "N" to indicate negative off condition, and "1" or "Y" for an affirmative on condition.
Names should be meaningful, self-documenting, and related to the condition being tested.
As an aid for future maintenance, the "88-level" condition data name will be used when defining any
logical switch.
The "88" condition name will have the elementary variable topic it is describing as the prefix for the switch
name.
EXAMPLE-1:
01
05
88
88

TEST-SWITCHES.
EOF-PAY-MSTR PIC X(01) VALUE 'N'.
EOF-PAY-MSTR ON
VALUE 'Y'.
EOF-PAY-MSTR OFF
VALUE 'N'.

COBOL-CODING-1:

IF EOF-PAY-MSTR ON
PERFORM 800-CHK-LAST-PAY-MSTR
THRU 800-CHK-LAST-PAY-MSTR-EXIT.
EXAMPLE-2:
01
05
88
88
88
88

TEST-SWITCHES.
EMPLOYEE STATUS PIC X(01) VALUE ZERO.
EMPLOYEE-IS-NEW
VALUE '1'.
EMPLOYEE-ON-PROBATION
VALUE '2'.
EMPLOYEE-IS-RETIRED
VALUE '3'.
EMPLOYEE-UNCLASSIFIED
VALUE '9'.

COBOL-CODING-2:
IF EMPLOYEE-IS-NEW
PERFORM 550-ADD-NEW-EMPLOYEE
THRU 550-ADD-NEW-EMPLOYEE-EXIT.
Pass Areas.
This area should contain global data elements that will be passed by another program through LINKAGE
SECTION data elements.
Print Formats.
These are used to layout report headers, title lines, detail lines, total lines, etc.
Tables.
This grouping of data elements include tables, arrays, general definitions, etc.

1.3.2.3 LEVEL NUMBER


All level numbers must have two (2) digits.
Except for level 01 items, all level numbers should initially be assigned to values in increments such as: 05,
10, 15. Other level numbers may come about as a result of maintenance, enhancements, or changes in
requirements.
Level numbers should be indented in a consistent manner for each record. The COBOL coding form was
designed in a manner that is convenient to indent four columns for each level, but to establish this indentation
as a fixed standard may be unrealistic in a hierarchy that exceeds four or five levels. The main point here is
consistency.
Align all level specifications and attributes of the same numeric-level rank in the same column position.

1.3.2.4 PICTURE

The PIC form is preferred. The PIC clause and the associated characteristics should be grouped and aligned
in a method to facilitate summing field lengths. The following illustration requires a bit more clerical effort but
has an excellent payoff during desk-checking and maintenance
05
05
05
05
05

FLD-A
FLD-B
FLD-C
FLD-D
NUM-FLD

PIC
PIC
PIC
PIC
PIC

X(02).
X(05).
9(10).
X(22).
S9(05)V99.

For easy reference, PICTURE clauses will be aligned vertically whenever possible beginning in column 40.
When a REDEFINES clause is necessary, it should begin in column 30, and the PICTURE statements within
the redefining area should be under the REDEFINES.
But the key point is consistency to visually associate COBOL key-words. Use the following formats for attribute
descriptions:

Alpha fields as 'PIC X(nn)';


Integer fields as 'PIC 9(nn)';Decimal fields as 'PIC S9(nn)v9(nn)'.
However, when the decimal fraction portion of a field is less than 3 positions, use "99" or "9"
instead of 9(02) and V9(01) respectively.
Output suppression fields should be fully expanded to include editing characters
EXAMPLE:

05

FILLER

PIC

ZZZ,ZZZ.99

1.3.2.5 OCCURS
The OCCURS command is used to define relational table data elements or repeating groups of data
elements.
a.
b.
c.
d.
e.
f.
g.

Fixed length group items or tables in the WORKING-STORAGE SECTION or LINKAGE SECTION
may be as long as 131,071 bytes.
Variable length tables must not exceed 32,767 bytes.
When an OCCURS clause is required, the word OCCURS should start in the same column as the
word PIC, and FILLER...PIC should be on the next line.
EXAMPLE:
01
TABLE-ITEM
OCCURS 10 TIMES
05 FILLER
PIC X(05).
Use no more than one OCCURS...DEPENDING statement in the overall record description. The
overhead from nested OCCURS...DEPENDING is much greater than in a simple fixed occurrence specification.
Put the OCCURS...DEPENDING data at the end of the record, preceded by all fixed data elements. Extra
overhead is entailed in accessing any fixed data element that follows the variable data group, because the
relative position of the fixed data element is also varying.
When a program updates a file that has an OCCURS... DEPENDING record definition, the following technique
is recommended.

1. Use READ...INTO (or READ the record and MOVE it) to place the OCCURS...DEPENDING
record in Working Storage for processing.
2. In the Working Storage record description, specify a simple OCCURS (do not use
DEPENDING) with the maximum number of occurrences.
3. In the Procedure Division, refer only to the simple OCCURS data names defined in Working
Storage.
4. Specify a Level 01 COMP item to indicate the number of occurrences. If the number of
occurrences changes, modify this item but not the DEPENDING object.
Do not directly change the DEPENDING object, because that invokes expensive recalculation of record and
group sizes and relative positions, every time the object value is modified.
1. At WRITE time move the Level 01 item value to the DEPENDING object. Use the
WRITE...FROM statement to transfer the OCCURS...DEPENDING record from Working
Storage to the output file.
2. Specifying APPLY WRITE ONLY for the output file in the Environment Division causes the
access method routines to cut short each output block whenever the remaining space
would be inadequate for the maximum number of occurrences.
3. When using APPLY WRITE ONLY for the output file description, specify the data name of
another 01 Level item as the DEPENDING object - do not specify the corresponding field in
the record itself.
4. Be sure to specify COMP and SYNC for the DEPENDING object or else a conversion to
COMP is needed whenever the record, group lengths, and positions must be calculated.
5. Do not move groups or records containing variable length data to or from the record
description, except at READ and WRITE time, as described above.

1.3.2.6 VALUE
The VALUE clause must not be specified within the FILE SECTION.
Numeric data items should always be signed and have a signed value unless an absolute value is needed.

1.3.2.7 USAGE
Do not use DISPLAY data items for computations. Additional overhead is needed to convert the DISPLAY data
items into an arithmetic type both before and after the computation.
If DISPLAY data items must be used in computations, using up to 5-digits is fast, however, from 5-digits to 9digits is 15% slower, and from 10-digits to 13-digits is 50% slower.

1.3.2.8 COMPUTATIONAL
If arithmetic operations are performed on a numeric data item, it should have a usage of COMP-3 or COMP, as
appropriate. Internal elementary numeric items should be tagged with the appropriate computational form
whenever their primary use is in arithmetic operations.

Specify an odd number of digits for COMP and COMP-3 items, and use the fewest odd number of digits as
possible. Specify S in PICTURE for COMP and COMP-3 items. The SYNC items are processed more efficiently.
The SYNC clause is encouraged for computational items and must appear only at the elementary level.
Subscripts should be defined in the PICTURE with "S" and "COMP SYNC". Conversion to COMP will occur for
subscripts unless COMP is specified. COMP results in the fastest arithmetic instructions.
h.
i.
j.
k.
l.
m.
n.
o.

Use COMP-3 for data element that has more than four digits. Do not specify COMP when a
numeric field is larger than 4 digits. Use COMP for data items that are less than five digits.
One to four digits require two bytes; five to nine digits require four bytes; more than nine require
eight bytes and more complex machine instructions. Avoid using more than 15 digits. Machine instructions
cannot handle over 15 digits, so expensive subroutines are needed to process larger items
With COMP-3, each byte holds two digits for efficient use of space in memory and on peripheral
storage.
If the signed decimal numeric data field "PIC S9(07)" were specified as "COMP-3," the data field
length would be only 4 bytes, and not 7 bytes.
COMP-3 data is easy to read in a dump listing.
COMP is the best format for items used as subscripts, in extensive integer arithmetic, or as
OCCURS...DEPENDING objects.
Except where COMP is best, COMP-3 is the preferred format for all numeric items. Efficient
machine instructions process COMP 3 data directly; other formats often require conversion to COMP 3.
Fixed-point versus floating point (COMP-1 or COMP-2) is used for exponential expressions. When
using fixed-point exponentiation with large exponentials, the calculation can be done more efficiently (by almost
98% faster) by using operands that force the exponentiation to be evaluated in floating-point instead of fixedpoint.

1.3.2.9 RENAMES
Do not use the renames clause. REDEFINES can give the same result.

1.3.2.10 REDEFINES Clause


All redefining should refer to the originally defined statement regardless of the number of redefinitions.
All redefines entries must be of equal size and must have the same level numbers.
See the IBM COBOL reference manual's chapter on "Data Descriptions" when elements involved in the
REDEFINE have the SYNC option.

1.3.2.11 ERROR-SWITCH
Use Procedure-1 below to handle validation or exception error test conditions in the application program.
Include an error switch variable named ERROR SW that is one byte, and a constant variable named PROG ID
that is eight bytes.

ERROR SW will be initially set to zero. PROG ID will contain the value of the program's Program ID code.
PROCEDURE-1: HANDLING EXCEPTION CONDITION
1.For each exception condition:
a) Assign a number and constant variable name in WORKING-STORAGE to each possible
error message for easy reference.
b) DISPLAY an appropriate error message to the Control Report
c) DISPLAY the transaction FIELD, RECORD, or other useful information regarding
the exception. All error messages should be numbered and labeled for easy
reference.
2.For Program Execution Status
a) If program ran okay and the application job stream can continue processing, set the
ERROR SW to "0".
b) If the program has an error in logic and the next program should not continue
processing, set the ERROR SW to "1".
c) If an audit trail accumulator is out of balance and the next program must not run,
set the ERROR SW to "2".
d) If the program should abnormally terminate and the next program must not run, set
the ERROR SW to "A".
3.For the end of job routine, use the ERROR SW and set a program user RETURN CODE and display the
PROD-ID and an appropriate message to the control report.
4.
RETURN CODE = 000
IF ERROR SW = ZEROS.
5.
RETURN CODE = 111
IF ERROR SW = "1".
6.
RETURN CODE = 222
IF ERROR SW = "2".
7.
RETURN CODE = 888
IF ERROR SW = "A".
For each exception condition, print an appropriate error message similar to the messages in the Control
Report found in the standard COBOL skeleton program: XASA1A1HA1.

1.3.3 LINKAGE SECTION


The LINKAGE SECTION is used to describe data made available from another program.
Data item description entries in the LINKAGE SECTION provide names and description, but storage within the
program is not reserved since the data area exists elsewhere.
CICS/VS interface and storage control statements are found in the LINKAGE SECTION.
Example:
LINKAGE SECTION.
01
01
01

DFHCOMMAREA PIC X(010).


DB PCB1
PIC X(100).
DB PCB2
PIC X(100).

NOTE:
Heavily used parameters passed via Linkage Section should be moved to Working Storage variables.

1.4 PROCEDURE DIVISION


The procedure division contains the algorithm for the application program. Ensure that the program is structured
and modularized, uses structured-coding-constructs, avoids the use of the GO TO statement, and always uses
the PERFORM ... THRU format.
Ensure that the data structures and data types are appropriate for the algorithm. As an example, consider two
PERFORM ... VARYING loops, one with a DISPLAY data item for the loop variable, and the other with a COMP
data item to control the loop. The DISPLAY data item must be converted for each iteration of the loop, but the
COMP data item is used directly without a conversion.
1.4.1 Program Structure
Programs should be designed and developed in logical functional modules by establishing module types such
as initialization modules, data-edit-validation modules, data manipulation/processing modules, input/output
modules, etc.
The exact structure will be a matter of judgment and the only rigid standard will be inclusion of a main line
module which is a series of perform statements that can be readily analyzed to determine the major logical
sequence of events of the program. Primary purpose of the main line is to link all the processing modules
together.
Once the main line module structure has been determined, it should be coded at the beginning of the Procedure
Division. Other modules should follow the main line module in any manner that seems appropriate to the
programmer. A brief comment description of the logic purpose for a module is added in front of each module
structure for better program documentation.
The most important consideration to be given the processing modules is that they should be self indexing. A
consecutive numbering scheme is extremely efficient for this purpose. A separate number for each paragraph is
the preferred form. The paragraph names for the modules should be numbered according to their primary
function following these established ranges:
000-099
100
200
300
400
500-899
900

Declarative
Logic Driver/Initialization/Housekeeping
Main Algorithm Processing Logic
Error/Exception Handling
END OF JOB Logic
Processing Functions
Input/Output

The paragraph names will reflect the sole function of the statements included in the paragraphs and as such
make most programs self documenting in its purpose and scope.
The paragraph names should be brief, explicit, direct, and be defined only when necessary for PERFORM or
GO TO statements. Double space or "eject" between paragraphs or sections.
Remember, a paragraph name can consist of up to 30 characters. The use of meaningful and self
documenting names is always helpful for program maintenance. A sequential prefix will be given to each
paragraph name and assigned in an ascending order with a minimum increment of 10.
EXAMPLE:

100-OPEN-FILES.
OPEN
.....
200-GET-TAX-TABLES.
.....
210-GET-MAST-DATA.
PERFORM-900-READ-MSTR
THRU 900-READ-MSTR-EXIT.
.....
240-CALC-GET-TAX.
.....
900-READ-MSTR.
READ .... INTO .... AT END ....
.....
950-WRT-NEW-MSTR.
.....
The general structure and format for paragraph names is:
999-VERB-ADJECTIVE-OBJECT.
.....
999-VERB-ADJECTIVE-OBJECT-EXIT.
In addition to data manipulation and processing modules, the READ and WRITE processing will also
include PERFORM modules.
The program design should follow Structured Programming techniques. Structured programming involves
a systematic "TOP-DOWN" approach for the design and development of a program. A program should
follow a "TOP-DOWN" iterative construction.
The flow of control within a program (or paragraph) should be from top to bottom on a page. Here we are
attempting to reduce the indiscriminate unconditional jumping from one part of a program to another.
Ease of readability is the key here.
A structured program is subdivided into "modules" with each module consisting of one (1) paragraph. A module
is designed to perform one specific task. This allows future changes to the program to be localized to a few
modules and possibly reduce modification and enhancement design and development efforts.
Overlapping functions between modules should be kept of the barest minimum.
Within a program, the functional modules occupy a certain position in a hierarchy such that high level modules
control the activities of subordinate modules. The following technique is used to control the flow of activity within
the program.
A hierarchical relational system structure chart is built from a data flow diagram (DFD). The DFD is a graphical
tool used to identify the necessary processes, functions, steps, and flow of a program solution.
The DFD is used to produce a hierarchical structured chart to further visualize how the separate modules
(paragraphs) of the application solution will logically relate and fit together.
Each box in the hierarchical structure chart must be associated with one paragraph (module) in the program.

Each paragraph (module) must have only one point of entrance and one point of exit. This reduces the number
of alternative paths in a program.

1.4.2 Coding Structure


To minimize the effects of computer processing paging, any infrequently executed paragraph such as:
initialization, termination, error detectors, and exception routine should be grouped together and separated from
frequently executed paragraphs.
Data areas should be initialized in a separate reset area and processed just before they are needed to minimize
the possibility of a S0C7 (numerical data exception).
a.

References to the DATE, DAY, or TIME registers should be executed only once at the
beginning of the Procedure Division, in the initialization or housekeeping routine, and their return-values
moved to Working-Storage variables.
b.
Do not use commas or semi colons for punctuation. The period must be used at the end of
conditionals, sentences, paragraph names, and section names.
c.
Consistently indent the various statements to visually identify logical sequences of
instructions. Consistent indentation is especially needed when defining a complex sequence of
statements to be executed following the "IF" or "ELSE" statement.
Indent ELSE by aligning it with its associated IF. The ELSE must be the only text on that line. The
statements associated with the ELSE must be indented at least four spaces under it.
d.
e.
f.
g.
h.
i.
j.
k.
l.
m.
n.
o.
p.
q.
r.
s.
t.
u.
o
o
o
o
o
o
o
o
o

For ease of readability, code only one statement per line.


EXAMPLE:
Instead of the following code:
MOVE SPACES TO FIELD-A FIELD-B.
Code the above as:
MOVE SPACES TO FIELD-A
FIELD-B.
Or else code it as:
MOVE SPACES TO FIELD-A.
MOVE SPACES TO FIELD-B.
Consistent indentation and high visibility of keywords must be used to identify logical
sequences of instructions. Indent continuation lines at least four spaces past the keyword, for example
Indent AT END at least four spaces past the READ.
READ NEXT-TRANS-RECD INTO HOLD-TRANS-FIELDS
AT END PERFORM 400-END-JOB-WRAP-UP
THRU 400-END-JOB-WRAP-UP-EXIT.
Indent UNTIL and VARYING eight spaces past the PERFORM.
PERFORM 700-EDIT-TRANS-DATA
THRU 700-EDIT-TRANS-DATA-EXIT
VARYING INDXBY ONE
UNTIL
BAD-DATA.

o
Indent the GIVING to line up past the verb ADD or SUBTRACT.
o EXAMPLE:
o
o SUBTRACT ALLOTTED FROM APPROPRIATED
o GIVING ENCUMBRANCE.
v.
When possible, sum all control level break accumulators at one place in the program.
w.
For variable length files, use APPLY WRITE-ONLY in the output file description, specify the
data name of another level 01 item as the DEPENDING object not the corresponding field in the record.
x.
Be sure to specify COMP and SYNC for the DEPENDING object, or else a conversion to
COMP is needed whenever the record and group lengths and positions are calculated.
y.
Do not move groups or records containing variable length data, except at READ and
WRITE times.
z.
Start all batch programs with a DISPLAY start program message.
aa.
The STOP RUN or GO BACK must be coded only once in the mainline processing.

1.4.3 CALL Statement


The CALL subroutine name should be consistent using standard naming conventions. Do not use aliases.
CALL arguments may be elementary or groups with any level number. The size of an argument in the
USING clause may be greater than the size of the matching formal parameter, only when the argument or
formal parameter is a group item. Arithmetic expressions and literals may be used as CALL arguments.
Use of CALL statements should be minimized and coded in paragraphs to be performed when needed to
call shared global program processes
Use the DYNAM option when calling a subprogram.
Available standardized subroutine names and their descriptions that may be INCLUDED are found in
Appendix B.
Only the main entry point name will be Called. Available standardized subroutine names and their
descriptions that may be INCLUDED are found in Appendix B.
The parameter names should be aligned and begin on a consistent column
EXAMPLE:
CALL 'EXTRACTOR'
USING
MAST-IN-DATA
SELECT-CRITERIA
ACCEPTED-DATA.

1.4.4 COMMENTS
Comment lines may be written at any line, even before the IDENTIFICATION DIVISION header.
Comments will be used to point out or emphasize relationships and objectives of processes,
comparisons, variables, complex formulas, derivations of formulas, or uses of tables or arrays

Each program routine and subroutine will have comments to summarize the source and function of the
routine or subroutine, especially when its purpose is not immediately obvious by reading its COBOL
statements. Comments are made by entering the asterisk () in column 7.
EXAMPLE:
500 VERIFY VALID DATA.
TRANSACTION DATE FIELD IS VERIFIED. MONTH-DAY-YEAR
FIELDS RANGES ARE EDITED. KEY FIELDS OF CUSTOMER-ID
AND ORDER NUMBERS ARE CHECKED AGAINST TABLES.
Enter an asterisk () in column 7 to comment a line. Do not use the "NOTE" statement."
The use of meaningful comment statements in program is strongly recommended. Briefly describe the
task or function of the module to expand on the paragraph name.

1.4.5 Compound Conditions


A compound conditional statement contains multiple resultants for one elementary data item.
a.Compound statements that omit the test field's data name shall not be used. Use only simple conditional
tests.
b.Each compare condition should be explicitly stated. Use parenthesis to assure logical groupings of
operands.
c. Do not use compound negative conditional tests.
d.
EXAMPLE-1:
e.
f.
IF CHK-FIELD = 'A' OR = 'B' OR = 'C' .....
g.
h.
The above statement must be revised to be coded as:
i.
j.
IF CHK-FIELD = 'A' OR
k.
CHK-FIELD = 'B' OR
l.
CHK-FIELD = 'C'
m.
n.
EXAMPLE-2:
o.
p.
IF (FLD-A IS NOT GREATER THAN FLD-B) OR
q.
(FLD-C IS EQUAL TO FLD-D),....
r.
s.
EXAMPLE-3:
t.
u.
IF FLD-A IS NOT EQUAL TO NOT FLD-C
v.
w.
IF NOT FLD-B IS NOT LESS THAN NOT-FLD-D
x.
y.
IF NOT FLD-A IS NOT = FLD-B OR NOT FLD-C = FLD-D
The above conditional statements are examples of the type of logical comparisons to be avoided. As an
alternative in the first negative example it would be simpler just to say that "field-a = field-c".

1.4.6 COMPUTE Statement


For arithmetic expressions, the use of the COMPUTE statement is encouraged. It is easy to check out and
tends to be self documenting. However, sometimes it may be more intuitive to code
ADD 1 TO CNT-READ
instead of coding:
COMPUTE CNT-READ = CNT-READ + 1
Items referenced by arithmetic verbs should all be COMP or COMP 3. Items added or subtracted should have
the same number of decimal places.
For items not in ideal formats of same attributes and same decimal lengths, move them to ideal data item
formats in working storage before processing.
For computations involving several arithmetic operations, the COMPUTE verb is more efficient than a sequence
of separate arithmetic verbs. However, the precision of the intermediate results cannot be controlled using
COMPUTE, and may not generate the expected final report.
The relative speeds of the arithmetic operations are as follows:
ADD or +
SUBTRACT or MULTIPLY or
DIVIDE or /
(exponentiation)

fast
fast
slow
slower
very slow

Avoid costly multiplication by 0 or 1 or division into 0 by careful arrangement of the logic or by coding an extra IF
to bypass the calculation.
Eliminate unnecessary use of the rounded clause. Consider rounding directly in a calculation for values that
always have the same sign, but be sure the formula is documented to eliminate misinterpretation in later
maintenance.
The next example is the recommended syntax to control "rounding" for two decimal place accuracy after the
computation.
EXAMPLE:
COMPUTE PERCENT = RATE

TIME + 0.005.

The COMPUTE verb should always be used when multiple arithmetic operators are involved. Consider two sets
of equivalent code:
Poor Code:
MULTIPLY B BY B GIVING B SQUARED.
MULTIPLY 4 BY A GIVING FOUR-A.
MULTIPLY FOUR-A BY C GIVING FOUR-A-C.
SUBTRACT FOUR-A-C FROM B-SQUARED GIVING RESULT-1.
COMPUTE RESULT-2 = RESULT-1 .5.

SUBTRACT B FROM RESULT-2 GIVING NUMERATOR.


MULTIPLY 2 BY A GIVING DENOMINATOR.
DIVIDE NUMERATOR BY DENOMINATOR GIVING X.
Improved Code:
COMPUTE X = ( B + ((BB)

(4

C))

0.5) / (2

A).

Both 'poor-code' and 'improved-code' applies to the quadratic formula:


X = B + / (BB - 4AC)
2A
It is easier for the reader to determine what is happening from the single COMPUTE statement.
It is awkward and difficult to realize the cumulative effect of the 8 individual arithmetic statements. The
interpretation and understanding of the unacceptable poor-code is further clouded by the mandatory syntax
definition for temporary data names for the intermediate results, such as, RESULT-1, RESULT-2, etc.
Parentheses are often required in COMPUTE statements to control or alter the normal hierarchy of operations.
As an example, the parentheses are necessary around "2 A" in the denominator. If the parentheses had been
omitted, the numerator would have first been divided by "2" and then the quotient would have been multiplied by
"A".
Sometimes parentheses are optional to the compiler, but should be coded to clarify things for the computer
programmer. As an example, the set of parentheses around "4AC" do not alter the normal order of operations
and hence are optional.
1.4.7 Condition Names
Meaningful condition names in the DATA DIVISION make excellent documentation and can be a great aid in
revealing the program logic.

1.4.8 Conditional Tests


To minimize misunderstanding, the relational operators such as "&" , ">", and "<" should be coded "AND",
"GREATER THAN" and "LESS THAN". It makes the program listing more self-documenting and
more narrative and prose like
Do not use implied conditional subjects or operators.
Example:
IF X = FIVE OR SIX OR Y OR TWO

1.4.9 DISPLAY Statement

The DISPLAY UPON CONSOLE is permitted only to designate the start of the batch program, or the result of
the execution of the batch program.
Any other use requires prior approval from the Computer Operations Services Branch Chief. An important
exception to this rule is a situation requiring operator action, such as, multiple uses of tapes for
Read Only then Read/Write.
If the DISPLAY statement is used, a comment line should be noted in the FILE-CONTROL paragraph stating its
use in the program.
DISPLAY messages should be identified by the PROGRAM-ID that issues it.
Example:
DISPLAY "START PROGRAM - XLSA1A1L"
DISPLAY "ABNORMAL END OF JOB - XLSA1A1L"
DISPLAY "NORMAL END OF JOB - XLSA1A1L"

1.4.10 GO TO Statement
Do not use the DEPENDING ON format. Use separate nested "IF" statements instead.
Use of GO TO's will be kept to a bare minimum. The permissible GO TO's transfer control to a paragraph
"EXIT".
The "GO TO" statement when employed should direct control of the program to a point subordinate to it within
the same paragraph. Upward control movement is not allowed. The "GO TO" statement should not
be used to transfer control to a point outside of the module in which it resides.
Example:
200-SAMPLE-GOTO.
READ TRAN-REC INTO WS-TRAN-REC
AT END MOVE HIGH-VALUES TO PREV-ID.
IF PREV-ID = HIGH-VALUES
GO TO 200-SAMPLE-GOTO-EXIT.
MOVE ID
TO PREV-ID.
200-SAMPLE-GOTO-EXIT.
EXIT.
When it is necessary to loop back to the beginning of a module, use the "PERFORM ... VARYING ... UNTIL" or
"PERFORM ... UNTIL" or "PERFORM ... TIMES" in lieu of the "GO TO" statement. By doing so, the
condition(s) under which the looping is undertaken is well defined.

1.4.11 IF Statement
Nested IF statements are permitted. Nesting the "THEN" condition should be limited to no more than 3 levels.
For longer nested IF statements, use the "END-IF" (scope terminator) for each IF statement.
Consistent alignment of paired IF statements is required for ease of maintenance.

Example:
IF condition-1
IF condition-2
IF condition-3
statement-3-1
ELSE
statement-3-2
ELSE
IF condition-4
statement-4-1
ELSE
statement-4-2
ELSE
IF condition-5
statement-5-1
ELSE
statement-5-2.
Consistent indentation will show the subordination relationships.
Example:
IF GET-A-RECORD
PERFORM 210-GET-A-RECORD THRU
210-GET-A-RECORD-EXIT
ELSE
IF START-BROWSE
PERFORM 220-START-BROWSE THRU
220-START-BROWSE-EXIT
ELSE
IF GET-NEXT-RECORD
PERFORM 230-GET-NEXT-RECORD THRU
230-GET-NEXT-RECORD-EXIT
ELSE
IF GET-PREVIOUS-RECORD
PERFORM 240-GET-PREVIOUS-RECORD THRU
240-GET-PREVIOUS-RECORD-EXIT
ELSE
PERFORM 300-WRONG-GET-REQUEST THRU
300-WRONG-GET-REQUEST-EXIT.
The allowable exception to these relational indentations is for more than three (3) mutually exclusive case
selection criteria.
Example:
IF GET-A-RECORD
PERFORM 210-GET-A-RECORD THRU
210-GET-A-RECORD-EXIT
ELSE
IF START-BROWSE
PERFORM 220-START-BROWSE THRU
220-START-BROWSE-EXIT
ELSE

IF GET-NEXT-RECORD
PERFORM 230-GET-NEXT-RECORD THRU
230-GET-NEXT-RECORD-EXIT
ELSE
IF GET-PREVIOUS-RECORD
PERFORM 240-GET-PREVIOUS-RECORD THRU
240-GET-PREVIOUS-RECORD-EXIT
ELSE
IF ....
In a sequence of mutually exclusive IF statements, try to order the statements from most likely to least likely, but
do not sacrifice program readability or understandability.
Use the IF statement to isolate groups of code that do not require processing for every execution path.
Do not place any Input/Output statement within the conditional IF...ELSE.
The THEN is optional. It must be on a line by itself.
Example:
IF condition-1
THEN
IF condition-2
THEN
IF condition-3
THEN
statement-3-1
ELSE
statement-3-2
ELSE
IF condition-4
THEN
statement-4-1
ELSE
statement-4-2
ELSE
IF condition-5
THEN
statement-5-1
ELSE
statement-5-2
Use the negative IF condition only when the statement is more explicit, much clearer or eliminates the use of
"THEN NEXT SENTENCE".
Example:
IF VARIABLE-NAME NOT NUMERIC
PERFORM 500-NOT-NUMERIC THRU
500-NOT-NUMERIC-EXIT.

1.4.12 Logical Comparisons


For numeric compares, the items should both be COMP or COMP-3, be both signed or both unsigned, and
have similar PICTUREs. Numeric data must be either COMP or COMP-3 for the machine compare
instructions.
Comparing numeric items necessitates costly conversion and decimal point alignment steps, unless they have
identical formats. COMP-3 is easier to trace in a dump, but COMP is calculated slightly faster than
COMP-3.
The IF NUMERIC and IF ALPHABETIC class condition statements are quite essential but should be used with
care. They are very costly, and use of class compares should generally be limited to validating raw
input data.

1.4.13 MOVE Statement


Do not use MOVE CORRESPONDING. MOVE CORRESPONDING does not document well for readability, and
can be difficult to maintain when exceptions occur at some later date.
When using "MOVE ... TO ..." for a group of MOVEs, the word "TO" should be aligned on the same column to
improve readability.
Example:
MOVE PAY-SSN
MOVE PAY-NAME
MOVE PAY-ADDRESS

TO
TO
TO

PRT SSN.
PRT NAME.
PRT ADDRESS.

Literals:
The value of any alphanumeric literal field defined in WORKING-STORAGE will be alphanumeric data framed
within apostrophes.
Before the required MOVE of data, fill out the literal field with the same number of characters as the receiving
items.
If the sending/defining literal value is shorter than the receiving item, the statement actually results in an efficient
move of the literal followed by an inefficient move of spaces to clear the remaining character positions.
Literal variables should be filled out (padded) unless that would entail a large number of trailing blanks (for
example, 12 or more spaces).
Item Sizes
Moves are most efficient when the sending variable field is at least as large as the receiving variable field.
It is most efficient to define a constant data item of spaces in Working-Storage and move from this variable,
rather than using the figurative constant SPACES.

The recommended technique to save CPU time and conserve memory is to define a figurative constants with a
maximum size specification and let the compiler truncate it during the MOVE.
Example:
01
03
03
03

INIT-CONSTANTS.
ALL-SPACES
PIC X(080) VALUE SPACES.
ALL-HIGH-VALUE PIC X(100) VALUE HIGH-VALUE.
ALL-LOW-VALUE PIC X(100) VALUE LOW-VALUE.

Consider group level moves rather than separate moves of elementary items when PICTURE and USAGE of
sending and receiving items correspond.
The numeric move is always most efficient if both items are COMP or COMP-3, have the same number of
decimal places (if any), and both (or neither) have S in PICTURE. However, if data items are initially not
aligned, a planned move to the ideally formatted data items in Working-Storage will save repeated conversions.
Moves to an item which is the object of an OCCURS ... DEPENDING clause should be avoided except at
WRITE time.

1.4.14 ON Condition
Eliminate unnecessary use of ON SIZE ERROR clause. Eliminate condition by using techniques such as
checking for zero before dividing, etc.

1.4.15 OPEN/CLOSE Statements


Use a single OPEN statement rather than separate OPEN statements for files opened around the same time.
Use of a single OPEN statement reduces routine loading time. System routines required for OPEN are
referenced once for each OPEN statement regardless of the number of files specified in the statement.
Sometimes a programmer uses a file over and over to hold temporary data, repeating OPEN WRITE CLOSE
and OPEN READ CLOSE sequences many times. These applications should be studied carefully to see
whether a working storage table could be used instead. OPEN and CLOSE are very costly statements and are
designed to be used only once or a couple of times by each program.
The OPEN/CLOSE statements should be executed only once per program. Files can be opened for INPUT,
OUTPUT, or I-O.
Programmers must ensure that all files are properly opened and closed, especially for temporary datasets that
are allocated in the step that executes the COBOL program.
The OPEN/CLOSE statements cannot be used in CICS programs.
1.4.16 PERFORM Statement
To eliminate the possibility of logical "fall-thru", use the "PERFORM procedure-name-1" THRU "procedurename-2" format. The "procedure-name-2" will be an exit for the "procedure-name-1" module.

EXAMPLE:
PERFORM 510-READ-DATA THRU 510-READ-DATA-EXIT.
Perform paragraphs, do not perform sections.
The PERFORM UNTIL option is encouraged. Its use is usually obvious and is easy to check out. If possible, the
program logic must check the parameters affecting the routine to assure it will not remain in a loop.
PERFORM VARYING format is permissible. Other forms are preferable.
When using the VARYING format, try to place numeric computations outside of the loop. When using the varied
variable's value for computations that depend on the number of times the paragraph is performed, do the
computations after the loop processing. The scope terminator (END-PERFORM) is required.
The VARYING or UNTIL clause should be indented on a line separate from the PERFORM verb.
EXAMPLE:
PERFORM 510-GET-VALID-TXN
THRU 510-GET-VALID-TXN-EXIT
UNTIL LAST-TXN-RECD.
Use multiple PERFORMS instead of NESTED PERFORMS.
1.4.17 Program Switches
Program switches should be kept at a minimum. However program initialization switches and end-of-job
switches are encouraged since their use is usually apparent.
Switches that are set only once per program run are also obvious and should be set via an input control
statement. Such as selecting only certain Counties to be processed; or selecting only certain reports to be
generated. In any event, detailed annotation of switches is required.
The recommended switch practice is to set a switch as a result of a logical controlling condition. A preferable
method is to test the condition again. If the condition is no longer present, anticipate the situation and route the
program through a different series of modules.
In place of a separate switch to identify an EOF condition, the non numeric literal KEY field of the record may be
set to high value. The KEY field can then be tested for the EOF condition. The high value in the KEY field
simplifies the overall logic to complete processing of other input files. But a separate switch offers more
flexibility.
If switches are used, use the level-88 feature and variable names that explain the condition.
Example:
05
88
88
88

EYES-COLOR
PIC X(02) VALUE SPACES.
EYES-ARE-BLUE VALUE "BL".
EYES-ARE-BROWN VALUE "BR".
EYES-ARE-GREEN VALUE "GR".

IF EYES-ARE-BLUE

PERFORM
520-BLUE-EYES
THRU 520-BLUE-EYES-EXIT.
IF EYES-ARE-BROWN
PERFORM 540-BROWN-EYES
THRU 540-BROWN-EYES-EXIT.
IF EYES-ARE-GREEN
PERFORM 560-GREEN-EYES
THRU 560-GREEN-EYES-EXIT.

3.4.18 Print Report Format


For traditional reports, before you start to build a line to be written out, move spaces to a redefined variable of
the entire print line layout area.
a. If the Print-Line area is in working storage, either move spaces during program initialization or specify VALUE
SPACES in the sub group or FILLER items.
b. Consider moving the variable of all space for one print line to blank out the whole line via the group name, or
moving spaces to specific positions.

1.4.19 Program Audit Control


Each program must have an audit control report. This report must include the following where it makes sense:
a. The literal "REPORT#: " in the upper left corner;
b. Program identification value in the IDENTIFICATION DIVISION with the last character changed to "R", follows
the above literal in the upper left corner;
c. The literal "FOR THE PERIOD: " followed by the control date of data, in the form of MM/DD/CCYY or "monthname CCYY" under the report number;
d. Center the report headers to identify the State, Department, Division, Branch, and subject matter of the
application program;
e. Center the report title containing the literal "CONTROL REPORT";
f. The literal "PAGE: " followed by the page count value;
g. Program run date (and optionally, execution CPU run time) in the under the page number;
h. Any input Parameter variable-name and last value;
i. Any input control statement;
j. Messages for errors or exception conditions;
k. Input/Output record counts;
l. Batch control totals.

1.4.20 Program Constants


Data names should be used to express constant values instead of the actual literal constant. This promotes
easier program maintenance and also provides for better readability and understanding.
Example:
05

VALUE-9

PIC

9(01)

VALUE "9".

05
05
05

VALUE-X
ONE
TWO

PIC
PIC
PIC

X(01)
S9(05)
S9(05)

VALUE "X".
VALUE +1.
VALUE +2.

1.4.21 Prohibited Or Restricted Verbs


The ALTER statement is never permitted.
ACCEPT FROM CONSOLE option is not permitted. If used, it should be noted in the FILE CONTROL
paragraph with a comment.
Try to use CONTINUE , instead of NEXT SENTENCE.
The EXAMINE verb is not permitted.
The ACCEPT, CURRENT DATE, DATE, DAY, DISPLAY, EXHIBIT, INSPECT, SIGN IS SEPARATE, STOP RUN,
TIME, AND UNSTRING verbs are not allowed for CICS programs.

1.4.22 READ Statement


Data is to be read into a working storage defined area before any processing, and data is never read into the
FD record description data fields for processing.
Use the READ...INTO...WORKING-STORAGE-INPUT-AREA format. This format provides a readable trace in
memory dumps.
Use the "AT END" or "INVALID KEY" clauses for any "READ" statement.
Code only one READ statement for each file in a paragraph, that is PERFORMED whenever the data is
needed.
Advantages of one functional READ or WRITE paragraph for each file are:
a. Coding can be added to count the processed records.
b. The files can be reformatted without changing the program's logic.
c. DEBUG statements can be easily added to DISPLAY records.
The input area should be filled with all high values at end of file unless the end of file condition forces an end of
job condition. This particular approach is in the interest of uniformity for EOF logic rather than gaining any
program advantage.
Whenever possible, avoid having more that one record per file in core at any one time. For example, when
master record (with KEY=121) is in core, do not read another record (with KEY=122) in core until record (with
KEY=121) has been completely processed. This avoids unnecessary complexity in a program.

1.4.23 Record Counts

Record Counts should be maintained for all input and output files. Definition of counter names should be
meaningful and representative to the file.
Record counts serve as a good debugging tool and should be printed or displayed as part of the end of job
routine whether the run is successful or not.
Record counts should be maintained when records are extracted, skipped, or found to contain severe errors.

1.4.24 REPORT WRITER Feature


Do not use the COBOL Report Writer Facility. The COBOL FOR MVS and VS COBOL II compilers do not
support the REPORT WRITER FACILITIES.

1.4.25 SEARCH Statement


a.
b.
c.
d.
e.
f.

Prior hit. Check the prior hit before beginning the search it may be what you need.
Unused table positions. Program the search logic so that searching stops with last meaningful item in the table.
Use SEARCH if the table has 50 or fewer entries.
If the table is sorted and contains over 50 entries, SEARCH ALL may be faster.
For any size table, put most frequently hit entries at the beginning of the table, if possible, and use SEARCH.
Alternatively, use IF to eliminate searching for the most frequently occurring items. If 60% of the customers are
in New York, use the IF...ELSE to check New York first before the SEARCH.
g. Note that several of these techniques can be combined into a single search strategy.
P>oNote that several of these techniques can be combined into a single search strategy.

1.4.26 Sequence Check


Sequence checking should be performed whenever specific sequence is required of an input file. Any sequence
error message generated should include previous and current keys as well as current record count.

1.4.27 SORT Feature


The COBOL SORT verb should be avoided for these important reasons:
1. The COBOL program becomes a subroutine to the SORT verb.
2. If program abends, the resulting dump is almost useless.
3. Programs using CICS cannot use SORT.
The SORT external utility is the recommended method for sorting.
The SORT feature, if it must be used, is for very short and very small files only. The record released to the
SORT should be an exact image of the input record with a sort key tagged on to the left most position.

SORT CORE SIZE will default to a value specified at the time the SORT program was installed. This MAXSIZE
should always be used. Give SORT as much information as possible. The USING file record size must be equal
to the giving file record size otherwise the program will abend with CC=OC4.
Most SORTS will be accomplished through the external procedures using the utility SORT.
EXAMPLE:
PROC=SORT
PROC=SORTD
PROC=REGSORT
Use simple key fields. Combine adjacent key fields to build super description keys.
The COBOL Optimizer will cause unpredictable results for the "USING/GIVING" clauses with the SORT feature.

1.4.28 STRING/UNSTRING
STRING/UNSTRING should be used with care. A character by character MOVE loop is more efficient.
It is more efficient to REDEFINE the data as a table of one character items and to unstring the data with IF and
MOVE statements.

1.4.29 SUBSCRIPT AND INDEX


The Indexed form is preferable but both forms are acceptable. The Indexed form is more efficient and generates
good documentation.
a. Indexing is usually more efficient than subscripting for sequential table searching or when the same subscript is
used several times in relation to the number of times its value is changed.
b. Always specify COMP SYNC and S in PICTURE for any item used as a subscript.
c. Indices are not interchangeable between tables.
d. If a table item is processed extensively (i.e., many references to the same item in the same logic path or loop)
move it to a fixed item in working storage, then direct all the references to the fixed item.
e. SET to a literal value is fast. SET to a value of a data name may require format conversion and may be slow.
f. Subscript with data names, do not use literals.

1.4.30 Tables
A fixed length table or fixed length group items must not exceed 131,071 bytes in length.
The maximum storage size of varying tables is 32,767 bytes.
When defining a table, design it so that the rightmost index varies the most often, having the leftmost subscript
vary the most is 7% slower.

When coding Table Entries, separate line entries should be made for each item in the table. Separate entries
will aid in the correction of entries and provide for better readability.
Always verify that the subscript is valid and within the range. Do not use the SSRANGE option to catch the
subscript range error.
Use indexes to address a table , do not use subscripts. The index already has the displacement from the start of
the table. Subscripts are an occurrence number that must be converted to a displacement value at run-time.
When using subscripts to address a table, use signed binary (COMP) data items with fewer than 8-digits,
preferable is using 4-digits or less.
EXAMPLE:
05
10

MONTH LITERAL TABLE.


FILLER PIC X(18) VALUE "JANUARY FEBRUARY".

The above is not acceptable, whereas the following is:


05
10
10

MONTH LITERAL TABLE.


FILLER PIC X(09) VALUE "JANUARY".
FILLER PIC X(09) VALUE "FEBRUARY".

When working with TABLES, always use TABLE MAXIMUM checks to keep from exceeding the boundaries of
the TABLE.
For efficiency, put frequently accessed items at the beginning of the TABLE for sequential searches.
Do not alter table entries in their table location. Move the entries to working storage areas and modify those
area and then move the values back to the table locations.
Any table whose size or values may change during a program run must be designed to be loaded each time the
program is executed.

1.4.31 Termination Processing


a.
o
o
o
b.
o
o
o
o
o

Normal termination processing for the control report from batch programs:
Display the audit trail cumulated fields.
Display the counts of input/output data sets.
Send a message to the console to identify the program name and its normal ending status.
Abnormal termination processing for the control report from batch programs
Display a message to explain the cause for the termination.
Display the record key and fields causing the termination.
Display the input/output counts for the data fields.
Set a return condition code as specified for the standard ERROR SW
Display an abnormal end of job message to the console and to the control report.

1.4.32 TRACE Verb

Do not use the TRACE verb for any CICS program.


RESET TRACE Verb consumes time even if TRACE is never activated. Therefore, it is important to remove
these statements when they are no longer needed for debugging.

1.4.33 WRITE Statement


The "WRITE FROM" format will be used.
Example:
WRITE PRINT-DETAIL FROM WORKING-OUTPUT-AREA.
The "AFTER ADVANCING" format is to be used instead of "AFTER POSITIONING".
WRITE statements will be kept to a minimum. One for TOP-OF-PAGE writing. And one other for all other writing
to a file. The most CPU time consuming COBOL verbs are the I/O verbs. Put WRITE's in paragraphs to be
PERFORMED.
Line counting is required for overflow testing.
REWRITE is a time-consuming verb. Often several successive transactions apply to the same record. Be sure
your program waits to REWRITE a record until no further use can be made of it and all changes have been
made to it.

Vous aimerez peut-être aussi