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

Update Count of Trailer for a VB File


IBM Mainframe Forums -> JCL & VSAM
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
rahuindo

New User


Joined: 09 Apr 2008
Posts: 83
Location: Chennai

PostPosted: Fri Sep 13, 2013 10:19 am
Reply with quote

Hi,
I know this has been posted multiple times in the forum and I've tried the following solution but I am not getting the desired output.

So, here is my requirement:
I've a VB file with lenght of 11054. The last records of the VB file is the trailer record. The trailer record consists of a Date and the count. Both are in Packed Decimal format. The rest of the fields in the Trailer are just blanks or spaces.
Code:

01  WS-TRAILER-RECORD.                                   
  02  PROCESSING-DATE2                    PIC S9(9) COMP-3.
  02  RECORD-COUNT                        PIC S9(7) COMP-3.
  02  TRAILER-CHECK-AREA                  PIC X(10).       
  02  FILL-AREA2                          PIC X(1331).     


I am able to strip the records using the SORT utility and I copy the stripped records into another file. This is my sort statement:
Code:

//SYSIN    DD SUBSYS=(CCSS,                                             
// ' SORT FIELDS=COPY                                           ',     
// ' OMIT COND=((505,1,CH,EQ,C'' ''),                             ',   
// '       OR,((505,1,CH,EQ,C''N''),AND,(524,1,CH,EQ,C''L'')),     ',   
// '       OR,((505,1,CH,EQ,C''D''),AND,(524,1,CH,EQ,C''R'')),     ',   
// '       OR,((505,1,CH,EQ,C''W''),AND,(524,1,CH,EQ,C''W'')),     ',   
// '       OR,((505,1,CH,EQ,C''W''),AND,(524,1,CH,EQ,C''X'')))     ',   
// ' END                                                        ')     


After I've copied the records to the 2nd file, I want to update the trailer count of the new file with the new value. This is my statement:
Code:

//DFSORT05 EXEC PGM=SORT                                               
//SORTIN   DD DSN=<InputFile>,DISP=SHR       
//SORTWK01 DD SPACE=(CYL,1500),UNIT=SYSOUT3                             
//SORTWK02 DD SPACE=(CYL,1000),UNIT=SYSOUT3                             
//SORTWK03 DD SPACE=(CYL,1000),UNIT=SYSOUT3                             
//SORTWK04 DD SPACE=(CYL,1000),UNIT=SYSOUT3                             
//SYSOUT   DD SYSOUT=*                                                 
//SYSPRT   DD SYSOUT=*                                                 
//SORTOUT  DD DSN=<Outputfile>,               
//            UNIT=DASD,RETPD=7,DISP=(NEW,CATLG,CATLG),                 
//            LIKE=<InputFile>
//SYSIN    DD *                                                         
  SORT FIELDS=COPY                                                     
                                                                       
    OUTFIL FNAMES=SORTIN,IFOUTLEN=11054,                                 
    IFTHEN=(WHEN=INIT,OVERLAY=(11050:SEQNUM,8,ZD)),                     
    IFTHEN=(WHEN=(5,5,CH,EQ,X'02'),                                     
    OVERLAY=(07:07,8,ZD,SUB,+2,M11,LENGTH=8))                           
//*--------------------------------------------------------------------*


However the output file is not updated and the record count remains the same. The above step just copies the Input File and does not update the count in the update file

This is my Trailer record in Hexadecimal format:
Code:

  j  k% 
003920096FFFFFFFFFFFFFFFFFFFFFFFFFFFF
2101C002CFFFFFFFFFFFFFFFFFFFFFFFFFFFF


Note: We do not have DFSORT and hence cannot use the IFTRAIL.
Any suggestions on what I am doing wrong? icon_rolleyes.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: Fri Sep 13, 2013 12:12 pm
Reply with quote

If you don't have DFSORT, please don't post in the DFSORT forum, Your topic has been moved to the JCL forum, where non-DFSORT sort questions live.

If you don't have DFSORT, why do you use it in your stepname?

Why are some of the control cards under the subsys and others not?

The whole thing can be done in one step, is there a need to split it?

Allthough you append temporary data to the end of fxied-length records, you do it at the beginning of variable-length records to preserve their variable-ness of length.

In addition to making all the records the same length when you extend them, you also tell the sysout to do that with the IFOUTLEN.

Your data remains unchanged because you made no attempt to change it.

To specify SORTIN on the OUTFIL is a bad idea. In a COPY operation, it is eeven worse.

From the output you show, the rest of the data on the trailer is not blanks or spaces but "high values", hexadecimal FF.

When finding a set of sort Control Cards, it is good to find out what they are doing.

Do you, reliably, have the date somewhere else in the data, like in the header? If you do, then the trailer can be reconstructed in OUTFIL using th in-built TRAILER1 and COUNT.

