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

SQL CODE 80M error in dynamic SQL


IBM Mainframe Forums -> COBOL Programming
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
rajesh 35

New User


Joined: 21 Sep 2010
Posts: 7
Location: chennai

PostPosted: Fri Jun 17, 2011 4:32 pm
Reply with quote

Hi,

I have gone through previous posts to resolve 80M sqlcode but not able to resolve it.

I have cobol code which prepares a dynamic sql ( select ) and excute it, I'm getting 80M while preparing the statment.

Could you please help where I'm going wrong and how to resolve it.


Spool:

Code:
********************************* TOP OF DATA **********************************
 SELECT ALL_DATE,ALL_BCODE FROM ALL_TABLE WHERE ALL_DATE = '2011-06-16' AND ALL_ISCODE LIKE '%'
 AT PREPARE :00000080M                                                         
******************************** BOTTOM OF DATA ********************************
Code : mentioned code upto prepare statement.

Code:
PROCEDURE DIVISION.                                     
  MAIN-PARA.                                               
     MOVE 'SELECT ALL_DATE,ALL_BCODE FROM ALL_TABLE'     
                              TO WS-LINE1.               
     MOVE " WHERE ALL_DATE = '2011-06-16'"               
                              TO WS-LINE2.           
           
     IF WS-TEXT2 IS EQUAL TO SPACES                       
        MOVE " AND ALL_ISCODE LIKE '%'"  TO WS-LINE3     
     ELSE                                                 
        MOVE " AND ALL_ISCODE = 'ASDFGHJKLOI'" TO WS-LINE3
     END-IF                                               
                                                         
     STRING WS-LINE1 WS-LINE2 WS-LINE3   
                DELIMITED BY '  ' INTO WS-LINE4   
     STRING WS-LINE4 DELIMITED BY SIZE INTO WSTEXT
                                                 
     DISPLAY WSTEXT.                           
                     
     EXEC SQL                                     
         PREPARE STMT FROM :WSTEXT               
     END-EXEC   

     EVALUATE TRUE                       
       WHEN SQLCODE = 0                   
            DISPLAY WSTEXT               
            DISPLAY "PREPARE SUCESSFUL"   
       WHEN OTHER                         
            DISPLAY "AT PREPARE :" SQLCODE
            STOP RUN                     
     END-EVALUATE                                                                           
Back to top
View user's profile Send private message
Bill Woodger

Moderator Emeritus


Joined: 09 Mar 2011
Posts: 7309
Location: Inside the Matrix

PostPosted: Fri Jun 17, 2011 4:53 pm
Reply with quote

What does the -804 mean?

Unrelated, but this

Code:
     STRING WS-LINE4 DELIMITED BY SIZE INTO WSTEXT


can be a plain old MOVE.
Back to top
View user's profile Send private message
rajesh 35

New User


Joined: 21 Sep 2010
Posts: 7
Location: chennai

PostPosted: Fri Jun 17, 2011 5:19 pm
Reply with quote

Hi Bill,

-804: AN ERROR WAS FOUND IN THE APPLICATION PROGRAM
INPUT PARAMETERS FOR THE SQL STATEMENT

I need to check ALL_ISCODE value in where clause based on condition so constructing and using strings combining it.

If value is spaces
AND ALL_ISCODE = 'ASDFGHJKLOI'
else
AND ALL_ISCODE LIKE '%'
end-if

If I not answared you question could you please describe the question.
Back to top
View user's profile Send private message
Bill Woodger

Moderator Emeritus


Joined: 09 Mar 2011
Posts: 7309
Location: Inside the Matrix

PostPosted: Fri Jun 17, 2011 5:37 pm
Reply with quote

Code:
 SELECT ALL_DATE,ALL_BCODE FROM ALL_TABLE WHERE ALL_DATE = '2011-06-16' AND ALL_ISCODE LIKE '%'
 AT PREPARE :00000080M


Rajesh, so something is wrong with the SELECT above (not a very helpful message, but it is dynamic, so less time to get a good one I suppose).

From looking, there is a space missing (probably not important) and I don't know personally that your date format is OK. There was some discussion of "%" in the DB2 forum recently.

If you can't see what is wrong with the above, I'd suggest trying to get the statement working as "non-dynamic" SQL so that you know for sure you are starting with a statement that works. Then, if it still doesn't work, it must be something you can't do. That's all I can do, as I don't know DB2.
Back to top
View user's profile Send private message
Robert Sample

Global Moderator


Joined: 06 Jun 2008
Posts: 8696
Location: Dubuque, Iowa, USA

PostPosted: Fri Jun 17, 2011 5:41 pm
Reply with quote

