IBM Mainframe Forum Index
 
Log In
 
IBM Mainframe Forum Index Mainframe: Search IBM Mainframe Forum: FAQ Register
 

How to handle a PS file of LRECL 30,000


IBM Mainframe Forums -> COBOL Programming
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
Thirumurgann

New User


Joined: 13 Feb 2008
Posts: 36
Location: India

PostPosted: Sun Aug 07, 2011 9:19 am
Reply with quote

Hi Guys,
Please help me out. i have defined a variable in FD section with recl of 15,000. The size of the variable is known only at the run time. Hence i have defined it with approx maximum size. When program is executed it fetched all the eligible records 1Lakh records with LRECL of 15,000. Now i wanted to FTP these records to textpad to give feed to other app.
Since the LRECL is huge, writing all the values including spaces into the textpad and results in huge memory. could any one help me how to handle file of LRECL above 15,000 with 1 lakh records.
Back to top
View user's profile Send private message
Robert Sample

Global Moderator


Joined: 06 Jun 2008
Posts: 8696
Location: Dubuque, Iowa, USA

PostPosted: Sun Aug 07, 2011 9:24 am
Reply with quote

You have not described any problem you are having. FTP has no inherent limits on the size of a file that can be transferred, so there is no issue about FTP no matter the LRECL or number of records.

If and when you DO encounter a problem, feel free to post again -- but provide as many details as you can when you do, including system error messages.
Back to top
View user's profile Send private message
Thirumurgann

New User


Joined: 13 Feb 2008
Posts: 36
Location: India

PostPosted: Sun Aug 07, 2011 9:38 am
Reply with quote

Hi Robert,

My FD looks like,

FD PROD-CODE-LAYOUT
LABEL RECORDS ARE STANDARD
RECORD IS VARYING IN SIZE
FROM 1 TO 15082 CHARACTERS
BLOCK CONTAINS 0 RECORDS
RECORDING MODE IS V
DATA RECORD IS PROD-CODE-REC.


01 PROD-CODE-REC.
10 FD-PDF-UPN PIC 9(09).
10 PRD-FILLER-1 PIC X(01).
10 FD-PDF-MEMBER-OF-UPN PIC 9(09).
10 PRD-FILLER-2 PIC X(01).
10 FD-PDF-BUSINESS-UNIT PIC X(40).
10 PRD-FILLER-3 PIC X(01).
10 FD-PDF-PRI-PROD-CODE PIC X(20).
10 PRD-FILLER-4 PIC X(01).
10 FD-PROD-CODE-NEW PIC X(15000).

My clarification is the filed FD-PROD-CODE-NEW is populated with value of different length every time when the PGM is executed. Say first record has lenth of 1000 with trailing spaces therafter. Then second record has length of 10,000 with traling spaces. When all the records are being fetched the file has lots of traling spaces at end of each record. When i do FTP these kind of records i had coccupied huge size in notepad. Please suggest me how to hangle these type of records and so that it could be optimized.
Back to top
View user's profile Send private message
Robert Sample

Global Moderator


Joined: 06 Jun 2008
Posts: 8696
Location: Dubuque, Iowa, USA

PostPosted: Sun Aug 07, 2011 9:43 am
Reply with quote

From what you've posted so far, I cannot tell what is your problem?
Is your problem:
- the trailing spaces in each record? If so -- how many trailing spaces are you getting in each record? Are they on the mainframe file?
- that NOTEPAD won't handle the long records? If so -- STOP USING NOTEPAD and find an editor (there are hundreds, if not thousands, to choose from. You may have to pay a bit -- although many good ones are free to try -- but that investment pays for itself in no time.)
- the trailing spaces are being transferred via FTP? If so -- get rid of them with the FTP parameter that gets rid of trailing spaces.
- something else you haven't described yet?
Back to top
View user's profile Send private message
dick scherrer

Moderator Emeritus


Joined: 23 Nov 2006
Posts: 19244
Location: Inside the Matrix

PostPosted: Sun Aug 07, 2011 9:50 am
Reply with quote

Hello,

While your FD says variable, the record layout is fixed at the maximum length. . .

Every record written will have both an rdw (because of the variable FD) and the maximum length because there has been nothng defined to limit this.

IIRC 1 lakh is 100,000 which is not such a large number of records. We ftp millions of 4k to 20k records all of the time with no problem.

Suggest you use something other than notepad/textpad on the pc or change the way the file is defined to generate data easier to use on the pc. I suspect the fd being used was to make things easier on the coder. . . Quite often not the best reason for file design.
Back to top
View user's profile Send private message
Thirumurgann

