FILE UNLOCK
The UNBLOCK statement is used to release a logical record lock on a previously locked file due to a READ with the UPDATE option. In CICS, when a record is read with UPDATE, it is locked to prevent other transactions from modifying it until the current transaction either rewrites the record (REWRITE), deletes the record (DELETE), or releases the lock (UNBLOCK), or SYNCPOINT is executed.
The UNBLOCK statement ensures a record is available for other transactions without modification.
Syntax -
EXEC CICS UNBLOCK
FILE('file-name')
[TOKEN(value)]
[SYSID(system-name)]
[RESP(response-field)]
[RESP2(response-field2)]
END-EXEC.
- FILE('file-name') - Specifies the VSAM file name whose record lock needs to be released.
- TOKEN(value) - Specifies a unique identifier for this READ with UPDATE request.
- SYSID(system-name) - Specifies the system name to which the request is directed.
- RBA|RRN|XRBA - Specifies the type of the file and data in the RIDFLD.
- RESP(response-variable) - Optional. It captures the response code of the UNBLOCK operation and used to check if the command executed successfully or encountered an error.
- RESP2(response2-variable) - Optional. It captures the response2 code of the UNBLOCK operation when the error occured.
How it works?
- A READ command with UPDATE is issued to retrieve and lock a record for modification.
- The record remains locked until it is rewritten, deleted, or unblocked.
- If the transaction decides not to update the record, it can execute UNBLOCK to release the lock.
- Other transactions can now access the record without waiting.
- The system ensures efficient concurrent processing by minimizing record contention.
Short Examples -
Scenario - Browsing a KSDS File from a Specific Key and update all the records by increasing balance 1000 except customer ID 22222.
...
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-CUSTOMER-RECORD.
05 WS-CUST-ID PIC X(10).
05 WS-CUST-NAME PIC X(30).
05 WS-CUST-ADDRESS PIC X(50).
05 WS-CUST-PHONE PIC X(15).
05 WS-CUST-BAL PIC 9(15).
...
PROCEDURE DIVISION.
MOVE "11111" TO WS-CUST-ID.
EXEC CICS STARTBR
FILE('CUSTFILE')
RIDFLD(WS-CUST-ID)
RESP(WS-RESP)
END-EXEC.
IF WS-RESP = DFHRESP(NORMAL) THEN
PERFORM READ-NEXT-REC
THRU READ-NEXT-EXIT
UNTIL EOF-CUST-FILE
END-IF.
EXEC CICS ENDBR
FILE('CUSTFILE')
END-EXEC.
...
READ-NEXT-REC.
EXEC CICS READNEXT
FILE('CUSTFILE')
INTO(WS-CUST-RECORD)
RESP(WS-RESP)
UPDATE
END-EXEC.
IF WS-RESP = DFHRESP(NORMAL) THEN
IF WS-CUST-ID = "22222"
PERFORM UNBLOCK-BROWSE
THRU UNBLOCK-BROWSE-EXIT
ELSE
PERFORM REWRITE-RECORD
THRU REWRITE-RECORD-EXIT.
END-IF
...
ELSE IF WS-RESP = DFHRESP(ENDFILE) THEN
SET EOF-CUST-FILE TO TRUE
ELSE
...
END-IF.
READ-NEXT-EXIT.
EXIT.
UNBLOCK-BROWSE.
EXEC CICS UNBLOCK
FILE('CUSTFILE')
RESP(WS-RESP)
END-EXEC.
IF WS-RESP = DFHRESP(NORMAL) THEN
...
ELSE
...
END-IF.
UNBLOCK-BROWSE-EXIT.
EXIT.
...
REWRITE-RECORD.
COMPUTE WS-CUST-BAL = WS-CUST-BAL + 1000
EXEC CICS REWRITE
FILE('CUSTFILE')
FROM(WS-CUST-RECORD)
RESP(WS-RESP)
END-EXEC
IF WS-RESP = 0 THEN
...
END-IF
REWRITE-RECORD-EXIT.
EXIT.
The STARTBR command starts the browse session for sequential access. The READNEXT command with UPDATE retrieves records one by one. If the retrived record key is "22222" then skips the update by unlocking the record (UNBLOCK). If the retrived record key is other than '22222' then update the balance increased by 1000. The loop continues until the last record is reached (ENDFILE). The ENDBR command is issued to close the browse session.
Error Conditions -
Eror Condition | RESP | RESP2 | Reason |
---|---|---|---|
FILENOTFOUND | 12 | 1 | A file name in the FILE option is not defined to CICS and SYSID has not been specified. |
INVREQ | 16 | 47 | An unlock includes a token whose value cannot be matched against any token in use for an existing READ with the UPDATE option. |
IOERR | 17 | 120 | There is an I/O error during the ENDBR operation. |
NOTOPEN | 19 | 60 | Below are the reasons for NOTOPEN
|
ILLOGIC | 21 | 110 | VSAM error occurs that is not in one of the other CICS response categories. |
SYSIDERR | 53 | 130 | The SYSID name specified is neither the local region nor a remote system or the link to the remote system is closed. |
ISCINVREQ | 54 | 70 | The remote system indicates a failure that does not correspond to a known condition. |
NOTAUTH | 70 | 101 | A resource security check has failed on FILE (filename). |
84 DISABLED | 84 | 50 | A file is disabled. |