RELEASE Statement


The RELEASE statement is used to send records from the input procedure to a sort work file in the sorting process. It is only used inside the INPUT PROCEDURE of a SORT operation.

Atleast one RELEASE statement should be coded within an input procedure.

Syntax -

RELEASE record-name [FROM ws-record-name]
Note! All statements coded in [ ] are optional.

Parameters -

  • record-name - This is the name of the record that we want to release to the sort work file.
  • FROM ws-record-name - This optional clause allows us to specify a different working-storage variable from which the record will be sourced. If we ignore this clause, the data is taken directly from the record named in record-name.

Practical Example -


Scenario - Let us assume we have a file with the employee information and need to sort the file based on the employee number (1-5 bytes). But, we need to skip the DIR (having employee number E0001) record before sorting.

Input -

MATEPK.EMPFILE.NSINPUT1

----+----1----+----2----+----3----+----4----+--
E0004EMPLOYEE4     TL   DEPT1LOC1 0000050000
E0002EMPLOYEE2     MGR  DEPT1LOC1 0000080000
E0006EMPLOYEE6     SE   DEPT1LOC1 0000034000
E0001EMPLOYEE1     DIR       LOC1 0000100000

Code -

----+----1----+----2----+----3----+----4----+----5----+
       IDENTIFICATION DIVISION.
       PROGRAM-ID. RELWFILE.
       AUTHOR. MTH.

       ENVIRONMENT DIVISION. 
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
           SELECT EMPFILE1 ASSIGN TO INPUT1. 
           SELECT EMPFILEO ASSIGN TO OUTPUT1.
           SELECT WORKFILE ASSIGN TO WORK1.

       DATA DIVISION.
       FILE SECTION.
       FD EMPFILE1 
           RECORD CONTAINS 47 CHARACTERS 
           DATA RECORD EMP-REC1
           RECORDING MODE F.
       01 EMP-REC1.
          COPY EMPREC.
       FD EMPFILEO
           RECORD CONTAINS 47 CHARACTERS
           DATA RECORD EMP-RECO
           RECORDING MODE F.
       01 EMP-RECO.
          COPY EMPREC.
       SD WORKFILE
           RECORD CONTAINS 47 CHARACTERS
           DATA RECORD WORK-REC
           RECORDING MODE F.
       01 WORK-REC.
          05 WORK-EMP-NUM         PIC 9(05).
          05 WORK-REM-REC         PIC X(42).
       WORKING-STORAGE SECTION.
       01 WS-VAR.
          05 WS-INPUT1-SW         PIC X(01) VALUE 'N'.
             88 INPUT1-EOF        VALUE 'Y'.
             88 NOT-INPUT1-EOF    VALUE 'N'.

       PROCEDURE DIVISION.
	  * Sorting WORKFILE using a input paragraph
	  * 1000-FILTER-RECORDS and writing to output file
	  * EMPFILEO.
           SORT WORKFILE
             ON ASCENDING KEY WORK-EMP-NUM 
             INPUT PROCEDURE IS 1000-FILTER-RECORDS
                GIVING EMPFILEO.
           STOP RUN.
		   
      * Input paragraph for SORT statement
       1000-FILTER-RECORDS.

           SET  NOT-INPUT1-EOF   TO TRUE
           OPEN INPUT EMPFILE1.
           READ EMPFILE1
                AT END SET INPUT1-EOF TO TRUE
           END-READ

           PERFORM UNTIL INPUT1-EOF
	  * Releases the WORK-REC after processing.
                IF EMP-NUM  OF EMP-REC1
                            NOT EQUAL 'E0001'
                   MOVE EMP-REC1      TO WORK-REC
                   RELEASE WORK-REC
                END-IF 
              READ EMPFILE1
                   AT END SET INPUT1-EOF TO TRUE 
              END-READ
           END-PERFORM.

           CLOSE EMPFILE1.

JCL -

//MATEPKRJ JOB MSGLEVEL=(1,1),NOTIFY=&SYSUID
//*
//STEP01  EXEC PGM=MERGEFLS
//STEPLIB  DD  DSN=MATEPK.COBOL.LOADLIB,DISP=SHR
//INPUT1   DD  DSN=MATEPK.EMPFILE.NSINPUT1,DISP=SHR
//OUTPUT1  DD  DSN=MATEPK.EMPFILE.NSOUTPUT,
//            DISP=(NEW,CATLG,DELETE),
//            SPACE=(TRK,(3,2),RLSE),
//            UNIT=SYSDA,
//            DCB=(DSORG=PS,RECFM=FB,LRECL=47,BLKSIZE=470)
//WORK1    DD  DSN=&&TEMP,
//            DISP=(NEW,DELETE,DELETE),
//            SPACE=(CYL,(10,5),RLSE),
//            UNIT=SYSDA,
//            DCB=(DSORG=PS,RECFM=FB,LRECL=47,BLKSIZE=470)
//SYSOUT   DD  SYSOUT=*  

Output (MATEPK.EMPFILE.NSOUTPUT) -

----+----1----+----2----+----3----+----4----+--
E0002EMPLOYEE2     MGR  DEPT1LOC1 0000080000   
E0004EMPLOYEE4     TL   DEPT1LOC1 0000050000   
E0006EMPLOYEE6     SE   DEPT1LOC1 0000034000

Explaining Example -

In the above example, SORT uses 1000-FILTER-RECORDS to read the input file, skips the E0001 record while moving it to the work file, and releases the work record after processing. The director record (E0001) is successfully skipped during the SORT operation.