VSAM bafflement - can load a file only once

Hello! I’m playing around with VSAM and have run into a situation I don’t understand at all. Here’s the sequence of events, code excerpts below.

  1. Create the VSAM file using IDCAMS ‘DEFINE CLUSTER’.
  2. Load the file using COBOL program EX14WRIT - completes normally (COND CODE 00).
  3. Verify the file has been loaded using IDCAMS ‘PRINT’.
  4. Delete all file contents using COBOL program EX14DELE - completes normally.
  5. Verify file is now empty using IDCAMS ‘PRINT’.
  6. Load the file again using EX14WRIT - completes normally BUT the OPEN fails with STATUS 37, RETURN 08, REASON 232.
    Status 37 seems to mean “An OPEN statement was attempted on a file that would not support the open mode specified in the OPEN statement”. I do not understand what this is trying to tell me. Any help greatly appreciated!

IDCAMS job used to create the file
//CAMSMAKE JOB
//DEFINE EXEC PGM=IDCAMS
//SYSPRINT DD SYSOUT=A
//SYSIN DD *
DELETE Z80501.PP.UNIT5.EX14DATA
DEFINE CLUSTER -
(NAME(Z80501.PP.UNIT5.EX14DATA) -
INDEXED -
RECORDSIZE(80 80) -
KEYS(5 0) -
FREESPACE(0 0) -
VOLUMES(VPWRKE) -
SHAREOPTIONS(3 3)) -
DATA (NAME(Z80501.PP.UNIT5.EX14DATA.DATA) -
TRK(1 1) -
CONTROLINTERVALSIZE(4096)) -
INDEX (NAME(Z80501.PP.UNIT5.EX14DATA.INDEX) -
TRK(1 1))
/*

DD statement for the VSAM file used in both EX14WRIT & EX14DELE:
//GO.OFILE DD DSN=Z80501.PP.UNIT5.EX14DATA,DISP=MOD

EX14WRIT.CBL
IDENTIFICATION DIVISION.
PROGRAM-ID. EX14WRIT.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT IFILE ASSIGN TO IFILE.
SELECT OFILE ASSIGN TO OFILE
ORGANIZATION IS INDEXED
ACCESS IS SEQUENTIAL
RECORD KEY IS OKEY
FILE STATUS IS FS-CODE VSAM-CODE.

    DATA DIVISION.
    FILE SECTION.
    FD IFILE
           RECORDING MODE F
           RECORD CONTAINS 80 CHARACTERS.
    01 IREC.
       02 IKEY PIC X(5).
       02 ITEXT PIC X(75).

    FD OFILE
       RECORD CONTAINS 80 CHARACTERS.
    01 OREC.
       02 OKEY PIC X(5).
       02 OTEXT PIC X(75).

    WORKING-STORAGE SECTION.
    01 EOF-FLAG PIC X VALUE 'N'.
    01 RETURN-STATUS.
        05 FS-CODE                  PIC XX.
        05 VSAM-CODE.
           10 VSAM-RETURN-CODE      PIC S9(2) Usage Binary.
           10 VSAM-COMPONENT-CODE   PIC S9(1) Usage Binary.
           10 VSAM-REASON-CODE      PIC S9(3) Usage Binary.
    01 NRECS-LOADED PIC 99 USAGE BINARY VALUE 0.
    01 NRECS-DELETED PIC 99 USAGE BINARY VALUE 0.
    01 PART PIC XXXXX.

    PROCEDURE DIVISION.
       OPEN INPUT IFILE.
       OPEN OUTPUT OFILE.
       IF FS-CODE NOT = '00'
           MOVE 'OPEN ' TO PART
           PERFORM 100-PRINT-ERROR
           GOBACK
       END-IF
       PERFORM 20-LOADDATA
       CLOSE IFILE
       CLOSE OFILE
       GOBACK
       .

   20-LOADDATA.
       DISPLAY "LOADDATA"
       MOVE 'N' TO EOF-FLAG
       PERFORM UNTIL EOF-FLAG = 'Y'
           READ IFILE
               AT END MOVE 'Y' TO EOF-FLAG
           NOT AT END
               PERFORM 30-LOADRECORD
           END-READ
        END-PERFORM
        DISPLAY "NRECS LOADED: " NRECS-LOADED
        .

   30-LOADRECORD.
        MOVE IKEY TO OKEY
        MOVE ITEXT TO OTEXT
        WRITE OREC
           INVALID KEY
               DISPLAY "INVALID KEY " OKEY
           NOT INVALID KEY
               DISPLAY "VALID KEY " OKEY
               PERFORM 35-CHECK-STATUS
        END-WRITE
        .

   35-CHECK-STATUS.
        IF FS-CODE = '00'
            DISPLAY "WRITTEN " OKEY
            ADD 1 TO NRECS-LOADED
        ELSE
            DISPLAY "NOT WRITTEN " OKEY
            MOVE 'WRITE' TO PART
            PERFORM 100-PRINT-ERROR
        END-IF
        .

   100-PRINT-ERROR.
        DISPLAY "PART: " PART " STATUS: " FS-CODE " VSAM-CODE ==>"
                " RETURN: "  VSAM-RETURN-CODE,
                " COMPONENT: "  VSAM-COMPONENT-CODE,
                " REASON: "  VSAM-REASON-CODE
        .

EX14DELE
IDENTIFICATION DIVISION.
PROGRAM-ID. EX14DELE.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT OFILE ASSIGN TO OFILE
ORGANIZATION IS INDEXED
ACCESS IS SEQUENTIAL
RECORD KEY IS OKEY
FILE STATUS IS FS-CODE VSAM-CODE.

    DATA DIVISION.
    FILE SECTION.
    FD OFILE
       RECORD CONTAINS 80 CHARACTERS.
    01 OREC.
       02 OKEY PIC X(5).
       02 OTEXT PIC X(75).

    WORKING-STORAGE SECTION.
    01 EOF-FLAG PIC X VALUE 'N'.
    01 RETURN-STATUS.
        05 FS-CODE                  PIC XX.
        05 VSAM-CODE.
           10 VSAM-RETURN-CODE      PIC S9(2) Usage Binary.
           10 VSAM-COMPONENT-CODE   PIC S9(1) Usage Binary.
           10 VSAM-REASON-CODE      PIC S9(3) Usage Binary.
    01 NRECS-DELETED PIC 99 USAGE BINARY VALUE 0.
    01 PART PIC XXXXX.

    PROCEDURE DIVISION.
       OPEN I-O OFILE.
       IF FS-CODE NOT = '00'
           MOVE 'OPEN ' TO PART
           PERFORM 100-PRINT-ERROR
           GOBACK
       END-IF
       PERFORM 10-DELETE-EXISTING-DATA
       CLOSE OFILE
       GOBACK
       .

   10-DELETE-EXISTING-DATA.
       MOVE 'N' TO EOF-FLAG
       PERFORM UNTIL EOF-FLAG = 'Y'
           READ OFILE
               AT END MOVE 'Y' TO EOF-FLAG
           NOT AT END
               DISPLAY "READ: " OKEY
               PERFORM 15-DELETERECORD
           END-READ
        END-PERFORM
        DISPLAY "NRECS DELETED: " NRECS-DELETED
        CLOSE OFILE
        .

   15-DELETERECORD.
        DELETE OFILE
        IF FS-CODE = '00'
            DISPLAY "DELETED " OKEY
            ADD 1 TO NRECS-DELETED
        ELSE
            DISPLAY "NOT DELETED " OKEY
            MOVE 'DELET' TO PART
            PERFORM 100-PRINT-ERROR
        END-IF
        .


   100-PRINT-ERROR.
        DISPLAY "PART: " PART " STATUS: " FS-CODE " VSAM-CODE ==>"
                " RETURN: "  VSAM-RETURN-CODE,
                " COMPONENT: "  VSAM-COMPONENT-CODE,
                " REASON: "  VSAM-REASON-CODE
        .

I’ve figured this out - sort of. For the second load of the file I had to change the OPEN statement from ‘OPEN OUTPUT’ to ‘OPEN EXTEND’. In looking at the COBOL Programming Guide I find that a distinction is made between a newly created file and one that has been used and is now empty. I do not understand why this is, but that seems to be my answer.

I think you always need to do an idcams delete/define before writing to a vsam file.

alterkacker is correct - a VSAM file that has been written to but have had all its records deleted is different than a newly defined VSAM file. VSAM work files are typically created with the REUSE option that (I believe) would have avoided your error on the second run.

note: a VSAM file obviously needs to be defined to perform COBOL operations against it; saying a delete/define always needs to be performed before writing to a VSAM file is technically inaccurate

Thanks Jim, the REUSE parameter does what I wanted. I don’t know how I could have missed that considering the three days I’ve spent playing with VSAM & perusing the simple and straightforward documentation. :wink:

If I want to get really obsessive about this, is there a ZOS utility that gives one a view of the internals of a VSAM file, i.e. CIs, CAs, etc…?

…sorry for the delay

I think a LISTCAT will give you what you need - I am a big fan of the information File-Aid provides for VSAM datasets, but realize that not every IBM shop opts to use it.

The File Manager DSList (F.3.4) option I (display entry information) gives some definition specifics, but I do not believe provides the detailed usage information you are looking for.

Hope this helps!