Previous Topic: Connecting Records to a SetNext Topic: Accessing Bill-of-Materials Structures


Disconnecting Records from a Set

To cancel the membership of a record occurrence in a set occurrence defined with the optional set membership option, perform the following steps:

  1. Ready all affected areas in one of the update usage modes (for more information, see Area Usage Modes).

    Areas should be readied whether they are affected explicitly or implicitly (for example, as owner of a set whose members are being disconnected).

  2. Establish the following currencies:
  3. Issue the DISCONNECT statement.
  4. Perform the IDMS-STATUS routine if the DBMS returns a nonzero value.

Accessing a Disconnected Record

Following successful execution of the DISCONNECT statement, you cannot access the record through the set for which membership was canceled. You can still access the record in the following ways:

Currencies after a DISCONNECT

Although a successfully executed DISCONNECT statement nullifies currency in the specified set, the DBMS maintains next, prior (if specified), and owner currencies so you can still issue the OBTAIN NEXT, PRIOR, or OWNER WITHIN SET statements.

'Native VSAM users'. The DISCONNECT statement is not valid because all sets in native VSAM files must be defined as mandatory automatic.

Example of Disconnecting and Connecting Records

The program excerpt below disconnects and subsequently reconnects EMPLOYEE records in the DEPT-EMPLOYEE set.

Employees have been transferred to another department. The program ensures that both the new and the old departments exist before disconnecting the EMPLOYEE record from the old DEPT-EMPLOYEE set and connecting it to the new DEPT-EMPLOYEE set.

 DATA DIVISION.
 FILE SECTION.
 FD  DEPT-TRANSFER-FILE.
 01  TRANS-EMP-REC-IN.
     02  NEW-DEPT-ID-IN          PIC 9(4).
     02  OLD-DEPT-ID-IN          PIC 9(4).
     02  EMP-ID-IN               PIC 9(4).
 WORKING-STORAGE SECTION.
 01  SWITCHES.
     05 EOF-SW                   PIC X    VALUE 'N'.
       88 END-OF-FILE                     VALUE 'Y'.
 01  CONNECT-DBKEY               PIC S9(8) COMP SYNC.
 PROCEDURE DIVISION.
          .
     READ DEPT-TRANSFER-FILE
          AT END MOVE 'Y' TO EOF-SW.
     PERFORM A300-DISCONNECT-EMP THRU A300-EXIT
                        UNTIL END-OF-FILE.
     FINISH.
     GOBACK.
 A300-DISCONNECT-EMP.
     MOVE NEW-DEPT-ID-IN TO DEPT-ID-0410.
     FIND CALC DEPARTMENT.
*** IF ERROR-STATUS = 0326, NEW DEPT ID IS INVALID ***
     IF DB-REC-NOT-FOUND
         DISPLAY
        'NEW DEPARTMENT ' NEW-DEPT-ID-IN ' NOT FOUND'
        'FOR EMPLOYEE ID ' EMP-ID-IN
        GO TO A300-GET-NEXT
     ELSE IF DB-STATUS-OK
        NEXT SENTENCE
     ELSE
        PERFORM IDMS-STATUS.
*** SAVE NEW DEPT DB-KEY TO REOBTAIN RECORD LATER ***
     MOVE DBKEY TO CONNECT-DBKEY.
     PERFORM IDMS-STATUS.

     MOVE OLD-DEPT-ID-IN TO DEPT-ID-0410.
     FIND CALC DEPARTMENT.
*** IF ERROR-STATUS = 0326, OLD DEPT ID IS INVALID ***
     IF DB-REC-NOT-FOUND
         DISPLAY
        'OLD DEPARTMENT ' OLD-DEPT-ID-IN ' NOT FOUND'
        'FOR EMPLOYEE ID ' EMP-ID-IN '
         GO TO A300-GET-NEXT
     ELSE IF DB-STATUS-OK
        NEXT SENTENCE
     ELSE
        PERFORM IDMS-STATUS.
     MOVE EMP-ID-IN TO EMP-ID-0415.
     OBTAIN CALC EMPLOYEE.
*** IF ERROR-STATUS = 0326, EMP ID IS INVALID ***
     IF DB-REC-NOT-FOUND
         DISPLAY
        'EMPLOYEE ' EMP-ID-IN ' NOT FOUND'
        'FOR OLD DEPARTMENT ' OLD-DEPT-ID-IN
        '*** NEW DEPARTMENT ' NEW-DEPT-ID-IN
        GO TO A300-GET-NEXT
     ELSE IF DB-STATUS-OK
        NEXT SENTENCE
     ELSE
        PERFORM IDMS-STATUS.
*** CHECK IF EMPLOYEE IS A MEMBER IN DEPT-EMPLOYEE SET ***
     IF NOT DEPT-EMPLOYEE MEMBER
         DISPLAY
        'EMPLOYEE ' EMP-ID-IN
        'NOT CONNECTED TO DEPARTMENT ' OLD-DEPT-ID-IN
         GO TO A300-GET-NEXT.
     DISCONNECT EMPLOYEE FROM DEPT-EMPLOYEE.
     PERFORM IDMS-STATUS.
*** REACCESS NEW DEPARTMENT USING ITS DB-KEY ***
     FIND DEPARTMENT DB-KEY IS CONNECT-DBKEY.
     PERFORM IDMS-STATUS.
     CONNECT EMPLOYEE TO DEPT-EMPLOYEE.
     PERFORM IDMS-STATUS.