You are on page 1of 15

10/5/2019 Examples of Using Indicators in ILE COBOL Programs

Modernize your platform with IBM i 7.4


Use the latest features to drive innovation
See how 

Home  IBM i 7.1  Programming  


Programming languages  COBOL
ILE COBOL Programmer's Guide  ILE COBOL Input-Output Considerations  Using Transaction Files 
Using Indicators with Transaction Files 

Examples of Using Indicators in ILE COBOL


Programs
Search in all products

Search in this product... 


Change version or product 

Rate this content


 Print  PDF   Help Take a tour

Examples of Using Indicators in ILE COBOL Programs


This section contains examples of ILE COBOL programs that illustrate the use of indicators in
either a record area or a separate indicator area.

All of the ILE COBOL programs do the following:

1. Determine the current date.


2. If it is the first day of the month, turn on an option indicator that causes an output field to
appear and blink.
3. Allow you to press function keys to terminate the program, or turn on response indicators
and call programs to write daily or monthly reports.
https://www.ibm.com/support/knowledgecenter/en/ssw_ibm_i_71/rzase/sc092540641.htm 1/15
10/5/2019 Examples of Using Indicators in ILE COBOL Programs

Figure 135 shows an ILE COBOL program that uses indicators in the record area but does not
use the INDICATORS phrase in any I/O statement. Figure 134 shows the associated DDS for
the file.

Figure 136 shows an ILE COBOL program that uses indicators in the record area and the
INDICATORS phrase in the I/O statements. The associated DDS for Figure 136 is Figure 134.

Figure 138 shows an ILE COBOL program that uses indicators in a separate indicator area,
defined in the WORKING-STORAGE SECTION by using the Format 2 COPY statement. Figure
137 shows the associated DDS for the file.

Figure 139 shows an ILE COBOL program that uses indicators in a separate indicator area,
defined in a table in the WORKING-STORAGE SECTION. The associated DDS for the file is the
same as Figure 137.

Figure 134. Example of a Program Using Indicators in the Record Area without Using the
INDICATORS Phrase in the I/O Statement—DDS
....+....1....+....2....+....3....+....4....+....5....+....6....+....7...
A* DISPLAY FILE DDS FOR INDICATOR EXAMPLES - INDICATORS IN RECORD ARE
A* DSPFILEX  1 
A  2  R FORMAT1  3 CF01(99 'END OF PROGRAM')
A CF05(51 'DAILY REPORT')
A CF09(52 'MONTHLY REPORT')

Rate this content


A*
A  4  10 10'DEPARTMENT NUMBER:'
A DEPTNO 5 I 10 32
A  5 01 20 26'PRODUCE MONTHLY REPORTS'
A DSPATR(BL)
A*
A  6  24 01'F5 = DAILY REPORT'
A 24 26'F9 = MONTHLY REPORT'
A 24 53'F1 = TERMINATE'
A R ERRFMT
A 98 6 5'INPUT-OUTPUT ERROR'

 1 
The INDARA keyword is not used; indicators are stored in the record area with the data
fields.
 2 
Record format FORMAT1 is specified.
 3 
Three indicators are associated with three function keys. Indicator 99 will be set on when
you press F1, and so on.
 4 
https://www.ibm.com/support/knowledgecenter/en/ssw_ibm_i_71/rzase/sc092540641.htm 2/15
10/5/2019 Examples of Using Indicators in ILE COBOL Programs

One field is defined for input.


 5 
Indicator 01 is defined to cause the associated constant field to blink if the indicator is on.
 6 
The function (F) key definitions are documented on the workstation display.
Figure 135. Example of a Program Using Indicators in the Record Area without Using the
INDICATORS Phrase in the I/O Statement—COBOL Source Program
5722WDS V5R4M0 060210 LN
IBM ILE COBOL CBLGUIDE/INDIC1
S o u r c e
STMT PL SEQNBR -A 1 B..+....2....+....3....+....4....+....5....+....6...
1 000100 IDENTIFICATION DIVISION.
2 000200 PROGRAM-ID. INDIC1.
000300* SAMPLE PROGRAM WITH INDICATORS IN RECORD AREA.
000400
3 000500 ENVIRONMENT DIVISION.
4 000600 CONFIGURATION SECTION.
5 000700 SOURCE-COMPUTER. IBM-ISERIES
6 000800 OBJECT-COMPUTER. IBM-ISERIES
7 000900 INPUT-OUTPUT SECTION.
8 001000 FILE-CONTROL.
9 001100 SELECT DISPFILE
10 001200 ASSIGN TO WORKSTATION-DSPFILEX  1 
11 001300 ORGANIZATION IS TRANSACTION
12 001400 ACCESS IS SEQUENTIAL.
001500
13 001600 DATA DIVISION.

