HP 3000 Manuals

CKREWRITE [ KSAM/3000 Reference Manual ] MPE/iX 5.0 Documentation


KSAM/3000 Reference Manual

CKREWRITE 

The procedure CKREWRITE replaces a record existing in a KSAM file with
another record having a matching primary key.

       CALL "CKREWRITE" USING filetable, status, record, recordsize 

You can replace an existing record in a KSAM file with the procedure
CKREWRITE. This procedure replaces a record previously read from the file
with another record whose primary key matches the primary key of the
record being replaced.

PARAMETERS 

filetable        an 8-word record containing the number and name of the
                 file, its input-output type, access mode, and a code
                 indicating whether the previous operation was
                 unsuccessful and if so what it was.  (Refer to Filetable
                 parameter discussion earlier in this section.)

status           one word (two 8-bit characters) set to a pair of values
                 upon the completion of the call to CKREWRITE indicating
                 whether or not the call was successful and if not why
                 not.  (Refer to Status Parameter discussion earlier in
                 this section.)

record           a record defined in the WORKING-STORAGE SECTION
                 containing data to be written as a logical record to the
                 file replacing the record with a matching primary key.

recordsize       an integer (S9(4)COMP) containing the length in
                 characters of the record to be written.  It must not
                 exceed the maximum record length established for the
                 file creation.

USING CKREWRITE 

In order to call procedure CKREWRITE, the file must be open for both
input and output (inputoutput type=2).  The access mode can be
sequential, random, or dynamic.  If access mode is sequential, CKREAD
must have been executed successfully just prior to the call to CKREWRITE.
In random or dynamic mode, no prior read is required; the system searches
the file for the record to be rewritten.

REWRITE IN SEQUENTIAL MODE. When the file is opened in sequential mode
(access mode = 0), CKREAD must be executed before CKREWRITE, The primary
key in the record to be written by CKREWRITE must be identical to the
primary key in the record read by CKREAD. A simple way to insure that the
keys match is to read a record into WORKING-STORAGE, modify it without
altering the primary key, and then write it back to the file using
CKREWRITE. Since the primary key is not changed, the sequence of records
in the file is not affected.

Rewriting Records With Duplicate Keys.  If you want to rewrite in
sequential mode all the records in a chain of records with duplicate
keys, use either CKSTART or CKREADBYKEY to position to the first record
in the chain.  Then call CKREWRITE to update the first record in the
chain.  Subsequent calls depend on whether you are changing any key value
in the record (not necessarily the selected key).

If no key in the record is changed, the record pointer continues to point
to the current record.  Only a subsequent CKREAD advances the pointer to
the next record in the duplicate key chain.  In this case, you can issue
CKREAD and CKREWRITE calls until all records with the duplicated key
value have been rewritten.

If any key in the record is changed, the new key is written to the end of
the chain of duplicate keys in the key file.  After the first call to
CKREWRITE, the record pointer points to the record whose key value
follows the changed key.  Since this key is now at the end of the chain
of duplicate keys, a subsequent call to CKREWRITE skips all records with
keys in the duplicate key chain and rewrites the record with the next
higher key value.  In this case, you must precede each call to CKREWRITE
with a call to CKSTART or CKREADBYKEY in order to update all subsequent
records with duplicate keys.

If you are updating a primary key value which is duplicated, it is good
practice to use CKDELETE to delete the selected record and then rewrite
it as a new record with CKWRITE.

REWRITE IN RANDOM MODE. When the file is opened in random or dynamic mode
(access mode = 1 or 2), no prior call to a read procedure is needed.  You
specify the record to be written in WORKING-STORAGE and then call
CKREWRITE. However, you must use the primary key to position to the
record to be modified.  When the procedure is executed, the file is
searched for a record whose primary key matches that of the record to be
written.  If such a record is found, it is replaced by the record
specified in CKREWRITE. If not found, an invalid key condition is
diagnosed and status is set to the "23".

A call to CKREWRITE in random mode only updates the first record with a
key in the chain of duplicate keys.

POSITION OF POINTER. Regardless of the mode, after any call to CKREWRITE
that does not modify a key value, the record pointer is positioned to the
key of the record just modified.  However, if any key in the modified
record was changed, the record must be deleted and then rewritten by a
write procedure.  If the access mode is sequential and a key was
modified, the pointer is moved to the record with the next key value in
ascending sequence after the modified key.  If the access mode is random
or dynamic, and a key was modified, the pointer is moved to the record
with the next key in ascending sequence after the primary key in the
modified record.  This means that in random or dynamic mode the key
pointer may change if it was pointing to an alternate key before the call
to CKREWRITE,

REWRITE WITH SHARED ACCESS. If the file was opened for shared access with
CKOPENSHR, then you must lock the file with a call to CKLOCK before
rewriting any records with CKREWRITE. After the records are rewritten,
you should unlock the file with CKUNLOCK.

To insure that you are updating the correct record in sequential mode,
you should call CKLOCK before positioning the pointer with CKSTART or
CKREADBYKEY, then specify the sequential calls to CKREAD and CKREWRITE
before unlocking the file with CKUNLOCK. This insures that no other users
change the position of the pointer while you are sequentially updating
the file.

INVALID KEY. In sequential mode, the invalid key condition exists when
the record just read by CKREAD and the record to be written by CKREWRITE
do not have the same primary key value.  In random or dynamic mode, an
invalid key condition exists if no record can be found in the file whose
primary key matches that of the record to be written by CKREWRITE. In
either case, status is set to the value "23".

