----------------------------------------------------------------------------------------------------------

Mainframe COBOL Reference available with ISPF/TSO

        On the main menu, there is a library reference option called Bookmanager

BOOKMANAGER option L0

        Type 'L0' at the main menu and press <enter>.

        There will be a listing of library resources. One of the sources is the COBOL bookshelf.

        Place your cursor at the line which has IGYMS002 and press <enter>.

__ IGYMS002 COBOL for MVS & VM Bookshelf

        There next will be a listing of COBOL resources. Select the COBOL Language reference by placing your cursor on the line which has  IGYLR102 and press <enter>.

__ IGYLR102 COBOL Language Reference

        Browse the reference

------------------------------------------------------------------------------------------------------------

HIERARCHICAL Structure within the DIVISIONS of a COBOL Program

IDENTIFICATION    ENVIRONMENT    DATA         PROCEDURE

                                      Sections                     Sections         Sections

Paragraphs                   Paragraphs                                       Paragraphs

Entries                          Entries                       Entries           Sentences

Clauses                         Clauses                      Clauses         Statements

                                                                                                Phrases

- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -

Definitions

        Clause -- specifies an attribute of an entry.
        Entry -- is a series of clauses ending with a period.
        Statement -- a COBOL verb and its operands
        Sentence -- one or more statements ending with a period.

------------------------------------------------------------------------------------------------------------

DIVISIONS                                       SECTIONS                           PARAGRAPHS

IDENTIFICATION                                                                          PROGRAM-ID
                                                                                                           AUTHOR
                                                                                                           INSTALLATION
                                                                                                           DATE-WRITTEN
                                                                                                           SECURITY

ENVIRONMENT                             CONFIGURATION             SOURCE-COMPUTER
                                                                                                           OBJECT-COMPUTER
                                                                                                           SPECIAL-NAMES

                                                            INPUT-OUTPUT                  FILE-CONTROL

DATA                                                 FILE
                                                            WORKING-STORAGE

PROCEDURE                                    user section names               user paragraph names

-----------------------------------------------------------------------------------------------------------

Rules for forming paragraph-names.  The same rules as required for data-names
except paragraph-names may have all digits.

1. 1-30 characters.
2. letters, digits and hyphens (-) only.
3. no embedded blanks.
4. do not began or end with a hyphen (-)

-----------------------------------------------------------------------------------------------------------

Basic PERFORM paragraph-1 through paragraph-2.

100-a PERFORM 200-c THRU 600-x

200-c ---------------------------|
                                 |
300-d PERFORM 400-e THRU 500-k   |
                                 |
400-e ----------------|          |
                      |          |
500-k ----------------|          |
                                 |
600-x ---------------------------|

------------------------------------------------------------------------------------------------------------

Where is a period required?

        At the end of the word DIVISION
        At the end of the word SECTION
        At the end of paragraph names coded in Area A
        To denote the end of a sentence
        To denote the end of an entry
        After the last statement in each paragraph

------------------------------------------------------------------------------------------------------------
WORKING-STORAGE SECTION

A place to reserve storage for data that is not part of the program's input or output.
This area contains fields that are used as temporary storage while the program is executing.

Some temporary storage variables include:
        switches,
        flags,
        fields containing textual comments,
        fields to accumulate numeric totals.

------------------------------------------------------------------------------------------------------------
Level 77 - An Area A label that indicates Independent Data Items

This data item is not related to any other data item.

        77     EOF-FLAG                     PIC XXX VALUE 'NO'.
        77     DISPLAY-HI                    PIC X(15) VALUE ' HELLO WORLD '.
        77     SUMMARY-FIELD         PIC 9(9) VALUE ZEROS.

------------------------------------------------------------------------------------------------------------
Level 01 --     An Area A label that can also represent independent data items
                        if it contains a PIC clause.

        01     NEW-FLAG                     PIC XXX         VALUE 'YES'.
        01     DISPLAY-TA-TA             PIC X(15)        VALUE ' PROGRAM ENDED'.
        01     SUB-TOTAL-FIELD        PIC 9(9)          VALUE ZEROS.

------------------------------------------------------------------------------------------------------------
Level 01 -- An Area A label that usually represents data items that are
                    related or grouped together.

                    Should not contain a PIC clause.

        01     NAME-FIELD.
                 05     FIRST-NAME              PIC X(10) VALUE 'JOHN'.
                 05     MIDDLE-INITIAL         PIC X VALUE 'H'.
                 05     LAST-NAME               PIC X(20) VALUE 'PETLICKI'.

Note:
NAME-FIELD is a group data item. There is no PIC clause.
FIRST-NAME is an elementary data item There is a PIC clause

------------------------------------------------------------------------------------------------------------
Data items with Level numbers 02 through 50

    are related hierarchically to the previous lower level number
    are started in Area B
    can be group data items (02 thru 49) or elementary data items(02 thru 50).

