2120lec4.su06

advertisement
The Procedure Division
Chapter 4
1
Main Two Sections
• File Section
– Used to define files and record formats
– Field names within records
• Working Storage Section
– All accumulators, counters, subscripts, flags,
tables, etc.
– All constant records, such as print header
records and other constant or near-constant
records.
• But first:
2
PROCEDURE DIVISION.
Contains all the instructions that the computer will execute.
Other divisions: identification, environment, data (all i/o areas (file section) and
Other data areas (working-storage section) remaining chapters - mostly
procedure division...
FORMAT OF PROCEDURE DIVISION.
.
Procedure division divided into paragraphs
(modules/routines/functions)
. Designed to perform a specific function
. Set of operations ===> one function.
. A area = paragraph names only
. all instructions - b area.
RULES FOR PARAGRAPH NAMES:
Must be unique names
. Should be descriptive
. See our "standards" <<<======yes yes!!
. Numbering of modules - four digits
.
3
0000-MAIN
1000- funct
2100- funct
2000- funct
2300- funct
3000- funct
4000- funct
2500- funct
etc...
e.g. 1000-initialize; 2000-read, ...
From structured design:
Statements and sentences:
. Verbs start statements.
. Statements followed by period = sentence
. Paragraphs consist of sentences
Sequences of instructions
. Statements are executed in order (sequence) unless a "transfer of
control" type statement is executed, such as a perform, goto.
Well-written programs - written "top-down"
. Code main module first.
. Lower level modules next.
. Progress to lower levels (more detailed)
4
STRUCTURE OF PROCEDURE DIVISION:
PROCEDURE DIVISION.
0000-MAIN.
.....
....
1000-INITIALIZE-TIME-DATE.
....
2000-INITIALIZE-READS.
....
ETC.
PARAGRAPH NAMES COINCIDE WITH MODULES IN STRUCTURE
CHART
MAIN + FOUR SUBORDINATE FUNCTIONS
==> FIVE PARAGRAPHS.
5
PROCEDURE DIVISION STATEMENTS - MAIN MODULE
OPEN STATEMENT
SYNTAX: OPEN
INPUT
OUTPUT
filename1…
. UPPERCASE = COBOL RESERVED WORD
. UNDERLINE = REQUIRED
{ } MUST SELECT SOMETHING INSIDE
... MEANS ANY NUMBER OF PRECEDING ITEMS.
MUST SAY:
OPEN “INPUT” OR “OUTPUT”
EACH MUST BE FOLLOWED BY ANY NUMBER OF FILE NAMES...
(BUT AT LEAST ONE...)
CAN SAY OPEN INPUT FILENAME-1,
FILENAME-2.
OR
OPEN INPUT FILENAME-1.
OPEN INPUT FILENAME-2.
6
A FILE MUST BE (OPENED) BEFORE IT CAN BE PROCESSED! .
EVERY FILE NAMED IN A SELECT STATEMENT WILL HAVE AN FD.
THIS IMPLIES THAT EACH FILE WILL BE OPENED FOR EITHER INPUT OR
OUTPUT.
OPEN DESIGNATES THE FILE AS “INPUT” OR “OUTPUT”
OPEN CAUSES THE DEVICE (TAPE OR DISK) TO BE ACCESSED TO FIND
AND LOCATE FILE.
IF OPEN INPUT WITH LABELS (TYPICALLY TAPES OR DISKS)
THE HEADER LABEL (IN FRONT OF FILE) IS CHECKED TO
SEE IF THIS IS THE CORRECT FILE.
IF OPEN OUTPUT WITH LABELS
DEVICE IS ACCESSED AND HEADER LABEL IS WRITTEN
TO THE FRONT OF THE FILE TO BE CREATED.
THEREFORE, LABELS ARE CREATED OR CHECKED.
7
The Read Statement
Transfers data (a record) from input device to the input storage area. (The 01 - process area)
Format: (older versions of Cobol)
READ filename
AT END
STATEMENT(S).
OR
READ filename
(COBOL 85)
AT END
STATEMENT
STATEMENT
STATEMENT...
END-READ.
Fourth time we have seen the filename.
Transfers one record into the process area: the 01.
Read also checks length of record inputted against record description.
The At End
==> Did I hit EOF or unsuccessful read?
If so,do what follows the at end entry:
8
In COBOL-85, we have a newer READ statement:
READ filename
AT END
STATEMENTS
[ NOT AT END
STATEMENTS]
[END-READ]
EITHER MUST END IN PERIOD OR END-READ.
EXAMPLE: Here are two READ statements….
1.
READ SALES-FILE
AT END
PERFORM 2000-BEGIN-PROCESS
PERFORM 2100-CONTINUE.
<------ (period)
OR
2.
(BOOK [ BUT I CHANGED EOF FLAG....]
IF AMT = ZERO
READ IN-FILE
AT END
MOVE 1 TO F-EOF
END-READ
END-IF
NOTE THE SCOPE TERMINATORS.
9
GIVEN THE CHOICE, USE OF THE SCOPE TERMINATORS IS STRONGLY ENCOURAGED.
THE PERFORM ... UNTIL
FORMAT: (THE ‘TRANSFER OF CONTROL’ PERFORM:)
PERFORM procedure-name-1 UNTIL condition
OR
COBOL 85: (THE ‘IN-LINE’ PERFORM)
PERFORM UNTIL condition
STATEMENTS
STATEMENTS
END-PERFORM
The Perform is critical for implementing structured design and
programming techniques
FIRST FORMAT:
. The Perform is thee mechanism by which control is transferred from a
higher level module to a lower level module.
. Perform transfers control to a procedure and repeatedly executes the
procedure (module, paragraph...) ‘until’ the cited condition becomes true.
. Then, control returns to the next sequential instruction following the
10
perform. (We will spend considerable time on this verb.)
THE PERFORM ... UNTIL
Example: (Traditional Perform)
100-SOME-PARAGRAPH.
…
<Preceding statements>
PERFORM 200-CALCULATE-TOTALS UNTIL X > 25
<Next statements following the perform>
…
200-CALCULATE-TOTALS.
<Statements>
<More statements>
<SOME STATEMENT THAT ADJUSTS VALUE OF X TOO…>
300-DO-MORE.
EXPLAIN…
11
“IN-LINE PERFORM” (COBOL 85 AND 2002 VERSIONS)
PERFORM UNTIL condition
....
....
....
END-PERFORM.
HERE, USE OF THE SCOPE TERMINATOR IS ESSENTIAL.
EXAMPLE:
MOVE INPUTFIELD-A TO OUTPUTFIELD-B
PERFORM UNTIL F-EOF = 1
READ EMPLOYEE-FILE
AT END
...
NOT AT END
...
END-READ
MOVE fields...
WRITE some printline...
END-PERFORM.
Can readily see the “scope” of the Perform via the scope terminators.
Called “in line” Perform because there is no explicit branching to a paragraph and returning.
12
THE NOTION OF THE "PRETEST" AND POST-TEST":
Consider:
PERFORM 2000-CALCULATE UNTIL EOF = 1.
Condition: (EOF = 1) is tested before loop is ever executed. (Pretest).
Then, after each iteration, the condition is tested repeatedly. (Post-test)
Here, EOF is assumed to be set initially to 0 (or at least not 1)
OR
05 F-EOF
05 F-EOF
PIC 9
VALUE 0.
PIC XXX VALUE "YES".
13
More on Pretest and Post-test
Let's consider the notions of
1.. THE PERFORM ... UNTIL AND THE READ STATEMENT
(WITH BAD CODING APPROACH ... )
2. THE PERFORM ... UNTIL AND THE READ STATEMENT
(GOOD CODING TECHNIQUE)
Poorly-written code:
0000-MAIN-MODULE.
OPEN INPUT ....
PERFORM 2000-CALC-ROUTINE
UNTIL EOF=1.
....
2000-CALC-ROUTINE.
READ INPUT-FILE
AT END
MOVE 1 TO F-EOF
END-READ
MOVE...
COMPUTE….
Are there potential problems??
2100-NEXT-PARA.
Discuss pre-test and post-test…
14
BETTER WAY TO GO.....
1. SCOPE TERMINATORS; 2..PRIMING READ
0000-MAIN-MODULE.
OPEN INPUT ....
...
READ INPUT-FILE
<---- PRIMING READ (ONE TIME)
AT END
MOVE 1 TO F-EOF
END-READ
PERFORM 2000-CALC-ROUTINE <--- PRETEST; POST TEST
UNTIL EOF=1
END-PERFORM
<--- NICE SCOPE TERMINATOR
PERFORM 4000-SUMMARY-ROUTINE
CLOSE....
STOP RUN.
2000-CALC-ROUTINE.
MOVE...
... <all other computations and /or data manipulations >
...
READ INPUT-FILE <--- THE "MAIN" READING OF THE FILE
AT END
MOVE 1 TO F-EOF <---- MERELY SETS A SWITCH
END-READ.
DOES NOT STOP LOOP ITERATION
LAST STATEMENT IN PARAGRAPH
2100-NEXT-PARA.
15
END-OF-JOB PROCESSING
The Close and Stop Run statements.
Typically have two statements part of every EOJ routine: Close files and Stop Run.
CLOSE:
Releases files and "deactivates" the devices
(Releases devices for other assignments....)
Format: Close filename1,
filename2, ...
.. Creates trailer labels (and more on old technologies)
.. No "input" or "output" cited.
.. Use separate Closes if appropriate to close files in different parts of a
larger program.
STOP RUN
Last executable statement of program
. In Cobol 85 and 2002, the Stop Run will close any opened files, but
explicitly Close them anyway.
.
16
.
SYNTAX:
THE SIMPLIFIED MOVE.
MOVE identifier-1 TO identifier-2
. Moves data from first field to second
. First field remains unchanged
EXAMPLES:
MOVE ER-NAME-IN TO PR-NAME-OUT
MOVE ER-AMT-OF-CREDIT-IN TO PR-AMT-OF-CREDIT-OUT
Assumption: fields are of same type
(size is also a consideration - later...)
17
THE WRITE STATEMENT
WE READ FILES AND WRITE RECORDS
READ a filename.
WRITE a record name
THE WRITE SPECIFIES WHICH FORMAT IS TO BE WRITTEN
We can have multiple output formats (detail records, column headers,
report headers, page trailers, etc.
We use the FD name (file name) when we Read
We use a record name when we Write.
18
We use the 01 name (record name) when we write.
Now: let's look at multiple record format - for output.
FD PRINTFILE
... .
01 REPORT-HDR.
....
01 COLUMN-HDR.
....
01 DETAIL REC.
...
All are output record formats
What are “report headers” and “column headers?”
What are “footer” records (“trailer” records)
What are “detail” records?
Explain....
____________________________________________________________
STOCK NUMBER
.......................
.......................
.......................
.......................
.......................
INVENTORY REPORT
QTY-ON-HAND REORDER POINT UNIT COST WAREHOUSE
...........
..................
..............
..............
...........
..................
..............
..............
...........
..................
..............
..............
...........
..................
..............
..............
...........
..................
..............
..............
PAGE NO: 14
19
Where are they written from?
20
Writing Records
So, we must WRITE all records from the single output process area, that is, the 01
area – FOR EACH FILE.
Because of the availability of the Value clause, however, we can set up these
"constant records" in working-storage, and move them to the print area and
‘write’ them as needed. (Set up records already ‘built’ and ready to be printed…)
Otherwise, we would have to build up these constant records each time we wish
to write the report trailers and the report header(s)... (since we have but a single
output area from which Writing will occur.
Do, however, use the file section’s 01 for the detail record (variable data).
Why? Explain?
Important to note...
Looking ahead:
Two classes of verbs:
1... Arithmetic, and
2… Conditional Statements
21
BASIC FORMATS:
ADD
identifier-1
literal-1
TO
identifier-2 …
SUBTRACT identifier-1 FROM identifier-2…
literal-1
MULTIPLY
DIVIDE
identifier-1
literal-1
identifier-1
literal-1
BY
identifier-2
INTO
identifier-2
BASIC IF FORMAT:
IF (condition)
(statement-1) …
[ELSE
(statement-2) …
END-IF]
22
Examples
Add 1 to Counter
Add over-time-pay to regular-pay
Subtract 1 from Total
Subtract discount-amt from sub-total
Multiply amt by 1.05
Divide temp into field-total
If a > b
Move …..
Write …..
Else
Move…
Add…
End-if
IF C = D
Write printrec from hdr-1 after advancing Page
End-if.
23
Download