Rate this content


14 001700 FILE SECTION.
15 001800 FD DISPFILE.
16 001900 01 DISP-REC.
002000 COPY DDS-ALL-FORMATS OF DSPFILEX.  2 
17 +000001 05 DSPFILEX-RECORD PIC X(8).
+000002* INPUT FORMAT:FORMAT1 FROM FILE DSPFILEX OF LIBRARY
+000003*
18 +000004 05 FORMAT1-I REDEFINES DSPFILEX-RECORD.
19 +000005 06 FORMAT1-I-INDIC.
20 +000006 07 IN99 PIC 1 INDIC 99.  3 
+000007* END OF PROGRAM
21 +000008 07 IN51 PIC 1 INDIC 51.
+000009* DAILY REPORT
22 +000010 07 IN52 PIC 1 INDIC 52.
+000011* MONTHLY REPORT
23 +000012 06 DEPTNO PIC X(5).
+000013* OUTPUT FORMAT:FORMAT1 FROM FILE DSPFILEX OF LIBRARY
+000014*
24 +000015 05 FORMAT1-O REDEFINES DSPFILEX-RECORD.
25 +000016 06 FORMAT1-O-INDIC.
26 +000017 07 IN01 PIC 1 INDIC 01.
+000018* INPUT FORMAT:ERRFMT FROM FILE DSPFILEX OF LIBRARY
https://www.ibm.com/support/knowledgecenter/en/ssw_ibm_i_71/rzase/sc092540641.htm 3/15
10/5/2019 Examples of Using Indicators in ILE COBOL Programs
+000019*
+000020* 05 ERRFMT-I REDEFINES DSPFILEX-RECORD.
+000021* OUTPUT FORMAT:ERRFMT FROM FILE DSPFILEX OF LIBRARY
+000022*
27 +000023 05 ERRFMT-O REDEFINES DSPFILEX-RECORD.
28 +000024 06 ERRFMT-O-INDIC.
29 +000025 07 IN98 PIC 1 INDIC 98.
002100
30 002200 WORKING-STORAGE SECTION.
31 002300 01 CURRENT-DATE.
32 002400 05 CURR-YEAR PIC 9(2).
33 002500 05 CURR-MONTH PIC 9(2).
34 002600 05 CURR-DAY PIC 9(2).
35 002700 01 INDIC-AREA.  4 
36 002800 05 IN01 PIC 1.

5722WDS V5R4M0 060210 LN IBM ILE COBOL CBLGUIDE/INDIC1


STMT PL SEQNBR -A 1 B..+....2....+....3....+....4....+....5....+....6...
37 002900 88 NEW-MONTH VALUE B"1".  5 
38 003000 05 IN51 PIC 1.
39 003100 88 WANT-DAILY VALUE B"1".
40 003200 05 IN52 PIC 1.
41 003300 88 WANT-MONTHLY VALUE B"1".
42 003400 05 IN98 PIC 1.
43 003500 88 IO-ERROR VALUE B"1".
44 003600 05 IN99 PIC 1.
45 003700 88 NOT-END-OF-JOB VALUE B"0".

Rate this content