New User


Joined: 13 Feb 2008
Posts: 36
Location: India

PostPosted: Sun Aug 07, 2011 9:57 am
Reply with quote

Hi Robert,

First of all my thanks to you for your Quick reply. Thanks a lot.

Yes its a PS file. The traling spaces at the end of each records would differ for each record. Say approximately 2000 or wharever its determined only at the run time. Out of PIC X(15000) it would occupy few thousand bytes for some and entire 15000 bytes for some other.Is these possible to remove these traling spaces while wrting into PS Variable length file.? Some times i end up with S0C4 abend once the space limit has been reached.

The DSN allocation for the file is:

OPRDFEED DD DSN=&ACE..&JNAME..PROD.CODE.FEED,
DISP=(MOD,CATLG,CATLG),
DCB=(RECFM=V,LRECL=15086,BLKSIZE=30500),
UNIT=(SYSDA,5),SPACE=(CYL,(3000,3000),RLSE)
Back to top
View user's profile Send private message
Thirumurgann

New User


Joined: 13 Feb 2008
Posts: 36
Location: India

PostPosted: Sun Aug 07, 2011 10:03 am
Reply with quote

Hi dick scherrer,

I read many of ur post. You are doing a good job and helping other people. Its nice to see ur reply on my post.


Could you please suggest how could i make the record layout not fixed at the maximum length.

01 PROD-CODE-REC.
10 FD-PDF-UPN PIC 9(09).
10 PRD-FILLER-1 PIC X(01).
10 FD-PDF-MEMBER-OF-UPN PIC 9(09).
10 PRD-FILLER-2 PIC X(01).
10 FD-PDF-BUSINESS-UNIT PIC X(40).
10 PRD-FILLER-3 PIC X(01).
10 FD-PDF-PRI-PROD-CODE PIC X(20).
10 PRD-FILLER-4 PIC X(01).
10 FD-PROD-CODE-NEW PIC X(15000).

Thanks in advance...
Back to top
View user's profile Send private message
Robert Sample

Global Moderator


Joined: 06 Jun 2008
Posts: 8696
Location: Dubuque, Iowa, USA

PostPosted: Sun Aug 07, 2011 10:10 am
Reply with quote

As Dick said, if your code has
Code:
WRITE PROD-CODE-REC
then you are going to write the entire 15,082 bytes of PROD-CODE-REC every time your program does the WRITE statement, and trailing spaces will be used if your record needs them. You either need multiple 01 records under your FD and WRITE the appropriate 01 to get a varying number of bytes output, or you could change your code to
Code:
RECORD IS VARYING IN SIZE
FROM 1 TO 15082 CHARACTERS
DEPENDING ON WS-PROD-CODE-REC-SIZE
and add to your program
Code:
77  WS-PROD-CODE-REC-SIZE      PIC 9(05).
but if you do this, you'll have to set the value of WS-PROD-CODE-REC-SIZE before each WRITE statement to contain the right number of bytes to output.
Back to top
View user's profile Send private message
dick scherrer

Moderator Emeritus


Joined: 23 Nov 2006
Posts: 19244
Location: Inside the Matrix

PostPosted: Sun Aug 07, 2011 10:20 am
Reply with quote

Hello,

Quote:
You are doing a good job and helping other people. Its nice to see ur reply on my post.

You're welcome - thank you for the kind words icon_smile.gif

How will the data be actually used on the pc?

Knowng this may help us better suggest how to create the download data.

If is almost for sure that the data will be input to some application or utility other than notepad/textpad . . .
Back to top
View user's profile Send private message
Thirumurgann

New User


Joined: 13 Feb 2008
Posts: 36
Location: India

PostPosted: Sun Aug 07, 2011 10:50 am
Reply with quote

Hi Dick,

I am generaing a feed file to java webserver. The other java down stream systems would use these files as a converted xml files and do the processing as required by the front end.

Thanks,
Thiru
Back to top
View user's profile Send private message
Bill O'Boyle

CICS Moderator


Joined: 14 Jan 2008
Posts: 2501
Location: Atlanta, Georgia, USA

PostPosted: Sun Aug 07, 2011 12:31 pm
Reply with quote

With a max record-length of 15082 for this VB file, shouldn't the optimum BLOCKSIZE be 30168 (15082 * 2) + 4?

Bill
Back to top
View user's profile Send private message
yuvrajdutta

New User