This
Quote:
If value is spaces
AND ALL_ISCODE = 'ASDFGHJKLOI'
else
AND ALL_ISCODE LIKE '%'
end-if
is directly the opposite of the code
Code:
     IF WS-TEXT2 IS EQUAL TO SPACES                       
        MOVE " AND ALL_ISCODE LIKE '%'"  TO WS-LINE3     
     ELSE                                                 
        MOVE " AND ALL_ISCODE = 'ASDFGHJKLOI'" TO WS-LINE3
     END-IF   
so your first problem is you are not clear on what you are doing.

Second, the system is telling you it doesn't like something about what you are doing. If nothing else, try the SELECT without the WHERE to make sure that's okay. Then add one WHERE clause at a time until the error recrurs. At that point, you'll know which clause the system does not like and you can look at the syntax to see where you've gone wrong.
Back to top
View user's profile Send private message
rajesh 35

New User


Joined: 21 Sep 2010
Posts: 7
Location: chennai

PostPosted: Fri Jun 17, 2011 5:41 pm
Reply with quote

Hi Bill,

Thank you for your response.

I have executed the querry in SPUFI it is working fine.
Back to top
View user's profile Send private message
Robert Sample

Global Moderator


Joined: 06 Jun 2008
Posts: 8696
Location: Dubuque, Iowa, USA

PostPosted: Fri Jun 17, 2011 5:48 pm
Reply with quote

Quote:
I have executed the querry in SPUFI it is working fine.
In that case, why run it in COBOL at all? If you have to run it in COBOL, then obviously the fact that a similar (but not identical -- it could not be identical since COBOL is a compiled language) query worked in SPUFI is completely and totally irrelevant to your problem.
Back to top
View user's profile Send private message
Craq Giegerich

Senior Member


Joined: 19 May 2007
Posts: 1512
Location: Virginia, USA

PostPosted: Fri Jun 17, 2011 6:16 pm
Reply with quote

What are the definitions of wstext, ws-line1, ws-line2, ws-line3, and ws-line4.
Code:
   STRING WS-LINE1 WS-LINE2 WS-LINE3   
                DELIMITED BY '  ' INTO WS-LINE4   
     STRING WS-LINE4 DELIMITED BY SIZE INTO WSTEXT
 


The part of WS-LINE4 that exceeds the combined length of the other three fields will contain what ever was in the field before the string statement. The same for WSTEXT after the second string statement.
Back to top
View user's profile Send private message
Bill Woodger

Moderator Emeritus


Joined: 09 Mar 2011
Posts: 7309
Location: Inside the Matrix

PostPosted: Fri Jun 17, 2011 6:49 pm
Reply with quote

Rajesh, Craq is right. Might or might not be causing the problem, but fix anyway. Move space to WS-LINE4. Change the 2nd string to a MOVE as suggested before. If you don't have value space on WS-LINE4, you'll be passing on some sort of rubbish at the end of your SQL statement. If you do have that value, you can only guarantee it working first time, as the two SQL statements you generate are different lengths. The long one would always be "right", the short one always wrong, unless the first SQL statement generated.

I'd comment the use of th ' ' (two spaces) so that no-one idly "fixes" it, or use a different method to build the parts of the command with spaces in. Like including a value which can't appear in your data, at the end of your data, and using that to delimit.

Why are the things called line1, line2, line3 and line4? Why not something like w-sql-select-part, w-sql-where-part, w-sql-and-part, w-sql-statement?

Does the code need to be dynamic?

Manual seems to suggest, at a three-second glance, that you'll need a CURSOR at some point, but I guess you'll get to that.
Back to top
View user's profile Send private message
rajesh 35

New User


Joined: 21 Sep 2010
Posts: 7
Location: chennai

PostPosted: Fri Jun 17, 2011 7:49 pm
Reply with quote

Hi Robert,

I have tried to execute select statement without where clause and got same error message and I'm looking into my code where I'm going wrong.
however could you please tell me where I'm going wrong in the code. ( Now I'm completely blank icon_smile.gif ).

Craq... I have given lenght of ws-line1 as X(40) exact length of the querry.

Bill... Thanks for your time on this, I will change nameing coventions later.

Code :

Code:
DATA DIVISION.                       
WORKING-STORAGE SECTION.             
                                     
77 WS-LINE1  PIC X(40) VALUE SPACES.
01 WSTEXT.                         
   49 WSSQLLEN PIC S9(04) COMP SYNC.
   49 WSLINE5   PIC X(40).   
EXEC SQL       
  INCLUDE SQLCA
END-EXEC.     
               
EXEC SQL       
  INCLUDE xxxxx
END-EXEC.   

 EXEC SQL                     
   DECLARE CS1 CURSOR FOR STMT
 END-EXEC.                   
 PROCEDURE DIVISION.                                     
*                                                         
 MAIN-PARA.                                               
     MOVE 'SELECT ALL_DATE,ALL_BCODE FROM ALL_TABLE'     
                              TO WS-LINE1.               
 STRING WS-LINE1 DELIMITED BY SIZE INTO WSTEXT
 DISPLAY WSTEXT.