46 003800 88 END-OF-JOB VALUE B"1".
003900
47 004000 PROCEDURE DIVISION.
48 004100 DECLARATIVES.
004200 DISPLAY-ERR-SECTION SECTION.
004300 USE AFTER STANDARD EXCEPTION PROCEDURE ON DISPFILE.
004400 DISPLAY-ERR-PARAGRAPH.
49 004500 SET IO-ERROR TO TRUE
50 004600 MOVE CORR INDIC-AREA TO ERRFMT-O-INDIC
*** CORRESPONDING items for statement 50:
*** IN98
*** End of CORRESPONDING items for statement 50
51 004700 WRITE DISP-REC FORMAT IS "ERRFMT"
004800 END-WRITE
52 004900 CLOSE DISPFILE.
53 005000 STOP RUN.
005100 END DECLARATIVES.
005200
005300 MAIN-PROGRAM SECTION.
005400 MAINLINE.
54 005500 OPEN I-O DISPFILE.
55 005600 ACCEPT CURRENT-DATE FROM DATE.
56 005700 SET NOT END OF JOB TO TRUE
https://www.ibm.com/support/knowledgecenter/en/ssw_ibm_i_71/rzase/sc092540641.htm 4/15
10/5/2019 Examples of Using Indicators in ILE COBOL Programs
56 005700 SET NOT-END-OF-JOB TO TRUE.
57 005800 PERFORM UNTIL END-OF-JOB
005900
58 006000 MOVE ZEROS TO INDIC-AREA  6 
59 006100 IF CURR-DAY = 01 THEN
60 006200 SET NEW-MONTH TO TRUE  7 
006300 END-IF
61 006400 MOVE CORR INDIC-AREA TO FORMAT1-O-INDIC  8 
*** CORRESPONDING items for statement 61:
*** IN01
*** End of CORRESPONDING items for statement 61
62 006500 WRITE DISP-REC FORMAT IS "FORMAT1"  9 
006600 END-WRITE
006700
63 006800 MOVE ZEROS TO INDIC-AREA
64 006900 READ DISPFILE FORMAT IS "FORMAT1"  10 
007000 END-READ
65 007100 MOVE CORR FORMAT1-I-INDIC TO INDIC-AREA  11 
*** CORRESPONDING items for statement 65:
*** IN99
*** IN51
*** IN52
*** End of CORRESPONDING items for statement 65
66 007200 IF WANT-DAILY THEN
67 007300 CALL "DAILY" USING DEPTNO
007400 ELSE
68 007500 IF WANT-MONTHLY THEN

Rate this content


69 007600 CALL "MONTHLY" USING DEPTNO  12 
007700 END-IF
007800 END-IF
007900
008000 END-PERFORM.
70 008100 CLOSE DISPFILE.
71 008200 STOP RUN.
* * * * * E N D O F S O U R C E * * * *

 1 
The separate indicator area attribute, SI, is not coded in the ASSIGN clause. As a result, the
indicators form part of the record area.
 2 
The Format 2 COPY statement defines data fields and indicators in the record area.
 3 
Because the file indicators form part of the record area, response and option indicators are
defined in the order in which they are used in the DDS, and the indicator numbers are
treated as documentation.
 4 
All indicators used by the program are defined with meaningful names in data description
entries in the WORKING-STORAGE SECTION. Indicator numbers are omitted here because
https://www.ibm.com/support/knowledgecenter/en/ssw_ibm_i_71/rzase/sc092540641.htm 5/15
10/5/2019 Examples of Using Indicators in ILE COBOL Programs

they have no effect.


 5 
For each indicator, a meaningful level-88 condition-name is associated with a value for that
indicator.
 6 
Initialize group level to zeros.
 7 
IN01 in the WORKING-STORAGE SECTION is set on if it is the first day of the month.
 8 
Indicators appropriate to the output of FORMAT1 are copied to the record area.
 9 
FORMAT1 is written to the workstation display with both data and indicator values in the
record area.
The INDICATORS phrase is not necessary because there is no separate indicator area and
indicator values have been set in the record area through the previous MOVE
CORRESPONDING statement.

 10 
FORMAT1, including both data and indicators, is read from the display.
 11 
The response indicators for FORMAT1 are copied from the record area to the data
description entries in the WORKING-STORAGE SECTION.
 12 
If F5 has been pressed, a program call is processed.
Figure 136. Example of Program Using Indicators in the Record Area and the INDICATORS

Rate this content


