You are on page 1of 56

COBOL (COMMON

BUSINESS ORIENTED
LANGUAGE)

Overview
COBOL Fundamentals

DAY1
Session Plan

 Day 1:

 Introduction to COBOL

 Evolution, Features & Language Fundamentals

 Program Structure

 Data description entry


References

 M.K.Roy and D. Ghosh Dastidar, COBOL Programming,


Tata McGraw Hill, New York, 1973.

 Nancy Stern and Robert Stern, COBOL Programming,


John Wiley & Sons, New York, 1973.

 Newcomer and Lawrence, Programming with


Structured COBOL, McGraw Hill Books, New York,
1973.
History of COBOL

 1959 – United States Department of Defense


 1960 - COBOL initial specifications presented by CODASYL
(Conference on
Data Systems Languages)

 1964 – BASIC COBOL extended to Visual COBOL


 1968 – ANSI (American National Standards Institute)
developed
American National Standard (ANS) COBOL
 1974 – ANSI published revised version of (ANS) COBOL
– Business applications needed to manipulate
character as well as numeric data
– String operations added
 1985 – COBOL 85 Standards was introduced with revised
version of COBOL-74.
COBOL

 What does COBOL stand for?


COmmon Business Oriented Language.

 Which are target area of COBOL applications?


Defense, Aircraft, Insurance, Finance,
Retail etc
(file & data oriented applications
involved)

 So we can say that COBOL is basically used for


writing business applications and not for
developing system software
COBOL – Program Structure
PROGRAM
Principal portions of a program.
There are 4 divisions –
DIVISIONS a) Identification (Required)
b) Environment (Optional)
Userc)defined
Datachunk of code
(Optional)
which consists of one/more
d) Procedure (Required)
SECTIONS paragraphs.
e.g.
User defined chunk of code
a) U000-CHECK-LOG SECTION.
which consists of one/more
b) FILE SECTION.
sentences.
PARAGRAPHS e.g.
A
a) SENTENCE consists of one or
P000-PRINT-FINAL-TOTALS.
b) PROGRAM-ID.andconsists
A
more STATEMENT
statements is of a
COBOL verb
terminated by a full stop.and an
SENTENCES
e.g. a) MOVEoperand or operands.
.21 TO VAT-RATE
RESERVEDb) WORDS
e.g.
COMPUTE VAT-AMOUNT =
SUBTRACT
PRODUCT-COST T-TAX. FROM
* VAT-RATE GROSS-
CHARACTERS
STATEMENTS PAY GIVING NET-PAY
USER DEFINED WORDS
COBOL CHARACTER
SET

Overview
Character Meaning

Space
+ Plus sign
- Minus sign or hyphen
* Asterisk
/ Forward slash or solidus
= Equal sign
$ Currency sign1
, Comma
; Semicolon
. Decimal point or period
" Quotation mark2
( Left parenthesis
) Right parenthesis
> Greater than
< Less than
: Colon
' Apostrophe
A-Z Alphabet (uppercase)
a-z Alphabet (lowercase)
0-9 Numeric characters
IDENTIFICATION DIVISION …
Compiler takes this as
Program Identifier.
PROGRAM-ID comes
IDENTIFICATION DIVISION. immediately after ID
Division.
PROGRAM-ID. PROG1.
AUTHOR. R.R. BHATT.
INSTALLATION. ABC CORP.
DATE-WRITTEN. 01-JAN-2005.
DATE-COMPILED. 01-JAN-2005. OPTIONAL
SECURITY. HIGH.
ENVIRONMENT DIVISION

ENVIRONMENT DIVISION

CONFIGURATION SECTION INPUT-OUTPUTT SECTION

Identifies the Identifies the


computer used for resources used for
compiling of programs executing the program
DATA DIVISION

 The DATA DIVISION is used to describe the data structures used in the
program.

 There are sections in the DATA DIVISION


 FILE SECTION
 WORKING-STORAGE SECTION
 LINKAGE SECTION
 REPORT SECTION
The two most commonly used components (sections) are

a) WORKING-STORAGE SECTION
Internal data structures are defined here.
b) FILE SECTION
File I/O buffer areas are defined here.
DATA DIVISION

