Example

The following is an example of a program that creates a stored procedure "mfexecsptest" using data source "SQLServer 2000" and then retrieves data from "publishers" table using a cursor "c1" with dynamic SQL.

$SET SQL
 WORKING-STORAGE SECTION.

 EXEC SQL INCLUDE SQLCA  END-EXEC

*> after an sql error this has the full message text
 01 MFSQLMESSAGETEXT  PIC X(250).
 01 IDX               PIC X(04)  COMP-5.

 EXEC SQL BEGIN DECLARE SECTION  END-EXEC
*> Put your host variables here if you need to port
*> to other COBOL compilers

 01  stateParam          pic xx.
 01  pubid               pic x(4).
 01  pubname             pic x(40).
 01  pubcity             pic x(20).

 01  sql-stat            pic x(256).

 EXEC SQL END DECLARE SECTION END-EXEC

 PROCEDURE DIVISION.

     EXEC SQL
         WHENEVER SQLERROR perform OpenESQL-Error
     END-EXEC

     EXEC SQL
         CONNECT TO 'SQLServer 2000' USER 'SA'
     END-EXEC

*> Put your program logic/SQL statements here

     EXEC SQL
         create procedure mfexecsptest
                 (@stateParam char(2) = 'NY' ) as

         select pub_id, pub_name, city from publishers
          where state = @stateParam
     END-EXEC

     exec sql
         declare c1 scroll cursor for dsql2 for read only
     end-exec

     move "{call mfexecsptest(?)}" to sql-stat
     exec sql prepare dsql2 from :sql-stat end-exec

     move "CA" to stateParam
     exec sql
         open c1 using :stateParam
     end-exec

     display "Testing cursor with stored procedure"
     perform until exit
         exec sql
             fetch c1 into :pubid, :pubname, :pubcity
         end-exec

         if sqlcode = 100
             exec sql close c1 end-exec
             exit perform
         else
             display pubid " " pubname " " pubcity
         end-if
     end-perform

      EXEC SQL close c1  END-EXEC

      EXEC SQL DISCONNECT CURRENT END-EXEC
      EXIT PROGRAM.
      STOP RUN.
*> Default sql error routine / modify to stop program if
*> needed
 OpenESQL-Error Section.

     display "SQL Error = " sqlstate " " sqlcode
     display MFSQLMESSAGETEXT
      *> stop run
     exit.