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 

Cursor query not retreiving values

 
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Database
View previous topic :: View next topic  
Author Message
shekar123
Advanced


Joined: 22 Jul 2005
Posts: 528
Topics: 90
Location: Bangalore India

PostPosted: Tue Dec 05, 2006 9:12 am    Post subject: Cursor query not retreiving values Reply with quote

Hi All,

I have a file with records and in each record we are having EMPNO.I am reading from a file record by record and then i am making use of a cursor to retrieve mutiple information which each employee will have.Below are the codes for cursor , and when i check in the DB2 table i have records for each employee number with mutiple rows which meet the cursor but i am unable to get values from the table and i am getting SQLCODE as 100 and the values EMPNO EMPNAME EMPMARKS i get blanks after the fetching.Please help me out where i am going wrong ? The Host variables have been in the way as per the design.

Code:

WORKING STORAGE SECTION
01 INPUT-EMPNO    PIC X(06).
01 WS-LITERALS.
   05 H-EMPNO     PIC X(06).
   05 H-EMPNAME   PIC X(30).
   05 H-EMPMARKS  PIC 9(02).

05 SWITCH-CURSOR            PIC X(01) VALUE SPACE.
   88 MORE-ROWS               VALUE 'Y'.       
   88 NO-MORE-ROWS            VALUE 'N'.       

EXEC SQL DECLARE WS-CSR CURSOR FOR
  SELECT EMPNO, EMPNAME, EMPMARKS
  FROM EMPLOYEE
  WHERE EMPNO = :H-EMPNO
  GROUP BY CLASSNO
  FOR FETCH ONLY
END-EXEC.

COLUMN NAMES

EMPNO
EMPNAME
EMPMARKS



Program code:
Code:

           SET INP-NOT-EOF TO TRUE.                                   
           PERFORM UNTIL INP-EOF                                       
             READ INP-FILE                                             
               AT END                                                   
                  SET INP-EOF TO TRUE                                 
               NOT AT END                                               
                  IF INP-FILE-STATUS IS EQUAL TO '00'                 
                     PERFORM WRITE-OUT-RPT                   
                  ELSE                                                 
                     DISPLAY 'READING FILE INP-FILE;'       
                             'FILE-STATUS = ' INP-FILE-STATUS         
                     PERFORM ABEND-ERROR 
                  END-IF                                               
             END-READ                                                   
           END-PERFORM.                                                 

WRITE-OUT-RPT.
           MOVE INPUT-EMPNO TO H-EMPNO.                     
                                                                       
           EXEC SQL                                                     
                    OPEN WS-CSR                                 
           END-EXEC.                                                   
                                                                       
           IF SQLCODE NOT EQUAL TO 0                                   
             DISPLAY 'OPENING CURSOR WS-CSR SQLCODE = ' SQLCODE
                     PERFORM ABEND-ERROR 
           END-IF.                                                     
                                                                       
           SET MORE-ROWS TO TRUE.                                       
           PERFORM UNTIL NO-MORE-ROWS                                   
                           
              INITIALIZE H-EMPNO                                       
                         H-EMPNAME                                       
                         H-EMPMARKS                                     
                                                                       
              EXEC SQL                                                 
                   FETCH WS-CSR                                 
                   INTO :H-EMPNO, :H-EMPNAME, :H-EMPMARKS                   
              END-EXEC                                                 
                                                                       
              DISPLAY 'SQLCODE = ' SQLCODE   
                           
              EVALUATE SQLCODE                                         
                 WHEN 0                                                 
                      MOVE H-EMPNO           TO WS-EMPNO           
                      MOVE H-EMPNAME         TO WS-EMPNAME           
                      MOVE H-EMPMARKS        TO WS-EMPMARKS
                      WRITE OUTPUT-REC FROM WS-EMP-REC
                 WHEN 100                                               
                      SET NO-MORE-ROWS TO TRUE                         
                 WHEN OTHER                                             
                      DISPLAY 'ERROR FETCHING CURSOR WS-CSR SQLCODE = ' SQLCODE
                      PERFORM ABEND-ERROR
              END-EVALUATE                                             
           END-PERFORM.                                                 
                                                                       
           EXEC SQL                                                     
                    CLOSE WS-CSR                                 
           END-EXEC.

_________________
Shekar
Grow Technically
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


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

PostPosted: Tue Dec 05, 2006 9:25 am    Post subject: Reply with quote

Shekar,

1. What is the column definition of EMPNO in the table? Is it also defined as character(06) or is it defined as smallint/integer.

2. Did you check if the host variable had the empno populated correctly from the file? check with displays.

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


Joined: 22 Jul 2005
Posts: 528
Topics: 90
Location: Bangalore India

PostPosted: Tue Dec 05, 2006 12:22 pm    Post subject: Reply with quote

Kolusu,

Sorry for the delay in replying back to you.

1. What is the column definition of EMPNO in the table? Is it also defined as character(06) or is it defined as smallint/integer.

EMPNO is character only in the table defination CHAR(06)

2. Did you check if the host variable had the empno populated correctly from the file? check with displays.

Yes the value is populating properly from the file when i displayed also it is giving me the EMPNO correctly.

One update is that the cursor shown is wrongly posted by me instead of EMPMARKS it is SUM(EMPMARKS) like below.Please let me know how to proceed ahead to solve the problem as i am unable to figure out where is the mistake.
Code:

EXEC SQL DECLARE WS-CSR CURSOR FOR
  SELECT EMPNO, EMPNAME, SUM(EMPMARKS)
  FROM EMPLOYEE
  WHERE EMPNO = :H-EMPNO
  GROUP BY CLASSNO
  FOR FETCH ONLY
END-EXEC.

Morever i have data in the table as follows:
Code:

EMPNO  EMPNAME            EMPMARKS
-----  -----    ------------------
00001  A                     1.00
00001  A                     2.00
00001  A                     3.00
00001  A                     4.00
00001  A                     5.00

I hope i am clear in conveying the requirement correctly.
_________________
Shekar
Grow Technically
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


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

PostPosted: Tue Dec 05, 2006 12:53 pm    Post subject: Reply with quote

Quote:

SELECT EMPNO, EMPNAME, SUM(EMPMARKS)
FROM EMPLOYEE
WHERE EMPNO = :H-EMPNO
GROUP BY CLASSNO
FOR FETCH ONLY


Shekhar,

Did your pgm even compile with that sql ? You are selecting empno and empname while summing the empmarks with a group by on classno which is invalid in DB2.

You need to have the empno and empname also in the group by clause.

with the sample data you have shown is this what are you expecting from the cursor?

Code:

---------+---------+---------+-----
EMPNO   EMPNAME           EMPMARKS
---------+---------+---------+-----
000001  A                    15.00


if so change your cursor definition to the following sql

Code:

SELECT EMPNO
      ,EMPNAME
      ,SUM(EMPMARKS)
  FROM EMPLOYEE
 WHERE EMPNO = :H-EMPNO
 GROUP BY EMPNO
         ,EMPNAME
   FOR FETCH ONLY


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
Display posts from previous:   
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Database 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