Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and...

38
Any Questions!

Transcript of Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and...

Page 1: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Any Questions!

Page 2: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Agenda

• Fun with Functions

– how to get the system date

• Condition Names

• INDARA and SI

• Iteration

• Logical Files

• Positioning the file pointer

Page 3: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

IBM LibraryCOBOL

reference linksIBM Boulder, Colorado library

 

http://publib.boulder.ibm.com/infocenter/iseries/v5r4/index.jsp

 

COBOL Programmers Manual

 

http://publib.boulder.ibm.com/iseries/v5r2/ic2924/books/c0925393.pdf

 

 

Page 4: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Fun with Functions

Refer to COBOL Intrinsic functions handout

Move FUNCTION CURRENT DATE (1:8) to …

Page 5: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Condition Names

• Used with Code Fields– Eg. ARE-THERE-MORE-RECORDS– Eg. FINAL-GRADE– Eg. Indicators

Page 6: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Condition Names

01 ARE-THERE-MORE-RECORDS PIC X(3) VALUE ‘YES’.88 THERE-ARE-MORE-RECORDS VALUE ‘YES’.88 END-OF-FILE VALUE ‘NO’.

IF THERE-ARE-MORE-RECORDSREAD EMPLOYEE-FILE.

IF END-OF-FILEPERFORM TERMINATION-RTN.

Page 7: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Set Verb

• Used to initialize fields to a Condition-Name.

01 ARE-THERE-MORE-RECORDS PIC X(3).

88 THERE-ARE-MORE-RECORDS VALUE ‘YES’.

88 END-OF-FILE VALUE ‘NO’.

SET END-OF-FILE TO TRUE.

Page 8: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Conditions Cont’d

01 WORK-DAYS PIC X(3).88 MONDAY VALUE ‘MON’.88 TUESDAY VALUE ‘TUE’.88 WEDNESDAY VALUE ‘WED’.88 THURSDAY VALUE ‘THU’88 FRIDAY VALUE ‘FRI’.

SET MONDAY TO TRUE.IF FRIDAY

DISPLAY ‘GO HOME EARLY’.

Page 9: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Conditions Cont’d

01 FALL-MONTHS PIC X(3).88 SEPTEMBER VALUE ‘SEP’.88 OCTOBER VALUE ‘OCT’.88 NOVEMBER VALUE ‘NOV’.88 DECEMBER VALUE ‘DEC’.

IF OCTOBERDISPLAY ‘HAPPY HALLOWEEN!!’

SET DECEMBER TO TRUE.

Page 10: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

INDARA and SI

The relation ship between the externally declared (DDS) interactive screen file

and the COBOL internally declared indicator usage area

Page 11: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

As externally defined and created in DDS

0000.30 A DSPSIZ(24 80 *DS3)

0000.40 A INDARA In file area (GLOBAL)

