any questions!. test coming up! agenda printing with externally described printer files arrays

41
Any Questions!

Upload: marion-cain

Post on 14-Dec-2015

214 views

Category:

Documents


0 download

TRANSCRIPT

Any Questions!

Test Coming Up!

Agenda

• Printing with Externally Described Printer Files

• Arrays

Printing with Externally Described Printer Files

• New addition to the select statement – FORMATFILE!

select report-file

assign to formatfile-filename.

Writing to an Externally Described Printer File

Write record-name

format is ‘RECORD’

eop perform print-heading

End-write.

(eop means end of page)

What is an array?

Example

January

February

March

April

May

June

July

August

September

October

November

December

Example 21 January

3 March

5 May

7 July

9 September

11 November

2 February

4 April

6 June

8 August

10 October

12 December

Example 1

January

February

March

April

May

June

July

August

September

October

November

December

Coding Example

01 Month-Names.

05 Month1 PIC X(15) VALUE ‘January’.

05 Month2 PIC X(15) VALUE ‘February’.

…..

05 Month12 PIC X(15) VALUE ‘December’.

Coding Example - Arrays

01 Month-Names-Array.

05 Month-Names

OCCURS 12 TIMES PIC X(15).

Use Subscripts (position) to access information in arrays.

Example 21 January

3 March

5 May

7 July

9 September

11 November

2 February

4 April

6 June

8 August

10 October

12 December

Coding Example

01 Month-Names.

05 Month1.

10 Month1-Number PIC 9(2) VALUE 1.

10 Month1-Name PIC X(15) VALUE ‘January’.

05 Month2.

10 Month2-Number PIC 9(2) VALUE 2.

10 Month2-Name PIC X(15) VALUE ‘February’

…..

05 Month12.

10 Month12-Number PIC 9(2) VALUE 12.

05 Month12-Number PIC X(15) VALUE ‘December’.

Coding Example - Arrays

01 Month-Names-Array.

05 Month-Entries

OCCURS 12 TIMES.

10 Month-Number PIC 9(2).

10 Month-Name PIC X(15).

Use Subscripts (position) to access information in arrays.

Loading Arrays - Redefines

01 Month-Names.

05 Month-String PIC X(36)

VALUE ‘JanFebMarAprMayJunJul…

05 Month-Entries REDEFINES

Month-String

OCCURS 12 TIMES PIC X(3).

Loading Arrays - Redefines

MOVE ‘January’ TO Month-Entries (1).

MOVE ‘February’ TO Month-Entries (2).

MOVE ‘March’ TO Month-Entries (3).

MOVE ‘April’ TO Month-Entries (4).

MOVE ‘May’ TO Month-Entries (5).

MOVE ‘June’ TO Month-Entries (6).

MOVE ‘July’ TO Month-Entries (7).

Loading Arrays – Read from a File

• Create a physical file (Month-File) with the fields:– Month Number

– Month Name

• Create an array as follows01 Month-Table.

05 Month-Entries occurs 12 times.

10 Month-Number PIC 9(2).

10 Month-Name PIC X(15).

Loading Arrays – Read from a File

PERFORM 120-Read-Table-RtnVARYING Sub FROM 1 by 1UNTIL Sub > 12.

120-Read-Table-Rtn.READ Month-File into Month-Entries (sub)

AT END DISPLAY ‘Not enough table records’ END-READ.

Searching Arrays

January

February

March

April

May

June

July

August

September

October

November

December

Searching Arrays

01 Sub PIC 9(2).

01 Month-Names-Array.

05 Month-Names

OCCURS 12 TIMES PIC X(15).

MOVE 11 TO Sub.

MOVE Month-Names (sub) to Month-Name-Out.

Searching Arrays1 January

3 March

5 May

7 July

9 September

11 November

2 February

4 April

6 June

8 August

10 October

12 December

Searching Arrays – Using Sub-Scripts

01 Sub PIC 9(2).01 Month-Names-Array.

05 Month-EntriesOCCURS 12 TIMES.10 Month-Number PIC 9(2).10 Month-Name PIC X(15).

PERFORM 120-Get-Month-Name Until Month-Number (Sub) = 11.

MOVE Month-Name (SUB) to Month-Name-Out.

120-Get-Month-Name. Add 1 to Sub.

Searching Arrays – Using Indexes and the Search Verb

01 Month-Names-Array.05 Month-Entries

OCCURS 12 TIMES INDEXED BY Sub.10 Month-Number PIC 9(2).10 Month-Name PIC X(15).

SET Sub to 1.SEARCH Month-Entries AT END

MOVE ‘Error’ to Month-Name-out WHEN Month-Number (Sub) = 11 MOVE Month-Name (Sub) to Month-Name-OutEND-SEARCH.