01  NAME-FIELD.
      05     LEGAL-NAME.
                10     FIRST-NAME             PIC X(10) VALUE 'JOHN'.
                10     MIDDLE-INITIAL        PIC X VALUE 'H'.
                10     LAST-NAME              PIC X(20) VALUE 'PETLICKI'.
      05     ALIAS                                   PIC X(10) VALUE 'GURU'.
------------------------------------------------------------------------------------------------------------
To get input from a file, a COBOL program requires:

1)         A SELECT statement assigning the COBOL file name to the external name.
            This is done in the FILE-CONTROL paragraph of the
            INPUT-OUTPUT SECTION.

ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
        SELECT INFILE ASSIGN TO INSTUFF.
                          |                                          |
                          |                                          |
                          |            This is an "external" name in your program. JCL uses exactly that
                          |            same name to connect your program to the input file.
                          |            //INSTUFF DD DSN=CSCSMS.CSC.DATUM(DATA2),DISP=SHR
                          |
                          |
                        This is the File name used for all references within the COBOL program.

2) FD INFILE -- a file description entry in the FILE SECTION.

3) File access references in the PROCEDURE DIVISION

        OPEN INPUT INFILE

                    - - -

        READ INFILE AT END MOVE 'YES' TO SWITCH.

                    - - -

        CLOSE INFILE.

-----------------------------------------------------------------------------------------------------------

FD - File Description -- A file description requires information about the file's characteristics:

Are the records singular or grouped together (BLOCKed)?
Should the system use its own resources to find out about the blocking?
How big is a record?
Are the records all the same size?
Are there Label records that describe the file?
What are the names of the records that come in with this file?

------------------------------------------------------------------------------------------------------------
FD from PROG2

DATA DIVISION.
FILE SECTION.
FD INFILE
    BLOCK CONTAINS 0 RECORDS
    RECORD CONTAINS 80 CHARACTERS
    RECORDING MODE IS F
    LABEL RECORDS ARE STANDARD
    DATA RECORD IS IN-REC.

OR could you use the shorter version of?

DATA DIVISION.
FILE SECTION.
FD  INFILE.
 

- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
BLOCK CONTAINS 0 RECORDS (Optional for COBOL 85)

Tells the system to go find out for itself whether the records are
grouped or not. This statement is recommended. The programmer
reduces the flexibility of the program and might be wrong if they state
how many records are in a block.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
RECORD CONTAINS 80 CHARACTERS (Optional)

Tells the system how big the record is in terms of bytes. This number
Is compared to the record description for consistency checking by the compiler.

- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
RECORDING MODE IS F (Optional comment)

Old method of telling the system that all the records are the same size.
This is no longer required since the system could find this out for itself.

- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
LABEL RECORDS ARE STANDARD (Optional for COBOL 85)

Tells the system that this is a typical file that has system created labels
preceding and following the file data itself. Since labels exist, the system
can use them for file characteristics.

- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
DATA RECORD IS IN-REC. (Optional)

Tells the system the names of the records that belong in the file.

------------------------------------------------------------------------------------------------------------
01 Level -- Record Description Entry.

Input record of PROG2

        01 IN-REC.
            05 NAME-IN PIC X(20).
            05 SALARY PIC 9(3)V9(2).
            05 PIC X.
            05 BONUS PIC 9(3)V99.
            05 PIC X(49).

The 05 areas without any data names are used to account for unused spaces that exist in the input record.

Older versions of COBOL would require the use of the word FILLER as a name and the record would appear as follows.

        01 IN-REC.
            05 NAME-IN PIC X(20).
            05 SALARY PIC 9(3)V9(2).
            05 FILLER PIC X.
            05 BONUS PIC 9(3)V99.
                        05 FILLER PIC X(49).

All data names must be unique, except the word FILLER in the DATA DIVISION.

------------------------------------------------------------------------------------------------------------

PIC X            That portion of the record can contain one byte of any character.

PIC 9            This portion of the record should contain a digit in the range of 0 to 9.

PIC 9V9        The V does not represent a storage position. The V is used to 'logically'
                        parse the number into integer and decimal portions. Numbers that exist
                        before the V are the whole part of the number, while numbers that exist
                        after the V are the decimal portion.

------------------------------------------------------------------------------------------------------------
The OPEN Statement.

        Before a file could be read, it must be OPENed for input.

    OPEN INPUT INFILE.

            While the file is OPENed, do not open it again.
            Do not try to READ from the file before it is OPENed.
            Do not try to CLOSE the file if it is not OPEN.

------------------------------------------------------------------------------------------------------------
The READ Statement

            Before the data in a file could be processed it should be READ.

        READ INFILE AT END MOVE 'YES' TO SWITCH.

            Do not try to READ a file after you reach the end.

------------------------------------------------------------------------------------------------------------
The CLOSE Statement

            When the end of a file is reached, it is time to close it.

        CLOSE INFILE.

            AFTER the program CLOSEs a file
            Do not try to READ from it unless you OPEN it again.
            Do not CLOSE the file unless it is OPEN.
 