Regardless of mode, an invalid key condition occurs if an alternate key
value in the record to be written duplicates a corresponding alternate
key for which duplicates are prohibited.  When rewriting a record, try to
avoid specifying an alternate key value that may duplicate a value
existing in the file unless duplicates are allowed for the key.  A
duplicate key condition where duplicates are not allowed causes status to
be set to "22" and the procedure is not executed.

EXAMPLES 

The first example is of a sequential update that clears the value of an
item in each record of the file.  The second example searches the file
for a record whose primary key has a particular value in order to change
the alternate key for that record.  Both examples assume the
WORKING-STORAGE SECTION from Figure 3-2 and the FINISH procedure from
CKCLOSE.

   1.  Sequential Update.

       Use CKSTART to position the current record pointer to the start of
       the file.  Then read each record in sequence and set its non-key
       items to blanks:

            DATA DIVISION.
            .
            .
            .
            WORKING-STORAGE SECTION.        \
            77 RELOP        PICS9(4)   COMP.|
            77 KEYVAL       PIC X(20).      |--------- items required by CKSTART 
            77 KEYLOC       PIC S9(4)  COMP.|
            77 KEYLENGTH    PIC S9(4)  COMP.|
            .                               /
            .
            .
            PROCEDURE DIVISION.
            START.
               MOVE 2 TO I-O-TYPE.
               MOVE 0 TO A-MODE.
               CALL "CKOPEN" USING FILETABLE, STAT.
               .
               .<---------------------------- check status 
               .
            UPDATE-FILE.
               MOVE 1 TO RELOP.
               MOVE "000-0000" TO KEYVAL.<---------- set up CKSTART parameters to start 
               MOVE 23 TO KEYLOC.                     reading at lowest alternate key value 
               MOVE 8 TO KEYLENGTH.
               CALL "CKSTART" USING FILETABLE, STAT, RELOP, KEYVAL, KEYLOC, KEYLENGTH.
               IF STATUS-KEY-1="0" THEN
                   GO TO READ-RECORD;
               ELSE
                   DISPLAY "CKSTART ERROR, STATUS", STAT.
                   IF STATUS-KEY-1 = "9" THEN
                       CALL "CKERROR" USING STAT, RESULT
                       DISPLAY "CKERROR NO.", RESULT
                   GO TO FINISH.
            READ-RECORD.
               CALL "CKREAD" USING FILETABLE, STAT, REC, RECSIZE.
               IF STATUS-KEY-1 = "1" THEN
                   GO TO FINISH. <------------------ end of file 
               IF STATUS-KEY-1 = "0" THEN
                   GO TO WRITE-RECORD
               ELSE
                   DISPLAY "CKREAD ERROR,STATUS =", STAT.
                   IF STATUS-KEY-1 = "9" THEN
                       CALL "CKERROR" USING STAT, RESULT
                       DISPLAY "CKERROR NO. ", RESULT
                   GO TO READ-RECORD.
            WRITE-RECORD.
              MOVE SPACES TO OTHERDATA OF REC.
              CALL "CKREWRITE" USING FILETABLE,
              IF STATUS-KEY-1 = "0" THEN
                  DISPLAY NAME OF"DATA CLEARED"
                  GO TO READ-RECORD.
              DISPLAY "CKREWRITE ERROR, STATUS=",
              IF STATUS-KEY-1 = "9" THEN
                  CALL "CKERROR" USING STAT, RESULT,
                  DISPLAY "CKERROR NO.=",
                  GO TO READ-RECORD.

       _________________________________________________________________ 

       NOTE  If the file was opened for shared access with a call to
             CKOPENSHR, then the file should be locked with a call to
             CKLOCK before the call to CKSTART. The file should be
             unlocked with a call to CKUNLOCK only when the final record
             is updated, probably in the FINISH procedure.

       _________________________________________________________________ 

   2.  Random Update.  Find the record with the primary key "ECKSTEIN,
       LEO "and change the value of the secondary key to "257-5137":

            PROCEDURE DIVISION.
            START.
            .
            .
            .
              MOVE 2 TO I-O-TYPE, A-MODE.
              CALL "CKOPEN" USING FILETABLE, STAT.
              IF STATUS-KEY-1 = "0" THEN
                  GO TO F-UPDATE.
              DISPLAY "CKOPEN ERROR, STA", STAT.
              IF STATUS-KEY-1 = "9" THEN
                  CALL "CKERROR" USING STAT, RESULT
                  DISPLAY "CKERROR NO.=", RESULT
              GO TO FINISH.
            F-UPDATE.
              MOVE "ECKSTEIN, LEO "TO NAME OF REC.
              MOVE "257-5137" TO PHONE OF REC.
              MOVE SPACES TO OTHERDATA OF REC.
              CALL "CKREWRITE" USING FILETABLE, STAT, REC, RECSlZE.
              IF STATUS-KEY-1="0" THEN
                  DISPLAY REC "UPDATED"
                  GO TO FINISH.
              IF STAT = "23" THEN
                  DISPLAY NAME OF REC "NOT FOUND"
                  GO TO FINISH.
              DISPLAY "CKREWRITE ERROR, STATUS =", STAT.
              IF STATUS-KEY-1 = "9" THEN
                  CALL "CKERROR" USING STAT, RESULT
                  DISPLAY "CKERROR NO.=", RESULT.
              GO TO FINISH.



MPE/iX 5.0 Documentation