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 

Error in VAR-LIST Dynamic SELECT statement

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


Joined: 18 Mar 2008
Posts: 24
Topics: 6

PostPosted: Thu Mar 05, 2009 6:18 am    Post subject: Error in VAR-LIST Dynamic SELECT statement Reply with quote

Hello,

I'm getting an Abend while trying to perform a FETCH statement in a var-list Dynamic Select operation. I tryed the following:
Code:

WORKING-STORAGE     SECTION.
01 DSTRING.                                                     
   05 DSTRING-LEN PIC S9(04) COMP.                               
   05 DSTRING-TXT PIC X(500).

01 WS-NUMERO-RAPPORTO PIC X(12) VALUE SPACES.

PROCEDURE DIVISION.
MOVE +1            TO DSTRING-LEN                           
STRING 'SELECT *'                                           
       ' FROM AGABPL.TBAGTRFR WHERE NUMERO_RAPPORTO = ?'     
       DELIMITED BY SIZE                                     
       INTO DSTRING-TXT                                     
       WITH POINTER DSTRING-LEN                             
END-STRING                                                   
COMPUTE DSTRING-LEN = DSTRING-LEN - 1

EXEC SQL PREPARE S2                                         
     FROM :DSTRING                                           
END-EXEC.

MOVE 40 TO SQLN                                             
                                                                   
EXEC SQL DESCRIBE S2 INTO :SQLDA USING NAMES                 
END-EXEC.

EXEC SQL DECLARE C2 CURSOR FOR S2                           
END-EXEC.

MOVE '000095132423'              TO WS-NUMERO-RAPPORTO                                                                       
EXEC SQL OPEN C2                                             
     USING :WS-NUMERO-RAPPORTO                               
END-EXEC.

EXEC SQL FETCH C2 USING DESCRIPTOR :SQLDA                   
END-EXEC

After the FETCH statement I'm getting:
Code:

CEE3250C The system or user abend S04E  R=00E7000C was issued. From compile unit AGPEK030 at entry point AGPEK030 at statement 2936 at compile unit offset +0000589C at  entry offset +0000589C at address 1BA8F46C.


Can anyone help me with this problem ? Thanks a lot in advance.
Back to top
View user's profile Send private message
jsharon1248
Intermediate


Joined: 08 Aug 2007
Posts: 291
Topics: 2
Location: Chicago

PostPosted: Thu Mar 05, 2009 9:48 am    Post subject: Reply with quote

Varying list dynamic SQL is extremely difficult. I hope you've done your homework and you really need to do this.

The DECLARE is a not an executable statement, but it must precede all statements that explicitely refer to the cursor by name. You reference the cursor name in your PREPARE, but coded the PREPARE and the DESCRIBE before the DECLARE. Most shops want the DECLAREs in WS. Some put them in the Procedure Division. I think it makes more sense to put them in WS because they are not executable. Just make sure that the DECLARE is physically before the PREPARE. You should also issue the PREPARE with the INTO clause. That will eliminate the need for the DESCRIBE. PREPARE/INTO is equivalent to PREPARE followed by DECSRIBE. Either is fine, but doing it in one statement seems to make more sense to me. After you issue the PREPARE/INTO, that's where the fun starts. You need to dig through the SQLDA, and allocate storage for each column specified in the SELECT list. This is very complicated because you need to be able to reference each area of storage with the correct COBOL variable type. I don't like the IBM example for allocating storage at all. I defined different COBOL variables in the LS, and then used the CEEGTST LE service to allocate the storage for them. A little tricky, but I think it's a better solution than the sample. Your OPEN is incomplete because you defined the cursor with parameter markers, but did not code the USING clause. You need to populate variables with the values you want used by the OPEN, and then code the OPEN with the USING clause referencing those variables.

I'll stress this again. This should only be done if there are really no other options. This is very powerful, but it takes much longer to develop the programs especially if it's your first time.
Back to top
View user's profile Send private message
dragone_007
Beginner