Phrase in I/O Statements–COBOL Source Program
5722WDS V5R4M0 060210 LN
IBM ILE COBOL CBLGUIDE/INDIC1
S o u r c e
STMT PL SEQNBR -A 1 B..+....2....+....3....+....4....+....5....+....6...
1 000100 IDENTIFICATION DIVISION.
2 000200 PROGRAM-ID. INDIC2.
000300* SAMPLE PROGRAM - FILE WITH INDICATORS IN RECORD AREA
000400
3 000500 ENVIRONMENT DIVISION.
4 000600 CONFIGURATION SECTION.
5 000700 SOURCE-COMPUTER. IBM-ISERIES
6 000800 OBJECT-COMPUTER. IBM-ISERIES
7 000900 INPUT-OUTPUT SECTION.
8 001000 FILE-CONTROL.
9 001100 SELECT DISPFILE
10 001200 ASSIGN TO WORKSTATION-DSPFILEX  1 
11 001300 ORGANIZATION IS TRANSACTION
12 001400 ACCESS IS SEQUENTIAL.
001500
13 001600 DATA DIVISION.
14 001700 FILE SECTION.
15 001800 FD DISPFILE.
16 001900 01 DISP-REC
https://www.ibm.com/support/knowledgecenter/en/ssw_ibm_i_71/rzase/sc092540641.htm 6/15
10/5/2019 Examples of Using Indicators in ILE COBOL Programs
16 001900 01 DISP-REC.
002000 COPY DDS-ALL-FORMATS OF DSPFILEX.  2 
17 +000001 05 DSPFILEX-RECORD PIC X(8).
+000002* INPUT FORMAT:FORMAT1 FROM FILE DSPFILEX OF LIBRARY
+000003*
18 +000004 05 FORMAT1-I REDEFINES DSPFILEX-RECORD.
19 +000005 06 FORMAT1-I-INDIC.
20 +000006 07 IN99 PIC 1 INDIC 99.  3 
+000007* END OF PROGRAM
21 +000008 07 IN51 PIC 1 INDIC 51.
+000009* DAILY REPORT
22 +000010 07 IN52 PIC 1 INDIC 52.
+000011* MONTHLY REPORT
23 +000012 06 DEPTNO PIC X(5).
+000013* OUTPUT FORMAT:FORMAT1 FROM FILE DSPFILEX OF LIBRARY
+000014*
24 +000015 05 FORMAT1-O REDEFINES DSPFILEX-RECORD.
25 +000016 06 FORMAT1-O-INDIC.
26 +000017 07 IN01 PIC 1 INDIC 01.
+000018* INPUT FORMAT:ERRFMT FROM FILE DSPFILEX OF LIBRARY
+000019*
+000020* 05 ERRFMT-I REDEFINES DSPFILEX-RECORD.
+000021* OUTPUT FORMAT:ERRFMT FROM FILE DSPFILEX OF LIBRARY
+000022*
27 +000023 05 ERRFMT-O REDEFINES DSPFILEX-RECORD.
28 +000024 06 ERRFMT-O-INDIC.
29 +000025 07 IN98 PIC 1 INDIC 98.

Rate this content


002100
30 002200 WORKING-STORAGE SECTION.
31 002300 01 CURRENT-DATE.
32 002400 05 CURR-YEAR PIC 9(2).
33 002500 05 CURR-MONTH PIC 9(2).
34 002600 05 CURR-DAY PIC 9(2).
002700
35 002800 77 IND-OFF PIC 1 VALUE B"0".

5722WDS V5R4M0 060210 LN IBM ILE COBOL CBLGUIDE/INDIC1


STMT PL SEQNBR -A 1 B..+....2....+....3....+....4....+....5....+....6...
36 002900 77 IND-ON PIC 1 VALUE B"1".
003000
37 003100 01 RESPONSE-INDICS.
38 003200 05 END-OF-PROGRAM PIC 1.  4 
39 003300 05 DAILY-REPORT PIC 1.
40 003400 05 MONTHLY-REPORT PIC 1.
41 003500 01 OPTION-INDICS.
42 003600 05 NEW-MONTH PIC 1.
43 003700 01 ERROR-INDICS.
44 003800 05 IO-ERROR PIC 1.
003900
45 004000 PROCEDURE DIVISION
https://www.ibm.com/support/knowledgecenter/en/ssw_ibm_i_71/rzase/sc092540641.htm 7/15
10/5/2019 Examples of Using Indicators in ILE COBOL Programs
45 004000 PROCEDURE DIVISION.
46 004100 DECLARATIVES.
004200 DISPLAY-ERR-SECTION SECTION.
004300 USE AFTER STANDARD EXCEPTION PROCEDURE ON DISPFILE.
004400 DISPLAY-ERR-PARAGRAPH.
47 004500 MOVE IND-ON TO IO-ERROR
48 004600 WRITE DISP-REC FORMAT IS "ERRFMT"
004700 INDICATORS ARE ERROR-INDICS
004800 END-WRITE
49 004900 CLOSE DISPFILE.
50 005000 STOP RUN.
005100 END DECLARATIVES.
005200
005300 MAIN-PROGRAM SECTION.
005400 MAINLINE.
51 005500 OPEN I-O DISPFILE.
52 005600 ACCEPT CURRENT-DATE FROM DATE.
53 005700 MOVE IND-OFF TO END-OF-PROGRAM.
54 005800 PERFORM UNTIL END-OF-PROGRAM = IND-ON
55 005900 MOVE ZEROS TO OPTION-INDICS
56 006000 IF CURR-DAY = 01 THEN  5 
57 006100 MOVE IND-ON TO NEW-MONTH
006200 END-IF
58 006300 WRITE DISP-REC FORMAT IS "FORMAT1"  6 
006400 INDICATORS ARE OPTION-INDICS
006500 END-WRITE
006600

