[Info-vax] Example of random access by record number on an RMS fixed record size, relative organization file?
Brian Schenkenberger
mail at SendSpamHere.ORG
Mon Sep 18 12:20:20 EDT 2023
On 2023-09-16 19:51:49 +0000, T. Kurt Bond said:
> Does anybody have an example program that uses random access by record
> number on an RMS fixed record size, relative organization file they'd be
> willing to share? I'm missing something, probably something obvious,
> but I've not been able to get random access by record number to work.
> I'm working in VAX MACRO (on VMS 5.5-2), but should be able to use an
> example in any language.
When I was writing RMS-CDC, I worked closely with Hein. He wrote many
test/example programs to check RMS-CDC functionality. Here is one of
his program in COBOL used to test RELATIVE RMS file accesses.
IDENTIFICATION DIVISION.
PROGRAM-ID. hein.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT the-file
ASSIGN TO "test-file"
ORGANIZATION IS RELATIVE
ACCESS MODE IS DYNAMIC
RELATIVE KEY IS the-key
FILE STATUS IS file-status.
DATA DIVISION.
FILE SECTION.
FD the-file.
01 the-record.
03 some-data PIC X(80).
WORKING-STORAGE SECTION.
01 the-key-txt.
03 filler PIC X(1) VALUE "(".
03 the-key PIC 9(9).
03 filler PIC X(2) VALUE ") ".
01 txt-key PIC X(9).
01 x PIC 9(9) COMP.
01 choice PIC 9.
01 file-status PIC XX.
01 sts PIC 9(9).
01 stv PIC 9(9).
01 rab_pt POINTER.
01 rfa_pt POINTER.
01 rfa.
03 vbn PIC 9(9) COMP VALUE 0.
03 id PIC 9(4) COMP VALUE 0.
01 rfa-txt.
03 filler PIC X(6) VALUE " RFA=(".
03 vbn-txt PIC 9(9).
03 filler PIC X(1) VALUE ",".
03 id-txt PIC 9(4).
03 filler PIC X(6) VALUE ") Rec=".
PROCEDURE DIVISION.
DECLARATIVES.
ERROR-HANDLER SECTION.
USE AFTER STANDARD EXCEPTION PROCEDURE ON the-file.
HERE-WE-GO.
MOVE RMS-STS TO sts.
MOVE RMS-STV TO stv.
DISPLAY "File status ", file-status, " STS=", sts, " STV=", stv.
END DECLARATIVES.
MAIN-CONTROL SECTION.
begin-here.
OPEN I-O the-file ALLOWING ALL.
CALL "DCOB$RMS_CURRENT_RAB" GIVING rab_pt
ADD 16 TO rab_pt GIVING rfa_pt.
The-loop.
CALL "OTS$MOVE3" USING BY VALUE 6, BY VALUE RFA_PT, BY REFERENCE RFA.
MOVE "----------------------------------------" TO some-data.
DISPLAY "1 Read, 2 Next, 3 Write, 4 Update, 5 Delete ? "
WITH NO ADVANCING
ACCEPT choice AT END STOP RUN.
GO TO 1-Read, 2-Next, 3-Write, 4-Update, 5-Delete
DEPENDING ON choice.
1-Read.
DISPLAY "Key value: " WITH NO ADVANCING.
ACCEPT txt-key AT END GO TO the-loop.
MOVE 0 to x.
INSPECT txt-key TALLYING x FOR CHARACTERS BEFORE INITIAL SPACE.
MOVE txt-key(1:x) TO the-key.
READ the-file RECORD.
DISPLAY the-key-txt, some-data.
GO TO the-loop.
2-Next.
READ the-file NEXT RECORD.
DISPLAY the-key-txt, some-data.
GO TO the-loop.
3-Write.
DISPLAY "Key value: " WITH NO ADVANCING.
ACCEPT txt-key AT END GO TO the-loop.
MOVE 0 to x.
INSPECT txt-key TALLYING x FOR CHARACTERS BEFORE INITIAL SPACE.
MOVE txt-key(1:x) TO the-key.
DISPLAY "New data : " WITH NO ADVANCING.
ACCEPT some-data AT END GO TO 3-Write.
WRITE the-record.
CALL "SYS$FLUSH" USING BY VALUE rab_pt.
GO TO the-loop.
4-Update.
DISPLAY "New data : " WITH NO ADVANCING.
ACCEPT some-data.
REWRITE the-record.
GO TO the-loop.
5-Delete.
DELETE the-file RECORD.
GO TO the-loop.
— VAXman
More information about the Info-vax
mailing list