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.