|
View previous topic :: View next topic
|
| Author |
Message |
rahuindo
New User
Joined: 09 Apr 2008 Posts: 83 Location: Chennai
|
|
|
|
Hi All,
I am trying to execute the Stored Procedure from my Client program but each time i execute my Client Program, the SQLCode is "000" during the "CALL" statement.
Here are the code snippets:
The Create Stored Procedure DDL
| Code: |
CREATE PROCEDURE Schema.SP1
( IN VALUE1 VARCHAR(34) CCSID EBCDIC
,OUT SQLCD INTEGER
)
DYNAMIC RESULT SETS 5
EXTERNAL NAME 'SP1'
LANGUAGE COBOL
PARAMETER STYLE GENERAL WITH NULLS
NOT DETERMINISTIC
NULL CALL
FENCED
READS SQL DATA
NO DBINFO
COLLID collid
WLM ENVIRONMENT D1WLM1ENV
ASUTIME LIMIT 2
STAY RESIDENT NO
PROGRAM TYPE MAIN
SECURITY DB2
RUN OPTIONS 'MSGFILE(OUTFILE,,,,ENQ)'
COMMIT ON RETURN NO
INHERIT SPECIAL REGISTERS
;
|
Here is the declaration for the Linkage Section of the Stored Proc:
| Code: |
LINKAGE SECTION.
01 PL-VAR-INP PIC X(34).
01 P-INP-SQL-CD PIC S9(9) COMP.
|
Cursor Declaration:
| Code: |
EXEC SQL
DECLARE L4NMINFO CURSOR WITH HOLD WITH RETURN FOR
SELECT PERS.SSN_NUM
,NPN.NPN_NUM
,PERS.FRST_NAME
,PERS.MID_NAME
,PERS.LST_NAME
,PERS.SUBJ_ID
FROM BX70RFP9.UTT_PERS PERS,
BX70RFP9.UTT_NPN_MASTER NPN
WHERE
PERS.LST_NAME = :WS-LAST-NAME
AND NPN.PERS_FIRM_IND = 'P'
AND PERS.SSN_NUM LIKE :WS-L4-SSN-NUM
AND NPN.SSN_TIN_NUM = PERS.SSN_NUM
FOR FETCH ONLY
END-EXEC
|
Then i open the cursor.
My COBOL Client Program:
| Code: |
LINKAGE SECTION.
01 PL-VAR-INP PIC X(34).
01 P-INP-SQL-CD PIC S9(9) COMP.
PROCEDURE DIVISION USING PL-VAR-INP P-INP-SQL-CD.
|
My CALL statement:
| Code: |
EXEC SQL
CALL UTP51001(:PL-VAR-INP, :P-INP-SQL-CD)
END-EXEC.
EXEC SQL
DESCRIBE PROCEDURE UTP51001 INTO :SQLDA
END-EXEC
EXEC SQL
ASSOCIATE LOCATOR (:LOC01)
WITH PROCEDURE UTP51001
END-EXEC.
EXEC SQL
ALLOCATE L4NMINFO CURSOR FOR RESULT SET :LOC01
END-EXEC.
EXEC SQL
FETCH L4NMINFO INTO :R1-SSN-NUM
,:R1-NPN-NUM
,:R1-FRST-NAME
,:R1-MID-NAME
,:R1-LST-NAME
,:R1-SUBJ-ID
END-EXEC.
|
I always hit the SQLCode "000" during the CALL statement. I am not able to find the appropriate reason for it.
The tables have data and on checking manually i am able to retrieve data.
Can anyone let me know what can be the probable reason? |
|
| Back to top |
|
 |
ashimer
Active Member

Joined: 13 Feb 2004 Posts: 551 Location: Bangalore
|
|
|
|
What is the value of SQLCD from the SP ?
Check on the ASUTIME of 2 ... this could not be the reason but it could be too less for the SP to open the cursor and return back the result set .... |
|
| Back to top |
|
 |
