0

I am changing three values inside of a file that is defines 7500 bytes. I used to put all of the file definition after my file so that I could see it better. But since I have moved up a level at COBOL I just want to make everything a filler and then have the four fields that I need to access visible.

I keep getting a sB37 error when I run my JCL. My output file is defined as 7500 bytes as well. I looked in the compile listing and it shows all of my fields in the correct locations.

I looked at my output file and there seems to be only 28,000 records written and the first ten look to have some garbage information.

I cannot list up the whole program for company rules but how would I go about solving the sB37 error.

Question: How to fix a sB37 error?

Code:

FD OUTPUT-FILE                                   
     RECORD VARYING FROM 2900 TO 7500          
     RECORDING MODE IS V                       
     BLOCK CONTAINS 0.                         
 01 O-PROVIDER-RECORD.                            
     05 FILLER              PIC X(149).           
     05 END-DTE             PIC X(8).             
     05 CANCEL              PIC X(2).             
     05 FILLER              PIC X(1133).          
     05 LAST-ACTIVITY-DTE   PIC X(8).             
     05 FILLER              PIC X(1598).          
     05 GROUP-CTR           PIC S999 COMP-3.      
     05 FILLER              PIC X(4600).  

JCL:

//STEP2      EXEC PGM=programnamehere             
//STEPLIB     DD DSN=SW89.DEBUG.programnamehere,DISP=SHR                 
//SYSOUT      DD SYSOUT=1                                         
//SYSDBOUT    DD SYSOUT=1                                         
//SYSOUC      DD SYSOUT=2                                         
//SYSPRINT    DD SYSOUT=1                                         
//SYSUDUMP    DD SYSOUT=1                                         
//INPUT1      DD DSN=MainFile.B01(+0),DISP=SHR,BUFNO=30               
//INPUT2      DD DSN=CDP.PARMLIB(SW00T111),DISP=SHR               
//OUTPUT1     DD DSN=SW89.DEBUG.OUTPUTFILE,DISP=(NEW,CATLG),             
//            DCB=TS20.VB7504.MODEL,MGMTCLAS=TMM,                 
//            SPACE=(CYL,(100,10),RLSE)                           
//PRTOUTA     DD SYSOUT=3,DCB=(BLKSIZE=0,LRECL=133,RECFM=FBM)     
//*         

Last Part of File:

 05  AREA.                                                    
     10  IND                     PIC X.                 
     10  CTR                     PIC S999  COMP-3.      
    10 P-GROUP-INFO OCCURS 200 TIMES DEPENDING ON CTR.
         15  P-NO                PIC 9(7).              
         15  P-START-DTE.                                
             20  PSTART-CC       PIC 99.                 
             20  P-START-DATE.                           
                 25  P-START-YY  PIC 99.                 
                 25  P-START-MM  PIC 99.                 
                 25  P-START-DD  PIC 99.                 
         15  P-STOP-DTE.                                 
             20  P-STOP-CC       PIC 99.                 
             20  P-STOP-DATE.                            
                 25  YY          PIC 99.                 
                 25  MM          PIC 99.                 
                 25  DD          PIC 99.                 

When I go to check my matches I find that my write statement is inserting a blank line in between all of my regular file lines. The only think that should happen here is that the three values are changed in the o-provider-record and then are written back to the file. There should be no blank lines with this new information on every other line.

Code:

CHECK-MATCH.                                                     
    PERFORM VARYING SUB FROM 1 BY 1 UNTIL SUB > TABLECOUNTER     
      IF P-PROVIDER >= TRIG-PROV-FROM(SUB) AND                   
         P-PROVIDER <= TRIG-PROV-THRU(SUB) THEN                  
         IF WS-CURRENT-DATE < P-END-DTE THEN                     
            IF P-YTD-TOTAL-PD  = 0 AND                           
               P-PYR-TOTAL-PD  = 0 AND                           
               P-PYR2-TOTAL-PD = 0 AND                           
               P-PYR3-TOTAL-PD = 0 AND                           
               P-PYR4-TOTAL-PD = 0 THEN                          
               IF P-NON-BILL-IND NOT EQUAL 'Y'                   
                PERFORM VARYING TAB FROM 1 BY 1 UNTIL TAB > 5    
                 IF P-TAXONOMY-CD(TAB) = TRIG-TAXONOMY(SUB) THEN 

                    ADD 1 TO T-REC-FOUND                       
                    ADD 1 TO T-REC-UPDATED                     

                    MOVE 'ZZ' TO O-CANCEL                      
                    MOVE '93939393' TO O-END-DTE               
                    MOVE '93939393' TO O-LAST-ACTIVITY-DTE    

                    PERFORM LOAD-PRINT-REPORT THRU X-LPR       
                    PERFORM PRINT-REPORT      THRU X-PR        
                    PERFORM ERASE-REPORT      THRU X-ER        
                 END-IF                                        
                END-PERFORM                                    
               END-IF                                          
            END-IF                                             
         END-IF                                                
      END-IF                                                   
     ADD 1 TO T-REC-WRITTEN              
     WRITE O-PROVIDER-RECORD END-WRITE   
    END-PERFORM.                         
