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 

Why DB2 checks consistency token for every SQL execution

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


Joined: 20 Dec 2014
Posts: 38
Topics: 9

PostPosted: Tue Apr 24, 2018 9:33 am    Post subject: Why DB2 checks consistency token for every SQL execution Reply with quote

Hello,

I wrote below code for testing purpose.
I received -805 during the 2nd execution of the query,
Does db2 know that I have changed the consistency token in program and hence checks for it during 2nd execution of the query?
Does it checks for the token in every execution? If yes then why?

i.e if a query is in a loop then db2 will check the token in every occurrence even though the query is same?

Code:

PROCEDURE DIVISION.
-----------------------------------
0000-MAINLINE.
    PERFORM 1000-TEST
       THRU 1000-EXIT
    ADD +1    TO SQL-TIMESTAMP-1
    PERFORM 1000-TEST
       THRU 1000-EXIT
    GOBACK
    .
0000-EXIT.
    EXIT.
1000-TEST.
    EXEC SQL
         SELECT CURRENT_TIMESTAMP
         INTO  :WS-DB2-TIMESTAMP
         FROM  SYSIBM.SYSDUMMY1
    END-EXEC
    MOVE SQLCODE                     TO WS-SQLCODE

    EVALUATE WS-SQLCODE
        WHEN 0
             DISPLAY 'WS-SQLCODE :' WS-SQLCODE
        WHEN +100
            DISPLAY 'ROW NOT FOUND'
        WHEN OTHER
             DISPLAY 'WS-SQLCODE : ' WS-SQLCODE
    END-EVALUATE
    .
1000-EXIT.
    EXIT.
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


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

PostPosted: Tue Apr 24, 2018 2:42 pm    Post subject: Reply with quote

rsantosh,


Are you compiling the program every time you run? You also need to bind the PLAN every time you compile. what are your BIND parameters?
_________________
Kolusu - DFSORT Development Team (IBM)
DFSORT is on the Web at:
www.ibm.com/storage/dfsort

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


Joined: 20 Dec 2014
Posts: 38
Topics: 9

PostPosted: Tue Apr 24, 2018 7:41 pm    Post subject: Reply with quote

Hello Kolusu,

No. I compiled just once and bound the package once.
For first call of 1000- it gives SQLCODE 0, for the 2nd call of 1000- before which I put ADD statement to change con token it gave -805.
I am calling 1000- twice in the 0000- para.
Will provide BIND. Parameter later in the day.
Santosh
Back to top
View user's profile Send private message
rsantosh
Beginner


Joined: 20 Dec 2014
Posts: 38
Topics: 9

PostPosted: Wed Apr 25, 2018 8:46 am    Post subject: Reply with quote

Bind parameter
Code:

ACTION        REPLACE,
OWNER         XXXXX,
QUALIFIER     XXX,
VALIDATE      BIND,
EXPLAIN       NO,
ISOLATION     CS,
RELEASE       COMMIT,
COPY,
APREUSE       NONE,
APCOMPARE     NONE,
APRETAINDUP,
BUSTIMESENSITIVE YES,
SYSTIMESENSITIVE YES,
ARCHIVESENSITIVE YES,
APPLCOMPAT V11R1,
SQLERROR      NOPACKAGE,
CURRENTDATA   NO,
DEGREE        ANY,
DYNAMICRULES  BIND,
NODEFER       PREPARE,
REOPT         NONE,
KEEPDYNAMIC   NO,
IMMEDWRITE    NO,
DBPROTOCOL    DRDA,
OPTHINT,
ENCODING      EBCDIC(00037),
PLANMGMT      OFF,
PLANMGMTSCOPE STATIC,
CONCURRENTACCESSRESOLUTION,
EXTENDEDINDICATOR,
QUERYACCELERATION
GETACCELARCHIVE,
ACCELERATOR
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


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

PostPosted: Wed Apr 25, 2018 12:22 pm    Post subject: Reply with quote

rsantosh,

We are missing something. You have couple of BIND parameters that are out of normal. You have SQLERROR - nopackage

It means it will NOT create the package if an error occurred. So are you authorized? Did the package already exist?

Also can you add DISPLAY statements before invoking the paragraphs?


How about you bind the program using the following parameters?

Code:

//SYSTSIN  DD  *                     
 DSN SYSTEM(XXXX)                     
 BIND PLAN(YYYYYY)              +     
      MEMBER(ZZZZZZZZ)          +     
      ACTION(REPLACE)           +     
      RETAIN                    +     
      VALIDATE(BIND)            +     
      ISOLATION(CS)             +     
      CACHESIZE(0)              +     
      ACQUIRE(USE)              +     
      RELEASE(COMMIT)           +     
      CURRENTDATA(NO)           +     
      EXPLAIN(NO)                     
 END                                 
