************************************************************************* 
      ** 
      ** Source File Name = dbauth.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 obtain and print out authorization information of the current 
      **    user to the currently attached database. 
      **    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 : 
      **       GET AUTHORIZATION     sqlgadau 
      ** 
      ** 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. "dbauth".

       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.
       01 st.
          05 stmt occurs 2 times pic x(40).

       Procedure Division.
       dbauth Section.
           display "Sample COBOL program: DBAUTH".

           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 " ".

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

           display "Administrative Authorizations for Current User".
           move SQL-AUTHORIZATION-SIZE to SQL-AUTHORIZATIONS-LEN.

      ******************************** 
      * GET AUTHORIZATION API called * 
      ******************************** 
           call "sqlgadau" using
                                 by reference SQL-AUTHORIZATIONS
                                 by reference sqlca
                           returning rc.
           move "getting authorization list" to errloc.
           call "checkerr" using SQLCA errloc.

           perform list-auth.

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

       End-dbauth. stop run.

      * printing out authorization information 
       list-auth Section.

           display "Direct SYSADM authority = " with no advancing.
           if SQL-SYSADM-AUTH equal 1 then
              display "YES"
           else
              display "NO".
           display " ".

           display "Direct SYSCTRL authority = " with no advancing.
           if SQL-SYSCTRL-AUTH equal 1 then
              display "YES"
           else
              display "NO".
           display " ".

           display "Direct SYSMAINT authority = " with no advancing.
           if SQL-SYSMAINT-AUTH equal 1 then
              display "YES"
           else
              display "NO".
           display " ".

           display "Direct DBADM authority = " with no advancing.
           if SQL-DBADM-AUTH equal 1 then
              display "YES"
           else
              display "NO".
           display " ".

           display "Direct CREATETAB authority = " with no advancing.
           if SQL-CREATETAB-AUTH equal 1 then
              display "YES"
           else
              display "NO".
           display " ".

           display "Direct BINDADD authority = " with no advancing.
           if SQL-BINDADD-AUTH equal 1 then
              display "YES"
           else
              display "NO".
           display " ".

           display "Direct CONNECT authority = " with no advancing.
           if SQL-CONNECT-AUTH equal 1 then
              display "YES"
           else
              display "NO".
           display " ".

           display "Direct CREATE-NOT-FENC authority = " with
                   no advancing.
           if SQL-CREATE-NOT-FENC-AUTH equal 1 then
              display "YES"
           else
              display "NO".
           display " ".

           display "Indirect SYSADM authority = " with no advancing.
           if SQL-SYSADM-GRP-AUTH equal 1 then
              display "YES"
           else
              display "NO".
           display " ".

           display "Indirect SYSCTRL authority = " with no advancing.
           if SQL-SYSCTRL-GRP-AUTH equal 1 then
              display "YES"
           else
              display "NO".
           display " ".

           display "Indirect SYSMAINT authority = " with no advancing.
           if SQL-SYSMAINT-GRP-AUTH equal 1 then
              display "YES"
           else
              display "NO".
           display " ".

           display "Indirect DBADM authority = " with no advancing.
           if SQL-DBADM-GRP-AUTH equal 1 then
              display "YES"
           else
              display "NO".
           display " ".

           display "Indirect CREATETAB authority = " with no advancing.
           if SQL-CREATETAB-GRP-AUTH equal 1 then
              display "YES"
           else
              display "NO".
           display " ".

           display "Indirect BINDADD authority = " with no advancing.
           if SQL-BINDADD-GRP-AUTH equal 1 then
              display "YES"
           else
              display "NO".
           display " ".

           display "Indirect CONNECT authority = " with no advancing.
           if SQL-CONNECT-GRP-AUTH equal 1 then
              display "YES"
           else
              display "NO".
           display " ".

           display "Indirect CREATE-NOT-FENC authority = " with
                   no advancing.
           if SQL-CREATE-NOT-FENC-GRP-AUTH equal 1 then
              display "YES"
           else
              display "NO".
           display " ".

       end-list-auth. exit.