Rate this content


59 006700 MOVE ZEROS TO RESPONSE-INDICS
60 006800 READ DISPFILE FORMAT IS "FORMAT1"  7 
006900 INDICATORS ARE RESPONSE-INDICS  8 
007000 END-READ
61 007100 IF DAILY-REPORT = IND-ON THEN
62 007200 CALL "DAILY" USING DEPTNO  9 
007300 ELSE
63 007400 IF MONTHLY-REPORT = IND-ON THEN
64 007500 CALL "MONTHLY" USING DEPTNO
007600 END-IF
007700 END-IF
007800
007900 END-PERFORM
65 008000 CLOSE DISPFILE.
66 008100 STOP RUN.
008200
* * * * * E N D O F S O U R C E * * * *

 1 
The separate indicator area attribute, SI, is not coded in the ASSIGN clause.
 2 
The Format 2 COPY statement defines data fields and indicators in the record area
https://www.ibm.com/support/knowledgecenter/en/ssw_ibm_i_71/rzase/sc092540641.htm 8/15
10/5/2019 Examples of Using Indicators in ILE COBOL Programs
The Format 2 COPY statement defines data fields and indicators in the record area.
 3 
Because the file does not have a separate indicator area, response and option indicators are
defined in the order in which they are used in the DDS, and the indicator numbers are
treated as documentation.
 4 
All indicators used by the program are defined with meaningful names in data description
entries in the WORKING-STORAGE SECTION. Indicator numbers are omitted here because
they have no effect. Indicators should be defined in the order needed by the display file.
 5 
IN01 in the WORKING-STORAGE SECTION is set on if it is the first day of the month.
 6 
FORMAT1 is written to the workstation display:
• The INDICATORS phrase causes the contents of the variable OPTION-INDICS to be
copied to the beginning of the record area.
• Data and indicator values are written to the workstation display.

 7 
FORMAT1, including both data and indicators, is read from the work station display.
 8 
The INDICATORS phrase causes bytes to be copied from the beginning of the record area to
RESPONSE-INDICS.
 9 
If F5 has been pressed, a program call is processed.
Figure 137. Example of a Program Using Indicators in a Separate Indicator Area, Defined in
WORKING-STORAGE by Using the COPY Statement ** DDS

Rate this content


....+....1....+....2....+....3....+....4....+....5....+....6....+....7...
A* DISPLAY FILE FOR INDICATOR EXAMPLES - INDICATORS IN SI AREA
A* DSPFILE
A INDARA  1 
A R FORMAT1 CF01(99 'END OF PROGRAM')
A CF05(51 'DAILY REPORT')
A CF09(52 'MONTHLY REPORT')
A*
A 10 10'DEPARTMENT NUMBER:'
A DEPTNO 5 I 10 32
A 01 20 26'PRODUCE MONTHLY REPORTS'
A DSPATR(BL)
A*
A 24 01'F5 = DAILY REPORT'
A 24 26'F9 = MONTHLY REPORT'
A 24 53'F1 = TERMINATE'
A R ERRFMT
A 98 6 5'INPUT-OUTPUT ERROR'

 1 
The INDARA keyword is specified; indicators are stored in a separate indicator area, not in
h d E f hi ifi i h DDS f
https://www.ibm.com/support/knowledgecenter/en/ssw_ibm_i_71/rzase/sc092540641.htm hi fil i h h h 9/15
10/5/2019 Examples of Using Indicators in ILE COBOL Programs
the record area. Except for this specification, the DDS for this file is the same as that shown
in Figure 134.
Figure 138. COBOL Listing Using Indicators in a Separate Indicator Area
5722WDS V5R4M0 060210 LN
IBM ILE COBOL CBLGUIDE/INDIC1
S o u r c e
STMT PL SEQNBR -A 1 B..+....2....+....3....+....4....+....5....+....6...
1 000100 IDENTIFICATION DIVISION.
2 000200 PROGRAM-ID. INDIC3.
000300* SAMPLE PROGRAM - FILE WITH SEPERATE INDICATORS AREA
000400
3 000500 ENVIRONMENT DIVISION.
4 000600 CONFIGURATION SECTION.
5 000700 SOURCE-COMPUTER. IBM-ISERIES
6 000800 OBJECT-COMPUTER. IBM-ISERIES
7 000900 INPUT-OUTPUT SECTION.
8 001000 FILE-CONTROL.
9 001100 SELECT DISPFILE
10 001200 ASSIGN TO WORKSTATION-DSPFILE-SI  1 
11 001300 ORGANIZATION IS TRANSACTION
12 001400 ACCESS IS SEQUENTIAL.
001500
13 001600 DATA DIVISION.
14 001700 FILE SECTION.
15 001800 FD DISPFILE.
16 001900 01 DISP-REC.
002000 COPY DDS-ALL-FORMATS OF DSPFILE.  2 

