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 gkittelson on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Reading a Binary Sequential File 2

Status
Not open for further replies.

SiouxCityElvis

Programmer
Jun 6, 2003
228
US
If I have a file that is 1 line and it has been told to me that it is a Binary Sequential File, how should I take that file and read it's one line into records with a length of 94?

I'm thinking...
FD BINARY-FILE-IN.
01 BINARY-RECORD PIC X(Huge/variable length unknown)

FD SEQ-LINE-OUT.
01 SEQ-RECORD PIC X(94).

WS-BINARY-IN PIC X(I have no idea what the length will be of its 1 huge line)

WS-LINE-SEQ-OUT PIC X(94)

OPEN BINARY-FILE-IN.
OPEN SEQ-LINE-OUT.
MOVE 1 TO BINARY-CTR.
PEFORM UNTIL SW-EOF-BINARY = "Y"
READ BINARY-RECORD
AT END
MOVE "Y" TO SW-EOF-BINARY
NOT AT END
MOVE BINARY-RECORD(BINARY-CTR:94)
TO WS-LINE-SEQ-OUT
WRITE SEQ-RECORD FROM WS-LINE-SEQ-OUT
MOVE SPACES TO SEQ-RECORD, WS-LINE-SEQ-OUT
ADD 94 TO BINARY-CTR
END-READ
END-PERFORM
 
Have you tried to declare this file as a Relative file with record length = 94 ?

Hope This Help, PH.
Want to get great answers to your Tek-Tips questions? Have a look at FAQ219-2884
 
No. I was just told that it was a binary file, and I know that it has only 1 line by looking at it in Vi. I'm using RMCOBOL-85 on Linux. I've never worked with anything but Indexed and Line Sequential files. So, I'm trying to figure out how I'd take this one huge line from this binary file and parse it out into record lengths of 94 and write out to a sequential line file. I know how to write out to a sequential line file. I just don't understand anything about reading a binary file that has only one huge line of data in it and break it down into multiple records of 94.
 
IDENTIFICATION DIVISION.
PROGRAM-ID. REINDEX.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT GET-FILE
ASSIGN TO "INPUTFILE"
ORGANIZATION IS BINARY SEQUENTIAL
ACCESS MODE IS SEQUENTIAL
FILE STATUS IS SF-FILE-STATUS.
DATA DIVISION.
FILE SECTION.

* REPLACE "999" WITH MAX RECORD LENGTH
FD GET-FILE
RECORD IS VARYING FROM 1 TO 999.
01 GET-REC.
03 FILLER PIX X(999).
WORKING-STORAGE SECTION.
01 SF-FILE-STATUS PIC XX.
88 SF-EOF VALUE "10".




Regards

Frederico Fonseca
SysSoft Integrated Ltd
 
Frederico,

Is your example for my binary file that has one huge line set as a minimum length of 1 and max of 999? I just want to make sure I understand you.

Then I would read through the look like I showed earlier in this thread checking for your switch value on each iteration, correct?

Thanks.
-David
 
David, Frederico,

As soon as you trigger "variable length" anything in binary sequential files, RM/COBOL expects a 4-byte record length header and trailer on the record. The first read will fail if the trailer does not match the header. (Note to PH: relative fails for similar reasons.) Therefore, you need to keep it fixed length binary sequential. However, at OPEN time, a fixed length binary sequential file must be a multiple of the record length.

The question then returns to, "What length should my record be?"

The answer is: PIC X(1). You read the file one character at a time.

Tom Morrison
 
Okay. Now I'm lost, sorry.
FD GET-FILE RECORD IS VARYING FROM 1 TO 999.
01 GET-REC.
03 FILLER PIX X(999).

should now be?...

FD GET-FILE RECORD IS VARYING FROM 1 TO 999.
01 GET-REC.
03 FILLER PIX X.

I just want to read this binary file that contains 1 huge line in it and parse it out into records of 94 in length.
In other words, the 1st 94 starting at 1 goes into WS-LINE-SEQ-OUT, then starting at 95 and ending at 188, the 2nd record of 94 characters I write out, etc.


 
IDENTIFICATION DIVISION.
PROGRAM-ID. REINDEX.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT GET-FILE
ASSIGN TO "INPUTFILE"
ORGANIZATION IS BINARY SEQUENTIAL
ACCESS MODE IS SEQUENTIAL
FILE STATUS IS SF-FILE-STATUS.
DATA DIVISION.
FILE SECTION.

