VSAM files are created with IDCAMS Utility program.
---------------------------------------------------------------------
Define the data and primary index components
//DEFINE EXEC PGM=IDCAMS
//SYSPRINT DD SYSOUT=*
//SYSIN DD *
DEFINE CLUSTER (NAME(filename for
the VSAM dataset) -
INDEXED - /* defines
this as a KSDS file */
RECSZ(average-record-length maximum-record-length)
-
KEYS(length-of-the-key offset-from-first-position)
-
VOL(volid)) -
RECORDS(primary-amount secondary-amount)
-
FSPC(control-interval% control-area%)
-
DATA (NAME(filename.DATA))
-
INDEX (NAME(filename.INDEX))
---------------------------------------------------------------------
INDEXED FILES (KSDS)
Reading Indexed Files
SELECT File-name ASSIGN TO ddname
ORGANIZATION IS INDEXED
ACCESS IS [ SEQUENTIAL | RANDOM | DYNAMIC
]
RECORD KEY IS primary-key-field
FILE STATUS IS ws-status-field.
---------------------------------------------------------------------------------------------------------
VSAM ACCESS MODE
SEQUENTIAL
Default access mode if the ACCESS IS statement is omitted. Records are read in the sequence of their position in the file. This mode is used to read all the records in the file. The system does not have to use the index to locate the next record. Since the next record may be the end of the file, AT END logic is required.
RANDOM
This mode is used to read and process one or more
records
in the file. The records do not have to
be processed based on their sequential position in the file. In order to
select a record, the program must have a key value before issuing the READ
statement. The index is searched for a matching key and the storage location
containing the record. Since the key may not exist in the file, INVALID
KEY logic is required.
DYNAMIC
This mode can use both random and sequential access to a record. When doing a search by key, INVALID KEY logic is required. After a successful read, sequential access using READ … NEXT commands require AT END logic.
---------------------------------------------------------------------------------------------------------
Questions
OPEN I-O file-name
----------------------------------------------------------------------
ACCESS IS SEQUENTIAL (updating)
? Changing a record is a read and rewrite
----------------------------------------------------------------
ACCESS IS RANDOM (reading)
---------------------------------------------------------------------------------------------------------
ACCESS IS RANDOM (updating)
000100 IDENTIFICATION DVISION.
000200 PROGRAM-ID. UPDATEI.
000300 AUTHOR. JOHN H PETLICKI.
000400 ENVIRONMENT DIVISION.
000500 INPUT-OUTPUT SECTION.
000600 FILE-CONTROL.
000700 SELECT MASTER ASSIGN
TO MAST
000710
ORGANIZATION IS INDEXED
000800
ACCESS IS RANDOM
000900
RECORD KEY IS MASTER-ID
001000
FILE STATUS IS MASTER-FILE-STATUS.
001100 SELECT TRANSACTIONS
ASSIGN TO TRANS.
001200 DATA DIVISION.
001300 FILE SECTION.
001400 FD MASTER
001500 DATA RECORD IS
MASTER-REC.
001600 01 MASTER-REC.
001700 05 MASTER-ID
PIC XX.
001800 05 MASTER-VALUE
PIC 9(3)V99.
001900 FD TRANSACTIONS
002000 DATA RECORD IS
TRANS-REC.
002100 01 TRANS-REC.
002200 05 TRANS-ID
PIC XX.
002300 05 TRANS-VALUE
PIC 9(3)V99.
002400 05 TRANS-TYPE
PIC X.
002500
88 VALID-TRANS-TYPE VALUES ARE 'A' 'C' 'D'.
002600
88 ADD-TRANS VALUE
IS 'A'.
002700
88 CHANGE-TRANS VALUE IS 'C'.
002800
88 DELETE-TRANS VALUE IS 'D'.
002900 WORKING-STORAGE SECTION.
003000 01 MASTER-FILE-STATUS
PIC 99.
003100 01 TRANSACTION-SWITCH
PIC XXX VALUE SPACES.
003200 01 COUNTERS.
003300 05 TOTAL-MASTERS-ADDED
PIC 9(5) VALUE ZEROS.
003400 05 TOTAL-MASTERS-DELETED
PIC 9(5) VALUE ZEROS.
003500
003600 05 TOTAL-TRANS-ENTERED
PIC 9(5) VALUE ZEROS.
003700 05 TOTAL-ADDS-ENTERED
PIC 9(5) VALUE ZEROS.
003800 05 TOTAL-CHANGES-ENTERED
PIC 9(5) VALUE ZEROS.
003900 05 TOTAL-DELETES-ENTERED
PIC 9(5) VALUE ZEROS.
004000 05 TOTAL-OTHER-ENTERED
PIC 9(5) VALUE ZEROS.
004100
004200 05 TOTAL-TRANS-APPLIED
PIC 9(5) VALUE ZEROS.
004300 05 TOTAL-ADDS-APPLIED
PIC 9(5) VALUE ZEROS.
004400 05 TOTAL-CHANGES-APPLIED
PIC 9(5) VALUE ZEROS.
004500 05 TOTAL-DELETES-APPLIED
PIC 9(5) VALUE ZEROS.
004600 05 TOTAL-OTHER-APPLIED
PIC 9(5) VALUE ZEROS.
004700
004800 05 TOTAL-TRANS-REJECTED
PIC 9(5) VALUE ZEROS.
004900 05 TOTAL-ADDS-REJECTED
PIC 9(5) VALUE ZEROS.
005000 05 TOTAL-CHANGES-REJECTED
PIC 9(5) VALUE ZEROS.
005100 05 TOTAL-DELETES-REJECTED
PIC 9(5) VALUE ZEROS.
005200 05 TOTAL-OTHER-REJECTED
PIC 9(5) VALUE ZEROS.
005300 PROCEDURE DIVISION.
005400 OPEN
I-O MASTER
005500 INPUT TRANSACTIONS
005600
005700 PERFORM UNTIL TRANSACTION-SWITCH
= 'EOF'
005800 READ
TRANSACTIONS
005900
AT END MOVE "EOF" TO TRANSACTION-SWITCH
006000
NOT AT END
006100
ADD 1 TO TOTAL-TRANS-ENTERED
006200
EVALUATE TRUE
006300
WHEN ADD-TRANS ADD 1 TO TOTAL-ADDS-ENTERED
006400
WHEN CHANGE-TRANS ADD 1 TO TOTAL-CHANGES-ENTERED
006500
WHEN DELETE-TRANS ADD 1 TO TOTAL-DELETES-ENTERED
006600
WHEN OTHER ADD 1 TO TOTAL-OTHER-ENTERED
006700
END-EVALUATE
006800
PERFORM 300-VALIDATE-TRANSACTIONS
006900 END-READ
007000 END-PERFORM
007100
007200 CLOSE MASTER
007300
TRANSACTIONS
007400 GOBACK.
007500
007600 300-VALIDATE-TRANSACTIONS.
007700 IF TRANS-VALUE
NUMERIC
007800 AND VALID-TRANS-TYPE
007900
PERFORM 400-APPLY-TRANS-TO-MASTER
008000 ELSE
008100
DISPLAY 'TRANSACTION REJECTED ' TRANS-REC
008200
PERFORM 660-TALLY-TRANS-REJECTED
008300 END-IF
008400 .
008500 400-APPLY-TRANS-TO-MASTER.
008600 EVALUATE TRUE
008700
008800 WHEN
ADD-TRANS
008900
MOVE TRANS-REC TO MASTER-REC
009000
WRITE MASTER-REC
009100
INVALID KEY
009200
DISPLAY MASTER-FILE-STATUS TRANS-ID
009300
PERFORM 660-TALLY-TRANS-REJECTED
009400
NOT INVALID KEY
009500
PERFORM 650-TALLY-TRANS-APPLIED
009600
END-WRITE
009700
009800 WHEN
CHANGE-TRANS
009900
MOVE TRANS-ID TO MASTER-ID
010000
READ MASTER
010100
INVALID KEY
010200
DISPLAY MASTER-FILE-STATUS TRANS-ID
010300
PERFORM 660-TALLY-TRANS-REJECTED
010400
NOT INVALID KEY
010500
ADD TRANS-VALUE TO MASTER-VALUE
010600
REWRITE MASTER-REC
010700
INVALID KEY
010800
DISPLAY MASTER-FILE-STATUS TRANS-ID
010900
PERFORM 660-TALLY-TRANS-REJECTED
011000
NOT INVALID KEY
011100
PERFORM 650-TALLY-TRANS-APPLIED
011200
END-REWRITE
011300
END-READ
011400
011500 WHEN
DELETE-TRANS
011600
MOVE TRANS-ID TO MASTER-ID
011700
DELETE MASTER RECORD
011800
INVALID KEY
011900
DISPLAY MASTER-FILE-STATUS TRANS-ID
012000
PERFORM 660-TALLY-TRANS-REJECTED
012100
NOT INVALID KEY
012200
PERFORM 650-TALLY-TRANS-APPLIED
012210
END-DELETE
012300
WHEN OTHER
012400
DISPLAY 'INVALID TRANSACTION ' TRANS-REC
012500
PERFORM 660-TALLY-TRANS-REJECTED
012600 END-EVALUATE.
012700
012800 650-TALLY-TRANS-APPLIED.
012900 ADD 1 TO TOTAL-TRANS-APPLIED
013000 EVALUATE TRUE
013100 WHEN
ADD-TRANS ADD 1 TO TOTAL-ADDS-APPLIED
013200
TOTAL-MASTERS-ADDED
013300 WHEN
CHANGE-TRANS ADD 1 TO TOTAL-CHANGES-APPLIED
013400 WHEN
DELETE-TRANS ADD 1 TO TOTAL-DELETES-APPLIED
013500
TOTAL-MASTERS-DELETED
013600 WHEN
OTHER ADD 1 TO TOTAL-OTHER-APPLIED
013700 END-EVALUATE.
013800
013900 660-TALLY-TRANS-REJECTED.
014000 ADD 1 TO TOTAL-TRANS-REJECTED
014100 EVALUATE TRUE
014200 WHEN
ADD-TRANS ADD 1 TO TOTAL-ADDS-REJECTED
014300 WHEN
CHANGE-TRANS ADD 1 TO TOTAL-CHANGES-REJECTED
014400 WHEN
DELETE-TRANS ADD 1 TO TOTAL-DELETES-REJECTED
014500 WHEN
OTHER ADD 1 TO TOTAL-OTHER-REJECTED
014600 END-EVALUATE.
014700
-------------------------------------------------------------
The FILE STATUS Clause
The FILE STATUS clause causes the system to store a two-character code in a data item at the completion of each I/O statement. You can test the status code after each I/O statement.
SELECT
FILE STATUS data-name
The following table contains some of the system status codes
Key-1 key-2 meaning
Successful completion :
0 0
normal ok status code
2
duplicate key detected
4
wrong fixed-length record compared to file description
7
CLOSE with NO REWIND or REEL for nontape
End-of-file :
1 0
sequential read -- no more input records
4
relative record READ outside file boundary
Invalid key:
2 1
sequence error --- keys not in correct order
2
duplicate key
3
record not found
4
key outside the boundary of the file
Permanent I/O error:
3 0
no further information -- hardware problem
4
record outside file boundary -- sequential file
5
OPEN and required file not found
7
OPEN with invalid mode (INPUT / OUTPUT / I-O)
8
OPEN of file closed with LOCK
9
OPEN unsuccessful because of conflicting file attributes
Logic error:
4 1
OPEN of file already open
2
CLOSE for file not open
3
READ not executed correctly before REWRITE
4
REWRITE of different size record
6
READ after EOF (end of file)
7
READ attempted for file not open I-O or INPUT
8
WRITE for file not opened OUTPUT, I-O, or EXTEND
9
DELETE or REWRITE for file not opened I-O.
Specific compiler-defined conditions:
9 0
no further information
1
VSAM password failure
2
logic error
3
VSAM Resources not available
4
VSAM sequential record not available
5
VSAM invalid or incomplete file information
6
VSAM--no DD statement
7
VSAM OPEN successful. File integrity verified.