HP 3000 Manuals

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


KSAM/3000 Reference Manual

CKWRITE 

Procedure CKWRITE copies a logical record from the program's data area to
an output or an input-output file.

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

A call to procedure CKWRITE may be used to write records to a KSAM file
either in sequential order or randomly by key value.  The file must have
been opened for output or for input-output, but not for input only.

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 on the file
                 was successful 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 completion of the call to CKWRITE to indicate
                 whether or not the record was successfully written 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 to the file by CKWRITE.

recordsize       an interger (S9(4)COMP) containing the length in
                 characters of the record to be written.lt must not
                 exceed the maximum record length established for the
                 file when it was created, and it must be long enough to
                 contain all the keys.

USING CKWRITE 

The file to which the content of record is written must be open for
output only if sequential mode is specified.  It may be opened for output
or input-output if the access mode at open is random or dynamic.

WRITING IN SEQUENTIAL MODE. When the file is opened for sequential access
(access mode = 0) and for output only (I-O type = 1), then records must
be written to the file in ascending sequential order by primary key
value.  The value of the primary key in the record to be written must be
greater than the value of the primary key in any record previously
written to the file.  This insures that the records written to the file
are initially in ascending order physically as well as logically.

When I-O type = 1, CKWRITE writes records starting at the beginning of
the file, thereby effectively clearing any records previously written to
the file.

WRITING IN RANDOM MODE. In a file opened for random or dynamic access
(access mode = 1 or 2) and for output only or for input-output (I-O type
= 1 or 2), records can be written in any order; the value of the primary
key need not be in any particular relation to the primary key values of
previously written records.

If you want to preserve existing records in the file, you should open the
file with the input-output type equal to 2; when input-output type = 1,
all existing records are cleared prior to the write.

WRITING WHEN ACCESS IS SHARED. If the file was opened for shared access
with CKOPENSHR, then you must lock the file with a call to CKLOCK before
writing any records.  After the records are written, you should unlock
the file with a call to CKUNLOCK.

INVALID KEY. The invalid key condition (left byte of status="2") can
occur as a result of the following circumstances:

 *  File was opened for sequential access in output mode and the value of
    the primary key in the record being written is less than or equal to
    the value of the primary key in the record just written; status="21".

 *  File was opened for sequential or random access in output or
    input-output mode and the value of the primary key is equal to the
    value of the primary key in an existing record; status="22".

 *  File was opened for sequential or random access in output or
    input-output mode and the value of an alternate key for which
    duplicates are prohibited equals the value of a corresponding key in
    an existing record; status="22".

 *  File was opened for sequential or random access in output or
    input-output mode and an attempt was made to write a record beyond
    the physical bounds of the file; status="24".

EXAMPLES 

Assume a KSAM file called KSAMFILE with records containing 74 characters
(72 characters of data following two characters reserved for the delete
code), one primary key containing a name, and an alternate key containing
a phone number.  The data is read from an input file called DATA-FILE.
(Refer to Figure 3-2 for a diagram of the structure of this file.)

The first example writes data to KSAMFILE in sequential order by the
primary key.  The second example, using the same DATA DIVISION and the
same FINISH procedure, writes one record to the file containing the
"ADAMSON JOHN" as its primary key value.

   1.  Example of Sequential Write.

            DATA DIVISION
            .
            .
            .
            WORKING-STORAGE SECTION.
            77  RECSIZE          PIC S9(4)     COMP VALUE 74.
            77  RESULT           PIC 9(4)      VALUE 0.
            01  REC.
              03  FILLER       PIC XX        VALUE SPACES.
              03  NAME         PIC X(20).
              03  PHONE        PIC X(8).
              03  OTHERDATA    PIC X(44).
            01  DAT.
              03  NAME         PIC X(20).
              03  PHONE        PIC X(8).
              03  OTHERDATA    PIC X(44).
            01  FILETABLE.
              03  FILENUMBER   PIC S9(4)      COMP VALUE 0.
              03  FILENAME     PIC X(8)       VALUE "KSAMFILE".
              03  I-O-TYPE     PIC S9(4)      COMP VALUE 0.
              03  A-MODE       PIC S9(4)      COMP VALUE 0.
              03  PREV-OP      PIC S9(4)      COMP VALUE 0.
            01 STAT.
              03  STATUS-KEY-1 PIC X.
              03  STATUS-KEY-2 PIC X.
            .
            .
            .
            PROCEDURE DIVISION.
            START.
            .
            .
            .
                 MOVE 1 TO I-O-TYPE,<----------------- set type to output only 
                 CALL "CKOPEN" USING FILETABLE, STAT.
                 IF STATUS-KEY-1="O" THEN GO TO WRITE-F.
                 DISPLAY "CKOPEN ERROR, STATUS = ", STAT.
                 IF STATUS-KEY-1= "9" THEN
                      CALL "CKERROR" USING STAT, RESULT
                      DISPLAY "CKERROR NO. ", RESULT.
                 STOP RUN.
            WRITE-F.
                 READ DATA-FILE INTO DAT;
                      AT END GO TO FINISH.
                 MOVE CORRESPONDING DAT TO REC.
                 CALL "CKWRITE" USING FILETABLE, STAT, REC, RECSIZE.
                 IF STATUS-KEY-1="0" THEN
                      DISPLAY REC.
                      GO TO WRITE-F.
                 IF STAT="21" THEN
                      DISPLAY "SEQUENCE ERROR IN", NAME OF REC
                      GO TO WRITE-F.
                 IF STAT = "22" THEN
                     DISPLAY "DUPLICATE KEY", NAME OF REC
                     GO TO WRITE-F.
                 IF STAT = "24" THEN
                     DISPLAY "END OF FILE"
                     GO TO FINISH.
            .
            .
            .
            FINISH
                CLOSE DATA-FILE.
                CALL "CKCLOSE" USING FILETABLE, STAT.
                IF STATUS-KEY-1="9" THEN
                    CALL "CKERROR" USING STAT, RESULT
                    DISPLAY "CKCLOSE ERROR NO. ", RESULT.
                STOP RUN.

   2.  Example of random write.

            PROCEDURE DIVISION.
            START.
            .
            .
            .
              MOVE 1 TO I-O TYPE.<------------- output only 
              MOVE 2 TO A-MODE.<-------------- random access 
              CALL "CKOPEN"USING FILETABLE, STAT.
              .
              . check status 
              .
            FIND-REC.
              READ DATA-FILE INTO DAT;
                  AT END GO TO FINISH.
              IF NAME OF DAT = "ADAMSON        JOHN" THEN
                  GO TO WRlTE-REC;
                  ELSE GO TO FIND-REC.
            WRITE-REC.
              MOVE CORRESPONDING DAT TO REC.
              CALL "CKWRITE" USING FILETABLE, STAT, REC, RECSIZE.
              IF STATUS-KEY-1="0" THEN
                  DISPLAY REC," RECORD WRITTEN"
                  GO TO FINISH.
              IF STAT = "22" THEN
                  DISPLAY "DUPLICATE KEY"
                  GO TO FINISH.
              IF STAT = "24" THEN
                  DISPLAY "NO ROOM IN FILE"
                  GO TO FINISH.
            .
            .
            .



MPE/iX 5.0 Documentation