>> Rodney Roberts IS & Education Professional Homepage   >> Programming Tutorials And Downloads







Science makes it known,
Engineering makes it work,
Art makes it beautiful.




 

This is a non-commercial tutorial page to be used for educational purposes only
It is meant to be an outline of COBOL, highlighting the programming language. For in-depth study, refer to the appropriate manuals.



Structure and Elements of a COBOL Program

COBOL Columns

Fixed Format:
 Sequence number area   Line Number, if blank, source file is unnumbered; see COBOL Line Numbering Utility for more information 
 Column 7  Use an asterisk in this column for a comment line 
 Area A  DIVISION, SECTION, and PARAGRAPH start in this area.
 Area B  SENTENCEs start in this area.
 Column 73 - 80  largely ignored


    A COBOL program is structured by DIVISION, SECTION, PARAGRAPH, SENTENCE, STATEMENT, CLAUSE:
  • A DIVISION (begins in column 8) may have one or more SECTIONs
  • A SECTION (begins in column 8) may have one or more PARAGRAPHs
  • A PARAGRAPH (begins in column 8) may have one or more SENTENCEs (begins in column 12)
  • A SENTENCE (begins in column 12) has one or more STATEMENTs; SENTENCEs end with a period
  • A STATEMENT may have one or more CLAUSEs
  • END PROGRAM header specifies the end of a program.

A DIVISION may consist of PARAGRAPHs and SENTENCEs, or even simply SENTENCEs.