DATA DIVISION.
FILE SECTION.
FD INVENTORY-FILE
RECORD CONTAINS 78 CHARACTERS.
01 INVENTORY-REC.
05 IF-PART-NUMBER PIC X(09).
05 PIC X(24).
05 IF-WHSE-LOCS.
10 IF-MAIN-LOC PIC X(06).
10 IF-ALT-LOC PIC X(06).
05 PIC X(33).
FD PRINT-FILE.
01 PRINT-REC.
05 PIC X(10).
05 P-PART-NUMBER PIC X(09).
05 PIC X(05).
05 P-MAIN-LOC PIC X(06).
05 PIC X(05).
05 P-ALT-LOC PIC X(06).
WORKING-STORAGE SECTION.
01 FLAGS.
05 F-MORE-RECORDS PIC X VALUE 'Y'.
PROCEDURE DIVISION ..

 The PROCEDURE DIVISION consists of the


following –

 Sections

 Paragraphs

 Sentences

 Statements
PROCEDURE DIVISION
Section contain one or
Section more Paragraphs.

PROCEDURE DIVISION.

0001-ACCOUNT-SECTION. Paragraph
A PARAGRAPH
001-ACCOUNT-READ-PARA.
comprises of one or
READ ACC-FILE AT END
MOVE ‘Y’ TO EOF. more sentences
MOVE TAX-REDUCT TO TAX-AMOUNT
A SENTENCE is a
001-ACCOUNT-VALIDATE-PARA. combination of one or
ADD AMOUNT TO TOT-AMOUNT. Sentences more statements and is
terminated by a full
stop.
ACCEPT EMPLOYEE-SALARY
DISPLAY “Current Employee Salary “
EMPLOYEE-SALARY.
001-EXIT-PARA. statement
STOP RUN. A STATEMENT is a
combination of a
COBOL verb and one
or more operands.
First COBOL program

IDENTIFICATION DIVISION.
PROGRAM-ID. FIRSTPG.
PROCEDURE DIVISION.
A0000-MAIN-PARA.
DISPLAY ‘-------------------------------’.
DISPLAY ‘ WELCOME TO COBOL’.
DISPLAY ‘--------------------------------’.
STOP RUN.
COBOL coding sheet

Column numbers
1 2 3 4 5 6 7 8 9 10 11 12 72 80

I
Column numbers * Area A Area B D
E
N
T

- I
F
I
/ C
A
T
I
O
N

A
R
E
A
COBOL coding sheet

Almost all COBOL compilers treat a line of


COBOL code as if it contained two distinct
areas. These are -

AREA A AREA B

*) Between Column 8 to 11 *) Between Column 12 to 72


*) Division, Section, Paragraph *) All Sentences & Statements
names, FD entries & 01 start in Area B
level entries must start in
Area A
COBOL coding rules

 Each line is considered to be made up of 80 columns.


 Columns 1 to 6 are reserved for line numbers.
Column 7 is an indicator column and has special
meaning to the compiler.

Asterisk ( * ) indicates comments


Hyphen ( - ) indicates continuation
Slash ( / ) indicates form feed
 Columns 8 to 11 are called Area A.
All COBOL DIVISIONs,
SECTIONs, paragraphs and some special entries must
begin in Area A.
 Columns 12 to 72 are called Area B. All COBOL
statements must begin in Area B.
 Columns 73 to 80 are identification area.
Basic data types

 Alphabetic ( A)
 Numeric( 9)
 Alphanumeric (X)
 Edited numeric ( Z, $)
 Edited alphanumeric(/,-)
Data names

 Are named memory locations.

 Must be described in the DATA DIVISION


before they can be used in the PROCEDURE
DIVISION.

 Can be of elementary or group type.

 Can be subscripted for Arrays.

 Are user defined words .


Rules for forming User-defined words

 Can be at most 30 characters in length.

 Only alphabets, digits and hyphen are allowed.

 Blanks are not allowed.

 May not begin or end with a hyphen.

 Should not be a COBOL reserved word like


ADD,SUBTRACT,MOVE,DISPLAY etc….
Description of data names
 All the data names used in the PROCEDURE DIVISION
must be described in the DATA DIVISION.
 The description of a data name is done with the aid of
the following –

(1) Level number


(2) PICTURE clause
(3) VALUE clause

DATA DIVISION.
01 WS-EMPL-NO PIC X(10) VALUE 1001.

LEVEL NO Data Name Picture Clause VALUE Clause


