STD_COBOL_formal_coding_standards_RV04
STD_COBOL_formal_coding_standards_RV04
INDEX
1. INTRODUCTION ..................................................................................................................................................... 3
2. PROGRAMS .............................................................................................................................................................. 4
2.1. IDENTIFICATION DIVISION...................................................................................................................................................... 5
2.2. ENVIRONMENT DIVISION ........................................................................................................................................................ 6
2.3. DATA DIVISION .......................................................................................................................................................................... 8
2.4. PROCEDURE DIVISION............................................................................................................................................................ 13
3. COPYBOOKS .......................................................................................................................................................... 21
4. DCLGEN .................................................................................................................................................................. 22
1. Introduction
The present document describes the formal coding standards for COBOL elements. The definition
of formal standards is not only intended to increase the legibility of the code but also to standardize
the aspect of the programs, so that the overall presentation has a professional “finish” that is fitting
to a software company.
It is essential for Alnova platform developers to accomplish these standards, although in the future
an automatic code formatting tool1 will be available, which will transform the programs and other
elements into similar elements that will be capable of fulfilling the standards reflected in the present
document.
Even so, programmers are urged to familiarize themselves with the standards described below, and
to use them to generate codes that come as close as possible to the general coding standards. We
believe that the use of these standards from the early stages of development will be conducive to
legibility and professionalism, and will improve communications between the different elements of
our development teams.
An in-depth explanation of the standards that apply to COBOL programs is followed by a
description of those that are applicable to COPYBOOKS and DCLGENS.
Standards are preceded by an identification code with the format [FSDDTNNNN]. Here FS refers
to this document, DD indicates the COBOL division to which it applies, ID is the IDENTIFICATION
DIVISION, ED the ENVIRONMENT DIVISION, DD the DATA DIVISION, PD la PROCEDURE
DIVISION, AD for standards that apply to all the divisions, CS for COPYBOOK standards and
finally DS for DCLGENS standards. The letter T will be C to indicate that the standard applies to the
comment of an element, whilst it will be S for standards denoting sentences. Finally, NNNN will be
a sequential number.
1 This tool is currently being developed and will be marketed under the trade name Beauty COBOL.
2. Programs
[FSADC0001] Contents expressed in columns 1 to 6 will be deleted.
[FSADC0002] Contents expressed in columns 73 to 80 will be deleted.
[FSADC0003] Only the following line comments will be maintained:
Block comments specified below as part of the standard.
Blank lines containing only the comment character in column 7.
Blank lines that will be replaced by a line with an „*‟ in column 7.
Lines starting with a comment character in column 7 having only blank and „*‟ characters.
Will be replaced by a line with 66 „*‟ characters.
Blocks delimited by the marks. PR, .MC, .IE or .FE.
Furthermore, if there are two or more consecutive comment lines that are exactly the same, they will
be substituted by a single line.
* PPPPPPPP: DDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDD *
* DDDDDDDDDDDDDDDDDDDDDDDDD *
******************************************************************
*A.PD.S *
*TEXTO LIBRE DE DESCRIPCION CORTA DEL PROGRAMA . . . . . . . . . *
*. . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . *
*. . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . *
*. . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . *
*A.PD.E *
*B.PD.S *
*PROGRAM SHORT DESCRIPTION . . . . . . . . . .. . . . . . . . . .*
*. . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . *
*. . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . *
*. . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . *
*B.PD.E *
******************************************************************
* IDENTIFICATION DIVISION *
******************************************************************
Where PPPPPPPP is the name of the program and DDD......DDD is the short description of the
program. These data will be automatically extracted from ART by the formatting tool.
[FSIDC0002] Any other block comments preceding the IDENTIFICATION DIVISION will be
deleted.
[FSIDS0001] The following will be the only valid and mandatory clauses in the IDENTIFICATION
DIVISION:
IDENTIFICATION DIVISION.
PROGRAM-ID. <program-name>.
AUTHOR. ALNOVA TECHNOLOGIES CORPORATION.
DATE-WRITTEN. <dd-mm-yyyy>.
The name of the program will be obtained from ART, in addition to the DATE-WRITTEN field,
which refers to the date on which the object was created.
******************************************************************
*A.OR.S *
* TEXTO LIBRE DE DESCRIPCIÓN EXTENSA DEL PROGRAMA............... *
* .............................................................. *
* .............................................................. *
* .............................................................. *
*A.OR.E *
*B.OR.S *
* PROGRAM LONG DESCRIPTION.......................................*
* .............................................................. *
* .............................................................. *
* .............................................................. *
*B.OR.E *
******************************************************************
[FSEDC0002] It is mandatory to include a block comment with the modifications LOG, even though
modifications do not yet exist. The format will be as follows:
* MODIFICATIONS LOG *
******************************************************************
* CODE AUTHOR DATE DESCRIPTION *
* -------- -------- -------- -------------------------------- *
*B.MD cccccccc aaaaaaaa dd-mm-yy dddddddddddddddddddddddddddddddd*
******************************************************************
[FSEDC0003] The following division mark must precede the division name:
* ENVIRONMENT DIVISION *
******************************************************************
[FSEDS0001] The CONFIGURATION SECTION is mandatory and can only contain the sentence
that denotes the comma as having a decimal-point separator. The format will be as follows:
ENVIRONMENT DIVISION.
*
CONFIGURATION SECTION.
*
SPECIAL-NAMES. DECIMAL-POINT IS COMMA.
2The present document does not take into account multi-language marks. The examples in this document will
be mono-language marks, although it must be understood that multi-language marks will also be valid. The
same applies to code marks that admit continuations.
[FSEDS0002] The INPUT-OUTPUT SECTION will only appear in the event file input is to be
defined. If this section is included, the format will be:
*
INPUT-OUTPUT SECTION.
*
FILE-CONTROL.
SELECT <logic-name> ASSIGN TO <ddname>[.]
[<additional-clauses>...]
*
******************************************************************
* DATA DIVISION *
******************************************************************
DATA DIVISION.
[FSDDC0002] The FILE SECTION should only be included when there are FD sentences. When this
is the case, this section must be preceded by the following comment mark:
*
******************************************************************
* FILE SECTION *
******************************************************************
FILE SECTION.
[FSDDC0003] The WORKING-STORAGE SECTION must always be included and will be preceded
by the following block comments:
*
******************************************************************
* WORKING-STORAGE SECTION *
******************************************************************
WORKING-STORAGE SECTION.
[FSDDC0004] The LINKAGE SECTION will only appear when it is not blank (contains data). If this
is the case, it will be preceded by the following comment mark.
*
******************************************************************
* LINKAGE SECTION *
******************************************************************
LINKAGE SECTION.
[FSDDS0001] The sections LOCAL-STORAGE, COMMUNICATION and REPORT will not appear.
[FSDDS0002] SD clauses are not admitted.
[FSDDS0003] FD clauses are specified with the following format (the initial block comments are
optional):
*
******************************************************************
* <logic-name> *
* *
* <short description of the file............................> *
******************************************************************
*
FD <logic-name>
[<additional-clauses>]
BLOCK CONTAINS 0 RECORDS
DATA RECORD IS <name-record-data>.
*
01 <name-record-data> <picture>.
[FSDDS0004] The WORKING-STORAGE SECTION must start on the 01 level and have the
following format:
*
**** WORKING STORAGE START MARK **********************************
01 CA-STTDAT.
05 CA-TXT-STTDAT PIC X(40) VALUE
'** START WORKING-STORAGE FOR PPPPPPPP **'.
[FSDDS0005] The WORKING-STORAGE SECTION must end on the 01 level and have the
following format:
*
**** WORKING STORAGE END MARK ************************************
01 CA-FINDAT.
05 CA-TXT-FINDAT PIC X(40) VALUE
'*** END WORKING-STORAGE FOR PPPPPPPP ***'.
[FSDDS0006] Level 01 data definitions must be preceded by a single-line containing only the
comment mark. It is optional to add a comment line after the variable name. Level 01 must appear
in column 8. Example:
*
**** LIST OF SWITCHES USED IN THIS PROGRAM ***********************
01 SW-SWITCHES.
[FSDDS0010] Level numbers must be lined-up in such a way that those having the same level start
in the same column.
[FSDDS0011] Two separation spaces must be left between the level number and the name of the
variable.
[FSDDS0012] The WORKING-STORAGE SECTION can only have the 01 levels listed below. Levels
can only appear in the event they contain subordinate variable names, and cannot have an
associated PICTURE. Inputs must appear in the order in which they are listed:
1. 01 CA-STTDAT
2. 01 VA-VARIABLES
3. 01 SW-SWITCHES
4. 01 CA-CONSTANTS
5. 01 TB-TABLES
6. 01 VA-OTHDTA
7. 01 CA-FINDAT
3 All standards referring to the alignment of COBOL sentence parts in a column must be understood as
follows. The key word or subclause indicated appears on the same line as the rest of the sentence and in the
column indicated if this is possible. If the alignment column appears occupied on the original line (or in the
transformation up to this point), the subclause appears on the next line and in the alignment column. The
standards only indicate those subclauses that are not aligned in the event that they can be rewritten
completely on the current line.
EXEC SQL
DECLARE <cursor> CURSOR [WITH HOLD] FOR
SELECT <field-1>,
<field-2>,
.........
<field-n>
FROM <table-1> <alias-1>,
<table-2> <alias-2>,
.........
<table-n> <alias-n>
WHERE <simple-condition-1>
AND <simple-condition-2>
OR <simple-condition-3>
AND <l-field-1> [NOT] IN
( SELECT <field-s>
FROM <table-s>
WHERE <simple-condition-s1>
AND <simple-condition-s2>
)
OR [NOT] EXISTS
( SELECT <field-s2>
FROM <table-s2>
WHERE <simple-condition-s3>
AND <simple-condition-s4>
)
GROUP BY <field-1>,
<field-2>,
.........
<field-n>
ORDER BY <field-1>,
<field-2>,
.........
<field-n>
HAVING <simple-condition-4>
AND <simple-condition-2>
OR <simple-condition-3>
FOR UPDATE OF
<field-1>,
<field-2>,
.........
<field-n>
END-EXEC.
*
******************************************************************
* PROCEDURE DIVISION *
******************************************************************
PROCEDURE DIVISION.
[FSPDC0002] All paragraph names must be preceded by a block comment with the following
format:
*
******************************************************************
*.PN <name-of-paragraph> *
*A.PR.S *
* TEXTO LIBRE DE DESCRIPCIÓN EXTENSA DEL PÁRRAFP............ . . *
* ...............................................................*
* .............................................................. *
* .............................................................. *
*A.PR.E *
*B.PR.S *
* PARAGRAPH LONG DESCRIPTION. . . . . . . . . . . . . .......... *
* .............................................................. *
* .............................................................. *
* .............................................................. *
*B.PR.E *
******************************************************************
<name-of-paragraph>.
In the event the block comment is not included in the original program, a blank block comment
with the previous structure will be inserted.
[FSPDC0003] All the comment lines will be deleted between the last sentence of the previous
paragraph up to the name of the paragraph, except for the following:
Those that are in a block comment, like the one previously described.
A single line containing only a comment character in column 7.
Those that are delimited by a block of marks. MC, .IE or .FE.
[FSPDS0001] Only one instruction (verb) can be written per line, although the instruction itself can
use as many lines as it needs.
[FSPDS0002] Paragraph and section names must start in column 8.
[FSPDS0003] The PROCEDURE DIVISION must always and exclusively invoke the paragraphs
START, PROCESS and END in this order, as described below (paragraph numbering, as can be
observed in FSPDS0005, will depend on the program in question).
PROCEDURE DIVISION.
*
PERFORM nnnn-START.
*
PERFORM nnnn-PROCESS [...].
*
PERFORM nnnn-END.
[FSPDS0004] paragraph names will have the structure nnnn-PPP....P, where nnnn is a consecutive,
sequential number, 0001 corresponding to the first, and PPP...P is the name of the paragraph itself,
starting with a letter. The sequential numbers must be increased one by one and maintain the order
in which the paragraphs have been written.
[FSPDS0005] The destinations of the verbs ADD, CLOSE, INITIALIZE, MOVE. OPEN, SET, STRING
and UNSTRING must be aligned on the left starting in column 44. The reserved word indicating the
start of the lit of destinations for these variables is aligned on the right of column 42. The origins for
the verb STRING are also aligned on the left of column 44.
[FSPDS0006] Imperative sentences must be aligned on the left along with other sentences of the
same level. The first imperative sentence for each paragraph will start in column 12.
[FSPDS0007] The verbs IF, EVALUATE, PERFORM, SEARCH, READ and WRITE, and in general
any verb admitting internal imperatives, introduce a new level, implying that imperative sentences
which form part of the sentence delimited by one of these verbs must be displayed two columns to
the right of the first column.
[FSPDS0008] The sentence IF must always be delimited by its respective END-IF. The latter must be
aligned on the left with the initial IF.
[FSPDS0009] The word THEN must not be specified in IF sentences.
[FSPDS0010] The word ELSE must be aligned on the left with its corresponding IF and appear on a
separate line.
[FSPDS0011] The sentence EVALUATE must always be delimited by its respective END-
EVALUATE. The latter must be aligned on the left with the initial EVALUATE.
[FSPDS0012] The word WHEN must appear two columns to the right of the start of the
corresponding EVALUATE or SEARCH. The imperative sentences that belong to this condition will
appear two columns more to the right and on different lines from the word WHEN.
[FSPDS0013] The sentence PERFORM must be delimited by its respective END-PERFORM, when
this construction contains imperative sentences. The latter must be aligned on the left with the
initial PERFORM.
[FSPDS0014] The sentence SEARCH must always be delimited by its respective END-SEARCH. The
latter must be aligned on the left with the initial SEARCH.
[FSPDS0015] The sentence READ must be delimited by its respective END-READ, when said
construction contains imperative sentences. The latter must be aligned on the left with the initial
READ.
[FSPDS0016] The sentence WRITE must be delimited by its respective END-WRITE, when said
construction contains imperative sentences. The latter must be aligned on the left with the initial
WRITE.
[FSPDS0017] A sentence can only finish with a period („.‟) when:
It is the last sentence in the paragraph.
It is an END-EXEC.
[FSPDS0019] For all sentences that accept conditions, the words OR and AND will end the current
line. The part that follows after an OR or an AND must appear on the next line, and be placed at
least one column to the right of the end of the word that introduces the condition (IF, WHEN, etc.).
[FSPDS0020] The comparative operators >, <, =, >= y <= cannot be used. Instead the operators
GREATER, LESS, EQUAL, GREATER OR EQUAL, LESS OR EQUAL will be used.
[FSPDS0021] The following reserved word sequences appear at the beginning of a new line and one
column to the right of the end of the verb to which they apply, except when they follow on
immediately after the verb, in which case, they can remain on the same line:
UNTIL
VARYING
WITH TEST AFTER
WITH TEST BEFORE
[NOT] AT END
[NOT] ON SIZE ERROR
[NOT] ON OVERFLOW
[NOT] ON EXCEPTION
KEY IS
[NOT] INVALID KEY
GIVING
REMAINDER
TALLYING
REPLACING
CONVERTING
INPUT
OUTPUT
I-O
EXTEND
DELIMITED BY
BEFORE ADVANCING
AFTER ADVANCING
[NOT] AT END-OF-PAGE
[FSPDS0022] CICS sentences will have the following general format:
EXEC CICS
<verb> <parm-1[(attr1)]>
<parm-2[(attr2)]>
.................
<parm-n[(attr2)]>
END-EXEC.
EXEC SQL
<verb> <subclause-1>
...............
<subclause-n>
END-EXEC.
[FSPDS0024] The SQL OPEN CURSOR sentence will have the following format:
EXEC SQL
OPEN <name-cursor>
[USING <host-variable>]
[DESCRIPTOR <descriptor-name>]
END-EXEC.
[FSPDS0025] The SQL CLOSE CURSOR sentence will have the following format:
EXEC SQL
CLOSE <name-cursor>
END-EXEC.
EXEC SQL
FETCH [FROM] <name-cursor>
INTO :<variable-1>,
:<variable-2>,
.............
.............
.............
:<variable-n>
[USING DESCRIPTOR <descriptor-name>]
END-EXEC.
EXEC SQL
SELECT <field-1>,
<field-2>,
.........
<field-n>
INTO :<variable-host-1>,
:<variable-host-2>,
.........
:<variable-host-n>
FROM <table-1> <alias-1>,
<table-2> <alias-2>,
.........
<table-n> <alias-n>
WHERE <simple-condition-1>
AND <simple-condition-2>
OR <simple-condition-3>
AND <l-field-1> [NOT] IN
( SELECT <field-s>
FROM <table-s>
WHERE <simple-condition-s1>
AND <simple-condition-s2>
)
OR [NOT] EXISTS
( SELECT <field-s2>
FROM <table-s2>
WHERE <simple-condition-s3>
AND <simple-condition-s4>
)
GROUP BY <field-1>,
<field-2>,
.........
<field-n>
ORDER BY <field-1>,
<field-2>,
.........
<field-n>
HAVING <simple-condition-4>
AND <simple-condition-2>
OR <simple-condition-3>
END-EXEC.
EXEC SQL
INSERT INTO <table-view>
(<field-1>,
<field-2>,
..........
<field-n>)
VALUES
(<value-1>,
<value-2>,
..........
<value-n>)
END-EXEC.
EXEC SQL
UPDATE <table-view>
SET <field-1> = :<value-1>,
<field-2> = :<value-2>,
......
......
<field-n> = :<value-n>
WHERE <simple-condition-1>
AND <simple-condition-2>
OR <simple-condition-3>
AND <l-field-1> [NOT] IN
( SELECT <field-s>
FROM <table-s>
WHERE <simple-condition-s1>
AND <simple-condition-s2>
)
OR [NOT] EXISTS
( SELECT <field-s2>
FROM <table-s2>
WHERE <simple-condition-s3>
AND <simple-condition-s4>
)
HAVING <simple-condition-4>
AND <simple-condition-2>
OR <simple-condition-3>
END-EXEC.
EXEC SQL
UPDATE <table-view>
SET <field-1> = :<value-1>,
<field-2> = :<value-2>,
......
......
<field-n> = :<value-n>
WHERE CURRENT OF <name-cursor>
END-EXEC.
[FSPDS0030] The format for the DELETE sentence will be one of the following:
EXEC SQL
DELETE
FROM <name-table-view>
WHERE <simple-condition-1>
AND <simple-condition-2>
OR <simple-condition-3>
AND <l-field-1> [NOT] IN
( SELECT <field-s>
FROM <table-s>
WHERE <simple-condition-s1>
AND <simple-condition-s2>
)
OR [NOT] EXISTS
( SELECT <field-s2>
FROM <table-s2>
WHERE <simple-condition-s3>
AND <simple-condition-s4>
)
HAVING <simple-condition-4>
AND <simple-condition-2>
OR <simple-condition-3>
END-EXEC.
EXEC SQL
DELETE
FROM <name-table-view>
WHERE CURRENT OF <name-cursor>
END-EXEC.
3. COPYBOOKS
The following standards are applied to all the COPYBOOKS:
FSADC0001
FSADC0002
FSADC0003
FSEDC0001: Prior to the code, but not in the IDENTIFICATION.
FSEDC0002: Prior to the code, but not in the IDENTIFICATION.
FSDDS0006
FSDDS0007
FSDDS0008
FSDDS0009
FSDDS0010
FSDDS0011
FSDDS0014
FSDDS0015
FSDDS0016
FSDDS0017
FSDDS0018
FSDDS0019
FSDDS0020
FSDDS0021
FSDDS0022
FSDDS0023
FSDDS0024
FSDDS0025
In general, in addition to the above, the following standards are defined for COPYBOOKS:
[FSCSC0001] Data definitions should be preceded by block comments with the following structure:
* CCCCCCCC: DDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDDD *
* DDDDDDDDDDDDDDDDDDDDDDDDD *
******************************************************************
Where CCCCCCCC is the name of the COPYBOOK and DDD......DDD refers to its short
description. These data will be automatically extracted from the ART by the formatting tool.
4. DCLGEN
In general, all the standards defined for COPYBOOKS are applicable to DCLGENS with the sole
exception of the FSCSC0001 standard, in which the CCCCCCCC field should be the name of the
DCLGEN instead of the name of the COPYBOOK.
Furthermore, the following exclusive DCLGEN standards are defined:
[FSDSS0001] The COBOL declaration on the table must be defined on level 01. The variable name
entered by the first declaration on level 01 will be: DCL<table-name> o DCL<view-name>, as
applicable.
[FSDSS0002] The sentence DECLARE TABLE must have the following format:
EXEC SQL DECLARE <name-table-view> TABLE
( <column-table-1> <column-type-1>,
<column-table-2> <column-type-2>,
................. ................,
................. ................,
................. ................,
................. ................,
<column-table-n> <column-type-n>
) END-EXEC.
Alnova Financial Solutions is a registered trademark owned by Alnova Technologies Corporation, S.L.