------------------------------------------------------------------------------------------------------------
To print output, a COBOL program requires:

1) A SELECT statement assigning the COBOL file name to the external name.This is done in the FILE-CONTROL paragraph of the INPUT-OUTPUT SECTION.

ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT OUTFILE ASSIGN TO OUTSTUFF.
                     |                                          |
                     |                                          |
                     |                     This is an "external" name in your
                     |                     program.  JCL uses exactly that
                     |                    same name to connect your program
                     |                    to the input file.
                     |                     //OUTSTUFF DD SYSOUT=*
                     |
                     |
                     |
This is the File name used for all references within the COBOL program.

2) FD  OUTFILE  -- a file description entry in the FILE SECTION.

3) File access references in the PROCEDURE DIVISION

        OPEN OUTPUT OUTFILE
        - - -
        WRITE OUT-REC AFTER 2
        - - -
        CLOSE OUTFILE.
 

------------------------------------------------------------------------------------------------------------
FD - File Description --  Since the output did not exist until this program creates it, the programmer is responsible for determining some attributes about the file being created:

         Are the records singular or grouped together (BLOCKed)?
         How big is a record?
         Are the records all the same size?
         Are there Label records that describe the file?
-------------------------------------------------------------------------------------
FD for output from PROG2

DATA DIVISION.
FILE SECTION.
- - -
FD  OUTFILE
    BLOCK CONTAINS 0 RECORDS
    RECORD CONTAINS 132 CHARACTERS
    RECORDING MODE IS F
    LABEL RECORDS ARE STANDARD
    DATA RECORD IS OUT-REC.

OR the more abbreviated?

 FD  OUTFILE.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
BLOCK CONTAINS 0 RECORDS   (Optional for COBOL 85)

Tells the system that you will use JCL to determine the block size. This statement is recommended.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
RECORD CONTAINS 132 CHARACTERS  (Optional)
 
 Tells the system how big the record is in terms of bytes.  Many programs use
131, 132 or 133 print positions when sending output that is to be printed.
This number Is compared to the record description for consistency checking by the compiler.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
RECORDING MODE IS F   (Optional comment)

Method of telling the system that all the records are the same size.

- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
LABEL RECORDS ARE STANDARD  (Optional for COBOL 85)
 
Tells the system that this is a typical file that has system created labels preceding and following the file data itself.  Since labels exist, the system can use them for file characteristics.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
DATA RECORD IS OUT-REC.        (Optional)

Tells the system the names of the records that belong in the file.

--------------------------------------------------------------------------------------------
01 Level -- Record Description Entry.

Output record of PROG2

01  OUT-REC.
    05               PIC X.
    05  NAME-OUT     PIC X(20).
    05               PIC X(10).
    05  NEW-GROSS    PIC $$,$$$.99.
    05               PIC X(92).

The 05 areas without any data names are used to account for unused spaces existing in the input record.

Older versions of COBOL would require the use of the word FILLER as a name and the record would appear as follows.

01  OUT-REC.
    05  FILLER        PIC X.
    05  NAME-OUT      PIC X(20).
    05  FILLER        PIC X(10).
    05  NEW-GROSS     PIC $$,$$$.99.
    05  FILLER        PIC X(92).

All data names must be unique, except the word FILLER in the DATA DIVISION.

------------------------------------------------------------------------------------------------------------
PIC $$,$$$.99.

Commas and decimals points would be a waste of space in a computer, so the picture of a number may be 9(4)V99 which would require 6 storage locations.

People have an easier time reading printed dollars if they are formatted with the dollar sign and have commas and decimals.  Each comma and decimal requires a print location. In this case, printing a dollar value from a 6 positions storage location, requires 9 positions for output. WHY?

------------------------------------------------------------------------------------------------
The OPEN Statement.

 Before a file could be written, it must be OPENed for output.

 OPEN OUTPUT OUTFILE.

 While the file is OPENed, do not open it again.

------------------------------------------------------------------------------------------------------------
The WRITE Statement
 
 Before the data in a file could be processed it should be READ.

WRITE OUT-REC AFTER 2.

 Do not try to WRITE to the file before it is OPENed.

 AFTER 2  is a signal to print after skipping a line.
 
The default is the print AFTER 1.
The system uses the 1st byte of the output record to signal the printer whether 1 or more lines are to be skipped.
 
------------------------------------------------------------------------------------------------------------
The CLOSE Statement

 When you are finished writing to a file, close it.

             CLOSE OUTFILE.

AFTER the program CLOSEs a file
         Do not try to WRITE to it.
         Do not CLOSE the file unless it is OPEN.

------------------------------------------------------------------------------------------------------------
Put something into the fields before writing output.

Per the example of PROG2, data can be MOVEd or calculated into fields of the output record before the record is written.

MOVE SPACES TO OUT-REC.
MOVE NAME-IN TO NAME-OUT.
COMPUTE NEW-GROSS = SALARY + BONUS
WRITE OUT-REC AFTER 2.
------------------------------------------------------------------------------------------------------------