If not, then generally the same approach as you have:

Create a sequence number at the start of the record. Run this on your test data and look at the output. Note that the output is variable-length. Look at the output from your existing Control Cards and note that it is fixed at the maximum LRECL.

I now see that there is nothing on the trailer to identify it as a trailer, is there? You test for 02 was to try to compare to the first part of the date? You do realise that will only work for the next 86 years?

Code:
  OPTION COPY
  INREC BUILD=(1,4,SEQNUM,8,ZD,5)


Code:
  OPTION COPY
  INREC IFTHEN=(WHEN=INIT,BUILD=(1,4,SEQNUM,8,ZD,5)),
        IFTHEN=(WHEN=(13,1,CH,EQ,X'02'), => note 13 because of the extra 8 bytes
            OVERLAY=(15:5,8,ZD,SUB,+2,TO=PD,LENGTH=4))


Note, I've not attempted to run this, so attempt to fix any errors yourself without asking back here. Ensure that you understand what everything is doing (read the manual, check example, ask colleagues). If still have problems, ask here. Let us know how it goes, please.
Back to top
View user's profile Send private message
rahuindo

New User


Joined: 09 Apr 2008
Posts: 83
Location: Chennai

PostPosted: Sat Sep 21, 2013 2:23 am
Reply with quote

So, finally I was able to implement the changes. Here is my solution:
Code:

//SYSIN    DD *                                                         
        SORT FIELDS=COPY                                               
         INREC IFTHEN=(WHEN=INIT,OVERLAY=(11055:SEQNUM,7,ZD)),         
               IFTHEN=(WHEN=(14,1,CH,EQ,X'FF'),                         
                         OVERLAY=(10:11055,7,ZD,TO=PD,LENGTH=4))       
        OUTREC IFTHEN=(WHEN=INIT,BUILD=(1,11054))                       
//CHECK2   EXEC PGM=XX079,COND=(0,EQ,SORT05)                           
//*--------------------------------------------------------------------*

I had noticed that the trailer had High values after the Count and no other records have High values. So, I have used that as a condition to search for the High value.
Bill, thanks for all your support.
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: Sat Sep 21, 2013 3:45 am
Reply with quote

Are all your input records the same length? They are now on the output.

If not the same length, and you want to retain the input length, let us know.

If your records are the same length, you can specify IFOUTLEN=yourrecordlength on the INREC to chop off the extension sequence number automatically.

You don't need the OUTREC then.

Remember, unless you have a particular reason, there is no need for this to be seperate from the code which does the selection for the file - will save processing the file twice.
Back to top
View user's profile Send private message
rahuindo

New User


Joined: 09 Apr 2008
Posts: 83
Location: Chennai

PostPosted: Mon Sep 23, 2013 10:38 pm
Reply with quote

Quote:

Are all your input records the same length? They are now on the output.

The data on each of the record may not take up the entire 11050 lenght. We've a trailer section on the records and the data in their will vary for each record. So, it may not be of the same length.
So, yes I will want to retain the input lenght. How do I do that?

I tried using to do the sorting within this OUTREC but was not able to achieve it. So, I had to do it in 2 steps. How do I do it in 1 step?
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: Tue Sep 24, 2013 1:38 am
Reply with quote

Code:
         SORT FIELDS=COPY                                               
 
    OMIT COND=((505,1,CH,EQ,C'' ''),                               
       OR,((505,1,CH,EQ,C''N''),AND,(524,1,CH,EQ,C''L'')),       
       OR,((505,1,CH,EQ,C''D''),AND,(524,1,CH,EQ,C''R'')),       
       OR,((505,1,CH,EQ,C''W''),AND,(524,1,CH,EQ,C''W'')),       
       OR,((505,1,CH,EQ,C''W''),AND,(524,1,CH,EQ,C''X'')))

    INREC IFTHEN=(WHEN=INIT,BUILD=(,1,4,SEQNUM,4,PD,5)),         
          IFTHEN=(WHEN=(18,1,CH,EQ,X'FF'),                         
                   BUILD=(1,4,9,9,5,4,18)),
          IFTHEN=(WHEN=NONE,BUILD=(1,4,9))   
 


Something like this.

When adding fields to variable-length records, you have to do it in the fixed part of the record. The easiest place to ensure that is a data position 1 (record position 5).

The ,5, ,9 and ,18 none of which have a length say "from here to the end of the current record".

Your first COPY is simply excluding records, so it is very easy just to combine with the new code you have.
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 -> JCL & VSAM

 


Similar Topics
Topic Forum Replies
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
No new posts Extracting Variable decimal numbers f... DFSORT/ICETOOL 17
No new posts To get the count of rows for every 1 ... DB2 3
Search our Forums:

Back to Top