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

ISAM and abend S03B


IBM Mainframe Forums -> JCL & VSAM
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
I?aki Viggers

New User


Joined: 18 Jun 2005
Posts: 13

PostPosted: Sat Dec 09, 2023 5:13 am
Reply with quote

Hello,

On TurnKey4 I'm getting S03B when opening an ISAM dataset. I know the ISAM dataset is not the problem, since program IEBISAM displays the data contents as expected.
Code:
000001 //IVJCL10 JOB (1234),IVJCL10,CLASS=A,MSGCLASS=H                     
000002 //IVEX10  EXEC COBUCG,                                             
000003 //      PARM.COB='FLAGW,LOAD,SUBMAP,SIZE=2048K,BUFF=1024K'         
000004 //COB.SYSPUNCH DD DUMMY                                             
000005 //COB.SYSIN DD *                                                   
000006        IDENTIFICATION DIVISION.                                     
000007        PROGRAM-ID. IVJCL10.                                         
000008        ENVIRONMENT DIVISION.                                       
000009        INPUT-OUTPUT SECTION.                                       
000010        FILE-CONTROL.                                               
000011            SELECT FHAND ASSIGN TO DA-I-POLYISAM                     
000012       *        ORGANIZATION IS INDEXED                             
000013                RECORD KEY IS W-FLD1                                 
000014                NOMINAL KEY IS INP-VAL                               
000015                ACCESS MODE IS RANDOM.                               
000016        DATA DIVISION.                                               
000017        FILE SECTION.                                               
000018        FD  FHAND LABEL RECORDS ARE STANDARD.                       
000019        01  W-RCD.                                                   
000020        05  FILLER PIC X.                                           
000021        05  W-FLD1 PIC X(5).                                         
000022        05  W-FLD2 PIC X(75).                                       
000023        WORKING-STORAGE SECTION.                                     
000024        01  INP-VAL PIC X(5).                                       
000025        PROCEDURE DIVISION.                                         
000026        MAIN-PROC.                                                   
000027            ACCEPT INP-VAL.                                         
000028            OPEN INPUT FHAND.                                       
000029            CLOSE FHAND.                                             
000030            STOP RUN.                                               
000031 //COB.SYSLIB DD DISP=SHR,DSN=SYS1.COBLIB                           
000032 //GO.POLYISAM DD DISP=OLD,DCB=DSORG=IS,DSN=HERC01.YOUTUBE.POLYISAM 
000033 //GO.SYSIN DD *                                                     
000034 25679                                                               
000035 /*                                                                 
000036 //GO.SYSOUT DD SYSOUT=*,DCB=(RECFM=FB,LRECL=81,BLKSIZE=810)         
000037 //                                                                 


(Line 12 is commented out because the COBOL compiler on TK4 rejects that clause).

The log reads as follows:
Code:
                                                J E S 2   J O B   L O G         
00.26.31 JOB  700  $HASP373 IVJCL10  STARTED - INIT  1 - CLASS A - SYS TK4-     
00.26.31 JOB  700  IEF403I IVJCL10 - STARTED - TIME=00.26.31                   
00.26.32 JOB  700  IEFACTRT - Stepname  Procstep  Program   Retcode             
00.26.32 JOB  700  IVJCL10    IVEX10    COB       IKFCBL00  RC= 0000           
00.26.32 JOB  700  +IEW1991 ERROR - USER PROGRAM HAS ABNORMALLY TERMINATED     
00.26.32 JOB  700  IEF450I IVJCL10 GO IVEX10 - ABEND S03B U0000 - TIME=00.26.32
00.26.32 JOB  700  IVJCL10    IVEX10    GO        LOADER    AB S03B             
00.26.32 JOB  700  IEF404I IVJCL10 - ENDED - TIME=00.26.32                     
00.26.32 JOB  700  $HASP395 IVJCL10  ENDED                                     
    1     //IVJCL10 JOB (1234),IVJCL10,CLASS=A,MSGCLASS=H,                     
          //            USER=HERC01,PASSWORD=            GENERATED BY GDL       
    2     //IVEX10  EXEC COBUCG,                                               
          //      PARM.COB='FLAGW,LOAD,SUBMAP,SIZE=2048K,BUFF=1024K'           
    3     XXCOBUCG PROC SOUT='*'                                               
    4     XXCOB EXEC PGM=IKFCBL00,                                             
          XX         PARM='LOAD,SIZE=2048K,BUF=1024K'                           
    5     XXSYSPRINT DD SYSOUT=&SOUT                                           
    6     XXSYSUT1 DD UNIT=SYSDA,SPACE=(460,(700,100))                         
    7     XXSYSUT2 DD UNIT=SYSDA,SPACE=(460,(700,100))                         
    8     XXSYSUT3 DD UNIT=SYSDA,SPACE=(460,(700,100))                         
    9     XXSYSUT4 DD UNIT=SYSDA,SPACE=(460,(700,100))                         
   10     XXSYSLIN DD DSNAME=&LOADSET,DISP=(MOD,PASS),                         
          XX             UNIT=SYSDA,SPACE=(80,(500,100))                       
   11     //COB.SYSPUNCH DD DUMMY                                               
   12     //COB.SYSIN DD *                                                     
   13     //COB.SYSLIB DD DISP=SHR,DSN=SYS1.COBLIB                             
   14     XXGO EXEC PGM=LOADER,PARM='MAP,LET',COND=(5,LT,COB)                   
   15     XXSYSLIN DD DSNAME=*.COB.SYSLIN,DISP=(OLD,DELETE)                     
   16     XXSYSLOUT DD SYSOUT=&SOUT                                             
   17     XXSYSLIB DD DSNAME=SYS1.COBLIB,DISP=SHR                               
   18     //GO.POLYISAM DD DISP=OLD,DCB=DSORG=IS,DSN=HERC01.YOUTUBE.POLYISAM   
   19     //GO.SYSIN DD *                                                       
   20     //GO.SYSOUT DD SYSOUT=*,DCB=(RECFM=FB,LRECL=81,BLKSIZE=810)           
 STMT NO. MESSAGE                                                               
-                                                                               
    5     IEF653I SUBSTITUTION JCL - SYSOUT=*                                   
   16     IEF653I SUBSTITUTION JCL - SYSOUT=*                         7608K FREE
IEF236I ALLOC. FOR IVJCL10 COB IVEX10                                           
IEF237I JES2 ALLOCATED TO SYSPRINT                                             
IEF237I 140  ALLOCATED TO SYSUT1                                               
IEF237I 180  ALLOCATED TO SYSUT2                                               
IEF237I 170  ALLOCATED TO SYSUT3                                               
IEF237I 190  ALLOCATED TO SYSUT4                                               
IEF237I 180  ALLOCATED TO SYSLIN                                               
IEF237I DMY  ALLOCATED TO SYSPUNCH                                             
IEF237I JES2 ALLOCATED TO SYSIN                                                 
IEF237I 148  ALLOCATED TO SYSLIB                                               
IEF142I IVJCL10 COB IVEX10 - STEP WAS EXECUTED - COND CODE 0000                 
IEF285I   JES2.JOB00700.SO0103                         SYSOUT                   
IEF285I   SYS23343.T002631.RA000.IVJCL10.R0000001      DELETED       *--------6
IEF285I   VOL SER NOS= WORK00.                                                 
IEF285I   SYS23343.T002631.RA000.IVJCL10.R0000002      DELETED       *--------6
IEF285I   VOL SER NOS= WORK02.                                                 
IEF285I   SYS23343.T002631.RA000.IVJCL10.R0000003      DELETED       *--------9
IEF285I   VOL SER NOS= WORK01.                                                 
IEF285I   SYS23343.T002631.RA000.IVJCL10.R0000004      DELETED       *--------3
IEF285I   VOL SER NOS= WORK03.                                                 
IEF285I   SYS23343.T002631.RA000.IVJCL10.LOADSET       PASSED        *-------43
IEF285I   VOL SER NOS= WORK02.                                                 
IEF285I   JES2.JOB00700.SI0101                         SYSIN                   
IEF285I   SYS1.COBLIB                                  KEPT          *--------0
IEF285I   VOL SER NOS= MVSRES.                                                 
IEF373I STEP /COB     / START 23343.0026                                       
IEF374I STEP /COB     / STOP  23343.0026 CPU    0MIN 00.08SEC SRB    0MIN 00.04S
********************************************************************************
*     1. Jobstep of job: IVJCL10     Stepname: COB         Program name: IKFCBL0
*         elapsed time  00:00:00,21                      CPU-Identifier:  TK4- 
*             CPU time  00:00:00,12               Virtual Storage used:    820K
*           corr. CPU:  00:00:00,12   CPU time has been corrected by  1 / 1,0  m
*                                                                               
*     I/O Operation                                                             
*     Number of records read via DD * or DD DATA:     25                       
*     DMY.......0 140.......6 180.......6 170.......9 190.......3 180......43 DM
*                                                                               
*                                          Charge for step (w/o SYSOUT):       
********************************************************************* 7608K FREE
IEF236I ALLOC. FOR IVJCL10 GO IVEX10                                           
IEF237I 180  ALLOCATED TO SYSLIN                                               
IEF237I JES2 ALLOCATED TO SYSLOUT                                               
IEF237I 148  ALLOCATED TO SYSLIB                                               
IEF237I 241  ALLOCATED TO POLYISAM                                             
IEF237I 240  ALLOCATED TO SYS00096                                             
IEF237I JES2 ALLOCATED TO SYSIN                                                 
IEF237I JES2 ALLOCATED TO SYSOUT                                               
IEW1991 ERROR - USER PROGRAM HAS ABNORMALLY TERMINATED                         
IEF472I IVJCL10 GO IVEX10 - COMPLETION CODE - SYSTEM=03B USER=0000             
IEF285I   SYS23343.T002631.RA000.IVJCL10.LOADSET       DELETED       *-------44
IEF285I   VOL SER NOS= WORK02.                                                 
IEF285I   JES2.JOB00700.SO0104                         SYSOUT                   
IEF285I   SYS1.COBLIB                                  KEPT          *-------15
IEF285I   VOL SER NOS= MVSRES.                                                 
IEF285I   HERC01.YOUTUBE.POLYISAM                      KEPT          *--------0
IEF285I   VOL SER NOS= PUB010.                                                 
IEF285I   SYS1.UCAT.TSO                                KEPT          *--------0
IEF285I   VOL SER NOS= PUB000.                                                 
IEF285I   JES2.JOB00700.SI0102                         SYSIN                   
IEF285I   JES2.JOB00700.SO0105                         SYSOUT                   
IEF373I STEP /GO      / START 23343.0026                                       
IEF374I STEP /GO      / STOP  23343.0026 CPU    0MIN 00.03SEC SRB    0MIN 00.01S
********************************************************************************
*     2. Jobstep of job: IVJCL10     Stepname: GO          Program name: LOADER
*         elapsed time  00:00:00,07                      CPU-Identifier:  TK4- 
*             CPU time  00:00:00,04               Virtual Storage used:    332K
*           corr. CPU:  00:00:00,04   CPU time has been corrected by  1 / 1,0  m
*                                                                               
*     I/O Operation                                                             
*     Number of records read via DD * or DD DATA:      1                       
*     180......44 DMY.......0 148......15 241.......0 240.......0 DMY.......0 DM
*                                                                               
*                                          Charge for step (w/o SYSOUT):       
********************************************************************************
IEF375I  JOB /IVJCL10 / START 23343.0026                                       
IEF376I  JOB /IVJCL10 / STOP  23343.0026 CPU    0MIN 00.11SEC SRB    0MIN 00.05S
  CB545 V2 LVL78 01MAY72                 IBM OS AMERICAN NATIONAL STANDARD COBOL
   1                                                                           
00001          IDENTIFICATION DIVISION.                                         
00002          PROGRAM-ID. IVJCL10.                                             
00003          ENVIRONMENT DIVISION.                                           
00004          INPUT-OUTPUT SECTION.                                           
00005          FILE-CONTROL.                                                   
00006              SELECT FHAND ASSIGN TO DA-I-POLYISAM                         
00007         *        ORGANIZATION IS INDEXED                                 
00008                  RECORD KEY IS W-FLD1                                     
00009                  NOMINAL KEY IS INP-VAL                                   
00010                  ACCESS MODE IS RANDOM.                                   
00011          DATA DIVISION.                                                   
00012          FILE SECTION.                                                   
00013          FD  FHAND LABEL RECORDS ARE STANDARD.                           
00014          01  W-RCD.                                                       
00015          05  FILLER PIC X.                                               
00016          05  W-FLD1 PIC X(5).                                             
00017          05  W-FLD2 PIC X(75).                                           
00018          WORKING-STORAGE SECTION.                                         
00019          01  INP-VAL PIC X(5).                                           
00020          PROCEDURE DIVISION.                                             
00021          MAIN-PROC.                                                       
00022              ACCEPT INP-VAL.                                             
00023              OPEN INPUT FHAND.                                           
00024              CLOSE FHAND.                                                 
00025              STOP RUN.                                                   
   2                                                                           
                                                                               
*STATISTICS*     SOURCE RECORDS =    25     DATA DIVISION STATEMENTS =     6   
*OPTIONS IN EFFECT*     SIZE = 2097152  BUF = 1048576  LINECNT = 57  SPACE1, FLA
*OPTIONS IN EFFECT*     NODMAP, NOPMAP, NOCLIST,   SUPMAP, NOXREF,   LOAD, NODEC
*OPTIONS IN EFFECT*       ZWB                                                   
                                                      VS LOADER                 
OPTIONS USED - PRINT,MAP,LET,CALL,RES,NOTERM,SIZE=307200,NAME=**GO             
     NAME  TYPE  ADDR        NAME  TYPE  ADDR        NAME  TYPE  ADDR        NAM
  IVJCL10    SD  AC010    ILBOSTP0*  SD  AC590    ILBOSTP1*  LR  AC5A6    ILBOAC
  TOTAL LENGTH      7A0                                                         
  ENTRY ADDRESS   AC010                                                         


I also tried using in the SELECT instruction the UT prefix (instead of DA), but to no avail.

Looking up the possible causes of S03B, it is trivial to rule out causes 1-3 and 5. Cause #4 can also be discarded because the conversion of my sequential dataset to ISAM is as follows:
Code:
000001 //IVJCL8  JOB (1234),IVJCL8,CLASS=A,MSGCLASS=H             
000002 //IVEX  EXEC PGM=IEBDG                                     
000003 //SYSPRINT DD SYSOUT=*                                     
000004 //SEQIN DD DSN=HERC01.YOUTUBE.IVDAT6,DISP=SHR             
000005 //ISAMDS DD DSN=HERC01.YOUTUBE.POLYISAM,DISP=OLD,         
000006 //         DCB=DSORG=IS                                   
000007 //SYSIN DD *                                               
000008   DSD OUTPUT=(ISAMDS),INPUT=(SEQIN)                       
000009   FD NAME=BYTE0,LENGTH=1,STARTLOC=1,FILL=X'00'             
000010   FD NAME=FLD1,LENGTH=80,STARTLOC=2,FROMLOC=1,INPUT=SEQIN 
000011   CREATE NAME=(BYTE0,FLD1),INPUT=SEQIN                     
000012   END                                                     
000013 /*                                                         
000014 //                                                         


What am I missing? How can I overcome this abend?

Thanks.
Back to top
View user's profile Send private message
Pedro

Global Moderator


Joined: 01 Sep 2006
Posts: 2547
Location: Silicon Valley

PostPosted: Sat Dec 09, 2023 6:11 am
Reply with quote

I know nothing about ISAM nor 03B, but I am somewhat surprised that the registers were not displayed. Were there any messages related to the job in the syslog at the time of the abend?

Also, the explanation of 03B mentions that blksize and lrecl might be a problem. Please provide here.
Back to top
View user's profile Send private message
I?aki Viggers

New User


Joined: 18 Jun 2005
Posts: 13

PostPosted: Sat Dec 09, 2023 4:16 pm
Reply with quote

Thanks Pedro.

Pedro wrote:
I know nothing about ISAM nor 03B, but I am somewhat surprised that the registers were not displayed.

The JES log doesn't displays registers other than what I posted aove (I assume you mean the 16 GPRs, the PSW, and so forth). Adding the parameter PMAP in PARM.COB gives the assembler listing, but not the runtime values because that's just the compiler.

Pedro wrote:
Were there any messages related to the job in the syslog at the time of the abend?

Typing S[how] on SYSLOG only returns "No output available".

Pedro wrote:
Also, the explanation of 03B mentions that blksize and lrecl might be a problem. Please provide here.

It's not clear to me why that might be the case here. Both W-RCD in COBOL and the record definition in the JCL for IEBDG indicate a length of 81 bytes: the very first byte is a "deleted" indicator, and the other 80 contain the actual data. You'll see in the JCL below the COBOL source code that BLKSIZE is set to a multiple of LRECL.
Back to top
View user's profile Send private message
enrico-sorichetti

Superior Member


Joined: 14 Mar 2007
Posts: 10873
Location: italy

PostPosted: Sat Dec 09, 2023 7:14 pm
Reply with quote

for Turnkey4 issues You might find more help at

groups.io/g/H390-MVS
Back to top
View user's profile Send private message
Pedro

Global Moderator


Joined: 01 Sep 2006
Posts: 2547
Location: Silicon Valley

PostPosted: Sat Dec 09, 2023 9:44 pm
Reply with quote

re: "You'll see in the JCL"

I do not see the DCB attributes of the ISAM file in the JCL.

fyi: the 03B abend is described as: "an error occurred during processing of an OPEN macro instruction for an indexed sequential data set"

That is, IMHO, the problem is with your GO.POLYISAM file and not with the SYSOUT file.
Back to top
View user's profile Send private message
I?aki Viggers

New User


Joined: 18 Jun 2005
Posts: 13

PostPosted: Sun Dec 10, 2023 2:09 am
Reply with quote

Pedro wrote:
I do not see the DCB attributes of the ISAM file in the JCL.

That is, IMHO, the problem is with your GO.POLYISAM file and not with the SYSOUT file.

Oh ok, I hear you. I should have posted the JCL that creates POLYISAM:

Code:
000001 //IVJCL7 JOB (1234),IVJCL7,CLASS=A,MSGCLASS=H         
000002 //IVEX EXEC PGM=IEFBR14                               
000003 //ISAMDS DD DSN=HERC01.YOUTUBE.POLYISAM(PRIME),       
  3350 //    DISP=(NEW,KEEP),UNIT=3350,VOL=SER=PUB010,       
000005 //    SPACE=(CYL,(6,1)),                               
000006 //    DCB=(DSORG=IS,RECFM=FB,LRECL=81,BLKSIZE=810,     
000007 //      KEYLEN=5,RKP=1,OPTCD=ILMWY,CYLOFL=2,NTM=2)     
000008 //    DD DSN=HERC01.YOUTUBE.POLYISAM(OVFLOW),         
000009 //      DISP=(NEW,KEEP),                               
  3350 //      UNIT=3350,VOL=SER=PUB010,SPACE=(CYL,(1)),     
000011 //      DCB=*.ISAMDS                                   
000012 //*                                                   
000013 //CATLG EXEC PGM=IEHPROGM                             
000014 //SYSPRINT DD SYSOUT=*                                 
  3350 //DASD DD UNIT=3350,VOL=SER=PUB010,DISP=OLD           
000016 //SYSIN DD *                                           
000017   CATLG DSNAME=HERC01.YOUTUBE.POLYISAM,VOL=3350=PUB010
000018 /*                                                     
000019 //                                                     


Still, both LRECL and BLKSIZE are consistent with the code I posted previously.
Back to top
View user's profile Send private message
I?aki Viggers

New User


Joined: 18 Jun 2005
Posts: 13

PostPosted: Sun Dec 10, 2023 2:12 am
Reply with quote

enrico-sorichetti wrote:
for Turnkey4 issues You might find more help at

groups.io/g/H390-MVS

Thank you.

Are you suggesting that this could be a TK4 issue rather than something that would abend on an actual mainframe? If so, I might just move on.
Back to top
View user's profile Send private message
enrico-sorichetti

Superior Member


Joined: 14 Mar 2007
Posts: 10873
Location: italy

PostPosted: Sun Dec 10, 2023 7:09 pm
Reply with quote

Quote:
Are you suggesting that this could be a TK4 issue


NO...
since you are facing a problem/issue on something running on TK4 ( MVS 3.8 )
somebody with more knowledge of tk4 and mvs 3.8 will probably be more helpful for the problem determination and problem solution

remember ...
most of the people hanging around here have never heard of mvs 3.8
Back to top
View user's profile Send private message
Pete Wilson

Active Member


Joined: 31 Dec 2009
Posts: 582
Location: London

PostPosted: Mon Dec 11, 2023 5:20 pm
Reply with quote

I'm familiar with MVS3.8 (or OS/VS2 R3.8) but it's so long ago the memories are faded. We moved on to MVS/ESA and MVS/XA quite quickly and then OS/390 as it emerged.

ISAM was always a pain from an operational perspective, and I was glad support was dropped for it from Z/OS.

I'm not a programmer so can't really help much in this case.
Back to top
View user's profile Send private message
Pete Wilson

Active Member


Joined: 31 Dec 2009
Posts: 582
Location: London

PostPosted: Mon Dec 11, 2023 8:56 pm
Reply with quote

Found this reference in Wikipedia page en.wikipedia.org/wiki/MVS.

It timed out trying to open it but may work for you

wotho.ethz.ch/tk4-/
Back to top
View user's profile Send private message
I?aki Viggers

New User


Joined: 18 Jun 2005
Posts: 13

PostPosted: Mon Apr 08, 2024 2:51 am
Reply with quote

I revisited this issue. The abend can be prevented by including
Code:
BLOCK CONTAINS n RECORDS
(n being some actual number) in the SELECT statement, in FILE SECTION.

I didn't expect that omission to cause the problem, there being seemingly more important clauses that also were missing such as "RECORDING MODE IS F" or specifying the record length.

This update/clarification might be helpful to other users of TK4 who also are in their learning curve.

Thanks everyone for chiming in when I brought up this issue.
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 Abend S0C4 11 (Page Translation Excep... PL/I & Assembler 16
No new posts WER999A - UNSUCCESSFUL SORT 8ED U Ab... SYNCSORT 5
No new posts the system or user abend SF0F R=NULL COBOL Programming 0
No new posts Need to get an DLI abend like U0200 IMS DB/DC 2
No new posts Getting an abend (I/O abend was trapp... ABENDS & Debugging 3
Search our Forums:

Back to Top