************************************************************************* 
      ** 
      ** Source File Name = outsrv.sqb 
      ** 
      ** Licensed Materials - Property of IBM 
      ** 
      ** (C) COPYRIGHT International Business Machines Corp. 1995, 2000  
      ** 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 outcli executable (placed on the client)        
      **              - the outsrv library (placed on the server)           
      **                                                                    
      **          Instead of connecting to a remote database                
      **                                                                    
      **          The outcli routine will allocate and initialize a one     
      **          variable output SQLDA.  The outcli routine will then      
      **          call the sqlgproc API passing it the output SQLDA.        
      **                                                                    
      **          The sqlgproc API will call the outsrv routine stored      
      **          in the outsrv library.                                    
      **                                                                    
      **          The outsrv routine will obtain the median salary of       
      **          employees in the "staff" table of the "sample" database.  
      **          This value will be placed in the output SQLDA and         
      **          returned to the outcli routine.  The outcli routine will  
      **          then print out the median salary.                         
      **                                                                    
      ** 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. "outsrv".

       Data Division.
       Working-Storage Section.

      * Copy Files for Constants and Structures 

       copy "sql.cbl".
       copy "sqlenv.cbl".                                               1
       copy "sqlca.cbl".

      * Declare Host Variables 
       EXEC SQL BEGIN DECLARE SECTION END-EXEC.
         77  num-records  pic s9(9) comp-5 .
         01  stmt.
             49 stmt-len pic s9(4) comp-5.
             49 stmt-str pic x(50).
       EXEC SQL END DECLARE SECTION END-EXEC.

      * Declare Miscellaneous Variables 
       77  cntr1 pic s9(9) comp-5 .
       77  cntr2 pic s9(9) comp-5 .

       Linkage Section.

      * Declare Parameters 
       77  reserved1   pointer.
       77  reserved2   pointer.
       77  inout-sqlda pointer.

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

       Main Section.
           EXEC SQL WHENEVER SQLERROR GOTO ERROR-EXIT END-EXEC.
           EXEC SQL WHENEVER SQLWARNING CONTINUE END-EXEC.

           EXEC SQL DECLARE C1 CURSOR FOR S1 END-EXEC.

      * Prepare a Statement to Obtain and Order all Salaries. 
           move 50 to stmt-len.
           move "SELECT salary FROM staff ORDER BY salary" to stmt-str.
           EXEC SQL PREPARE S1 FROM :stmt END-EXEC.

      * Determine Total Number of Records. 
           EXEC SQL SELECT COUNT(*) INTO :num-records                   3 
                    FROM staff END-EXEC.

           EXEC SQL OPEN C1 END-EXEC.

      * Fetch Salaries until the Median Salary is Obtained. 
           move 0 to cntr1.      
           compute cntr2 = 1 + num-records / 2.
           perform Fetch-Row until cntr1 = cntr2.                       4

           EXEC SQL CLOSE C1 END-EXEC.

           EXEC SQL COMMIT END-EXEC.

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

       Fetch-Row.
           add 1 to cntr1.
           EXEC SQL FETCH C1 USING DESCRIPTOR :inout-sqlda END-EXEC.

       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-HOLD-PROC to return-code
           goback.