rahuindo
New User
Joined: 09 Apr 2008 Posts: 83 Location: Chennai
|
|
|
|
Hi Ashimer,
During the CALL statement execution, the SQLCODE is "000" and then during the ASSOCIATE LOCATOR it is "-482".
I modified the ASUTIME parameter to 5 but it still shows the same error. |
|
| Back to top |
|
 |
ashimer
Active Member

Joined: 13 Feb 2004 Posts: 551 Location: Bangalore
|
|
|
|
-482 specifies that no locator was returned by the stored procedure ...
increase the ASUTIME to 100000 or NOLIMIT and try again .... dont worry about the figure .... |
|
| Back to top |
|
 |
rahuindo
New User
Joined: 09 Apr 2008 Posts: 83 Location: Chennai
|
|
|
|
| It still shows the same SQLCODE...no change |
|
| Back to top |
|
 |
ashimer
Active Member

Joined: 13 Feb 2004 Posts: 551 Location: Bangalore
|
|
|
|
| Code: |
DYNAMIC RESULT SETS 5
|
??? for one cursor return |
|
| Back to top |
|
 |
dbzTHEdinosauer
Global Moderator

Joined: 20 Oct 2006 Posts: 6965 Location: porcelain throne
|
|
| Back to top |
|
 |
rahuindo
New User
Joined: 09 Apr 2008 Posts: 83 Location: Chennai
|
|
|
|
Hi Ashimer, After your suggestion i had already changed the ASUTIME to NOLIMIT but i still faced the same issues.
I identified the error occurs during the Opening of the cursor which ultimately is due to the Cursor declaration.
Here i have a question that do we need to have the schema-name or the collection id or the user-id attached with the tables while declaring the cursor. |
|
| Back to top |
|
 |
rahuindo
New User
Joined: 09 Apr 2008 Posts: 83 Location: Chennai
|
|
|
|
Hi,
I solved that error and now i am stuck up with -981. This is due to the application attempting to execute an SQL operation, but the RRSAF connection iss not in a state that allows the processing of SQL
statements.
I compiled my Stored Procedure with ATTACH(RRSAF) and NODYNAM option but i am still facing the same issue. Is there something else i am missing??
I went through the document about the RRS and the Language Environment Setup but the problem persists.
The SQLError Code is given below:
- DSNT408I SQLCODE = -981
REASON 00C12219
DSNT418I SQLSTATE = 57015 SQLSTATE RETURN CODE
DSNT415I SQLERRP = DSNARA00 SQL PROCEDURE DETECTING ERROR |
|
| Back to top |
|
 |
dbzTHEdinosauer
Global Moderator

Joined: 20 Oct 2006 Posts: 6965 Location: porcelain throne
|
|
|
|
you need to connect to RRS, which you have not.
since you have RRSAF in your shop, someone, someplace, somehow, is connecting to RRS.
ask your peers, project manager, or support group how it is done at your site. |
|
| Back to top |
|
 |
Anuj Dhawan
Superior Member

Joined: 22 Apr 2006 Posts: 6248 Location: Mumbai, India
|
|
|
|
| Just a passing thought-- can't you use "DB2 Store Builder" from IBM to test Store PROCs instead of CALLing store procs from a COBOL program, that makes things pretty easy. |
|
| Back to top |
|
 |
rahuindo
New User
Joined: 09 Apr 2008 Posts: 83 Location: Chennai
|
|
|
|
| No Anuj...we don't have "DB@ Store Builder" in our shop and hence the COBOL programs. |
|
| Back to top |
|
 |
dbzTHEdinosauer
Global Moderator

Joined: 20 Oct 2006 Posts: 6965 Location: porcelain throne
|
|
|
|
you need to connect to RRS, which you have not.
since you have RRSAF in your shop, someone, someplace, somehow, is connecting to RRS.
ask your peers, project manager, or support group how it is done at your site. |
|
| Back to top |
|
 |
rahuindo
New User
Joined: 09 Apr 2008 Posts: 83 Location: Chennai
|
|
|
|
Hi Dino..this is the first time we are implementing Stored Procs so nobody have any idea about this error or the working of Stored Procs!! I am contacting the Support system for "How To Connect RRS" and it will take some time.  |
|
| Back to top |
|
 |