Joined: 13 Jul 2009
Posts: 40
Location: India

PostPosted: Sun Aug 07, 2011 1:48 pm
Reply with quote

Bill.. I second you.. how about creating a variable blocked out put in the first place and then write into it PROPERLY

Code:

000100*WRITE VARIABLE SIZE DATA INTO A FILE AND READ THEM LATER         00010099
000200 ID DIVISION.                                                     00020000
000300 PROGRAM-ID.                                                      00030099
000400     FILDISVW.                                                    00040099
000500 DATE-COMPILED.                                                   00050099
000600 ENVIRONMENT DIVISION.                                            00060086
000700 INPUT-OUTPUT SECTION.                                            00070086
000800 FILE-CONTROL.                                                    00080099
000900     SELECT INPUT-FILE ASSIGN TO READER                           00090099
001000     ORGANIZATION IS SEQUENTIAL                                   00100099
001100     ACCESS MODE IS SEQUENTIAL                                    00110099
001200     FILE STATUS IS FILE-STATUS.                                  00120099
001300*I-O-CONTROL.                                                     00130099
001400*    RERUN ON RESCUE EVERY 50 RECORDS OF INPUT-FILE.              00140099
001500 DATA DIVISION.                                                   00150086
001600 FILE SECTION.                                                    00160086
001700 FD INPUT-FILE                                                    00170086
001800     BLOCK CONTAINS 100 RECORDS                                   00180099
001900     RECORD IS VARYING IN SIZE FROM 1 TO 296 CHARACTERS           00190099
002000     DEPENDING ON SIZE-VAR                                        00200099
002100     LABEL RECORDS ARE STANDARD                                   00210099
002200     DATA RECORD IS INPUT-REC                                     00220099
002300     RECORDING MODE IS V.                                         00230099
002400 01 INPUT-REC.                                                    00240086
002500    88  END-OF-FILE VALUE HIGH-VALUES.                            00250099
002600    05  STRING-IN PIC X(296).                                     00260099
002700 WORKING-STORAGE SECTION.                                         00270000
002800 01 FILE-STATUS PIC X(2).                                         00280099
002900 01 SIZE-VAR    PIC 9(3) VALUE 5.                                 00290099
003000 01 COUNTER     PIC 9(3).                                         00300099
003100 PROCEDURE DIVISION.                                              00310000
003200 DECLARATIVES.                                                    00320099
003300 USE-PROCEDURE SECTION.                                           00330099
003400     USE AFTER STANDARD EXCEPTION PROCEDURE ON INPUT-FILE.        00340099
003500 COPY-PROCEDURE.                                                  00350099
003600     COPY FILESTAT.                                               00360099
003700 END DECLARATIVES.                                                00370099
003800 MAINLINE SECTION.                                                00380099
003900 100-MAIN-PARA.                                                   00390099
004000     OPEN OUTPUT INPUT-FILE                                       00400099
004100     PERFORM VARYING COUNTER FROM 1 BY 1 UNTIL COUNTER > 200      00410099
004200         INITIALIZE STRING-IN                                     00420099
004300         MOVE 'HELLO' TO STRING-IN(COUNTER:5)                     00430099
004400         DISPLAY 'INITIATE WRITE FOR RECORD NUMBER ' COUNTER      00440099
004500         WRITE INPUT-REC                                          00450099
004600         DISPLAY 'WRITE DONE FILE STATUS ' FILE-STATUS            00460099
004700         ADD 1 TO SIZE-VAR                                        00470099
004800     END-PERFORM                                                  00480099
004900     DISPLAY 'AFTER WRITE FILE'                                   00490099
005000     CLOSE INPUT-FILE                                             00500099
005100     INITIALIZE SIZE-VAR                                          00510099
005200     OPEN INPUT INPUT-FILE                                        00520099
005300     PERFORM UNTIL END-OF-FILE                                    00530099
005400         READ INPUT-FILE                                          00540099
005500             AT END                                               00550099
005600                 SET END-OF-FILE TO TRUE                          00560099
005700             NOT AT END                                           00570099
005800                 PERFORM 200-DISPLAY-PARA                         00580099
005900         END-READ                                                 00590099
006000     END-PERFORM                                                  00600099
006100     CLOSE INPUT-FILE                                             00610099
006200     STOP RUN.                                                    00620098
006300 200-DISPLAY-PARA.                                                00630099
006400     DISPLAY 'DATA SIZE: ' SIZE-VAR                               00640099
006500     DISPLAY 'DATA TEXT: ' STRING-IN(1:SIZE-VAR).                 00650099