Joined: 18 Mar 2008
Posts: 24
Topics: 6

PostPosted: Thu Mar 05, 2009 10:16 am    Post subject: Reply with quote

Thaks a lot for your time jsharon1248,

I followed your advice to DECLARE first and to PREPARE and DESCRIBE after and this gave no error in compilation but, I'm still having the same abend:
CEE3250C The system or user abend S04E R=00E7000C was issued. From compile unit AGPEK030 at entry point AGPEK030 at statement 2936 at compile unit offset +0000589C at entry offset +0000589C at address 1BA8F46C.

I also digged into SQLDA area and found all information regarding the Column NAMES and TYPE's of each like this:

SQLDAID = SQLDA
SQLDABC = 0000001776
CAMPI IN OUTPUT (SQLN) = 00040
CAMPI IN INPUT (SQLD) = 00040
SQLTYPE = 00452
SQLLEN = 00012
SQLNAMEL = 00015
SQLNAMEC = NUMERO_RAPPORTO
SQLDATA = 0000001144
SQLIND = 0000000000
SQLLONGLEN = 0029622284
SQLDATALEN = 0000000000
SQLDATATYPE-NAMEL = 00015
SQLDATATYPE-NAMEC = NUMERO_RAPPORTO

and so on for my 40 COLUMNS

but how can I pass (and where) the size of each column again to the SQLDA area ? What is the CEEGTST LE service that you mentioned ? How can I access to that ? Thanks a lot again for your effort
Back to top
View user's profile Send private message
jsharon1248
Intermediate


Joined: 08 Aug 2007
Posts: 291
Topics: 2
Location: Chicago

PostPosted: Thu Mar 05, 2009 12:42 pm    Post subject: Reply with quote

Here is a link that will direct you to a manual for LE. Scroll down to Language Environment, and open the LE Programming Reference Manual. Chapter 2 provides details about all the Callable Services, including CEEGTST (section 2.2.5.45).
http://publibz.boulder.ibm.com/bookmgr_OS390/libraryserver/zosv1r9/

The DECLARE, PREPARE/INTO, and OPEN/USING are straightforward. The FETCH is the statement where things get tricky. I believe that you're having problems because you're issuing your FETCH before you acquire storage for the columns in the SELECT list. After the PREPARE/INTO but before the first FETCH, you need to allocate storage to store the values returned by the FETCH for each column in the SELECT list. You need to store the address for each host variable in the SQLDA. COBOL is not at all accomodating with this type of work. What I do, is define generic variables in the Linkage Section, and then SET POINTERs to access the data returned. To start, here's how I define the most common generic variables in LS.

Code:
 LINKAGE SECTION.                             
 01  LS-CHAR-VAL               PIC  X(256).   
                                             
 01  LS-INTEGER-VAL            PIC S9(09) COMP.
                                               
 01  LS-SMALLINT-VAL           PIC S9(04) COMP.
                                             
 01  LS-TIMESTAMP-VAL          PIC  X(26).   
                                             
 01  LS-DATE-VAL               PIC  X(10).   
                                             
 01  LS-TIME-VAL               PIC  X(08).     
                                               
 01  LS-NULL-IND               PIC S9(04) COMP.
                                               
 01  LS-VARCHAR-VAL.                           
     49  LS-VARCHAR-VAL-LEN    PIC S9(04) COMP.
     49  LS-VARCHAR-VAL-TEXT   PIC  X(4000). 


Let's work with the first column in your SQLDA. The type is 452, which is CHAR, not nullable. The length is 12. Issue a CALL to CEEGTST to acquire 12 bytes of storage. CEEGTST will return an address. SET SQLDATA(1) to the address returned by CEEGTST. Now, when you issue the FETCH, DB2 will return the value of the first column in your SELECT list into the storage location starting at the address you stored in SQLDATA(1). When you want to retrieve it, you code the following:
SET ADDRESS OF LS-CHAR-VAL TO SQLDATA(1).