Raghu navaikulam
Active User
Joined: 27 Sep 2008 Posts: 194 Location: chennai
|
|
|
|
Hi rahuindo
Can you please post the two JCLs that you have used to compile the server(Stored procedure(STP)) program and the client program( the program calling the STP)?
If so some one can help you.
Regards
Raghu |
|
| Back to top |
|
 |
dbzTHEdinosauer
Global Moderator

Joined: 20 Oct 2006 Posts: 6965 Location: porcelain throne
|
|
|
|
rahuindo,
there are many ways to connect to RRS,
that is why you need to use the methodology used by your site.
Also, why is RRSAF being used if you are only utilizing one resource - DB2 -
in your application/SP?
For instance,
RRSAF is used when an application/pgm accesses MQS and DB2 during the same task. |
|
| Back to top |
|
 |
rahuindo
New User
Joined: 09 Apr 2008 Posts: 83 Location: Chennai
|
|
|
|
Hi Raghu,
We compile the Stored Procedure and the CLient Program using Changeman. hence i am including only some of the important steps as each JCL runs into 400 lines of code:
Client Program:
| Code: |
//* DB2 PRECOMPILER
//****************************************************************
//DSNHPC EXEC PGM=DSNHPC,
// PARM='APOST,ATTACH(RRSAF),SOURCE,LEVEL(A123),HOST(IBMCOB)'
//DBRMLIB DD DSN=HLQ.MNM.CM.DBRMLIB(SPRCSTUB),DISP=SHR
//STEPLIB DD DSN=HLQ.DB2.SDSNLOAD,DISP=SHR
//SYSCIN DD DSN=&&DSNHPC,DISP=(MOD,PASS),UNIT=DASD,
// SPACE=(800,(500,500))
//SYSLIB DD SN=HLQ.MNM.CMN.PACKNO.DCL, DISP=SHR
// DD DSN=HLQ.MNM.CMN.PACKNO.DCL,DISP=SHR
// DD DSN=HLQ.MNM.CMN.PACKNO.CPY,DISP=SHR
// DD DSN=SYS5.TCR.CICS.COPYLIB,DISP=SHR
//SYSPRINT DD SYSOUT=*
//SYSTERM DD SYSOUT=*
//SYSUDUMP DD SYSOUT=*
//SYSUT1 DD SPACE=(800,(500,500),,,ROUND),UNIT=DASD
//SYSUT2 DD SPACE=(800,(500,500),,,ROUND),UNIT=DASD
//SYSIN DD DSN=HLQ.MNM.CMN.PACKNO.SRC(SPRCSTUB),DISP=SHR
//* COBOLII COMPILER
//*----------------------------------------------------------
//COMPILE EXEC PGM=IGYCRCTL,COND=(4,LT),
// PARM=('NODBCS,APOST,TRUNC(BIN),NOFLAGSAA,NODYNAM')
//STEPLIB DD DISP=SHR,DSN=SYS1.ECOBOL.SIGYCOMP
//SYSLIB DD DSN=HLQ.MNM.CMN.PACKNO.DCL,DISP=SHR
// DD DSN=HLQ.MNM.CMN.PACKNO.DCL,DISP=SHR
// DD DSN=HLQ.MNM.CMN.PACKNO.CPY,DISP=SHR
// DD DSN=SYS5.TCR.CICS.COPYLIB,DISP=SHR
// DD DSN=SYS5.TCR.CICS.COPYLIB,DISP=SHR
// DD DISP=SHR,DSN=SYS1.LE370.SCEESAMP
// DD DISP=SHR,DSN=SYS5.CTS.COBOL.COPYLIB
// DD DISP=SHR,DSN=SYS5.ICD.DG.V231.SAMPS
//SYSIN DD DSN=&&DSNHPC,DISP=(OLD,DELETE)
//SYSLIN DD DSN=&&OBJ,UNIT=VIO,
// DCB=(LRECL=80,BLKSIZE=80,RECFM=F),
// SPACE=(23440,(10,5),RLSE),DISP=(NEW,PASS)
//SYSPRINT DD SYSOUT=*
//SYSUT1 DD UNIT=SYSOUT3,SPACE=(23476,(30,30))
//SYSUT2 DD UNIT=SYSOUT3,SPACE=(23476,(30,30))
//SYSUT3 DD UNIT=SYSOUT3,SPACE=(23476,(30,30))
//SYSUT4 DD UNIT=SYSOUT3,SPACE=(23476,(30,30))
//SYSUT5 DD UNIT=SYSOUT3,SPACE=(23476,(30,30))
//SYSUT6 DD UNIT=SYSOUT3,SPACE=(23476,(30,30))
//SYSUT7 DD UNIT=SYSOUT3,SPACE=(23476,(30,30))
//*----------------------------------------------------------------
//* LINKEDIT
//*----------------------------------------------------------------
//LINKEDIT EXEC PGM=IEWL,
// PARM=('LIST,XREF,LET,MAP'),
// COND=(4,LT)
//SYSLIB DD DISP=SHR,DSN=HLQ.TEST.ECOBOL.LOD
// DD DISP=SHR,DSN=HLQ.MNM.CMN.PACKNO.LOD
// DD DISP=SHR,DSN=HLQ.DB2.SDSNLOAD
// DD DISP=SHR,DSN=SYS1.LE370.SCEELKED
// DD DISP=SHR,DSN=ADXXA6.DB2.SDSNEXIT
// DD DISP=SHR,DSN=ADXXA6.DB2.SDSNLOAD
// DD DISP=SHR,DSN=SYS1.EXTS.LINKLIST
// DD DISP=SHR,DSN=HLQ.LINK.SKELETON.ALIAS.CSECT
// DD DISP=SHR,DSN=HLQ.CMN.DB2.SDSNLOD
// DD DISP=SHR,DSN=SYS5.ICD.DG.V231.SPLOAD
// DD DISP=SHR,DSN=SYS1.SEZATCP
// DD DISP=SHR,DSN=SYS5.MDWARE.V23.SPOBJ
// DD DISP=SHR,DSN=SYS1.SISPLOAD
// DD DISP=SHR,DSN=SYS1.SADMMOD
//SYSLMOD DD DSN=HLQ.CMN.LOADLIB(UTP51001),DISP=SHR
//SYSUT1 DD UNIT=VIO,DCB=BLKSIZE=1024,SPACE=(1024,(200,20))
//SYSPRINT DD SYSOUT=*
//SYSLIN DD DSN=&&OBJ,DISP=(OLD,DELETE)
//LKED.SYSIN DD *
INCLUDE SYSLIB(DSNRLI,DSNTIAR)
|
Stored Procedure:
| Code: |
//* DB2 PRECOMPILER
//************************************************************
//DSNHPC EXEC PGM=DSNHPC,
// PARM='APOST,ATTACH(RRSAF),SOURCE,LEVEL(A123),HOST(IBMCOB)'
//DBRMLIB DD DSN=HLQ.MNM.CMN.PACKNO.DBRMLIB(UTP51001),DISP=SHR
//STEPLIB DD DSN=HLQ.DB2.SDSNLOAD,DISP=SHR
//SYSCIN DD DSN=&&DSNHPC,DISP=(MOD,PASS),UNIT=DASD,
// SPACE=(800,(500,500))
//SYSLIB DD DSN=HLQ.MNM.CMN.PACKNO.DCL, DISP=SHR
// DD DSN=HLQ.MNM.CMN.PACKNO.DCL,DISP=SHR
// DD DSN=SYS5.TCR.CICS.COPYLIB,DISP=SHR
//SYSPRINT DD SYSOUT=*
//SYSTERM DD SYSOUT=*
//SYSUDUMP DD SYSOUT=*
//SYSUT1 DD SPACE=(800,(500,500),,,ROUND), UNIT=DASD
//SYSUT2 DD SPACE=(800,(500,500),,,ROUND), UNIT=DASD
//SYSIN DD DSN=HLQ.MNM.CMN.PACKNO.WLS(UTP51001),DISP=SHR
//*
//*----------------------------------------------------------
//* COBOLII COMPILER
//*----------------------------------------------------------
//COMPILE EXEC PGM=IGYCRCTL,COND=(4,LT),
// PARM=('NODBCS,APOST,TRUNC(BIN),NOFLAGSAA,NODYNAM')
//STEPLIB DD DISP=SHR,DSN=SYS1.ECOBOL.SIGYCOMP
//SYSLIB DD DSN=HLQ.MNM.CMN.PACKNO.DCL,DISP=SHR
// DD DSN=HLQ.MNM.CMN.PACKNO.DCL,DISP=SHR
// DD DSN=HLQ.MNM.CMN.PACKNO.CPY,DISP=SHR
// DD DSN=SYS5.TCR.CICS.COPYLIB,DISP=SHR
//SYSIN DD DSN=&&DSNHPC,DISP=(OLD,DELETE)
//SYSLIN DD DSN=&&OBJ,UNIT=VIO,
// DCB=(LRECL=80,BLKSIZE=80,RECFM=F),
// SPACE=(23440,(10,5),RLSE),DISP=(NEW,PASS)
//SYSPRINT DD SYSOUT=*
//SYSUT1 DD UNIT=SYSOUT3,SPACE=(23476,(30,30))
//SYSUT2 DD UNIT=SYSOUT3,SPACE=(23476,(30,30))
//SYSUT3 DD UNIT=SYSOUT3,SPACE=(23476,(30,30))
//SYSUT4 DD UNIT=SYSOUT3,SPACE=(23476,(30,30))
//SYSUT5 DD UNIT=SYSOUT3,SPACE=(23476,(30,30))
//SYSUT6 DD UNIT=SYSOUT3,SPACE=(23476,(30,30))
//SYSUT7 DD UNIT=SYSOUT3,SPACE=(23476,(30,30))
//************************************************************
//* LINKEDIT IF THE PRECOMPILE AND COMPILE *
//* RETURN CODES ARE 4 OR LESS. *
//********************************************************************
//LKED EXEC PGM=IEWL,PARM='MAP',
// COND=(4,LT)
//SYSLIB DD DISP=SHR,DSN=HLQ.TEST.ECOBOL.LOD
// DD DISP=SHR,DSN=HLQ.MNM.CMN.PACKNO.WLD
// DD DISP=SHR,DSN=HLQ.DB2.SDSNLOAD
// DD DISP=SHR,DSN=SYS1.LE370.SCEELKED
// DD DISP=SHR,DSN=ADXXA6.DB2.SDSNEXIT
// DD DISP=SHR,DSN=ADXXA6.DB2.SDSNLOAD
// DD DISP=SHR,DSN=SYS1.EXTS.LINKLIST
// DD DISP=SHR,DSN=HLQ.LINK.SKELETON.ALIAS.CSECT
// DD DISP=SHR,DSN=HLQ.CMN.DB2.SDSNLOD
// DD DISP=SHR,DSN=SYS5.ICD.DG.V231.SPLOAD
// DD DISP=SHR,DSN=SYS1.SEZATCP
// DD DISP=SHR,DSN=SYS5.MDWARE.V23.SPOBJ
// DD DISP=SHR,DSN=SYS1.SISPLOAD
// DD DISP=SHR,DSN=SYS1.SADMMOD
//SYSLMOD DD DSN=HLQ.MNM.CMN.PACKNO.LOD(UTP51001),DISP=SHR
//SYSUT1 DD UNIT=VIO,DCB=BLKSIZE=1024,SPACE=(1024,(200,20))
//SYSPRINT DD SYSOUT=*
//SYSLIN DD DSN=&&OBJ,DISP=(OLD,DELETE)
//LKED.SYSIN DD *
INCLUDE SYSLIB(DSNRLI,DSNTIAR)
|
|
|
| Back to top |
|
 |
