Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations strongm on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Using a list passed from an Oracle COBOL pgm to a DB2 COBOL pgm

Status
Not open for further replies.

hawley

Programmer
Dec 16, 2002
37
US
This may belong in the DB2 forum but I am using this with COBOL so put it here.

I have a fun problem. I have a COBOL program that is retriving a list of numbers from an Oracle database. Each time it retrieves a new number it puts that number in a comma delimited string with single quotes around each number (ex.. '8','7'). The list is defined as "PIC X(500) VALUE SPACES". When all the numbers are put in the list that varable is moved to another variable that is in a copybook containing working storage elements. That copybook variable is defined as PIC X(500). This copybook is then called in a COBOL program that calls a DB2 select statement. The copybook variable is moved to a local variable defined as "PIC X(500) VALUE SPACES". That local variable is then put in a where clause of a select statement.

My issue is that when the data is returned from that select statement it is like the "not in" statement that list is used in is ignored. I run the query outside of the program in sql/station and it works perfect.

Any ideas or suggestions as to why that not in statment would be ignored? I know this is probably complicated to follow but anything is appriciated.
 
Debug the program which uses the DB2-select statement to see, what happens. You have probably an error, when constructing the select-statement in your COBOL program.
I used similar things, that is I first computed a string and then I used it in where-condition and it worked fine.
 
please post a full sample of the exec SQL you are using on the DB2 COBOL program, including all variable definition.

Also bear in mind that any WS variable that is not used on dynamicly prepared SQL will be treated as a SINGLE item on any SQL, e.g. it can not be used as if it contained a list of items to use on a "WHERE FIELD IN (a,b,c,d)".



Regards

Frederico Fonseca
SysSoft Integrated Ltd

FAQ219-2884
FAQ181-2886
 
Thank you both for replying.

mikrom -
I have tried to debug but we have changed our debugger and I didn't know what I was doing. I will have to ask for help today on how get things started.

fredericofonseca -
If I understand you correctly then what I am trying to do will not work. Here is what you were asking for though.

Code:
[tab]*Working Storage Definition
[tab][tab]01  PM164-PARAMETERS.
[tab][tab]    05  PM164-GET-EXCLD-STR-PARMS.
[tab][tab]        10  PM164-EXCLD-STR             PIC  X(50).
[tab]*Values of PM164-EXCLD-STR being passed
[tab]*I have tried it with one store and with two stores.
[tab][tab]PM164-EXCLD-STR = '8'     OR    PM164-EXCLD-STR = '8','7' 
[tab]*Program
[tab][tab]05  PV-STR-LIST                 PIC  X(50) VALUE SPACES.
[tab][tab]MOVE PM164-EXCLD-STR                 TO PV-STR-LIST.
[tab]*found in a paragraph.  Didn't use a cursor since only one value is found.  
[tab][tab]PERFORM WITH TEST AFTER
[tab][tab]  VARYING PV-SELECT-COUNTER
[tab][tab]  FROM 1 BY 1
[tab][tab]UNTIL (PV-SELECT-COUNTER > PC-MAX-RETRY-CNT OR
[tab][tab]       SQLCODE NOT = -904)
[tab][tab]    EXEC SQL
[tab][tab]        SELECT
[tab][tab]            MIN(A.FIRST_RCVD_DATE)
[tab][tab]        INTO
[tab][tab]            :TSKST-FIRST-RCVD-DATE :PV-FIRST-RCVD-[tab][tab]DATE-NULL
[tab][tab]        FROM
[tab][tab]            TSKST A
[tab][tab]        WHERE
[tab][tab]              A.ITEM_NMBR = :PV-ITM-NBR
[tab][tab]          AND A.LOC_NBR <> 0
[tab][tab]          AND CHAR(A.LOC_NBR) NOT IN ([b]:PV-STR-LIST[/b])
[tab][tab]          AND (A.FIRST_RCVD_DATE > 0
[tab][tab]              OR A.FIRST_RCVD_DATE < 800101)
[tab][tab]        GROUP BY A.ITEM_NMBR
[tab][tab]    WITH UR
[tab][tab]END-EXEC
 
