Quellcode-Bibliothek
© Kompilation durch diese Firma
[Weder Korrektheit noch Funktionsfähigkeit der Software werden zugesichert.]
Datei:
xts762.cob
Sprache: Cobol
|
|
IDENTIFICATION DIVISION.
PROGRAM-ID. YTS767.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. xyz.
OBJECT-COMPUTER. xyz.
DATA DIVISION.
WORKING-STORAGE SECTION.
* Standard COBOL (file "YTS767.SCO") calling SQL
* procedures in file "YTS767.MCO".
*Copyright 1996 National Computing Centre Ltd,
*and Computer Logic R&D S.A
*on behalf of 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
*
* YTS767.SCO
* WRITTEN BY: Susan Watters
* TRANSLATED AUTOMATICALLY FROM EMBEDDED COBOL BY CHRIS SCHANZLE
*
* Access To CHECK_CONSTRAINTS view
* a) Explicit table constraints in CHECK_CONSTRAINTS view
* b) Column constraints in CHECK_CONSTRAINTS view.
* c) Domain constraints in CHECK_CONSTRAINTS view.
* d) Unique identification in CHECK_CONSTRAINTS view.
*
*
* REFERENCES
* 21.2.15 CHECK_CONSTRAINTS view
* 21.2.13 TABLE_CONSTRAINTS view
* 11.4 SR9 <column constraint definition>
* 11.6 SR1 <table constraint definition>
* 11.9 <check constraint definition>
* 10.6 SR2 <constraint name definition> and
* <constraint attributes>
* 11.6 SR2 <table constraint definition>
* 11.21 <domain definition>
* F# 33 Constraint tables
* F# 25 Domain definition
* F# 17 Multiple schemas per user
* F# 3 Basic schema manipulation
* F# 2 Basic information schema
*
* DATE LAST ALTERED 02.01.96 CTS5 Hand-over Test
* 12.12.95 Remove references to CONSTRAINT_SCHEMA
*
* QA Status: Full FC
*
* Revised by DWF 1996-03-11
* Added rollback after authid
* Removed EXEC SQL from inside printf
* Fixed identifiers in info schem
* Get constraint schema too in case name is re-used
* Cleanups
* Added visual check warning
* Fixed string length
* Fixed syntax errors
* Fixed bad schema references
****************************************************************
* EXEC SQL BEGIN DECLARE SECTION END-EXEC
01 SQLCODE PIC S9(9) COMP.
01 SQLSTATE PIC X(5).
01 conam1 PIC X(128).
01 cosch1 PIC X(128).
01 chck PIC X(30).
01 indic1 PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
01 co PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
01 co2 PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
01 uid PIC X(18).
01 uidx PIC X(18).
* 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 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, yts767.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 TEST7544 *******************
MOVE 1 TO flag
MOVE 1 TO flag2
DISPLAY " TEST7544 "
DISPLAY " Explicit table constr. in CHECK_CONSTRAINTS
- " view"
DISPLAY "References:"
DISPLAY " 21.2.15 CHECK_CONSTRAINTS view"
DISPLAY " 21.3.13 TABLE_CONSTRAINTS view"
DISPLAY " 11.4 SR9 "
DISPLAY " 11.6 SR1 "
DISPLAY " 11.9 "
DISPLAY " 10.6 SR2 and "
DISPLAY " "
DISPLAY " 11.6 SR2 "
DISPLAY " F# 33 Constraint tables"
DISPLAY " F# 17 Multiple schemas per user"
DISPLAY " F# 3 Basic schema manipulation"
DISPLAY " F# 2 Basic information schema"
DISPLAY " - - - - - - - - - - - - - - - - - - -"
COMPUTE SQLCODE = -1
MOVE "xxxxx" TO SQLSTATE
*ensure CHECK CONSTRAINT in table staff7 schema CTS1 appears
*initialise all variables
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO conam1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO cosch1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO chck
MOVE 99 TO indic1
DISPLAY "SELECT CONSTRAINT_SCHEMA, CONSTRAINT_NAME"
DISPLAY "INTO :cosch1, :conam1"
DISPLAY "FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS"
DISPLAY "WHERE TABLE_SCHEMA = 'CTS1' AND"
DISPLAY "TABLE_NAME = 'STAFF7' AND"
DISPLAY "CONSTRAINT_TYPE = 'CHECK';"
* EXEC SQL SELECT CONSTRAINT_SCHEMA, CONSTRAINT_NAME
* INTO :cosch1, :conam1
* FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS
* WHERE TABLE_SCHEMA = 'CTS1' AND
* TABLE_NAME = 'STAFF7' AND
* CONSTRAINT_TYPE = 'CHECK';
CALL "SUB3" USING SQLCODE SQLSTATE cosch1 conam1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*check row is featured in the CHECK_CONSTRAINTS view
DISPLAY "SELECT CHECK_CLAUSE INTO :chck:indic1"
DISPLAY "FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS"
DISPLAY "WHERE CONSTRAINT_SCHEMA = :cosch1"
DISPLAY "AND CONSTRAINT_NAME = :conam1;"
* EXEC SQL SELECT CHECK_CLAUSE INTO :chck:indic1
* FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS
* WHERE CONSTRAINT_SCHEMA = :cosch1
* AND CONSTRAINT_NAME = :conam1;
CALL "SUB4" USING SQLCODE SQLSTATE chck indic1 cosch1
conam1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*check value returned is correct
*as length of check clause is above 18 chars the implementation
*may store either a NULL value or the check clause itself
if (indic1 = -1) then
DISPLAY "indic1 is -1 -- skip subtest"
else
DISPLAY "Value expected is CHECK (GRADE BETWEEN 1 AND
- " 20)"
DISPLAY "chck is ", chck
if (chck NOT = "CHECK (GRADE BETWEEN 1 AND 20)") then
DISPLAY "VISUAL CHECK REQUIRED -- ALTERNATE SYNTAX MAY
- " BE VALID"
MOVE 0 TO flag2
END-IF
END-IF
DISPLAY " "
*ensure CHECK_CONSTRAINT in table staff7, schema cts1b appears
*initialise all variables
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO conam1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO cosch1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO chck
MOVE 99 TO indic1
DISPLAY "SELECT CONSTRAINT_SCHEMA, CONSTRAINT_NAME"
DISPLAY "INTO :cosch1, :conam1"
DISPLAY "FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS"
DISPLAY "WHERE TABLE_SCHEMA = 'CTS1B' AND"
DISPLAY "TABLE_NAME = 'STAFF7';"
* EXEC SQL SELECT CONSTRAINT_SCHEMA, CONSTRAINT_NAME
* INTO :cosch1, :conam1
* FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS
* WHERE TABLE_SCHEMA = 'CTS1B' AND
* TABLE_NAME = 'STAFF7';
CALL "SUB5" USING SQLCODE SQLSTATE cosch1 conam1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*check row is featured in the CHECK_CONSTRAINTS view
DISPLAY "SELECT CHECK_CLAUSE INTO :chck:indic1"
DISPLAY "FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS"
DISPLAY "WHERE CONSTRAINT_SCHEMA = :cosch1"
DISPLAY "AND CONSTRAINT_NAME = :conam1;"
* EXEC SQL SELECT CHECK_CLAUSE INTO :chck:indic1
* FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS
* WHERE CONSTRAINT_SCHEMA = :cosch1
* AND CONSTRAINT_NAME = :conam1;
CALL "SUB6" USING SQLCODE SQLSTATE chck indic1 cosch1
conam1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*check value returned is correct
*as length of check clause is above 18 chars the implementation
*may store either a NULL value or the check clause itself
if (indic1 = -1) then
DISPLAY "indic1 is -1 -- skip subtest"
else
DISPLAY "Value expected is CHECK (GRADE BETWEEN 1 AND
- " 20)"
DISPLAY "chck is ", chck
if (chck NOT = "CHECK (GRADE BETWEEN 1 AND 20)") then
DISPLAY "VISUAL CHECK REQUIRED -- ALTERNATE SYNTAX MAY
- " BE VALID"
MOVE 0 TO flag2
END-IF
END-IF
DISPLAY " "
*ensure CHECK CONSTRAINT in PROJ_DURATION schema CTS1 appears
*reinitialise all variables
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO conam1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO cosch1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO chck
DISPLAY "SELECT CONSTRAINT_SCHEMA, CONSTRAINT_NAME"
DISPLAY "INTO :cosch1, :conam1"
DISPLAY "FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS"
DISPLAY "WHERE TABLE_SCHEMA = 'CTS1' AND"
DISPLAY "TABLE_NAME = 'PROJ_DURATION';"
* EXEC SQL SELECT CONSTRAINT_SCHEMA, CONSTRAINT_NAME
* INTO :cosch1, :conam1
* FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS
* WHERE TABLE_SCHEMA = 'CTS1' AND
* TABLE_NAME = 'PROJ_DURATION';
CALL "SUB7" USING SQLCODE SQLSTATE cosch1 conam1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*check row is featured in the CHECK_CONSTRAINTS view
DISPLAY "SELECT CHECK_CLAUSE INTO :chck:indic1"
DISPLAY "FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS"
DISPLAY "WHERE CONSTRAINT_SCHEMA = :cosch1"
DISPLAY "AND CONSTRAINT_NAME = :conam1;"
* EXEC SQL SELECT CHECK_CLAUSE INTO :chck:indic1
* FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS
* WHERE CONSTRAINT_SCHEMA = :cosch1
* AND CONSTRAINT_NAME = :conam1;
CALL "SUB8" USING SQLCODE SQLSTATE chck indic1 cosch1 conam1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if (indic1 = -1) then
DISPLAY "indic1 is -1 -- skip subtest"
else
DISPLAY "Value expected is CHECK (MONTHS > 0)"
DISPLAY "chck is ", chck
if (chck NOT = "CHECK (MONTHS > 0)") then
DISPLAY "VISUAL CHECK REQUIRED -- ALTERNATE SYNTAX MAY
- " BE VALID"
MOVE 0 TO flag2
END-IF
END-IF
DISPLAY " "
*ensure CHECK CONSTRAINT in PROJ_DURATION schema CTS1b appears
*reinitialise all variables
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO conam1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO cosch1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO chck
DISPLAY "SELECT CONSTRAINT_SCHEMA, CONSTRAINT_NAME"
DISPLAY "INTO :cosch1, :conam1"
DISPLAY "FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS"
DISPLAY "WHERE TABLE_SCHEMA = 'CTS1B' AND"
DISPLAY "TABLE_NAME = 'PROJ_DURATION';"
* EXEC SQL SELECT CONSTRAINT_SCHEMA, CONSTRAINT_NAME
* INTO :cosch1, :conam1
* FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS
* WHERE TABLE_SCHEMA = 'CTS1B' AND
* TABLE_NAME = 'PROJ_DURATION';
CALL "SUB9" USING SQLCODE SQLSTATE cosch1 conam1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*check row is featured in the CHECK_CONSTRAINTS view
DISPLAY "SELECT CHECK_CLAUSE INTO :chck:indic1"
DISPLAY "FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS"
DISPLAY "WHERE CONSTRAINT_SCHEMA = :cosch1"
DISPLAY "AND CONSTRAINT_NAME = :conam1;"
* EXEC SQL SELECT CHECK_CLAUSE INTO :chck:indic1
* FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS
* WHERE CONSTRAINT_SCHEMA = :cosch1
* AND CONSTRAINT_NAME = :conam1;
CALL "SUB10" USING SQLCODE SQLSTATE chck indic1 cosch1 conam1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*ensure value for CHECK_CLAUSE is as expected
if (indic1 = -1) then
DISPLAY "indic1 is -1 -- skip subtest"
else
DISPLAY "Value expected is CHECK (MONTHS > 0)"
DISPLAY "chck is ", chck
if (chck NOT = "CHECK (MONTHS > 0)") then
DISPLAY "VISUAL CHECK REQUIRED -- ALTERNATE SYNTAX MAY
- " BE VALID"
MOVE 0 TO flag2
END-IF
END-IF
DISPLAY " "
DISPLAY "ROLLBACK WORK;"
* EXEC SQL ROLLBACK WORK;
CALL "SUB11" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if (flag NOT = 1) then
DISPLAY " yts767.mco *** fail *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7544','fail','MCO');
CALL "SUB12" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
COMPUTE errcnt = errcnt + 1
else
if (flag2 = 1) then
DISPLAY " yts767.mco *** pass *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7544','pass','MCO');
CALL "SUB13" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
else
DISPLAY " yts767.mco *** nogo *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7544','nogo','MCO');
CALL "SUB14" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
COMPUTE errcnt = errcnt + 1
END-IF
END-IF
DISPLAY "==============================================="
* EXEC SQL COMMIT WORK;
CALL "SUB15" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
******************** END TEST7544 ********************
******************** BEGIN TEST7545 *******************
MOVE 1 TO flag
MOVE 1 TO flag2
DISPLAY " TEST7545 "
DISPLAY " Column constraints in CHECK_CONSTRAINTS view"
DISPLAY "References:"
DISPLAY " 21.2.15 CHECK_CONSTRAINTS view"
DISPLAY " 21.3.13 TABLE_CONSTRAINTS view"
DISPLAY " 11.4 SR9 "
DISPLAY " 11.6 SR1 "
DISPLAY " 11.9 "
DISPLAY " 10.6 SR2 and "
DISPLAY " "
DISPLAY " 11.6 SR2 "
DISPLAY " F# 33 Constraint tables"
DISPLAY " F# 17 Multiple Schemas Per User"
DISPLAY " F# 3 Basic Schema Manipulation"
DISPLAY " F# 2 Basic information schema"
DISPLAY " - - - - - - - - - - - - - - - - - - -"
COMPUTE SQLCODE = -1
MOVE "xxxxx" TO SQLSTATE
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO conam1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO cosch1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO chck
DISPLAY "SELECT CONSTRAINT_SCHEMA, CONSTRAINT_NAME"
DISPLAY "INTO :cosch1, :conam1"
DISPLAY "FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS"
DISPLAY "WHERE TABLE_SCHEMA = 'CTS1' AND"
DISPLAY "CONSTRAINT_TYPE = 'CHECK' AND"
DISPLAY "TABLE_NAME = 'STAFFZ';"
* EXEC SQL SELECT CONSTRAINT_SCHEMA, CONSTRAINT_NAME
* INTO :cosch1, :conam1
* FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS
* WHERE TABLE_SCHEMA = 'CTS1' AND
* CONSTRAINT_TYPE = 'CHECK' AND
* TABLE_NAME = 'STAFFZ';
CALL "SUB16" USING SQLCODE SQLSTATE cosch1 conam1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "SELECT CHECK_CLAUSE INTO :chck:indic1"
DISPLAY "FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS"
DISPLAY "WHERE CONSTRAINT_SCHEMA = :cosch1"
DISPLAY "AND CONSTRAINT_NAME = :conam1;"
* EXEC SQL SELECT CHECK_CLAUSE INTO :chck:indic1
* FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS
* WHERE CONSTRAINT_SCHEMA = :cosch1
* AND CONSTRAINT_NAME = :conam1;
CALL "SUB17" USING SQLCODE SQLSTATE chck indic1 cosch1 conam1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if (indic1 = -1) then
DISPLAY "indic1 is -1 -- skip subtest"
else
DISPLAY "Value expected is CHECK (SALARY > 0)"
DISPLAY "chck is ", chck
if (chck NOT = "CHECK (SALARY > 0)") then
DISPLAY "VISUAL CHECK REQUIRED -- ALTERNATE SYNTAX MAY
- " BE VALID"
MOVE 0 TO flag2
END-IF
END-IF
DISPLAY " "
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO conam1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO cosch1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO chck
DISPLAY "SELECT CONSTRAINT_SCHEMA, CONSTRAINT_NAME"
DISPLAY "INTO :cosch1, :conam1"
DISPLAY "FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS"
DISPLAY "WHERE TABLE_SCHEMA = 'CTS1B' AND"
DISPLAY "CONSTRAINT_TYPE = 'CHECK' AND"
DISPLAY "TABLE_NAME = 'STAFFZ';"
* EXEC SQL SELECT CONSTRAINT_SCHEMA, CONSTRAINT_NAME
* INTO :cosch1, :conam1
* FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS
* WHERE TABLE_SCHEMA = 'CTS1B' AND
* CONSTRAINT_TYPE = 'CHECK' AND
* TABLE_NAME = 'STAFFZ';
CALL "SUB18" USING SQLCODE SQLSTATE cosch1 conam1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "SELECT CHECK_CLAUSE INTO :chck:indic1"
DISPLAY "FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS"
DISPLAY "WHERE CONSTRAINT_SCHEMA = :cosch1"
DISPLAY "AND CONSTRAINT_NAME = :conam1;"
* EXEC SQL SELECT CHECK_CLAUSE INTO :chck:indic1
* FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS
* WHERE CONSTRAINT_SCHEMA = :cosch1
* AND CONSTRAINT_NAME = :conam1;
CALL "SUB19" USING SQLCODE SQLSTATE chck indic1 cosch1 conam1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if (indic1 = -1) then
DISPLAY "indic1 is -1 -- skip subtest"
else
DISPLAY "Value expected is CHECK (SALARY > 0)"
DISPLAY "chck is ", chck
if (chck NOT = "CHECK (SALARY > 0)") then
DISPLAY "VISUAL CHECK REQUIRED -- ALTERNATE SYNTAX MAY
- " BE VALID"
MOVE 0 TO flag2
END-IF
END-IF
DISPLAY " "
DISPLAY "ROLLBACK WORK;"
* EXEC SQL ROLLBACK WORK;
CALL "SUB20" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if (flag NOT = 1) then
DISPLAY " yts767.mco *** fail *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7545','fail','MCO');
CALL "SUB21" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
COMPUTE errcnt = errcnt + 1
else
if (flag2 = 1) then
DISPLAY " yts767.mco *** pass *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7545','pass','MCO');
CALL "SUB22" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
else
DISPLAY " yts767.mco *** nogo *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7545','nogo','MCO');
CALL "SUB23" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
COMPUTE errcnt = errcnt + 1
END-IF
END-IF
DISPLAY "==============================================="
* EXEC SQL COMMIT WORK;
CALL "SUB24" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
******************** END TEST7545 ********************
******************** BEGIN TEST7546 *******************
MOVE 1 TO flag
MOVE 1 TO flag2
DISPLAY " TEST7546 "
DISPLAY " Domain constraints in CHECK_CONSTRAINTS view"
DISPLAY "References:"
DISPLAY " 21.2.15 CHECK_CONSTRAINTS view"
DISPLAY " 21.3.13 TABLE_CONSTRAINTS view"
DISPLAY " 11.4 SR9 "
DISPLAY " 11.6 SR1 "
DISPLAY " 11.9 "
DISPLAY " 10.6 SR2 and "
DISPLAY " "
DISPLAY " 11.6 SR2 "
DISPLAY " 11.21 "
DISPLAY " F# 33 Constraint tables"
DISPLAY " F# 25 Domain definition"
DISPLAY " F# 17 Multiple Schemas Per User"
DISPLAY " F# 3 Basic Schema Manipulation"
DISPLAY " F# 2 Basic information schema"
DISPLAY " - - - - - - - - - - - - - - - - - - -"
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO conam1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO cosch1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO chck
DISPLAY "SELECT CONSTRAINT_SCHEMA, CONSTRAINT_NAME"
DISPLAY "INTO :cosch1, :conam1"
DISPLAY "FROM INFORMATION_SCHEMA.DOMAIN_CONSTRAINTS"
DISPLAY "WHERE DOMAIN_SCHEMA = 'CTS1' AND"
DISPLAY "DOMAIN_NAME = 'ESAL';"
* EXEC SQL SELECT CONSTRAINT_SCHEMA, CONSTRAINT_NAME
* INTO :cosch1, :conam1
* FROM INFORMATION_SCHEMA.DOMAIN_CONSTRAINTS
* WHERE DOMAIN_SCHEMA = 'CTS1' AND
* DOMAIN_NAME = 'ESAL';
CALL "SUB25" USING SQLCODE SQLSTATE cosch1 conam1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "SELECT CHECK_CLAUSE INTO :chck:indic1"
DISPLAY "FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS"
DISPLAY "WHERE CONSTRAINT_SCHEMA = :cosch1"
DISPLAY "AND CONSTRAINT_NAME = :conam1;"
* EXEC SQL SELECT CHECK_CLAUSE INTO :chck:indic1
* FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS
* WHERE CONSTRAINT_SCHEMA = :cosch1
* AND CONSTRAINT_NAME = :conam1;
CALL "SUB26" USING SQLCODE SQLSTATE chck indic1 cosch1 conam1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if (indic1 = -1) then
DISPLAY "indic1 is -1 -- skip subtest"
else
DISPLAY "Value expected is CHECK (VALUE > 500)"
DISPLAY "chck is ", chck
if (chck NOT = "CHECK (VALUE > 500)") then
DISPLAY "VISUAL CHECK REQUIRED -- ALTERNATE SYNTAX MAY
- " BE VALID"
MOVE 0 TO flag2
END-IF
END-IF
DISPLAY " "
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO conam1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO cosch1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO chck
DISPLAY "SELECT CONSTRAINT_SCHEMA, CONSTRAINT_NAME"
DISPLAY "INTO :cosch1, :conam1"
DISPLAY "FROM INFORMATION_SCHEMA.DOMAIN_CONSTRAINTS"
DISPLAY "WHERE DOMAIN_SCHEMA = 'CTS1B' AND"
DISPLAY "DOMAIN_NAME = 'ESAL';"
* EXEC SQL SELECT CONSTRAINT_SCHEMA, CONSTRAINT_NAME
* INTO :cosch1, :conam1
* FROM INFORMATION_SCHEMA.DOMAIN_CONSTRAINTS
* WHERE DOMAIN_SCHEMA = 'CTS1B' AND
* DOMAIN_NAME = 'ESAL';
CALL "SUB27" USING SQLCODE SQLSTATE cosch1 conam1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "SELECT CHECK_CLAUSE INTO :chck:indic1"
DISPLAY "FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS"
DISPLAY "WHERE CONSTRAINT_SCHEMA = :cosch1"
DISPLAY "AND CONSTRAINT_NAME = :conam1;"
* EXEC SQL SELECT CHECK_CLAUSE INTO :chck:indic1
* FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS
* WHERE CONSTRAINT_SCHEMA = :cosch1
* AND CONSTRAINT_NAME = :conam1;
CALL "SUB28" USING SQLCODE SQLSTATE chck indic1 cosch1 conam1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if (indic1 = -1) then
DISPLAY "indic1 is -1 -- skip subtest"
else
DISPLAY "Value expected is CHECK (VALUE > 500)"
DISPLAY "chck is ", chck
if (chck NOT = "CHECK (VALUE > 500)") then
DISPLAY "VISUAL CHECK REQUIRED -- ALTERNATE SYNTAX MAY
- " BE VALID"
MOVE 0 TO flag2
END-IF
END-IF
DISPLAY " "
DISPLAY "ROLLBACK WORK;"
* EXEC SQL ROLLBACK WORK;
CALL "SUB29" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if (flag NOT = 1) then
DISPLAY " yts767.mco *** fail *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7546','fail','MCO');
CALL "SUB30" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
COMPUTE errcnt = errcnt + 1
else
if (flag2 = 1) then
DISPLAY " yts767.mco *** pass *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7546','pass','MCO');
CALL "SUB31" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
else
DISPLAY " yts767.mco *** nogo *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7546','nogo','MCO');
CALL "SUB32" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
COMPUTE errcnt = errcnt + 1
END-IF
END-IF
DISPLAY "==============================================="
* EXEC SQL COMMIT WORK;
CALL "SUB33" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
******************** END TEST7546 ********************
******************** BEGIN TEST7547 *******************
MOVE 1 TO flag
DISPLAY " TEST7547 "
DISPLAY " Unique identification in CHECK_CONSTRAINTS
- " view"
DISPLAY "References:"
DISPLAY " 21.2.15 CHECK_CONSTRAINTS view"
DISPLAY " 21.3.13 TABLE_CONSTRAINTS view"
DISPLAY " 11.4 SR9 "
DISPLAY " 11.6 SR1 "
DISPLAY " 11.9 "
DISPLAY " 10.6 SR2 and "
DISPLAY " "
DISPLAY " 11.6 SR2 "
DISPLAY " F# 33 Constraint tables"
DISPLAY " F# 17 Multiple Schemas Per User"
DISPLAY " F# 3 Basic Schema Manipulation"
DISPLAY " F# 2 Basic information schema"
DISPLAY " - - - - - - - - - - - - - - - - - - -"
*check CONSTRAINT_CATALOG contains no NULL values
DISPLAY "SELECT COUNT (*) INTO :co"
DISPLAY "FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS"
DISPLAY "WHERE CONSTRAINT_CATALOG IS NULL"
* EXEC SQL SELECT COUNT (*) INTO :co
* FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS
* WHERE CONSTRAINT_CATALOG IS NULL;
CALL "SUB34" USING SQLCODE SQLSTATE co
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "co should be 0; its value is ", co
if (co NOT = 0) then
MOVE 0 TO flag
END-IF
*check constraint_schema contains no null values
DISPLAY "SELECT COUNT (*) INTO :co"
DISPLAY "FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS"
DISPLAY "WHERE CONSTRAINT_SCHEMA IS NULL;"
* EXEC SQL SELECT COUNT (*) INTO :co
* FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS
* WHERE CONSTRAINT_SCHEMA IS NULL;
CALL "SUB35" USING SQLCODE SQLSTATE co
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "co should be 0; its value is ", co
if (co NOT = 0) then
MOVE 0 TO flag
END-IF
*check constraint_name contains no NULL values
DISPLAY "SELECT COUNT (*) INTO :co"
DISPLAY "FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS"
DISPLAY "WHERE CONSTRAINT_NAME IS NULL;"
* EXEC SQL SELECT COUNT (*) INTO :co
* FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS
* WHERE CONSTRAINT_NAME IS NULL;
CALL "SUB36" USING SQLCODE SQLSTATE co
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "co should be 0; its value is ", co
if (co NOT = 0) then
MOVE 0 TO flag
END-IF
*check combined values of CATALOG,
*NAME and SCHEMA are unique
MOVE 99 TO co
COMPUTE co2 = -1
DISPLAY "SELECT COUNT (*) INTO :co"
DISPLAY "FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS;"
* EXEC SQL SELECT COUNT (*) INTO :co
* FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS;
CALL "SUB37" USING SQLCODE SQLSTATE co
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "SELECT COUNT (*) INTO :co2"
DISPLAY "FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS AS T"
DISPLAY "WHERE"
DISPLAY "UNIQUE ("
DISPLAY " SELECT * FROM
- " INFORMATION_SCHEMA.CHECK_CONSTRAINTS"
DISPLAY " WHERE CONSTRAINT_CATALOG =
- " T.CONSTRAINT_CATALOG AND"
DISPLAY " CONSTRAINT_NAME = T.CONSTRAINT_NAME AND"
DISPLAY " CONSTRAINT_SCHEMA = T.CONSTRAINT_SCHEMA"
DISPLAY " );"
* EXEC SQL SELECT COUNT (*) INTO :co2
* FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS AS T
* WHERE
* UNIQUE (
* SELECT * FROM INFORMATION_SCHEMA.CHECK_CONSTRAINTS
* WHERE CONSTRAINT_CATALOG = T.CONSTRAINT_CATALOG AND
* CONSTRAINT_NAME = T.CONSTRAINT_NAME AND
* CONSTRAINT_SCHEMA = T.CONSTRAINT_SCHEMA
* );
CALL "SUB38" USING SQLCODE SQLSTATE co2
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "co should be equal to co2; co is ", co, ", co2 is
- " ", co2
if (co NOT = co2) then
MOVE 0 TO flag
END-IF
DISPLAY "ROLLBACK WORK;"
* EXEC SQL ROLLBACK WORK;
CALL "SUB39" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if ( flag = 1 ) then
DISPLAY " yts767.mco *** pass *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7547','pass','MCO');
CALL "SUB40" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
else
DISPLAY " yts767.mco *** fail *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7547','fail','MCO');
CALL "SUB41" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
COMPUTE errcnt = errcnt + 1
END-IF
DISPLAY "==============================================="
* EXEC SQL COMMIT WORK;
CALL "SUB42" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
******************** END TEST7547 ********************
**** 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.73 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.
|
| |