Searching Arrays – Sorted Arrays1 January

2 February

3 March

4 April

5 May

6 June

7 July

8 August

9 September

10 October

11 November

12 December

Searching Arrays – Sorted Arrays(Binary Sort)

01 Month-Names-Array.05 Month-Entries

OCCURS 12 TIMES INDEXED BY Sub

ASCENDING KEY IS MONTH-NUMBER.10 Month-Number PIC 9(2).10 Month-Name PIC X(15).

SEARCH ALL Month-Entries AT END

MOVE ‘Error’ to Month-Name-out WHEN Month-Number (Sub) = 11 MOVE Month-Name (Sub) to Month-Name-OutEND-SEARCH.

26

Review of someBasics

27

Moving Data Basics

The MOVE

28

MOVE ident1 TO ident2

• It copies the contents of a field, variable, or literal into another field or variable

• The fields and variables must be defined in the data division accordingly

• Ident1 = any variable defined in the data division or any literal

• Literal:

Numeric constant such as -1.25 and 350.456

Alphanumeric constant such as ‘JOHN’ and ’OFFICE’

29

MOVE ident1 TO ident2

• Ident2= any variable defined in the data division or any literal

• Ident1is called the sending variable

• Ident2 is called the receiving variable

• Ident1 and Ident2 are expected to be of the same type (both alphanumeric or both numeric)

• Size can be different but programmer should be aware of abnormal results

30

MOVE Examples WORKING-STORAGE SECTION. ====

01 WORKING-VARIABLES. 05 PLANT1-DEPART PIC X(4). 05 PLANT2-DEPART PIC X(6). 05 PLANT1-STAFF PIC 999. 05 PLANT1-SALARY PIC 9999V99. 05 PLANT2-STAFF PIC 999. 05 PLANT2-SALARY PIC 9999V99.

PROCEDURE DIVISION.

===

MOVE ‘OFFI’ TO PLANT1-DEPART MOVE ‘PRODUC’ TO PLANT2-DEPART MOVE PLANT2-STAFF TO PLANT1-STAFF

===

MOVE 257.89 TO PLANT1-SALARY MOVE 340 TO PLANT2-STAFF MOVE PLANT1-SALARY TO PLANT2-SALARY

31

Il lustration of the MOVE statement: Alphanumeric Sending Field to AlphanumericReceiving Field

SENDING FIELD RECEIVING FIELD

PICTURE CONTENTS PICTURE CONTENTS

(a) X(5) A B C D E X(5) A B C D E

(b) X(5) A B C D E X(4) A B C D

(c) X(5) A B C D E X(6) A B C D E F

MOVE SENDING-FIELD TO RECEIVING-FIELD

Content of the Receiving field after MOVE execution

Content of the Receiving field after MOVE execution

32

Illustration of the MOVE statement: Numeric Sending Field to Numeric ReceivingField

SENDING FIELD RECEIVING FIELD

PICTURE CONTENTS PICTURE CONTENTS

(a) 9(5) 1 2 3 4 5 9(5) 1 2 3 4 5

(b) 9(5) 1 2 3 4 5 9(4) 2 3 4 5

(c) 9(5) 1 2 3 4 5 9(6) 0 1 2 3 4 5

(d) 9(3)V99 1 2 3 v 4 5 9(3) 1 2 3

(e) 9(3)V99 1 2 3 v 4 5 9V99 3 v 4 5

(f) 9(3) 1 2 3 9(3)V99 1 2 3 v 0 0

MOVE SENDING-FIELD TO RECEIVING-FIELD

Contents of Receiving fields after MOVE execution

Contents of Receiving fields after MOVE execution

33

NUMERIC EDITED FIELDS

• Variable used as a MASK that present the contents of a variable in a meaningful way to the user

• Used as output variables: sent to a printer, monitor, etc.

• Basic editing:

$

decimal point sign

suppression of leading zeros

34

NUMERIC EDITED FIELDS 01 DETAIL-LINE. 05 FILLER PIC X(8) VALUE SPACES. 05 DET-NAME PIC X(25). 05 FILLER PIC XX VALUE SPACES. 05 DET-HOURS PIC ZZZ. 05 FILLER PIC XX VALUE SPACES. 05 DET-PAY PIC $Z,ZZZ.99.

05 FILLER PIC X(92) VALUE SPACES.

PROCEDURE DIVISION.

===

====

PIC ZZZ

Any leading zero is replaced by blanks after the MOVE

PIC ZZZ

Any leading zero is replaced by blanks after the MOVE

3 2 MOVE 032 TO DET-HOURS

DET-HOURS

35

NUMERIC EDITED FIELDS AND THE MOVE STATEMENT