DATA NAME  LEVEL NO

Level number

 Is used to specify the the data hierarchy.

Level Number Purpose


01 Record description and independent items
02 to 49 Fields within records and sub items
66 RENAMES clause
77 Independent items
88 Condition names
Piture Clause

Code Meaning

9 Numeric
PICTURE
clause A Alphabetic

X Alphanumeric

V Implicit Decimal

S Sign bit
COBOL ‘PICTURE’ Clauses

 Some examples
 PICTURE 999 a three digit (+ive only) integer
 PICTURE S999 a three digit (+ive/-ive) integer
 PICTURE XXXX a four character text item or
string
 PICTURE 99V99 a +ive ‘real’ in the range 0 to
99.99
 PICTURE S9V9 a +ive/-ive ‘real’ in the range ?

 If you wish you can use the abbreviation PIC.

 Numeric values can have a maximum of 18 (eighteen)


digits (i.e. 9’s).
Abbreviating recurring symbols

 Recurring symbols can be specified using a ‘repeat’


factor inside round brackets
 PIC 9(6) is equivalent to PICTURE 999999
 PIC 9(6)V99 is equivalent to PIC 999999V99
 PICTURE X(10) is equivalent to PIC XXXXXXXXXX
 PIC S9(4)V9(4) is equivalent to PIC S9999V9999
 PIC 9(18) is equivalent to PIC
999999999999999999
Declaring DATA in COBOL

 In COBOL a variable declaration consists of a line containing the following


items;
ΠA level number.
 A data-name or identifier.
Ž A PICTURE clause.

 We can give a starting value to variables by means of an extension to the


picture clause called the value clause.

DATA DIVISION.
WORKING-STORAGE SECTION.
01 Num1 PIC 999 VALUE ZEROS.
01 VatRate PIC V99 VALUE .18.
01 StudentName PIC X(10) VALUE SPACES.

DATA
Num1 VatRate StudentName

000 .18
Description of data names ..

VALUE clause

 Is used to assign an initial value to a


elementary data item.

 The initial value can be numeric literal, non-


numeric literal or figurative constant.

 Is an optional clause.
Literals

 Literals are symbols whose value does not


change in a program.

 There are 3 types of literals namely

(1) Numeric literals.

(2) Non-numeric literals.

(3) Figurative constants.


Literals – Figurative Constants

Figurative constants Meaning

ZERO(S) or ZEROES Represents the value 0, one or


more depending on the context
SPACE(S) Represents one or more spaces
HIGH-VALUE(S) Represents the highest value
LOW-VALUE(S) Represents the lowest value
QUOTE(S) Represents single or double
quotes

ALL literal Fill With Literal


Figurative Constants - Examples

01 GrossPay PIC 9(5)V99 VALUE 13.5.


ZERO
MOVE ZEROS TO GrossPay.
ZEROES

GrossPay
0 0 0 1 3 5 0


01 StudentName PIC X(10) VALUE "MIKE".

MOVE ALL "-" TO StudentName.

StudentName
M I K E     
Figurative Constants - Examples
01 GrossPay PIC 9(5)V99 VALUE 13.5.
ZERO
MOVE ZEROS TO GrossPay.
ZEROES

GrossPay
0 0 0 0 0 0 0


01 StudentName PIC X(10) VALUE "MIKE".

MOVE ALL "-" TO StudentName.

StudentName
- - - - - - - - - -
Group and elementary items
 In COBOL the term “group item” is
used to describe a data item which
has been further subdivided.

WORKING-STORAGE SECTION.
01 EMPLOYEE-DETAILS PIC X(30).  A Group item is declared using
a level number and a data
name. It cannot have a picture
01 EMPLOYEE-DETAILS. clause.
05 EMP-NUM PIC 9(4).
05 EMP-NAME PIC X(10).
05 EMP-DEPT PIC X(4).  Where a group item is the
05 EMP-LOC PIC X(12). highest item in a data
hierarchy it is referred to as a
record and uses the level
number 01.
 Picture clauses are NOT
specified for ‘group’ data
items because the size of a
group item is the sum of the
sizes of its subordinate,
elementary items and its type
is always assumed to be PIC X.
Group Items/Records - Example

WORKING-STORAGE SECTION.
01 EMPLOYEE-DETAILS PIC X(20).

