|
10 | 10 | FILE-CONTROL. |
11 | 11 | SELECT PRINT-LINE ASSIGN TO PRTLINE. |
12 | 12 | SELECT ACCT-REC ASSIGN TO ACCTREC. |
| 13 | + *SELECT clause creates an internal file name |
| 14 | + *ASSIGN clause creates a name for an external data source, |
| 15 | + *which is associated with the JCL DDNAME used by the z/OS |
| 16 | + *e.g. ACCTREC is linked in JCL file CBL0001J to &SYSUID..DATA |
| 17 | + *where &SYSUID. stands for Your z/OS user id |
| 18 | + *e.g. if Your user id is Z54321, |
| 19 | + *the data set used for ACCTREC is Z54321.DATA |
13 | 20 | *------------- |
14 | 21 | DATA DIVISION. |
15 | 22 | *------------- |
|
19 | 26 | 05 ACCT-NO-O PIC X(8). |
20 | 27 | 05 ACCT-LIMIT-O PIC $$,$$$,$$9.99. |
21 | 28 | 05 ACCT-BALANCE-O PIC $$,$$$,$$9.99. |
| 29 | + * PIC $$,$$$,$$9.99 -- Alternative for PIC on chapter 7.2.3, |
| 30 | + * using $ to allow values of different amounts of digits |
| 31 | + * and .99 instead of v99 to allow period display on output |
22 | 32 | 05 LAST-NAME-O PIC X(20). |
23 | 33 | 05 FIRST-NAME-O PIC X(15). |
24 | 34 | 05 COMMENTS-O PIC X(50). |
| 35 | + * since the level 05 is higher than level 01, |
| 36 | + * all variables belong to PRINT-REC (see chapter 7.3.3) |
25 | 37 | * |
26 | 38 | FD ACCT-REC RECORDING MODE F. |
27 | 39 | 01 ACCT-FIELDS. |
28 | 40 | 05 ACCT-NO PIC X(8). |
29 | 41 | 05 ACCT-LIMIT PIC S9(7)V99 COMP-3. |
30 | 42 | 05 ACCT-BALANCE PIC S9(7)V99 COMP-3. |
| 43 | + * PIC S9(7)v99 -- seven-digit plus a sign digit value |
| 44 | + * COMP-3 -- packed BCD (binary coded decimal) representation |
31 | 45 | 05 LAST-NAME PIC X(20). |
32 | 46 | 05 FIRST-NAME PIC X(15). |
33 | 47 | 05 CLIENT-ADDR. |
|
49 | 63 | * |
50 | 64 | READ-NEXT-RECORD. |
51 | 65 | PERFORM READ-RECORD |
| 66 | + * The previous statement is needed before entering the loop. |
| 67 | + * Both the loop condition LASTREC = 'Y' |
| 68 | + * and the call to WRITE-RECORD depend on READ-RECORD having |
| 69 | + * been executed before. |
| 70 | + * The loop starts at the next line with PERFORM UNTIL |
52 | 71 | PERFORM UNTIL LASTREC = 'Y' |
53 | 72 | PERFORM WRITE-RECORD |
54 | 73 | PERFORM READ-RECORD |
|
0 commit comments