01 DETAIL-LINE. 05 FILLER PIC X(8) VALUE SPACES. 05 DET-NAME PIC X(25). 05 FILLER PIC XX VALUE SPACES. 05 DET-HOURS PIC ZZZ. 05 FILLER PIC XX VALUE SPACES. 05 DET-PAY PIC $Z,ZZZ.99.

05 FILLER PIC X(92) VALUE SPACES.

PROCEDURE DIVISION.

===

====

PIC $Z,ZZZ.99

Any leading zero is replaced by blanks and $ inserted to the left after the MOVE

PIC $Z,ZZZ.99

Any leading zero is replaced by blanks and $ inserted to the left after the MOVE

$ 985.27 MOVE 098527 TO DET-PAY

MOVE 198527 TO DET-PAY $1,985.27DET-PAY

36

Moving Record To Record 01 PRINT-LINE PIC X(132).

WORKING-STORAGE SECTION. 01 HEADING-LINE. 05 FILLER PIC X(12) VALUE 'EMPLOYEE... '. 05 FILLER PIC X(110) VALUE SPACES.

PROCEDURE DIVISION.

MOVE HEADING-LINE TO PRINT-LINE

• The entire content of PRINT-LINE is moved to HEADING-LINE• Size of both records should be the same; otherwise, truncation occurs• The content is moved as ALPHANUMERIC: from left to right

37

PERFORM Basics

The PERFORM…UNTIL

38

The PERFORM UNTIL

• Executes a paragraph (group of statements) until a condition is met

• The condition must be changed within the paragraph in order to allow the loop end

• Format:

PERFORM paragraph-name UNTIL condition

39

CONDITION? ATRUE

FALSE

(a) DO WHILE Construct

The Iteration StructurePERFORM….UNTIL is equivalent to DO…WHILE

PERFORM….UNTIL is equivalent to DO…WHILE

MOVE ‘Y’ TO FLAG

PERFORM UPDATE-FILE UNTIL FLAG = ‘N’

====

UPDATE-FILE.

COMPUTE SALES-TOTAL = SALES-WEEK + PREVIOUS-YEAR

IF SALES-TOTAL

MOVE ‘N’ TO FLAG.

= ===

40

PROCESS APOST.

IDENTIFICATION DIVISION. PROGRAM-ID. PAYREP. AUTHOR. ANDRE BERNS. DATE-WRITTEN. JAN/13. DATE-COMPILED. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT PAYROLL-FILE ASSIGN TO DATABASE-PT001F ORGANIZATION IS SEQUENTIAL. SELECT PRINT-FILE ASSIGN TO PRINTER.

DATA DIVISION. FILE SECTION. FD PAYROLL-FILE RECORD CONTAINS 45 CHARACTERS DATA RECORD IS EMPLOYEE-IN.

01 EMPLOYEE-IN. 05 EMP-NAME PIC X(25). 05 EMP-HOURS PIC 9(03). 05 EMP-RATE PIC 99V9 USAGE COMP-3. 05 EMP-DEP PIC X(15).

FD PRINT-FILE RECORD CONTAINS 132 CHARACTERS DATA RECORD IS PRINT-LINE. 01 PRINT-LINE PIC X(132).

WORKING-STORAGE SECTION.

01 HEADING-LINE. 05 FILLER PIC X(12) VALUE 'EMPLOYEE... '. 05 FILLER PIC X(110) VALUE SPACES.

01 DETAIL-LINE. 05 FILLER PIC X(8) VALUE SPACES. 05 DET-NAME PIC X(25). 05 FILLER PIC XX VALUE SPACES. 05 DET-HOURS PIC ZZZ. 05 FILLER PIC XX VALUE SPACES. 05 DET-PAY PIC $Z,ZZZ.99. 05 FILLER PIC X(92) VALUE SPACES.

77 EOF-FLAG PIC X VALUE SPACES.

41

PROCEDURE DIVISION.00-MAIN. OPEN INPUT PAYROLL-FILE OUTPUT PRINT-FILE. READ PAYROLL-FILE AT END MOVE 'N' TO EOF-FLAG END-READ.

PERFORM HEADER-LINE

PERFORM PROCESS-RECORDS UNTIL EOF-FLAG = 'N'.

CLOSE PAYROLL-FILE PRINT-FILE. STOP RUN.

HEADER-LINE. MOVE HEADING-LINE TO PRINT-LINE. WRITE PRINT-LINE.

PROCESS-RECORDS. MOVE EMP-NAME TO DET-NAME MOVE EMP-HOURS TO DET-HOURS COMPUTE DET-PAY = EMP-HOURS * EMP-RATE MOVE DETAIL-LINE TO PRINT-LINE

WRITE PRINT-LINE

READ PAYROLL-FILE AT END MOVE 'N' TO EOF-FLAG END-READ.

Putting the pieces together