Your program will have addressability to the entire 256 bytes of LS-CHAR-VAL, but only the 1st 12 bytes will store the value for your column. You'll want to use reference modification or a STRING to only work with the first 12 bytes. The length is stored in SQLLEN(1).

Once you get this working, you'll do the same thing for each column in the SQLDA. You'll also need to obtain storage and establish addressability for NULL indicators when necessary.
Back to top
View user's profile Send private message
dragone_007
Beginner


Joined: 18 Mar 2008
Posts: 24
Topics: 6

PostPosted: Fri Mar 06, 2009 10:26 am    Post subject: Reply with quote

Hi jsharon1248,

Thanks a lot for your time and example provided. I tryed to apply the CALL to the CEEGTST program to allocate the storage I need by gives me an error in compilation saying that the COPY CEEIGZCT has not been found and so the RC=12. By the way I did an implementation following the example shawn in "Squeezing the Most Out of Dynamic SQL with DB2 for z/OS and OS/390" (manual) to what I wrote yesterday like this:
Code:

*----------------------------------------------------------------*
 WORKING-STORAGE     SECTION.
*----------------------------------------------------------------*
 01 OUTAREA.                                                     
    05 OUTAREA-LEN           PIC S9(09) COMP.                     
    05 OUTAREA-CHAR OCCURS 1000 PIC X.                           
 01 OUTAREA-INIZIO           PIC S9(09) COMP.                     
 01 OUTAREA-FINE             PIC S9(09) COMP.
 
 01 OUTNULLS.                                                     
    05 OUTIND                   PIC S9(04) COMP OCCURS 750.       
 01 OUTPTR POINTER.                                               
 01 OUTPTR-NUM REDEFINES OUTPTR PIC S9(09) COMP.                 
 01 NULLPTR POINTER.                                             
 01 NULLPTR-NUM REDEFINES NULLPTR PIC S9(09) COMP.               
                                                                   
 01 VARNUM               PIC S9(04) COMP VALUE +0.               
 01 TIPO-CAMPO           PIC S9(04) COMP.                         
 01 VARCHAR-TYPE         PIC S9(04) COMP VALUE +448.             
 01 CHAR-TYPE            PIC S9(04) COMP VALUE +452.             
 01 LONG-VARCHAR-TYPE    PIC S9(04) COMP VALUE +456.             
 01 VARGRAPHIC-TYPE      PIC S9(04) COMP VALUE +464.             
 01 GRAPHIC-TYPE         PIC S9(04) COMP VALUE +468.             
 01 LONG-VARGRAPHIC-TYPE PIC S9(04) COMP VALUE +472.             
 01 FLOAT-TYPE           PIC S9(04) COMP VALUE +480.             
 01 DECIMAL-TYPE         PIC S9(04) COMP VALUE +484.             
 01 INT-TYPE             PIC S9(04) COMP VALUE +496.             
 01 SMALL-INT-TYPE       PIC S9(04) COMP VALUE +500.             
 01 DATE-TYPE            PIC S9(04) COMP VALUE +384.
 01 TIME-TYPE            PIC S9(04) COMP VALUE +388.             
 01 TIMESTAMP-TYPE       PIC S9(04) COMP VALUE +392.             
 01 DUMMY                PIC S9(04) COMP.                         
 01 COLUMN-IND           PIC S9(04) COMP.                         
 01 COLUMN-LEN           PIC S9(04) BINARY.                       
 01 COLUMN-PREC          PIC S9(04) COMP.                         
 01 COLUMN-SCALE         PIC S9(04) COMP.
..
..
..
..
*----------------------------------------------------------------*
 PROCEDURE DIVISION.                                             
*----------------------------------------------------------------*
..
..
..
*----------------------------------------------------------------*
 CALCOLA-DYNCURSOR-VAR.                                           
