z/OS DFSORT Application Programming Guide
Previous topic | Next topic | Contents | Contact z/OS | Library | PDF


COBOL E15 user exit: altering records

z/OS DFSORT Application Programming Guide
SC23-6878-00

Figure 1 shows an example of a COBOL E15 routine for a data set with fixed-length records of 100 bytes. It examines the department field in the passed record and takes the following action:
  • If the department is D29, it changes it to J99.
  • If the department is not D29, it accepts the record unchanged.
Figure 1. COBOL E15 Routine Example (FLR)
IDENTIFICATION DIVISION.
  PROGRAM-ID.
      CE15.
  ENVIRONMENT DIVISION.
  DATA DIVISION.
  LINKAGE SECTION.
  01  RECORD-FLAGS       PIC 9(8) BINARY.
      88  FIRST-REC            VALUE 00.
      88  MIDDLE-REC           VALUE 04.
      88  END-REC              VALUE 08.
  01  NEW-REC.
   05 NFILL1             PIC X(10).
   05 NEW-DEPT           PIC X(3).
   05 NFILL2             PIC X(87).
  01  RETURN-REC.
   05 RFILL1             PIC X(10).
   05 RETURN-DEPT        PIC X(3).
   05 RFILL2             PIC X(87).

  PROCEDURE DIVISION USING RECORD-FLAGS, NEW-REC, RETURN-REC.

      IF END-REC
         MOVE 8 TO RETURN-CODE
      ELSE
        IF NEW-DEPT EQUAL TO "D29"
           MOVE NEW-REC TO RETURN-REC
           MOVE "J99" TO RETURN-DEPT
           MOVE 20 TO RETURN-CODE
        ELSE
           MOVE 0 TO RETURN-CODE
        END-IF
      END-IF

      GOBACK.

Go to the previous page Go to the next page




Copyright IBM Corporation 1990, 2014