A COBOL program has four divisions (as will be seen, many compilers have their own unique extensions):
  1. IDENTIFICATION DIVISION
    Must be the first DIVISION.
    Specifies the name of the program; except for PROGRAM-ID paragraph, these paragraphs are obsolete language elements used for writing comment lines.
    Does not have any SECTIONs, only PARAGRAPHs.
    IDENTIFICATION DIVISION example

  2. ENVIRONMENT DIVISION
    Must be the second DIVISION. Tends to be very platform specific.
    Consist of two sections - the CONFIGURATION SECTION (SOURCE-COMPUTER and OBJECT-COMPUTER paragraphs - name the computer hardware; SPECIAL-NAMES paragraph - assign programmer-defined special names) and the INPUT-OUTPUT SECTION (consisting of FILE-CONTROL and I-O CONTROL paragraphs, specifies what files are used and how they are accessed with which physical I/O devices)
    ENVIRONMENT DIVISION example
    (see USPSFILE.COB, used in AMSWIN.COB, for an example of File Select Assign statement. Placed in ENVIRONMENT DIVISION, INPUT-OUTPUT SECTION, FILE-CONTROL.)

  3. DATA DIVISION
    Must be the third DIVISION.
    Commonly used sections are the FILE SECTION (defines file record layouts), WORKING-STORAGE SECTION (used primarily for 77 Level Items), LINKAGE SECTION (subprograms only), and REPORT SECTION. These sections define the data used by the program.
    DATA DIVISION with vendor extensions example
    (Shaded areas indicates FUJITSU COBOL85 extension)

    (see AMSWIN.COB, for examples of FILE SECTION, WORKING-STORAGE SECTION, and CONSTANT SECTION; see USPSLIST.COB and OUTREC.COB for examples of the FILE SECTION's file description (FD) entry.)

    The FILE SECTION's sort file description (SD) entry is structured as shown:
    sort file description
    A fully populated
    [; RECORD    CONTAINS [<integer-1>   TO]   <integer-2> CHARACTERS]
    <clause> in the FD or SD indicates variable length records


     REPORT SECTION
     Report Description (RD)

     RD <ReportName> is linked to a
        FD   <file-name>

        via the FD's
        REPORT IS <ReportName>
        <clause>



     Used in printing a report to a printer. 
    Report Description (RD)

    Records

    A file contains 1 or more records. A record, a collection of related data, is a top-level Group item and may contain lower level Group items in addition to Elementary items (fields), and has a level number of 01
       01  <record-name>.
    Not all records are associated with files.  Records may also be used in WORKING-STORAGE SECTION and LINKAGE SECTION.

    May contain IS GLOBAL [IS EXTERNAL] clause(s).

    IS GLOBAL  : data is available to all programs in program unit (basicaly, a source code file compiled into a single .obj, .lib, and/or .dll file)

    IS EXTERNAL : data is available to all programs in application; must be declared exactly the same in each program accessing the data; recommend using COPY / INCLUDE files.

    See ADRBRKDN.COB for an example of a program unit consisting of four subprograms (nested programs), IS GLOBAL clause, and IS GLOBAL IS EXTERNAL clauses (INCLUDE files COMDATA.COB and STADDR.COB)
    COBOL Listing

    Group items:
       <NN>  <group-name>.
       where <NN> is a two digit level number
    Any data item that can be subdivided into smaller data item (either another Group item or an Elementary item)
    Top level Group item has a level number of 01 (record) and begins in column 8
       Example:
        10  UPM-HEADER.
    UPM-HEADER is associated with a higher level Group item

    Elementary items (fields):
       individual data item
       <NN>  <field-name>     <picture-clause>.
       again, <NN> is the level number; this number is greater than its associated group item level number (if any)
       <field-name> is the variable name
       <picture-clause> combines data type, size, and format
     <picture-clause>   data type, size, format 
     PIC S9(4) COMP-5   signed 2 byte Integer (binary data) 
     PIC 9(4) COMP-5   unsigned 2 byte Integer (binary data) 
     PIC S9(9) COMP-5   signed 4 byte Integer (binary data) 
     S9(4)V9(3) PACKED-DECIMAL   signed Packed Decimal (binary data); V indicates an implicit decimal point; HP COBOL extends 
     this as COMP-3;
    stores two decimal digits in one byte
     COMP-1   4 byte IEEE floating point (binary data) 
     PIC 9(<N>)   Numeric edited data (ASCII, EBCDIC, etc.) of N digits 
     PIC $9(<N>).9(<D>)   Numeric edited data (ASCII, EBCDIC, etc.) of width N + D digits + 2 (for $ symbol and decimal point) 
     PIC X(<N>)   Alphanumeric data (ASCII, EBCDIC, etc.) of N characters 
       Example:
         15  UML-ID                    PIC X(006).
    UML-ID is associated with a Group item
    77 level items are not a part of any group item


    Arrays:
       commonly referred to as tables
       use an OCCURS CLAUSE in either a Group item or Elementary item
       <NN>  <group-name>    OCCURS  <M> TIMES.
          or
       <NN>  <field-name>      OCCURS  <M> TIMES    <picture-clause>.
       <NN> is the level number
       <M> is an Integer - number of elements in array.

       Examples:
       1. two Group item OCCURS CLAUSEs to produce a 2 dimensional array (or matrix):
    000130     05  IC-POINT-ARRAY-REDEF  REDEFINES  IC-POINT-ARRAY.
    000140         10  ICP-ROW           OCCURS  30 TIMES.
    000150             15  ICP-COL       OCCURS  10 TIMES.
    000160                 20  IC-POINT  PIC S9(4)  COMP-5.
         
       2. Elementary item OCCURS CLAUSE to produce a 1 dimensional array (or vector):
    000310             15  UPM-H2-BYT      OCCURS    31 TIMES
    000320                                           PIC X(001).
         
    Condition names:
       <field-name> may have a condition name (prefixed with 88)
       Condition name can be used in IF statement
       Example:
       15  UPM-RIB1-UML-ID          PIC X(006).
            88  VALID-RIB1-FILE
                  VALUE "ECRWSS", "ECRLOT".

       Condition name in IF statement example:
       IF VALID-RIB1-FILE THEN
       is equivalent to
       IF (UPM-RIB1-UML-ID = "ECRWSS")
         OR (UPM-RIB1-UML-ID = "ECRLOT") THEN

  4. PROCEDURE DIVISION
    Must be the fourth DIVISION.
    Contains the executable statements (sentences), can be grouped into SECTIONs containing PARAGRAPHs. Last statement is the END PROGRAM header.
    PROCEDURE DIVISION formats:


    PROCEDURE DIVISION 3 formats
    [Format 3] example:
    PROCEDURE DIVISION with DECLARATIVEs example
    COBOL subprogram PROCEDURE DIVISION
    Subprogram Procedure Division, Parameter List, Calling model
    data-names listed in the USING CLAUSE must be defined in the LINKAGE SECTION
    (Shaded area indicates FUJITSU COBOL85 Windows extension)
    (corresponds to Object Pascal's
    procedure <procedure-name> [(<formal-parameter-list>)]; <call-model>;)

    <section-name> SECTION:
       begins in column 8
       composed of one or more <paragraph-name>s, extends to the next <section-name> or the end of the program
       Commonly used for SORT and MERGE Procedures
       <operand> for PERFORM

    <paragraph-name>:
       begins in column 8
       <operand> for PERFORM, GO TO
       Example:
       0500-INIT-AMSWIN.

    <sentence>:
       begins in column 12
       comprised of <executable statement> [,<operand-1> <clause> <operand-2> [,[<clause>] <operand-3>][, ...]]
       <operand-1> is a <group-name>, <field-name>, or <literal> (alphabetic or numeric), depending on the <executable statement>
       again, <operand-2> [, <operand-3>] is (are) a <group-name>, <field-name> or <literal> (alphabetic or numeric), depending on
       the <executable statement>

       <executable statement> usually referred to as <verb>
     <executable statement>   Description - see your compiler's documentation for exact format 
     ACCEPT   Input Operation - ACCEPT <group-name> or <field-name> [FROM <device>]
     ADD   Add two or more <field-name> or <literal> 
     ALTER   Replaces <operand> of GOTO statement 
     CALL   Calls Subprogram 
     CALL <subprogram-name> [USING <operand-1> [, <operand-2> [, ...]]] 
     (See COBOL calling FORTRAN for a CALL verb example) 
     CANCEL   Restores COBOL subprogram to its initial state; used in calling program 
     CLOSE   Input/Output Operation - Terminate FILE Processing 
     COMPUTE   arithmetic operators : (-) (negation), +, -, * (multiplication), / (division), ** (exponentiation to an Integer power) 
     COMPUTE <field-name> = <arithmetic-expression> 
     has several <clause>s 
     CONTINUE   No executable statement is present; no-operation statement; often used in IF statements 
     COPY   Usually compiler directive, not statement; 
     copies text into COBOL source code from a library;
     may be implemented as INCLUDE
     DELETE   Output Operation - Logically removes a record from a relative or indexed file - record is flagged as deleted 
     but physically remains. 
     DISPLAY   Output Operation - output low volume data to console, terminal, or printer 
     DIVIDE   Divide one <operand> by (or into) another; has multiple formats and <clause>s 
     ENTER   Usually compiler directive, not statement; on some compilers, can be comment; on others, allows COBOL 
     program to call non-COBOL subprograms; not applicable in most compilers 
     ENTER <programming-language-name> <subprogram-name> [USING <operand-1> [, ...]] 
     ENTRY   HP COBOL and FUJITSU COBOL85 extension; secondary entry point for the called program; 
     same concept as FORTRAN's ENTRY 
     EVALUATE   Multi-condition case construct 
     EXAMINE   HP COBOL extension; replaces or counts the number of occurrences of <literal> in <operand>; 
     <operand> may be either <group-name> or <field-name> 
     EXCLUSIVE   HP COBOL extension; Input/Output Operation - provides a method for locking a file opened for SHARED 
     access 
     EXIT   Only statement in <paragraph-name-n> of PERFORM <paragraph-name-1> THRU <paragraph-name-n>; 
     exits the procedure, and returns control implicitly to the statement following the PERFORM statement 
     EXIT PERFORM   FUJITSU COBOL85 extension; specifies the exit of an in-line PERFORM statement 
     EXIT PROGRAM   Return to calling program from the called subprogram 
     GENERATE   Report Writing - Writes a report according to a RD (Report Description) entry 
     GOBACK   HP COBOL II extension; logical end of subprogram 
     GO TO   GO TO <operand>; transfer of control within program 
     IF   Used to test whether a condition is true or false, can contain processing for true condition, 
     false condition, or both 
     INITIALIZE   Sets predefined data fields (<group-name>s and/or <field-name>s) to predefined values 
     INITIATE   Report Writer - Initiates a report writing process 
     INSPECT   replaces and/or counts the number of occurrences of <literal> in <operand> 
     <operand> may be either <group-name> or <field-name> 
     MERGE   Combine two or more identically structured files into one file. Has elements common with SORTing  
     (MERGE work file defined in a sort file description (SD) entry, RETURN statement, OUTPUT PROCEDURE)
     MOVE   MOVE (actually copies) data to <group-name> or <field-name>; see example below  
     MULTIPLY   Multiply <operand-1> by <operand-2>; has multiple formats and <clause>s 
     NOTE   Usually compiler directive, not statement; programmer comments 
     OPEN   Input/Output Operation - Initiate FILE Processing 
     PERFORM   PERFORM <section-name> or PERFORM <paragraph-name>; the PERFORM <operand> is called the 
     procedure name. A Procedure is simply a group of <executable statement>s executed by the PERFORM 
     statement; Transfers control explicitly, returns control implicitly; 
     Similar idea as Dartmouth Basic's GOSUB statement 
     READ   Input Operation - READ <file-name> 
     RELEASE   SORT Operation - "Writes" record to sort-file prior to sorting 
     RETURN   SORT/MERGE Operations - "Reads" record from sort/merge-file after file is sorted or merged 
     REWRITE   Output Operation - Logically replaces an existing record in a sequential, relative, random, or indexed 
     file; (variable length records not allowed) 
     SEARCH   Used to search a table for an element satisfying a specified condition; 
     has multiple formats and <clause>s 
     SEEK   HP COBOL 85 extension; Input Operation - used with relative files (dynamic or random access) and 
     random access files; initiates access prior to a key based READ  
     SET   Multiple uses : set table handling indices to a <field-name> or <literal> (numeric) initial value; set index 
     increment/decrement; alter status of external switches; alter value of conditional variables 
     SORT   Sort a file; format of a simple SORT verb: 
    SORT verb
     START   Input Operation - logical positioning within a relative or indexed file (sequential or dynamic access mode) 
     for subsequent record retrieval 
     STOP   STOP RUN terminates program execution; STOP <literal> - halts program execution and displays <literal> 
     STRING   Partial/complete concatenation of two or more alphanumeric <operand>s 
     SUBTRACT   Subtract one <operand> from another; has multiple formats and <clause>s 
     For the ADD, DIVIDE, MULTIPLY, and SUBTRACT verbs, for the format being used, verify which <operand> 
     the result will be stored in.
     
     SUPPRESS   Report Writer - suppresses the report group presentation 
     TERMINATE   Report Writer - terminates the report processing 
     UN-EXCLUSIVE   HP COBOL 85 extension; Input/Output Operation - unlocks a file previously locked by an EXCLUSIVE 
     command 
     UNLOCK   Input/Output Operation - cancels all locks for the specified file 
     UNSTRING   Divides data in a sending <field-name> and places segments of the data in multiple receiving <field-name>s 
     USE   Specifies procedures for : Input/Output error handling; user label processing; debugging 
     WRITE   Output Operation - WRITE <record-name> 

       Example:
    000790     MOVE  ZERO  TO USPS-CUR-REC-NUM
    000800                    USPS-CYCL-STRT-REC-NUM
    000810                    EAS-CUR-REC-NUM
    000820                    EAS-CYCL-STRT-REC-NUM
    000830                    ERR-CODE
    000840                    ERR-MSG-STYLE
    000850                    RTRN-INT
    000860                    Z4GP-RETCC.
         


Sources: COBOL85 User's Guide 3.0 © 1997 Fujitsu Limited; COBOL85 Reference Manual © 1997 Fujitsu Limited;
COBOL for Small and Medium-sized Computers © 1976; HP COBOL II/V Reference Manual © 1989; COBOL STUDY MATERIAL;
COBOL Tutorial: (Based on M.G. University - BCA Programme); The COBOL Report Writer;
Bristol Community College

Any and all © copyrights, ™ trademarks, or other intellectual property (IP) mentioned/used here are the property of their respective owners.  No infringement is intended.
If you suspect infringement occurred, please contact me at hp3000guru@yahoo.com, fully describing.

Page best viewed with Mozilla Firefox 3.6.13 (or higher) and Safari 5.1.7 - Internet Explorer may not display or link correctly. Avoid Smart Applications Speed Browser.

Website is supported on DESKTOP platforms only.

Web hosting provided by  
Award Space Web Hosting ,   Free Web Hosting ,  & X10hosting Free Web Hosting.

>> Rodney Roberts IS & Education Professional Homepage   >> Programming Tutorials And Downloads