*----------------------------------------------------------------*
  MOVE '000095132423'              TO WS-NUMERO-RAPPORTO       
                                                                   
 EXEC SQL OPEN C2                                             
       USING :WS-NUMERO-RAPPORTO                               
 END-EXEC
       
 MOVE OUTPTR-NUM                TO OUTAREA-CHAR(1)                   
 MOVE NULLPTR-NUM               TO OUTIND(1)                   
                                                                   
 MOVE 1                         TO VARNUM                       
 PERFORM                                                     
   UNTIL VARNUM > SQLD                                       
         PERFORM 2530-SET-EACH-COL  THRU 2530-EX             
         PERFORM FETCH-DYNCURSOR-VAR                         
            THRU FETCH-VAR-EX                                 
         ADD 1                  TO VARNUM                       
 END-PERFORM.
                                               
CALCOLA-DYN-VAR-EX.     EXIT.                                   
*----------------------------------------------------------------*
 2530-SET-EACH-COL.                                               
*----------------------------------------------------------------*
 SET SQLDATA(VARNUM) TO OUTPTR                               
 SET SQLIND(VARNUM)  TO NULLPTR                               
 MOVE SQLLEN(VARNUM) TO COLUMN-LEN                           
 DIVIDE SQLTYPE(VARNUM) BY 2 GIVING DUMMY                     
        REMAINDER COLUMN-IND                                 
                                                                 
 MOVE SQLTYPE(VARNUM) TO TIPO-CAMPO                           
 SUBTRACT COLUMN-IND FROM TIPO-CAMPO                         
                                                                 
 EVALUATE TIPO-CAMPO                                         
 WHEN CHAR-TYPE   
      DISPLAY '     TIPO COLONNA : ' CHAR-TYPE ' = CHAR' 
 WHEN DATE-TYPE                                           
      DISPLAY '     TIPO COLONNA : ' DATE-TYPE ' = DATE' 
 WHEN TIME-TYPE                                           
      DISPLAY '     TIPO COLONNA : ' TIME-TYPE ' = TIME' 
 WHEN TIMESTAMP-TYPE                                     
      DISPLAY '     TIPO COLONNA : ' TIMESTAMP-TYPE       
              ' = TIMESTAMP'                             
 WHEN FLOAT-TYPE                                         
      DISPLAY '     TIPO COLONNA : ' FLOAT-TYPE           
              ' = FLOATING POINT'                         
      CONTINUE                                           
 WHEN VARCHAR-TYPE                                       
      DISPLAY '     TIPO COLONNA : ' VARCHAR-TYPE         
              ' = VARCHAR'                               
      ADD 2 TO COLUMN-LEN                                 
 WHEN LONG-VARCHAR-TYPE                                   
      DISPLAY '     TIPO CAMPO : ' LONG-VARCHAR-TYPE     
      ' = LONG VARCHAR'
      ADD 2 TO COLUMN-LEN                                 
 WHEN GRAPHIC-TYPE                                       
      DISPLAY '     TIPO CAMPO : ' GRAPHIC-TYPE           
            ' = GRAPHIC'                               
      MULTIPLY COLUMN-LEN BY 2 GIVING COLUMN-LEN         
 WHEN VARGRAPHIC-TYPE                                     
      DISPLAY '     TIPO CAMPO : ' VARGRAPHIC-TYPE       
              ' = VARGRAPHIC'                             
      MULTIPLY COLUMN-LEN BY 2 GIVING COLUMN-LEN         
      ADD 2                  TO COLUMN-LEN               
 WHEN LONG-VARGRAPHIC-TYPE                               
      DISPLAY '     TIPO CAMPO : ' LONG-VARGRAPHIC-TYPE   
              ' = LONG VARGRAPHIC'                       
      MULTIPLY COLUMN-LEN BY 2 GIVING COLUMN-LEN         
      ADD 2                  TO COLUMN-LEN               
 WHEN SMALL-INT-TYPE                                     
      DISPLAY '     TIPO CAMPO : ' SMALL-INT-TYPE         
              ' = SMALL INTEGER'                         
      MOVE 2                  TO COLUMN-LEN               
 WHEN INT-TYPE   
      DISPLAY '     TIPO CAMPO : ' INT-TYPE               
              ' = INTEGER'                               
      MOVE 4                  TO COLUMN-LEN               
 WHEN DECIMAL-TYPE                                       
      DISPLAY '     TIPO CAMPO : ' DECIMAL-TYPE           
              ' = DECIMAL'                               
      PERFORM 2532-DEC-LENGTH  THRU 2532-EX               
 WHEN OTHER                                               
      DISPLAY ' --> TIPO CAMPO NON CONVENZIONALE : '     
              TIPO-CAMPO                           
 END-EVALUATE                                                 
                                                                   
 ADD COLUMN-LEN              TO OUTPTR-NUM                   
 ADD 1 TO NULLPTR-NUM.                                       
 IF OUTAREA-FINE = ZERO                                       
    MOVE 1                   TO OUTAREA-INIZIO               
    MOVE OUTPTR-NUM          TO OUTAREA-FINE                 
 ELSE           
    COMPUTE OUTAREA-INIZIO = OUTAREA-FINE + 1                 
    COMPUTE OUTAREA-FINE   = OUTAREA-INIZIO + COLUMN-LEN     
 END-IF                                                       
                                                                   
 DISPLAY '     NAME-LENGTH    = ' SQLNAMEL(VARNUM)           
 DISPLAY '     NAME-FIELD     = ' SQLNAMEC(VARNUM)           
 DISPLAY '     COLUMN-LEN     = ' COLUMN-LEN.                 
 DISPLAY '     OUTPTR-NUM     = ' OUTPTR-NUM.                 
 DISPLAY '     NULLPTR-NUM    = ' NULLPTR-NUM.               
 DISPLAY '     OUTAREA-INIZIO = ' OUTAREA-INIZIO.             
 DISPLAY '     OUTAREA-FINE   = ' OUTAREA-FINE.               
                                                                                                                                       
 2530-EX.                EXIT.   
