Quellcode-Bibliothek
© Kompilation durch diese Firma
[Weder Korrektheit noch Funktionsfähigkeit der Software werden zugesichert.]
Datei:
xts730.cob
Sprache: Cobol
|
|
IDENTIFICATION DIVISION.
PROGRAM-ID. XTS730.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. xyz.
OBJECT-COMPUTER. xyz.
DATA DIVISION.
WORKING-STORAGE SECTION.
* EMBEDDED COBOL (file "XTS730.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
*
* XTS730.PCO
* WRITTEN BY: Manolis Megaloikonomou
* TRANSLATED AUTOMATICALLY FROM EMBEDDED C BY CHRIS SCHANZLE
*
* Table name with 19 characters - delimited.
*
* REFERENCES
* 11.3 -- <table definition>
* 5.4 -- <Names and identifiers>
* 5.4 GR.1
* 5.2 -- <token> and <separator>
* 5.2 SR.9
* 5.2 SR.13
* 5.2 SR.14
* 5.2 LR.2a -- Raised. Entry SQL restriction which
* restricted the length of a <regular identifier>
* up to 18 <character representation>s.
* F#2 -- Basic information schema.
* F#3 -- Basic schema manipulation.
* F#39 -- Long identifiers.
*
* DATE LAST ALTERED 12/12/95 CTS5 Hand-over Test
*
* Cleanups and fixes by V. Kogakis 05/12/95:
* Include Files
* Define NOSUBCLASS/CHCKOK at test beginning
* Define cal variable
* Add ROLLBACK after AUTHID
* print timestamp
* delete multiple SQLCODE and SQLSTATE initialisation
* change string initialisation
* Clean-up database at the end of the test
*
* QA Status: Full FC
*
*Revised by DWF 1996-02-05
* Fixed SDL transactions
* Fixed printouts
* Removed CHCKOK after cursor definition
* Removed field widths from printfs
****************************************************************
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 aa PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
01 bb PIC X(49).
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, xts730.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 TEST7030 *******************
MOVE 1 TO flag
DISPLAY " TEST7030 "
DISPLAY " Table name with 19 characters - delimited."
DISPLAY "References:"
DISPLAY " 11.3 -- "
DISPLAY " 5.4 -- "
DISPLAY " 5.4 GR.1"
DISPLAY " 5.2 -- and "
DISPLAY " 5.2 SR.9"
DISPLAY " 5.2 SR.13"
DISPLAY " 5.2 SR.14"
DISPLAY " 5.2 LR.2a -- Raised. Entry SQL restriction
- " which"
DISPLAY " restricted the length of a
- " identifier>"
DISPLAY " up to 18 s."
DISPLAY " F#2 -- Basic information schema."
DISPLAY " F#3 -- Basic schema manipulation."
DISPLAY " F#39 -- Long identifiers."
DISPLAY " - - - - - - - - - - - - - - - - - - -"
DISPLAY "Note: This test will need some changes if your
- " collating"
DISPLAY "sequence is not ASCII."
*Initialise error reporting variables
COMPUTE SQLCODE = -1
MOVE "xxxxx" TO SQLSTATE
*Create tables
*Ensure all have names which are 19 characters long
*Ensure names include upper & lower cases, digits and punctuatio
DISPLAY "CREATE TABLE ""LONGIDENTIFIERSAAAA"" (TNUM
- " NUMERIC(5));"
EXEC SQL CREATE TABLE LONGIDENTIFIERSAAAA (TNUM
NUMERIC(5)) 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 ""longidentifiersaaab"" (TNUM
- " NUMERIC(5));"
EXEC SQL CREATE TABLE longidentifiersaaab (TNUM
NUMERIC(5)) 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 ""0""""LONGIDENTIFIERS_1"" (TNUM
- " NUMERIC(5));"
EXEC SQL CREATE TABLE LONGIDENTIFIERS_1 (TNUM
NUMERIC(5)) 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 ""0""""LONGIDENTIFIERS_2"" (TNUM
- " NUMERIC(5));"
EXEC SQL CREATE TABLE LONGIDENTIFIERS_2 (TNUM
NUMERIC(5)) 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 ""lngIDENTIFIER% .,()"" (TNUM
- " NUMERIC(5));"
EXEC SQL CREATE TABLE lngIDENTIFIER (TNUM
NUMERIC(5)) 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 " "
*Initialize host variables
MOVE 99 TO aa
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO
bb
*Ensure all tables are mentioned in the INFORMATION_SCHEMA
DISPLAY "SELECT COUNT(*) INTO :aa FROM
- " INFORMATION_SCHEMA.TABLES"
DISPLAY "WHERE TABLE_SCHEMA = 'CTS1' AND TABLE_TYPE = 'BASE
- " TABLE'"
DISPLAY "AND (TABLE_NAME = 'LONGIDENTIFIERSAAAA'"
DISPLAY " OR TABLE_NAME = 'longidentifiersaaab'"
DISPLAY " OR TABLE_NAME = '0""LONGIDENTIFIERS_1'"
DISPLAY " OR TABLE_NAME = '0""LONGIDENTIFIERS_2'"
DISPLAY " OR TABLE_NAME = 'lngIDENTIFIER% .,()' );"
EXEC SQL SELECT COUNT(*) INTO :aa
FROM INFORMATION_SCHEMA.TABLES
WHERE TABLE_SCHEMA = 'CTS1'
AND TABLE_TYPE = 'BASE TABLE'
AND ( TABLE_NAME = 'LONGIDENTIFIERSAAAA'
OR TABLE_NAME = 'longidentifiersaaab'
OR TABLE_NAME = '0"LONGIDENTIFIERS_1'
OR TABLE_NAME = '0"LONGIDENTIFIERS_2'
OR TABLE_NAME = 'lngIDENTIFIER% .,()' ) END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "aa should be 5; its value is: aa = ", aa
if ( aa NOT = 5 ) then
MOVE 0 TO flag
END-IF
DISPLAY " "
*Ensure all INFORMATION_SCHEMA entries are correct
DISPLAY "DECLARE a CURSOR"
DISPLAY "FOR SELECT TABLE_NAME FROM
- " INFORMATION_SCHEMA.TABLES"
DISPLAY "WHERE TABLE_SCHEMA = 'CTS1' AND TABLE_TYPE = 'BASE
- " TABLE'"
DISPLAY "AND (TABLE_NAME = 'LONGIDENTIFIERSAAAA'"
DISPLAY " OR TABLE_NAME = 'longidentifiersaaab'"
DISPLAY " OR TABLE_NAME = '0""LONGIDENTIFIERS_1'"
DISPLAY " OR TABLE_NAME = '0""LONGIDENTIFIERS_2'"
DISPLAY " OR TABLE_NAME = 'lngIDENTIFIER% .,()' );"
DISPLAY "ORDER BY TABLE_NAME;"
EXEC SQL DECLARE a CURSOR
FOR SELECT TABLE_NAME FROM INFORMATION_SCHEMA.TABLES
WHERE TABLE_SCHEMA = 'CTS1' AND TABLE_TYPE = 'BASE TABLE'
AND ( TABLE_NAME = 'LONGIDENTIFIERSAAAA'
OR TABLE_NAME = 'longidentifiersaaab'
OR TABLE_NAME = '0"LONGIDENTIFIERS_1'
OR TABLE_NAME = '0"LONGIDENTIFIERS_2'
OR TABLE_NAME = 'lngIDENTIFIER% .,()' )
ORDER BY TABLE_NAME END-EXEC
DISPLAY "OPEN a;"
EXEC SQL OPEN a END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "FETCH a INTO :bb;"
EXEC SQL FETCH a INTO :bb END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "bb should be 0""LONGIDENTIFIERS_1; its value is ",
bb
if (bb NOT = "0""LONGIDENTIFIERS_1") then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO
bb
DISPLAY "FETCH a INTO :bb;"
EXEC SQL FETCH a INTO :bb END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "bb should be 0""LONGIDENTIFIERS_2; its value is ",
bb
if (bb NOT = "0""LONGIDENTIFIERS_2") then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO
bb
DISPLAY "FETCH a INTO :bb;"
EXEC SQL FETCH a INTO :bb END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "bb should be LONGIDENTIFIERSAAAA; its value is ",
bb
if (bb NOT = "LONGIDENTIFIERSAAAA") then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO
bb
DISPLAY "FETCH a INTO :bb;"
EXEC SQL FETCH a INTO :bb END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "bb should be lngIDENTIFIER% .,(); its value is ",
bb
if (bb NOT = "lngIDENTIFIER% .,()") then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO
bb
DISPLAY "FETCH a INTO :bb;"
EXEC SQL FETCH a INTO :bb END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "bb should be longidentifiersaaab; its value is ",
bb
if (bb NOT = "longidentifiersaaab") 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 " "
*Now clean-up database
DISPLAY "DROP TABLE ""LONGIDENTIFIERSAAAA"" CASCADE;"
EXEC SQL DROP TABLE LONGIDENTIFIERSAAAA END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "DROP TABLE ""longidentifiersaaab"" CASCADE;"
EXEC SQL DROP TABLE longidentifiersaaab END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "DROP TABLE ""0""""LONGIDENTIFIERS_1"" CASCADE;"
EXEC SQL DROP TABLE LONGIDENTIFIERS_1 END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "DROP TABLE ""0""""LONGIDENTIFIERS_2"" CASCADE;"
EXEC SQL DROP TABLE LONGIDENTIFIERS_2 END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "DROP TABLE ""lngIDENTIFIER% .,()"" CASCADE;"
EXEC SQL DROP TABLE lngIDENTIFIER 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 " "
if ( flag = 1 ) then
DISPLAY " xts730.pco *** pass *** "
EXEC SQL INSERT INTO CTS1.TESTREPORT
VALUES('7030','pass','PCO') END-EXEC
MOVE SQLCODE TO SQL-COD
else
DISPLAY " xts730.pco *** fail *** "
EXEC SQL INSERT INTO CTS1.TESTREPORT
VALUES('7030','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 TEST7030 ********************
**** 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.9 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.
|
|
|