jaspal
New User
Joined: 22 May 2007 Posts: 68 Location: mumbai
|
|
|
|
Hi Techies,
I think Rahuindo has coded a stored procedure and would retrieve result from it after firing from front web based application and is testing SP through a cobol DB2 component.
Fot this you require below :
1). Schema
2). SP - compile with WLM attach = 'Y; option
3). if you are retrieving multiple result set then declare GTT table in the SP populate it
4). declare the cursor - consider A
5). At last open the cursor A and go back and end the SP.
Now coming to calling component that will call the SP , i have attached program that would help you..
1). schema
2). calling DB2 component
3). SP
THANKS,
JASPAL |
|
| Back to top |
|
 |
Raghu navaikulam
Active User
Joined: 27 Sep 2008 Posts: 194 Location: chennai
|
|
|
|
Hi rahuindo
I suggest a modification in the LINKEDIT step in the Client Program JCL.
| Quote: |
//LKED.SYSIN DD *
INCLUDE SYSLIB(DSNRLI,DSNTIAR) |
Change it into
| Code: |
//LKED.SYSIN DD *
INCLUDE SYSLIB(DSNELI,DSNTIAR) |
Hope this will help you.
Post the response.
Regards
Raghu |
|
| Back to top |
|
 |
dbzTHEdinosauer
Global Moderator

