IDENTIFICATION DIVISION.
PROGRAM-ID. XTS799.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. xyz.
OBJECT-COMPUTER. xyz.
DATA DIVISION.
WORKING-STORAGE SECTION.
* Standard COBOL (file "XTS799.SCO") calling SQL
* procedures in file "XTS799.MCO".
*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
*
* XTS799.SCO
* WRITTEN BY: Nickos Backalidis
* TRANSLATED AUTOMATICALLY FROM EMBEDDED COBOL BY CHRIS SCHANZLE
*
* COALESCE with three <value expression>s
*
* REFERENCES
* 6.9 FT.2 -- <case abbreviation>
* 6.9 SR.2
* 6.9 SR.3
* 6.9 LR.2a Raised. Entry SQL restriction which prohibited
* the use of a <case expression>
* 6.11 LR.2c Raised. Entry SQL restriction which stated that
* a <value expression primary> should not be a
* <case expression>
* 9.3 -- <Set operation result data types>
* 9.3 SR.3
* F#26 -- CASE expression
*
* DATE LAST ALTERED 18/12/95 CTS5 Hand-over Test
*
* Cleanups and fixes by V. Kogakis 18/12/95
* Print timestamp
* Include Files
* Define NOSUBCLASS/CHCKOK at test beginning
*
* QA STATUS : QA CHECK
*
* Revised by DWF 1996-02-28
* Fixed coding rule violations (variable names, field widths)
* Removed status checks after cursor definitions
* Fixed printout and pass criteria
* Initialized variables as required by test code
* Fixed string lengths
****************************************************************
* 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 hmpnum PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
01 numhst PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
01 strhst PIC X(20).
01 indic1 PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
01 indic2 PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
01 hv1 PIC X(20).
01 hv2 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;
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, xts799.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 TEST7003 *******************
MOVE 1 TO flag
DISPLAY " TEST7003 "
DISPLAY " COALESCE with three s "
DISPLAY " References:"
DISPLAY " 6.9 FT.2 -- "
DISPLAY " 6.9 SR.2"
DISPLAY " 6.9 SR.3"
DISPLAY " 6.9 LR.2a Raised. Entry SQL restriction which
- " prohibited"
DISPLAY " the use of a "
DISPLAY " 6.11 LR.2c Raised. Entry SQL restriction which
- " stated that"
DISPLAY " a
- " should not be a"
DISPLAY "
- " "
DISPLAY " 9.3 -- "
DISPLAY " 9.3 SR.3"
DISPLAY " F#26 -- CASE expression"
DISPLAY " - - - - - - - - - - - - - - - - - - -"
*Populate the table CL_EMPLOYEE with 5 rows
COMPUTE SQLCODE = -1
MOVE "xxxxx" TO SQLSTATE
*Ensure that the table CL_EMPLOYEE is empty
DISPLAY "DELETE FROM CL_EMPLOYEE;"
* EXEC SQL DELETE FROM CL_EMPLOYEE;
CALL "SUB3" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
DISPLAY "COMMIT WORK;"
* EXEC SQL COMMIT WORK;
CALL "SUB4" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "INSERT INTO CL_EMPLOYEE
- " VALUES(5000,NULL,NULL,NULL,NULL,NULL,NULL);"
* EXEC SQL INSERT INTO CL_EMPLOYEE
* VALUES(5000,NULL,NULL,NULL,NULL,NULL,NULL);
CALL "SUB5" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "INSERT INTO CL_EMPLOYEE
- " VALUES(6000,NULL,'CRETA','JIM',NULL,4,130);"
* EXEC SQL INSERT INTO CL_EMPLOYEE
* VALUES(6000,NULL,'CRETA','JIM',NULL,4,130);
CALL "SUB6" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "INSERT INTO CL_EMPLOYEE
- " VALUES(7000,'P2',NULL,NULL,NULL,NULL,150);"
* EXEC SQL INSERT INTO CL_EMPLOYEE
* VALUES(7000,'P2',NULL,NULL,NULL,NULL,150);
CALL "SUB7" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "INSERT INTO CL_EMPLOYEE"
DISPLAY " VALUES(8000,'P2','HALKIDA',NULL,30000,6,NULL);"
* EXEC SQL INSERT INTO CL_EMPLOYEE
* VALUES(8000,'P2','HALKIDA',NULL,30000,6,NULL);
CALL "SUB8" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "INSERT INTO CL_EMPLOYEE"
DISPLAY "
- " VALUES(9000,'P1','SANTORINH','ANDREWS',15000,5,125);"
* EXEC SQL INSERT INTO CL_EMPLOYEE
* VALUES(9000,'P1','SANTORINH','ANDREWS',15000,5,125)
* ;
CALL "SUB9" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "DECLARE a CURSOR FOR SELECT EMPNUM,"
DISPLAY "COALESCE(SALARY,GRADE,HOURS),"
DISPLAY "COALESCE(EMPNAME,LOC,DEPTNO) FROM
- " CTS1.CL_EMPLOYEE"
DISPLAY "ORDER BY EMPNUM;"
* EXEC SQL DECLARE a CURSOR FOR SELECT EMPNUM,
* COALESCE(SALARY,GRADE,HOURS),
* COALESCE(EMPNAME,LOC,DEPTNO)
* FROM CTS1.CL_EMPLOYEE
* ORDER BY EMPNUM END-EXEC
DISPLAY "OPEN a;"
* EXEC SQL OPEN a;
CALL "SUB10" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*initialise host variables
MOVE 0 TO hmpnum
MOVE 0 TO numhst
MOVE "xxxxxxxxxxxxxxxxxxxx" TO strhst
MOVE 99 TO indic1
MOVE 99 TO indic2
*start fetching rows from the table five in total
DISPLAY "FETCH a INTO :hmpnum, :numhst:indic2
- " ,:strhst:indic1;"
* EXEC SQL FETCH a INTO :hmpnum, :numhst:indic2
* ,:strhst:indic1;
CALL "SUB11" USING SQLCODE SQLSTATE hmpnum numhst indic2
strhst indic1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "HMPNUM should be 5000; its value is ", hmpnum, "
- " "
DISPLAY "indic1 should be -1; its value is ", indic1
DISPLAY "indic2 should be -1; its value is ", indic2
if ( hmpnum NOT = 5000 OR indic2 NOT = -1 OR
indic1 NOT = -1 ) then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE 0 TO hmpnum
MOVE 0 TO numhst
MOVE "xxxxxxxxxxxxxxxxxxxx" TO strhst
MOVE 99 TO indic1
MOVE 99 TO indic2
*fetch the second row of the table
DISPLAY "FETCH a INTO :hmpnum, :numhst ,:strhst;"
* EXEC SQL FETCH a INTO :hmpnum, :numhst ,:strhst;
CALL "SUB12" USING SQLCODE SQLSTATE hmpnum numhst strhst
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "HMPNUM should be 6000; its value is ", hmpnum, "
- " "
DISPLAY "NUMHST should be 4; its value is ", numhst
DISPLAY "STRHST should be JIM; its value is ", strhst
if ( hmpnum NOT = 6000 OR numhst NOT = 4 OR strhst
NOT = "JIM" ) then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE 0 TO hmpnum
MOVE 0 TO numhst
MOVE "xxxxxxxxxxxxxxxxxxxx" TO strhst
MOVE 99 TO indic1
MOVE 99 TO indic2
*fetch the third row of the table
DISPLAY "FETCH a INTO :hmpnum, :numhst ,:strhst;"
* EXEC SQL FETCH a INTO :hmpnum, :numhst ,:strhst;
CALL "SUB13" USING SQLCODE SQLSTATE hmpnum numhst strhst
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "HMPNUM should be 7000; its value is ", hmpnum, "
- " "
DISPLAY "NUMHST should be 150; its value is ", numhst
DISPLAY "STRHST should be P2; its value is ", strhst
if ( hmpnum NOT = 7000 OR numhst NOT = 150 OR strhst
NOT = "P2" ) then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE 0 TO hmpnum
MOVE 0 TO numhst
MOVE "xxxxxxxxxxxxxxxxxxxx" TO strhst
MOVE 99 TO indic1
MOVE 99 TO indic2
*fetch the fourth row of the table
DISPLAY "FETCH a INTO :hmpnum, :numhst ,:strhst;"
* EXEC SQL FETCH a INTO :hmpnum, :numhst ,:strhst;
CALL "SUB14" USING SQLCODE SQLSTATE hmpnum numhst strhst
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "HMPNUM should be 8000; its value is ", hmpnum,
" "
DISPLAY "NUMHST should be 30000; its value is ", numhst
DISPLAY "STRHST should be HALKIDA; its value is ", strhst
if (hmpnum NOT = 8000 OR numhst NOT = 30000 OR
strhst NOT = "HALKIDA") then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE 0 TO hmpnum
MOVE 0 TO numhst
MOVE "xxxxxxxxxxxxxxxxxxxx" TO strhst
MOVE 99 TO indic1
MOVE 99 TO indic2
*fetch the last row of the table
DISPLAY "FETCH a INTO :hmpnum, :numhst ,:strhst;"
* EXEC SQL FETCH a INTO :hmpnum, :numhst ,:strhst;
CALL "SUB15" USING SQLCODE SQLSTATE hmpnum numhst strhst
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "HMPNUM should be 9000; its value is ", hmpnum,
" "
DISPLAY "NUMHST should be 15000; its value is ", numhst
DISPLAY "STRHST should be ANDREWS; its value is ", strhst
if (hmpnum NOT = 9000 OR numhst NOT = 15000 OR
strhst NOT = "ANDREWS") then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE 0 TO hmpnum
MOVE 50000 TO numhst
MOVE "ATHENS " TO strhst
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hv1
MOVE 0 TO hv2
DISPLAY "SELECT EMPNUM, COALESCE(DEPTNO,LOC, :strhst), "
DISPLAY "COALESCE(SALARY, :numhst, GRADE) "
DISPLAY "INTO :hmpnum, :hv1, :hv2 "
DISPLAY "FROM CL_EMPLOYEE "
DISPLAY "WHERE EMPNUM = 5000;"
* EXEC SQL SELECT EMPNUM, COALESCE(DEPTNO,LOC,:strhst),
* COALESCE(SALARY,:numhst,GRADE) INTO :hmpnum, :hv1, :hv2
* FROM CL_EMPLOYEE
* WHERE EMPNUM = 5000;
CALL "SUB16" USING SQLCODE SQLSTATE strhst numhst hmpnum
hv1 hv2
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "HMPNUM should be 5000; its value is ", hmpnum, "
- " "
DISPLAY "hv1 should be ATHENS; its value is ", hv1
DISPLAY "hv2 should be 50000; its value is ", hv2
if (hmpnum NOT = 5000 OR hv1 NOT = "ATHENS" OR
hv2 NOT = 50000 ) then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE 0 TO hmpnum
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hv1
MOVE 0 TO hv2
********** 2nd select statement: single row *************
DISPLAY "SELECT EMPNUM, COALESCE('NICKOS',DEPTNO,LOC), "
DISPLAY "COALESCE(SALARY, GRADE,47000) "
DISPLAY "INTO :hmpnum, :hv1, :hv2 "
DISPLAY "FROM CL_EMPLOYEE "
DISPLAY "WHERE EMPNUM = 7000;"
* EXEC SQL SELECT EMPNUM, COALESCE('NICKOS',DEPTNO,LOC),
* COALESCE(SALARY,GRADE,47000) INTO :hmpnum, :hv1, :hv2
* FROM CL_EMPLOYEE
* WHERE EMPNUM = 7000;
CALL "SUB17" USING SQLCODE SQLSTATE hmpnum hv1 hv2
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "HMPNUM should be 7000; its value is ", hmpnum, "
- " "
DISPLAY "hv1 should be NICKOS; its value is ", hv1
DISPLAY "hv2 should be 47000; its value is ", hv2
if (hmpnum NOT = 7000 OR hv1 NOT = "NICKOS" OR
hv2 NOT = 47000 ) then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE 0 TO hmpnum
MOVE 12000 TO numhst
MOVE "PAGRATI " TO strhst
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hv1
MOVE 0 TO hv2
DISPLAY "SELECT EMPNUM, COALESCE(EMPNAME,:strhst,LOC), "
DISPLAY "COALESCE(:numhst, SALARY,GRADE) "
DISPLAY "INTO :hmpnum, :hv1, :hv2 "
DISPLAY "FROM CL_EMPLOYEE "
DISPLAY "WHERE EMPNUM = 8000;"
* EXEC SQL SELECT EMPNUM, COALESCE(EMPNAME,:strhst,LOC),
* COALESCE(:numhst,SALARY,GRADE) INTO :hmpnum, :hv1, :hv2
* FROM CL_EMPLOYEE
* WHERE EMPNUM = 8000;
CALL "SUB18" USING SQLCODE SQLSTATE strhst numhst hmpnum
hv1 hv2
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "HMPNUM should be 8000; its value is ", hmpnum,
" "
DISPLAY "hv1 should be PAGRATI; its value is ", hv1
DISPLAY "hv2 should be 12000; its value is ", hv2
if (hmpnum NOT = 8000 OR hv1 NOT = "PAGRATI" OR
hv2 NOT = 12000 ) then
MOVE 0 TO flag
END-IF
DISPLAY " "
DISPLAY "ROLLBACK WORK;"
* EXEC SQL ROLLBACK WORK;
CALL "SUB19" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if ( flag = 1 ) then
DISPLAY " xts799.mco *** pass *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7003','pass','MCO');
CALL "SUB20" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
else
DISPLAY " xts799.mco *** fail *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7003','fail','MCO');
CALL "SUB21" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
COMPUTE errcnt = errcnt + 1
END-IF
DISPLAY "========================================"
* EXEC SQL COMMIT WORK;
CALL "SUB22" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
******************** END TEST7003 ********************
**** 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.29 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.
|