//*

_________________
Kolusu - DFSORT Development Team (IBM)
DFSORT is on the Web at:
www.ibm.com/storage/dfsort

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


Joined: 20 Dec 2014
Posts: 38
Topics: 9

PostPosted: Thu Apr 26, 2018 12:04 am    Post subject: Reply with quote

Hello Kolusu,

Yes, so that means package wouldnt have gotten created had there been any error during bind. I have bind access. When first time I executed the program I received -805 at the first call of 1000- para itself because I forgot to bind the package. Then i did the bind and received 0 at first call and -805 at 2nd call.

I will put the display and share the sysout with you.

Santosh
Back to top
View user's profile Send private message
rsantosh
Beginner


Joined: 20 Dec 2014
Posts: 38
Topics: 9

PostPosted: Thu Apr 26, 2018 2:28 am    Post subject: Reply with quote

kolusu wrote:
rsantosh,
Also can you add DISPLAY statements before invoking the paragraphs?



Code:


0000-MAINLINE.
    DISPLAY 'BEFORE 1ST CALL TO 1000- PARA'
    PERFORM 1000-TEST
       THRU 1000-EXIT
    DISPLAY 'AFTER 1ST CALL TO 1000- PARA'
    ADD +1    TO SQL-TIMESTAMP-1
    DISPLAY 'BEFORE 2ND CALL TO 1000- PARA'
    PERFORM 1000-TEST
       THRU 1000-EXIT
    DISPLAY 'AFTER 2ND CALL TO 1000- PARA'
    GOBACK
    .
0000-EXIT.
    EXIT.

1000-TEST.
    DISPLAY 'INSIDE 1000- PARA'
    EXEC SQL
         SELECT CURRENT_TIMESTAMP
         INTO  :WS-DB2-TIMESTAMP
         FROM  SYSIBM.SYSDUMMY1
    END-EXEC
    MOVE SQLCODE                     TO WS-SQLCODE

    EVALUATE WS-SQLCODE
        WHEN 0
             DISPLAY 'WS-SQLCODE :' WS-SQLCODE
        WHEN +100
            DISPLAY 'ROW NOT FOUND'
        WHEN OTHER
             DISPLAY 'WS-SQLCODE : ' WS-SQLCODE
    END-EVALUATE
    .
1000-EXIT.
    EXIT.



,XXXX,OUTPUT DISPLAY XXXXXXXX JOB14008         101 LINE 0       COLUMNS 02- 81
,COMMAND INPUT ===>,                                          ,SCROLL ===>,CSR ,
********************************* TOP OF DATA **********************************
BEFORE 1ST CALL TO 1000- PARA
INSIDE 1000- PARA
WS-SQLCODE :0000
AFTER 1ST CALL TO 1000- PARA
BEFORE 2ND CALL TO 1000- PARA
INSIDE 1000- PARA
WS-SQLCODE : 080N
AFTER 2ND CALL TO 1000- PARA
******************************** BOTTOM OF DATA ********************************
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


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

PostPosted: Thu Apr 26, 2018 10:54 am    Post subject: Reply with quote

rsantosh,

Just before the EXEC SQL statement add the following statement

Code:

INITIALIZE WS-DB2-TIMESTAMP


What exactly are you trying to do adding +1 to SQL-TIMESTAMP-1 ? Is SQL-TIMESTAMP-1 a redefined version of WS-DB2-TIMESTAMP? If your intention is add 1 sec then you can do it directly like this
Code:

SELECT CURRENT_TIMESTAMP + 1 SECOND   
  INTO :WS-DB2-TIMESTAMP
  FROM SYSIBM.SYSDUMMY1               


or adding microsecond.
Code:

SELECT CURRENT_TIMESTAMP + 1 MICROSECOND             
  INTO :WS-DB2-TIMESTAMP
  FROM SYSIBM.SYSDUMMY1                               

_________________
Kolusu - DFSORT Development Team (IBM)
DFSORT is on the Web at:
www.ibm.com/storage/dfsort

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


Joined: 20 Dec 2014
Posts: 38
Topics: 9

PostPosted: Thu Apr 26, 2018 11:25 pm    Post subject: Reply with quote

Hello Kolusu,

Sorry, Looks like I didnt phrase my question properly.

SQL-TIMESTAMP-1 is the first part of consistency token which gets generated during pre-compile and I believe is used to match the token with load module during program execution.

