File with RECFM=VB
Select messages from
# through # FAQ
[/[Print]\]

MVSFORUMS.com -> Application Programming

#1: File with RECFM=VB Author: Jai PostPosted: Fri Jul 18, 2003 7:12 am
    —
Hi,

Please let me know more about Variable Block Files.
Actually, I was taking i/p from Flat files with RECFM=FB and updating the Flat file with RECFM=FB based on some condition(business logic) and it was successful. But the same thing when I changed RECFM=VB(both i/p and o/p) the program was running with RC=0 but not reading the File itself.
Some 4 bytes extra thing is there. I tried to declare first 4 bytes as filler also for VB File, but even then it was not reading the file.

Please can you update me what could be the reason and what needs to be
done to rectify it.

Thanks in advance.

#2:  Author: vijay PostPosted: Fri Jul 18, 2003 8:41 am
    —
Say the FB file length is 100 and now you're converting to VB.Don't change the COBOL copybook layout.Just add 4 to the LRECL i.e 104 in the JCL.don't put anything like 'recording mode' in select clause.It should work

#3:  Author: SureshKumar PostPosted: Fri Jul 18, 2003 8:43 am
    —
Jai,
The first 4 bytes is transparent to the program. User need not code for it. The extra 4 bytes is codded on the JCL. Treat your file as a normal FB file (but make sure you are differentiating the different record types). There is good documentation in the reference section of the forum).

#4:  Author: SureshKumar PostPosted: Fri Jul 18, 2003 8:47 am
    —
Example :
PROGRAM
FD INPUT-FILE
LABEL RECORDS ARE STANDARD
RECORDING MODE V
BLOCK CONTAINS 0 RECORDS.

01 INPUT-FIELDS.
05 INPUT-RECORD-TYPE PIC X(02).
05 INPUT-DATA PIC X(20).

JCL
//INPUT DD DSN=CREATE-YOUR-INPUT-FILE-AS ,
// DISP=(,CATLG,CATLG),
// UNIT=SYSDA,SPACE=(CYL,(20,20),RLSE),
// DCB=(RECFM=VB,LRECL=26)

#5:  Author: vijay PostPosted: Fri Jul 18, 2003 9:09 am
    —
here is sample code
Code:

IDENTIFICATION DIVISION.                                 
PROGRAM-ID.   TESTCOB1.                                   
AUTHOR.       **********.                                 
ENVIRONMENT DIVISION.                                     
CONFIGURATION SECTION.                                   
SOURCE-COMPUTER. IBM-370-168.                             
OBJECT-COMPUTER. IBM-370-168.                             
INPUT-OUTPUT SECTION.                                     
FILE-CONTROL.                                             
    SELECT FILEIN ASSIGN TO UT-S-FILEIN.                 
    SELECT FILEOUT ASSIGN TO      UT-S-FILEOUT.           
                                                         
DATA DIVISION.                                           
FILE SECTION.                                             
FD FILEIN                                                 
    RECORDING MODE IS V                                   
    BLOCK CONTAINS 0 RECORDS                             
    .                                                     
01  FILEIN-RECORD.                                       
    05  FILEIN-ID                         PIC X(02).     
    05  FILEIN-DATE-ID                    PIC X(09).     
    05  FILEIN-DATE-CONSTANT              PIC X(12).     
    05  FILEIN-DATE-CREATION-DATE         PIC X(08).     
    05  FILLER                            PIC X(01).     
    05  FILEIN-DATE-CREATE-DATE-ALPHA     PIC X(21).     
    05  FILEIN-DATE-FILE-NAME             PIC X(27).     
FD FILEOUT                                               
    RECORDING MODE IS V                                   
    BLOCK CONTAINS 0 RECORDS                             
    .                                                     
01  FILEOUT-RECORD.                                       
    05  FILEOUT-ID                        PIC X(02).     
    05  FILEOUT-DATE-ID                   PIC X(09).     
    05  FILEOUT-DATE-CONSTANT             PIC X(12).     
    05  FILEOUT-DATE-CREATION-DATE        PIC X(08).     
    05  FILLER                            PIC X(01).     
    05  FILEOUT-DATE-CREATE-DATE-ALPHA    PIC X(21).     
    05  FILEOUT-DATE-FILE-NAME            PIC X(27).     
WORKING-STORAGE SECTION.                                 
01 ARE-THERE-MORE-RECORDS      PIC X(3) VALUE 'YES'.     
  88  MORE-RECORDS                     VALUE 'YES'.       
   88  NO-MORE-RECORDS                  VALUE 'NO'.       
PROCEDURE DIVISION.                                       
0000-FILEOUT-CONTROL.                                     
         PERFORM 1000-INIT-FILES.                         
         PERFORM 2000-READ-FILEIN.                       
         PERFORM 1100-REPORT-FILEIN-RECORDS               
            UNTIL NO-MORE-RECORDS.                       
         PERFORM 1200-CLOSE-FILES.                       
         STOP RUN.                                       
                                                         
1000-INIT-FILES.                                         
         OPEN       INPUT FILEIN                         
                    OUTPUT FILEOUT.                       
                                                         
1100-REPORT-FILEIN-RECORDS.                               
       IF FILEIN-ID EQUAL '01'                           
         MOVE FILEIN-RECORD TO FILEOUT-RECORD             
         WRITE FILEOUT-RECORD.                           
         PERFORM 2000-READ-FILEIN.                       
