Let's have a look at a very basic Hello World example written in COBOL compatible with older versions of COBOL compilers. 

1
2
3
4
5
6
7
8
9
10
11
000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. HELLO.
000300 ENVIRONMENT DIVISION.
000400 DATA DIVISION.
000500 PROCEDURE DIVISION.
000600
000700 PROGRAM-BEGIN.
000800     DISPLAY "Hello world".
000900
001000 PROGRAM-DONE.
001100     STOP RUN.

 Building blocks of a COBOL program

A COBOL program always consists of four parts called DIVISIONS.

Some DIVISIONS are not mandatory in newer COBOL compilers anymore.

In fact you are even able to leave out the whole PROCEDURE division, although someone might ask what good this might do. Maybe simple DATA division modules providing constants? But that is speculation for now. 

Each DIVISION can be broken down into SECTIONS, which again can contain PARAGRAPHS.

A PARAGRAPH can contain several sentences.

DIVISION
|_SECTION
          |_PARAGRAPH
|_SENTENCE
|_STATEMENT

IDENTIFICATION Division

The IDENTIFICATION division is used to provide basic information on a program.

In the above example it provides only the program name using the PROGRAM-ID.

The PROGRAM-ID is mandatory paragraph, which will be required by most compilers.

ENVIRONMENT Division

The ENVIRONMENT division is used to provide details on a system environment a COBOL program is running in. 

Above example does not provide any environment information as it is very simple.

This has been introduced to enable COBOL to run programs in various different environments.

DATA Division

This division provides the data a COBOL operates on like variable declarations.

The DATA division can be optional in newer compilers / more recent versions of COBOL.

PROCEDURE Division

Contains the main processing part of a COBOL program. Here is where the magic happens.

It contains two paragraphs called PROGRAM-BEGIN and PROGRAM-DONE.

PARAGRAPHS are sections, which contain commands called SENTENCES

PROGRAM-DONE is a paragraph, which contains just one SENTENCE.

The sentence STOP-RUN terminates the program and is required by most compilers.

SECTIONS

Sections can be mandatory depending on their parent DIVISION and their purpose.

SECTIONS are created using the following syntax.

[name for a section] SECTION.

A mandatory SECTION whenever working with variables in the DATA-DIVISION is the WORKING-STORAGE SECTION.

Layout of a COBOL program

In older versions each command had to be ended with a dot. This has been abolished since the period is a termination character, which ends any sentence and was root cause of many bugs.

So you use a period to terminate a sentence, but you should use it as few times as possible in a program.

The first six characters in a COBOL program are reserved for the line numbers. In the early days of COBOL computers were programmed using punch cards (cards with holes in it).

Each punch card carried one line of code. If the sequence of cards and therefore the sequence of lines was out of order, the compiler would throw a warning.

The line numbers like 00100 are optional on PCs. Most compilers will not throw a warning message, if you leave the line numbers out.

However, older complier versions might require you to stick with the layout. 

The first 6 columns are reserved for the line numbers and it is called the sequence number area.

The seventh column is blank, but if you place an asterisk there you indicate a one line comment. This is called the indicator area.

Area A from column 8 through 11 is reserved for DIVISIONs, SECTIONs and PARAGRAPHs.

Area B from column 12 through 72 contains the SENTENCEs of a program. Its good practise to start sentences in column 12.