01 EMPLOYEE-DETAILS. Group item


05 EMP-NUM PIC 9(4).
05 EMP-NAME PIC X(10).
05 EMP-DEPT PIC X(4).
05 EMP-LOC PIC X(12). Sub-Items
Group Items/Records - Example

123456789012345678901234567890 (cols)
1234JyothiS E&R Bangalore
Data in input file
2234Archana E&R Marathi
9999Bhushan E&R C++

Variable for file read Value

WORKING-STORAGE SECTION.
01 EMPLOYEE-DETAILS PIC X(30). 1234JyothiS E&R Bangalore
Group Items/Records - Example
Data in input file
123456789012345678901234567890 (cols)
1234JyothiS E&R Bangalore
2234Archana E&R Mysore
9999Bhushan E&R Chennai

Variable for file read Value

WORKING-STORAGE SECTION.
01 EMPLOYEE-DETAILS PIC X(30). 1234JyothiS E&R Bangalore

01 EMPLOYEE-DETAILS.
05 EMP-NUM PIC 9(4). 1234
05 EMP-NAME PIC X(10). JyothiS
05 EMP-DEPT PIC X(4). E&R
05 EMP-LOC PIC X(12). Bangalore
LEVEL Numbers & DATA hierarchy

 In COBOL, Level numbers


WORKING-STORAGE SECTION. are used to express data
01 POLICY-DETAILS. hierarchy. The higher the
05 POLICY-NO.
10 POLICY-TYP PIC X(4).
level number, the lower
10 POLICY-LOC PIC X(2). the item is in the
10 POLICY-ID PIC X(5). hierarchy.
05 POLICY-TYPE PIC X(10).
05 POLICY-EXPDT PIC X(10).  So Group items contain
sets of elementary items
with lower level numbers.
At the lowest level the
data is completely atomic.
Description of data names

DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-REGNO PIC X(5).
01 WS-NAME.
05 WS-FIRST-NAME PIC A(15).
05 WS-MID-NAME PIC A(15).
05 WS-LAST-NAME PIC A(10).
01 WS-AGE PIC 99V99.
01 WS-SCHOLARSHIP PIC 9(4) VALUE 1000.
Group
Items/Records

WORKING-STORAGE SECTION.
01 StudentDetails PIC X(26).

StudentDetails
H E N N E S S Y R M 9 2 3 0 1 6 5 L M 5 1 0 5 5 0 F
Group
Items/Records

WORKING-STORAGE SECTION.
01 StudentDetails.
02 StudentName PIC X(10).
02 StudentId PIC 9(7).
02 CourseCode PIC X(4).
02 Grant PIC 9(4).
02 Gender PIC X.

StudentDetails
H EN N E S S Y RM 9 2 3 0 1 6 5 L M 5 1 0 5 5 0 F
StudentName StudentId CourseCode Grant Gender
Group
Items/Records

WORKING-STORAGE SECTION.
01 StudentDetails.
02 StudentName.
03 Surname PIC X(8).
03 Initials PIC XX.
02 StudentId PIC 9(7).
02 CourseCode PIC X(4).
02 Grant PIC 9(4).
02 Gender PIC X.

StudentDetails
H EN N E S S Y RM 9 2 3 0 1 6 5 L M 5 1 0 5 5 0 F
StudentName StudentId CourseCode Grant Gender
Surname Initials
MOVE VERB

Overview
The MOVE
Verb

 Identifier 
MOVE   TO { Identifier } ...
 Literal 
 MOVE copies data from the source identifier or
literal to one or more destination identifiers.

 MOVE copies data to Group or elementary data


items.

 MOVE always performs LEFT JUSTIFICATION to


Character

 MOVE always perform RIGHT JUSTIFICATION to


Numeric data.

 When data is MOVEd into an item the contents of


the item are completely replaced.
MOVEing
Data

MOVE “RYAN” TO Surname.


MOVE “FITZPATRICK” TO Surname.

01 Surname PIC X(8).


C O U G H L A N
MOVEing
Data

MOVE “RYAN” TO Surname.


MOVE “FITZPATRICK” TO Surname.

01 Surname PIC X(8).


R Y A N
MOVEing
Data

MOVE “RYAN” TO Surname.


MOVE “FITZPATRICK” TO Surname.

01 Surname PIC X(8).


