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: xts759.cob   Sprache: Cobol

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


      * EMBEDDED COBOL (file "XTS759.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                               
      *                                                              
      * XTS759.PCO                                                   
      * WRITTEN BY: Nickos Backalidis                                
      * TRANSLATED AUTOMATICALLY FROM EMBEDDED C BY CHRIS SCHANZLE
      *                                                              
      *Scrolled cursor on grouped view,FETCH RELATIVE,FIRST,ABSOLUTE 
      *                                                              
      * REFERENCES                                                   
      *   13.1    -- <Declare cursor>                                
      *   13.3    -- <Fetch statement>                               
      *   13.3    GR.5bi                                             
      *   F#3     -- Basic schema manipulation                       
      *   F#24    -- Keyword relaxations                             
      *   F#43    -- Scrolled cursors                                
      *                                                              
      * DATE LAST ALTERED  18/12/95 CTS5 Hand-over Test              
      *                                                              
      * Cleanups and fixes by V. Kogakis 15/12/95                    
      *        Print timestamp                                       
      *        Include Files                                         
      *        Define NOSUBCLASS/CHCKOK at test beginning            
      *                                                              
      * QA STATUS : QA CHECK                                         
      *                                                              
      * Revised by DWF 1996-02-20                                    
      *   Removed status checks after cursor definition              
      *   Added order by clause to enforce ordering that was assumed 
      *   Fixed relative fetch to get expected results               
      *   Added printouts                                            
      *   Fixed string lengths                                       
      *   Removed coding rule violations                             
      ****************************************************************



           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  col1 PIC  X(20).
       01  col2 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
       01  rowptr PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
             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  flag PIC S9(9) DISPLAY SIGN LEADING SEPARATE.

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

       PROCEDURE DIVISION.
       P0.

             MOVE "CTS1 " 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, xts759.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 TEST7059 *******************
             MOVE 1 TO flag
             DISPLAY " TEST7059"
             DISPLAY " Scrolled cursor on grouped view,FETCH
      -    " RELATIVE,FIRST,ABSOLUTE"
             DISPLAY " References"
             DISPLAY " 13.1 -- "
             DISPLAY " 13.3 -- "
             DISPLAY " 13.3 GR.5bi "
             DISPLAY " F#24 -- Keyword relaxations"
             DISPLAY " F#43 -- Scrolled cursors "
             DISPLAY " - - - - - - - - - - - - - - - - - - -"

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

      *create a grouped view under the current schema 
             DISPLAY "CREATE VIEW VA759 (WORKERS,CITCOUN)"
             DISPLAY "AS SELECT EMPNAME,COUNT(CITY)"
             DISPLAY "FROM CTS1.STAFFc"
             DISPLAY "GROUP BY EMPNAME;"
             EXEC SQL CREATE VIEW VA759 (WORKERS,CITCOUN) 
               AS SELECT EMPNAME,COUNT(CITY)
               FROM CTS1.STAFFc
               GROUP BY EMPNAME 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 "DECLARE ACURS SCROLL CURSOR FOR SELECT
      -    " WORKERS,CITCOUN"
             DISPLAY "FROM VA759 ORDER BY WORKERS;"
             EXEC SQL DECLARE ACURS SCROLL CURSOR FOR SELECT
             WORKERS,CITCOUN
               FROM VA759 ORDER BY WORKERS END-EXEC

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

      *initialise host variables 
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO col1
             MOVE 3 TO rowptr
             DISPLAY "rowptr = 3;"
             MOVE 0 TO col2

      *now fetch the third row of the grouped view 
             DISPLAY "FETCH ABSOLUTE :rowptr FROM ACURS INTO
      -    " :col1,:col2;"
             EXEC SQL FETCH ABSOLUTE :rowptr FROM ACURS INTO :col1,:col2
             END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "WORKERS1 should be Carmen; its value is ", col1
             DISPLAY "CITCOUN should be 1; its value is ", col2
             if (col1  NOT  =   "Carmen"  OR  col2  NOT =  1) then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

      *initialise host variables 
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO col1
             MOVE 0 TO col2

      *now fetch the first row of the grouped view 
             DISPLAY "FETCH FIRST FROM ACURS INTO :col1,:col2;"
             EXEC SQL FETCH FIRST FROM ACURS INTO :col1,:col2 END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "WORKERS1 should be Alice; its value is ", col1
             DISPLAY "CITCOUN should be 1; its value is ", col2
             if (col1  NOT  =   "Alice"  OR  col2  NOT =  1) then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

      *initialise host variables 
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO col1
             MOVE 0 TO rowptr
             DISPLAY "rowptr = 0;"
             MOVE 0 TO col2

      *now fetch again the first row of the grouped view 
             DISPLAY "FETCH RELATIVE :rowptr FROM ACURS INTO
      -    " :col1,:col2;"
             EXEC SQL FETCH RELATIVE :rowptr FROM ACURS INTO :col1,:col2
             END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "WORKERS1 should be Alice; its value is ", col1
             DISPLAY "CITCOUN should be 1; its value is ", col2
             if (col1  NOT  =   "Alice"  OR  col2  NOT =  1) then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

      *initialise host variables 
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO col1
             MOVE 5 TO rowptr
             DISPLAY "rowptr = 5;"
             MOVE 0 TO col2

      *now retrieve the last row of the grouped view 
             DISPLAY "FETCH RELATIVE :rowptr FROM ACURS INTO
      -    " :col1,:col2;"
             EXEC SQL FETCH RELATIVE :rowptr FROM ACURS INTO :col1,:col2
             END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "WORKERS1 should be Tom; its value is ", col1
             DISPLAY "CITCOUN should be 1; its value is ", col2
             if (col1  NOT  =   "Tom"  OR  col2  NOT =  1) then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

      *initialise host variables 
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO col1
             COMPUTE rowptr = -1
             DISPLAY "rowptr = -1;"
             MOVE 0 TO col2

      *now retrieve the rest of the view rows in reverse order
             DISPLAY "FETCH RELATIVE :rowptr FROM ACURS INTO
      -    " :col1,:col2;"
             EXEC SQL FETCH RELATIVE :rowptr FROM ACURS INTO :col1,:col2
             END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "WORKERS1 should be Kingdom; its value is ", col1
             DISPLAY "CITCOUN should be 1; its value is ", col2
             if (col1  NOT  =   "Kingdom"  OR  col2  NOT =  1) then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

      *initialise host variables 
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO col1
             COMPUTE rowptr = -1
             MOVE 0 TO col2

             DISPLAY "FETCH RELATIVE :rowptr FROM ACURS INTO
      -    " :col1,:col2;"
             EXEC SQL FETCH RELATIVE :rowptr FROM ACURS INTO :col1,:col2
             END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "WORKERS1 should be Don; its value is ", col1
             DISPLAY "CITCOUN should be 2; its value is ", col2
             if (col1  NOT  =   "Don"  OR  col2  NOT =  2) then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

      *initialise host variables 
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO col1
             COMPUTE rowptr = -1
             MOVE 0 TO col2

             DISPLAY "FETCH RELATIVE :rowptr FROM ACURS INTO
      -    " :col1,:col2;"
             EXEC SQL FETCH RELATIVE :rowptr FROM ACURS INTO :col1,:col2
             END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "WORKERS1 should be Carmen; its value is ", col1
             DISPLAY "CITCOUN should be 1; its value is ", col2
             if (col1  NOT  =   "Carmen"  OR  col2  NOT =  1) then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

      *initialise host variables 
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO col1
             COMPUTE rowptr = -1
             MOVE 0 TO col2

             DISPLAY "FETCH RELATIVE :rowptr FROM ACURS INTO
      -    " :col1,:col2;"
             EXEC SQL FETCH RELATIVE :rowptr FROM ACURS INTO :col1,:col2
             END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "WORKERS1 should be Betty; its value is ", col1
             DISPLAY "CITCOUN should be 1; its value is ", col2
             if (col1  NOT  =   "Betty"  OR  col2  NOT =  1) then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

      *initialise host variables 
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO col1
             COMPUTE rowptr = -1
             MOVE 0 TO col2

      *now fetch first and final row 
             DISPLAY "FETCH RELATIVE :rowptr FROM ACURS INTO
      -    " :col1,:col2;"
             EXEC SQL FETCH RELATIVE :rowptr FROM ACURS INTO :col1,:col2
             END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "WORKERS1 should be Alice; its value is ", col1
             DISPLAY "CITCOUN should be 1; its value is ", col2
             if (col1  NOT  =   "Alice"  OR  col2  NOT =  1) then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

             DISPLAY "CLOSE ACURS;"
             EXEC SQL CLOSE ACURS END-EXEC
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

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

      *restore database in its original state 
      *by dropping the grouped view 

             DISPLAY "DROP VIEW VA759 CASCADE;"
             EXEC SQL DROP VIEW VA759 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 " xts759.pco *** pass *** "
               EXEC SQL INSERT INTO CTS1.TESTREPORT
                 VALUES('7059','pass','PCO'END-EXEC
               MOVE SQLCODE TO SQL-COD
             else
               DISPLAY " xts759.pco *** fail *** "
               EXEC SQL INSERT INTO CTS1.TESTREPORT
                 VALUES('7059','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 TEST7059 ********************

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

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