Hawley,
Let me see if I have understood correctly what you are trying to achieve. You are dynamically building a list of values eg 'A1', 'B1', 'C1' and then passing that to DB2:

SELECT COL1 FROM TABLE WHERE COL2 NOT IN :)WS-VARIABLE)

where WS-VARIABLE contains 'A1', 'B1', 'C1'. You are expecting DB2 to pass back any rows where COL2 is either A1 or B1 or C1.

If that is what you are expecting, then it is not going to work. DB2 will look at WS-VARIABLE and treat it as one variable i.e it will pass back any rows where COL2 equals "'A1', 'B1', 'C1'".

You will have to build the query using dynamic SQL and the PREPARE statement, I think.

Hope this helps.
Marc
 
Here is something I was trying this weekend. I was just passing in a store in a seperate variable and then comparing it to the result from the sql.
My issue with this is for some reason my if statement is wrong. Any ideas and/or suggestions would be helpful.

Code:
*definition in the working storage
01  PM164-PARAMETERS.
    05  PM164-GET-EXCLD-STR-PARMS.
        10  PM164-STR-01                PIC  X(04).

*definition in the program
05  PV-LOC-NBR                  PIC  X(04)  VALUE SPACES.

*sql used for the cursor.
      EXEC SQL
          DECLARE FRSTRCVDCSR CURSOR
          FOR SELECT
              CHAR(A.LOC_NBR),
              A.FIRST_RCVD_DATE
          FROM
              TSKST A
          WHERE
                A.ITEM_NMBR = :PV-ITM-NBR
            AND A.LOC_NBR <> 0
            AND (A.FIRST_RCVD_DATE > 0
                OR A.FIRST_RCVD_DATE < 800101)
          WITH UR
      END-EXEC.
*open the cursor

*fetch the cursor
EXEC SQL
    FETCH  FRSTRCVDCSR
     INTO  :PV-LOC-NBR
          ,:TSKST-FIRST-RCVD-DATE :PV-FIRST-RCVD-DATE-NULL
END-EXEC.
        WHEN SQLCODE = +0
            ..........
            DISPLAY 'DB2 LOC-NBR = ' PV-LOC-NBR '.'
            DISPLAY 'FIRST STORE = ' PM164-STR-01 '.'
            IF (PV-LOC-NBR EQUAL PM164-STR-01)
               DISPLAY 'STORE NUMBER IS SAME AS 1 '
            ELSE
               DISPLAY 'STORE NUMBER IS NOT SAME AS 1'
               MOVE TSKST-FIRST-RCVD-DATE TO PV-MIN-FIRST-DATE
            END-IF

The output displays. 
DB2 LOC-NBR = 8   .
FIRST STORE = 8   .
STORE NUMBER IS NOT SAME AS 1
[\code]
Why is the stores not seen as being equal?

I have also tried it this way.  
[code]
*definition in the working storage
01  PM164-PARAMETERS.
    05  PM164-GET-EXCLD-STR-PARMS.
        10  PM164-STR-01                PIC  X(04).

*definition in the program
05  PV-LOC-NBR                  PIC  X(04)  VALUE SPACES.

*sql used for the cursor.
      EXEC SQL
          DECLARE FRSTRCVDCSR CURSOR
          FOR SELECT
              CHAR(A.LOC_NBR),
              A.FIRST_RCVD_DATE
          FROM
              TSKST A
          WHERE
                A.ITEM_NMBR = :PV-ITM-NBR
            AND A.LOC_NBR <> 0
            AND (A.FIRST_RCVD_DATE > 0
                OR A.FIRST_RCVD_DATE < 800101)
          WITH UR
      END-EXEC.
*open the cursor

*fetch the cursor
EXEC SQL
    FETCH  FRSTRCVDCSR
     INTO  :PV-LOC-NBR
          ,:TSKST-FIRST-RCVD-DATE :PV-FIRST-RCVD-DATE-NULL