EXEC SQL                             
    PREPARE STMT FROM :WSTEXT       
END-EXEC                             
                                     
EVALUATE TRUE                       
  WHEN SQLCODE = 0                   
       DISPLAY WSTEXT               
       DISPLAY "PREPARE SUCESSFUL"   
  WHEN OTHER                         
       DISPLAY "AT PREPARE :" SQLCODE
       STOP RUN                     
END-EVALUATE                         
Back to top
View user's profile Send private message
Robert Sample

Global Moderator


Joined: 06 Jun 2008
Posts: 8696
Location: Dubuque, Iowa, USA

PostPosted: Fri Jun 17, 2011 8:20 pm
Reply with quote

Rajesh -- I am not a DB2 person; the last time I coded anything in DB2 was 1989. However, the fact that the straight SELECT with no WHERE is generating the same error tells me the problem is not your WHERE. There is something else fundamentally wrong with your code. Perhaps the lack of value for WSSQLLEN? Perhaps a table name? I don't know but there's something not correct when even the simple SELECT isn't working.
Back to top
View user's profile Send private message
Akatsukami

Global Moderator


Joined: 03 Oct 2009
Posts: 1788
Location: Bloomington, IL

PostPosted: Fri Jun 17, 2011 8:27 pm
Reply with quote

What is the reason code associated with the error?
Back to top
View user's profile Send private message
don.leahy

Active Member


Joined: 06 Jul 2010
Posts: 765
Location: Whitby, ON, Canada

PostPosted: Sat Jun 18, 2011 12:21 am
Reply with quote

Your STRING statement is clobbering WSSQLLEN
Back to top
View user's profile Send private message
Bill Woodger

Moderator Emeritus


Joined: 09 Mar 2011
Posts: 7309
Location: Inside the Matrix

PostPosted: Sat Jun 18, 2011 1:34 am
Reply with quote

Good spot Don. I suppose somewhere along the way WSSQLLEN should have a value placed in it? At a wild guess, the length the of the SQL statement?

If you haven't already seen it Rajesh, search the forum for INSPECT FUNCTION(REVERSE) to see how to get the length excluding trailing spaces.

As previously suggested by Craq, you should initialise the field you are going to STRING into before doing the STRING. If there are only 30 bytes to string and your field is 40, then the last 10 bytes of the field will retain their previous contents. Your program will not work with the two options for generating statements that you have shown in your original example. The VALUE clause is not particularly helpful in this instance, as you need it to be space each time before you use it.

I'm going to push this little theme. IF you had taken the time to make your data-names meaningfull from the very first letter you typed, 1) you might have avoided the problem, 2) the problem would have been spotted earlier.


Code:

77 WS-CONSTRUCTED-SQL-STATEMENT  PIC X(40).
01 WS-FULL-DYNAMIC-DATA-TO-PASS-TO-SQL.                         
   49 WS-LENGTH-OF-DYNAMIC-DATA-FOR-SQL PIC S9(04) COMP SYNC.
   49 WS-DYNAMIC-SQL-TEXT   PIC X(40).   

MOVE WS-CONSTRUCTED-SQL-STATEMENT TO WS-FULL-DYNAMIC-DATA-TO-PASS-TO-SQL


Even if you manage to code the MOVE like that, someone else looking at it should be able to say, "why's that called 'FULL'"? Snap. Problem solved. That one, anyway.

I'm wondering about the SYNC. The first subordinate item to an 01 is always going to be where it should be for SYNC (it'll be on a double-word boundary). However, since SQL wants it SYNC it's probably better to have it there in case its absence confuses someone else. If you, and I'm not saying you should, had another area after this for another dynamic SQL you 3 times out of 4 (in "pefect" conditions) need the SYNC for the second anyway. If you're not certain of what the SYNC is doing, look it up.
Back to top
View user's profile Send private message
don.leahy

Active Member


Joined: 06 Jul 2010
Posts: 765
Location: Whitby, ON, Canada

PostPosted: Sat Jun 18, 2011 3:08 am
Reply with quote

Correct. WSSQLLEN is supposed to have the length of the SQL statement.

If I recall correctly, the length does not have to be accurate. It just needs to be >= the length of the statement text. (I hope it goes without saying that it should also be less than or equal to the length of the statement text field).

I agree that more meaningful variable names would have helped. The use of STRING instead of MOVE also helped to obscure what was actually a very simple issue.
Back to top
View user's profile Send private message
yuvrajdutta

New User


Joined: 13 Jul 2009
Posts: 40
Location: India

PostPosted: Mon Jun 20, 2011 6:35 pm
Reply with quote

This may be overkill.. but may be helpful @ your level.. this is the simpler dynamic SELECT statement without parameter markers(which i think you do not have)..

