products/Sources/formale Sprachen/COBOL/verschiedene-Autoren/IBM image not shown  

Quellcode-Bibliothek

© Kompilation durch diese Firma

[Weder Korrektheit noch Funktionsfähigkeit der Software werden zugesichert.]

Datei: tangent_line.prf   Sprache: Cobol

Original von: verschiedene©

      ******************************************************************
      ** Licensed Materials - Property of IBM
      **
      ** Governed under the terms of the International
      ** License Agreement for Non-Warranted Sample Code.
      **
      ** (C) COPYRIGHT International Business Machines Corp. 1995 - 2002
      ** All Rights Reserved.
      **
      ** US Government Users Restricted Rights - Use, duplication or
      ** disclosure restricted by GSA ADP Schedule Contract with IBM Cor
      ******************************************************************
      **
      ** SOURCE FILE NAME: tabsql.sqb
      **
      ** SAMPLE: Demonstrates common table expressions using SQL
      **
      **         This program demonstrates how to use common table
      **         expressions using the following advanced SQL statements
      **
      **   WITH
      **   PAYLEVEL AS (SELECT EMPNO, YEAR(HIREDATE) AS HIREYEAR, EDLEVE
      **      SALARY+BONUS+COMM AS TOTAL_PAY FROM EMPLOYEE
      **      WHERE EDLEVEL > 16),
      **   PAYBYED (EDUC_LEVEL, YEAR_OF_HIRE, AVG_TOTAL_PAY) AS
      **      (SELECT EDLEVEL, HIREYEAR, AVG(TOTAL_PAY) FROM PAYLEVEL
      **      GROUP BY EDLEVEL, HIREYEAR)
      **   SELECT EMPNO, EDLEVEL, YEAR_OF_HIRE, TOTAL_PAY, AVG_TOTAL_PAY
      **      FROM PAYLEVEL, PAYBYED
      **      WHERE EDLEVEL=EDUC_LEVEL
      **         AND HIREYEAR = YEAR_OF_HIRE
      **         AND TOTAL_PAY < AVG_TOTAL_PAY;
      **
      **            The second example is described in the "Nested Table
      **            Expressions" section of "Using SQL - Advanced".
      **   SELECT EDLEVEL, HIREYEAR, AVG(TOTAL_PAY)
      **      FROM (
      **         SELECT EMPNO, YEAR(HIREDATE) AS HIREYEAR, EDLEVEL,
      **            SALARY+BONUS+COMM AS TOTAL_PAY FROM EMPLOYEE
      **            WHERE EDLEVEL > 16
      **         ) AS PAY_LEVEL
      **      GROUP BY EDLEVEL, HIREYEAR
      **
      ** SQL STATEMENTS USED:
      **         BEGIN DECLARE SECTION
      **         END DECLARE SECTION
      **         CONNECT
      **         DECLARE
      **         FETCH
      **         OPEN
      **
      ** OUTPUT FILE: tabsql.out (available in the online documentation)
      ******************************************************************
      **
      ** For more information on the sample programs, see the README fil
      **
      ** For information on developing COBOL applications, see the
      ** Application Development Guide.
      **
      ** For information on using SQL statements, see the SQL Reference.
      **
      ** For the latest information on programming, compiling, and runni
      ** DB2 applications, visit the DB2 application development website
      **     http://www.software.ibm.com/data/db2/udb/ad
      ******************************************************************

       Identification Division.
       Program-ID"tabsql".

       Data Division.
       Working-Storage Section.

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

           EXEC SQL BEGIN DECLARE SECTION END-EXEC.
       01 userid            pic x(8).
       01 passwd.
         49 passwd-length   pic s9(4) comp-5 value 0.
         49 passwd-name     pic x(18).
       01 employee-empno    pic x(6).
       01 employee-edlevel  pic s9(4) comp-5.
       01 employee-hireyear pic s9(9) comp-5.
       01 employee-avg-tpay pic s9(11)v9(2) comp-3.
       01 employee-totpay   pic s9(11)v9(2) comp-3.
           EXEC SQL END DECLARE SECTION END-EXEC.

       77 disp-pay        pic z(11).99 usage display.
       77 disp-pay2       pic z(11).99 usage display.
       77 errloc          pic x(80).
       77 counter         pic s9(4) comp-5 value 0.

       Procedure Division.
       Main Section.
           display "Sample COBOL program: TABSQL".
           display " ".

      * Get database connection information.
           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 fo
      * with the length of the input string.
           inspect passwd-name tallying passwd-length for characters
              before initial " ".

           display " ".

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

      * COMMON TABLE EXPRESSION EXAMPLE
           display "COMMON TABLE EXPRESSIONS EXAMPLE".
           display "^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^".

           EXEC SQL DECLARE c1 CURSOR FOR
                    WITH
                    PAYLEVEL AS (SELECT EMPNO, YEAR(HIREDATE) AS
                       HIREYEAR, EDLEVEL, (SALARY+BONUS+COMM) AS
                       TOTAL_PAY FROM EMPLOYEE
                       WHERE EDLEVEL > 6),
                    PAYBYED (EDUC_LEVEL, YEAR_OF_HIRE, AVG_TOTAL_PAY)
                       AS (SELECT EDLEVEL, HIREYEAR, AVG(TOTAL_PAY)
                       FROM PAYLEVEL GROUP BY EDLEVEL, HIREYEAR)
                    SELECT EMPNO, EDLEVEL, YEAR_OF_HIRE, TOTAL_PAY,
                       AVG_TOTAL_PAY FROM PAYLEVEL, PAYBYED
                       WHERE EDLEVEL=EDUC_LEVEL
                          AND HIREYEAR = YEAR_OF_HIRE
                          AND TOTAL_PAY < AVG_TOTAL_PAY END-EXEC.

           EXEC SQL OPEN c1 END-EXEC.
           move "OPEN c1" to errloc.
           call "checkerr" using SQLCA errloc.

           display "EMPNO EDLEVEL YEAR_OF_HIRE TOTAL_PAY AVG_TOTAL_P
      -       "AY".
      * FETCH the rows for the COMMON TABLE EXPRESSIONS select statement
           perform Common-Fetch-Loop thru End-Common-Fetch
              until SQLCODE not equal 0.

           display " ", counter, " record(s) selected".
           move 0 to counter.
           display " ".

      * NESTED TABLE EXPRESSIONS EXAMPLE
           display "NESTED TABLE EXPRESSIONS EXAMPLES".
           display "^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^".
           display "QUESTION: What is the average total pay, by educatio
      -            "n level".
           display " and year of hire, for those with an educat
      -            "ion".
           display " level greater than 16?".
           display "ANSWER:".

           EXEC SQL DECLARE c2 CURSOR FOR
                    SELECT EDLEVEL, HIREYEAR, AVG(TOTAL_PAY) AS
                       AVG_TOTAL_PAY FROM
                       (SELECT EMPNO, YEAR(HIREDATE) AS HIREYEAR,
                          EDLEVEL, SALARY+BONUS+COMM AS TOTAL_PAY FROM
                          EMPLOYEE WHERE EDLEVEL > 16)
                       AS PAY_LEVEL
                    GROUP BY EDLEVEL, HIREYEAR END-EXEC.

           EXEC SQL OPEN c2 END-EXEC.
           move "OPEN c2" to errloc.
           call "checkerr" using SQLCA errloc.

           display "EDLEVEL HIREYEAR AVG_TOTAL_PAY".
      * FETCH the rows for the NESTED TABLE EXPRESSIONS select statement
           perform Nested-Fetch-Loop thru End-Nested-Fetch
              until SQLCODE not equal 0.

           display " ", counter, " record(s) selected".

           EXEC SQL CONNECT RESET END-EXEC.
           move "CONNECT RESET" to errloc.
           call "checkerr" using SQLCA errloc.
       End-Main.
           go to End-Prog.

       Common-Fetch-Loop Section.
           EXEC SQL FETCH c1 INTO :employee-empno,
              :employee-edlevel, :employee-hireyear,
              :employee-totpay, :employee-avg-tpay END-EXEC.

           move employee-totpay to disp-pay.
           move employee-avg-tpay to disp-pay2.
           if SQLCODE not equal 0
              go to End-Common-Fetch.
           display employee-empno, " ", employee-edlevel, " ",
              employee-hireyear, " ", disp-pay, disp-pay2.

           add 1 to counter.
       End-Common-Fetch. exit.

       Nested-Fetch-Loop Section.
           EXEC SQL FETCH c2 INTO :employee-edlevel, :employee-hireyear,
              :employee-avg-tpay END-EXEC.

           move employee-avg-tpay to disp-pay.
           if SQLCODE not equal 0
              go to End-Nested-Fetch.
           display employee-edlevel, " ", employee-hireyear, " ",
              disp-pay.

           add 1 to counter.
       End-Nested-Fetch. exit.

       End-Prog.
           stop run.


¤ Dauer der Verarbeitung: 0.16 Sekunden  (vorverarbeitet)  ¤





Download des
Quellennavigators
Download des
sprechenden Kalenders

in der Quellcodebibliothek suchen




Haftungshinweis

Die Informationen auf dieser Webseite wurden nach bestem Wissen sorgfältig zusammengestellt. Es wird jedoch weder Vollständigkeit, noch Richtigkeit, noch Qualität der bereit gestellten Informationen zugesichert.


Bemerkung:

Die farbliche Syntaxdarstellung ist noch experimentell.


Bot Zugriff