*----------------------------------------------------------------*
 2532-DEC-LENGTH.                                                 
*----------------------------------------------------------------*
  DIVIDE COLUMN-LEN BY 256 GIVING COLUMN-PREC                 
        REMAINDER COLUMN-SCALE                               
                                                                 
  MOVE COLUMN-PREC TO COLUMN-LEN                               
  ADD 1            TO COLUMN-LEN                               
  DIVIDE COLUMN-LEN BY 2 GIVING COLUMN-LEN.                   
  DISPLAY '     COLUMN-SCALE = ' COLUMN-SCALE                 
  DISPLAY '     COLUMN-PREC  = ' COLUMN-PREC                   
  DISPLAY '     COLUMN-LEN   = ' COLUMN-LEN.                   
                                                                 
 2532-EX.                EXIT.       


So I'm intercepting correctly (seems to me) all values to FETCH (including right positions, types, length) but I'm getting the following SQLCODE -804 error :

Execution SYSOUT:
--> SONO IN : CALCOLA-DYNCURSOR-VAR                                           
--> SONO IN : OPEN-DYNCURSOR-VAR                                               
     SQLCODE : +000000000                                                       
--> SONO IN : 2530-SET-EACH-COL                                               
     TIPO COLONNA : 00452 = CHAR                                               
     NAME-LENGTH    = 00015                                                     
     NAME-FIELD     = NUMERO_RAPPORTO                                           
     COLUMN-LEN     = 00012                                                     
     OUTPTR-NUM     = 0000000012                                               
     NULLPTR-NUM    = 0000000001                                               
     OUTAREA-INIZIO = 0000000001                                               
     OUTAREA-FINE   = 0000000012                                               
--> SONO IN : FETCH-DYNCURSOR-VAR                                             
     SQLCODE : -000000804   