Joined: 20 Oct 2006 Posts: 6965 Location: porcelain throne
|
|
|
|
Raghu,
until rahuindo changes his attach statement for the pre-compile from (ATTACH(RRSAF)) to (ATTACH(TSO)),
I don't think the proposed changes by you will have any effect.
Also, rahuindo has not responded as to why he has the attach to RRSAF in the first place. |
|
| Back to top |
|
 |
Raghu navaikulam
Active User
Joined: 27 Sep 2008 Posts: 194 Location: chennai
|
|
|
|
Hi Dick
I noticed the ATTACH statement in the beginning of the pre-compile. I came to a conclusion that the LINKEDIT step the last one, so that may not be a problem. If it is not working, the ATTACH(RRSAF) for the client program's JCL has to be modified. Let him respond....
Thanks for your response.
Regards
Raghu |
|
| Back to top |
|
 |
rahuindo
New User
Joined: 09 Apr 2008 Posts: 83 Location: Chennai
|
|
|
|
Hi Dino,
I was not attaching RRSAF until i encountered this Error. As the explanation for the -981 suggested that the RRSAF connection may not be there. Hence i compiled the program and stored proc with ATTACH(RRSAF).
Raghu,
I link-edited the program as suggested by you.
| Code: |
//LKED.SYSIN DD *
INCLUDE SYSLIB(DSNELI,DSNTIAR)
|
but i encounter the SQLCODE -927.
Thanks for the response. |
|
| Back to top |
|
 |
