************************************************************************* 
      ** 
      ** Source File Name = tload.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: to show the usage of LOAD and QUIESCE APIs 
      ** 
      ** APIs : 
      **        EXPORT                          sqlgexpr 
      **        QUIESCE TABLESPACES FOR TABLE   sqlgvqdp 
      **        LOAD                            sqlgload 
      ** 
      ** 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. "tload".

       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 stmt                pic x(254).
       77 impstmt             pic x(254).

       77 rc                  pic s9(9) comp-5.

      * Variables for IMPORT/EXPORT APIs 
       77 msgfile-x           pic x(10) value "EXPMSG.TXT".
       77 msgfile-x-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.

      * Variables for the QUIESCE TABLESPACES FOR TABLE API 
       77 tname-len     pic s9(4) comp-5 value +9.
       77 quiesce-mode  pic s9(4) comp-5 value +2.
       77 tname         pic x(19) value "loadtable".

      * Variables for the LOAD API 
       77 lclfile-len   pic s9(4) comp-5 value +7.
       77 lclfile       pic x(7)  value "LOADMSG".
       77 rmtfile-len   pic s9(4) comp-5 value +8.
       77 rmtfile       pic x(8)  value "RLOADMSG".
       77 null-ind      pic s9(9) comp-5.

       01 datafile-len1          pic 9(4)  comp-5 value 12.

       01 datafile-ixf.
           05 datafile-len       pic 9(9)  comp-5 value 12.
           05 datafile           pic x(12) value "EXPTABLE.IXF".

       01 work-dir-ixf.
           05 work-dir-len       pic 9(9)  comp-5 value 1.
           05 work-dir-path      pic x(12) value ".".

       01 copy-dir-ixf.
           05 copy-dir-len       pic 9(9)  comp-5 value 1.
           05 copy-dir-path      pic x(12) value ".".

       01 lob-dir-ixf.
           05 lob-dir-len        pic 9(9)  comp-5 value 1.
           05 lob-dir-path       pic x(12) value ".".

       01 datafile-list.
           05 SQL-MEDIA-TYPE         PIC X.
           05 SQL-FILLER             PIC X(3).
           05 SQL-SESSIONS           PIC S9(9) COMP-5.
           05 SQL-TARGET.
               10 SQL-MEDIA          USAGE IS POINTER.
               10 SQL-VENDOR         REDEFINES SQL-MEDIA
                                     USAGE IS POINTER.
               10 SQL-LOCATION       REDEFINES SQL-MEDIA
                                     USAGE IS POINTER.
               10 FILLER             REDEFINES SQL-MEDIA
                                     PIC X(4).

       01 work-dir.
           05 SQL-MEDIA-TYPE         PIC X.
           05 SQL-FILLER             PIC X(3).
           05 SQL-SESSIONS           PIC S9(9) COMP-5.
           05 SQL-TARGET.
               10 SQL-MEDIA          USAGE IS POINTER.
               10 SQL-VENDOR         REDEFINES SQL-MEDIA
                                     USAGE IS POINTER.
               10 SQL-LOCATION       REDEFINES SQL-MEDIA
                                     USAGE IS POINTER.
               10 FILLER             REDEFINES SQL-MEDIA
                                     PIC X(4).

       01 copy-target.
           05 SQL-MEDIA-TYPE         PIC X.
           05 SQL-FILLER             PIC X(3).
           05 SQL-SESSIONS           PIC S9(9) COMP-5.
           05 SQL-TARGET.
               10 SQL-MEDIA          USAGE IS POINTER.
               10 SQL-VENDOR         REDEFINES SQL-MEDIA
                                     USAGE IS POINTER.
               10 SQL-LOCATION       REDEFINES SQL-MEDIA
                                     USAGE IS POINTER.
               10 FILLER             REDEFINES SQL-MEDIA
                                     PIC X(4).

       01 lobpaths.
           05 SQL-MEDIA-TYPE         PIC X.
           05 SQL-FILLER             PIC X(3).
           05 SQL-SESSIONS           PIC S9(9) COMP-5.
           05 SQL-TARGET.
               10 SQL-MEDIA          USAGE IS POINTER.
               10 SQL-VENDOR         REDEFINES SQL-MEDIA
                                     USAGE IS POINTER.
               10 SQL-LOCATION       REDEFINES SQL-MEDIA
                                     USAGE IS POINTER.
               10 FILLER             REDEFINES SQL-MEDIA
                                     PIC X(4).

      * COMMON Variables among the above APIs 
       77 reserved-x    pic s9(9) comp-5 value 0.
       77 msgfile-len   pic s9(4) comp-5.
       77 filetype-len  pic s9(4) comp-5 value 3.
       77 msgfile       pic x(1025).
       77 filetype      pic x(3)  value "IXF".
       77 callerac      pic s9(4) comp-5.

       Procedure Division.
       tload Section.
           display "Sample COBOL program: TLOAD".

           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 id,name from staff" to stmt.
           move "insert into imptable (id,name)" 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 25                to SQL-TCOLSTRG-LEN.
           move SQL-METH-D        to SQL-DCOLMETH.

           move 0                 to SQL-FILETMOD-LEN of SQL-FILETMOD.

      * 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 "Exporting id and name from staff table into file: ",
                   datafile.

      ********************* 
      * EXPORT API called * 
      ********************* 
           call "sqlgexpr" using
                                 by value     datafile-len1
                                 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 just in case it already exists 
           move "drop table loadtable" to statement.
           EXEC SQL EXECUTE IMMEDIATE :statement END-EXEC.
           EXEC SQL COMMIT END-EXEC.

      * create the table loadtable 
            EXEC SQL CREATE TABLE loadtable (num char(6),
                 format varchar(10))
                END-EXEC.
           move "CREATE TABLE loadtable" to errloc.
           call "checkerr" using SQLCA errloc.
           EXEC SQL COMMIT END-EXEC.
           move "COMMIT the CREATE TABLE" to errloc.
           call "checkerr" using SQLCA errloc.

      ********************************* 
      * QUIESCE TABLESPACES FOR TABLE * 
      ********************************* 
           move SQLU-QUIESCEMODE-EXCLUSIVE to quiesce-mode.
           call "sqlgvqdp" using
                                 by value tname-len
                                 by reference   tname
                                 by value       quiesce-mode
                                 by reference   reserved-x
                                 by reference   sqlca
                           returning rc.

           move "QUIESCE TABLESPACES FOR TABLE" to errloc.
           call "checkerr" using SQLCA errloc.

           display "Tablespace for loadtable has been quiesced.".

      ******** 
      * LOAD * 
      ******** 

      * initialize variables for the Load API 
           move SQLU-SERVER-LOCATION
                            to SQL-MEDIA-TYPE of datafile-list.
           move +1          to SQL-SESSIONS   of datafile-list.

      * set the pointer 
           set SQL-MEDIA of datafile-list
                            to address of datafile-len.

           move SQLU-INITIAL to callerac.

           move +0          to SQL-SESSIONS   of work-dir.
           move SQLU-LOCAL-MEDIA
                            to SQL-MEDIA-TYPE of work-dir.
           set SQL-LOCATION of work-dir to address of work-dir-len.

           move +0          to SQL-SESSIONS   of copy-target.
           move SQLU-LOCAL-MEDIA
                            to SQL-MEDIA-TYPE of copy-target.
           set SQL-LOCATION of work-dir to address of copy-dir-len.

           move +0          to SQL-SESSIONS   of lobpaths.
           move SQLU-LOCAL-MEDIA
                            to SQL-MEDIA-TYPE of lobpaths.
           set SQL-LOCATION of lobpaths to address of lob-dir-len.

           move +0 to   null-ind.
           move +0 to  reserved-x.

           initialize SQLULOAD-IN.
           move SQLULOAD-IN-SIZE to SQL-SIZE-OF-STRUCT   of SQLULOAD-IN.
           move +0               to SQL-SAVECNT          of SQLULOAD-IN.
           move +0               to SQL-RESTARTCOUNT     of SQLULOAD-IN.
           move +0               to SQL-ROWCNT           of SQLULOAD-IN.
           move +0               to SQL-WARNINGCNT       of SQLULOAD-IN.
           move +0               to SQL-DATA-BUFFER-SIZE of SQLULOAD-IN.
           move +0               to SQL-SORT-BUFFER-SIZE of SQLULOAD-IN.
           move +0               to SQL-HOLD-QUIESCE     of SQLULOAD-IN.
           move " "              to SQL-RESTARTPHASE     of SQLULOAD-IN.
           move SQLU-STATS-NONE  to SQL-STATSOPT         of SQLULOAD-IN.

           move SQL-METH-D       to SQL-DCOLMETH         of SQL-DCOLDATA.

           initialize SQLULOAD-OUT.
           move SQLULOAD-OUT-SIZE to
                              SQL-SIZE-OF-STRUCT of  SQLULOAD-out.

           move "insert into loadtable " to impstmt.
           move impstmt                  to SQL-TCOLSTRG-DATA.
           move 21                       to SQL-TCOLSTRG-LEN.
           move SQL-DEL                  to filetype.

      * Call LOAD API 
           call "sqlgload" using
                                 by value       filetype-len
                                 by value       lclfile-len
                                 by value       rmtfile-len
                                 by reference   datafile-list
                                 by reference   lobpaths
                                 by reference   SQL-DCOLDATA
                                 by reference   SQL-TCOLSTRG
                                 by reference   filetype
                                 by reference   SQL-FILETMOD
                                 by reference   lclfile
                                 by reference   rmtfile
                                 by value       callerac
                                 by reference   SQLULOAD-IN
                                 by reference   SQLULOAD-OUT
                                 by reference   work-dir
                                 by reference   copy-target
                                 by reference   null-ind
                                 by reference   reserved-x
                                 by reference   sqlca
                           returning rc.
           move "LOAD" to errloc.
           call "checkerr" using SQLCA errloc.

           display "Load of table LOADTABLE is complete.".
           display "Rows loaded: ", SQL-ROWS-LOADED.
           display "Rows committed: ", SQL-ROWS-COMMITTED.

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

       End-tload. stop run.