Rate this content


17 +000001 05 DSPFILE-RECORD PIC X(5).
+000002* INPUT FORMAT:FORMAT1 FROM FILE DSPFILE OF LIBRARY
+000003*
18 +000004 05 FORMAT1-I REDEFINES DSPFILE-RECORD.
19 +000005 06 DEPTNO PIC X(5).
+000006* OUTPUT FORMAT:FORMAT1 FROM FILE DSPFILE OF LIBRARY
+000007*
+000008* 05 FORMAT1-O REDEFINES DSPFILE-RECORD.
+000009* INPUT FORMAT:ERRFMT FROM FILE DSPFILE OF LIBRARY
+000010*
+000011* 05 ERRFMT-I REDEFINES DSPFILE-RECORD.
+000012* OUTPUT FORMAT:ERRFMT FROM FILE DSPFILE OF LIBRARY
+000013*
+000014* 05 ERRFMT-O REDEFINES DSPFILE-RECORD.
002100
20 002200 WORKING-STORAGE SECTION.
21 002300 01 CURRENT-DATE.
22 002400 05 CURR-YEAR PIC 9(2).
23 002500 05 CURR-MONTH PIC 9(2).
24 002600 05 CURR-DAY PIC 9(2).
002700
25 002800 77 IND-OFF PIC 1 VALUE B"0".
26 002900 77 IND-ON PIC 1 VALUE B"1"
https://www.ibm.com/support/knowledgecenter/en/ssw_ibm_i_71/rzase/sc092540641.htm 10/15
10/5/2019 Examples of Using Indicators in ILE COBOL Programs
26 002900 77 IND-ON PIC 1 VALUE B 1 .
003000
27 003100 01 DISPFILE-INDICS.
003200 COPY DDS-ALL-FORMATS-INDIC OF DSPFILE.  3 
28 +000001 05 DSPFILE-RECORD.
+000002* INPUT FORMAT:FORMAT1 FROM FILE DSPFILE OF LIBRARY
+000003*
29 +000004 06 FORMAT1-I-INDIC.
30 +000005 07 IN51 PIC 1 INDIC 51.  4 
+000006* DAILY REPORT
31 +000007 07 IN52 PIC 1 INDIC 52.

5722WDS V5R4M0 060210 LN IBM ILE COBOL CBLGUIDE/INDIC1


STMT PL SEQNBR -A 1 B..+....2....+....3....+....4....+....5....+....6...
+000008* MONTHLY REPORT
32 +000009 07 IN99 PIC 1 INDIC 99.
+000010* END OF PROGRAM
+000011* OUTPUT FORMAT:FORMAT1 FROM FILE DSPFILE OF LIBRARY
+000012*
33 +000013 06 FORMAT1-O-INDIC.
34 +000014 07 IN01 PIC 1 INDIC 01.
+000015* INPUT FORMAT:ERRFMT FROM FILE DSPFILE OF LIBRARY
+000016*
+000017* 06 ERRFMT-I-INDIC.
+000018* OUTPUT FORMAT:ERRFMT FROM FILE DSPFILE OF LIBRARY
+000019*
35 +000020 06 ERRFMT-O-INDIC.
36 +000021 07 IN98 PIC 1 INDIC 98.

Rate this content