1200-CLOSE-FILES.                                         
         CLOSE FILEIN                                     
               FILEOUT.                                   
                                                         
2000-READ-FILEIN.                                         
          READ FILEIN                                     
             AT END MOVE 'NO' TO ARE-THERE-MORE-RECORDS. 


#6:  Author: Jai PostPosted: Tue Jul 22, 2003 2:57 am
    —
Hi All,

Thanks a lot! for your quick response. But I have taken care of all the things which you all have mentioned. Even for Fixed Block, while updating, I am getting '{' in the filler place and that too only for the first record. I think only reason for this might be that I am filling the input data manually. I will try to get the input data in the input file through the batch program itself and see if it works.
Please suggest me what could be the reason of not getting the correct result, if it is manually updated i/p file.
I think, even if we update it manually it should come correctly. What could be the reason for this. Please guide me with your valuable suggestions.
I will update you all once I make this input also through the batch itself and if I get the correct result for both FB and VB.

Thanks again.
Have a Great Day.

#7:  Author: sladeLocation: Edison, NJ USA PostPosted: Wed Jul 23, 2003 3:03 pm
    —
I've encountered three situations when attempting to process IBM's variable length records. Here's a description of the methods I use in each of those situations. This may also be valid for non-IBM environments.

1) Don't know the lengths of the recs in the file. (Use Method 1 below.)

2) Can identify each variable rec that you read by knowing the rec type field value of each rec. (Use Method 2.)

3) Record description contains a variable table. (Use Method 3.)


Method 1.

In your FD
Code:

 RECORD VARYING FROM 1 TO max len expected
               DEPENDING ON WS-REC-LEN

If you don't know the max len use 32K.

Define the FD 01 as:
Code:

01 IP-REC.
   05 NBR-OF-BYTES PIC X
                   OCCURS FROM 1 TO nn DEPENDING ON WS-REC-LEN.

where, nn = max len expected used in VARYING,
WS-REC-LEN is an unsigned numeric data item large enough to hold "max len expected".

When you read an IP rec, the length of the rec just read will appear in
WS-REC-LEN.

If you decide to write the rec to an OP file is is your responsibility to populate that field with the appropriate length. If you decide to expand or reduce the size of the rec before you write it, you must first adjust the WS-REC-LEN field accordingly.


Method 2.

In the FD
Code:

 RECORD CONTAINS FROM 1 TO max len expected.

If you don't know the max len use 32K.

Define the FD 01 for as many types of recs as you have, e.g.:
(These could also be copybooks.)
Code:

01 IP-REC-1.
   05 REC-TYPE-1 PIC X.
   05 yada, yada, yada
01 IP-REC-2.
   05 REC-TYPE-2 PIC X.
   05 yada, yada, yada
01 yada, yada, yada
.
.
.

In the PD:
Code:

READ IP-FILE
IF REC-TYPE-1 = '1'
   do stuff only using IP-REC-1 datanames
   WRITE IP-REC-1
END-IF 
IF REC-TYPE-2 = '2'
   do stuff only using IP-REC-2 datanames
   WRITE IP-REC-2
END-IF
etc.

Note that you write the record, not the file.

Also, although I chose to make the rec type PIC X, it could be anything, so long as there is agreement that a given value will always reference a rec of a predetermined length and content.


Method 3.

In the FD
Code:

 RECORD CONTAINS FROM 1 TO max len expected.


Define the FD 01 which will contain a variable table, e.g.:
(This could also be a copybook.)
Code:

01 IP-REC-1.
   05 fixed part of rec PIC  X(nnn).
   05 MO-NBR            PIC  9(002).
   05 REC1-TBL.
      10 REC1-ENTRY OCCURS 1 TO 12 DEPENDING ON MO-NBR.
         15 REC1-MO     PIC  X(003).

.
.
.

In the PD:
Code:

READ IP-FILE


If you need to update the data in the file and create a new variable OP file from it, create an OP FD similar to that above. You can use the same copybook or you can create another rec description w/a variable table in it.

If the number of entries in the var table changes, be sure to update the "depending on" field before you WRITE the rec. If not you can move the IP "depending on" field to its OP counterpart.


JCL Notes:

Variable recs are built by the access method in 2 parts: control data and user data.
The control data is composed of a 4 byte Block Descriptor Word (BDW) and a 4 byte Record Descriptor Word (RDW). In each the 1st 2 bytes contain a binary representation of the length.

So, when coding the LRECL and BLKSIZE add 4 or 8 bytes respectively to the longest area expected for your data.

Note that in the COBOL pgm you state the data area sizes only. The BDWs & RDWs are not considered in the pgm.

While I'm on the subject of data length, you can always specify a rec or block length LARGER than the ACTUAL largest rec/block in the file. Just make sure that the BLKSIZE is 4 bytes longer than the LRECL. The only downside is that you waste buffer space. This shouldn't present a hardship, but the technique is handy in those situations where you may not know the exact file attributes.



MVSFORUMS.com -> Application Programming


output generated using printer-friendly topic mod. All times are GMT - 5 Hours

Page 1 of 1

Powered by phpBB © 2001, 2005 phpBB Group