IDENTIFICATION DIVISION.
PROGRAM-ID. YTS768.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. xyz.
OBJECT-COMPUTER. xyz.
DATA DIVISION.
WORKING-STORAGE SECTION.
* Standard COBOL (file "YTS768.SCO") calling SQL
* procedures in file "YTS768.MCO".
*Copyright 1996 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
*
* YTS768.SCO
* WRITTEN BY: Susan Watters
* TRANSLATED AUTOMATICALLY FROM EMBEDDED COBOL BY CHRIS SCHANZLE
*
* This routine tests that a user can access the SCHEMATA
* view in the information schema
*
*
* REFERENCES
* 21.2 -- Information schema
* 21.2.4 -- SCHEMATA view
* F#35 -- Intermediate information schema
* F#17 -- Multiple schemas per user
*
* DATE LAST ALTERED 02.01.96 CTS5 Hand-over Test
*
* QA Status: Full FC
*
* Revised by DWF 1996-03-12
* Added rollback after authid
* Removed EXEC SQL from inside printf
* Cleanups
* Fixed syntax error
****************************************************************
* 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 catn PIC X(128).
01 schn PIC X(128).
01 scho PIC X(128).
01 count1 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
01 count2 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.
01 i PIC S9(4) 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 flag2 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;
CALL "SUB1" USING SQLCODE SQLSTATE uidx
MOVE SQLCODE TO SQL-COD
* EXEC SQL ROLLBACK WORK;
CALL "SUB2" USING SQLCODE SQLSTATE
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, Module COBOL, yts768.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 TEST7550 *******************
MOVE 1 TO flag
DISPLAY " TEST7550 "
DISPLAY "Access to SCHEMATA view"
DISPLAY "References:"
DISPLAY "21.2 -- Information schema"
DISPLAY "21.2.4 -- SCHEMATA view"
DISPLAY "F#35 -- Intermediate information schema"
DISPLAY "F#17 -- Multiple schemas per user"
DISPLAY " - - - - - - - - - - - - - - - - - - -"
COMPUTE SQLCODE = -1
MOVE "xxxxx" TO SQLSTATE
*User CTS1 is expected to own two schemas : CTS1 and CTS1B
MOVE 0 TO count1
*Check that the correct number of rows are selected
*from the SCHEMATA view
DISPLAY "SELECT COUNT (*) INTO :count1 FROM"
DISPLAY "INFORMATION_SCHEMA.SCHEMATA;"
* EXEC SQL SELECT COUNT (*) INTO :count1 FROM
* INFORMATION_SCHEMA.SCHEMATA;
CALL "SUB3" USING SQLCODE SQLSTATE count1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "count1 should be 2; its value is ", count1
if (count1 NOT = 2) then
MOVE 0 TO flag
END-IF
*declare cursor based on INFORMATION_SCHEMA.SCHEMATA
DISPLAY "DECLARE data768 CURSOR FOR"
DISPLAY "SELECT CATALOG_NAME, SCHEMA_NAME, SCHEMA_OWNER"
DISPLAY "FROM INFORMATION_SCHEMA.SCHEMATA;"
* EXEC SQL DECLARE data768 CURSOR FOR
* SELECT CATALOG_NAME, SCHEMA_NAME, SCHEMA_OWNER
* FROM INFORMATION_SCHEMA.SCHEMATA END-EXEC
DISPLAY "OPEN data768;"
* EXEC SQL OPEN data768;
CALL "SUB4" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO schn
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO scho
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO catn
*fetch first row from SCHEMATA view
DISPLAY "FETCH data768 INTO :catn, :schn, :scho;"
* EXEC SQL FETCH data768 INTO :catn, :schn, :scho;
CALL "SUB5" USING SQLCODE SQLSTATE catn schn scho
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "scho should be CTS1, it is ", scho
if (scho NOT = "CTS1") then
MOVE 0 TO flag
END-IF
DISPLAY "schn should be CTS1 or CTS1B, it is ", schn
if (schn NOT = "CTS1" AND schn NOT = "CTS1B")
then
MOVE 0 TO flag
END-IF
*fetch second row from SCHEMATA view
*reinitialise host variables
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO schn
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO scho
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO catn
DISPLAY "FETCH data768 INTO :catn, :schn, :scho;"
* EXEC SQL FETCH data768 INTO :catn, :schn, :scho;
CALL "SUB6" USING SQLCODE SQLSTATE catn schn scho
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "scho should be CTS1, it is ", scho
if (scho NOT = "CTS1") then
MOVE 0 TO flag
END-IF
DISPLAY "schn should be CTS1 or CTS1B, it is ", schn
if (schn NOT = "CTS1" AND schn NOT = "CTS1B")
then
MOVE 0 TO flag
END-IF
*check no data condition is raised
DISPLAY "FETCH data768 INTO :catn, :schn, :scho;"
* EXEC SQL FETCH data768 INTO :catn, :schn, :scho;
CALL "SUB7" USING SQLCODE SQLSTATE catn schn scho
MOVE SQLCODE TO SQL-COD
*That should generate a no data completion condition
*which is SQLSTATE 02000
DISPLAY "SQLCODE should be 100; its value is ", SQL-COD
if (SQLCODE NOT = 100) then
MOVE 0 TO flag
END-IF
DISPLAY "SQLSTATE should be 02000; its value is ", SQLSTATE
PERFORM NOSUBCLASS THRU EXIT-NOSUBCLASS
if (NORMSQ NOT = "02000") then
MOVE 0 TO flag
END-IF
if (NORMSQ = "02000" AND NORMSQ NOT = SQLSTATE)
then
DISPLAY "Valid implementation-defined SQLSTATE accepted."
END-IF
DISPLAY " "
*ensure that only schemas owned by the current user can be refer
MOVE 99 TO count2
DISPLAY "SELECT COUNT (*) INTO :count2"
DISPLAY "FROM INFORMATION_SCHEMA.SCHEMATA"
DISPLAY "WHERE SCHEMA_OWNER = 'CTS2';"
* EXEC SQL SELECT COUNT (*) INTO :count2
* FROM INFORMATION_SCHEMA.SCHEMATA
* WHERE SCHEMA_OWNER = 'CTS2';
CALL "SUB8" USING SQLCODE SQLSTATE count2
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " value 0 expected, ", count2, " returned"
if (count2 NOT = 0) then
MOVE 0 TO flag
END-IF
DISPLAY "ROLLBACK WORK;"
* EXEC SQL ROLLBACK WORK;
CALL "SUB9" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if ( flag = 1 ) then
DISPLAY " YTS768.PC *** pass *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7550','pass','MCO');
CALL "SUB10" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
else
DISPLAY " YTS768.PC *** fail *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7550','fail','MCO');
CALL "SUB11" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
COMPUTE errcnt = errcnt + 1
END-IF
DISPLAY "==============================================="
* EXEC SQL COMMIT WORK;
CALL "SUB12" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
******************** END TEST7550 ********************
**** 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)
¤
|
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.
|