products/sources/formale sprachen/Cobol/Test-Suite/SQL M image not shown  

Quellcode-Bibliothek

© Kompilation durch diese Firma

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

Datei: dml086.cob   Sprache: Cobol

       IDENTIFICATION DIVISION.
       PROGRAM-ID.  DML086.
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SOURCE-COMPUTER.  xyz.
       OBJECT-COMPUTER.  xyz.
       DATA DIVISION.
       WORKING-STORAGE SECTION.


      * Standard COBOL (file "DML086.SCO") calling SQL
      * procedures in file "DML086.MCO".
      * STANDARD COBOL (file "DML086.SCO")  

      ****************************************************************
      *                                                              
      *                 COMMENT SECTION                              
      *                                                              
      * DATE 1992/07/21 STANDARD COBOL LANGUAGE                          
      * NIST SQL VALIDATION TEST SUITE V6.0                          
      *  DISCLAIMER:                                                  
      *  This program was written by employees of NIST to test SQL    
      *  implementations for conformance to the SQL standards.        
      *  NIST assumes no responsibility for any party's use of        
      *  this program.
      *                                                              
      * DML086.SCO                                                    
      * CREATED BY: DAVID W. FLATER                                  
      *    using                                                     
      * DML041.SCO                                                    
      * WRITTEN BY: HU YANPING                                       
      *                                                              
      *   THIS ROUTINE TESTS THE ENFORCEMENT OF                      
      *     CHECK CONSTRAINTS IN NESTED VIEWS                        
      *     EACH WITH AN IMPLICIT CASCADED OPTION.                   
      *   
      *   NOTE: This routine does NOT contain tests for the FULL SQL 
      *     requirement to support the LOCAL check option.           
      *                                                              
      * REFERENCES                                                   
      *   ANSI SQL-1992,                                             
      *     section 11.19  <view definition>  GR11,                  
      *     Annex E #3                                               
      *                                                              
      *                                                              
      *   13.8 <insert statement>, 13.9 & 13.10 <update statements> 
      *                                                              
      ****************************************************************



      * EXEC SQL BEGIN DECLARE SECTION END-EXEC
       01  EMPNO1 PIC  X(3).
       01  HOURS1 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
       01  I PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
       01  uid PIC  X(18).
       01  uidx PIC  X(18).
      *  EXEC SQL END DECLARE SECTION END-EXEC
       01  SQLCODE PIC S9(9) COMP.
       01  errcnt PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
      *date_time declaration 
       01  TO-DAY PIC 9(6).
       01  THE-TIME PIC 9(8).
       01  ifpass PIC S9(9) DISPLAY SIGN LEADING SEPARATE.


       01  SQL-COD PIC S9(9) DISPLAY SIGN LEADING SEPARATE.

       PROCEDURE DIVISION.
       P0.

             MOVE "HU" TO uid
             CALL "AUTHID" USING uid
             MOVE "not logged in, not" TO uidx
      *  EXEC SQL SELECT USER INTO :uidx FROM HU.ECCO;
             CALL "SUB1" USING SQLCODE uidx
             MOVE SQLCODE TO SQL-COD
             if (uid  NOT  =   uidx) then
               DISPLAY "ERROR: User ", uid " expected. User ", uidx "
      -    " connected"
             STOP RUN 
             END-IF
             MOVE 0 TO errcnt
           DISPLAY
              "SQL Test Suite, V6.0, Standard COBOL, dml086.sco"
           DISPLAY
           "59-byte ID"
             DISPLAY "TEd Version #"
      *date_time print 
           ACCEPT TO-DAY FROM DATE
           ACCEPT THE-TIME FROM TIME
           DISPLAY "Date run YYMMDD: " TO-DAY " at hhmmssff: " THE-TIME


      ******************** BEGIN TEST0511 *******************

             DISPLAY " TEST0511 "
             DISPLAY " CHECK clauses in nested views--clarified."
             DISPLAY "Reference ANSI SQL-1992,"
             DISPLAY " section 11.19 GR11,"
             DISPLAY " Annex E #3"
             DISPLAY " - - - - - - - - - - - - - - - - - - -"

      *   CREATE VIEW V_WORKS1                
      *          AS SELECT * FROM WORKS       
      *             WHERE HOURS > 15          
      *          WITH CHECK OPTION;           

      *   CREATE VIEW V_WORKS2                
      *          AS SELECT * FROM V_WORKS1    
      *             WHERE EMPNUM = 'E1'       
      *                OR EMPNUM = 'E6';      

      *   CREATE VIEW V_WORKS3                
      *          AS SELECT * FROM V_WORKS2    
      *             WHERE PNUM = 'P2'         
      *                OR PNUM = 'P7'         
      *          WITH CHECK OPTION;           

             MOVE 1 TO ifpass

      *  EXEC SQL INSERT INTO V_WORKS2
      *    VALUES('E9','P7',13);
             CALL "SUB2" USING SQLCODE
             MOVE SQLCODE TO SQL-COD

             if (SQLCODE  =  0) then
               DISPLAY "Fail: Violates constraint of "
               DISPLAY " underlying view (with check option)"
               MOVE 0 TO ifpass
             END-IF

      *  EXEC SQL INSERT INTO V_WORKS2
      *    VALUES('E7','P4',95);
             CALL "SUB3" USING SQLCODE
             MOVE SQLCODE TO SQL-COD

             if (SQLCODE  NOT =  0) then
               DISPLAY "Fail: Will not insert outside of view 2 def. (no
      -    " check),"
               DISPLAY "Satisfies constraint of underlying view (with
      -    " check opt)"
               MOVE 0 TO ifpass
             END-IF

      *  EXEC SQL INSERT INTO V_WORKS3
      *    VALUES('E8','P2',85);
             CALL "SUB4" USING SQLCODE
             MOVE SQLCODE TO SQL-COD

      *NOTE: The standard has been clarified on the following issue. 
             if (SQLCODE  =  0) then
               DISPLAY "Row ('E8','P2',85) was inserted into view
      -    " V_WORKS3."
               DISPLAY "This SQL implementation inserts a row which is:"
               DISPLAY " Inside view 1 def. (with check)"
               DISPLAY " Outside view 2 def. (no check)"
               DISPLAY " Inside view 3 def. (with check)"
               DISPLAY " (This is now considered incorrect.)"
               DISPLAY "Fail: Outer check option with implicit CASCADE
      -    " not enforced."
               DISPLAY "This behavior violates GR11a of 11.19
      -    " definition> with"
               DISPLAY " V_WORKS3 considered as spanning itself (see
      -    " GR9)."
               MOVE 0 TO ifpass
             else
               DISPLAY "Row ('E8','P2',85) was NOT inserted into view
      -    " V_WORKS3."
               DISPLAY "This SQL implementation will not insert row
      -    " which is:"
               DISPLAY " Inside view 1 def. (with check)"
               DISPLAY " Outside view 2 def. (no check)"
               DISPLAY " Inside view 3 def. (with check)"
               DISPLAY "Outer check option with implicit CASCADE"
               DISPLAY "implies inner check options."
               DISPLAY "This is correct behavior based on GR9 and GR11a"
               DISPLAY "with V_WORKS3 spanning itself!"
             END-IF

      *  EXEC SQL INSERT INTO V_WORKS3
      *    VALUES('E1','P7',90);
             CALL "SUB5" USING SQLCODE
             MOVE SQLCODE TO SQL-COD

             if (SQLCODE  NOT =  0) then
               DISPLAY "Fail: Will not insert row satisfying "
               DISPLAY " all nested view definitions"
               MOVE 0 TO ifpass
             END-IF

      *  EXEC SQL INSERT INTO V_WORKS3
      *    VALUES('E9','P2',10);
             CALL "SUB6" USING SQLCODE
             MOVE SQLCODE TO SQL-COD

             if (SQLCODE  =  0) then
               DISPLAY "Fail: Violates constraint of "
               DISPLAY " underlying view (with check option)"
               MOVE 0 TO ifpass
             END-IF

             MOVE 0 TO I

      *  EXEC SQL SELECT COUNT(*)
      *    INTO  :I
      *    FROM  WORKS
      *    WHERE EMPNUM = 'E9';
             CALL "SUB7" USING SQLCODE I
             MOVE SQLCODE TO SQL-COD


             if (I  >  0 ) then
               MOVE 0 TO ifpass
               DISPLAY "Fail: Nested views fail to enforce "
               DISPLAY " underlying check constraint."
             END-IF


             MOVE 0 TO I

      *  EXEC SQL SELECT COUNT(*)
      *    INTO  :I
      *    FROM  WORKS
      *    WHERE HOURS > 85;
             CALL "SUB8" USING SQLCODE I
             MOVE SQLCODE TO SQL-COD

             if (I  NOT =  2) then
               DISPLAY "Fail: Will not insert rows satisfying underlying
      -    " views"
               MOVE 0 TO ifpass
             END-IF

      *  EXEC SQL UPDATE V_WORKS3
      *    SET EMPNUM = 'E12', HOURS = 222
      *    WHERE EMPNUM = 'E1' AND PNUM = 'P2';
             CALL "SUB9" USING SQLCODE
             MOVE SQLCODE TO SQL-COD

             if (SQLCODE  =  0) then
               DISPLAY "Fail: View 3 CHECK OPTION must be CASCADED to "
               DISPLAY " View 2 definition in UPDATE: searched! "
               MOVE 0 TO ifpass
             END-IF

      *  EXEC SQL INSERT INTO WORKS VALUES ('E6','P2',55);
             CALL "SUB10" USING SQLCODE
             MOVE SQLCODE TO SQL-COD
      *  EXEC SQL DECLARE QWERTY CURSOR FOR 
      *    SELECT HOURS FROM V_WORKS3 
      *    WHERE EMPNUM = 'E6' AND PNUM = 'P2' END-EXEC
      *  EXEC SQL OPEN QWERTY;
             CALL "SUB11" USING SQLCODE
             MOVE SQLCODE TO SQL-COD
      *  EXEC SQL FETCH QWERTY INTO :HOURS1;
             CALL "SUB12" USING SQLCODE HOURS1
             MOVE SQLCODE TO SQL-COD
      *  EXEC SQL UPDATE V_WORKS3
      *    SET EMPNUM = 'E13', HOURS = 222
      *    WHERE CURRENT OF QWERTY;
             CALL "SUB13" USING SQLCODE
             MOVE SQLCODE TO SQL-COD

             if (SQLCODE  =  0) then
               DISPLAY "Fail: View 3 CHECK OPTION must be CASCADED to "
               DISPLAY " View 2 definition in UPDATE: positioned! "
               MOVE 0 TO ifpass
             END-IF

             COMPUTE I = -1

      *  EXEC SQL SELECT COUNT(*) INTO :I FROM WORKS WHERE HOURS =
      *  222;
             CALL "SUB14" USING SQLCODE I
             MOVE SQLCODE TO SQL-COD
             if (I  NOT =  0) then
               DISPLAY "Number of rows updated is ", I
               DISPLAY "Fail: View 3 CHECK OPTION must cascade to View 2
      -    " definition ! "
               MOVE 0 TO ifpass
             END-IF


      *  EXEC SQL ROLLBACK WORK;
             CALL "SUB15" USING SQLCODE
             MOVE SQLCODE TO SQL-COD

             if (ifpass  =  1) then
               DISPLAY " *** pass *** "
      *    EXEC SQL INSERT INTO TESTREPORT
      *  VALUES('0511','pass','MCO');
               CALL "SUB16" USING SQLCODE
               MOVE SQLCODE TO SQL-COD
             else
               DISPLAY " dml086.sco *** fail *** "
      *    EXEC SQL INSERT INTO TESTREPORT
      *  VALUES('0511','fail','MCO');
               CALL "SUB17" USING SQLCODE
               MOVE SQLCODE TO SQL-COD
               COMPUTE errcnt = errcnt + 1
             END-IF


             DISPLAY
             "==================================================="

             DISPLAY  " "

      *  EXEC SQL COMMIT WORK;
             CALL "SUB18" USING SQLCODE
             MOVE SQLCODE TO SQL-COD
      ******************** END TEST0511 *******************

      **** TESTER MAY CHOOSE TO INSERT CODE FOR errcnt > 0
           STOP RUN.

      *    ****  Procedures for PERFORM statements

¤ Dauer der Verarbeitung: 0.21 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