IDENTIFICATION DIVISION.
PROGRAM-ID. YTS789.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. xyz.
OBJECT-COMPUTER. xyz.
DATA DIVISION.
WORKING-STORAGE SECTION.
* EMBEDDED COBOL (file "YTS789.PCO")
*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
*
* YTS789.PCO
* WRITTEN BY: Susan Watters
* TRANSLATED AUTOMATICALLY FROM EMBEDDED C BY CHRIS SCHANZLE
*
* CREATE CHAR SET in schema def,COLLATION FROM DEFAULT
*
*
* REFERENCES
* 11.28 <character set definition>
* 11.1 <schema definition>
* 21.2.18 CHARACTER_SETS view
* F#45 Character set definition
* F#31 Schema definition statement
* F#2 Basic information schema
*
* DATE LAST ALTERED 02.01.96 CTS5 Hand-over Test
*
* QA Status: Full FC
*
* Revised by DWF 1996-03-21
* Changes very similar to yts788
* Fixed schema references
* Fixed char set usage
* Deleted problematic subtest
* Init flag2
****************************************************************
EXEC SQL BEGIN DECLARE SECTION END-EXEC
01 SQLCODE PIC S9(9) COMP.
01 SQLSTATE PIC X(5).
01 i PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
01 form1 PIC X(128).
01 form2 PIC X(128).
01 num1 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
01 num2 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
01 cat1 PIC X(128).
01 cat2 PIC X(128).
01 schem1 PIC X(128).
01 schem2 PIC X(128).
01 name1 PIC X(128).
01 name2 PIC X(128).
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 k 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 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, yts789.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 TEST7523 *******************
MOVE 1 TO flag
MOVE 1 TO flag2
DISPLAY " TEST7523 "
DISPLAY " CREATE CHAR SET in schema def,COLLATION FROM
- " DEFLT"
DISPLAY "References:"
DISPLAY " 11.28 "
DISPLAY " 11.1 "
DISPLAY " 21.2.18 CHARACTER_SETS view"
DISPLAY " F#45 Character set definition"
DISPLAY " F#31 Schema definition statement"
DISPLAY " F#2 Basic information schema"
DISPLAY " - - - - - - - - - - - - - - - - - - -"
COMPUTE SQLCODE = -1
MOVE "xxxxx" TO SQLSTATE
*initialise host variables
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO cat1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO cat2
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO form1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO form2
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO name1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO name2
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO schem1
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
- "xxxxxxxx" TO schem2
COMPUTE num1 = -1
COMPUTE num2 = -1
*create schema CTSC
DISPLAY "CREATE SCHEMA CTSC"
DISPLAY " "
DISPLAY "CREATE CHARACTER SET CST GET SQL_TEXT"
DISPLAY " COLLATION FROM DEFAULT"
DISPLAY " "
DISPLAY "CREATE TABLE Tab"
DISPLAY " Col1 CHARACTER(3) CHARACTER SET CST"
EXEC SQL CREATE SCHEMA CTSC
CREATE CHARACTER SET CST GET SQL_TEXT
COLLATION FROM DEFAULT
CREATE TABLE Tab
(Col1 CHARACTER(3) CHARACTER SET CST) 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 "SELECT COUNT(*) INTO :i"
DISPLAY "FROM INFORMATION_SCHEMA.CHARACTER_SETS WHERE "
DISPLAY "CHARACTER_SET_SCHEMA = 'CTSC'"
DISPLAY "AND CHARACTER_SET_NAME = 'CST';"
EXEC SQL SELECT COUNT(*) INTO :i
FROM INFORMATION_SCHEMA.CHARACTER_SETS WHERE
CHARACTER_SET_SCHEMA = 'CTSC'
AND CHARACTER_SET_NAME = 'CST' END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "i should be 1; its value is ", i
if (i NOT = 1) then
MOVE 0 TO flag
END-IF
*check row inserted in CHARACTER_SETS view is correct
*return new row for CST
DISPLAY "The following two selects should return the same
- " results."
DISPLAY "SELECT FORM_OF_USE, NUMBER_OF_CHARACTERS,"
DISPLAY "DEFAULT_COLLATE_CATALOG, DEFAULT_COLLATE_SCHEMA,"
DISPLAY "DEFAULT_COLLATE_NAME "
DISPLAY "INTO :form1, :num1, :cat1, :schem1, :name1"
DISPLAY "FROM INFORMATION_SCHEMA.CHARACTER_SETS"
DISPLAY "WHERE CHARACTER_SET_SCHEMA = 'CTSC'"
DISPLAY "AND CHARACTER_SET_NAME = 'CST';"
EXEC SQL SELECT FORM_OF_USE, NUMBER_OF_CHARACTERS,
DEFAULT_COLLATE_CATALOG, DEFAULT_COLLATE_SCHEMA,
DEFAULT_COLLATE_NAME
INTO :form1, :num1, :cat1, :schem1, :name1
FROM INFORMATION_SCHEMA.CHARACTER_SETS
WHERE CHARACTER_SET_SCHEMA = 'CTSC'
AND CHARACTER_SET_NAME = 'CST' END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*get row for SQL_TEXT - should contain same as new row
DISPLAY "SELECT FORM_OF_USE, NUMBER_OF_CHARACTERS,"
DISPLAY "DEFAULT_COLLATE_CATALOG, DEFAULT_COLLATE_SCHEMA,"
DISPLAY "DEFAULT_COLLATE_NAME "
DISPLAY "INTO :form2, :num2, :cat2, :schem2, :name2"
DISPLAY "FROM INFORMATION_SCHEMA.CHARACTER_SETS"
DISPLAY "WHERE CHARACTER_SET_SCHEMA = 'INFORMATION_SCHEMA'"
DISPLAY "AND CHARACTER_SET_NAME = 'SQL_TEXT';"
EXEC SQL SELECT FORM_OF_USE, NUMBER_OF_CHARACTERS,
DEFAULT_COLLATE_CATALOG, DEFAULT_COLLATE_SCHEMA,
DEFAULT_COLLATE_NAME
INTO :form2, :num2, :cat2, :schem2, :name2
FROM INFORMATION_SCHEMA.CHARACTER_SETS
WHERE CHARACTER_SET_SCHEMA = 'INFORMATION_SCHEMA'
AND CHARACTER_SET_NAME = 'SQL_TEXT' END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "Comparing values...."
if (form1 NOT = form2) then
MOVE 0 TO flag2
END-IF
if (num1 NOT = num2) then
MOVE 0 TO flag2
END-IF
if (cat1 NOT = cat2) then
MOVE 0 TO flag2
END-IF
if (schem1 NOT = schem2) then
MOVE 0 TO flag2
END-IF
if (name1 NOT = name2) then
MOVE 0 TO flag2
END-IF
if (flag2 = 0) then
DISPLAY "Values do not match"
DISPLAY "form1 is ", form1
DISPLAY "num1 is ", num1
DISPLAY "cat1 is ", cat1
DISPLAY "schem1 is ", schem1
DISPLAY "name1 is ", name1
DISPLAY "form2 is ", form2
DISPLAY "num2 is ", num2
DISPLAY "cat2 is ", cat2
DISPLAY "schem2 is ", schem2
DISPLAY "name2 is ", name2
MOVE 0 TO flag
else
DISPLAY "Row inserted into CHARACTER_SETS view is
- " correct"
END-IF
DISPLAY " "
DISPLAY "INSERT INTO CTSC.Tab VALUES (_CTSC.CST 'f')"
EXEC SQL INSERT INTO CTSC.Tab VALUES (_CTSC.CST 'f')
END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
MOVE 0 TO i
DISPLAY "SELECT COUNT (*) INTO :i FROM CTSC.Tab;"
EXEC SQL SELECT COUNT (*) INTO :i FROM CTSC.Tab END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "i should be 1; its value is ", i
if (i NOT = 1) then
MOVE 0 TO flag
END-IF
DISPLAY "ROLLBACK WORK;"
EXEC SQL ROLLBACK WORK END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "DROP SCHEMA CTSC CASCADE"
EXEC SQL DROP SCHEMA CTSC 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 " "
if ( flag = 1 ) then
DISPLAY " yts789.pco *** pass *** "
EXEC SQL INSERT INTO CTS1.TESTREPORT
VALUES('7523','pass','PCO') END-EXEC
MOVE SQLCODE TO SQL-COD
else
DISPLAY " yts789.pco *** fail *** "
EXEC SQL INSERT INTO CTS1.TESTREPORT
VALUES('7523','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 TEST7523 ********************
**** 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.39Angebot
Wie Sie bei der Firma Beratungs- und Dienstleistungen beauftragen können
¤
|
Lebenszyklus
Die hierunter aufgelisteten Ziele sind für diese Firma wichtig
Ziele
Entwicklung einer Software für die statische Quellcodeanalyse
|