I used to think that if a program has multiple sql queries then db2 will verify the token only for the 1st query it encounters during the execution of the program and not for every query which the progarm has.
Or if the program program hits the same query multiple times(like in PERFORM in loop) then db2 will verify the token only once during the execution of the program.

To check this I wrote this test program and changed the 1st part of consistency token using ADD statement.

So when my program ran, during 1st call of 1000- para the query executed with sqlcode 000 as expected. After the ADD statement(which changed the consistency token during the execution), 1000- para was called again and this time the same query returned sqlcode -805. That means every time the query is encountered, db2 verifies the token if it is matching with load module or not. So why does db2 verifies token every time in the same instance of program run?


This is the sample, I will share the compile listing later on.
Code:

01 SQL-PLIST1.

05 SQL-PLIST-CON PIC S9(9) COMP-4 VALUE +2654208.

05 SQL-CALLTYPE PIC S9(4) COMP-4 VALUE +30.

05 SQL-PROG-NAME PIC X(8) VALUE 'BV174V02'.

05 SQL-TIMESTAMP-1 PIC S9(9) COMP-4 VALUE +368527768.

05 SQL-TIMESTAMP-2 PIC S9(9) COMP-4 VALUE +507831332.

05 SQL-SECTION PIC S9(4) COMP-4 VALUE +2.

05 SQL-CODEPTR PIC S9(9) COMP-4.

05 SQL-VPARMPTR PIC S9(9) COMP-4 VALUE +0.

05 SQL-APARMPTR PIC S9(9) COMP-4 VALUE +0.

05 SQL-STMT-NUM PIC S9(4) COMP-4 VALUE +431.

05 SQL-STMT-TYPE PIC S9(4) COMP-4 VALUE +233.


Santosh
Back to top
View user's profile Send private message
rsantosh
Beginner


Joined: 20 Dec 2014
Posts: 38
Topics: 9

PostPosted: Fri Apr 27, 2018 2:33 am    Post subject: Reply with quote

Full code and compile listing below

Code:

 ID DIVISION.
 PROGRAM-ID.   XXXX.
 ENVIRONMENT DIVISION.
 DATA DIVISION.
 WORKING-STORAGE SECTION.

 01 WS-SQLCODE                   PIC S9(04) COMP.
 01 WS-DB2-TIMESTAMP             PIC X(26).
     EXEC SQL
         INCLUDE SQLCA
     END-EXEC.

*----------------------------------------------------------------*
 PROCEDURE DIVISION.
*----------------------------------------------------------------*
 0000-MAINLINE.
     DISPLAY 'BEFORE 1ST CALL TO 1000- PARA'
     PERFORM 1000-TEST
        THRU 1000-EXIT
     DISPLAY 'AFTER 1ST CALL TO 1000- PARA'
     ADD +1    TO SQL-TIMESTAMP-1
     DISPLAY 'BEFORE 2ND CALL TO 1000- PARA'
     PERFORM 1000-TEST
        THRU 1000-EXIT
     DISPLAY 'AFTER 2ND CALL TO 1000- PARA'
     GOBACK
     .
 0000-EXIT.
     EXIT.

 1000-TEST.
     DISPLAY 'INSIDE 1000- PARA'
     EXEC SQL
          SELECT CURRENT_TIMESTAMP
          INTO  :WS-DB2-TIMESTAMP
          FROM  SYSIBM.SYSDUMMY1
     END-EXEC
     MOVE SQLCODE                     TO WS-SQLCODE

     EVALUATE WS-SQLCODE
         WHEN 0
              DISPLAY 'WS-SQLCODE :' WS-SQLCODE
         WHEN +100
             DISPLAY 'ROW NOT FOUND'
         WHEN OTHER
              DISPLAY 'WS-SQLCODE : ' WS-SQLCODE
     END-EVALUATE
     .
 1000-EXIT.
     EXIT.
********************** Bottom of Data **************

Compile listing


 ID DIVISION.
 PROGRAM-ID.   TBYTES02.
 ENVIRONMENT DIVISION.
 DATA DIVISION.
 WORKING-STORAGE SECTION.

 01 WS-SQLCODE                   PIC S9(04) COMP.
 01 WS-DB2-TIMESTAMP             PIC X(26).
