SYNCPOINT


The CICS SYNCPOINT statement is used to commit all changes made by a transaction to recoverable resources, such as VSAM files, temporary storage (TSQs), transient data queues (TDQs), and databases. It ensures data integrity by making all updates permanent or rolling them back in case of failure.

In CICS, transactions can perform multiple operations, but these changes are not final until a SYNCPOINT is issued. If the transaction abends (fails) before a SYNCPOINT, all changes are automatically rolled back.

Syntax -

EXEC CICS SYNCPOINT
     [ROLLBACK]
     [RESP(response-field)]
     [RESP2(response-field2)]
     END-EXEC.
  • ROLLBACK - Optional. If specified, undo all changes made by the transaction and restores data to its previous state.
  • RESP(response-variable) - Optional. It captures the response code of the SYNCPOINT 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 SYNCPOINT operation when the error occured.

How it works?

  • A transaction performs updates on recoverable resources (VSAM, DB2, TSQ, TDQ).
  • CICS temporarily holds these updates until a commit is issued.
  • When a SYNCPOINT is executed, all updates are made permanent.
  • If a transaction abends before SYNCPOINT, CICS rolls back all changes automatically.
  • If a SYNCPOINT ROLLBACK is executed, all updates since the last commit are undone.

Short Examples -


Scenario - Committing file updates using SYNCPOINT

...
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).
   
...
PROCEDURE DIVISION.

    MOVE "12345" TO WS-CUST-ID.

    EXEC CICS READ
         FILE('CUSTFILE')
         INTO(WS-CUST-RECORD)
         RIDFLD(WS-CUST-ID)
         UPDATE
         RESP(WS-RESP)
         END-EXEC.

    IF WS-RESP NOT = 0 THEN

        MOVE "9876543210" TO WS-CUST-PHONE

        EXEC CICS REWRITE
             FILE('CUSTFILE')
             FROM(WS-CUST-RECORD)
             RESP(WS-RESP)
             END-EXEC

        IF WS-RESP = 0 THEN
			EXEC CICS SYNCPOINT
				 RESP(WS-RESP)
				 END-EXEC 
		ELSE
			EXEC CICS SYNCPOINT ROLLBACK
				 RESP(WS-RESP)
				 END-EXEC 
		END-IF
	END-IF.
	
    ...

A record is rewritten to the VSAM dataset EMPFILE. If the WRITE operation is successful, a SYNCPOINT is issued to commit the transaction. If an error occurs, SYNCPOINT ROLLBACK undoes all changes.

Error Conditions -


Eror Condition RESP RESP2 Reason
16 INVREQ 16 200 SYNCPOINT was in a program from a remote system that has not specified the SYNCONRETURN option or if it has been linked to locally and is defined with EXECUTIONSET=DPLSUBSET.
82 ROLLEDBACK 82 Occurs when a SYNCPOINT command is ambitious into rollback by a remote system that is unable to commit the syncpoint.