MVSFORUMS.com Forum Index MVSFORUMS.com
A Community of and for MVS Professionals
 
 FAQFAQ   SearchSearch   Quick Manuals   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

Regarding the runtime abend - SFCB.

 
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> IMS
View previous topic :: View next topic  
Author Message
jayant_tibhe
Beginner


Joined: 24 Feb 2006
Posts: 8
Topics: 2
Location: PUNE

PostPosted: Mon Feb 12, 2007 8:35 am    Post subject: Regarding the runtime abend - SFCB. Reply with quote

Hi,

I am executing a simple IMS DB test program. The DBD, PSB and program compillation all are successful.But at the runtime I am getting the Abend SFCB. I am not getting why this is? Whether my System is supporting or not?

Please help me in this....

Details in SPOOL for Abend :
Code:

IEF237I JES2 ALLOCATED TO DFSVSAMP                             
IEA995I SYMPTOM DUMP OUTPUT                                   
SYSTEM COMPLETION CODE=FCB                                     
 TIME=12.41.03  SEQ=00273  CPU=0000  ASID=0022                 
 PSW AT TIME OF ERROR  070C1000   80FFEBD2  ILC 2  INTC 0D     
   NO ACTIVE MODULE FOUND                                     
   NAME=UNKNOWN                                               
   DATA AT PSW  00FFEBCC - 00181610  0A0D4110  016D182F       




My COBOL Code is :

USERS.MOUNESH.IMSDB(CBLPGM)

Code:


IDENTIFICATION DIVISION.                                   
PROGRAM-ID. ISRTPGM.                                       
AUTHOR.  MOUNESH.                                           
ENVIRONMENT DIVISION.                                       
CONFIGURATION SECTION.                                     
SOURCE-COMPUTER. IBM-370.                                   
OBJECT-COMPUTER. IBM-370.                                   
INPUT-OUTPUT SECTION.                                       
DATA DIVISION.                                             
WORKING-STORAGE SECTION.                                   
01  WS-RECORD             PIC X(20).                       
01  UNQUAL-SSA-HOSP       PIC X(11) VALUE 'HOSPITAL*  '.   
01  UNQUAL-SSA-WARD       PIC X(09) VALUE 'WARD     '.     
                                                           
01  CN-IMS-FUNCTIONS.                                       
    05  CN-GU                     PIC XXXX    VALUE 'GU  '.
     05  CN-GN                     PIC XXXX    VALUE 'GN  '.   
     05  CN-GNP                    PIC XXXX    VALUE 'GNP '.   
     05  CN-GHU                    PIC XXXX    VALUE 'GHU '.   
     05  CN-GHN                    PIC XXXX    VALUE 'GHN '.   
     05  CN-GHNP                   PIC XXXX    VALUE 'GHNP'.   
     05  CN-ISRT                   PIC XXXX    VALUE 'ISRT'.   
     05  CN-DLET                   PIC XXXX    VALUE 'DLET'.   
     05  CN-REPL                   PIC XXXX    VALUE 'REPL'.   
                                                               
 LINKAGE SECTION.                                             
                                                               
 01  PCB-HOSPMASK.                                             
     05 PCB-HOSP-DBDNAME            PIC X(08).                 
     05 PCB-HOSP-LEVEL-NUMBER       PIC X(02).                 
     05 PCB-HOSP-STATUS-CODE        PIC X(02).                 
     05 PCB-HOSP-PROC-OPTIONS       PIC X(04).                 
     05 PCB-HOSP-JCB-ADDRESS        PIC X(04).                 
     05 PCB-HOSP-SEGMENT-NAME       PIC X(08).                   
     05 PCB-HOSP-KEY-LENGTH         PIC S9(05) COMP.             
     05 PCB-HOSP-NUMBER-SEGS        PIC S9(05) COMP.             
     05 PCB-HOSP-KEY-FEEDBACK       PIC X(48).                   
 PROCEDURE DIVISION.                                             
 0000-MAIN-PARA.                                                 
     ENTRY 'DLITCBL' USING PCB-HOSPMASK.                         