END-EXEC.
        WHEN SQLCODE = +0
            ..........
            DISPLAY 'DB2 LOC-NBR = ' PV-LOC-NBR '.'
            DISPLAY 'FIRST STORE = ' PM164-STR-01 '.'
            IF (PV-LOC-NBR NOT EQUAL PM164-STR-01)
                DISPLAY 'STORE NUMBER IS NOT SAME AS 1'
                MOVE TSKST-FIRST-RCVD-DATE TO PV-MIN-FIRST-DATE
            ELSE
                DISPLAY 'STORE NUMBER IS SAME AS 1'
            END-IF

The output displays. 
DB2 LOC-NBR = 8   .
FIRST STORE = 8   .
STORE NUMBER IS NOT SAME AS 1
[\code]
Stores are not being seen as equal here either...why?
 
Didn't see the code was not wrapped correctly...here is the post again...a bit cleaner.

MarcLodge - I figured that as my issue after seeing fredericofonseca post. I will try the dynamic sql as well. Thanks for the help

Here is something I was trying this weekend. I was just passing in a store in a seperate variable and then comparing it to the result from the sql.
My issue with this is for some reason my if statement is wrong. Any ideas and/or suggestions would be helpful.

Code:
*definition in the working storage
01  PM164-PARAMETERS.
    05  PM164-GET-EXCLD-STR-PARMS.
        10  PM164-STR-01                PIC  X(04).

*definition in the program
05  PV-LOC-NBR                  PIC  X(04)  VALUE SPACES.

*sql used for the cursor.
      EXEC SQL
          DECLARE FRSTRCVDCSR CURSOR
          FOR SELECT
              CHAR(A.LOC_NBR),
              A.FIRST_RCVD_DATE
          FROM
              TSKST A
          WHERE
                A.ITEM_NMBR = :PV-ITM-NBR
            AND A.LOC_NBR <> 0
            AND (A.FIRST_RCVD_DATE > 0
                OR A.FIRST_RCVD_DATE < 800101)
          WITH UR
      END-EXEC.
*open the cursor

*fetch the cursor
EXEC SQL
    FETCH  FRSTRCVDCSR
     INTO  :PV-LOC-NBR
          ,:TSKST-FIRST-RCVD-DATE :PV-FIRST-RCVD-DATE-NULL
END-EXEC.
        WHEN SQLCODE = +0
            ..........
            DISPLAY 'DB2 LOC-NBR = ' PV-LOC-NBR '.'
            DISPLAY 'FIRST STORE = ' PM164-STR-01 '.'
            IF (PV-LOC-NBR EQUAL PM164-STR-01)
               DISPLAY 'STORE NUMBER IS SAME AS 1 '
            ELSE
               DISPLAY 'STORE NUMBER IS NOT SAME AS 1'
               MOVE TSKST-FIRST-RCVD-DATE TO PV-MIN-FIRST-DATE
            END-IF

The output displays. 
DB2 LOC-NBR = 8   .
FIRST STORE = 8   .
STORE NUMBER IS NOT SAME AS 1
Why is the stores not seen as being equal?

I have also tried it this way.
Code:
*definition in the working storage
01  PM164-PARAMETERS.
    05  PM164-GET-EXCLD-STR-PARMS.
        10  PM164-STR-01                PIC  X(04).

*definition in the program
05  PV-LOC-NBR                  PIC  X(04)  VALUE SPACES.

*sql used for the cursor.
      EXEC SQL
          DECLARE FRSTRCVDCSR CURSOR
          FOR SELECT
              CHAR(A.LOC_NBR),
              A.FIRST_RCVD_DATE
          FROM
              TSKST A
          WHERE
                A.ITEM_NMBR = :PV-ITM-NBR
            AND A.LOC_NBR <> 0
            AND (A.FIRST_RCVD_DATE > 0
                OR A.FIRST_RCVD_DATE < 800101)
          WITH UR
      END-EXEC.
