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

Quellcode-Bibliothek

© Kompilation durch diese Firma

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

Datei: README.txt   Sprache: Cobol

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


      * EMBEDDED COBOL (file "XTS723.PCO")
                             

      *Copyright 1995 National Computing Centre Limited               
      *and Computer Logic R&D S.A                                     
      *on behalf of the CTS5 SQL2 Project.                            
      *All rights reserved.                                          
      *The CTS5 SQL2 Project is sponsored by the European Community. 
      *                                                             
      *The National Computing Centre Limited and Computer Logic R&D  
      *have given permission to NIST to distribute this program      
      *over the World Wide Web in order to promote SQL standards.    
      *DISCLAIMER:                                                   
      *This program was reviewed by employees of NIST for            
      *conformance to the SQL standards.                             
      *NIST assumes no responsibility for any party's use of         
      *this program.                                                 


      ****************************************************************
      *                                                              
      *                 COMMENT SECTION                              
      *                                                              
      * SQL VALIDATION TEST SUITE V6.0                               
      *                                                              
      * XTS723.PCO                                                   
      * WRITTEN BY: Nickos Backalidis                                
      * TRANSLATED AUTOMATICALLY FROM EMBEDDED C BY CHRIS SCHANZLE
      *                                                              
      * Access to CONSTRAINT_COLUMN_USAGE view                       
      *                                                              
      * REFERENCES                                                   
      *   21.2.24 -- CONSTRAINT_COLUMN_USAGE view                    
      *   21.3.18 -- CHECK_COLUMN_USAGE base table                   
      *   21.3.15 -- REFERENTIAL_CONSTRAINTS base table              
      *   21.3.14 -- KEY_COLUMN_USAGE base table                     
      *   21.3.13 -- TABLE_CONSTRAINTS base table                    
      *   F#2     -- Basic information schema                        
      *   F#3     -- Basic schema manipulation                       
      *   F#34    -- Usage tables                                    
      *                                                              
      * DATE LAST ALTERED  14/12/95 CTS5 Hand-over Test              
      *                                                              
      * Cleanups and fixes by V. Kogakis 04/12/95:                   
      *     Correct Header of test in printout                       
      *      Respect length of strings in variable initialization.   
      *                                                              
      * QA Status: QA CHECK                                          
      *                                                              
      * Revised by DWF 1/29/96                                       
      *   Removed extraneous SQL syntax                              
      *   Fixed SDL transactions                                     
      *   Copied corrected table definitions from xts722            
      *   Removed status checks after cursor definition              
      *   Corrected expected results per erratum                     
      *   Fixed broken printout                                      
      ****************************************************************



           EXEC SQL BEGIN DECLARE SECTION END-EXEC
       01  SQLCODE PIC S9(9) COMP.
       01  SQLSTATE PIC  X(5).
       01  uid PIC  X(18).
       01  uidx PIC  X(18).
       01  coun1 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
       01  colnam PIC  X(128).
       01  connam PIC  X(128).
             EXEC SQL END DECLARE SECTION END-EXEC
       01  norm1 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
       01  norm2 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
       01  ALPNUM-TABLE VALUE IS
               "01234ABCDEFGH56789IJKLMNOPQRSTUVWXYZ".
           05  ALPNUM PIC X OCCURS 36 TIMES.
       01  NORMSQ.
           05  NORMSQX PIC X OCCURS 5 TIMES.
       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  i PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
       01  flag PIC S9(9) DISPLAY SIGN LEADING SEPARATE.

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

       PROCEDURE DIVISION.
       P0.

             MOVE "CTS4 " TO uid
             CALL "AUTHID" USING uid
             MOVE "not logged in, not" TO uidx
             EXEC SQL SELECT USER INTO :uidx FROM CTS1.ECCO END-EXEC
             MOVE SQLCODE TO SQL-COD
             EXEC SQL ROLLBACK WORK END-EXEC
             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, Embedded COBOL, xts723.pco"
             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 TEST7023 *******************
             MOVE 1 TO flag
             DISPLAY " TEST7023"
             DISPLAY " Access to CONSTRAINT_COLUMN_USAGE view "
             DISPLAY " References "
             DISPLAY " 21.2.24 -- CONSTRAINT_COLUMN_USAGE view "
             DISPLAY " 21.3.18 -- CHECK_COLUMN_USAGE base table "
             DISPLAY " 21.3.15 -- REFERENTIAL_CONSTRAINTS base table "
             DISPLAY " 21.3.14 -- KEY_COLUMN_USAGE base table"
             DISPLAY " 21.3.13 -- TABLE_CONSTRAINTS base table "
             DISPLAY " F#2 -- Basic information schema "
             DISPLAY " F#3 -- Basic schema manipulation "
             DISPLAY " F#34 -- Usage tables "
             DISPLAY " - - - - - - - - - - - - - - - - - - -"

      *initialise error reporting variables 
             COMPUTE SQLCODE = -1
             MOVE "xxxxx" TO SQLSTATE

      *initialise host variable 
      *we expect a zero so initiliase it to a value <> 0 
             MOVE 9 TO coun1

      *Access the CONSTRAINT_COLUMN_USAGE_VIEW 
             DISPLAY "SELECT COUNT(*) INTO :coun1"
             DISPLAY "FROM INFORMATION_SCHEMA.CONSTRAINT_COLUMN_USAGE"
             DISPLAY "WHERE TABLE_SCHEMA = 'CTS4';"
             EXEC SQL SELECT COUNT(*) INTO :coun1
               FROM INFORMATION_SCHEMA.CONSTRAINT_COLUMN_USAGE
               WHERE TABLE_SCHEMA = 'CTS4' END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "coun1 should be 0 its value is : ", coun1
             if (coun1  NOT =  0) then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

             DISPLAY "COMMIT WORK;"
             EXEC SQL COMMIT WORK END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             DISPLAY "CREATE TABLE TAB722a "
             DISPLAY "(COLNUM1 NUMERIC(5),"
             DISPLAY "COLNUM2 NUMERIC(5),"
             DISPLAY "COLSTR1 CHAR(3),"
             DISPLAY "CONSTRAINT 722ACONS1 PRIMARY KEY (COLSTR1),"
             DISPLAY "CONSTRAINT 722ACONS2 CHECK(COLNUM2 > 0));"
             EXEC SQL CREATE TABLE TAB722a 
               (COLNUM1 NUMERIC(5),
               COLNUM2 NUMERIC(5),
               COLSTR1 CHAR(3),
               CONSTRAINT 722ACONS1 PRIMARY KEY (COLSTR1),
               CONSTRAINT 722ACONS2 CHECK(COLNUM2 > 0)) END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             DISPLAY "COMMIT WORK;"
             EXEC SQL COMMIT WORK END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             DISPLAY "CREATE TABLE TAB722b"
             DISPLAY "( C1 CHAR(3),"
             DISPLAY " C2 CHAR(10),"
             DISPLAY " CONSTRAINT 722B FOREIGN KEY(C1)"
             DISPLAY " REFERENCES TAB722a(COLSTR1);"
             EXEC SQL CREATE TABLE TAB722b
               ( C1 CHAR(3),
               C2 CHAR(10),
               CONSTRAINT 722B FOREIGN KEY(C1) 
               REFERENCES TAB722a(COLSTR1)) END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             DISPLAY "COMMIT WORK;"
             EXEC SQL COMMIT WORK END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

      *Contents of CONSTRAINT_COLUMN_USAGE are now: 
      *TAB722A.COLSTR1  722ACONS1 
      *TAB722A.COLNUM2  722ACONS2 
      *TAB722A.COLSTR1  722B 
      *The last row would be TAB722B.C1 prior to the erratum. 

      *for test 7023 use an ordered cursor and access the 
      *CONSTRAINT_COLUMN_USAGE view to determine how many 
      *rows are present after the two tables were created 
             DISPLAY "DECLARE F7023 CURSOR FOR SELECT"
             DISPLAY "COLUMN_NAME,CONSTRAINT_NAME"
             DISPLAY "FROM INFORMATION_SCHEMA.CONSTRAINT_COLUMN_USAGE"
             DISPLAY "ORDER BY CONSTRAINT_NAME;"
             EXEC SQL DECLARE F7023 CURSOR FOR SELECT 
               COLUMN_NAME,CONSTRAINT_NAME
               FROM INFORMATION_SCHEMA.CONSTRAINT_COLUMN_USAGE
               ORDER BY CONSTRAINT_NAME END-EXEC

             DISPLAY "OPEN F7023;"
             EXEC SQL OPEN F7023 END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

      *init host vars 
             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO colnam
             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO connam


      *now start fetching rows, three in total 
      *fetch first row 
             DISPLAY "FETCH F7023 INTO :colnam,:connam;"
             EXEC SQL FETCH F7023 INTO :colnam,:connam END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "COLUMN_NAME should be COLSTR1; it is ",
             colnam
             DISPLAY "CONSTRAINT_NAME should be 722ACONS1; it is ",
             connam
             if (colnam  NOT  =   "COLSTR1"  OR  connam  NOT  =  
             "722ACONS1"then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO colnam
             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO connam


      *fetch second row 
             DISPLAY "FETCH F7023 INTO :colnam,:connam;"
             EXEC SQL FETCH F7023 INTO :colnam,:connam END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "COLUMN_NAME should be COLNUM2; it is ",
             colnam
             DISPLAY "CONSTRAINT_NAME should be 722ACONS2; it is ",
             connam
             if (colnam  NOT  =   "COLNUM2"  OR  connam  NOT  =  
             "722ACONS2"then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO colnam
             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO connam


      *fetch third and final row 
             DISPLAY "FETCH F7023 INTO :colnam,:connam;"
             EXEC SQL FETCH F7023 INTO :colnam,:connam END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "COLUMN_NAME should be COLSTR1; it is ",
             colnam
             DISPLAY "CONSTRAINT_NAME should be 722B; it is ", connam
             if (colnam  NOT  =   "COLSTR1"  OR  connam  NOT  =  
             "722B"then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

      *end fetches 
             DISPLAY "CLOSE F7023;"
             EXEC SQL CLOSE F7023 END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             DISPLAY "COMMIT WORK;"
             EXEC SQL COMMIT WORK END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

      *Drop table TAB722A 
             DISPLAY "DROP TABLE TAB722a CASCADE;"
             EXEC SQL DROP TABLE TAB722a CASCADE END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             DISPLAY "COMMIT WORK;"
             EXEC SQL COMMIT WORK END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

      *By Dropping table TAB722a the foreign key constraint 
      *declared in TAB722b should be dropped 
      *now access the CONSTRAINT_COLUMN_USAGE VIEW 
             MOVE 5 TO coun1
             DISPLAY "SELECT COUNT(CONSTRAINT_NAME)"
             DISPLAY "INTO :coun1"
             DISPLAY "FROM INFORMATION_SCHEMA.CONSTRAINT_COLUMN_USAGE;"
             EXEC SQL SELECT COUNT(CONSTRAINT_NAME)
               INTO :coun1
               FROM INFORMATION_SCHEMA.CONSTRAINT_COLUMN_USAGE END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "coun1 should be 0 it is ", coun1
             if (coun1  NOT =  0) then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

             DISPLAY "ROLLBACK WORK;"
             EXEC SQL ROLLBACK WORK END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

      *restore database
             DISPLAY "DROP TABLE TAB722b CASCADE;"
             EXEC SQL DROP TABLE TAB722b CASCADE END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             DISPLAY "COMMIT WORK;"
             EXEC SQL COMMIT WORK END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

      *record results 
             if ( flag  =  1 ) then
               DISPLAY " xts723.pco *** pass *** "
               EXEC SQL INSERT INTO CTS1.TESTREPORT
                 VALUES('7023','pass','PCO'END-EXEC
               MOVE SQLCODE TO SQL-COD
             else
               DISPLAY " xts723.pco *** fail *** "
               EXEC SQL INSERT INTO CTS1.TESTREPORT
                 VALUES('7023','fail','PCO'END-EXEC
               MOVE SQLCODE TO SQL-COD
               COMPUTE errcnt = errcnt + 1
             END-IF

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

             EXEC SQL COMMIT WORK END-EXEC
             MOVE SQLCODE TO SQL-COD

      ******************** END TEST7023 ********************

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

      *    ****  Procedures for PERFORM statements

      *Test SQLCODE and SQLSTATE for normal completion. 
       CHCKOK.
             DISPLAY "SQLCODE should be 0; its value is ", SQL-COD
             DISPLAY "SQLSTATE should be 00000; its value is ", SQLSTATE
             PERFORM NOSUBCLASS THRU EXIT-NOSUBCLASS
             if (SQLCODE NOT =  0  OR   NORMSQ NOT = "00000"then
               MOVE 0 TO flag
             END-IF
             if (NORMSQ = "00000"  AND  NORMSQ NOT = SQLSTATE)
             then
               DISPLAY "Valid implementation-defined SQLSTATE accepted."
             END-IF
             .

       NOSUBCLASS.

      *This routine replaces valid implementation-defined       
      *subclasses with 000.  This replacement equates valid     
      *implementation-defined subclasses with the 000 value     
      *expected by the test case; otherwise the test will fail. 
      *After calling NOSUBCLASS, NORMSQ will be tested          
      *                          SQLSTATE will be printed.      

           MOVE SQLSTATE TO NORMSQ

           MOVE 3 TO norm1
      *subclass begins in position 3 of char array NORMSQ 
      *valid subclass begins with 5-9, I-Z, end of ALPNUM table 
           PERFORM VARYING norm2 FROM 14 BY 1 UNTIL norm2 > 36
           if (NORMSQX(norm1)  =  ALPNUM(norm2)) then
             MOVE "0" TO NORMSQX(norm1)
           END-IF
           END-PERFORM
           
      *Quit if NORMSQ is unchanged.  Subclass is not impl.-def. 
      *Changed NORMSQ means implementation-defined subclass,    
      *so proceed to zero it out, if valid (0-9,A-Z)            
           if (NORMSQ   =   SQLSTATE) then
             GO TO EXIT-NOSUBCLASS
           END-IF

           MOVE 4 TO norm1
      *examining position 4 of char array NORMSQ 
      *valid characters are 0-9, A-Z 
           PERFORM VARYING norm2 FROM 1 BY 1 UNTIL norm2 > 36
           if (NORMSQX(norm1)  =  ALPNUM(norm2)) then
             MOVE "0" TO NORMSQX(norm1)
           END-IF
           END-PERFORM
          
           MOVE 5 TO norm1
      *valid characters are 0-9, A-Z 
      *examining position 5 of char array NORMSQ 
           PERFORM VARYING norm2 FROM 1 BY 1 UNTIL norm2 > 36
           if (NORMSQX(norm1)  =  ALPNUM(norm2)) then
             MOVE "0" TO NORMSQX(norm1)
           END-IF
           END-PERFORM
   
      *implementation-defined subclasses are allowed for warnings 
      *(class = 01).  These equate to successful completion 
      *SQLSTATE values of 00000. 
      *Reference SQL-92 4.28 SQL-transactions, paragraph 2 

           if (NORMSQX(1)  =  "0"  AND  NORMSQX(2)  =  "1"then
             MOVE "0" TO NORMSQX(2)
           END-IF
           .

       EXIT-NOSUBCLASS.
           EXIT.

¤ Diese beiden folgenden Angebotsgruppen bietet das Unternehmen0.25Angebot  Wie Sie bei der Firma Beratungs- und Dienstleistungen beauftragen können  ¤





Druckansicht
unsichere Verbindung
Druckansicht
Hier finden Sie eine Liste der Produkte des Unternehmens

Mittel




Lebenszyklus

Die hierunter aufgelisteten Ziele sind für diese Firma wichtig


Ziele

Entwicklung einer Software für die statische Quellcodeanalyse


Bot Zugriff