*    MOVE 'ZEBRA  HOSPITAL     SOUTH EXTENSION, NEW DELHI-29 01101
*    '126543   ERT             55002020015PHYSIO             '   
     MOVE 'ZEBRA  HOSPITAL' TO WS-RECORD.                         
                                                                 
     CALL 'CBLTDLI' USING CN-ISRT                                 
                        PCB-HOSPMASK                             
                        WS-RECORD                                 
                        UNQUAL-SSA-HOSP                           
*                       UNQUAL-SSA-WARD.                         
       IF PCB-HOSP-STATUS-CODE NOT = SPACES                       
          DISPLAY '******ERROR ON ISRT******'   
          DISPLAY 'PCB-HOSPMASK: ' PCB-HOSPMASK 
          GOBACK                                 
       END-IF.                                   
      DISPLAY '******THE END******'.             
      GOBACK.         




The run JCL for this Pgm is :

USERS.MOUNESH.IMSDB(RUNCOIMS)


Code:

//MOUNESHR JOB NOTIFY=&SYSUID,PRTY=15                   
//*************************************                       
// SET MBR=CBLPGM                                             
// SET PSB=HOSPPSB                                           
// SET PSBLIB=USERS.MOUNESH.PSBLIB                           
// SET DBDLIB=USERS.MOUNESH.DBDLIB                           
// SET LOADLIB=USERS.MOUNESH.LOAD                             
//*************************************                       
//G      EXEC PGM=DFSRRC00,REGION=4M,                         
//            PARM=(DLI,&MBR,&PSB,7,,,,,N,,T,,,N,,,N,,,,,,,N)
//STEPLIB  DD DSN=IMS810.SDFSRESL,DISP=SHR                   
//         DD DSN=IMS810.PGMLIB,DISP=SHR                     
//         DD DSN=&LOADLIB(&MBR),DISP=SHR                     
//SYSPRINT DD SYSOUT=*                                       
//DFSRESLB DD DSN=IMS810.SDFSRESL,DISP=SHR                   
//IMS      DD DSN=&PSBLIB,DISP=SHR                           
//         DD DSN=&DBDLIB,DISP=SHR                       
//PRIME    DD DSN=USERS.MOUNESH.KSDS,DISP=SHR           
//OVERFLOW DD DSN=USERS.MOUNESH.ESDS,DISP=SHR           
//*INFILE1  DD DSN=USERS.MOUNESH.INPUT.HOSPITAL,DISP=SHR
//*INFILE2  DD DSN=USERS.MOUNESH.INPUT.WARD,DISP=SHR     
//*INFILE3  DD DSN=USERS.MOUNESH.INPUT.PATIENT,DISP=SHR 
//IMSLOGR  DD DSN=USERS.MOUNESH.LOG,DISP=(MOD,CATLG),   
//    DCB=(RECFM=VB,BLKSIZE=1920,                       
//    LRECL=1916,BUFNO=2),SPACE=(TRK,(5,5))             
//IEFRDER  DD DSN=USERS.MOUNESH.IEFRDER,DISP=(MOD,CATLG),
//    DCB=(RECFM=VB,BLKSIZE=1920,                       
//    LRECL=1916,BUFNO=2),SPACE=(TRK,(5,5))             
//SYSUDUMP DD SYSOUT=*,                                 
//         DCB=(RECFM=FBA,LRECL=121,BLKSIZE=605),       
//         SPACE=(605,(500,500),RLSE,,ROUND)             
//IMSMON   DD DUMMY                                     
//DFSVSAMP DD *                                         
//*VSRBF=4096,4       
/*                   


Please resolve my query....Thanks in advance.
_________________
Thanks and regards,
Jayant S Tibhe
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12382
Topics: 75
Location: San Jose

PostPosted: Mon Feb 12, 2007 9:35 am    Post subject: Reply with quote

Jayant S Tibhe,

I think the problem is with this
Quote:

PROGRAM-ID. ISRTPGM.


and your set statement is pointing to
Quote:

// SET MBR=CBLPGM


The load module is created under the name ISRTPGM and you are refering the pgm as CBLPGM in your JCL. Change program id to be CBLPGM and compile your pgm and re-run the job.

Hope this helps...

Cheers

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
jayant_tibhe
Beginner


Joined: 24 Feb 2006
Posts: 8
Topics: 2
Location: PUNE

PostPosted: Mon Feb 12, 2007 9:42 am    Post subject: Reply with quote

Hi Kolusu,

I have make that change and re compile and run the pgm..

Code:

IDENTIFICATION DIVISION.
PROGRAM-ID. CBLPGM.     



But I am getting the same problem SFCB abend.

The load module of the pgm is also


USERS.MOUNESH.LOAD(CBLPGM)


Please help me out!
_________________
Thanks and regards,
Jayant S Tibhe
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12382
Topics: 75
Location: San Jose

PostPosted: Mon Feb 12, 2007 10:39 am    Post subject: Reply with quote

jayant_tibhe,

What are the DCB atrributes of these load module datasets?
Code:

// SET PSBLIB=USERS.MOUNESH.PSBLIB                           
// SET DBDLIB=USERS.MOUNESH.DBDLIB                           
// SET LOADLIB=USERS.MOUNESH.LOAD                             


make sure that the RECFM of the load dataset is U

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
jayant_tibhe
Beginner


Joined: 24 Feb 2006
Posts: 8
Topics: 2
Location: PUNE

PostPosted: Tue Feb 13, 2007 1:00 am    Post subject: Reply with quote

Hi Kolusu,

I have checked the record Record format and found it was already "U" .
Please suggest me further in this regard.

Please find the properties of the load dataset in below snap shot:

Code:


Data Set Name  . . . : USERS.MOUNESH.LOAD                           
                                                                   
General Data                          Current Allocation           
 Volume serial . . . : AMDSYS          Allocated tracks  . : 10     
 Device type . . . . : 3390            Allocated extents . : 1     
 Organization  . . . : PO                                           
 Record format . . . : U                                           
 Record length . . . : 0                                           
 Block size  . . . . : 32760          Current Utilization           
 1st extent tracks . : 10              Used tracks . . . . : 10     
 Secondary tracks  . : 5               Used extents  . . . : 1     
                                                                   
 Creation date . . . : 2006/08/01                                   
 Referenced date . . : 2007/02/13                                   
 Expiration date . . : ***None***                                   

_________________
Thanks and regards,
Jayant S Tibhe
Back to top
View user's profile Send private message
programmer1
Beginner


Joined: 18 Feb 2004
Posts: 138
Topics: 14

PostPosted: Tue Feb 13, 2007 3:31 pm    Post subject: Reply with quote

What does SFCB mean ?

Did you check the quick reference for this error code ?
_________________
Regards,
Programmer
Back to top
View user's profile Send private message
jayant_tibhe
Beginner


Joined: 24 Feb 2006
Posts: 8
Topics: 2
Location: PUNE

PostPosted: Wed Feb 14, 2007 12:15 am    Post subject: Reply with quote

Ya I checked with that,

There is no error with this name.....
I am not getting why this is repeatadely happen!!!
_________________
Thanks and regards,
Jayant S Tibhe
Back to top
View user's profile Send private message
Nic Clouston
Advanced


Joined: 01 Feb 2007
Posts: 1075
Topics: 7
Location: At Home

PostPosted: Wed Feb 14, 2007 5:36 am    Post subject: Reply with quote

From Quickref:
Programs coded or compiled to run on CMS systems commonly issue SVCs
200-204 (X'C8'- X'CC'). If one of these objects is linked into an MVS
load module, it will get the corresponding Fnn ABEND when that
instruction is executed. The fix is to write such code so that it
detects which operating system it's running on and execute the
appropriate instructions.

so maybe you have a CMS module linked into an MVS module. CB is theSVC in question.
_________________
Utility and Program control cards are NOT, repeat NOT, JCL.
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> IMS All times are GMT - 5 Hours
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


MVSFORUMS
Powered by phpBB © 2001, 2005 phpBB Group