************************************************************************* 
      ** 
      ** Source File Name = inpcli.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 io-data variable.  It will then call the sqlgproc 
      **          API passing it the input SQLDA and the io-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. "inpcli".

       Data Division.
       Working-Storage Section.

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

      * Declare an Input/Output SQLDA Structure. 
       01  io-sqlda sync.
           05 io-sqldaid     pic x(8) value "IN-DA   ".
           05 io-sqldabc     pic s9(9) comp-5.
           05 io-sqln        pic s9(4) comp-5.
           05 io-sqld        pic s9(4) comp-5.
           05 io-sqlvar-entries occurs 0 to 99 times
              depending on io-sqld.
              10 io-sqlvar.
                 15 io-sqltype  pic s9(4) comp-5.
                 15 io-sqllen   pic s9(4) comp-5.
                 15 io-sqldata  usage is pointer.
                 15 io-sqlind   usage is pointer.
                 15 io-sqlname.
                    20 io-sqlnamel   pic s9(4) comp-5.
                    20 io-sqlnamec   pic x(30).

       EXEC SQL BEGIN DECLARE SECTION END-EXEC.
       01 dbname            pic x(8).
       01 userid            pic x(8).
       01 passwd.
         49 passwd-length   pic s9(4) comp-5 value 0.
         49 passwd-name     pic x(18).

       01 table-name     pic x(10) value "PRESIDENTS".
       01 io-data1       pic x(20) value "Washington          ".
       01 io-data2       pic x(20) value "Jefferson           ".
       01 io-data3       pic x(20) value "Lincoln             ".

      * Declare and Initialize Indicator Variables. 
       01  table-nameind pic s9(4) comp-5 value 0.
       01  io-dataind1   pic s9(4) comp-5 value 0.
       01  io-dataind2   pic s9(4) comp-5 value 0.
       01  io-dataind3   pic s9(4) comp-5 value 0.

       01  prog-name     pic x(12) value "inpsrv".
       EXEC SQL END DECLARE SECTION END-EXEC.

      * Declare a Null Pointer Variable. 
       77  null-ptr-int  pic s9(9) comp-5.
       77  null-ptr redefines null-ptr-int pointer.

       77 errloc         pic x(80).

       Procedure Division.
      * CONNECT TO DATABASE 
           display "Enter in the database name : " with no advancing.
           accept dbname.

           display "Enter your user id (default none): " 
                with no advancing.
           accept userid.

           if userid = spaces
             EXEC SQL CONNECT TO sample END-EXEC
           else
             display "Enter your password : " with no advancing
             accept passwd-name.

      * Passwords in a CONNECT statement must be entered in a VARCHAR format 
      * with the length of the input string. 
           move 0 to passwd-length.
           inspect passwd-name tallying passwd-length for characters
              before initial " ".

           EXEC SQL CONNECT TO :dbname USER :userid USING :passwd
               END-EXEC.
           move "CONNECT TO" to errloc.
           call "checkerr" using SQLCA errloc.

      * Call the Remote Procedure. 
           display "Use CALL with Host Variable to invoke the Server Pro
      -       "cedure".

           EXEC SQL CALL :prog-name                                     2a
                            (:table-name:table-nameind,
                            :io-data1:io-dataind1,
                            :io-data2:io-dataind2,
                            :io-data3:io-dataind3) END-EXEC.
           move "SQLCALL HV" to errloc.
           call "checkerr" using SQLCA errloc.
           display "Server Procedure Complete.".

      *    Initialize the Input/Output SQLDA Structure 
           move 4 to io-sqln.                                           1
           move 4 to io-sqld.

           move SQL-TYP-NCHAR to io-sqltype(1).
           set io-sqldata(1) to address of table-name.
           set io-sqlind(1)  to address of table-nameind.
           move 10 to io-sqllen(1).

           move SQL-TYP-NCHAR to io-sqltype(2).
           set io-sqldata(2) to address of io-data1.
           set io-sqlind(2)  to address of io-dataind1.
           move 20 to io-sqllen(2).

           move SQL-TYP-NCHAR to io-sqltype(3).
           set io-sqldata(3) to address of io-data2.
           set io-sqlind(3)  to address of io-dataind2.
           move 20 to io-sqllen(3).

           move SQL-TYP-NCHAR to io-sqltype(4).
           set io-sqldata(4) to address of io-data3.
           set io-sqlind(4)  to address of io-dataind3.
           move 20 to io-sqllen(4).

      * Call the Remote Procedure. 
           display "Use CALL with SQLDA to invoke the Server Procedure n
      -       "amed".
           EXEC SQL CALL :prog-name USING DESCRIPTOR                    2b
                                    :io-sqlda END-EXEC.
           move "SQLCALL DA" to errloc.
           call "checkerr" using SQLCA errloc.
           display "Server Procedure Complete.".

      * Disconnect from Remote Database. 
           EXEC SQL CONNECT RESET END-EXEC.
           stop run.
           exit.