************************************************************************* 
      ** 
      ** Source File Name = impexp.sqb  1.3 
      ** 
      ** 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 program is an example of how APIs are implemented in order to 
      **   export and import tables and table data. 
      **   The order of the program is as follows 
      **       - export a table to a comma-delimited text file 
      **       - import the comma-delimited text file to a DB2 table 
      **   This program needs the embedded SQL calls in order to connect to 
      **   an existing database, then to create a temporary table to work with. 
      ** 
      **    APIs USED : 
      **            IMPORT TO             sqlgimpr 
      **            EXPORT                sqlgexpr 
      ** 
      ** 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. "impexp".

       Data Division.
       Working-Storage Section.

           copy "sqlenv.cbl".
           copy "sqlca.cbl".
           copy "sqlutil.cbl".

           EXEC SQL BEGIN DECLARE SECTION END-EXEC.

       77 statement         pic x(254).

       01 userid            pic x(8).
       01 passwd.
         49 passwd-length   pic s9(4) comp-5 value 0.
         49 passwd-name     pic x(18).

           EXEC SQL END DECLARE SECTION END-EXEC.

       77 errloc              pic x(80).
       77 rc                  pic s9(9) comp-5.
       77 stmt                pic x(254).
       77 impstmt             pic x(254).

      * variables for import/export APIs 
       77 datafile            pic x(12) value "EXPTABLE.IXF".
       77 datafile-len        pic 9(4) comp-5 value 12.
       77 msgfile-x           pic x(10) value "EXPMSG.TXT".
       77 msgfile-x-len       pic 9(4) comp-5 value 10.
       77 msgfile-m           pic x(10) value "IMPMSG.TXT".
       77 msgfile-m-len       pic 9(4) comp-5 value 10.
       77 fileformat          pic x(3) value "DEL".
       77 fileformat-len      pic 9(4) comp-5 value 3.

       Procedure Division.
       impexp Section.
           display "Sample COBOL program: IMPEXP".

           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.

           inspect passwd-name tallying passwd-length for characters
              before initial " ".

           display " ".

      * need to preset the size of structure field and counts 
           move "select name,id from staff" to stmt.
           move "insert into imptable (name,id)" to impstmt.
           move SQLUEXPT-OUT-SIZE to SQL-SIZE-OF-UEXPT-OUT.
           move 0                 to SQL-COMMITCNT.
           move 0                 to SQL-RESTARTCNT.
           move stmt              to SQL-TCOLSTRG-DATA.
           move 254               to SQL-TCOLSTRG-LEN.
           move SQL-METH-D        to SQL-DCOLMETH.

      * connecting to SAMPLE database. 
           EXEC SQL CONNECT TO sample USER :userid USING :passwd
                END-EXEC.
           move "CONNECT TO SAMPLE" to errloc.
           call "checkerr" using SQLCA errloc.

           display "export name,id from staff table into file: ",
                   datafile.

      ********************* 
      * EXPORT API called * 
      ********************* 
           call "sqlgexpr" using
                                 by value     datafile-len
                                 by value     fileformat-len
                                 by value     msgfile-x-len
                                 by reference datafile
                                 by value     0
                                 by value     0
                                 by reference SQL-DCOLDATA
                                 by reference SQL-TCOLSTRG
                                 by reference fileformat
                                 by reference SQL-FILETMOD
                                 by reference msgfile-x
                                 by value     SQLU-INITIAL
                                 by reference SQL-UEXPT-OUT
                                 by value     0
                                 by reference sqlca
                             returning rc.
           move "exporting table" to errloc.
           call "checkerr" using SQLCA errloc.

           display "rows exported : ", SQL-ROWSEXPORTED.

      * drop the table before creating it, just in case it already exists 
           move "drop table imptable" to statement.
           EXEC SQL EXECUTE IMMEDIATE :statement END-EXEC.
           EXEC SQL COMMIT END-EXEC.
           move "COMMIT the DROP TABLE" to errloc.
           call "checkerr" using SQLCA errloc.

      * create a temporary table to import into 
           EXEC SQL CREATE TABLE imptable (name varchar(15), id int)
                END-EXEC.
           move "CREATE TABLE" to errloc.
           call "checkerr" using SQLCA errloc.

      * need to preset the size of structure field and counts 
           move SQLUIMPT-IN-SIZE  to SQL-SIZE-OF-UIMPT-IN.
           move SQLUIMPT-OUT-SIZE to SQL-SIZE-OF-UIMPT-OUT.
           move 0                 to SQL-COMMITCNT.
           move 0                 to SQL-RESTARTCNT.
           move impstmt           to SQL-TCOLSTRG-DATA.
           move 254               to SQL-TCOLSTRG-LEN.
           move SQL-METH-D        to SQL-DCOLMETH.
           display "importing the file ", datafile, " into 'imptable'".

      ********************* 
      * IMPORT API called * 
      ********************* 
           call "sqlgimpr" using
                                 by value     datafile-len
                                 by value     fileformat-len
                                 by value     msgfile-m-len
                                 by reference datafile
                                 by value     0
                                 by reference SQL-DCOLDATA
                                 by reference SQL-TCOLSTRG
                                 by reference fileformat
                                 by reference SQL-FILETMOD
                                 by reference msgfile-m
                                 by value     SQLU-INITIAL
                                 by reference SQL-UIMPT-IN
                                 by reference SQL-UIMPT-OUT
                                 by value     0
                                 by value     0
                                 by reference sqlca
                             returning rc.
           move "importing table" to errloc.
           call "checkerr" using SQLCA errloc.

           display "rows imported : ", SQL-ROWSINSERTED.
           display "rows committed : ", SQL-ROWSCOMMITTED.

           EXEC SQL CONNECT RESET END-EXEC.
           move "CONNECT RESET" to errloc.
           call "checkerr" using SQLCA errloc.

       End-impexp. stop run.