--> SONO IN : 2530-SET-EACH-COL                                               
     TIPO COLONNA : 00452 = CHAR                                               
     NAME-LENGTH    = 00020                                                     
     NAME-FIELD     = NUMERO_FINANZIAMENTO                                     
     COLUMN-LEN     = 00006                                                     
     OUTPTR-NUM     = 0000000018                                               
     NULLPTR-NUM    = 0000000002                                               
     OUTAREA-INIZIO = 0000000013                                               
     OUTAREA-FINE   = 0000000019                                               
 --> SONO IN : FETCH-DYNCURSOR-VAR                                             
     SQLCODE : -000000804       
 ..
 ..
 ..

and so on for all other columns to retrieve. Do you think SQLCODE= -804 is for any reason that I could handle so far ? Thanks again for your effort.

Greetings
Back to top
View user's profile Send private message
jsharon1248
Intermediate


Joined: 08 Aug 2007
Posts: 291
Topics: 2
Location: Chicago

PostPosted: Fri Mar 06, 2009 2:42 pm    Post subject: Reply with quote

The CEEIGZCT copybook is in an installation specific copylib. You'd have to find out the copylib DSN at your site to use it. I hard coded my own version.
Code:
01  CEEGTST-PARM-AREA.
    05  CEEGTST-HEAP-ID             PIC S9(09) COMP VALUE +0.
    05  CEEGTST-BYTES-QTY           PIC S9(09) COMP.
    05  CEEGTST-STORAGE-ADDR            USAGE IS POINTER.


Do you have the link to the manual you mentioned? This sample looks different from the one I've seen in the past. It's likely better than what I saw years ago.

The -804 SQLCODE has several different causes. You'll need to look up the -804 and find the specific cause based on the reason code displayed in the error message. If you're not already doing it, you should pass the SQLCA to DSNTIAR and let DSNTIAR format the error messages for you.
Back to top
View user's profile Send private message
dragone_007
Beginner


Joined: 18 Mar 2008
Posts: 24
Topics: 6

PostPosted: Mon Mar 09, 2009 4:59 am    Post subject: Reply with quote

Hi jsharon1248,

If you want I can send you the latest manual's versions regarding Dynamic SQL. Unfortunately I don't have any link to post. By the way are IBM Redbook series about DB2 version 8. Tell me where do I have to send those to you. Thanks again by the way.
Back to top
View user's profile Send private message
dragone_007
Beginner


Joined: 18 Mar 2008
Posts: 24
Topics: 6

PostPosted: Mon Mar 09, 2009 6:36 am    Post subject: Reply with quote

Sorry jsharon1248,

I forgot to post the results of GET DIAGNOSTICS :
Code:

--> SONO IN : FETCH-DYNCURSOR-VAR                                             
      GET DIAGNOSTICS                                                           
      ------------------------------------------------                         
      ROW_COUNT                  : +000000000000000000                         
      NUMBER                     : +000000000000000001                         
                                                                               
      GET DIAGNOSTICS CONDITION 1                                               
      ------------------------------------------------                         
      SQLCODE                       : -000000804                                   
      SQLSTATE                      : 07002                                       
      DB2_ERROR_CODE1            : -000000204                                   
      DB2_ERROR_CODE2            : +000000000                                   
      DB2_ERROR_CODE3            : +000000000                                   
      DB2_ERROR_CODE4            : -000000001                                   
      DB2_REASON_CODE            : +000000007                                   
      DB2_ROW_NUMBER             : +000000000000000000                         
      CONDITION_NUMBER           : +000000000000000001                         
      DB2_MODULE_DETECTING_ERROR : DSNXECP                                     
      CATALOG_NAME               :                                             

      MESSAGE_TEXT               : AN ERROR WAS FOUND IN THE APPLICATION   PROGRAM INPUT PARAMETERS FOR THE SQL STATEMENT, REASON 07

