COBOL Programming Fundamental
COBOL Programming Fundamental
COBOL Programming
Fundamental
ISSC SH
Walker JIA
Version 1.0
2004/11
Training Schedule
Day 1
Moring
Introduction to COBOL
Day 2
Introduction to
Sequential
Files
Simple iteration
with the
PERFORM
verb
Processing
Sequential
Files
Arithmetic and
Edited
Pictures
COBOL Basics 1
Exercise 1
After
noon
Day 3
Exercise 2
Exercise 3
Day 4
Conditions
Tables and the
PERFORM .
.. VARYING
Exercise 3
(Cont.)
COBOL Basics 2
Designing
Programs
Table of contents
Introduction to COBOL
COBOL Basics 1
COBOL Basics 2
Introduction to Sequential Files
Processing Sequential Files
Simple iteration with the PERFORM verb
Arithmetic and Edited Pictures
Conditions
Tables and the PERFORM ... VARYING
Designing Programs
Introduction to COBOL
Overview
COBOL design goals.
Structure of COBOL programs.
The four divisions.
IDENTIFICATION DIVISION, DATA DIVISION, PROCEDURE
DIVISION.
Sections, paragraphs, sentences and statements.
Example COBOL programs.
Introduction to COBOL
COBOL
COBOL is an acronym which stands for
Introduction to COBOL
COBOL idiosyncracies
One of the design goals was to make the language as Englishlike as possible. As a consequence
the COBOL reserved word list is quite extensive and contains
hundreds of entries.
COBOL uses structural concepts normally associated with English
prose such as section, paragraph, sentence and so on.
As a result COBOL programs tend to be verbose.
Introduction to COBOL
Structure of COBOL programs
Program
Program
Divisions
Divisions
Section(s)
Section(s)
Paragraph(s)
Paragraph(s)
Sentence(s)
Sentence(s)
Statement(s)
Statement(s)
7
Introduction to COBOL
The Four Divisions
Introduction to COBOL
Functions of the four divisions
The IDENTIFICATION DIVISION is used to supply information
about the program to the programmer and to the compiler.
The ENVIRONMENT DIVISION describes to the compiler the
environment in which the program will run.
As the name suggests, the DATA DIVISION is used to provide the
descriptions of most of the data to be processed by the program.
The PROCEDURE DIVISION contains the description of the
algorithm which will manipulate the data previously described. Like
other languages COBOL provides a means for specifying
sequence, selection and iteration constructs.
Introduction to COBOL
COBOL Program Text Structure
IDENTIFICATION DIVISION.
Program Details
DATA DIVISION.
Data Descriptions
PROCEDURE DIVISION.
NNOTE
OTE
The
Thekeyword
keyword
DIVISION
DIVISIONand
andaa
full-stop
full-stopisisused
used
ininevery
everycase.
case.
Algorithm Description
10
Introduction to COBOL
IDENTIFICATION DIVISION
The purpose of the IDENTIFICATION DIVISION is to provide
information about the program to the programmer and to the
compiler.
Most of the entries in the IDENTIFICATION DIVISION are directed
at the programmer and are treated by the compiler as comments.
An exception to this is the PROGRAM-ID clause. Every COBOL
program must have a PROGRAM-ID. It is used to enable the
compiler to identify the program.
There are several other informational paragraphs in the
IDENTIFICATION DIVISION but we will ignore them for the
moment.
11
Introduction to COBOL
The IDENTIFICATION DIVISION Syntax
IDENTIFICATION
IDENTIFICATION DIVISION.
DIVISION.
PROGRAM-ID.
PROGRAM-ID. BMJA01.
BMJA01.
AUTHOR.
AUTHOR. Michael
Michael Coughlan.
Coughlan.
12
Introduction to COBOL
The DATA DIVISION
13
FILE SECTION.
WORKING-STORAGE SECTION.
Introduction to COBOL
DATA DIVISION Syntax
DIVISION
.
SECTION
.
File
Section
WORKING
- STORAGE
WS entries.
entries.
SECTION
IDENTIFICATION
IDENTIFICATION DIVISION.
DIVISION.
PROGRAM-ID.
PROGRAM-ID. Sequence-Program.
Sequence-Program.
AUTHOR.
Michael
AUTHOR. Michael Coughlan.
Coughlan.
DATA
DATA DIVISION.
DIVISION.
WORKING-STORAGE
WORKING-STORAGE SECTION.
SECTION.
01
PIC
01 Num1
Num1
PIC 99 VALUE
VALUE ZEROS.
ZEROS.
01
Num2
PIC
9
VALUE
ZEROS.
01 Num2
PIC 9 VALUE ZEROS.
01
PIC
01 Result
Result
PIC 99
99 VALUE
VALUE ZEROS.
ZEROS.
14
Introduction to COBOL
The PROCEDURE DIVISION
Introduction to COBOL
Sections
A section begins with the section name and ends where the next
section name is encountered or where the program text ends.
16
Introduction to COBOL
Paragraphs
17
Introduction to COBOL
Sentences and Statements
18
Introduction to COBOL
A Full COBOL program
IDENTIFICATION
IDENTIFICATIONDIVISION.
DIVISION.
PROGRAM-ID.
SAMPLE1.
PROGRAM-ID. SAMPLE1.
AUTHOR.
AUTHOR. Michael
MichaelCoughlan.
Coughlan.
DATA
DATADIVISION.
DIVISION.
WORKING-STORAGE
WORKING-STORAGESECTION.
SECTION.
01
Num1
PIC
9
VALUE
01 Num1
PIC 9 VALUEZEROS.
ZEROS.
01
Num2
PIC
9
VALUE
ZEROS.
01 Num2
PIC 9 VALUE ZEROS.
01
Result
PIC
01 Result
PIC99
99VALUE
VALUEZEROS.
ZEROS.
PROCEDURE
PROCEDUREDIVISION.
DIVISION.
CalculateResult.
CalculateResult.
ACCEPT
ACCEPTNum1.
Num1.
ACCEPT
Num2.
ACCEPT Num2.
MULTIPLY
MULTIPLYNum1
Num1BY
BYNum2
Num2GIVING
GIVINGResult.
Result.
DISPLAY
"Result
is
=
",
Result.
DISPLAY "Result is = ", Result.
STOP
STOPRUN.
RUN.
19
Introduction to COBOL
The minimum COBOL program
IDENTIFICATION DIVISION.
IDENTIFICATION DIVISION.
PROGRAM-ID. SAMPLE2.
PROGRAM-ID. SAMPLE2.
PROCEDURE DIVISION.
PROCEDURE DIVISION.
DisplayPrompt.
DisplayPrompt.
DISPLAY "I did it".
DISPLAY "I did it".
STOP RUN.
STOP RUN.
20
Table of contents
Introduction to COBOL
COBOL Basics 1
COBOL Basics 2
Introduction to Sequential Files
Processing Sequential Files
Simple iteration with the PERFORM verb
Arithmetic and Edited Pictures
Conditions
Tables and the PERFORM ... VARYING
Designing Programs
21
COBOL Basics 1
Overview
22
COBOL Basics 1
COBOL coding rules
*Identification Area7th byte
AAreaA8th 11th byte
BArea B12th 72th byte
Almost all COBOL compilers treat a line of COBOL code as if it contained
two distinct areas. These are known as;
Area A and Area B
When a COBOL compiler recognizes these two areas, all division, section,
paragraph names, FD entries and 01 level numbers must start in Area A. All
other sentences must start in Area B.
IDENTIFICATION
IDENTIFICATION DIVISION.
DIVISION.
PROGRAM-ID.
Program.
PROGRAM-ID. Program.
** This
This is
is aa comment.
comment. It
It starts
starts
** with
an
asterisk
in
column
with an asterisk in column 11
23
COBOL Basics 1
Name Construction
24
They must contain at least one character and not more than 30
characters.
They must contain at least one alphabetic character and they must
not begin or end with a hyphen.
COBOL Basics 1
Describing DATA
There are basically three kinds of data used in COBOL programs;
1.
2.
3.
Variables.
Literals.
Figurative Constants.
25
COBOL Basics 1
Data-Names / Variables
26
COBOL Basics 1
Using Variables
01 StudentName
StudentName
27
COBOL Basics 1
Using Variables
01 StudentName
StudentName
J
28
COBOL Basics 1
Using Variables
01 StudentName
StudentName
My name is JOHN
29
O H
COBOL Basics 1
COBOL Data Types
For the time being we will focus on just two data types,
numeric
text or string
30
COBOL Basics 1
Quick Review of Data Typing
The type usually determines the range of values the data item can store.
For instance a CARDINAL item can store values between 0..65,535 and an
INTEGER between -32,768..32,767
31
From the type of the item the compiler can establish how much memory to
set aside for storing its values.
COBOL Basics 1
COBOL data description
32
COBOL Basics 1
COBOL PICTURE Clause symbols
33
COBOL Basics 1
COBOL PICTURE Clauses
Some examples
PICTURE 999
PICTURE S999
PICTURE XXXX
PICTURE 99V99
PICTURE S9V9
34
COBOL Basics 1
Abbreviating recurring symbols
35
COBOL Basics 1
Declaring DATA in COBOL
DATA
Num1
Num1 VatRate
VatRate
000
000
36
DATA DIVISION.
WORKING-STORAGE SECTION.
01 Num1
PIC 999
01 VatRate
PIC V99
01 StudentName
PIC X(10)
VALUE ZEROS.
VALUE .18.
VALUE SPACES.
StudentName
StudentName
.18
.18
COBOL Programming Fundamental
COBOL Basics 1
COBOL Literals
Numeric literals may consist of numerals, the decimal point and the plus or
minus sign. Numeric literals are not enclosed in quotes.
e.g. 123, 123.45, -256, +2987
37
COBOL Basics 1
Figurative Constants
38
SPACE
SPACEor
orSPACES
SPACES
ZERO
ZEROor
orZEROS
ZEROSor
orZEROS
ZEROS
==
==
QUOTE
QUOTEor
orQUOTES
QUOTES
HIGH
-VALUE or
-VALUES
HIGH-VALUE
orHIGH
HIGH-VALUES
==
==
LOW
-VALUE or
-VALUES
LOW-VALUE
orLOW
LOW-VALUES
ALL
ALLliteral
literal
==
==
00
""
Max
MaxValue
Value
Min
MinValue
Value
Fill
FillWith
WithLiteral
Literal
COBOL Basics 1
Figurative Constants - Examples
01
01 GrossPay
GrossPay PIC
PIC 9(5)V99
9(5)V99 VALUE
VALUE 13.5.
13.5.
ZERO
MOVE
TO
MOVE ZEROS
TO GrossPay.
GrossPay.
ZEROES
GrossPay
0
l
StudentName
StudentName
PIC
PIC X(10)
X(10) VALUE
VALUE "MIKE".
"MIKE".
MOVE
MOVE ALL
ALL "-"
"-" TO
TO StudentName.
StudentName.
StudentName
M I K E
39
COBOL Basics 1
Figurative Constants - Examples
01
01 GrossPay
GrossPay
ZERO
MOVE
MOVE ZEROS
PIC
PIC 9(5)V99
9(5)V99 VALUE
VALUE 13.5.
13.5.
TO
TO GrossPay.
GrossPay.
ZEROES
GrossPay
0
l
01
01 StudentName
StudentName
PIC
PIC X(10)
X(10) VALUE
VALUE "MIKE".
"MIKE".
MOVE
MOVE ALL
ALL "-"
"-" TO
TO StudentName.
StudentName.
StudentName
- - - - - - - - - 40
COBOL Basics 1
Editing, Compiling, Running
41
COBOL Basics 1
Editing, Compiling, Running
//EV6098A JOB (F9500B,WD01X),'EV6098',NOTIFY=EV6098,
//
MSGLEVEL=(1,1),
//
CLASS=M,MSGCLASS=R,USER=WD01UJ1,PASSWORD=MON10JUN
//*********************************************************************
//* UIBMCL: COMPILE AND LINKEDIT A COBOL PROGRAM
//*
//UIBMCL PROC WSPC=500,NAME=TEMPNAME
//*
//*
COMPILE THE COBOL PROGRAM
//*
//COB
EXEC PGM=IGYCRCTL,
//
PARM='APOST,LIB,NOSEQ,RENT,TRUNC(BIN),LANG(UE)
//STEPLIB DD DSN=SYS1.IGY.SIGYCOMP,DISP=SHR
//SYSIN
DD DSN=WD01I.DS.COBOL&SRC(&NAME),DISP=SHR
//SYSLIB
DD DSN=WD01I.DS.COPY©,DISP=SHR <=== BLK 3120
//
DD DSN=MQM.SCSQCOBC,DISP=SHR
//SYSLIN
DD DSN=WD01I.DS.UT.OBJ&SRC(&NAME),DISP=SHR
//OUTDEF OUTPUT PRMODE=SOSI2,CHARS=(KN10,KNJE)
//SYSPRINT DD SYSOUT=*,OUTPUT=*.OUTDEF
//SYSUDUMP DD SYSOUT=*
//SYSUT1
DD SPACE=(800,(&WSPC,&WSPC),,,ROUND),UNIT=3390
//SYSUT2
DD SPACE=(800,(&WSPC,&WSPC),,,ROUND),UNIT=3390
42
COBOL Basics 1
Editing, Compiling, Running
//*
//*
LINKEDIT IF THE COMPILE
//*
RETURN CODES ARE 4 OR LESS
//*
//LKED
EXEC PGM=HEWL,PARM='XREF',COND=(4,LT,COB)
//SYSLIB
DD DSN=SYS1.SCEELKED,DISP=SHR
//
DD DSN=DSNCFD.SDSNEXIT,DISP=SHR
//
DD DSN=DSNCFD.DSNLOAD,DISP=SHR
//OBJECT
DD DSN=WD01I.DS.UT.OBJ&SRC,DISP=SHR
//CSQSTUB DD DSN=MQM.SCSQLOAD,DISP=SHR
//CEEUOPT DD DSN=WD01I.DS.LOAD00,DISP=SHR
//SYSLMOD DD DSN=WD01I.DS.UT.LOAD&SRC(&NAME),DISP=SHR
//SYSLIN
DD DSN=WD01I.DS.UT.OBJ&SRC(&NAME),DISP=SHR
//
DD DSN=WD01I.CSL1.PARMLIB(DSNELI),DISP=SHR
//
DD DSN=WD01I.DS.PARAM00(CEEUOPT),DISP=SHR
//OUTDEF OUTPUT PRMODE=SOSI2,CHARS=(KN10,KNJE)
//SYSPRINT DD SYSOUT=*,OUTPUT=*.OUTDEF
//SYSUDUMP DD SYSOUT=*
//SYSUT1
DD SPACE=(4096,(500,500)),UNIT=3390
//
PEND
//*
//COMP
EXEC UIBMCL,SRC=00,COPY=00,NAME=BUAC25
//COB.SYSIN DD DSN=WD01I.EV6098.COBOL00(BUAC25)
43
COBOL Basics 1
Editing, Compiling, Running
//EV6098G2 JOB (F9500B,WD01X),CFD,TIME=1440,
//
REGION=8M,CLASS=M,MSGCLASS=R,MSGLEVEL=(1,1),
//
NOTIFY=EV6098,USER=WD01UJ1,PASSWORD=MON10JUN
//JOBLIB
DD DSN=WD01I.DS.UT.LOAD00,DISP=SHR
//
DD DSN=DSNCFD.DSNLOAD,DISP=SHR
//********************************************************************
//SCR
EXEC DSNDCR
DSN=WD01I.DS.PCDERR.CHK.REPORT
//*------------------------------------------------------------------//*
BUAC25 DUW25 CREATE
***
//*------------------------------------------------------------------//STEP160 EXEC PGM=BUAC25,COND=(4,LT)
//IDUW13
DD DSN=&&DUW13T,DISP=(OLD,DELETE)
//UAC250
DD DSN=WD01I.DS.PCDERR.CHK.REPORT,DISP=(,CATLG),
//
UNIT=3390,VOL=SER=EGF001,SPACE=(CYL,(15,15),RLSE),
//
DCB=(RECFM=FBA,LRECL=133,BLKSIZE=0)
//OFSW16
DD SYSOUT=*
//SYSPRINT DD SYSOUT=*
//SYSUDUMP DD SYSOUT=*
//SYSABOUT DD SYSOUT=*
//SYSOUT
DD SYSOUT=*
/*
44
EXERCISE 1
45
Table of contents
Introduction to COBOL
COBOL Basics 1
COBOL Basics 2
Introduction to Sequential Files
Processing Sequential Files
Simple iteration with the PERFORM verb
Arithmetic and Edited Pictures
Conditions
Tables and the PERFORM ... VARYING
Designing Programs
46
COBOL Basics 2
Overview
Level Numbers.
Group and elementary data items.
Group item PICTURE clauses.
The MOVE. MOVEing numeric items.
DISPLAY and ACCEPT.
47
COBOL Basics 2
Group Items/Records
WORKING-STORAGE
WORKING-STORAGE SECTION.
SECTION.
01
PIC
01 StudentDetails
StudentDetails
PIC X(26).
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
48
COBOL Basics 2
Group Items/Records
WORKING-STORAGE
WORKING-STORAGE SECTION.
SECTION.
01
StudentDetails.
01 StudentDetails.
02
PIC
02 StudentName
StudentName
PIC X(10).
X(10).
02
PIC
02 StudentId
StudentId
PIC 9(7).
9(7).
02
CourseCode
PIC
X(4).
02 CourseCode
PIC X(4).
02
PIC
02 Grant
Grant
PIC 9(4).
9(4).
02
Gender
PIC
X.
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
49
StudentId
CourseCode Grant
Gender
COBOL Basics 2
Group Items/Records
WORKING-STORAGE
WORKING-STORAGE SECTION.
SECTION.
01
01 StudentDetails.
StudentDetails.
02
.
02 StudentName
StudentName.
03
PIC
03 Surname
Surname
PIC X(8).
X(8).
03
Initials
PIC
XX.
03 Initials
PIC XX.
02
PIC
02 StudentId
StudentId
PIC 9(7).
9(7).
02
PIC
02 CourseCode
CourseCode
PIC X(4).
X(4).
02
Grant
PIC
9(4).
02 Grant
PIC 9(4).
02
PIC
02 Gender
Gender
PIC X.
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
Surname
50
StudentId
CourseCode Grant
Gender
Initials
COBOL Basics 2
LEVEL Numbers express DATA hierarchy
In this hierarchical structure the higher the level number, the lower the item
is in the hierarchy. At the lowest level the data is completely atomic.
The level numbers 01 through 49 are general level numbers but there are
also special level numbers such as 66, 77 and 88.
51
PIC X(8).
PIC XX.
X(8).
PIC
PIC 9(7).
XX.
PIC
PIC X(4).
9(7).
PIC
PIC 9(4).
X(4).
PIC
PIC X.
9(4).
PIC
PIC X.
01 StudentDetails.
01 05
StudentDetails.
StudentName.
05 10
StudentName.
Surname
10
Surname
10 Initials
10 Initials
05 StudentId
05 CourseCode
StudentId
05
05 Grant
CourseCode
05
05 Gender
Grant
05
05 Gender
PIC X(8).
PIC XX.
X(8).
PIC
PIC 9(7).
XX.
PIC
PIC X(4).
9(7).
PIC
PIC 9(4).
X(4).
PIC
PIC X.
9(4).
PIC
PIC X.
2004 IBM Corporation
COBOL Basics 2
Group and elementary items
In COBOL the term group item is used to describe a data item which has
been further subdivided.
A Group item is declared using a level number and a data name. It cannot have a picture
clause.
Where a group item is the highest item in a data hierarchy it is referred to as a record and
uses the level number 01.
The term elementary item is used to describe data items which are atomic;
that is, not further subdivided.
52
COBOL Basics 2
PICTUREs for Group Items
53
Picture clauses are NOT specified for group data items because the
size a group item is the sum of the sizes of its subordinate, elementary
items and its type is always assumed to be PIC X.
COBOL Basics 2
Assignment in COBOL
In strongly typed languages like Modula-2, Pascal or ADA the
assignment operation is simple because assignment is only allowed
between data items with compatible types.
The simplicity of assignment in these languages is achieved at the cost
of having a large number of data types.
In COBOL there are basically only three data types,
Alphabetic (PIC A)
Alphanumeric (PIC X)
Numeric (PIC 9)
But this simplicity is achieved only at the cost of having a very complex
assignment statement.
In COBOL assignment is achieved using the MOVE verb.
54
COBOL Basics 2
The MOVE Verb
Identifier
MOVE
TO {Identifier}...
Literal
55
The MOVE copies data from the source identifier or literal to one or
more destination identifiers.
When data is MOVEd into an item the contents of the item are
completely replaced. If the source data is too small to fill the
destination item entirely the remaining area is zero or space filled.
COBOL Basics 2
MOVEing Data
MOVE
MOVE RYAN
RYAN TO
TO Surname.
Surname.
MOVE
MOVE FITZPATRICK
FITZPATRICK TO
TO Surname.
Surname.
01 Surname
C
56
PIC X(8).
H
COBOL Basics 2
MOVEing Data
MOVE
RYAN TO
MOVE RYAN
TO Surname.
Surname.
MOVE
MOVE FITZPATRICK
FITZPATRICK TO
TO Surname.
Surname.
01 Surname
R
57
PIC X(8).
COBOL Basics 2
MOVEing Data
MOVE
MOVE RYAN
RYAN TO
TO Surname.
Surname.
MOVE
FITZPATRICK TO
MOVE FITZPATRICK
TO Surname.
Surname.
01 Surname
F
58
PIC X(8).
P
R I C K
COBOL Basics 2
MOVEing to a numeric item
59
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.
COBOL Basics 2
MOVEing to a numeric item
01 GrossPay
PIC 9(4)V99.
GrossPay
1 2
GrossPay
GrossPay
GrossPay
60
COBOL Basics 2
MOVEing to a numeric item
01 CountyPop
01 Price
PIC 999.
PIC 999V99.
CountyPop
CountyPop 0
Price
Price
3 5
l
61
COBOL Basics 2
Legal MOVEs
Certain combinations of sending and receiving data types are not
permitted (even by COBOL).
62
COBOL Basics 2
The DISPLAY Verb
Identifier Identifier
DISPLAY
...
Literal Literal
[UPON Mnemonic - Name ][WITH NO ADVANCING
63
COBOL Basics 2
The ACCEPT verb
Format 1. ACCEPT Identifier [FROM Mnemonic - name ]
DATE
DAY
DAY - OF - WEEK
TIME
01
CurrentDate
01
CurrentDate
* YYMMDD
PIC
PIC 9(6).
9(6).
01
DayOfYear
01
DayOfYear
* YYDDD
PIC
PIC 9(5).
9(5).
01
Day0fWeek
01
Day0fWeek
* D (1=Monday)
PIC
PIC 9.
9.
01
CurrentTime
01
CurrentTime
* HHMMSSss
s = S/100
PIC
PIC 9(8).
9(8).
* YYMMDD
* YYDDD
* D (1=Monday)
* HHMMSSss
64
s = S/100
COBOL Basics 2
65
Table of contents
Introduction to COBOL
COBOL Basics 1
COBOL Basics 2
Introduction to Sequential Files
Processing Sequential Files
Simple iteration with the PERFORM verb
Arithmetic and Edited Pictures
Conditions
Tables and the PERFORM ... VARYING
Designing Programs
66
67
68
69
STUDENTS.DAT
StudId
StudId StudName
StudName DateOfBirth
DateOfBirth
9723456
9723456 COUGHLAN
COUGHLAN
9724567
RYAN
9724567 RYAN
9534118
9534118 COFFEY
COFFEY
9423458
O'BRIEN
9423458 O'BRIEN
9312876
9312876 SMITH
SMITH
10091961
10091961
31121976
31121976
23061964
23061964
03111979
03111979
12121976
12121976
DATA
DATA DIVISION.
DIVISION.
FILE
SECTION.
FILE SECTION.
FD
FD StudentFile.
StudentFile.
01
StudentDetails.
01 StudentDetails.
02
PIC
02 StudId
StudId
PIC 9(7).
9(7).
02
StudName
PIC
X(8).
02 StudName
PIC X(8).
02
DateOfBirth
PIC
02 DateOfBirth PIC X(8).
X(8).
70
occurrences
Record Type
(Template)
(Structure)
71
Files are repositories of data that reside on backing storage (hard disk
or magnetic tape).
Files are processed by reading them into the computers memory one
record at a time.
72
To process a file records are read from the file into the computers
memory one record at a time.
The record buffer is the only connection between the program and
the records in the file.
Program
DISK
Record Instance
STUDENTS.DAT
73
IDENTIFICATION DIVISION.
etc.
ENVIRONMENT DIVISION.
etc.
DATA DIVISION.
FILE SECTION.
RecordBuffer
Declaration
If your program processes more than one file you will have to
describe a record buffer for each file.
74
Student Details.
Student
StudentId.
Id.
Student
StudentName.
Name.
Surname
Surname
Initials
Initials
Date
DateofofBirth
Birth
75
Year of Birth
Year of Birth
Month of Birth
Month of Birth
Day of Birth
Day of Birth
Course
CourseCode
Code
Value
Valueofofgrant
grant
Gender
Gender
01 StudentDetails.
01 StudentDetails.
02 StudentId
PIC 9(7).
02 StudentId
PIC 9(7).
02 StudentName.
02 StudentName.
03 Surname PIC X(8).
03 Surname PIC X(8).
03 Initials PIC XX.
03 Initials PIC XX.
02 DateOfBirth.
02 DateOfBirth.
03
YOBirth
PIC 99.
03
YOBirth
PIC 99.
03
MOBirth
PIC 99.
03
MOBirth
PIC 99.
03
DOBirth
PIC 99.
03
DOBirth
PIC 99.
02 CourseCode PIC X(4).
02 CourseCode PIC X(4).
02 Grant
PIC 9(4).
02 Grant
PIC 9(4).
02 Gender
PIC X.
02 Gender
PIC X.
76
DATA
DIVISION.
DATA
DIVISION.
FILE
SECTION.
FILE
SECTION.
FD
StudentFile.
FD StudentDetails.
StudentFile.
01
01 02
StudentDetails.
StudentId
PIC
9(7).
02
StudentId
PIC
9(7).
02
StudentName.
02 03
StudentName.
Surname
PIC
X(8).
03
Surname
PIC
X(8).
03
Initials
PIC
XX.
03 Initials
PIC XX.
02
DateOfBirth.
02 03
DateOfBirth.
YOBirth
PIC
9(2).
03
YOBirth
PIC
9(2).
03
MOBirth
PIC
9(2).
03 DOBirth
MOBirth
PIC 9(2).
9(2).
03
PIC
03 DOBirth
PIC X(4).
9(2).
02
CourseCode
PIC
02 Grant
CourseCode
PIC 9(4).
X(4).
02
PIC
02 Gender
Grant
PIC X.
9(4).
02
PIC
02 Gender
PIC X.
The record type/template/buffer of every file used in a program
must be described in the FILE SECTION by means of an FD (file
description) entry.
The FD entry consists of the letters FD and an internal file name.
COBOL Programming Fundamental
ASSIGN
ASSIGN TO
TO STUDENTS.
STUDENTS.
DATA
DIVISION.
DATA
DIVISION.
FILE
SECTION.
FILE
SECTION.
FD
StudentFile.
FD StudentDetails.
StudentFile.
01
01 02
StudentDetails.
StudentId
PIC
9(7).
02
StudentId
PIC
9(7).
DISK
02
StudentName.
02 03
StudentName.
Surname
PIC
X(8).
03
Surname
PIC
X(8).
03
Initials
PIC
XX.
03 Initials
PIC XX.
STUDENTS.DAT
02
DateOfBirth.
02 03
DateOfBirth.
YOBirth
PIC
9(2).
03
YOBirth
PIC
9(2).
03
MOBirth
PIC
9(2).
03 DOBirth
MOBirth
PIC 9(2).
9(2).
03
PIC
03 DOBirth
PIC 9(2).
********
********
The internal file name used in the FD entry is connected to an external file (on
disk or tape) by means of the Select and Assign clause.
77
[ORGANIZATION IS
SEQUENTIAL].
RECORD
78
79
OPEN
Before your program can access the data in an input file or place data in an
output file you must make the file available to the program by OPENing it.
READ
The READ copies a record occurrence/instance from the file and places it in
the record buffer.
WRITE
The WRITE copies the record it finds in the record buffer to the file.
CLOSE
You must ensure that (before terminating) your program closes all the files it
has opened. Failure to do so may result in data not being written to the file or
users being prevented from accessing the file.
OPEN OUTPUT
EXTEND
80
81
Once the system has opened a file and made it available to the program
it is the programmers responsibility to process it correctly.
Remember, the file record buffer is our only connection with the file and
it is only able to store a single record at a time.
To process all the records in the file we have to transfer them, one
record at a time, from the file to the buffer.
[INTO
Identifier
[NEXT ] RECORD
]
AT END StatementB
END - READ
Using INTO Identifier clause causes the data to be read into the
record buffer and then copied from there to the specified
Identifier in one operation.
82
lock
When this option is used there will be two copies of the data. It is
the equivalent of a READ followed by a MOVE.
COBOL Programming Fundamental
9
9
9
9
3
3
3
3
3
8
4
7
4
3
7
8
5
7
2
8
Course.
StudentName
6
1
9
1
7
5
2
1
F r a n k
F
T
T
B
r
h
o
i
a
o
n
l
C u r t a i n
n k
C u
m a s
H
y
O B
l y
D o
r
e
r
w
t
a
i
n
a
l
a
e
i n
y
n
s
L M 0 5 1
L
L
L
L
M
M
M
M
0
0
0
0
5
6
5
2
1
8
1
1
EOF
PERFORM UNTIL StudentRecord = HIGH-VALUES
READ StudentRecords
AT END MOVE HIGH-VALUES TO StudentRecord
END-READ
END-PERFORM.
83
9
9
9
9
3
3
3
3
3
8
4
7
4
3
7
8
5
7
2
8
Course.
StudentName
6
1
9
1
7
5
2
1
T h o m a s
F
T
T
B
r
h
o
i
a
o
n
l
H e a l y
n k
C u
m a s
H
y
O B
l y
D o
r
e
r
w
t
a
i
n
a
l
a
e
i n
y
n
s
L M 0 6 8
L
L
L
L
M
M
M
M
0
0
0
0
5
6
5
2
1
8
1
1
EOF
PERFORM UNTIL StudentRecord = HIGH-VALUES
READ StudentRecords
AT END MOVE HIGH-VALUES TO StudentRecord
END-READ
END-PERFORM.
84
9
9
9
9
3
3
3
3
3
8
4
7
4
3
7
8
5
7
2
8
Course.
StudentName
6
1
9
1
7
5
2
1
T o n y
F
T
T
B
r
h
o
i
a
o
n
l
O B r i a n
n k
C u
m a s
H
y
O B
l y
D o
r
e
r
w
t
a
i
n
a
l
a
e
i n
y
n
s
L M 0 5 1
L
L
L
L
M
M
M
M
0
0
0
0
5
6
5
2
1
8
1
1
EOF
PERFORM UNTIL StudentRecord = HIGH-VALUES
READ StudentRecords
AT END MOVE HIGH-VALUES TO StudentRecord
END-READ
END-PERFORM.
85
9 3 7 8 8 1 1 B i l l y
9
9
9
9
3
3
3
3
3
8
4
7
4
3
7
8
5
7
2
8
Course.
StudentName
6
1
9
1
7
5
2
1
F
T
T
B
r
h
o
i
a
o
n
l
D o w n e s
n k
C u
m a s
H
y
O B
l y
D o
r
e
r
w
t
a
i
n
a
l
a
e
i n
y
n
s
L M 0 2 1
L
L
L
L
M
M
M
M
0
0
0
0
5
6
5
2
1
8
1
1
EOF
PERFORM UNTIL StudentRecord = HIGH-VALUES
READ StudentRecords
AT END MOVE HIGH-VALUES TO StudentRecord
END-READ
END-PERFORM.
86
Course.
StudentName
J J J J J J J J J J J J J J J J J J J J J J J J J J J
HIGH-VALUES
9
9
9
9
3
3
3
3
3
8
4
7
4
3
7
8
5
7
2
8
6
1
9
1
7
5
2
1
F
T
T
B
r
h
o
i
a
o
n
l
n k
C u
m a s
H
y
O B
l y
D o
r
e
r
w
t
a
i
n
a
l
a
e
i n
y
n
s
L
L
L
L
M
M
M
M
0
0
0
0
5
6
5
2
1
8
1
1
EOF
PERFORM UNTIL StudentRecord = HIGH-VALUES
READ StudentRecords
AT END MOVE HIGH-VALUES TO StudentRecord
END-READ
END-PERFORM.
87
[FROM
Identifier
AdvanceNum
88
LINE
LINES
me
StudentName
F r a n k
C u r t a i n
Course.
L M 0 5 1
Students.Dat
9 3 3 4 5 6 7 F r a n k
C u r t a i n
L M 0 5 1
EOF
89
StudentName
T h o m a s
H e a l y
Course.
L M 0 6 8
Students.Dat
9 3 3 4 5 6 7 F r a n k
C u r t a i n
9 3 8 3 7 1 5 T h o m a s
H e a l y
L M 0 5 1
L M 0 6 8
EOF
90
91
92
Table of contents
Introduction to COBOL
COBOL Basics 1
COBOL Basics 2
Introduction to Sequential Files
Processing Sequential Files
Simple iteration with the PERFORM verb
Arithmetic and Edited Pictures
Conditions
Tables and the PERFORM ... VARYING
Designing Programs
93
94
OPEN OUTPUT
StudentFile
DISPLAY
"Enter
student details using template below. Press CR to end.".
DISPLAY
"Enter
student details using template below. Press CR to end.".
PERFORM GetStudentDetails
PERFORM UNTIL
GetStudentDetails
PERFORM
StudentDetails = SPACES
PERFORM
StudentDetails = SPACES
WRITE UNTIL
StudentDetails
WRITE
StudentDetails
PERFORM GetStudentDetails
PERFORM GetStudentDetails
END-PERFORM
END-PERFORM
CLOSE StudentFile
CLOSE
StudentFile
STOP
RUN.
STOP RUN.
GetStudentDetails.
GetStudentDetails.
DISPLAY "NNNNNNNSSSSSSSSIIYYMMDDCCCCGGGGS".
DISPLAY StudentDetails.
"NNNNNNNSSSSSSSSIIYYMMDDCCCCGGGGS".
ACCEPT
ACCEPT StudentDetails.
95
$ SET SOURCEFORMAT"FREE"
$ SET SOURCEFORMAT"FREE"
IDENTIFICATION
DIVISION.
IDENTIFICATION
DIVISION.
PROGRAM-ID.
SeqRead.
PROGRAM-ID.
SeqRead.
AUTHOR. Michael Coughlan.
AUTHOR. Michael Coughlan.
ENVIRONMENT DIVISION.
ENVIRONMENT SECTION.
DIVISION.
INPUT-OUTPUT
INPUT-OUTPUT SECTION.
FILE-CONTROL.
FILE-CONTROL.
SELECT StudentFile ASSIGN TO STUDENTS
SELECT
StudentFile
TO STUDENTS
ORGANIZATION
IS ASSIGN
LINE SEQUENTIAL.
ORGANIZATION IS LINE SEQUENTIAL.
DATA DIVISION.
DATASECTION.
DIVISION.
FILE
FILE
SECTION.
FD StudentFile.
FDStudentDetails.
StudentFile.
01
0102
StudentDetails.
StudentId
PIC 9(7).
02 StudentName.
StudentId
PIC 9(7).
02
02 03
StudentName.
Surname
PIC X(8).
03Initials
Surname
PICXX.
X(8).
03
PIC
03 Initials
PIC XX.
02 DateOfBirth.
02 03
DateOfBirth.
YOBirth
PIC 9(2).
03MOBirth
YOBirth
PIC9(2).
9(2).
03
PIC
03
MOBirth
PIC
9(2).
03 DOBirth
PIC 9(2).
03
DOBirth
PIC
9(2).
02 CourseCode
PIC X(4).
02 Grant
CourseCode
PIC9(4).
X(4).
02
PIC
02 Gender
Grant
PICX.
9(4).
02
PIC
02 Gender
PIC X.
PROCEDURE DIVISION.
PROCEDURE DIVISION.
Begin.
Begin.
OPEN INPUT StudentFile
OPEN StudentFile
INPUT StudentFile
READ
READ
AT StudentFile
END MOVE HIGH-VALUES TO StudentDetails
AT
END MOVE HIGH-VALUES TO StudentDetails
END-READ
END-READ
PERFORM
UNTIL StudentDetails = HIGH-VALUES
PERFORM
UNTIL
StudentDetails
= HIGH-VALUES
DISPLAY
StudentId
SPACE StudentName
SPACE CourseCode
DISPLAY
StudentId SPACE StudentName SPACE CourseCode
READ
StudentFile
READ
AT StudentFile
END MOVE HIGH-VALUES TO StudentDetails
AT END MOVE HIGH-VALUES TO StudentDetails
END-READ
END-READ
END-PERFORM
END-PERFORM
CLOSE
StudentFile
CLOSE
StudentFile
STOP
RUN.
STOP RUN.
96
DATA ORGANIZATION
METHOD OF ACCESS
Data organization refers to the way the records of the file are organized on
the backing storage device.
COBOL recognizes three main file organizations;
Sequential
Relative
Indexed
The method of access refers to the way in which records are accessed.
97
Unordered File
RecordA
RecordA
RecordM
RecordM
RecordB
RecordB
RecordH
RecordH
RecordG
RecordG
RecordB
RecordB
RecordH
RecordH
RecordN
RecordN
RecordK
RecordK
RecordA
RecordA
RecordM
RecordM
RecordK
RecordK
RecordN
RecordN
RecordG
RecordG
In an ordered file the records are sequenced on some field in the record.
99
PROGRAM
Unordered
File
RecordF
RecordF
FILE
FILE SECTION.
SECTION.
PROGRAM
RecordM
RecordM
TFRec
RecordP
RecordP
UFRec
RecordW
RecordW
100
RecordH
RecordH
RecordB
RecordB
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
OPEN
OPEN EXTEND
EXTEND UF.
UF.
OPEN
OPEN INPUT
INPUT TF.
TF.
RecordN
RecordN
READ
READ TF.
TF.
MOVE
MOVE TFRec
TFRec TO
TO UFRec.
UFRec.
RecordK
RecordK
WRITE
WRITE UFRec.
UFRec.
RecordG
RecordG
RecordA
RecordA
PROGRAM
FILE
FILE SECTION.
SECTION.
PROGRAM
RecordF
RecordP
RecordP
RecordF
RecordW
RecordW
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
OPEN
OPEN EXTEND
EXTEND UF.
UF.
OPEN
OPEN INPUT
INPUT TF.
TF.
READ
READ TF.
TF.
MOVE
MOVE TFRec
TFRec TO
TO UFRec.
UFRec.
WRITE
WRITE UFRec.
UFRec.
Unordered
File
RecordM
RecordM
RecordH
RecordH
RecordB
RecordB
RecordN
RecordN
RecordA
RecordA
RecordK
RecordK
RecordG
RecordG
RecordF
RecordF
101
Unordered
File
RecordF
RecordF
RecordM
RecordM
RecordP
RecordP
RecordH
RecordH
RecordW
RecordW
RecordB
RecordB
RecordN
RecordN
RESULT
RecordA
RecordA
RecordK
RecordK
RecordG
RecordG
RecordF
RecordF
RecordP
RecordP
RecordW
RecordW
102
103
104
The only way to delete Sequential file records is to create a new file
which does not contain them.
Why?
New File
RecordM
RecordM
RecordK
RecordK
RecordM
RecordM
Delete UF
Record?
NO
Unordered File
RecordM
RecordM
RecordH
RecordH
RecordB
RecordB
RecordN
RecordN
RecordA
RecordA
RecordK
RecordK
105
New File
RecordK
RecordK
RecordM
RecordM
Unordered File
Delete UF
Record?
NO
RecordH
RecordH
RecordM
RecordM
RecordH
RecordH
RecordB
RecordB
RecordN
RecordN
RecordA
RecordA
RecordK
RecordK
106
RecordB
RecordB
RecordM
RecordM
RecordK
RecordK
Unordered File
RecordM
RecordM
Delete UF
Record?
YES
RecordH
RecordH
RecordM
RecordM
RecordH
RecordH
RecordB
RecordB
RecordN
RecordN
RecordA
RecordA
RecordK
RecordK
107
RecordK
RecordK
RecordM
RecordM
Unordered File
RecordM
RecordM
Delete UF
Record?
NO
RecordH
RecordH
RecordN
RecordN
RecordH
RecordH
RecordB
RecordB
RecordN
RecordN
RecordA
RecordA
But wait...
We should have deleted RecordM.
Too late. Its already been written to
the new file.
RecordK
RecordK
108
Transaction File
RecordB
RecordB
FILE
FILE SECTION.
SECTION.
TFRec
RecordK
RecordK
OFRec
RecordM
RecordM
Ordered File
RecordA
RecordA
RecordB
RecordB
RecordG
RecordG
RecordH
RecordH
RecordK
RecordK
RecordM
RecordM
RecordN
RecordN
109
New File
NFRec
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
OPEN
INPUT
OPEN INPUT TF.
TF.
OPEN
INPUT
OF
OPEN INPUT OF
OPEN
OPEN OUTPUT
OUTPUT NF.
NF.
READ
TF.
READ TF.
READ
READ OF.
OF.
IF
TFKey
IF TFKey NOT
NOT == OFKey
OFKey
MOVE
OFRec
TO
MOVE OFRec TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ OF
OF
ELSE
ELSE
READ
READ TF
TF
READ
OF
READ OF
END-IF.
END-IF.
Transaction File
RecordB
RecordB
RecordK
RecordK
RecordM
RecordM
Ordered File
RecordA
RecordA
RecordB
RecordB
RecordG
RecordG
RecordH
RecordH
RecordK
RecordK
RecordM
RecordM
RecordN
RecordN
110
FILE
FILE SECTION.
SECTION.
RecordB
New File
RecordA
RecordA
RecordA
RecordA
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
OPEN
INPUT
OPEN INPUT TF.
TF.
OPEN
INPUT
OF
OPEN INPUT OF
OPEN
OPEN OUTPUT
OUTPUT NF.
NF.
READ
TF.
READ TF.
READ
READ OF.
OF.
IF
TFRec
IF TFRec NOT
NOT == OFRec
OFRec
MOVE
OFRec
TO
MOVE OFRec TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ OF
OF
ELSE
ELSE
READ
READ TF
TF
READ
OF
READ OF
END-IF.
END-IF.
Problem !!
How can we recognize
which record we want
to delete?
By its Key Field
2004 IBM Corporation
Transaction File
RecordB
RecordB
RecordK
RecordK
RecordM
RecordM
Ordered File
RecordA
RecordA
RecordB
RecordB
RecordG
RecordG
RecordH
RecordH
RecordK
RecordK
RecordM
RecordM
RecordN
RecordN
111
FILE
FILE SECTION.
SECTION.
RecordB
New File
RecordA
RecordA
RecordB
RecordA
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
OPEN
INPUT
OPEN INPUT TF.
TF.
OPEN
INPUT
OF
OPEN INPUT OF
OPEN
OPEN OUTPUT
OUTPUT NF.
NF.
READ
TF.
READ TF.
READ
READ OF.
OF.
IF
TFKey
IF TFKey NOT
NOT == OFKey
OFKey
MOVE
OFRec
TO
MOVE OFRec TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ OF
OF
ELSE
ELSE
READ
READ TF
TF
READ
OF
READ OF
END-IF.
END-IF.
Transaction File
RecordB
RecordB
RecordK
RecordK
RecordM
RecordM
Ordered File
RecordA
RecordA
RecordB
RecordB
RecordG
RecordG
RecordH
RecordH
RecordK
RecordK
RecordM
RecordM
RecordN
RecordN
112
FILE
FILE SECTION.
SECTION.
RecordK
RecordG
New File
RecordA
RecordA
RecordG
RecordG
RecordG
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
OPEN
INPUT
OPEN INPUT TF.
TF.
OPEN
INPUT
OF
OPEN INPUT OF
OPEN
OPEN OUTPUT
OUTPUT NF.
NF.
READ
TF.
READ TF.
READ
READ OF.
OF.
IF
TFKey
IF TFKey NOT
NOT == OFKey
OFKey
MOVE
OFRec
TO
MOVE OFRec TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ OF
OF
ELSE
ELSE
READ
READ TF
TF
READ
OF
READ OF
END-IF.
END-IF.
New File
RecordM
RecordM
RecordA
RecordA
RecordG
RecordG
Ordered File
RecordA
RecordA
RecordB
RecordB
RecordG
RecordG
RecordH
RecordH
RecordK
RecordK
RecordM
RecordM
RecordN
RecordN
113
RecordH
RecordH
RESULT
RecordN
RecordN
114
PROGRAM
New File
FILE
FILE SECTION.
SECTION.
RecordH
RecordH
TFRec
OFRec
RecordK
RecordK
NFRec
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
Ordered File
OPEN
INPUT
OPEN INPUT TF.
TF.
OPEN
INPUT
OF
OPEN INPUT OF
RecordA
OPEN
RecordA
OPEN OUTPUT
OUTPUT NF.
NF.
READ
TF.
READ TF.
RecordB
RecordB
READ
READ OF.
OF.
RecordG
IF
TFKey
RecordG
IF TFKey == OFKey
OFKey
Update
OFRec
Update OFRec with
with TFRec
TFRec
RecordH
RecordH
MOVE
OFRec+
TO
NFRec
MOVE OFRec+ TO NFRec
WRITE
RecordK
WRITE NFRec
NFRec
RecordK
READ
TF
READ TF
RecordM
RecordM
READ
READ OF
OF
ELSE
RecordN
ELSE
RecordN
MOVE
MOVE OFRec
OFRec TO
TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ OF
OF
COBOL Programming Fundamental
END-IF.
END-IF.
115
PROGRAM
FILE
FILE SECTION.
SECTION.
RecordB
RecordH
RecordH
RecordA
RecordK
RecordK
RecordA
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
OPEN
INPUT
Ordered File
OPEN INPUT TF.
TF.
OPEN
INPUT
OF
OPEN INPUT OF
OPEN
RecordA
OPEN OUTPUT
OUTPUT NF.
NF.
RecordA
READ
TF.
READ TF.
RecordB
READ
RecordB
READ OF.
OF.
IF
TFKey
RecordG
IF TFKey == OFKey
OFKey
RecordG
Update
OFRec
Update OFRec with
with TFRec
TFRec
RecordH
MOVE
OFRec+
TO
NFRec
RecordH
MOVE OFRec+ TO NFRec
WRITE
NFRec
WRITE
NFRec
RecordK
RecordK
READ
TF
READ TF
RecordM
READ
RecordM
READ OF
OF
ELSE
ELSE
RecordN
RecordN
MOVE
MOVE OFRec
OFRec TO
TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ OF
OF
END-IF.
COBOL Programming Fundamental
END-IF.
New File
RecordA
RecordA
PROGRAM
Transaction File
RecordB
RecordB
RecordH
RecordH
RecordK
RecordK
116
FILE
FILE SECTION.
SECTION.
RecordB
RecordB
New File
RecordA
RecordA
RecordB
+
RecordB+
RecordB+
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
OPEN
INPUT
OPEN INPUT TF.
TF.
OPEN
INPUT
OF
Ordered File
OPEN INPUT OF
OPEN
OPEN OUTPUT
OUTPUT NF.
NF.
READ
TF.
RecordA
READ TF.
RecordA
READ
READ OF.
OF.
RecordB
IF
TFKey
RecordB
IF TFKey == OFKey
OFKey
Update
OFRec
with
TFRec
Update
OFRec
with
TFRec
RecordG
RecordG
MOVE
OFRec+
TO
NFRec
MOVE OFRec+ TO NFRec
RecordH
WRITE
RecordH
WRITE NFRec
NFRec
READ
TF
READ TF
RecordK
RecordK
READ
READ OF
OF
RecordM
ELSE
RecordM
ELSE
MOVE
MOVE OFRec
OFRec TO
TO NFRec
NFRec
RecordN
RecordN
WRITE
NFRec
WRITE NFRec
READ
COBOL Programming Fundamental
READ OF
OF
END-IF.
END-IF.
PROGRAM
FILE
FILE SECTION.
SECTION.
Transaction File
RecordH
RecordB
RecordB
RecordG
RecordH
RecordH
RecordG
117
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
OPEN
INPUT
RecordK
OPEN INPUT TF.
TF.
RecordK
OPEN
INPUT
OF
OPEN INPUT OF
OPEN
OPEN OUTPUT
OUTPUT NF.
NF.
Ordered File
READ
TF.
READ TF.
READ
READ OF.
OF.
RecordA
IF
TFKey
RecordA
IF TFKey == OFKey
OFKey
Update
OFRec
RecordB
Update OFRec with
with TFRec
TFRec
RecordB
MOVE
OFRec+
TO
NFRec
MOVE OFRec+ TO NFRec
RecordG
WRITE
RecordG
WRITE NFRec
NFRec
READ
TF
RecordH
READ TF
RecordH
READ
READ OF
OF
RecordK
ELSE
RecordK
ELSE
MOVE
MOVE OFRec
OFRec TO
TO NFRec
NFRec
RecordM
RecordM
WRITE
NFRec
WRITE NFRec
RecordN
READ
RecordN
READ OF
OF
COBOL Programming Fundamental
END-IF.
END-IF.
New File
RecordA
RecordA
RecordB+
RecordB+
RecordG
RecordG
PROGRAM
Transaction File
RecordC
RecordC
New File
FILE
FILE SECTION.
SECTION.
TFRec
RecordF
RecordF
OFRec
RecordP
RecordP
NFRec
Ordered File
RecordA
RecordA
RecordB
RecordB
RecordG
RecordG
RecordH
RecordH
RecordK
RecordK
RecordM
RecordM
RecordN
RecordN
118
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
OPEN
INPUT
OPEN INPUT TF.
TF.
OPEN
INPUT
OF
OPEN INPUT OF
OPEN
OPEN OUTPUT
OUTPUT NF.
NF.
READ
TF.
READ TF.
READ
READ OF.
OF.
IF
TFKey
IF TFKey << OFKey
OFKey
MOVE
TFRec
MOVE TFRec TO
TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ TF
TF
ELSE
ELSE
MOVE
MOVE OFRec
OFRec TO
TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ OF
OF
END-IF.
END-IF.
Transaction File
RecordC
RecordC
RecordF
RecordF
RecordP
RecordP
Ordered File
RecordA
RecordA
RecordB
RecordB
RecordG
RecordG
RecordH
RecordH
RecordK
RecordK
RecordM
RecordM
RecordN
RecordN
119
FILE
FILE SECTION.
SECTION.
RecordC
New File
RecordA
RecordA
RecordA
RecordA
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
OPEN
INPUT
OPEN INPUT TF.
TF.
OPEN
INPUT
OF
OPEN INPUT OF
OPEN
OPEN OUTPUT
OUTPUT NF.
NF.
READ
TF.
READ TF.
READ
READ OF.
OF.
IF
TFKey
IF TFKey << OFKey
OFKey
MOVE
TFRec
MOVE TFRec TO
TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ TF
TF
ELSE
ELSE
MOVE
MOVE OFRec
OFRec TO
TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ OF
OF
END-IF.
END-IF.
Transaction File
RecordC
RecordC
RecordF
RecordF
RecordP
RecordP
Ordered File
RecordA
RecordA
RecordB
RecordB
RecordG
RecordG
RecordH
RecordH
RecordK
RecordK
RecordM
RecordM
RecordN
RecordN
120
FILE
FILE SECTION.
SECTION.
RecordC
RecordB
New File
RecordA
RecordA
RecordB
RecordB
RecordB
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
OPEN
INPUT
OPEN INPUT TF.
TF.
OPEN
INPUT
OF
OPEN INPUT OF
OPEN
OPEN OUTPUT
OUTPUT NF.
NF.
READ
TF.
READ TF.
READ
READ OF.
OF.
IF
TFKey
IF TFKey << OFKey
OFKey
MOVE
TFRec
MOVE TFRec TO
TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ TF
TF
ELSE
ELSE
MOVE
MOVE OFRec
OFRec TO
TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ OF
OF
END-IF.
END-IF.
Transaction File
RecordC
RecordC
RecordF
RecordF
RecordP
RecordP
Ordered File
RecordA
RecordA
RecordB
RecordB
RecordG
RecordG
RecordH
RecordH
RecordK
RecordK
RecordM
RecordM
RecordN
RecordN
121
FILE
FILE SECTION.
SECTION.
RecordC
RecordG
RecordC
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
OPEN
INPUT
OPEN INPUT TF.
TF.
OPEN
INPUT
OF
OPEN INPUT OF
OPEN
OPEN OUTPUT
OUTPUT NF.
NF.
READ
TF.
READ TF.
READ
READ OF.
OF.
IF
TFKey
IF TFKey << OFKey
OFKey
MOVE
TFRec
MOVE TFRec TO
TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ TF
TF
ELSE
ELSE
MOVE
MOVE OFRec
OFRec TO
TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ OF
OF
END-IF.
END-IF.
New File
RecordA
RecordA
RecordB
RecordB
RecordC
RecordC
Transaction File
RecordC
RecordC
RecordF
RecordF
RecordP
RecordP
Ordered File
RecordA
RecordA
RecordB
RecordB
RecordG
RecordG
RecordH
RecordH
RecordK
RecordK
RecordM
RecordM
RecordN
RecordN
122
FILE
FILE SECTION.
SECTION.
RecordF
RecordG
RecordF
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
OPEN
INPUT
OPEN INPUT TF.
TF.
OPEN
INPUT
OF
OPEN INPUT OF
OPEN
OPEN OUTPUT
OUTPUT NF.
NF.
READ
TF.
READ TF.
READ
READ OF.
OF.
IF
TFKey
IF TFKey << OFKey
OFKey
MOVE
TFRec
MOVE TFRec TO
TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ TF
TF
ELSE
ELSE
MOVE
MOVE OFRec
OFRec TO
TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ OF
OF
END-IF.
END-IF.
New File
RecordA
RecordA
RecordB
RecordB
RecordC
RecordC
RecordF
RecordF
PROGRAM
Transaction File
RecordC
RecordC
RecordF
RecordF
RecordP
RecordP
FILE
FILE SECTION.
SECTION.
RecordP
RecordG
RecordG
Ordered File
RecordA
RecordA
RecordB
RecordB
RecordG
RecordG
RecordH
RecordH
RecordK
RecordK
RecordM
RecordM
RecordN
RecordN
123
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
OPEN
INPUT
OPEN INPUT TF.
TF.
OPEN
INPUT
OF
OPEN INPUT OF
OPEN
OPEN OUTPUT
OUTPUT NF.
NF.
READ
TF.
READ TF.
READ
READ OF.
OF.
IF
TFKey
IF TFKey << OFKey
OFKey
MOVE
TFRec
MOVE TFRec TO
TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ TF
TF
ELSE
ELSE
MOVE
MOVE OFRec
OFRec TO
TO NFRec
NFRec
WRITE
NFRec
WRITE NFRec
READ
READ OF
OF
END-IF.
END-IF.
New File
RecordA
RecordA
RecordB
RecordB
RecordC
RecordC
RecordF
RecordF
RecordG
RecordG
EXERCISE 2
124
Table of contents
Introduction to COBOL
COBOL Basics 1
COBOL Basics 2
Introduction to Sequential Files
Processing Sequential Files
Simple iteration with the PERFORM verb
Arithmetic and Edited Pictures
Conditions
Tables and the PERFORM ... VARYING
Designing Programs
125
126
Non-Iteration PERFORM.
GO TO and PERFORM....THRU.
PERFORM n TIMES.
127
128
NOTE
NOTE
The
Thescope
scopeof
ofProcessRecord
ProcessRecordis
isdelimited
delimited
by
bythe
theoccurrence
occurrencethe
theparagraph
paragraphname
name
ProduceOutput.
ProduceOutput.
129
THRU
PERFORM 1stProc
EndProc
THROUGH
130
In
In TopLevel.
TopLevel. Starting
Starting to
to run
run program
program
>>>>
>>>> Now
Now in
in OneLevelDown
OneLevelDown
>>>>>>>>
Now
>>>>>>>> Now in
in TwoLevelsDown.
TwoLevelsDown.
>>>>
Back
in
OneLevelDown
>>>> Back in OneLevelDown
Back
Back in
in TopLevel.
TopLevel.
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
TopLevel
.
TopLevel.
DISPLAY
. Starting
DISPLAY"In
"InTopLevel
TopLevel.
Startingto
torun
runprogram"
program"
PERFORM
PERFORM OneLevelDown
OneLevelDown
DISPLAY
"Back
DISPLAY "Back in
in TopLevel.".
TopLevel.".
STOP
RUN.
STOP RUN.
TwoLevelsDown.
TwoLevelsDown.
DISPLAY
DISPLAY ">>>>>>>>
">>>>>>>> Now
Now in
in TwoLevelsDown."
TwoLevelsDown."
OneLevelDown.
OneLevelDown.
DISPLAY
DISPLAY ">>>>
">>>> Now
Now in
in OneLevelDown"
OneLevelDown"
PERFORM
TwoLevelsDown
PERFORM TwoLevelsDown
DISPLAY
DISPLAY ">>>>
">>>> Back
Back in
in OneLevelDown".
OneLevelDown".
131
In
In TopLevel.
TopLevel. Starting
Starting to
to run
run program
program
>>>>
Now
in
OneLevelDown
>>>> Now in OneLevelDown
>>>>>>>>
>>>>>>>> Now
Now in
in TwoLevelsDown.
TwoLevelsDown.
>>>>
Back
in
OneLevelDown
>>>> Back in OneLevelDown
Back
Back in
in TopLevel.
TopLevel.
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
TopLevel
.
TopLevel.
DISPLAY
DISPLAY "In
"In TopLevel.
TopLevel. Starting
Starting to
to run
run program"
program"
PERFORM
PERFORMOneLevelDown
OneLevelDown
DISPLAY
DISPLAY "Back
"Back in
in TopLevel.".
TopLevel.".
STOP
RUN.
STOP RUN.
TwoLevelsDown.
TwoLevelsDown.
DISPLAY
DISPLAY ">>>>>>>>
">>>>>>>> Now
Now in
in TwoLevelsDown."
TwoLevelsDown."
OneLevelDown.
OneLevelDown.
DISPLAY
DISPLAY ">>>>
">>>> Now
Now in
in OneLevelDown"
OneLevelDown"
PERFORM
TwoLevelsDown
PERFORM TwoLevelsDown
DISPLAY
DISPLAY ">>>>
">>>> Back
Back in
in OneLevelDown".
OneLevelDown".
132
Run of PerformFormat1
In
In TopLevel.
TopLevel. Starting
Starting to
to run
run program
program
>>>>
>>>> Now
Now in
in OneLevelDown
OneLevelDown
>>>>>>>>
>>>>>>>> Now
Now in
in TwoLevelsDown.
TwoLevelsDown.
>>>>
Back
in
OneLevelDown
>>>> Back in OneLevelDown
Back
Back in
in TopLevel.
TopLevel.
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
TopLevel.
TopLevel.
DISPLAY
DISPLAY "In
"In TopLevel.
TopLevel. Starting
Starting to
to run
run program"
program"
PERFORM
OneLevelDown
PERFORM OneLevelDown
DISPLAY
DISPLAY "Back
"Back in
in TopLevel.".
TopLevel.".
STOP
RUN.
STOP RUN.
TwoLevelsDown.
TwoLevelsDown.
DISPLAY
DISPLAY ">>>>>>>>
">>>>>>>> Now
Now in
in TwoLevelsDown."
TwoLevelsDown."
OneLevelDown
.
OneLevelDown.
DISPLAY
"
DISPLAY">>>>
">>>>Now
NowininOneLevelDown
OneLevelDown"
PERFORM
PERFORM TwoLevelsDown
TwoLevelsDown
DISPLAY
">>>>
DISPLAY ">>>> Back
Back in
in OneLevelDown".
OneLevelDown".
133
Run of PerformFormat1
In
In TopLevel.
TopLevel. Starting
Starting to
to run
run program
program
>>>>
Now
in
OneLevelDown
>>>> Now in OneLevelDown
>>>>>>>>
>>>>>>>> Now
Now in
in TwoLevelsDown.
TwoLevelsDown.
>>>>
Back
in
OneLevelDown
>>>> Back in OneLevelDown
Back
Back in
in TopLevel.
TopLevel.
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
TopLevel.
TopLevel.
DISPLAY
DISPLAY "In
"In TopLevel.
TopLevel. Starting
Starting to
to run
run program"
program"
PERFORM
OneLevelDown
PERFORM OneLevelDown
DISPLAY
DISPLAY "Back
"Back in
in TopLevel.".
TopLevel.".
STOP
RUN.
STOP RUN.
TwoLevelsDown.
TwoLevelsDown.
DISPLAY
DISPLAY ">>>>>>>>
">>>>>>>> Now
Now in
in TwoLevelsDown."
TwoLevelsDown."
OneLevelDown
.
OneLevelDown.
DISPLAY
DISPLAY ">>>>
">>>> Now
Now in
in OneLevelDown"
OneLevelDown"
PERFORM
PERFORMTwoLevelsDown
TwoLevelsDown
DISPLAY
DISPLAY ">>>>
">>>> Back
Back in
in OneLevelDown".
OneLevelDown".
134
Run of PerformFormat1
In
In TopLevel.
TopLevel. Starting
Starting to
to run
run program
program
>>>>
Now
in
OneLevelDown
>>>> Now in OneLevelDown
>>>>>>>>
>>>>>>>> Now
Now in
in TwoLevelsDown.
TwoLevelsDown.
>>>>
>>>> Back
Back in
in OneLevelDown
OneLevelDown
Back
in
TopLevel.
Back in TopLevel.
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
TopLevel.
TopLevel.
DISPLAY
DISPLAY "In
"In TopLevel.
TopLevel. Starting
Starting to
to run
run program"
program"
PERFORM
OneLevelDown
PERFORM OneLevelDown
DISPLAY
DISPLAY "Back
"Back in
in TopLevel.".
TopLevel.".
STOP
RUN.
STOP RUN.
TwoLevelsDown
.
TwoLevelsDown.
DISPLAY
."
DISPLAY">>>>>>>>
">>>>>>>>Now
NowininTwoLevelsDown
TwoLevelsDown."
OneLevelDown.
OneLevelDown.
DISPLAY
DISPLAY ">>>>
">>>> Now
Now in
in OneLevelDown"
OneLevelDown"
PERFORM
TwoLevelsDown
PERFORM TwoLevelsDown
DISPLAY
DISPLAY ">>>>
">>>> Back
Back in
in OneLevelDown".
OneLevelDown".
135
Run of PerformFormat1
In
In TopLevel.
TopLevel. Starting
Starting to
to run
run program
program
>>>>
Now
in
OneLevelDown
>>>> Now in OneLevelDown
>>>>>>>>
>>>>>>>> Now
Now in
in TwoLevelsDown.
TwoLevelsDown.
>>>>
>>>> Back
Back in
in OneLevelDown
OneLevelDown
Back
Back in
in TopLevel.
TopLevel.
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
TopLevel.
TopLevel.
DISPLAY
DISPLAY "In
"In TopLevel.
TopLevel. Starting
Starting to
to run
run program"
program"
PERFORM
OneLevelDown
PERFORM OneLevelDown
DISPLAY
DISPLAY "Back
"Back in
in TopLevel.".
TopLevel.".
STOP
RUN.
STOP RUN.
TwoLevelsDown.
TwoLevelsDown.
DISPLAY
DISPLAY ">>>>>>>>
">>>>>>>> Now
Now in
in TwoLevelsDown."
TwoLevelsDown."
OneLevelDown
.
OneLevelDown.
DISPLAY
DISPLAY ">>>>
">>>> Now
Now in
in OneLevelDown"
OneLevelDown"
PERFORM
TwoLevelsDown
PERFORM TwoLevelsDown
DISPLAY
".
DISPLAY">>>>
">>>>Back
BackininOneLevelDown
OneLevelDown".
136
In
In TopLevel.
TopLevel. Starting
Starting to
to run
run program
program
>>>>
Now
in
OneLevelDown
>>>> Now in OneLevelDown
>>>>>>>>
>>>>>>>> Now
Now in
in TwoLevelsDown.
TwoLevelsDown.
>>>>
Back
in
OneLevelDown
>>>> Back in OneLevelDown
Back
Back in
in TopLevel.
TopLevel.
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
TopLevel
.
TopLevel.
DISPLAY
DISPLAY "In
"In TopLevel.
TopLevel. Starting
Starting to
to run
run program"
program"
PERFORM
OneLevelDown
PERFORM OneLevelDown
DISPLAY
.".
DISPLAY"Back
"BackininTopLevel
TopLevel.".
STOP
STOP RUN.
RUN.
TwoLevelsDown.
TwoLevelsDown.
DISPLAY
DISPLAY ">>>>>>>>
">>>>>>>> Now
Now in
in TwoLevelsDown."
TwoLevelsDown."
OneLevelDown.
OneLevelDown.
DISPLAY
DISPLAY ">>>>
">>>> Now
Now in
in OneLevelDown"
OneLevelDown"
PERFORM
TwoLevelsDown
PERFORM TwoLevelsDown
DISPLAY
DISPLAY ">>>>
">>>> Back
Back in
in OneLevelDown".
OneLevelDown".
137
Statements
Statements
Statements
Statements
IF
IF NoErrorFound
NoErrorFound
Statements
Statements
Statements
Statements
IF
IF NoErrorFound
NoErrorFound
Statements
Statements
Statements
Statements
Statements
Statements
END-IF
END-IF
END-IF.
END-IF.
138
Statements
Statements
Statements
IF
IF ErrorFound
ErrorFound GO
GO TO
TO SumSalesExit
SumSalesExit
END-IF
END-IF
Statements
Statements
Statements
Statements
Statements
Statements
IF
IF ErrorFound
ErrorFound GO
GO TO
TO SumSalesExit
SumSalesExit
END-IF
END-IF
Statements
Statements
SumSalesExit.
SumSalesExit.
EXIT.
EXIT.
139
THRU
1stProc
THROUGH
RepeatCoun
t TIMES
[StatementB
EndProc
PROCEDURE
PROCEDUREDIVISION.
DIVISION.
Begin.
Begin.
Statements
STOP RUN.
DisplayName.
DisplayName.
DISPLAY Tom Ryan.
140
Run of PerformExample2
Starting to run program
Starting is
toan
run
>>>>This
inprogram
line Perform
>>>>This is an in line Perform
>>>>This is an in line Perform
>>>>This is
isan
an in
inline
linePerform
Perform
>>>>This
>>>>This
is
an
in
line
Finished in line PerformPerform
Finished
Perform
>>>>
This in
is line
an out
of line Perform
>>>> This is an out of line Perform
>>>> This is an out of line Perform
>>>>This
Thisis
isan
anout
out of
ofline
line Perform
Perform
>>>>
>>>>This
Thisis
isan
anout
out of
ofline
line Perform
Perform
>>>>
>>>> This is an out of line Perform
>>>> This is an out of line Perform
>>>>in
This
is an
out of
Back
Begin.
About
to line
Stop Perform
Back in Begin. About to Stop
PROCEDURE DIVISION.
PROCEDURE DIVISION.
Begin.
Begin.
DISPLAY "Starting to run program"
DISPLAY "Starting to run program"
PERFORM 3 TIMES
PERFORM
3 TIMES
DISPLAY
">>>>This is an in line Perform"
DISPLAY
END-PERFORM ">>>>This is an in line Perform"
END-PERFORM
DISPLAY "Finished in line Perform"
DISPLAY "Finished in line Perform"
PERFORM OutOfLineEG NumOfTimes TIMES
PERFORM"Back
OutOfLineEG
NumOfTimes
DISPLAY
in Begin.
About toTIMES
Stop".
DISPLAY
"Back
in
Begin.
About
to
Stop".
STOP RUN.
STOP RUN.
OutOfLineEG.
OutOfLineEG.
DISPLAY ">>>> This is an out of line Perform".
DISPLAY ">>>> This is an out of line Perform".
141
142
THRU
1stProc
THROUGH
UNTIL Condition
[StatementB lock END
EndProc
BEFORE
WITH
TEST
AFTER
- PERFORM
PERFORM
PERFORMWITH
WITH
TEST
TESTBEFORE
BEFORE==
WHILE
WHILE...
...DO
DO
Loop Body
test
False
True
Next Statement
143
Loop Body
test
False
True
Next Statement
2004 IBM Corporation
144
145
With the read ahead strategy we always try to stay one data item
ahead of the processing.
Algorithm Template
READ StudentRecords
AT END MOVE HIGHHIGH-VALUES TO StudentRecord
ENDEND-READ
PERFORM UNTIL StudentRecord = HIGHHIGH-VALUES
DISPLAY StudentRecord
READ StudentRecords
AT END MOVE HIGHHIGH-VALUES TO StudentRecord
ENDEND-READ
ENDEND-PERFORM
146
RUN OF SeqRead
9456789 COUGHLANMS LM51
9456789 COUGHLANMS LM51
9367892 RYAN
TG LM60
9367892 RYAN
TG LM60
9368934 WILSON HR LM61
9368934 WILSON HR LM61
PROCEDURE
PROCEDURE DIVISION.
DIVISION.
Begin.
Begin.
OPEN
OPEN INPUT
INPUT StudentFile
StudentFile
READ
READ StudentFile
StudentFile
AT
END
MOVE
HIGH-VALUES
TO
StudentDetails
AT
END
MOVE
HIGH-VALUES
TO
StudentDetails
END-READ
END-READUNTIL StudentDetails = HIGH-VALUES
PERFORM
PERFORM UNTIL StudentDetails = HIGH-VALUES
DISPLAY
StudentId
SPACE
StudentName
SPACE
CourseCode
DISPLAY
StudentId
SPACE
StudentName
SPACE
CourseCode
READ
StudentFile
READ StudentFile
AT
END
MOVE
HIGH-VALUES
TO
StudentDetails
AT
END
MOVE
HIGH-VALUES
TO
StudentDetails
END-READ
END-READ
END-PERFORM
END-PERFORM
CLOSE
StudentFile
CLOSE
StudentFile
STOP
RUN.
STOP RUN.
147
Table of contents
Introduction to COBOL
COBOL Basics 1
COBOL Basics 2
Introduction to Sequential Files
Processing Sequential Files
Simple iteration with the PERFORM verb
Arithmetic and Edited Pictures
Conditions
Tables and the PERFORM ... VARYING
Designing Programs
148
149
ROUNDED option.
Simple Insertion.
Special Insertion.
Fixed Insertion.
Floating Insertion.
Identifier K
[ROUNDED
Identifier
GIVING
Identifier
K
TO
Identifier FROM
VERB
BY
Literal
INTO
150
The exceptions are the COMPUTE and the DIVIDE with REMAINDER.
COBOL Programming Fundamental
151
PIC 9(3)V9.
123.25
123.2
123.3
PIC 9(3).
123.25
123
123
152
Actual Result
245.96
1245.9
PIC 9(3).
124
PIC 9(3).
1246
SIZE ERROR
Yes
Yes
No
124.45
124.45
Yes
Yes
No
3124.45
Yes
A size error condition exists when, after decimal point alignment, the
result is truncated on either the left or the right hand side.
Before
Before
After
After
Before
Before
After
After
Before
Before
After
After
153
ADD
ADD Cash
Cash TO
TO Total.
Total.
33
1000
1000
3
1003
ADD
ADD Cash,
Cash, 20
20 TO
TO
33
3
Total,
Total, Wage.
Wage.
1000
1000 100
100
1023
123
ADD
ADD Cash,
Cash, Total
TotalGIVING
GIVINGResult.
Result.
33
1000
0015
1000
0015
3
1000
1003
ADD
ADDMales
MalesTO
TOFemales
FemalesGIVING
GIVING TotalStudents.
TotalStudents.
1500
0625
1234
1500
0625
1234
1500
0625
2125
2004 IBM Corporation
Before
Before
After
After
Before
Before
After
After
Before
Before
After
After
154
SUBTRACT
SUBTRACT Tax
Tax FROM
FROMGrossPay,
GrossPay,Total.
Total.
120
4000
9120
120
4000
9120
120
3880
9000
SUBTRACT
SUBTRACT Tax,
Tax,80
80FROM
FROMTotal.
Total.
100
480
100
480
100
300
SUBTRACT
SUBTRACT Tax
Tax FROM
FROMGrossPay
GrossPayGIVING
GIVINGNetPay.
NetPay.
750
1000
0012
750
1000
0012
750
1000
0250
Members
Members
Before
Before
After
After
15.50
15.50
15.50
Before
Before
After
After
MULTIPLY
MULTIPLY10
10BY
BYMagnitude,
Magnitude, Size.
Size.
355
125
355
125
3550
1250
Before
Before
After
After
155
100
100
100
TotalSubs
TotalSubs
0123.45
0123.45
1550.00
DIVIDE
DIVIDE Total
Total BY
BY Members
MembersGIVING
GIVINGAverage
Average ROUNDED.
ROUNDED.
9234.55
100
1234.56
9234.55
100
1234.56
9234.55
COBOL Programming Fundamental
100
92.35
2004 IBM Corporation
DIVIDE
Before
Before
After
After
156
Identifier
Identifier
INTO
GIVING {Identifier [ ROUNDED
Literal
Literal
ON SIZE ERROR
Identifier
Identifier
BY
Literal
Literal
ON SIZE ERROR
GIVING
{Identifier
StatementB
[ ROUNDED
]} REMAINDER
]} REMAINDER
Identifier
Identifier
DIVIDE
DIVIDE201
201BY
BY10
10GIVING
GIVINGQuotient
Quotient REMAINDER
REMAINDERRemain.
Remain.
209
424
209
424
020
001
StatementB
lock
END
COMPUTE
NOT
ON
SIZE
ERROR
Precedence
Precedence Rules.
Rules.
1.
1.
2.
2.
3.
3.
Before
Before
After
After
157
****
**
//
++
--
==
==
==
==
==
POWER
POWER
MULTIPLY
MULTIPLY
DIVIDE
DIVIDE
ADD
ADD
SUBTRACT
SUBTRACT
NNNN
xx
++
--
Compute
ComputeIrishPrice
IrishPrice==SterlingPrice
SterlingPrice//Rate
Rate ** 100.
100.
1000.50
156.25
87
1000.50
156.25
87
179.59
156.25
87
Edited Pictures are PICTURE clauses which format data intended for output to
screen or printer.
The term edit is used because the edit symbols have the effect of changing, or
editing, the data inserted into the edited item.
Edited items can not be used as operands in a computation but they may be
used as the result or destination of a computation (i.e. to the right of the word
GIVING).
158
159
Simple Insertion
Special Insertion
Fixed Insertion
Floating Insertion
Zero suppression and replacement with spaces
Zero suppression and replacement with asterisks
Edit Symbol
,, B
B 00 //
..
++ -- CR
CR DB
DB $$
++ -- SS
ZZ **
160
Editing Type
Simple
SimpleInsertion
Insertion
Special
SpecialInsertion
Insertion
Fixed
FixedInsertion
Insertion
Floating
FloatingInsertion
Insertion
Suppression
Suppression and
and Replacement
Replacement
161
Sending
Sending
Picture
Data
Picture
Data
PIC
PIC999999
999999 123456
123456
PIC
000078
PIC9(6)
9(6)
000078
PIC
000078
PIC9(6)
9(6)
000078
PIC
000178
PIC9(6)
9(6)
000178
PIC
002178
PIC9(6)
9(6)
002178
Receiving
Receiving
Picture
Result
Picture
Result
PIC
123,456
PIC999,999
999,999
PIC
000,078
PIC9(3),9(3)
9(3),9(3)
PIC
78
PICZZZ,ZZZ
ZZZ,ZZZ
PIC
****178
PIC***,***
***,***
PIC
**2,178
PIC***,***
***,***
PIC
PIC9(6)
9(6)
PIC
PIC9(6)
9(6)
PIC
PIC9(6)
9(6)
PIC
PIC99B99B99
99B99B99
PIC
PIC99/99/99
99/99/99
PIC
PIC990099
990099
120183
120183
120183
120183
001245
001245
12 01 83
12/01/83
120045
2004 IBM Corporation
162
Sending
Sending
Picture
Data
Picture
Data
PIC
PIC999V99
999V99 12345
12345
Receiving
Receiving
Picture
Result
Picture
Result
PIC
123.45
PIC999.99
999.99
PIC
PIC999V99
999V99 02345
02345
PIC
PIC999.9
999.9
PIC
PIC999V99
999V99 51234
51234
PIC
PIC99.99
99.99
PIC
PIC999
999
PIC
PIC999.99
999.99
456
456
023.4
12.34
456.00
163
Sending
Sending
Picture
Data
Picture
Data
PIC
-123
PICS999
S999
-123
PIC
-123
PICS999
S999
-123
PIC
+123
PICS999
S999
+123
Receiving
Receiving
Picture
Result
Picture
Result
PIC
-123
PIC-999
-999
PIC
123PIC 999999PIC
123
PIC-999
-999
PIC
PICS9(5)
S9(5)
PIC
PICS9(3)
S9(3)
PIC
PICS9(3)
S9(3)
PIC
PIC+9(5)
+9(5)
PIC
PIC+9(3)
+9(3)
PIC
PIC999+
999+
+12345
+12345
-123
-123
-123
-123
+12345
-123
123 2004 IBM Corporation
164
Sending
Sending
Picture
Data
Picture
Data
PIC
+1234
PICS9(4)
S9(4)
+1234
PIC
-1234
PICS9(4)
S9(4)
-1234
PIC
+1234
PICS9(4)
S9(4)
+1234
PIC
-1234
PICS9(4)
S9(4)
-1234
Receiving
Receiving
Picture
Result
Picture
Result
PIC
1234
PIC9(4)CR
9(4)CR
PIC
1234CR
PIC9(4)CR
9(4)CR
PIC
1223
PIC9(4)DB
9(4)DB
PIC
1234DB
PIC9(4)DB
9(4)DB
PIC
PIC9(4)
9(4)
PIC
PIC9(4)
9(4)
PIC
PIC$99999
$99999
PIC
PIC$ZZZZZ
$ZZZZZ
1234
1234
0000
0000
$01234
$
2004 IBM Corporation
165
Sending
Sending
Picture
Data
Picture
Data
PIC
0000
PIC9(4)
9(4)
0000
PIC
0080
PIC9(4)
9(4)
0080
PIC
0128
PIC9(4)
9(4)
0128
PIC
57397
PIC9(5)
9(5)
57397
Receiving
Receiving
Picture
Resu
lt
Picture
Result
PIC
$0.00
PIC$$,$$9.99
$$,$$9.99
PIC
$80.00
PIC$$,$$9.00
$$,$$9.00
PIC
$128.00
PIC$$,$$9.99
$$,$$9.99
PIC
$7,397
PIC$$,$$9
$$,$$9
PIC
PICS9(4)
S9(4)
PIC
PICS9(4)
S9(4)
PIC
PICS9(4)
S9(4)
PIC
PICS9(5)
S9(5)
PIC
PIC++++9
++++9
PIC
PIC++++9
++++9
PIC
PIC-------- 99
PIC
PIC-------- 99
-- 0005
0005
+0080
+0080
-- 0080
0080
+71234
+71234
-5
+80
-80
1234
2004 IBM Corporation
Sending
Sending
Picture
Data
Picture
Data
PIC
12345
PIC9(5)
9(5)
12345
PIC
01234
PIC9(5)
9(5)
01234
PIC
00123
PIC9(5)
9(5)
00123
PIC
00012
PIC9(5)
9(5)
00012
PIC
05678
PIC9(5)
9(5)
05678
PIC
00567
PIC9(5)
9(5)
00567
PIC
00000
PIC9(5)
9(5)
00000
166
Receiving
Receiving
Picture
Result
Picture
Result
PIC
12,345
PICZZ,999
ZZ,999
PIC
1,234
PICZZ,999
ZZ,999
PIC
123
PICZZ,999
ZZ,999
PIC
012
PICZZ,999
ZZ,999
PIC
*5,678
PIC**,**9
**,**9
PIC
***567
PIC**,**9
**,**9
PIC
******
PIC**,***
**,***
2004 IBM Corporation
EXERCISE 3
167
Table of contents
Introduction to COBOL
COBOL Basics 1
COBOL Basics 2
Introduction to Sequential Files
Processing Sequential Files
Simple iteration with the PERFORM verb
Arithmetic and Edited Pictures
Conditions
Tables and the PERFORM ... VARYING
Designing Programs
168
Conditions
Overview
169
IF..THEN...ELSE.
Relation conditions.
Class conditions.
Sign conditions.
Complex conditions.
Implied Subjects.
Conditions
IF Syntax
StatementB lock
IF Condition THEN
NEXT
SENTENCE
StatementB lock
ELSE
[END - IF ]
NEXT
SENTENCE
CONDITION TYPES
Simple
SimpleConditions
Conditions
Relation
RelationConditions
Conditions
Class
ClassConditions
Conditions
Sign
SignConditions
Conditions
Complex
ComplexConditions
Conditions
Condition
ConditionNames
Names
170
Conditions
Relation Conditions
[NOT] GREATERTHAN
[NOT] >
[NOT] LESSTHAN
[
NOT
]
<
Identifier
[NOT] EQUALTO
Identifier
Literal
IS
Literal
NOT
=
[
]
ArithmeticExpression
>=
LESSTHAN OR EQUALTO
<=
171
Conditions
Class Conditions
Identifier
172
NUMERIC
ALPHABETIC
- LOWER
IS [ NOT ] ALPHABETIC
ALPHABETIC
- UPPER
UserDefine dClassName
Conditions
Sign Conditions
ArithExp
173
POSITIVE
IS [ NOT ] NEGATIVE
ZERO
Conditions
Complex conditions
AND
Condition
Condition
OR
174
Conditions
Complex conditions have precedence rules too
Precedence
Precedence Rules.
Rules.
1.
1.
2.
2.
NOT
NOT
AND
AND
==
==
****
**or
or//
3.
3.
OR
OR
== ++or
or--
Examples
IF ( Row > 0) AND (Row < 26) THEN
DISPLAY On Screen
END-IF
IF ( VarA > VarC ) OR ( VarC = VarD ) OR ( VarA NOT = VarF )
DISPLAY Done
END-IF
175
Conditions
Implied Subjects
176
Implied
ImpliedSubjects
Subjects
TotalAmt
TotalAmt
Grade
Grade==
VarA
VarA>>
2004 IBM Corporation
Conditions
Nested IFs
IF
IF (( VarA
VarA << 10
10 )) AND
AND (( VarB
VarB NOT
NOT >> VarC
VarC )) THEN
THEN
IF
VarG
=
14
THEN
IF VarG = 14 THEN
DISPLAY
DISPLAY First
First
ELSE
ELSE
DISPLAY
DISPLAY Second
Second
END-IF
END-IF
ELSE
ELSE
DISPLAY
DISPLAY Third
Third
END-IF
END-IF
VarA
VarA VarB
VarB VarC
VarC VarG
VarG
33 T
33 T
33 T
13
13F
177
44
44
44
44
T
T
F
T
15
15
15
15
33
15
15
14
14
15
15
14
14
14
14
T
F
DISPLAY
DISPLAY
First
Second
Third
Third
2004 IBM Corporation
Conditions
Condition Names
IF 4
VarA
THAN
VarB
1
4 4GREATER
4 4 4 4 44
24 4
4 4THEN
4 4 4Action
44
3
Condition is either
TRUE or False
Conditions
Defining Condition Names
Literal
VALUE
88 ConditionN ame
THROUGH
LowValue
VALUES
HighValue
THRU
179
Condition Names are defined in the DATA DIVISION using the special
level number 88.
They are always associated with a data item and are defined
immediately after the definition of the data item.
The VALUE clause is used to identify the values which make the
Condition Name TRUE.
COBOL Programming Fundamental
Conditions
Example
01
01 CityCode
CityCode
88
88 Dublin
Dublin
88
Limerick
88 Limerick
88
88 Cork
Cork
88
Galway
88 Galway
88
88 Sligo
Sligo
88
Waterford
88 Waterford
88
88 UniversityCity
UniversityCity
PIC
PIC 99 VALUE
VALUE 5.
5.
VALUE
VALUE 1.
1.
VALUE
2.
VALUE 2.
VALUE
VALUE 3.
3.
VALUE
4.
VALUE 4.
VALUE
VALUE 5.
5.
VALUE
6.
VALUE 6.
VALUE
VALUE 11 THRU
THRU 4.
4.
City Code
5
IF
IF Limerick
Limerick
DISPLAY
DISPLAY "Hey,
"Hey, we're
we're home."
home."
END-IF
END-IF
IF
IF UniversityCity
UniversityCity
PERFORM
PERFORM CalcRentSurcharge
CalcRentSurcharge
END-IF
END-IF
180
Dublin
Limerick FALSE
Cork
Galway
Sligo
Waterford
UniversityCity
FALSE
FALSE
FALSE
TRUE
FALSE
FALSE
2004 IBM Corporation
Conditions
Example
01
01 CityCode
CityCode
88
88 Dublin
Dublin
88
88 Limerick
Limerick
88
88 Cork
Cork
88
88 Galway
Galway
88
88 Sligo
Sligo
88
88 Waterford
Waterford
88
88 UniversityCity
UniversityCity
PIC
PIC 99 VALUE
VALUE 5.
5.
VALUE
VALUE 1.
1.
VALUE
VALUE 2.
2.
VALUE
VALUE 3.
3.
VALUE
VALUE 4.
4.
VALUE
VALUE 5.
5.
VALUE
VALUE 6.
6.
VALUE
VALUE 11 THRU
THRU 4.
4.
City Code
2
IF
IF Limerick
Limerick
DISPLAY
DISPLAY "Hey,
"Hey, we're
we're home."
home."
END-IF
END-IF
IF
IF UniversityCity
UniversityCity
PERFORM
PERFORM CalcRentSurcharge
CalcRentSurcharge
END-IF
END-IF
181
Dublin
Limerick TRUE
Cork
Galway
Sligo
Waterford
UniversityCity
FALSE
FALSE
FALSE
FALSE
FALSE
TRUE
2004 IBM Corporation
Conditions
Example
01
01 CityCode
CityCode
88
88 Dublin
Dublin
88
88 Limerick
Limerick
88
88 Cork
Cork
88
88 Galway
Galway
88
88 Sligo
Sligo
88
88 Waterford
Waterford
88
88 UniversityCity
UniversityCity
PIC
PIC 99
VALUE
VALUE
VALUE
VALUE
VALUE
VALUE
VALUE
VALUE
VALUE
VALUE
VALUE
VALUE
VALUE
VALUE
VALUE
VALUE 5.
5.
1.
1.
2.
2.
3.
3.
4.
4.
5.
5.
6.
6.
11 THRU
THRU 4.
4.
City Code
6
IF
IF Limerick
Limerick
DISPLAY
DISPLAY "Hey,
"Hey, we're
we're home."
home."
END-IF
END-IF
IF
IF UniversityCity
UniversityCity
PERFORM
PERFORM CalcRentSurcharge
CalcRentSurcharge
END-IF
END-IF
182
Dublin
Limerick FALSE
Cork
Galway
Sligo
Waterford
UniversityCity
FALSE
FALSE
FALSE
FALSE
TRUE
FALSE
2004 IBM Corporation
Conditions
Example
01
01 InputChar
InputChar
88
88 Vowel
Vowel
88
88 Consonant
Consonant
88
88 Digit
Digit
88
88 LowerCase
LowerCase
88
88 ValidChar
ValidChar
PIC
PIC X.
X.
VALUE
VALUE
VALUE
VALUE
"A","E","I","O","U".
"A","E","I","O","U".
"B"
"B" THRU
THRU "D",
"D", "F","G","H"
"F","G","H"
"J"
"J" THRU
THRU "N",
"N", "P"
"P" THRU
THRU "T"
"T"
"V"
"V" THRU
THRU "Z".
"Z".
VALUE
VALUE "0"
"0" THRU
THRU "9".
"9".
VALUE
VALUE "a"
"a" THRU
THRU "z".
"z".
VALUE
VALUE "A"
"A" THRU
THRU "Z","0"
"Z","0" THRU
THRU "9".
"9".
IF
IF ValidChar
ValidChar
DISPLAY
DISPLAY "Input
"Input OK."
OK."
END-IF
END-IF
IF
IF LowerCase
LowerCase
DISPLAY
DISPLAY "Not
"Not Upper
Upper Case"
Case"
END-IF
END-IF
IF
IF Vowel
Vowel
Display
Display "Vowel
"Vowel entered."
entered."
END-IF
END-IF
183
Input Char
E
Vowel
Consonant
Digit
LowerCase
ValidChar
TRUE
FALSE
FALSE
FALSE
TRUE
2004 IBM Corporation
Conditions
Example
01
01 InputChar
InputChar
88
88 Vowel
Vowel
88
88 Consonant
Consonant
88
88 Digit
Digit
88
88 LowerCase
LowerCase
88
88 ValidChar
ValidChar
PIC
PIC X.
X.
VALUE
VALUE
VALUE
VALUE
"A","E","I","O","U".
"A","E","I","O","U".
"B"
"B" THRU
THRU "D",
"D", "F","G","H"
"F","G","H"
"J"
"J" THRU
THRU "N",
"N", "P"
"P" THRU
THRU "T"
"T"
"V"
"V" THRU
THRU "Z".
"Z".
VALUE
VALUE "0"
"0" THRU
THRU "9".
"9".
VALUE
VALUE "a"
"a" THRU
THRU "z".
"z".
VALUE
VALUE "A"
"A" THRU
THRU "Z","0"
"Z","0" THRU
THRU "9".
"9".
IF
IF ValidChar
ValidChar
DISPLAY
DISPLAY "Input
"Input OK."
OK."
END-IF
END-IF
IF
IF LowerCase
LowerCase
DISPLAY
DISPLAY "Not
"Not Upper
Upper Case"
Case"
END-IF
END-IF
IF
IF Vowel
Vowel
Display
Display "Vowel
"Vowel entered."
entered."
END-IF
END-IF
184
Input Char
4
Vowel
Consonant
Digit
LowerCase
ValidChar
FALSE
FALSE
TRUE
FALSE
TRUE
2004 IBM Corporation
Conditions
Example
01
01 InputChar
InputChar
88
88 Vowel
Vowel
88
88 Consonant
Consonant
88
88 Digit
Digit
88
LowerCase
88 LowerCase
88
88 ValidChar
ValidChar
PIC
PIC X.
X.
VALUE
VALUE
VALUE
VALUE
"A","E","I","O","U".
"A","E","I","O","U".
"B"
"B" THRU
THRU "D",
"D", "F","G","H"
"F","G","H"
"J"
"J" THRU
THRU "N",
"N", "P"
"P" THRU
THRU "T"
"T"
"V"
"V" THRU
THRU "Z".
"Z".
VALUE
VALUE "0"
"0" THRU
THRU "9".
"9".
VALUE
"a"
THRU
VALUE
"a" THRU "z".
"z".
VALUE
"A"
THRU
"Z","0"
VALUE
"A" THRU "Z","0" THRU
THRU "9".
"9".
IF
IF ValidChar
ValidChar
DISPLAY
DISPLAY "Input
"Input OK."
OK."
END-IF
END-IF
IF
IF LowerCase
LowerCase
DISPLAY
DISPLAY "Not
"Not Upper
Upper Case"
Case"
END-IF
END-IF
IF
IF Vowel
Vowel
Display
Display "Vowel
"Vowel entered."
entered."
END-IF
END-IF
185
Input Char
g
Vowel
Consonant
Digit
LowerCase
ValidChar
FALSE
FALSE
FALSE
TRUE
FALSE
2004 IBM Corporation
Conditions
Example
01
01 EndOfFileFlag
EndOfFileFlag
88
88 EndOfFile
EndOfFile
PIC
PIC 99 VALUE
VALUE 0.
0.
VALUE
VALUE 1.
1.
EndOfFileFlag
0
EndOfFile
READ
READ InFile
InFile
AT
AT END
END MOVE
MOVE 11 TO
TO EndOfFileFlag
EndOfFileFlag
END-READ
END-READ
PERFORM
PERFORM UNTIL
UNTIL EndOfFile
EndOfFile
Statements
Statements
READ
READ InFile
InFile
AT
AT END
END MOVE
MOVE 11 TO
TO EndOfFileFlag
EndOfFileFlag
END-READ
END-READ
END-PERFORM
END-PERFORM
186
Conditions
Example
01
01 EndOfFileFlag
EndOfFileFlag PIC
PIC 99 VALUE
VALUE 0.
0.
88
VALUE
88 EndOfFile
EndOfFile
VALUE 1.
1.
EndOfFileFlag
1
EndOfFile
READ
READ InFile
InFile
AT
AT END
END MOVE
MOVE 11 TO
TO EndOfFileFlag
EndOfFileFlag
END-READ
END-READ
PERFORM
PERFORM UNTIL
UNTIL EndOfFile
EndOfFile
Statements
Statements
READ
READ InFile
InFile
AT
AT END
END MOVE
MOVE 11 TO
TO EndOfFileFlag
EndOfFileFlag
END-READ
END-READ
END-PERFORM
END-PERFORM
187
Conditions
Using the SET verb
FILLER
01
PIC
01 FILLER
FILLER
PIC 99 VALUE
VALUE 0.
0.
88
88 EndOfFile
EndOfFile VALUE
VALUE 1.
1.
88
NotEndOfFile
VALUE
0.
88 NotEndOfFile VALUE 0.
0
EndOfFile
1
NotEndOfFile 0
READ
READ InFile
InFile
AT
AT END
END SET
SET EndOfFile
EndOfFile TO
TO TRUE
TRUE
END-READ
END-READ
PERFORM
PERFORM UNTIL
UNTIL EndOfFile
EndOfFile
Statements
Statements
READ
READ InFile
InFile
AT
AT END
END SET
SET EndOfFile
EndOfFile TO
TO TRUE
TRUE
END-READ
END-READ
END-PERFORM
END-PERFORM
Set
Set NotEndOfFile
NotEndOfFile TO
TO TRUE.
TRUE.
188
Conditions
Using the SET verb
FILLER
01
PIC
01 FILLER
FILLER
PIC 99 VALUE
VALUE 0.
0.
88
88 EndOfFile
EndOfFile VALUE
VALUE 1.
1.
88
88 NotEndOfFile
NotEndOfFile VALUE
VALUE 0.
0.
1
EndOfFile
1
NotEndOfFile 0
READ
READ InFile
InFile
AT
AT END
END SET
SET EndOfFile
EndOfFile TO
TO TRUE
TRUE
END-READ
END-READ
PERFORM
PERFORM UNTIL
UNTIL EndOfFile
EndOfFile
Statements
Statements
READ
READ InFile
InFile
AT
AT END
END SET
SET EndOfFile
EndOfFile TO
TO TRUE
TRUE
END-READ
END-READ
END-PERFORM
END-PERFORM
Set
Set NotEndOfFile
NotEndOfFile TO
TO TRUE.
TRUE.
189
Conditions
Using the SET verb
FILLER
01
PIC
01 FILLER
FILLER
PIC 99 VALUE
VALUE 0.
0.
88
88 EndOfFile
EndOfFile VALUE
VALUE 1.
1.
88
NotEndOfFile
VALUE
0.
88 NotEndOfFile VALUE 0.
0
EndOfFile
1
NotEndOfFile 0
READ
READ InFile
InFile
AT
AT END
END SET
SET EndOfFile
EndOfFile TO
TO TRUE
TRUE
END-READ
END-READ
PERFORM
PERFORM UNTIL
UNTIL EndOfFile
EndOfFile
Statements
Statements
READ
READ InFile
InFile
AT
AT END
END SET
SET EndOfFile
EndOfFile TO
TO TRUE
TRUE
END-READ
END-READ
END-PERFORM
END-PERFORM
Set
Set NotEndOfFile
NotEndOfFile TO
TO TRUE.
TRUE.
190
Conditions
The Evaluate
Identifier
Literal
CondExpres sion
EVALUATE
K
ArithExpre ssion
TRUE
FALSE
ANY
Condition
WHEN TRUE
K StatementB lock K
FALSE
Identifier
Identifier
THRU
Literal
[NOT ] Literal
THROUGH
ArithExpre ssion
ArithExpre ssion
191
Conditions
The Evaluate
10
192
Conditions
Decision Table Implementation
Gender
M
F
M
F
Age
<20 <20 20-40 20-40
Service Any Any <10
<10
% Bonus 5
10
12
13
EVALUATE Gender
WHEN
"M"
WHEN
"F"
WHEN
"M"
WHEN
"F"
WHEN
"M"
WHEN
"F"
:
:
:
:
WHEN
"F"
END-EVALUATE.
193
TRUE
TRUE
Age<20
Age<20
Age>19 AND <41
Age>19 AND <41
Age>40
Age>40
:
:
ANY
M
40>
<10
20
F
40>
<10
15
ANY
ANY
Service<10
Service<10
Service<10
Service<10
:
:
Service>20
M
F
20-40 20-40 etc
10-20 10-20 etc
14
23
MOVE 5 TO Bonus
MOVE 10 TO Bonus
MOVE 12 TO Bonus
MOVE 13 TO Bonus
MOVE 20 TO Bonus
MOVE 15 TO Bonus
:
:
MOVE 25 TO Bonus
Table of contents
Introduction to COBOL
COBOL Basics 1
COBOL Basics 2
Introduction to Sequential Files
Processing Sequential Files
Simple iteration with the PERFORM verb
Arithmetic and Edited Pictures
Conditions
Tables and the PERFORM ... VARYING
Designing Programs
194
195
Introduction to tables.
Declaring tables.
Processing tables using the PERFORM..VARYING.
CountyNum
TaxPaid
PROCEDURE DIVISION.
Begin.
OPEN INPUT TaxFile
READ TaxFile
AT END SET EndOfTaxFile TO TRUE
END-READ
PERFORM UNTIL EndOfTaxFile
ADD TaxPaid TO TaxTotal
READ TaxFile
AT END SET EndOfTaxFile TO TRUE
END-READ
END-PERFORM.
DISPLAY "Total taxes are ", TaxTotal
CLOSE TaxFile
STOP RUN.
196
The program to
calculate the total
taxes paid for the
country is easy to
write.
BUT.
What do we do if we
want to calculate the
taxes paid in each
county?
2004 IBM Corporation
Tables
and the
PERFORM
... VARYING
County1
County2
County3
County4
County5
TaxTotal
TaxTotal
TaxTotal
TaxTotal
TaxTotal
PROCEDURE DIVISION.
Begin.
OPEN INPUT TaxFile
READ TaxFile
AT END SET EndOfTaxFile TO TRUE
END-READ
PERFORM SumCountyTaxes UNTIL EndOfTaxFile
DISPLAY "County 1 total is ", County1TaxTotal
: 24 Statements
: 24 Statements
58 Statements
197
AAtable
tableisisaacontiguous
contiguoussequence
sequenceof
ofmemory
memorylocations
locations
called
, which
name
calledelements
elements,
whichall
allhave
havethe
thesame
samename,
name,and
andare
are
uniquely
uniquelyidentified
identifiedby
bythat
thatname
nameand
andby
bytheir
theirposition
positionin
in
the
thesequence.
sequence.
CountyTax
10
5
1
2
3
4
6
MOVE 10 TO CountyTax(5)
ADD TaxPaid TO CountyTax(CountyNum)
ADD TaxPaid TO CountyTax(CountyNum + 2)
198
AAtable
tableisisaacontiguous
contiguoussequence
sequenceof
ofmemory
memorylocations
locations
called
, which
name
calledelements
elements,
whichall
allhave
havethe
thesame
samename,
name,and
andare
are
uniquely
uniquelyidentified
identifiedby
bythat
thatname
nameand
andby
bytheir
theirposition
positionin
in
the
thesequence.
sequence.
CountyTax
55
10
3
MOVE 10 TO CountyTax(5)
55
2
ADD TaxPaid TO CountyTax(CountyNum)
ADD TaxPaid TO CountyTax(CountyNum + 2)
199
AAtable
tableisisaacontiguous
contiguoussequence
sequenceof
ofmemory
memorylocations
locations
called
, which
name
calledelements
elements,
whichall
allhave
havethe
thesame
samename,
name,and
andare
are
uniquely
uniquelyidentified
identifiedby
bythat
thatname
nameand
andby
bytheir
theirposition
positionin
in
the
thesequence.
sequence.
CountyTax
55
1
55
4
10
5
MOVE 10 TO CountyTax(5)
ADD TaxPaid TO CountyTax(CountyNum)
ADD TaxPaid TO CountyTax(CountyNum + 2)
55
200
AAtable
tableisisaacontiguous
contiguoussequence
sequenceof
ofmemory
memorylocations
locations
called
, which
name
calledelements
elements,
whichall
allhave
havethe
thesame
samename,
name,and
andare
are
uniquely
uniquelyidentified
identifiedby
bythat
thatname
nameand
andby
bytheir
theirposition
positionin
in
the
thesequence.
sequence.The
Theposition
positionindex
indexisiscalled
calledaasubscript.
subscript.
CountyTax
55
1
55
10
Subscript
MOVE 10 TO CountyTax(5)
ADD TaxPaid TO CountyTax(CountyNum)
ADD TaxPaid TO CountyTax(CountyNum + 2)
201
PROCEDURE DIVISION.
Begin.
OPEN INPUT TaxFile
READ TaxFile
AT END SET EndOfTaxFile TO TRUE
END-READ
PERFORM UNTIL EndOfTaxFile
ADD TaxPaid TO CountyTax(CountyNum)
READ TaxFile
AT END SET EndOfTaxFile TO TRUE
END-READ
Subscript
END-PERFORM.
PERFORM VARYING Idx FROM 1 BY 1
UNTIL Idx GREATER THAN 26
DISPLAY "County ", CountyNum
" tax total is " CountyTax(Idx)
END-PERFORM
CLOSE TaxFile
9 Statements
STOP RUN.
202
CountyName
A-89432
TaxPaid
CLARE
7894.55
CountyTax
IF CountyName = "CARLOW"
ADD TaxPaid TO CountyTax(1)
END-IF
IF CountyName = "CAVAN"
ADD TaxPaid TO CountyTax(2)
END-IF
:
:
203
:
:
:
:
:
:
24 TIMES
:
:
CountyName
A-89432
CLARE
TaxPaid
Idx
7894.55
County
CARLOW
1
CAVAN
2
CLARE
3
CORK
4
500.50
1
125.75
2
1000.00
3
745.55
4
CountyTax
DONEGAL DUBLIN
5
6
345.23
5
123.45
6
CountyName
A-89432
TaxPaid
CLARE
Idx
7894.55
County
CARLOW
1
CAVAN
2
CLARE
3
CORK
4
1000.00
3
745.55
4
DONEGAL DUBLIN
5
6
CountyTax
500.50
1
125.75
2
345.23
5
123.45
6
CountyName
A-89432
CLARE
TaxPaid
Idx
7894.55
County
CARLOW
1
CAVAN
2
CLARE
3
CORK
4
125.75
2
1000.00
3
745.55
4
DONEGAL DUBLIN
5
6
CountyTax
500.50
1
345.23
5
123.45
6
CountyName
A-89432
CLARE
TaxPaid
Idx
7894.55
County
CARLOW
1
CAVAN
2
CLARE
3
CORK
4
125.75
2
8894.55
3
745.55
4
DONEGAL DUBLIN
5
6
CountyTax
500.50
1
345.23
5
123.45
6
TaxTotals
CountyTax
000000
000000
2
01
000000
000000
TaxTotals.
02 CountyTax
000000
000000
PIC 9(10)V99
OCCURS 26 TIMES.
or
02
CountyTax
OCCURS 26 TIMES
PIC 9(10)V99.
e.g.
67
3
000000
CountyTax
01
000000
PayerCount
CountyTaxDetails
TaxTotals.
02 CountyTaxDetails OCCURS 26 TIMES.
03 CountyTax
PIC 9(10)V99.
03 PayerCount
PIC 9(7).
e.g.
209
MOVE 25 TO PayerCount(2).
MOVE 67 TO CountyTax(5).
MOVE ZEROS TO CountyTaxDetails(3).
COBOL Programming Fundamental
PERFORM
1stProc
THRU
THROUGH
VARYING
EndProc
Identifer1
IndexName1
FROM
WITH
TEST
210
Identifier 2
IndexName 2
Literal
Identifier 3
BY
UNTIL Condition1
Literal
Identifier 5
Identifier 4
AFTER
FROM
4
IndexName
IndexName3
Literal
Identifier 6
BY
UNTIL Condition2
Literal
[StatementB
BEFORE
AFTER
Idx1
Move 1 to Idx1
True
Idx1 = 3
Next Statement
False
Loop Body
Inc Idx1
211
Idx1
Move 1 to Idx1
Idx1 = 3
True
Next Statement
False
Loop Body
Inc Idx1
212
Idx1
Move 1 to Idx1
Idx1 = 3
True
False
1
Next Statement
Loop Body
Inc Idx1
213
Idx1
Move 1 to Idx1
Idx1 = 3
True
False
2
Next Statement
Loop Body
Inc Idx1
214
Move 1 to Idx1
Idx1
2
Idx1 = 3
True
False
Next Statement
Loop Body
Inc Idx1
215
Idx1
Move 1 to Idx1
2
Idx1 = 3
True
False
Loop Body
Next Statement
1
2
Inc Idx1
216
Idx1
Move 1 to Idx1
3
Idx1 = 3
True
False
Loop Body
Next Statement
1
2
Inc Idx1
217
Move 1 to Idx1
Idx1
3
Idx1 = 3
True
False
218
Next Statement
Loop Body
1
2
Inc Idx1
Exit value = 3
Table of contents
Introduction to COBOL
COBOL Basics 1
COBOL Basics 2
Introduction to Sequential Files
Processing Sequential Files
Simple iteration with the PERFORM verb
Arithmetic and Edited Pictures
Conditions
Tables and the PERFORM ... VARYING
Designing Programs
219
Designing Programs
Overview
220
Efficiency vs Clarity.
Designing Programs
COBOL
221
Designing Programs
Cost of a system over its entire life
Coding
7%
Testing
15%
Analysis
and
Design 9%
Maintenance
67%
Zelkowitz
ACM 1978
p202
Maintenance Costs are only as low as this because many systems become so
unmaintainable early in their lives that they have to be SCRAPPED !!
:- B. Boehm
222
Designing Programs
Program Maintenance
2.
3.
4.
223
Designing Programs
How should write your programs?
You should write your programs with the expectation that they
will have to be changed.
224
You should write your programs as you would like them written if
you had to maintain them.
Designing Programs
Efficiency vs Clarity
225
As a rule 70% of the work of the program will be done in 10% of the
code.
Write your program as clearly as possible and then, if its too slow,
identify the 10% of the code where the work is being done and
optimize it.
Designing Programs
When shouldnt we design our programs?
226
Designing Programs
Producing a Good Design
227
Conscious design starts by separating the design task from the task
of program construction.
Designing Programs
Why separate design from construction?
228
It helps us to iron out problems with the specification and to discover any
bugs in our solution before we commit it to code (see next slide).
Designing Programs
Relative cost of fixing a bug
In Production
x82
In
Construction
x20
1
In Design
Designing Programs
Design Notations
230
Designing Programs
Flowcharts as design tools
231
Designing Programs
Structured Flowcharts as design tools
232
Designing Programs
Structured English
For
Foreach
eachtransaction
transactionrecord
recorddo
dothe
thefollowing
following
IF
IFthe
therecord
recordisisaareceipt
receiptthen
then
add
add11to
tothe
theReceiptsCount
ReceiptsCount
add
addthe
theAmount
Amountto
tothe
theBalance
Balance
otherwise
otherwise
add
add11to
tothe
thePaymentsCount
PaymentsCount
subtract
subtractthe
theAmount
Amountfrom
fromthe
theBalance
Balance
EndIF
EndIF
add
add11to
tothe
theRecordCount
RecordCount
Write
Writethe
theBalance
Balanceto
tothe
theCustomerFile
CustomerFile
When
Whenthe
thefile
filehas
hasbeen
beenprocessed
processed
Output
Output the
theReceiptsCount
ReceiptsCount
the
thePaymentsCount
PaymentsCount
and
andthe
theRecordCount
RecordCount
233
Designing Programs
The Jackson Method
234
Designing Programs
Warnier-Orr Diagrams
OpenFiles
ProcessRecords
UpdateCustomerBalance
PrintTotals
CloseFiles
235
ProcessReceipt
RecordType ?
ProcessPayment
WriteNewBalance
2004/11