*****EXEC SQL
*****    INCLUDE SQLCA
*****END-EXEC.
  01 SQLCA.
     05 SQLCAID     PIC X(8).
     05 SQLCABC     PIC S9(9) COMP-5.
     05 SQLCODE     PIC S9(9) COMP-5.
     05 SQLERRM.
        49 SQLERRML PIC S9(4) COMP-5.
        49 SQLERRMC PIC X(70).
     05 SQLERRP     PIC X(8).
     05 SQLERRD     OCCURS 6 TIMES
                    PIC S9(9) COMP-5.
     05 SQLWARN.
        10 SQLWARN0 PIC X.
        10 SQLWARN1 PIC X.
        10 SQLWARN2 PIC X.
        10 SQLWARN3 PIC X.
        10 SQLWARN4 PIC X.
        10 SQLWARN5 PIC X.
        10 SQLWARN6 PIC X.
        10 SQLWARN7 PIC X.
     05 SQLEXT.
        10 SQLWARN8 PIC X.
        10 SQLWARN9 PIC X.
        10 SQLWARNA PIC X.
        10 SQLSTATE PIC X(5).

*----------------------------------------------------------------*
  01 SQL-VERS.
     05 SQL-VERS-PREF    PIC X(04) VALUE 'VER.'.
     05 SQL-VERS-DATA    PIC X(64)
                         VALUE '2018-04-26-07.17.01.354294'.
  77 SQL-TEMP      PIC X(128).
  77 DSN-TEMP      PIC S9(9)  COMP-5.
  77 DSN-TMP2      PIC S9(18) COMP-3.
  77 DSNNROWS      PIC S9(9)  COMP-5.
  77 DSNNTYPE      PIC S9(4)  COMP-5.
  77 DSNNLEN       PIC S9(4)  COMP-5.
  77 SQL-NULL      PIC S9(9) COMP-5 VALUE +0.
  77 SQL-INIT-FLAG PIC S9(4) COMP-5 VALUE +0.
     88 SQL-INIT-DONE VALUE +1.
  77 SQL-FILE-READ      PIC S9(9) COMP-5 VALUE +2.
  77 SQL-FILE-CREATE    PIC S9(9) COMP-5 VALUE +8.
  77 SQL-FILE-OVERWRITE PIC S9(9) COMP-5 VALUE +16.
  77 SQL-FILE-APPEND    PIC S9(9) COMP-5 VALUE +32.
  01 SQL-PLIST1.
     05 SQL-PLIST-CON   PIC S9(9) COMP-5 VALUE +4195328.
     05 SQL-CALLTYPE    PIC S9(4) COMP-5 VALUE +30.
     05 SQL-PROG-NAME   PIC X(8)  VALUE X'54425954XXXXXX'.
     05 SQL-TIMESTAMP-1 PIC S9(9) COMP-5 VALUE +445093610.
     05 SQL-TIMESTAMP-2 PIC S9(9) COMP-5 VALUE +240602501.
    05 SQL-SECTION     PIC S9(4) COMP-5 VALUE +1.
    05 SQL-CODEPTR     PIC S9(9) COMP-5.
    05 SQL-VPARMPTR    PIC S9(9) COMP-5 VALUE +0.
    05 SQL-APARMPTR    PIC S9(9) COMP-5 VALUE +0.
    05 FILLER          PIC S9(4) COMP-5 VALUE +1208.
    05 SQL-STMT-TYPE   PIC S9(4) COMP-5 VALUE +231.
    05 SQL-STMT-NUM    PIC S9(9) COMP-5 VALUE +41.
    05 SQL-PLIST-FLG   PIC S9(4) COMP-5 VALUE +0.
    05 FILLER          PIC X(18) VALUE
       X'000000000000000000000000000000000000'.
    05 SQL-AVAR-LIST1.
       10 PRE-SQLDAID  PIC X(8)  VALUE 'SQLDA  ,'.
       10 PRE-SQLDABC  PIC S9(9) COMP-5 VALUE +60.
       10 PRE-SQLN     PIC S9(4) COMP-5 VALUE +1.
       10 PRE-SQLLD    PIC S9(4) COMP-5 VALUE +1.
       10 PRE-SQLVAR.
         12 SQLVAR-BASE1.
           15 SQL-AVAR-TYPE1      PIC S9(4) COMP-5 VALUE +452.
           15 SQL-AVAR-LEN1       PIC S9(4) COMP-5 VALUE +26.
           15 SQL-AVAR-ADDRS1.
              20 SQL-AVAR-ADDR1   PIC S9(9) COMP-5.
               20 SQL-AVAR-IND1    PIC S9(9) COMP-5.
            15 SQL-AVAR-NAME1.
               20 SQL-AVAR-NAMEL1  PIC S9(4) COMP-5 VALUE +0.
               20 SQL-AVAR-NAMEC1  PIC X(30) VALUE ' '.

 PROCEDURE DIVISION.
*----------------------------------------------------------------*
 DSNSQL SECTION.
 SQL-SKIP.
     GO TO SQL-INIT-END.
 SQL-INITIAL.
     MOVE 1 TO SQL-INIT-FLAG.
     CALL 'DSNHADDR' USING SQL-APARMPTR OF SQL-PLIST1 SQL-AVAR-LIS