Raghu navaikulam
Active User
Joined: 27 Sep 2008 Posts: 194 Location: chennai
|
|
|
|
Hi rahuindo
I think you have modified both the JCLs. Do not modify both. As I posted earlier, you just modify the JCL for Client program only. If you modify the SERVER program(STP) with DSNELI, you will get -927 sqlcode.
So make sure that you didn't modified both the JCLs.
For Server program -- use DSNRLI
For Client program -- use DSNELI.
For client program, you can avoid the use of ATTACH(RRSAF).
Post your resposnse.
Regards
Raghu |
|
| Back to top |
|
 |
rahuindo
New User
Joined: 09 Apr 2008 Posts: 83 Location: Chennai
|
|
|
|
Hi Raghu,
I am now trying to invoke the SP thru DB2I and on executing the SP, i constantly encounter the SQLCODE -981. I figured out to some extent the DSNRLI is not getting linked to the SP even though i have coded "INCLUDE SYSLIB(DSNRLI)" in the link-edit step. I can see that execution of each SQL Statements calls are made to DSNHLI instead of DSNRLI. I suspect this may be the reason for the SQLCODE -981.
Can anyone suggest that how can i modify my SP so that the calls are made to DSNRLI and not DSNHLI? |
|
| Back to top |
|
 |
takamal
New User
Joined: 10 Apr 2009 Posts: 4 Location: chennai
|
|
|
|
Hi '
please send application program using stored procedure.i want know how its work.with compiler change.
kamal
send my personal mail-id kamal.removed |
|
| Back to top |
|
 |
|
|
 |
All times are GMT + 6 Hours |
|