003300
37 003400 PROCEDURE DIVISION.
38 003500 DECLARATIVES.
003600 DISPLAY-ERR-SECTION SECTION.
003700 USE AFTER STANDARD EXCEPTION PROCEDURE ON DISPFILE.
003800 DISPLAY-ERR-PARAGRAPH.
39 003900 MOVE IND-ON TO IN98 IN ERRFMT-O-INDIC
40 004000 WRITE DISP-REC FORMAT IS "ERRFMT"
004100 INDICATORS ARE ERRFMT-O-INDIC
004200 END-WRITE
41 004300 CLOSE DISPFILE.
42 004400 STOP RUN.
004500 END DECLARATIVES.
004600
004700 MAIN-PROGRAM SECTION.
004800 MAINLINE.
004900
43 005000 OPEN I-O DISPFILE.
44 005100 ACCEPT CURRENT-DATE FROM DATE.
45 005200 MOVE IND-OFF TO IN99 IN FORMAT1-I-INDIC.
46 005300 PERFORM UNTIL IN99 IN FORMAT1-I-INDIC = IND-ON
005400
https://www.ibm.com/support/knowledgecenter/en/ssw_ibm_i_71/rzase/sc092540641.htm 11/15
10/5/2019 Examples of Using Indicators in ILE COBOL Programs
005400
47 005500 MOVE ZEROS TO FORMAT1-O-INDIC
48 005600 IF CURR-DAY = 01 THEN
49 005700 MOVE IND-ON TO IN01 IN FORMAT1-O-INDIC  5 
005800 END-IF
50 005900 WRITE DISP-REC FORMAT IS "FORMAT1"
006000 INDICATORS ARE FORMAT1-O-INDIC  6
006100 END-WRITE
006200
51 006300 MOVE ZEROS TO FORMAT1-I-INDIC
52 006400 READ DISPFILE FORMAT IS "FORMAT1"
006500 INDICATORS ARE FORMAT1-I-INDIC  7 
006600 END-READ
53 006700 IF IN51 IN FORMAT1-I-INDIC = IND-ON THEN
54 006800 CALL "DAILY" USING DEPTNO
006900 ELSE
55 007000 IF IN52 IN FORMAT1-I-INDIC = IND-ON THEN
56 007100 CALL "MONTHLY" USING DEPTNO  8 
007200 END-IF
007300 END-IF
007400
007500 END-PERFORM
57 007600 CLOSE DISPFILE.
58 007700 STOP RUN.
007800
* * * * * E N D O F S O U R C E * * * *

Rate this content


 1 
The separate indicator area attribute, SI, is specified in the ASSIGN clause.
 2 
The Format 2 COPY statement generates data descriptions in the record area for data fields
only. The data description entries for the indicators are not generated because a separate
indicator area has been specified for the file.
 3 
The Format 2 COPY statement, with the INDICATOR attribute, INDIC, defines data
description entries in the WORKING-STORAGE SECTION for all indicators used in the DDS
for the record format for the file.
 4 
Because the file has a separate indicator area, the indicator numbers used in the data
description entries are not treated as documentation.
 5 
IN01 in the separate indicator area for FORMAT1 is set on if it is the first day of the month.
 6 
The INDICATORS phrase is required to send indicator values to the workstation display.
 7 
The INDICATORS phrase is required to receive indicator values from the workstation
display. If you have pressed F5, IN51 is set on.
 8 
If IN51 has been set on a program call is processed
https://www.ibm.com/support/knowledgecenter/en/ssw_ibm_i_71/rzase/sc092540641.htm 12/15
10/5/2019 Examples of Using Indicators in ILE COBOL Programs
If IN51 has been set on, a program call is processed.
Figure 139. Example of a Program Using Indicators in a Separate Indicator Area, Defined in a
Table in WORKING-STORAGE
5722WDS V5R4M0 060210 LN
IBM ILE COBOL CBLGUIDE/INDIC4
S o u r c e
STMT PL SEQNBR -A 1 B..+....2....+....3....+....4....+....5....+....6...
1 000100 IDENTIFICATION DIVISION.
2 000200 PROGRAM-ID. INDIC4.
000300* SAMPLE PROGRAM
000400* FILE WITH SEPERATE INDICATORS AREA IN WORKING STORAGE
000500
3 000600 ENVIRONMENT DIVISION.
4 000700 CONFIGURATION SECTION.
5 000800 SOURCE-COMPUTER. IBM-ISERIES
6 000900 OBJECT-COMPUTER. IBM-ISERIES
7 001000 INPUT-OUTPUT SECTION.
8 001100 FILE-CONTROL.
9 001200 SELECT DISPFILE
10 001300 ASSIGN TO WORKSTATION-DSPFILE-SI  1 
11 001400 ORGANIZATION IS TRANSACTION
12 001500 ACCESS IS SEQUENTIAL.
001600
13 001700 DATA DIVISION.
14 001800 FILE SECTION.
15 001900 FD DISPFILE.
16 002000 01 DISP-REC.

Rate this content