-    T1.
     CALL 'DSNHADD2' USING SQL-AVAR-ADDRS1 IN
     SQL-AVAR-LIST1 WS-DB2-TIMESTAMP SQL-NULL.
     CALL 'DSNHADDR' USING SQL-CODEPTR OF SQL-PLIST1 SQLCA.
 SQL-INIT-END.
     CONTINUE.
 0000-MAINLINE.
     DISPLAY 'BEFORE 1ST CALL TO 1000- PARA'
     PERFORM 1000-TEST
        THRU 1000-EXIT
     DISPLAY 'AFTER 1ST CALL TO 1000- PARA'
     ADD +1    TO SQL-TIMESTAMP-1
     DISPLAY 'BEFORE 2ND CALL TO 1000- PARA'
     PERFORM 1000-TEST
        THRU 1000-EXIT
     DISPLAY 'AFTER 2ND CALL TO 1000- PARA'
     GOBACK
     .
 0000-EXIT.
     EXIT.

 1000-TEST.
     DISPLAY 'INSIDE 1000- PARA'
*****EXEC SQL
*****     SELECT CURRENT_TIMESTAMP
*****     INTO  :WS-DB2-TIMESTAMP
*****     FROM  SYSIBM.SYSDUMMY1
*****END-EXEC
     PERFORM SQL-INITIAL UNTIL SQL-INIT-DONE
     CALL 'DSNHLI2' USING SQL-PLIST1
     MOVE SQLCODE                     TO WS-SQLCODE

 High order digit positions in the sender may be truncated in the move t
 receiver "WS-SQLCODE (BINARY INTEGER)".


     EVALUATE WS-SQLCODE
         WHEN 0
              DISPLAY 'WS-SQLCODE :' WS-SQLCODE
         WHEN +100
             DISPLAY 'ROW NOT FOUND'
         WHEN OTHER
              DISPLAY 'WS-SQLCODE : ' WS-SQLCODE
     END-EVALUATE
     .
 1000-EXIT.
      EXIT.
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


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

PostPosted: Fri Apr 27, 2018 12:09 pm    Post subject: Reply with quote

rsantosh wrote:
Hello Kolusu,

Sorry, Looks like I didnt phrase my question properly.

SQL-TIMESTAMP-1 is the first part of consistency token which gets generated during pre-compile and I believe is used to match the token with load module during program execution.

I used to think that if a program has multiple sql queries then db2 will verify the token only for the 1st query it encounters during the execution of the program and not for every query which the progarm has.
Or if the program program hits the same query multiple times(like in PERFORM in loop) then db2 will verify the token only once during the execution of the program.

To check this I wrote this test program and changed the 1st part of consistency token using ADD statement.

So when my program ran, during 1st call of 1000- para the query executed with sqlcode 000 as expected. After the ADD statement(which changed the consistency token during the execution), 1000- para was called again and this time the same query returned sqlcode -805. That means every time the query is encountered, db2 verifies the token if it is matching with load module or not. So why does db2 verifies token every time in the same instance of program run?


Rsanthosh,

I am not sure as to why you are messing with Consistency tokens, but every execution is treated as if it is separate transaction. DB2 does NOT keep track of your programs or SQL it executed before.

The SQL precompiler(the first step in preparing an application program) places timestamp 'y' in the DBRM, and time stamp 'x' in the parameter list in the application program for each SQL statement. At BIND time, DB2 stores the DBRM timestamp for run-time use. At run-time, timestamp 'x',for the SQL statement being processed, is compared with timestamp 'y' derived from the DBRM 'z' at BIND time.If the two timestamps do not match then you will get errors like -805 or -818.

Think of a simple scenario. You are given a key to enter a room. Once you enter and exit out of it, then you modify the same key slightly. You cannot use the same key to get back in. The room does not keep track that you entered a minute ago.

If you really want to get fancy and change the consistency token for every SQL execution , you can try to update the column CONTOKEN in SYSIBM.SYSPACKAGE table and then run your individual queries.
_________________
Kolusu - DFSORT Development Team (IBM)
DFSORT is on the Web at:
www.ibm.com/storage/dfsort

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


Joined: 20 Dec 2014
Posts: 38
Topics: 9

PostPosted: Fri Apr 27, 2018 9:32 pm    Post subject: Reply with quote

Hello Kolusu,

Thank you.

So this is the essence.
Quote:

DB2 does NOT keep track of your programs or SQL it executed before.


I used to think otherwise and so to confirm this, changed the token during run time.

Santosh
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