X-CHECK-MATCH. EXIT.   

1 Answers1

4

You are writing an output record for each iteration of your outermost PERFORM. If there are two iterations (suspected from your earlier questions) then for each input record you will get two output records.

We know your file contains variable-length records. From the behaviour you describe you are not using APPLY WRITE ONLY for that file, so the behaviour is as expected. The COBOL points the FD/01 to the next available location in the output buffer, firstly after OPEN and then after each successful WRITE. Your first WRITE in the PERFORM loop will get the pointer moved on to the next available position, which contains, as a starting point, any old stuff that happens to be lying around (for the early WRITEs it will likely be binary-zeros, as the buffers get re-used, it'll be your old data).

You need some re-structuring, as suggested by NealB on an earlier question. You have lot of tests which are "invariant" within the loop. They should be outside, and the loop only entered if those invariant test show the possibility of the loop being needed in that case.

Back to earlier answers. This is going to be very confusing...

Now we can see your original record, you have OCCURS ... DEPENDING ON ... which is what is making the original file contain variable-length records when written from a COBOL program.

If you include the same count size and position in your definition and have an OCCURS with an entry with a length of 23 bytes you will make that portion of the record variable in length from zero to 4600 bytes (your replacement for CTR with a value zero through 200).

I'd not have made CTR a packed-decimal field, I'd have made it binary (BINARY/COMP/COMP-4) but that is not something you can change, and don't define in any different for your version of the layout, else very strange things will happen.

A guess:

You have RECORD [IS] VARYING ... but you do not have anything to vary the length of that particular record-layout.

There are generally three ways to deal with this: have OCCURS DEPENDING ON within the record, with a value earlier in the record which indicates how many times something occurs; use VARYING DEPENDING ON on the FD; use different record-layouts, multiple 01-levels, under the FD.

All the records you write using that 01 will be 7504 bytes long. If your input is somewhat less than this, your output dataset size is likely to be bigger, occupy more space, and the trailing part of each record may contain interesting values - unrelated directly to the actual data.

As we become more experienced, we use COPY and copybooks. It is not a problem at all if hundreds of fields are defined but only a few are used. Using a copybook, we don't need to check the positions, because we know we have the same as every program processing that data. Coding your own layouts is the wrong direction to go in.

Bill Woodger
  • 12,968
  • 4
  • 38
  • 47
  • It will run sometimes but gives me all bad data for the most part. Another person that I work with told me to use in my JCL SYSIN dd dsn=sw.t10.prime.filename,disp=(,CATLG),DCB=(LRECL=1500,RECFM=FB,BUFNO=25),RETPD=40,MGMTCLASS=TMM –  Mar 17 '14 at 19:16
  • Still getting bad data even if it is setup to just read in a record and then write that same record out to a file. Puts garbage in the fields. –  Mar 17 '14 at 20:34
  • Are you using WRITE or WRITE ... FROM ... ? If just WRITE, are you MOVEing your data to the output record before the WRITE? – Bill Woodger Mar 17 '14 at 20:40
  • WRITE O-PROVIDER-RECORD END-WRITE. <-- This is the write that I am using. –  Mar 18 '14 at 13:16
  • And how do you get data into O-PROVIDER-RECORD? – Bill Woodger Mar 18 '14 at 13:29
  • MOVE P-PROVIDER-RECORD to O-PROVIDER-RECORD. –  Mar 19 '14 at 13:02