F I T Z P A T R I C K
MOVEing to a numeric
item.

 When the destination item is numeric, or edited


numeric, then data is aligned along the decimal point
with zero filling or truncation as necessary.

 When the decimal point is not explicitly specified in


either the source or destination items, the item is
treated as if it had an assumed decimal point
immediately after its rightmost character.
01 GrossPay PIC 9(4)V99.

GrossPay
MOVE ZEROS TO GrossPay.
0 0 0 0 0 0


GrossPay
MOVE 12.4 TO GrossPay.
0 0 1 2 4 0

GrossPay
MOVE 123.456 TO GrossPay.
0 1 2 3

4 5 6
GrossPay
MOVE 12345.757 TO GrossPay.

1 2 3 4 5  7 5 7
01 CountyPop PIC 999.
01 Price PIC 999V99.

CountyPop
MOVE 1234 TO CountyPop. 1 2 3 4


CountyPop
MOVE 12.4 TO CountyPop.
0 1 2 4


Price
MOVE 154 TO Price.
1 5 40 0

Price
MOVE 3552.75 TO Price.
3 5 5 2 7 5


Before After

WS00-OUT1 0000 WS00-OUT1 3456


WS00-OUT2 000000 WS00-OUT2 345678

Before

WS00-OUT3 000000

After

WS00-OUT3 123456

Before After

WS00-OUT4 00000000 WS00-OUT4 12345678


MOVE .. example

****************************

Output SPOOL WS00-OUT1 : HARAYANA


WS00-OUT2 : HARAYANA
****************************
The DISPLAY
Verb
 Identifier    Identifier  
DISPLAY      ...
 Literal    Literal  
[ UPON Mnemonic - Name] [ WITH NO ADVANCING]
 From time to time it may be useful to display messages and
data values on the screen.

 A simple DISPLAY statement can be used to achieve this.

 A single DISPLAY can be used to display several data items or


literals or any combination of these.

 The WITH NO ADVANCING clause suppresses the carriage


return/line feed.
The ACCEPT
verb

Format 1. ACCEPT Identifier [ FROM Mnemonic - name]


DATE 

DAY 

Format 2. ACCEPT Identifier FROM  
DAY - OF - WEEK 

TIME 

01 CurrentDate PIC 9(6).


* YYMMDD
01 DayOfYear PIC 9(5).
* YYDDD
01 Day0fWeek PIC 9.
* D (1=Monday)
01 CurrentTime PIC 9(8).
* HHMMSSss s = S/100
IDENTIFICATION DIVISION.
PROGRAM-ID. AcceptAndDisplay.
AUTHOR. Michael Coughlan.

Run of Accept and Display program DATA DIVISION.


WORKING-STORAGE SECTION.
Enter student details using template below 01 StudentDetails.
02 StudentName.
NNNNNNNNNNSSSSSSSCCCCGGGGS 03 Surname PIC X(8).
COUGHLANMS9476532LM511245M 03 Initials PIC XX.
02 StudentId PIC 9(7).
Name is MS COUGHLAN 02 CourseCode PIC X(4).
Date is 24 01 94 02 Grant PIC 9(4).
02 Gender PIC X.
Today is day 024 of the year
The time is 22:23 01 CurrentDate.
02 CurrentYear PIC 99.
02 CurrentMonth PIC 99.
02 CurrentDay PIC 99.
01 DayOfYear.
02 FILLER PIC 99.
02 YearDay PIC 9(3).
01 CurrentTime.
02 CurrentHour PIC 99.
02 CurrentMinute PIC 99.
02 FILLER PIC 9(4).

PROCEDURE DIVISION.
Begin.
DISPLAY "Enter student details using template below".
DISPLAY "NNNNNNNNNNSSSSSSSCCCCGGGGS ".
ACCEPT StudentDetails.
ACCEPT CurrentDate FROM DATE.
ACCEPT DayOfYear FROM DAY.
ACCEPT CurrentTime FROM TIME.
DISPLAY "Name is ", Initials SPACE Surname.
DISPLAY "Date is " CurrentDay SPACE CurrentMonth SPACE CurrentYear.
DISPLAY "Today is day " YearDay " of the year".
DISPLAY "The time is " CurrentHour ":" CurrentMinute.
STOP RUN.
Example Program -
Date

Overview

You might also like