Method 4 example using SQLDAs

Following is an example that uses prepare and fetch with dynamic parameter markers and SQL descriptors.

       IDENTIFICATION DIVISION.
       PROGRAM-ID.  unittest.
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SOURCE-COMPUTER.  xyz.
       OBJECT-COMPUTER.  xyz.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       exec sql begin declare section end-exec
        01 uid pic x(10).
        01 pass pic x(10).
       exec sql end declare section end-exec
        01 input-descriptor.
                09 SD-SQLN PIC S9(4) COMP.
                09 SD-SQLD PIC S9(4) COMP.
                09 SD-COLUMN OCCURS 3 TIMES.
                 19 SD-DATAFMT.
                       29 SQL--NM PIC X(132).
                       29 SQL--NMLEN PIC S9(9) COMP.
                     29 SQL--DATATYPE PIC S9(9) COMP.    
                     29 SQL--FORMAT PIC S9(9) COMP.         
                         29 SQL--MAXLENGTH PIC S9(9) COMP.              
                         29 SQL--SCALE PIC S9(9) COMP.                  
                                29 SQL--PRECISION PIC S9(9) COMP.                      
                         29 SQL--STTUS PIC S9(9) COMP.                  
                     29 SQL--COUNT PIC S9(9) COMP.          
                               29 SQL--USERTYPE PIC S9(9) COMP.                       
                         29 SQL--LOCALE PIC S9(9) COMP.                 
                19 SD-SQLDATA PIC S9(9) COMP.                
                19 SD-SQLIND PIC S9(4) COMP.            
                19 SD-SQLLEN PIC S9(9) COMP.            
                19 SD-SQLMORE PIC S9(9) COMP.
        01 output-descriptor.
                09 SD-SQLN PIC S9(4) COMP.
                09 SD-SQLD PIC S9(4) COMP.
                09 SD-COLUMN OCCURS 3 TIMES.
                 19 SD-DATAFMT.
                     29 SQL--NM PIC X(132).
                     29 SQL--NMLEN PIC S9(9) COMP.
                     29 SQL--DATATYPE PIC S9(9) COMP.    
                     29 SQL--FORMAT PIC S9(9) COMP.         
                         29 SQL--MAXLENGTH PIC S9(9) COMP.              
                         29 SQL--SCALE PIC S9(9) COMP.                  
                                29 SQL--PRECISION PIC S9(9) COMP.                      
                         29 SQL--STTUS PIC S9(9) COMP.                  
                     29 SQL--COUNT PIC S9(9) COMP.          
                               29 SQL--USERTYPE PIC S9(9) COMP.                       
                         29 SQL--LOCALE PIC S9(9) COMP.                 
                19 SD-SQLDATA PIC S9(9) COMP.                
                19 SD-SQLIND PIC S9(4) COMP.            
                19 SD-SQLLEN PIC S9(9) COMP.            
                19 SD-SQLMORE PIC S9(9) COMP.
    01 conversion-tester pic s9(4) comp-3.
    01 charvar pic x(20).
    01 temp-int-1 pic s9(9) comp.
    01 temp-int-2 pic s9(9) comp.
    01 temp-int-3 pic s9(9) comp.
    01 temp-int-4 pic s9(9) comp.
    01 SQLCODE pic s9(9) comp.
    01 retcode pic s9(9) comp.
PROCEDURE DIVISION.
P0.
     MOVE "sa" TO uid.
     move" "to pass.
     exec sql connect :uid identified by :pass end-exec.
* setup
     exec sql whenever sqlwarning perform err-paraend-exec.
      exec sql drop table example end-exec.
      exec sql create table example (fruit char(30),
            number int)end-exec.
      exec sql insert example values (‘tangerine’, 1) end-exec.
      exec sql insert example values (‘pomegranate’, 2) end-exec.
      exec sql insert example values (‘banana’, 3) end-exec.
* test functionality using execute
      exec sql prepare statement from 
          "select fruit from example where number = ?" end-exec.
      exec sql describe input statement using descriptor 
           input-descriptor end-exec.
      if sd-sqld of input-descriptor not equal 1 
             or  sql--datatype of sd-datafmt of sd-column  of
             input-descriptor (1) not equal cs-int-type
            display "failed on first describe input"
            move cs-fail to p-retcode
      end-if.
      move 1 to temp-int-1.
      move 4 to temp-int-2.
      move 0 to temp-int-3.
      call "SYBSETSQLDA" using retcode input-descriptor 
             temp-int-1 conversion-tester syb-snines-pic 
             temp-int-2 temp-int-3 syb-comp3-usage syb-no-sign .
      move 2 to conversion-tester.
      exec sql describe output statement using descriptor
      output-descriptor end-exec.
      if sd-sqld of output-descriptor not equal 
             or  sql--datatype of sd-datafmt of sd-column  of
             output-descriptor (1) not equal cs-char-type
             display "failed on first describe output"
            move cs-fail to p-retcode
      end-if.
      move 1 to temp-int-1.
      move 20 to temp-int-2.
      move 0 to temp-int-3.
      call "SYBSETSQLDA" using retcode output-descriptor 
            temp-int-1 charvar syb-x-pic temp-int-2 
            temp-int-3 syb-no-usage syb-no-sign .
      exec sql execute statement into descriptor 
            output-descriptor using descriptor 
            input-descriptor end-exec.
      display "Expected pomegranate, got "charvar.
      exec sql deallocate prepare statement end-exec.
      exec sql prepare statement from
            "select number from example where fruit = ?" end-exec.
      exec sql declare c cursor for statement end-exec.
      exec sql describe input statement using descriptor
            input-descriptor end-exec.
      move 1 to temp-int-1.
      move 20 to temp-int-2.
      move 0 to temp-int-3.
      call "SYBSETSQLDA" using retcode input-descriptor 
            temp-int-1 charvar syb-x-pic temp-int-2 
            temp-int-3 syb-no-usage syb-no-sign .
      move "banana" to charvar.
      exec sql open c using descriptor input-descriptor end-exec.
      exec sql describe output statement using descripto
            output-descriptor end-exec.
      move 1 to temp-int-1.
      move 20 to temp-int-2.
      move 0 to temp-int-3.
      call "SYBSETSQLDA" using retcode output-descriptor 
           temp-int-1 charvar syb-x-pic temp-int-2 temp-int-3 
           syb-no-usage syb-no-sign .
      exec sql fetch c into descriptor output-descriptor 
            end-exec. 
      display "Expected 3, got "charvar.
      exec sql commit work end-exec.
      end program unittest.