*open the cursor

*fetch the cursor
EXEC SQL
    FETCH  FRSTRCVDCSR
     INTO  :PV-LOC-NBR
          ,:TSKST-FIRST-RCVD-DATE :PV-FIRST-RCVD-DATE-NULL
END-EXEC.
        WHEN SQLCODE = +0
            ..........
            DISPLAY 'DB2 LOC-NBR = ' PV-LOC-NBR '.'
            DISPLAY 'FIRST STORE = ' PM164-STR-01 '.'
            IF (PV-LOC-NBR NOT EQUAL PM164-STR-01)
                DISPLAY 'STORE NUMBER IS NOT SAME AS 1'
                MOVE TSKST-FIRST-RCVD-DATE TO PV-MIN-FIRST-DATE
            ELSE
                DISPLAY 'STORE NUMBER IS SAME AS 1'
            END-IF

The output displays. 
DB2 LOC-NBR = 8   .
FIRST STORE = 8   .
STORE NUMBER IS NOT SAME AS 1
Stores are not being seen as equal here either...why?
 
I may be wrong, but it looks like yout variable may contain low values or other "undisplayable" chars.
Try and compare one by one (with reference modification) and see what it says.

And now that you gave more details, only the following options available to you.

1- fully dynamic SQL.

2- if there is a limit to the number of IN list (e.g. 10 max or 20 max values) then you can code all of them as
db2_var in :)ws-var1, :ws-var2... ws-varn)

3 - use a global declared table on the main SQL, and when you receive the "variable list" from oracle, insert into that temporary table, and then open the cursor.
Select could then be using a inner join to link the main tble and that other temporary table.

Regards

Frederico Fonseca
SysSoft Integrated Ltd

FAQ219-2884
FAQ181-2886
 
Thanks for all the help. I ended up making my second solution work. When I kept the variables as numbers they compared to each other correctly.
 
Hi hawley,

Some times ago I have done similar thing. Here are the example code snippets from a program which is really running in production - I changed only some comments to English for better understanding:

1. First I define in Working Storage a string, which will hold my select statement
Code:
       [COLOR=#2e8b57][b]01 [/b][/color] SELECT-R000090V.
      [COLOR=#6a5acd]     [/color][COLOR=#2e8b57][b]05 [/b][/color] SELECT-ALL-R000090V     [COLOR=#804040][b]PIC[/b][/color] X([COLOR=#ff00ff]23[/color])  [COLOR=#804040][b]VALUE[/b][/color]
      [COLOR=#6a5acd]     [/color][COLOR=#ff00ff]'SELECT * FROM R000090V '[/color].
      [COLOR=#6a5acd]     [/color][COLOR=#2e8b57][b]05 [/b][/color] WHERE-BEDINGUNG         [COLOR=#804040][b]PIC[/b][/color] X([COLOR=#ff00ff]50[/color])  [COLOR=#804040][b]VALUE[/b][/color]
      [COLOR=#6a5acd]     [/color][COLOR=#ff00ff]'WHERE KONTOART = 2 AND LOESCHMKM = 0 AND TARIF IN '[/color].
      [COLOR=#6a5acd]     [/color][COLOR=#2e8b57][b]05 [/b][/color] TARIF-LISTE             [COLOR=#804040][b]PIC[/b][/color] X([COLOR=#ff00ff]100[/color]) [COLOR=#804040][b]VALUE[/b][/color] [COLOR=#ff00ff]SPACE[/color].
      [COLOR=#6a5acd]     [/color][COLOR=#2e8b57][b]05 [/b][/color] ORDER-BY                [COLOR=#804040][b]PIC[/b][/color] X([COLOR=#ff00ff]25[/color])  [COLOR=#804040][b]VALUE[/b][/color]
      [COLOR=#6a5acd]     [/color][COLOR=#ff00ff]'ORDER BY BSSTAMMNR, BSVNR'[/color].

2. Here the field TARIF-LISTE is a placeholder for a list of tarifes in this form ('AA', 'AB', 'ZC', 'XZ') which I compute with this paragraph/procedure from other table
Code:
       [COLOR=#804040][b]ERMITTLE-TARIFE[/b][/color].
      [COLOR=#0000ff]*    Alle Tarife aus P000140V ermitteln[/color]
      [COLOR=#0000ff]*    Declare Cursor for the SELECT[/color]
      [COLOR=#6a5acd]     [/color]EXEC SQL
      [COLOR=#6a5acd]       [/color]DECLARE C140 CURSOR [COLOR=#804040][b]FOR[/b][/color]
      [COLOR=#6a5acd]       [/color][COLOR=#804040][b]SELECT[/b][/color] DISTINCT(TARIF) [COLOR=#804040][b]FROM[/b][/color] P000140V
      [COLOR=#6a5acd]     [/color]END-EXEC.
      [COLOR=#0000ff]*    Open Cursor[/color]
      [COLOR=#6a5acd]     [/color]EXEC SQL
      [COLOR=#6a5acd]       [/color][COLOR=#804040][b]OPEN[/b][/color] C140
      [COLOR=#6a5acd]     [/color]END-EXEC.
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]INITIALIZE[/b][/color] ZW-NR-TARIF
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]MOVE[/b][/color] [COLOR=#ff00ff]'('[/color] [COLOR=#804040][b]TO[/b][/color] TARIF-LISTE
      [COLOR=#6a5acd]     [/color][COLOR=#008080]PERFORM[/color] [COLOR=#804040][b]UNTIL[/b][/color] SQLCODE [COLOR=#804040][b]NOT[/b][/color] = [COLOR=#ff00ff]ZERO[/color]
      [COLOR=#6a5acd]       [/color]EXEC SQL
      [COLOR=#6a5acd]         [/color]FETCH [COLOR=#804040][b]NEXT[/b][/color] [COLOR=#804040][b]FROM[/b][/color] C140 [COLOR=#804040][b]INTO[/b][/color] :ZW-TARIF
      [COLOR=#6a5acd]       [/color]END-EXEC
      [COLOR=#0000ff]*      If FETCH ok[/color]
      [COLOR=#6a5acd]       [/color][COLOR=#804040][b]IF[/b][/color] SQLCODE = [COLOR=#ff00ff]ZERO[/color]
      [COLOR=#6a5acd]          [/color][COLOR=#804040][b]ADD[/b][/color] [COLOR=#ff00ff]1[/color] [COLOR=#804040][b]TO[/b][/color] ZW-NR-TARIF
      [COLOR=#0000ff]*         insert ', ' before next Tarif[/color]
      [COLOR=#6a5acd]          [/color][COLOR=#804040][b]IF[/b][/color] ZW-NR-TARIF > [COLOR=#ff00ff]1[/color]
      [COLOR=#6a5acd]             [/color][COLOR=#804040][b]STRING[/b][/color] TARIF-LISTE [COLOR=#804040][b]DELIMITED[/b][/color] [COLOR=#804040][b]BY[/b][/color] [COLOR=#ff00ff]SPACE[/color]
      [COLOR=#6a5acd]                    [/color][COLOR=#ff00ff]','[/color]         [COLOR=#804040][b]DELIMITED[/b][/color] [COLOR=#804040][b]BY[/b][/color] [COLOR=#804040][b]SIZE[/b][/color]
      [COLOR=#6a5acd]                    [/color][COLOR=#804040][b]INTO[/b][/color] TARIF-LISTE
      [COLOR=#6a5acd]             [/color][COLOR=#804040][b]END-STRING[/b][/color]
      [COLOR=#6a5acd]          [/color][COLOR=#804040][b]END-IF[/b][/color]
      [COLOR=#6a5acd]          [/color][COLOR=#804040][b]STRING[/b][/color] TARIF-LISTE [COLOR=#804040][b]DELIMITED[/b][/color] [COLOR=#804040][b]BY[/b][/color] [COLOR=#ff00ff]SPACE[/color]
      [COLOR=#6a5acd]                 [/color]QUOTE       [COLOR=#804040][b]DELIMITED[/b][/color] [COLOR=#804040][b]BY[/b][/color] [COLOR=#ff00ff]SPACE[/color]
      [COLOR=#6a5acd]                 [/color]ZW-TARIF    [COLOR=#804040][b]DELIMITED[/b][/color] [COLOR=#804040][b]BY[/b][/color] [COLOR=#ff00ff]SPACE[/color]
      [COLOR=#6a5acd]                 [/color]QUOTE       [COLOR=#804040][b]DELIMITED[/b][/color] [COLOR=#804040][b]BY[/b][/color] [COLOR=#ff00ff]SPACE[/color]
      [COLOR=#6a5acd]                 [/color][COLOR=#804040][b]INTO[/b][/color] TARIF-LISTE
      [COLOR=#6a5acd]          [/color][COLOR=#804040][b]END-STRING[/b][/color]
      [COLOR=#6a5acd]       [/color][COLOR=#804040][b]END-IF[/b][/color]
      [COLOR=#6a5acd]     [/color][COLOR=#008080]END-PERFORM[/color]
      [COLOR=#0000ff]*    At End ')'[/color]
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]STRING[/b][/color] TARIF-LISTE [COLOR=#804040][b]DELIMITED[/b][/color] [COLOR=#804040][b]BY[/b][/color] [COLOR=#ff00ff]SPACE[/color]
      [COLOR=#6a5acd]            [/color][COLOR=#ff00ff]')'[/color]         [COLOR=#804040][b]DELIMITED[/b][/color] [COLOR=#804040][b]BY[/b][/color] [COLOR=#ff00ff]SPACE[/color]
      [COLOR=#6a5acd]            [/color][COLOR=#804040][b]INTO[/b][/color] TARIF-LISTE
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]END-STRING[/b][/color]
      [COLOR=#0000ff]*    Close Cursor[/color]
      [COLOR=#6a5acd]     [/color]EXEC SQL
      [COLOR=#6a5acd]       [/color][COLOR=#804040][b]CLOSE[/b][/color] C140
      [COLOR=#6a5acd]     [/color]END-EXEC.

3. Then the main processing paragraf is here
Code:
       [COLOR=#804040][b]VERARBEITUNG-DA[/b][/color].
      [COLOR=#6a5acd]     [/color][COLOR=#008080]PERFORM[/color] PREPARE-SELECT-R000090V
      [COLOR=#6a5acd]     [/color][COLOR=#008080]PERFORM[/color] OPEN-CURSOR-R000090V
      [COLOR=#0000ff]*    Processing in Loop[/color]
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]MOVE[/b][/color] SQLCODE [COLOR=#804040][b]TO[/b][/color] ZW-SQLCODE90
      [COLOR=#6a5acd]     [/color][COLOR=#008080]PERFORM[/color] [COLOR=#804040][b]UNTIL[/b][/color] ZW-SQLCODE90 [COLOR=#804040][b]NOT[/b][/color] = [COLOR=#ff00ff]ZERO[/color]
      [COLOR=#6a5acd]       [/color][COLOR=#008080]PERFORM[/color] FETCH-NEXT-R000090V
      [COLOR=#6a5acd]       [/color][COLOR=#804040][b]MOVE[/b][/color] SQLCODE [COLOR=#804040][b]TO[/b][/color] ZW-SQLCODE90
      [COLOR=#0000ff]*      if exists next record, i.e. if FETCH was ok[/color]
      [COLOR=#6a5acd]       [/color][COLOR=#804040][b]IF[/b][/color] ZW-SQLCODE90 = [COLOR=#ff00ff]ZERO[/color]
      [COLOR=#0000ff]*         Select fields from table R000090T[/color]
      [COLOR=#6a5acd]          [/color][COLOR=#804040][b]MOVE[/b][/color] BSSTAMMNR [COLOR=#804040][b]OF[/b][/color] R000090T [COLOR=#804040][b]TO[/b][/color] WS-BSSTAMMNR
      [COLOR=#6a5acd]          [/color][COLOR=#804040][b]MOVE[/b][/color] BSVNR     [COLOR=#804040][b]OF[/b][/color] R000090T [COLOR=#804040][b]TO[/b][/color] WS-BSVNR
      [COLOR=#6a5acd]          [/color][COLOR=#804040][b]MOVE[/b][/color] KONTOART  [COLOR=#804040][b]OF[/b][/color] R000090T [COLOR=#804040][b]TO[/b][/color] WS-KONTOART
      [COLOR=#6a5acd]          [/color][COLOR=#804040][b]MOVE[/b][/color] LOESCHMKM [COLOR=#804040][b]OF[/b][/color] R000090T [COLOR=#804040][b]TO[/b][/color] WS-LOESCHMKM
      [COLOR=#6a5acd]          [/color][COLOR=#804040][b]MOVE[/b][/color] TARIF     [COLOR=#804040][b]OF[/b][/color] R000090T [COLOR=#804040][b]TO[/b][/color] WS-TARIF
      [COLOR=#6a5acd]          [/color][COLOR=#804040][b]MOVE[/b][/color] ZINSSATZ  [COLOR=#804040][b]OF[/b][/color] R000090T [COLOR=#804040][b]TO[/b][/color] WS-ZINSSATZ
      [COLOR=#0000ff]*         Process selected fields [/color]
      [COLOR=#6a5acd]          [/color][COLOR=#008080]PERFORM[/color] VERARBEITE-SATZ-R000090V
      [COLOR=#6a5acd]             [/color][COLOR=#804040][b]THRU[/b][/color] VERARBEITE-SATZ-R000090V-EXIT
      [COLOR=#6a5acd]       [/color][COLOR=#804040][b]END-IF[/b][/color]
      [COLOR=#6a5acd]     [/color][COLOR=#008080]END-PERFORM[/color]
      [COLOR=#6a5acd]     [/color].

with these temorary paragraphs for preparing select statement and working with cursor (opening, closing, fetching)
Code:
       [COLOR=#804040][b]PREPARE-SELECT-R000090V[/b][/color].
      [COLOR=#6a5acd]     [/color][COLOR=#008080]PERFORM[/color] ERMITTLE-TARIFE
      [COLOR=#0000ff]*    Constructed SQL-SELECT into retazca[/color]
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]MOVE[/b][/color] SELECT-R000090V [COLOR=#804040][b]TO[/b][/color] SQLSOURCE

      [COLOR=#0000ff]*    Declare SQL-Statement SELECT90[/color]
      [COLOR=#6a5acd]     [/color]EXEC SQL
      [COLOR=#6a5acd]       [/color]DECLARE SELECT90 STATEMENT
      [COLOR=#6a5acd]     [/color]END-EXEC

      [COLOR=#0000ff]*    Declare Cursor for Statement[/color]
      [COLOR=#6a5acd]     [/color]EXEC SQL
      [COLOR=#6a5acd]       [/color]DECLARE CLOOP90 CURSOR [COLOR=#804040][b]FOR[/b][/color] SELECT90
      [COLOR=#6a5acd]     [/color]END-EXEC

      [COLOR=#0000ff]*    Prepare SQL-Statement form string SQLSOURCE[/color]
      [COLOR=#6a5acd]     [/color]EXEC SQL
      [COLOR=#6a5acd]       [/color]PREPARE SELECT90 [COLOR=#804040][b]FROM[/b][/color] :SQLSOURCE
      [COLOR=#6a5acd]     [/color]END-EXEC                  



       [COLOR=#804040][b]OPEN-CURSOR-R000090V[/b][/color].
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]IF[/b][/color] CLOOP-CLOSED
      [COLOR=#0000ff]*       Open Cursor[/color]
      [COLOR=#6a5acd]        [/color]EXEC SQL
      [COLOR=#6a5acd]          [/color][COLOR=#804040][b]OPEN[/b][/color] CLOOP90
      [COLOR=#6a5acd]        [/color]END-EXEC
      [COLOR=#6a5acd]        [/color][COLOR=#804040][b]MOVE[/b][/color] SQLSTATE [COLOR=#804040][b]TO[/b][/color] WS-SQLSTATE
      [COLOR=#6a5acd]        [/color][COLOR=#804040][b]IF[/b][/color] SQL-OK
      [COLOR=#6a5acd]           [/color][COLOR=#804040][b]SET[/b][/color] CLOOP-OPENED [COLOR=#804040][b]TO[/b][/color] [COLOR=#804040][b]TRUE[/b][/color]
      [COLOR=#6a5acd]        [/color][COLOR=#804040][b]END-IF[/b][/color]
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]END-IF[/b][/color].

       [COLOR=#804040][b]FETCH-NEXT-R000090V[/b][/color].
      [COLOR=#6a5acd]     [/color]EXEC SQL
      [COLOR=#6a5acd]       [/color]FETCH [COLOR=#804040][b]NEXT[/b][/color] [COLOR=#804040][b]FROM[/b][/color] CLOOP90 [COLOR=#804040][b]INTO[/b][/color] :R000090T
      [COLOR=#6a5acd]     [/color]END-EXEC.

       [COLOR=#804040][b]CLOSE-CURSOR-R000090V[/b][/color].
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]IF[/b][/color] CLOOP-OPENED
      [COLOR=#0000ff]*       Close Cursor[/color]
      [COLOR=#6a5acd]        [/color]EXEC SQL
      [COLOR=#6a5acd]          [/color][COLOR=#804040][b]CLOSE[/b][/color] CLOOP90
      [COLOR=#6a5acd]        [/color]END-EXEC
      [COLOR=#6a5acd]        [/color][COLOR=#804040][b]MOVE[/b][/color] SQLSTATE [COLOR=#804040][b]TO[/b][/color] WS-SQLSTATE
      [COLOR=#6a5acd]        [/color][COLOR=#804040][b]IF[/b][/color] SQL-OK [COLOR=#804040][b]OR[/b][/color] SQL-NOT-OPEN
      [COLOR=#6a5acd]           [/color][COLOR=#804040][b]SET[/b][/color] CLOOP-CLOSED [COLOR=#804040][b]TO[/b][/color] [COLOR=#804040][b]TRUE[/b][/color]
      [COLOR=#6a5acd]        [/color][COLOR=#804040][b]END-IF[/b][/color]
      [COLOR=#6a5acd]     [/color][COLOR=#804040][b]END-IF[/b][/color].

Look specially at paragraph PREPARE-SELECT-R000090V how do I create the SQL-statement from a constructed string and how do I declare cursor for that statement.

Happy COBOLing
:)
 
In the paragraph PREPARE-SELECT-R000090V I move the constructed SELECT-R000090V to string SQLSOURCE and then from this string I prepare the select-statement. I forgot it's definition in working storage - here is it:

Code:
[COLOR=#2e8b57][b]01 [/b][/color] SQLSOURCE                   [COLOR=#804040][b]PIC[/b][/color] X([COLOR=#ff00ff]2000[/color]).
 
It can be done with static SQL. You should realize that
Code:
where x in  ('1','2','3')
and
Code:
where x in  ('1','2','3','1','1','1','1','1')
generate the same result. DB2 performance does not suffer.
This means that you can code like this
Code:
01  w-group.
    49 w-gr-01 pic x(1).
    49 w-gr-02 pic x(1).
    49 w-gr-03 pic x(1).
    49 w-gr-04 pic x(1).
01  w-group-r redefines
    w-group    pic x(4).
move all '1' to w-group-r.
move     '2' to w-gr-02.
move     '3' to w-gr-03.
exec sql .... WHERE a in (:w-gr-01
                         ,:w-gr-02
                         ,:w-gr-03
                         ,:w-gr-04) end-exec
See what I mean?
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top