This deals with a comparatively smaler file (VB LRECL 300).. also the output is as below:

Code:

 BROWSE    R01029.COBOL.INPUT.VB                      Line 00000000 Col 001 080
 Command ===>                                                  Scroll ===> CSR 
********************************* Top of Data **********************************
HELLO                                                                           
 HELLO                                                                         
  HELLO                                                                         
   HELLO                                                                       
    HELLO                                                                       
     HELLO                                                                     
      HELLO                                                                     
       HELLO                                                                   
        HELLO                                                                   
         HELLO                                                                 
          HELLO                                                                 
           HELLO                                                               
            HELLO                                                               
             HELLO                                                             


Now is the data appropriate w.r.t. the RECFM??.. to check run a IDCAMS PRINT on this file as below:

Code:

//PRINT    EXEC PGM=IDCAMS,COND=(4,LE) 
//SYSPRINT DD SYSOUT=*                 
//SYSOUT   DD SYSOUT=*                 
//INDD     DD DSN=R01029.COBOL.INPUT.VB,
//            DISP=SHR,DCB=RECFM=U     
//SYSIN    DD *                         
  PRINT        -                       
  INFILE(INDD) -                       
  DUMP                                 


This will among other things show the RDW to you..

Code:

********************************* TOP OF DATA **********************************
IDCAMS  SYSTEM SERVICES                                           TIME: 13:28:30
                                                                               
  PRINT        -                                                        00200002
  INFILE(INDD) -                                                        00210002
  DUMP                                                                  00220002
IDCAMS  SYSTEM SERVICES                                           TIME: 13:28:30
LISTING OF DATA SET -R01029.COBOL.INPUT.VB                                     
RECORD SEQUENCE NUMBER - 1                                                     
000000  54C80000 00090000 C8C5D3D3 D6000A00   0040C8C5 D3D3D600 0B000040 40C8C5D
000020  D3D6000C 00004040 40C8C5D3 D3D6000D   00004040 4040C8C5 D3D3D600 0E00004
000040  40404040 C8C5D3D3 D6000F00 00404040   404040C8 C5D3D3D6 00100000 4040404


Can you SPOT that 0000 0009?? that is the RDW..a 4 BYTE field.. why 9??

well the RDW consists of the SIZE of the DATA field + SIZE of the RDW itself.. since HELLO is 5 bytes and RDW itself is of 4 BYTES the value is 9.

So what about the next record.. well the next record is deliberately shifted one place.. and thus its size is now 6 BYTES (>>> HELLO<<<) which when added to the RDW length(4 bytes) gives you

Code:

000A00   00


And when FTP'd the output file to my thinkpad and opened in NOTEPAD.. this is what I see..

Code:

HELLO
 HELLO
  HELLO
   HELLO
    HELLO
     HELLO
      HELLO


Hope this helps..
Back to top
View user's profile Send private message
yuvrajdutta

New User


Joined: 13 Jul 2009
Posts: 40
Location: India

PostPosted: Sun Aug 07, 2011 1:53 pm
Reply with quote

Code:

00090000


is the RDW and not

Code:

0000 0009


my mistake.. icon_sad.gif
Back to top
View user's profile Send private message
Bill Woodger

Moderator Emeritus


Joined: 09 Mar 2011
Posts: 7309
Location: Inside the Matrix

PostPosted: Sun Aug 07, 2011 2:10 pm
Reply with quote

yuvrajdutta wrote:
[...]
Code:

//PRINT    EXEC PGM=IDCAMS,COND=(4,LE) 
//SYSPRINT DD SYSOUT=*                 
//SYSOUT   DD SYSOUT=*                 
//INDD     DD DSN=R01029.COBOL.INPUT.VB,
//            DISP=SHR,DCB=RECFM=U     
//SYSIN    DD *                         
  PRINT        -                       
  INFILE(INDD) -                       
  DUMP                                 


This will among other things show the RDW to you..

Code:

********************************* TOP OF DATA **********************************
IDCAMS  SYSTEM SERVICES                                           TIME: 13:28:30
                                                                               
  PRINT        -                                                        00200002
  INFILE(INDD) -                                                        00210002
  DUMP                                                                  00220002