0000.50 A CA03(03 'Function Key 03 =

0000.60 A CA12(12 'Function Key 12 =

0000.70 A R SCREEN1

0000.80 A 1 9'ENTER' in RECORD area (LOCAL)

0000.90 A 1 26'PAYROLL DEPARTMENT'

0001.00 A 1 59'C1401.1'

0001.10 A 3 2'Type choice, press Enter.'

0001.20 A 5 4'Employee number . .'

0001.30 A EEMPNO 5D 0I 5 24ALIAS(SCR1_EMPLOYEE_NUMBER)

0001.40 A 99 ERRMSG('Employee number not

0001.50 A Re-enter valid number.' 99

0001.60 A 23 2'F3=Exit'

Page 12: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

SI special indicators - send to the screen for screen behavior / actionControl-area - keyed response received form the “screen”

0018.00 FILE-CONTROL.

0019.00 SELECT DISPLAY-FILE

0020.00 ASSIGN TO WORKSTATION-HM100DSP-SI

0021.00 ORGANIZATION IS TRANSACTION

0022.00 CONTROL-AREA IS WS-CONTROL.

0030.00 DATA DIVISION.

0032.00 FILE SECTION.

0033.00

0034.00 *File Definition for a Program Described File

0036.00 FD DISPLAY-FILE.

0038.00 01 DISPLAY-RECORD.

0039.00 COPY DD-ALL-FORMATS OF HM100DSP.

0045.00

0046.00 WORKING-STORAGE SECTION.

Page 13: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

indicatorsRESPONSE and RESULTING

0078.00 01 WS-CONTROL.

0079.00 05 WS-FUNCTION-KEY PIC X(2).

0080.00 88 WS-FUNCTION-KEY-03 VALUE '03'.

0083.00 88 NO-FUNCTION-KEY-WAS-PRESSED VALUE '00'.

0084.00 05 WS-DEVICE-NAME PIC X(10).

0085.00 05 WS-RECORD-FORMAT PIC X(10).

0087.00 01 WS-INDICATOR-LIST.

0088.00 05 IN99 INDICATOR 99 PIC 1 VALUE B'0'.

0089.00 88 INCORRECT-ACTION-CODE VALUE B'1'.

0090.00 88 CORRECT-ACTION-CODE VALUE B'0'.

0091.00 05 IN98 INDICATOR 98 PIC 1 VALUE B'0'.

0092.00 88 INVALID-HORSE VALUE B'1'.

0093.00 88 VALID-HORSE VALUE B'0'.

0094.00 05 IN97 INDICATOR 97 PIC 1 VALUE B'0'.

0095.00 88 REPORT-PRINTED VALUE B'1'.

0096.00 88 REPORT-NOT-PRINTED VALUE B'0'.

Page 14: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Program check and response logic

0216.00 EVALUATE TRUE screen variable

0217.00 WHEN SCR1-ACTION-CODE OF PROMPT-I = 'P'

0218.00 PERFORM 210-print-rtn

0224.00 WHEN OTHER

0225.00 SET INCORRECT-ACTION-CODE TO TRUE

0227.00 END-EVALUATE.

0249.01

0249.02 if not ws-function-key-03

0249.03 move save-action to scr1-action-code of prompt-o

0249.04 move save-horse to scr1-horse-code of prompt-o

0249.05 * Write the prompt screen to the screen

0249.06 WRITE DISPLAY-RECORD

0249.07 FORMAT IS 'PROMPT '

0249.08 INDICATORS ARE WS-INDICATOR-LIST

0249.09 end-write

0249.11 * Wait for input

0249.12 READ DISPLAY FILE RECORD

Page 15: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Option Indicators and Conditions

01 WS-indicators. 05 IN90 INDICATOR 90 PIC 1.

88 display-message value B’1’.88 dont-display-message value B’0’.

Set display-message to true.Set dont-display-message to true.If display-messageIf don’t-display-messageIf not display-message

Page 16: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Response Indicators and Conditions

01 WS-Control.05 ws-function-key pic x(2).

88 F3 value ’03’88 F12 value ’12’.88 Enter value ’00’

05 ws-device-name pic x(10).05 ws-record-format pic x(10).

If F3If not F3

Page 17: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Iteration

Looping

Page 18: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

BASIC Perform Statement

PERFORM (paragraph-name)

Page 19: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Basic PERFORM

READ Emp-File

PERFORM DSP-Rtn

STOP RUN

DSP-RTN

move emp-in to emp-out.

write dsp-record

format is ‘SCREEN’.

read dsp-file record.

Page 20: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

PERFORM Until

PERFORM paragraph-name

UNTIL Condition

Page 21: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

PERFORM Until

ConditionMet?

Execute Program

Statements

NO

YES

Page 22: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

PERFORM Until

READ Emp-File

AT END Move ‘YES’ TO EOF.

PERFORM Dsp-Rtn UNTIL EOF = ‘Y’

STOP RUN

DSP-RTN

move emp-in to emp-out.

write dsp-record

format is ‘SCREEN’.

read dsp-file RECORD.

read emp-file

at end

move ‘YES’ to EOF.

Page 23: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

PERFORM X Times

PERFORM (paragraph-name) THROUGH/THRU (paragraph-name)

(integer/variable) TIMES

Page 24: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

PERFORM X Times

Number ofTimes Met?

Execute Program

Statements

NO

YES

Page 25: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

PERFORM X Times

READ Emp-File

AT END Move ‘YES’ TO EOF.

PERFORM Dsp-Rtn

5 TIMES

STOP RUN

DSP-RTN

move emp-in to emp-out.

write dsp-record

format is ‘SCREEN’.

read dsp-file record.

Page 26: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

PERFORM With Test After

PERFORM (paragraph-name) THROUGH/THRU (paragraph-name)

WITH TEST AFTER

UNTIL Condition

Page 27: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

PERFORM With Test After

Condition Met?

Execute Program

Statements

NO

YES

Page 28: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

PERFORM With Test After

READ Emp-File

AT END Move ‘YES’ TO EOF.

PERFORM Dsp-Rtn

WITH TEST AFTER

UNTIL EOF = ‘Y’

STOP RUN

DSP-RTN

move emp-in to emp-out.

write dsp-record

format is ‘SCREEN’.

read dsp-file record.

read emp-file

AT END

MOVE ‘YES’ TO EOF.

Page 29: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

PERFORMs within PERFORMs

READ Emp-File

AT END Move ‘YES’ TO EOF.

PERFORM DSP-Rtn UNTIL 5 TIMES

STOP RUN

DSP-RTN

MOVE EMP-IN TO EMP-OUT.

PERFORM Write-Rtn

Page 30: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Iteration Statement to Use?

• Perform Until– Tests for the condition first– Statements are executed only if the condition is

true

• Perform With Test After– tests for the condition last– Statements are always executed at least once

Page 31: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Iteration Statement to Use?

• Perform X Times– Use this when you know the number of times

the paragraph(s) are to be executed.

Page 32: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Sorting Data

Using Access Paths

Page 33: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Physical Files vs Logical Files

EMPLOYEEPF *FILE

EMPLOYEE *FILE

Physical Files or Logical Files?

Page 34: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Externally Described Files

• Select Statement when physical/logical file has a key.

SELECT Cobol-file-name

ASSIGN TO database-actual-file-name

[ORGANIZATION IS INDEXED]

[ACCESS MODE IS SEQUENTIAL]

RECORD KEY is data-element.

(data-element could be EXTERNaLLY-DESCRIBED-KEY)

Page 35: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Externally Described Files

• Copying the record layout.

FD Cobol-file-name.01 Cobol-Record-Name.COPY DD-actualrecordname OF actualfilename.

(DD can be replaced by DDS if you require the 10 char field names instead of the aliases)

Page 36: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Handy Physical File Commands

DSPPFM – Display Physical File Member

Displays the contents of a Physical File in arrival sequence.

DSPFD – Display File Description

Information about the file – eg access path.

DSPFFD – Display File Field Description

Displays the fields in the file.

Page 37: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Positioning the File Pointer

Start Verb

Page 38: Any Questions!. Agenda Fun with Functions –how to get the system date Condition Names INDARA and SI Iteration Logical Files Positioning the file pointer.

Start Verb

Used only with Sequentially defined files.

Initialize the record key

START file-nameKey ConditionINVALID KEY

Perform Invalid-LogicNOT INVALID KEY

Perform valid-logicEND-START.