INF: Using a Stored Procedure in a Cursor Definition

ID: Q67172


The information in this article applies to:


SUMMARY

The code listed below demonstrates an extra feature of Microsoft Embedded SQL for COBOL and Microsoft SQL Server--the ability to use a stored procedure in a cursor definition. This sample program uses sp_who in the cursor definition to determine who is currently logged onto the SQL server. The basic idea is to declare the cursor, prepare the cursor statement as a call to a stored procedure, open the cursor, and fetch each row until an error is encountered or all rows have been returned.


MORE INFORMATION

For more information on this topic, please refer to the "Microsoft Embedded SQL for COBOL Programmer's Reference" manual.

Sample Code


    WORKING-STORAGE SECTION.

    EXEC SQL INCLUDE SQLCA END-EXEC

    EXEC SQL BEGIN DECLARE SECTION END-EXEC
    01  spid        pic x(6).                 *> sp_who.spid
    01  id-status   pic x(10).                *> sp_who.status
    01  loginame    pic x(12).                *> sp_who.loginame
    01  hostname    pic x(10).                *> sp_who.hostname
    01  blk         pic x(3).                 *> sp_who.blk
    01  dbname      pic x(10).                *> sp_who.dbname
    01  cmd         pic x(16).                *> sp_who.cmd
    01  prep        pic x(80).                *> prepared statements

    EXEC SQL END DECLARE SECTION END-EXEC

    PROCEDURE DIVISION.

   * Declare cursor, prepare stored procedure call, open cursor, *
   * fetch rows, close cursor. *

    EXEC SQL
      declare cur cursor for who
    END-EXEC
    if sqlcode not = 0
      perform sql-error
    else
      move "sp_who" to prep
      EXEC SQL
        prepare who from :prep
      END-EXEC
      if sqlcode not = 0
        perform sql-error
      else
        EXEC SQL
          open cur
        END-EXEC

   * Ignore warnings about truncated character strings. *

        if sqlcode not = 0 and sqlcode not = 1
          perform sql-error
        end-if
        display spaces
        display "spid  status    loginame    hostname  blk db

   -            "name    cmd"
        display "----  --------- ----------- --------- --- --
   -            "------- ----------------"
   * When no more rows are returned, sqlcode = 100. *
        perform fetch-rows until sqlcode < 0 or sqlcode = 100
        EXEC SQL
          close cur
        END-EXEC
        if sqlcode not = 0
          perform sql-error
        end-if
      end-if
    end-if
    stop run.

    fetch-rows.

   * Fetch each row and display it. *

    EXEC SQL
      fetch cur into :spid, :id-status, :loginame,
                          :hostname, :blk, :dbname, :cmd
    END-EXEC
    if sqlcode = 0
      display spid id-status loginame hostname blk " " dbname cmd
    else
      if sqlcode not = 100
        perform sql-error
      end-if
    end-if.

    sql-error.
    display "SQL error SQLCODE=" sqlcode. 

Additional query words:


Keywords          : kbprg SSrvCobol SSrvProg 
Version           : WINDOWS:4.2
Platform          : WINDOWS 
Issue type        : 

Last Reviewed: July 13, 1999