IDCAMS  SYSTEM SERVICES                                           TIME: 13:28:30
LISTING OF DATA SET -R01029.COBOL.INPUT.VB                                     
RECORD SEQUENCE NUMBER - 1                                                     
000000  54C80000 00090000 C8C5D3D3 D6000A00   0040C8C5 D3D3D600 0B000040 40C8C5D
000020  D3D6000C 00004040 40C8C5D3 D3D6000D   00004040 4040C8C5 D3D3D600 0E00004
000040  40404040 C8C5D3D3 D6000F00 00404040   404040C8 C5D3D3D6 00100000 4040404


[...]


Just curious, but how did you get to 54C8?

I think you should explain RECFM=U for TS, as he's unlikely to be aware of its significance.

Just because the LRECL is big, the optimal blocksize does not have to change. The LRECL is a maximum for the dataset.

Say that all records were close to the maximum, you'd only get two records per track (assuming a "popular" disk model). If you coded a blocksize of around lrecl+4, you'd get three.

With more evenly distributed lengths, you'd only get one block per track, but the "normal" value would give optimal track usage.
Back to top
View user's profile Send private message
yuvrajdutta

New User


Joined: 13 Jul 2009
Posts: 40
Location: India

PostPosted: Sun Aug 07, 2011 3:19 pm
Reply with quote

Bill..

As far as my knowledge goes the

Code:

54C80000


is the BLOCK DESCRIPTION WORD(first 2 BYTES only).. in HEX.. so in DEC it becomes.. 21704 BYTES implying all the records (200 in all atleast in this case) are being read as 1 block as we are yet to reach the BLOCKSIZE(Block size . . . . : 27998) which is also substantiated by the bottom part of the IDCAMS listing:

Code:

0054C0  404040C8 C5D3D3D6                                                       
IDC0005I NUMBER OF RECORDS PROCESSED WAS 1                                     
IDC0001I FUNCTION COMPLETED, HIGHEST CONDITION CODE WAS 0                       
IDCAMS  SYSTEM SERVICES                                           TIME: 13:28:30
                                                                               
IDC0002I IDCAMS PROCESSING COMPLETE. MAXIMUM CONDITION CODE WAS 0               


Regarding the RECFM=U w.r.t. the VB dataset in the IDCAMS step.. a "BLOCKSIZE" number of BYTES are READ at one go and DUMPED as a SINGLE RECORD.. the remaining RECORDS into another "BLOCKSIZE" number of BYTES and so on..

If the RECFM=U is omitted each record is treated as it is and read record by record.

Code:

IDC0005I NUMBER OF RECORDS PROCESSED WAS 200                                   
IDC0001I FUNCTION COMPLETED, HIGHEST CONDITION CODE WAS 0                       
IDCAMS  SYSTEM SERVICES                                           TIME: 14:58:37
                                                                               
IDC0002I IDCAMS PROCESSING COMPLETE. MAXIMUM CONDITION CODE WAS 0               


If the same IDCAMS STEP is run on the above dataset with 400 records let's say.. we will obtain an IDCAMS listing like

Code:

IDC0005I NUMBER OF RECORDS PROCESSED WAS 2                                     
IDC0001I FUNCTION COMPLETED, HIGHEST CONDITION CODE WAS 0                       
IDCAMS  SYSTEM SERVICES                                           TIME: 15:03:55
                                                                               
IDC0002I IDCAMS PROCESSING COMPLETE. MAXIMUM CONDITION CODE WAS 0               


Why? because with only 200 records I was approaching my maximum BLOCKSIZE.. so midway while reaching 400 records my first BLOCK read was DONE.. and the NEXT BLOCK was read.

Please correct me if I am wrong...
Back to top
View user's profile Send private message
Bill Woodger

Moderator Emeritus


Joined: 09 Mar 2011
Posts: 7309
Location: Inside the Matrix

PostPosted: Sun Aug 07, 2011 5:10 pm
Reply with quote

Yep. Correct.

If you want to look at the blocks, of data, do this, code RECFM=U to override the catalogued definition.
Back to top
View user's profile Send private message
View previous topic :: :: View next topic  
Post new topic   Reply to topic View Bookmarks
All times are GMT + 6 Hours
Forum Index -> COBOL Programming

 


Similar Topics
Topic Forum Replies
No new posts Compare 2 files and retrive records f... DFSORT/ICETOOL 0
No new posts WER247A SORTOUT HAS INCOMPATIBLE LRECL SYNCSORT 6
No new posts FTP VB File from Mainframe retaining ... JCL & VSAM 8
No new posts Extract the file name from another fi... DFSORT/ICETOOL 6
No new posts How to split large record length file... DFSORT/ICETOOL 10
Search our Forums:

Back to Top