002100 COPY DDS-ALL-FORMATS OF DSPFILE.  2 
17 +000001 05 DSPFILE-RECORD PIC X(5).
+000002* INPUT FORMAT:FORMAT1 FROM FILE DSPFILE OF LIBRARY
+000003*
18 +000004 05 FORMAT1-I REDEFINES DSPFILE-RECORD.
19 +000005 06 DEPTNO PIC X(5).
+000006* OUTPUT FORMAT:FORMAT1 FROM FILE DSPFILE OF LIBRARY
+000007*
+000008* 05 FORMAT1-O REDEFINES DSPFILE-RECORD.
+000009* INPUT FORMAT:ERRFMT FROM FILE DSPFILE OF LIBRARY
+000010*
+000011* 05 ERRFMT-I REDEFINES DSPFILE-RECORD.
+000012* OUTPUT FORMAT:ERRFMT FROM FILE DSPFILE OF LIBRARY
+000013*
+000014* 05 ERRFMT-O REDEFINES DSPFILE-RECORD.
002200
20 002300 WORKING-STORAGE SECTION.
21 002400 01 CURRENT-DATE.
22 002500 05 CURR-YEAR PIC 9(2).
23 002600 05 CURR-MONTH PIC 9(2).
24 002700 05 CURR-DAY PIC 9(2).
002800
25 002900 01 INDIC-AREA
https://www.ibm.com/support/knowledgecenter/en/ssw_ibm_i_71/rzase/sc092540641.htm 13/15
10/5/2019 Examples of Using Indicators in ILE COBOL Programs
25 002900 01 INDIC-AREA.
26 003000 05 INDIC-TABLE OCCURS 99 PIC 1 INDICATOR 1.
27 003100 88 IND-OFF VALUE B"0".
28 003200 88 IND-ON VALUE B"1".
003300
29 003400 01 DISPFILE-INDIC-USAGE.
30 003500 05 IND-NEW-MONTH PIC 9(2) VALUE 01.
31 003600 05 IND-DAILY PIC 9(2) VALUE 51.  4 
32 003700 05 IND-MONTHLY PIC 9(2) VALUE 52.
33 003800 05 IND-IO-ERROR PIC 9(2) VALUE 98.
34 003900 05 IND-EOJ PIC 9(2) VALUE 99.

5722WDS V5R4M0 060210 LN IBM ILE COBOL CBLGUIDE/INDIC4


STMT PL SEQNBR -A 1 B..+....2....+....3....+....4....+....5....+....6...
004000
35 004100 PROCEDURE DIVISION.
36 004200 DECLARATIVES.
004300 DISPLAY-ERR-SECTION SECTION.
004400 USE AFTER STANDARD EXCEPTION PROCEDURE ON DISPFILE.
004500 DISPLAY-ERR-PARAGRAPH.
37 004600 SET IND-ON (IND-IO-ERROR) TO TRUE
38 004700 WRITE DISP-REC FORMAT IS "ERRFMT"
004800 INDICATORS ARE INDIC-TABLE
004900 END-WRITE
39 005000 CLOSE DISPFILE.
40 005100 STOP RUN.
005200 END DECLARATIVES.
005300

Rate this content


005400 MAIN-PROGRAM SECTION.
005500 MAINLINE.
41 005600 OPEN I-O DISPFILE.
42 005700 ACCEPT CURRENT-DATE FROM DATE.
43 005800 SET IND-OFF (IND-EOJ) TO TRUE.
44 005900 PERFORM UNTIL IND-ON (IND-EOJ)
006000
45 006100 MOVE ZEROS TO INDIC-AREA
46 006200 IF CURR-DAY = 01 THEN
47 006300 SET IND-ON (IND-NEW-MONTH) TO TRUE  5 
006400 END-IF
48 006500 WRITE DISP-REC FORMAT IS "FORMAT1"
006600 INDICATORS ARE INDIC-TABLE  6 
006700 END-WRITE
006800

Please note that DISQUS operates this forum. When you sign in to comment, IBM will provide your
email, first name and last name to DISQUS. That information, along with your comments, will be
governed by DISQUS’ privacy policy. By commenting, you are accepting the DISQUS terms of service.

https://www.ibm.com/support/knowledgecenter/en/ssw_ibm_i_71/rzase/sc092540641.htm 14/15
10/5/2019 Examples of Using Indicators in ILE COBOL Programs

Sign In

Comments

t Tweet f Share Sort by Best

Nothing in this discussion yet.

🔒 Disqus' Privacy PolicyPrivacy PolicyPrivacy

Do you want to...


Open a ticket and download fixes at the IBM Find a best practice for integrating
Support Portal technologies in IBM Redbooks

Find a technical tutorial in IBM Developer Explore, learn and succeed with training on
the IBM Skills Gateway

Rate this content


Contact Privacy Terms of use Accessibility Feedback Cookie preferences

English 

https://www.ibm.com/support/knowledgecenter/en/ssw_ibm_i_71/rzase/sc092540641.htm 15/15

You might also like