FD GET-FILE
RECORD IS 94 CHARACTERS.
01 GET-REC.
03 FILLER PIX X(94).
WORKING-STORAGE SECTION.
01 SF-FILE-STATUS PIC XX.
88 SF-EOF VALUE "10".

Try this variation. Hopefully this will work for you.

etom
 
Ok...I was mistaken [blush]

I actually coded a test program. I hope this helps.
Code:
       identification division.
       program-id. binseq.
       environment division.
       input-output section.
       file-control.
           select a assign "binseq.dat"
               organization binary sequential.
           select b assign "binseq.dat"
               organization binary sequential.
       data division.
       file section.
       fd  a.
       01  a-rec   pic x(999).
       fd  b.
       01  b-rec   pic x(94).
       working-storage section.
       01  i pic 9(2).
       procedure division.
       x.
           open output a.
           write a-rec from all "0123456789".
           close a.
           open input b.
           perform 9999 times
               move all x"00" to b-rec
               read b at end
                   display "at end"
                   stop run
                 not at end
                   move 0 to i
                   inspect b-rec tallying i for characters
                                 before initial x"00"
                   display "Length: ", i,
                           ".  Record begins with: ", b-rec (1:40)
               end-read
           end-perform.

Produces the following output:

Code:
Length: 94.  Record begins with: 0123456789012345678901234567890123456789
Length: 94.  Record begins with: 4567890123456789012345678901234567890123
Length: 94.  Record begins with: 8901234567890123456789012345678901234567
Length: 94.  Record begins with: 2345678901234567890123456789012345678901
Length: 94.  Record begins with: 6789012345678901234567890123456789012345
Length: 94.  Record begins with: 0123456789012345678901234567890123456789
Length: 94.  Record begins with: 4567890123456789012345678901234567890123
Length: 94.  Record begins with: 8901234567890123456789012345678901234567
Length: 94.  Record begins with: 2345678901234567890123456789012345678901
Length: 94.  Record begins with: 6789012345678901234567890123456789012345
Length: 59.  Record begins with: 0123456789012345678901234567890123456789
at end

Tom Morrison
 
I'll try this, but I want my records written back out to be LINE SEQUENTIAL.

So, the file I'm reading with the huge line will break up into records of a length of PIC X(94) each.

characters 1-ninety four record blah blah blah
characters 95 through one-eighty-eigth blah blah balah
charceters one-eighty-eight through blablbabha

etc.
So that if I were breaking up the huge line into records of a length of 5 each(for simplicity of illustration) with an example of the 1 line in the Binary Sequential file(Input file) being...

abcdefghijklmnopqrstuvwxyz1234

would yield output line sequential records
abcde
fghij
klmno
pqrst
uvwxy
z1234

-David
 
So, try something like this:
SELECT BINARY-FILE-IN
ASSIGN "input.dat" ORGANIZATION BINARY SEQUENTIAL.
SELECT SEQ-LINE-OUT
ASSIGN "output.dat" ORGANIZATION LINE SEQUENTIAL.

FD BINARY-FILE-IN.
01 BINARY-RECORD PIC X(94)

FD SEQ-LINE-OUT.
01 SEQ-RECORD PIC X(94).

OPEN BINARY-FILE-IN.
OPEN SEQ-LINE-OUT.
PEFORM UNTIL EXIT
READ BINARY-RECORD
AT END
EXIT PERFORM
END-READ
WRITE SEQ-RECORD FROM BINARY-RECORD
END-PERFORM


Hope This Help, PH.
Want to get great answers to your Tek-Tips questions? Have a look at FAQ219-2884
 
David,

Yes, I understood that, but left that particular implementation for you to finish.

In the AT END leg of the READ statement, you might try something like WRITE SEQ-RECORD FROM BINARY-RECORD(1:I) instead of the DISPLAY statement.

Tom Morrison
 
David,

You didn't say you wanted a fully written, compiled, debugged, ready to run program.[bigsmile]

Dimandja
 
Thanks.
Basically, the solution was the same as PHV's with

MOVE SPACES TO BINARY-RECORD right before the READ statement.

Thanks everyone.
It's interesting that it works by reading the 1st 94 characters, 2nd 94 on next iteration, 3rd 94 on next iteration etc. with a simple READ statement.

-David
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top