and 'CALL'-ing to DSNTIAR module:

  --> FETCH DYNCURSOR VAR TBAGTRFR K.O                                         
  DSNT400I SQLCODE = 000,  SUCCESSFUL EXECUTION         


The strange thing is that when 'GET DIAGNOSTICS' statement is intercepting correctly the error, the DSNTIAR module is not doing the same. Thank you again
Back to top
View user's profile Send private message
jsharon1248
Intermediate


Joined: 08 Aug 2007
Posts: 291
Topics: 2
Location: Chicago

PostPosted: Mon Mar 09, 2009 12:22 pm    Post subject: Reply with quote

I haven't use the GET DIAGNOSTICs. But if I'm interpreting it's output correctly, the problem is that you haven't supplied the correct SQLDA length. Have you computed and set the length of the SQLDA before the FETCH? I used the following. You need to make sure SQLN is > 0.

Code:
COMPUTE SQLDABC = (SQLN * LENGTH OF SQLVAR) 
                  + LENGTH OF SQLDAID       
                  + LENGTH OF SQLDABC       
                  + LENGTH OF SQLN           
                  + LENGTH OF SQLD   


You need to CALL DSNTIAR following the completion of an SQL statement. Here's the WS fields and CALL that I use:

Code:
01 ERROR-MESSAGE.                                   
   05 ERROR-LEN         PIC S9(4) COMP VALUE +800. 
   05 ERROR-TEXT        PIC X(80) OCCURS 10 TIMES   
                        INDEXED BY ERROR-INDEX.     
                                                   
01 ERROR-TEXT-LEN       PIC S9(8) COMP VALUE +80.   

CALL 'DSNTIAR' USING SQLCA ERROR-MESSAGE ERROR-TEXT-LEN   
                                                         
IF RETURN-CODE <= 4                                       
   PERFORM VARYING ERROR-INDEX FROM +1 BY +1             
           UNTIL  ERROR-INDEX > +8                       
           IF  ERROR-TEXT (ERROR-INDEX) > SPACES         
               DISPLAY ERROR-TEXT (ERROR-INDEX)           
           END-IF                                         
   END-PERFORM                                           
   IF RETURN-CODE = 4                                     
       DISPLAY 'SOME DSNTIAR DATA WAS TRUNCATED'         
   END-IF                                                 
ELSE                                                     
   <error handling for unrecoverable errors>
END-IF
Back to top
View user's profile Send private message
dragone_007
Beginner


Joined: 18 Mar 2008
Posts: 24
Topics: 6

PostPosted: Tue Mar 10, 2009 7:19 am    Post subject: Reply with quote

Hi jsharon1248,

I followed your advice in calculating the SQLDA area for the return values of my select so I defined another area in WORKING-STORAGE similar to SQLDA like this:
Code:

 01 MY-SQLDA.                                                     
     05 MY-SQLDAID PIC X(8).                                       
     05 MY-SQLDABC PIC S9(9) BINARY.                               
     05 MY-SQLN PIC S9(4) BINARY.                                 
     05 MY-SQLD PIC S9(4) BINARY.                                 
     05 MY-SQLVAR OCCURS 0 TO 750 DEPENDING ON MY-SQLN.           
        10 MY-SQLVAR1.                                             
           15 MY-SQLTYPE PIC S9(4) BINARY.                         
           15 MY-SQLLEN PIC S9(4) BINARY.                         
           15 FILLER  REDEFINES MY-SQLLEN.                         
              20 MY-SQLPRECISION PIC X.                           
              20 MY-SQLSCALE    PIC X.                             
           15 MY-SQLDATA POINTER.                                 
           15 MY-SQLDATA-NUM REDEFINES MY-SQLDATA
                                           PIC S9(09) COMP.
           15 MY-SQLIND POINTER.                                   
           15 MY-SQLIND-NUM REDEFINES MY-SQLIND PIC S9(09) COMP.   
           15 MY-SQLNAME.                                         
              49 MY-SQLNAMEL PIC S9(4) BINARY.                     
              49 MY-SQLNAMEC PIC X(30).                           
        10 MY-SQLVAR2 REDEFINES MY-SQLVAR1.



