************************************************************************* 
      ** 
      ** Source File Name = inpsrv.sqb  1.2 
      ** 
      ** Licensed Materials - Property of IBM 
      ** 
      ** (C) COPYRIGHT International Business Machines Corp. 1995, 1999  
      ** All Rights Reserved. 
      ** 
      ** US Government Users Restricted Rights - Use, duplication or 
      ** disclosure restricted by GSA ADP Schedule Contract with IBM Corp. 
      ** 
      ** 
      ** PURPOSE: This sample program demonstrates stored procedures.       
      **                                                                    
      **          There are two parts to this program:                      
      **              - the inpcli executable (placed on the client)        
      **              - the inpsrv library (placed on the server)           
      **                                                                    
      **          The inpcli routine will fill in an input SQLDA with 3     
      **          entries.  The entries are the names of presidents.  The   
      **          inpcli routine will also place the value "Presidents" in  
      **          the input-data variable.  It will then call the sqlgproc  
      **          API passing it the input SQLDA and the input-data         
      **          variable.                                                 
      **                                                                    
      **          The sqlgproc API will call the inpsrv routine stored      
      **          in the inpsrv library.                                    
      **                                                                    
      **          The inpsrv routine will take the information received     
      **          and create a table called "Presidents" in the "sample"    
      **          database.  It will then place the values it received in   
      **          the input SQLDA into the "Presidents" table.              
      **                                                                    
      ** For more information about these samples see the README file. 
      ** 
      ** For more information on programming in COBOL, see the: 
      **    -  "Programming in COBOL" section of the Application Development Guide. 
      ** 
      ** For more information on Building COBOL Applications, see the: 
      **    - "Building COBOL Applications" section of the Application Building Guide. 
      ** 
      ** For more information on the SQL language see the SQL Reference. 
      ** 
      ************************************************************************* 

       Identification Division.
       Program-ID. "inpsrv".

       Data Division.
       Working-Storage Section.

      * Copy Files for Constants and Structures 
       copy "sql.cbl".
       copy "sqlenv.cbl".
       copy "sqlca.cbl".

      * Declare Host Variables 
       EXEC SQL BEGIN DECLARE SECTION END-EXEC.
         01 insert-data       pic x(12).
         01 insert-statement  pic x(40).
       EXEC SQL END DECLARE SECTION END-EXEC.

      * Declare and Initialize SQL Statement Strings 
       01 create-string sync.
          05 stringc1         pic x(13) value "CREATE TABLE ".
          05 var-string1      pic x(10).
          05 stringc2         pic x(16) value " (NAME CHAR(20))".

       01 insert-string sync.
          05 stringi1         pic x(12) value "INSERT INTO ".
          05 var-string2      pic x(11).
          05 stringi2         pic x(11) value " VALUES (?)".

      * Declare Miscellaneous Variables 
       77 idx                 pic 9(4) comp-5.

       Linkage Section.

      * Declare Parameters 
       01 input-data.
          05 input-len        pic 9(4) comp-5.
          05 input-char       pic x(80).

       77 reserved1   pointer.
       77 reserved2   pointer.
       01  inout-sqlda sync.
           05 inout-sqldaid     pic x(8).
           05 inout-sqldabc     pic s9(9) comp-5.
           05 inout-sqln        pic s9(4) comp-5.
           05 inout-sqld        pic s9(4) comp-5.
           05 inout-sqlvar occurs 1 to 1489 times
              depending on inout-sqld.
              10 inout-sqltype  pic s9(4) comp-5.
              10 inout-sqllen   pic s9(4) comp-5.
              10 inout-sqldata  usage is pointer.
              10 inout-sqlind   usage is pointer.
              10 inout-sqlname.
                 15 inout-sqlnamel   pic s9(4) comp-5.
                 15 inout-sqlnamec   pic x(30).

      * Declare Miscellaneous Variables 
       77 temp-name           pic x(20).
       77 temp-ind            pic s9(4) comp-5.
       77 table-name          pic x(10).
       77 table-ind           pic s9(4) comp-5.

       01 O-SQLCA SYNC.
          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.
             10 SQLWARN8 PIC X.
             10 SQLWARN9 PIC X.
             10 SQLWARNA PIC X.
          05 SQLSTATE PIC X(5).

       Procedure Division using reserved1 reserved2 inout-sqlda O-SQLCA.1

       Main Section.
           EXEC SQL WHENEVER SQLERROR CONTINUE END-EXEC.

      * Create "President" Table 
           set address of table-name to inout-sqldata(1).
           move table-name to var-string1.
           move create-string to insert-statement.

           EXEC SQL EXECUTE IMMEDIATE :insert-statement END-EXEC.       2

           EXEC SQL WHENEVER SQLERROR GOTO :Error-Exit END-EXEC.

      * Prepare for Insert 
           move table-name to var-string2.
           move insert-string to insert-statement.
           EXEC SQL PREPARE INSERTSTMT FROM :insert-statement END-EXEC. 3

      * Insert President Names stored in Input SQLDA into Newly Created Table 
           perform Add-Rows varying idx from 2 by 1 until idx > 4.      4

      * Return the SQLCA Information to the Calling Program. 
           move SQLCA to O-SQLCA.
           EXEC SQL COMMIT END-EXEC.
           move SQLZ-DISCONNECT-PROC to return-code
           goback.                                                      5

       Add-Rows.
           set address of temp-name to inout-sqldata(idx).
           move temp-name to insert-data.
           EXEC SQL EXECUTE INSERTSTMT USING :insert-data END-EXEC.

      * To minimize network flow, set the input-only variable to null 
      * by setting its indicator value to -128 so that they won"t 
      * be resent back to the client program. 
           set address of temp-ind  to inout-sqlind(idx).
           move -128      to temp-ind.

       Error-Exit.
      * An Error has Occurred -- ROLLBACK and Return to Calling Program. 
           EXEC SQL WHENEVER SQLERROR CONTINUE END-EXEC.
           move SQLCA to O-SQLCA.
           EXEC SQL ROLLBACK END-EXEC.
           move SQLZ-DISCONNECT-PROC to return-code
           goback.