Code:

*THIS PROGRAM USES FIXED LIST SELECT WITHOUT PARAMETER MARKERS   
 ID DIVISION.                                                     
 PROGRAM-ID. DB2COB4.                                             
 DATA DIVISION.                                                   
 WORKING-STORAGE SECTION.                                         
 01 STRING-VARIABLE.                                             
    49 STRING-VAR-LEN PIC S9(4) USAGE COMP.                       
    49 STRING-VAR-TXT PIC X(100).                                 
 01 COUNTER PIC 9(1) VALUE 3.                                     
 01 TEMPVAL PIC X(6).                                             
     EXEC SQL                                                     
          INCLUDE SQLCA                                           
     END-EXEC.                                                   
     EXEC SQL                                                     
          INCLUDE EMPDCL                                         
     END-EXEC.                                                   
 PROCEDURE DIVISION.                                             
     DISPLAY 'PERFORMING FIXED LIST SELECT WITHOUT ?'.           
     MOVE 'SELECT EMP_ID,FIRST_NAME FROM IBMGRP.EMP'             
     TO STRING-VAR-TXT.                                           
     MOVE ZEROES TO STRING-VAR-LEN.                               
     INSPECT FUNCTION REVERSE (STRING-VAR-TXT)                   
     TALLYING STRING-VAR-LEN                                     
     FOR LEADING SPACES.                                         
     COMPUTE STRING-VAR-LEN = FUNCTION LENGTH(STRING-VAR-TXT) -   
     STRING-VAR-LEN.                                             
     DISPLAY 'QUERY: ' STRING-VAR-TXT.                           
     DISPLAY 'QUERY LENGTH: ' STRING-VAR-LEN.                     
     EXEC SQL                                                     
          DECLARE STMT STATEMENT                                 
     END-EXEC.                                                   
     EXEC SQL                                                     
          DECLARE EMPCHECK CURSOR FOR STMT                       
     END-EXEC.                                                   
     EXEC SQL                                                     
          PREPARE STMT FROM :STRING-VARIABLE                     
     END-EXEC.                                                   
     EXEC SQL                                                     
          OPEN EMPCHECK                                           
     END-EXEC.                                                   
     PERFORM FETCH-PARA UNTIL SQLCODE EQUAL TO 100.               
     EXEC SQL                                                     
          CLOSE EMPCHECK                                         
     END-EXEC.                                                   
     STOP RUN.                                                   
 FETCH-PARA.                                                     
     MOVE LOW-VALUES TO DCLEMP                                   
     EXEC SQL                                                     
          FETCH EMPCHECK                                         
          INTO :DCLEMP :INDSTRUC                                 
     END-EXEC                                                     
     IF SQLCODE EQUAL TO 0 THEN                                   
     DISPLAY '*****************************************'         
     DISPLAY 'EMP ID: ' EMP-ID                                   
     DISPLAY 'FIRST NAME: ' FIRST-NAME                           
     IF INDSTRUC(COUNTER) EQUAL TO 0 THEN                         
     DISPLAY 'MIDDLE NAME: ' MIDDLE-NAME                         
     ELSE                                                         
     DISPLAY 'NO MIDDLE NAME'                                     
     END-IF                                                       
     DISPLAY 'LAST NAME: ' LAST-NAME                             
     DISPLAY 'SELECT SQLCODE- ' SQLCODE                           
     DISPLAY 'SELECT SQLSTATE- ' SQLSTATE                         
     DISPLAY '*****************************************'         
     DISPLAY ' '                                                 
     END-IF.                                                     


Hope this helps
Back to top
View user's profile Send private message
yuvrajdutta

New User


Joined: 13 Jul 2009
Posts: 40
Location: India

PostPosted: Mon Jun 20, 2011 6:39 pm
Reply with quote

also.. SQLSTATE may also be helpful in this case as the value in SQLSTATE is somewhat platform-dependent and thus more precise..
Back to top
View user's profile Send private message
rajesh 35

New User


Joined: 21 Sep 2010
Posts: 7
Location: chennai

PostPosted: Tue Jun 21, 2011 7:07 pm
Reply with quote

Thank you don/Bill, select is working after passing length to string to varchar length filed ( tried the sql without where clause ).

To complete the work, I was used different cursors for time being.

I will keep on update the staus by trying with dynamic sql with where clause.

Thank you Yuvraj for you code , it is much helpful.
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 -> COBOL Programming

 


Similar Topics
Topic Forum Replies
No new posts Error to read log with rexx CLIST & REXX 11
No new posts Error when install DB2 DB2 2
No new posts run rexx code with jcl CLIST & REXX 15
No new posts Compile rexx code with jcl CLIST & REXX 6
No new posts CLIST - Virtual storage allocation error CLIST & REXX 5
Search our Forums:

Back to Top