and I'm getting the right size and same position for Output Fields and values, but I'm still getting an abend in execution at the first FETCH:

Code:

--> SONO IN : OPEN-DYNCURSOR-VAR                                               
     OPEN-DYNCURSOR-VAR TBAGTRFR : +000000000                                   
 --> SONO IN : FETCH-DYNCURSOR-VAR                                             
     DATA AND ARRIVAL POSITION                                                 
     ----------------------------------------------                             
     MY-SQLDAID : SQLDA                                                         
     MY-SQLDABC : 0000001776                                                   
     MY-SQLN    : 00040                                                         
     MY-SQLD    : 00040                                                         
     ----------------------------------------------                             
     MY-SQLTYPE : 00452                                                         
     MY-SQLLEN  : 00012                                                         
     MY-SQLDATA : 0000000012                                                   
     MY-SQLIND  : 0000000001                                                   
     MY-SQLNAMEL: 00015                                                         
     MY-SQLNAMEC: NUMERO_RAPPORTO                                               
     MY-SQLTYPE : 00452                                                         
     MY-SQLLEN  : 00006                                                         
     ...
     ...
     ...
     MY-SQLTYPE : 00452                                                         
     MY-SQLLEN  : 00001                                                         
     MY-SQLDATA : 0000000191                                                   
     MY-SQLIND  : 0000000040                                                   
     MY-SQLNAMEL: 00023                                                         
     MY-SQLNAMEC: FLAG_TIPO_PIANO_ITA_FRA   

CEE3250C The system or user abend S04E  R=00E7000C was issued.
         From compile unit AGPEK030 at entry point AGPEK030 at statement 3724 at compile unit offset +000082BE at entry offset +000082BE at address 1BA91EE6.




Do you think I need something else to get finally my Output ? Thanks o lot
Back to top
View user's profile Send private message
dragone_007
Beginner


Joined: 18 Mar 2008
Posts: 24
Topics: 6

PostPosted: Tue Mar 10, 2009 7:24 am    Post subject: Reply with quote

Sorry I forgot the redefining items of MY-SQLVAR2:
Code:

      10 MY-SQLVAR2 REDEFINES MY-SQLVAR1.                       
           15 MY-SQLVAR2-RESERVED-1 PIC S9(9) BINARY.             
           15 MY-SQLLONGLEN  REDEFINES MY-SQLVAR2-RESERVED-1   
                                 PIC S9(9) BINARY.                 
           15 MY-SQLVAR2-RESERVED-2 PIC S9(9) BINARY.             
           15 MY-SQLDATALEN      POINTER.                         
           15 MY-SQLDATATYPE-NAME.                                 
              20 MY-SQLDATATYPE-NAMEL PIC S9(4) BINARY.           
              20 MY-SQLDATATYPE-NAMEC PIC X(30).
Back to top
View user's profile Send private message
jsharon1248
Intermediate


Joined: 08 Aug 2007
Posts: 291
Topics: 2
Location: Chicago

PostPosted: Thu Mar 12, 2009 10:47 am    Post subject: Reply with quote

I'm confused as to why you defined a separate SQLDA. Just use the original SQLDA to eliminate a source of confustion. The problem is in your setup of the SQLDA prior to the first fetch. You're showing SQLDATA(x) with the value 12. When you execute the FETCH, DB2 is attempting to store the results of that column at address 000012, which is owned by the operating system. SQLDATA(x) needs to be a valid address accessible by your program. You need to store the address returned by CEEGTST into SQLDATA(x). If you're going to use the IBM sample program mechanism, you'll need to bump the address in the POINTER variable manually.

I recommend that you simplify your SQL to return one column. Get that one column working and then add your loop for the other columns later.
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 -> 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