Program Structure


COBOL programming language has its program structure, like other programming languages, and it should apply to every program written in the COBOL language.

The COBOL program structure is a top-to-bottom hierarchical design and it consists of Divisions, Sections, Paragraphs, Sentences, Statements, and Character strings.

COBOL Program Structure

Let us discuss from the smaller element to the larger one for a better understanding.

Character Set -


The character set refers to the collection of valid characters that can be used within the language. It is used to define literals, variables, and other identifiers in a COBOL program. We have discussed about this verb in the previous topic.

Character Strings -


Character strings refer to sequences of characters that consist of letters, digits, spaces, and special characters. These are often used as literals, variables, keywords, etc. For example - WS-VAR, ZEROES, MOVE, IF, DISPLAY, etc.

Statements -


  • Statements are specific instructions used within the PROCEDURE DIVISION to define the operations that the program will perform on data. Statements decide the program's flow, data manipulations, input/output operations, and many more.
  • The statement is a combination of COBOL keywords and operands, and it should have at least one COBOL keyword.
  • All statements should be coded in Area-B in the PROCEDURE DIVISION and is marked with a period(.) at the end.
  • COBOL statements are divided into four types based on their usage, and those are -
    • Imperative Statements
    • Conditional Statements
    • Delimited scope Statements
    • Compiler directing Statements

For example - Two statements in a program.

----+----1----+----2----+----3----+----4----+----5
       IDENTIFICATION DIVISION.
       PROGRAM-ID. PROGSTRU.
	   AUTHOR. MTH.

       PROCEDURE DIVISION.
       1000-SEC1 SECTION.
       1000-PARA.
           DISPLAY "Hello World".      --> Statement1    
           DISPLAY "Welcome to MTH".   --> Statement2          
           STOP RUN.

Sentences -


  • A sentence is a sequence of one or more statements ended by a period (.) within the PROCEDURE DIVISION.
  • Sentences provide a way to group related statements together, and the period indicates the end of that particular logical sequence.
  • If the first statement ends with a period, it is considered a statement but not a sentence.
  • All sentences should be coded in Area-B in the PROCEDURE DIVISION.

For example - A sentence with two statements.

----+----1----+----2----+----3----+----4----+----5
       IDENTIFICATION DIVISION.
       PROGRAM-ID. PROGSTRU.
	   AUTHOR. MTH.

       PROCEDURE DIVISION.
       1000-SEC1 SECTION.
       1000-PARA.
           DISPLAY "Hello World"       --]   
           DISPLAY "Welcome to MTH".   --]--> Sentence          
           STOP RUN.

Paragraphs -


  • A paragraph is a block of code within the PROCEDURE DIVISION consisting of one or more sentences. It represents a specific unit of logic or functionality and can be directly called or performed by other parts of the program.
  • A paragraph begins with the paragraph name and ends when any of the following is met -
    • The scope terminator of the same paragraph.
    • Starting of another paragraph.
    • Beginning of the new section.
    • The program ends.
  • All paragraph names should code in Area-A and the logical code in it should code in Area-B.

For example - A paragraph in the program.

----+----1----+----2----+----3----+----4----+----5
       IDENTIFICATION DIVISION.
       PROGRAM-ID. PROGSTRU.
	   AUTHOR. MTH.

       PROCEDURE DIVISION.
       1000-SEC1 SECTION.
       1000-PARA.                --> Paragraph
           DISPLAY "Hello World" 
           DISPLAY "Welcome to MTH".         
           STOP RUN.

Sections -


  • A section is a collection of one or more related paragraphs within the PROCEDURE DIVISION.
  • Sections are coded by a name followed by the keyword SECTION. It ends at another section starting or ending the program.
  • When the section can be performed or called in the program, it executes all the paragraphs within that section sequentially.
  • All section names should code in Area-A, and the code in it should code in Area-B.

For example - Sections in the program.

----+----1----+----2----+----3----+----4----+----5
       IDENTIFICATION DIVISION.
       PROGRAM-ID. PROGSTRU.
	   AUTHOR. MTH.

       PROCEDURE DIVISION.
       1000-SEC1 SECTION.     --> Section
       1000-PARA.
           DISPLAY "Hello World" 
           DISPLAY "Welcome to MTH".         
           STOP RUN.

Divisions -


  • A division is one of the primary parts of a program, organizing its content and functionality. A division is a collection of one or more sections and paragraphs.
  • Division begins with the division name and ends at the beginning of the subsequent division or the program ends.
  • All divisions are system-defined and should begin in Area-A.
  • COBOL has four system-defined divisions, and those are -
    • IDENTIFICATION DIVISION (program metadata).
    • ENVIRONMENT DIVISION (configuration and I/O specifications).
    • DATA DIVISION (data definition).
    • PROCEDURE DIVISION (program logic).

For example - Sections in the program.

----+----1----+----2----+----3----+----4----+----5
       IDENTIFICATION DIVISION.  --> Division
       PROGRAM-ID. PROGSTRU.
	   AUTHOR. MTH.

       PROCEDURE DIVISION.       --> Division
       1000-SEC1 SECTION.
       1000-PARA.
           DISPLAY "Hello World" 
           DISPLAY "Welcome to MTH".         
           STOP RUN.

Syntactical Hierarchy -


Each division has its own set of elements, and the syntactical hierarchy is shown below -

Syntactical Hierarchy