Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations derfloh on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Writing to KSAM file 1

Status
Not open for further replies.

aHash

Programmer
Aug 22, 2000
78
US
I have a KSAM file at my clients place. I need to write a record in to this file. I have written a smaal program to do from the example provided by doc.hp.com. But that does not help. I dont know what I am doing wrong.

I do not know the exact file structure of the existing UNIFLSZ. I am trying to manipulate from what I look I am very skeptical about this. Any help is appreciated.


Here is the code:
================

001000$CONTROL LIST, USLINIT
001100 IDENTIFICATION DIVISION.
001200 PROGRAM-ID. UNIFLSRC.
001300
001400******************************************************************
001500* 002800
002900******************************************************************
003000* *
003100* WRITE A RECORD IN UNIFLSZ *
003200* *
003300******************************************************************
003400
003500 ENVIRONMENT DIVISION.
003600 CONFIGURATION SECTION.
003700 SOURCE-COMPUTER. HP3000.
003800 OBJECT-COMPUTER. HP3000.
003900 SPECIAL-NAMES.
004000 CONDITION-CODE IS INTRINSIC-RESULT.
004100 INPUT-OUTPUT SECTION.
004200 FILE-CONTROL.
004300 SELECT DATA-FILE ASSIGN TO "UNIFLSZ".
004300 DATA DIVISION.
004400 FILE SECTION.
004500 FD DATA-FILE LABEL RECORDS ARE STANDARD.
004600 01 REC.
004700 03 FILLER PIC XX.
004800 03 PRG-NAME PIC X(5).
004900 03 FILLER PIC X(2).
005000 03 MEM-SIZE PIC X(5).
005100 WORKING-STORAGE SECTION.
005200 77 RECSIZE PIC S9(4) COMP VALUE 15.
005300 77 RESULT PIC 9(4) VALUE 0.
005400 01 DAT.
005500 03 WS-PRG-NAME PIC X(5).
005650 03 FILLER PIC X(2) VALUE SPACES.
005700 03 WS-MEM-SIZE PIC X(5).
005800
005900 01 FILETABLE.
006000 03 FILENUMBER PIC S9(4) COMP VALUE 0.
006100 03 FILENAME PIC X(8) VALUE "UNIFLSZ".
006200 03 I-O-TYPE PIC S9(4) COMP VALUE 0.
006300 03 A-MODE PIC S9(4) COMP VALUE 0.
006400 03 PREV-OP PIC S9(4) COMP VALUE 0.
006500 01 STAT.
006600 03 STATUS-KEY-1 PIC X.
006700
006800
006900 03 STATUS-KEY-2 PIC X.
007000 PROCEDURE DIVISION.
007100 010-START-PROG.
007200 MOVE 1 TO I-O-TYPE.
007300 CALL "CKOPEN" USING FILETABLE, STAT.
007400 IF STATUS-KEY-1="O" THEN GO TO WRITE-F.
007500 DISPLAY "CKOPEN ERROR, STATUS = ", STAT.
007600 IF STATUS-KEY-1= "9" THEN
007700 CALL "CKERROR" USING STAT, RESULT
007800 DISPLAY "CKERROR NO. ", RESULT.
007900 STOP RUN.
008000 WRITE-F.
008100
008200
008300
008400
008500
008600
008700
008800 READ DATA-FILE INTO DAT
008900 AT END GO TO FINISH.
MOVE "DC362" TO WS-PRG-NAME.
MOVE "75000" TO WS-MEM-SIZE.
009000 MOVE WS-PRG-NAME TO PRG-NAME.
MOVE WS-MEM-SIZE TO MEM-SIZE.
010000 CALL "CKWRITE" USING FILETABLE, STAT, REC, RECSIZE.
010100 IF STATUS-KEY-1="0" THEN
010200 DISPLAY REC.
010300 GO TO WRITE-F.
010400 IF STAT="21" THEN
010500 DISPLAY "SEQUENCE ERROR IN", PRG-NAME OF REC
010600 GO TO WRITE-F.
010700 IF STAT = "22" THEN
010800 DISPLAY "DUPLICATE KEY", PRG-NAME OF REC
010900 GO TO WRITE-F.
011000 IF STAT = "24" THEN
011100 DISPLAY "END OF FILE"
011200 GO TO FINISH.
011300 FINISH.
011400 CLOSE DATA-FILE.
011500 CALL "CKCLOSE" USING FILETABLE, STAT.
011600 IF STATUS-KEY-1="9" THEN
011700 CALL "CKERROR" USING STAT, RESULT
011800 DISPLAY "CKCLOSE ERROR NO. ", RESULT.
011900 STOP RUN.
 
aHash -

Is the file NM KSAM or CM KSAM? You can tell by doing a LISTF.

The "CK" modules you reference in your COBOL are old, out-dated modules to process KSAM files. Using the CK modules, you don't do ANY standard COBOL file access techniques (READ, OPEN, CLOSE, SELECT, FD, etc). Using standard, COBOL indexed file techniques is more appropriate, e.g.:
Code:
SELECT DATA-FILE
    ASSIGN TO "UNIFLSZ"
    ORGANIZATION IS INDEXED
    ACCESS IS RANDOM
    RECORD KEY IS key-name.
...
OPEN OUTPUT DATA-FILE
WRITE REC
CLOSE ...
If you need to know more about the characteristics of the file, you can get information via LISTFILE or LISTF (or, for CM KSAM file, KSAMUTIL.PUB.SYS).

Regards.

Glenn
 
//Is the file NM KSAM or CM KSAM?//
I dont know what tye is that. I dont even know The CKWRITE and FWRITE are totally different. Well I know that now.
Most of my old existing programs are using FWRITE.
I think I need to follow a different example then.
 
BTW,
These programs are written using a sofware called CBAS3000. Anyone knows anything about it? This will help me for my future questions.
 
A :listf filename,2 can be used to tell if it's native mode KSAM or Compatability mode. A compatability mode file will have a code of "KSAM"; a native mode file will have a K in the string under "TYP" (e.g. FAK). I'm not sure that it will matter much to you, but the newer NM KSAM files are simpler, faster, easier to use.

You can do a :LISTF filename,5 to get information about the key structure with NM KSAM files. With CM files, you must use KSAMUTIL.

Please reference the online KSAM manuals if you need further details (
Regards.

Glenn
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top