IDENTIFICATION DIVISION.
PROGRAM-ID. XTS737.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. xyz.
OBJECT-COMPUTER. xyz.
DATA DIVISION.
WORKING-STORAGE SECTION.
* EMBEDDED COBOL (file "XTS737.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
*
* XTS737.PCO TEST7037
* WRITTEN BY: Nickos Backalidis
* TRANSLATED AUTOMATICALLY FROM EMBEDDED C BY CHRIS SCHANZLE
*
* Scrolled cursor with ORDER BY DESC, FETCH NEXT
*
* REFERENCES
* 13.1 -- <Declare cursor>
* 13.1 GR.3
* 13.3 -- <fetch statement>
* 13.3 GR.3
* F#43 -- Scrolled cursors
* F#24 -- Keyword relaxations
*
* DATE LAST ALTERED 18/12/95 CTS5 Hand-over Test
*
* Cleanups and fixes by V. Kogakis 07/12/95
* Include Files
* Define NOSUBCLASS/CHCKOK at test beginning
* print timestamp
*
* QA STATUS : FC
*
* Revised by DWF 1996-02-08
* Removed status checks after cursor declarations
* Fixed checks for wrong SQLCODE
* Removed field widths in printfs
* Fixed char 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 henum PIC X(3).
01 hename PIC X(20).
01 hgrade PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
01 hcity PIC X(15).
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, xts737.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 TEST7037 *******************
MOVE 1 TO flag
DISPLAY " TEST7037"
DISPLAY " Scrolled cursor with ORDER BY DESC, FETCH NEXT
- " "
DISPLAY "References "
DISPLAY " 13.1 -- "
DISPLAY " 13.1 GR.3 "
DISPLAY " 13.3 -- "
DISPLAY " 13.3 GR.3 "
DISPLAY " F#43 -- Scrolled cursors"
DISPLAY " F#24 -- Keyword relaxations "
DISPLAY " - - - - - - - - - - - - - - - - - - -"
*Initialise error reporting variables
COMPUTE SQLCODE = -1
MOVE "xxxxx" TO SQLSTATE
*USE table CTS1.STAFF from the standrard schema
*declare a scrolled cursor with ORDER BY DESC
*with a numeric data type as sort key
DISPLAY "DECLARE b SCROLL CURSOR "
DISPLAY "FOR SELECT EMPNUM, EMPNAME, GRADE, CITY"
DISPLAY "FROM STAFF"
DISPLAY "ORDER BY GRADE DESC, EMPNAME;"
EXEC SQL DECLARE b SCROLL CURSOR
FOR SELECT EMPNUM,EMPNAME,GRADE,CITY
FROM STAFF
ORDER BY GRADE DESC, EMPNAME END-EXEC
DISPLAY "OPEN b;"
EXEC SQL OPEN b END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*initialise host variables
MOVE "xxx" TO henum
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hename
MOVE 0 TO hgrade
MOVE "xxxxxxxxxxxxxxx" TO hcity
*start fetching rows in the cursor 5 in total
*fetch first row from STAFF
DISPLAY "FETCH FROM b INTO :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH FROM b INTO :henum,:hename,:hgrade,:hcity
END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "hemum should be E3; its value is ", henum
DISPLAY "hename should be Carmen; its value is ", hename
DISPLAY "hgrade should be 13; its value is ", hgrade
DISPLAY "hcity should be Vienna; its value is ", hcity
if (henum NOT = "E3" OR hgrade NOT = 13) then
MOVE 0 TO flag
END-IF
if (hcity NOT = "Vienna" OR hename NOT =
"Carmen") then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE "xxx" TO henum
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hename
MOVE 0 TO hgrade
MOVE "xxxxxxxxxxxxxxx" TO hcity
*fetch second row
DISPLAY "FETCH NEXT FROM b INTO
- " :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH NEXT FROM b INTO
:henum,:hename,:hgrade,:hcity END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "hemum should be E5; its value is ", henum
DISPLAY "hename should be Ed; its value is ", hename
DISPLAY "hgrade should be 13; its value is ", hgrade
DISPLAY "hcity should be Akron; its value is ", hcity
if (henum NOT = "E5" OR hgrade NOT = 13) then
MOVE 0 TO flag
END-IF
if (hcity NOT = "Akron" OR hename NOT = "Ed")
then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE "xxx" TO henum
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hename
MOVE 0 TO hgrade
MOVE "xxxxxxxxxxxxxxx" TO hcity
*fetch third row
DISPLAY "FETCH NEXT FROM b INTO
- " :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH NEXT FROM b INTO
:henum,:hename,:hgrade,:hcity END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "hemum should be E1; its value is ", henum
DISPLAY "hename should be Alice; its value is ", hename
DISPLAY "hgrade should be 12; its value is ", hgrade
DISPLAY "hcity should be Deale; its value is ", hcity
if (henum NOT = "E1" OR hgrade NOT = 12) then
MOVE 0 TO flag
END-IF
if (hcity NOT = "Deale" OR hename NOT = "Alice")
then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE "xxx" TO henum
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hename
MOVE 0 TO hgrade
MOVE "xxxxxxxxxxxxxxx" TO hcity
*fetch fourth row
DISPLAY "FETCH NEXT FROM b INTO
- " :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH NEXT FROM b INTO
:henum,:hename,:hgrade,:hcity END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "hemum should be E4; its value is ", henum
DISPLAY "hename should be Don; its value is ", hename
DISPLAY "hgrade should be 12; its value is ", hgrade
DISPLAY "hcity should be Deale; its value is ", hcity
if (henum NOT = "E4" OR hgrade NOT = 12) then
MOVE 0 TO flag
END-IF
if (hcity NOT = "Deale" OR hename NOT = "Don")
then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE "xxx" TO henum
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hename
MOVE 0 TO hgrade
MOVE "xxxxxxxxxxxxxxx" TO hcity
*fetch fifth row
DISPLAY "FETCH NEXT FROM b INTO
- " :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH NEXT FROM b INTO
:henum,:hename,:hgrade,:hcity END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "hemum should be E2; its value is ", henum
DISPLAY "hename should be Betty; its value is ", hename
DISPLAY "hgrade should be 10; its value is ", hgrade
DISPLAY "hcity should be Vienna; its value is ", hcity
if (henum NOT = "E2" OR hgrade NOT = 10) then
MOVE 0 TO flag
END-IF
if (hcity NOT = "Vienna" OR hename NOT = "Betty")
then
MOVE 0 TO flag
END-IF
DISPLAY " "
*Attemp to retrieve the row after the last row.
MOVE 10000 TO SQLCODE
MOVE "xxxxx" TO SQLSTATE
DISPLAY "FETCH NEXT FROM b INTO
- " :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH NEXT FROM b INTO
:henum,:hename,:hgrade,:hcity END-EXEC
MOVE SQLCODE TO SQL-COD
*Check that an exception condition no data is raised
*indicated in the value of SQLSTATE which should be 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 " "
DISPLAY "CLOSE b;"
EXEC SQL CLOSE b END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*USE table CTS1.STAFF from the standrard schema
*declare a scrolled cursor with ORDER BY DESC
*with a character data type as sort key
DISPLAY "DECLARE a SCROLL CURSOR "
DISPLAY "FOR SELECT EMPNUM, EMPNAME, GRADE, CITY"
DISPLAY "FROM STAFF ORDER BY EMPNAME DESC;"
EXEC SQL DECLARE a SCROLL CURSOR
FOR SELECT EMPNUM,EMPNAME,GRADE,CITY
FROM STAFF ORDER BY EMPNAME DESC END-EXEC
DISPLAY "OPEN a;"
EXEC SQL OPEN a END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*initialise host variables
MOVE "xxx" TO henum
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hename
MOVE 0 TO hgrade
MOVE "xxxxxxxxxxxxxxx" TO hcity
*start fetching rows in the cursor - 5 in total
*fetch first row from STAFF
DISPLAY "FETCH FROM a INTO :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH FROM a INTO :henum,:hename,:hgrade,:hcity
END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "hemum should be E5; its value is ", henum
DISPLAY "hename should be Ed; its value is ", hename
DISPLAY "hgrade should be 13; its value is ", hgrade
DISPLAY "hcity should be Akron; its value is ", hcity
if (henum NOT = "E5" OR hgrade NOT = 13) then
MOVE 0 TO flag
END-IF
if (hcity NOT = "Akron" OR hename NOT = "Ed")
then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE "xxx" TO henum
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hename
MOVE 0 TO hgrade
MOVE "xxxxxxxxxxxxxxx" TO hcity
*fetch second row
DISPLAY "FETCH NEXT FROM a INTO
- " :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH NEXT FROM a INTO
:henum,:hename,:hgrade,:hcity END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "hemum should be E4; its value is ", henum
DISPLAY "hename should be Don; its value is ", hename
DISPLAY "hgrade should be 12; its value is ", hgrade
DISPLAY "hcity should be Deale; its value is ", hcity
if (henum NOT = "E4" OR hgrade NOT = 12) then
MOVE 0 TO flag
END-IF
if (hcity NOT = "Deale" OR hename NOT = "Don")
then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE "xxx" TO henum
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hename
MOVE 0 TO hgrade
MOVE "xxxxxxxxxxxxxxx" TO hcity
*fetch third row
DISPLAY "FETCH NEXT FROM a INTO
- " :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH NEXT FROM a INTO
:henum,:hename,:hgrade,:hcity END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "hemum should be E3; its value is ", henum
DISPLAY "hename should be Carmen; its value is ", hename
DISPLAY "hgrade should be 13; its value is ", hgrade
DISPLAY "hcity should be Vienna; its value is ", hcity
if (henum NOT = "E3" OR hgrade NOT = 13) then
MOVE 0 TO flag
END-IF
if (hcity NOT = "Vienna" OR hename NOT =
"Carmen") then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE "xxx" TO henum
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hename
MOVE 0 TO hgrade
MOVE "xxxxxxxxxxxxxxx" TO hcity
*fetch fourth row
DISPLAY "FETCH NEXT FROM a INTO
- " :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH NEXT FROM a INTO
:henum,:hename,:hgrade,:hcity END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "hemum should be E2; its value is ", henum
DISPLAY "hename should be Betty; its value is ", hename
DISPLAY "hgrade should be 10; its value is ", hgrade
DISPLAY "hcity should be Vienna; its value is ", hcity
if (henum NOT = "E2" OR hgrade NOT = 10) then
MOVE 0 TO flag
END-IF
if (hcity NOT = "Vienna" OR hename NOT = "Betty")
then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE "xxx" TO henum
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hename
MOVE 0 TO hgrade
MOVE "xxxxxxxxxxxxxxx" TO hcity
*fetch fifth row
DISPLAY "FETCH NEXT FROM a INTO
- " :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH NEXT FROM a INTO
:henum,:hename,:hgrade,:hcity END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "hemum should be E1; its value is ", henum
DISPLAY "hename should be Alice; its value is ", hename
DISPLAY "hgrade should be 12; its value is ", hgrade
DISPLAY "hcity should be Deale; its value is ", hcity
if (henum NOT = "E1" OR hgrade NOT = 12) then
MOVE 0 TO flag
END-IF
if (hcity NOT = "Deale" OR hename NOT = "Alice")
then
MOVE 0 TO flag
END-IF
DISPLAY " "
*Attemp to retrieve the row after the last row.
MOVE 10000 TO SQLCODE
MOVE "xxxxx" TO SQLSTATE
DISPLAY "FETCH NEXT FROM a INTO
- " :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH NEXT FROM a INTO
:henum,:hename,:hgrade,:hcity END-EXEC
MOVE SQLCODE TO SQL-COD
*Check that an exception condition no data is raised
*indicated in the value of SQLSTATE which should be 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 " "
DISPLAY "CLOSE a;"
EXEC SQL CLOSE a END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*** declare a third cursor and check that all the rows
*** of table CTS1.STAFF have remained unaffected **
DISPLAY "DECLARE Z CURSOR FOR SELECT
- " EMPNUM,EMPNAME,GRADE,CITY "
DISPLAY "FROM STAFF ORDER BY EMPNUM;"
EXEC SQL DECLARE Z CURSOR FOR SELECT
EMPNUM,EMPNAME,GRADE,CITY
FROM STAFF ORDER BY EMPNUM END-EXEC
DISPLAY "OPEN Z;"
EXEC SQL OPEN Z END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*initialise host variables
MOVE "xxx" TO henum
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hename
MOVE 0 TO hgrade
MOVE "xxxxxxxxxxxxxxx" TO hcity
*start fetching rows in the cursor 5 in total
*fetch first row from STAFF
DISPLAY "FETCH Z INTO :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH Z INTO :henum,:hename,:hgrade,:hcity
END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "hemum should be E1; its value is ", henum
DISPLAY "hename should be Alice; its value is ", hename
DISPLAY "hgrade should be 12; its value is ", hgrade
DISPLAY "hcity should be Deale; its value is ", hcity
if (henum NOT = "E1" OR hgrade NOT = 12) then
MOVE 0 TO flag
END-IF
if (hcity NOT = "Deale" OR hename NOT = "Alice")
then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE "xxx" TO henum
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hename
MOVE 0 TO hgrade
MOVE "xxxxxxxxxxxxxxx" TO hcity
*fetch second row
DISPLAY "FETCH Z INTO :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH Z INTO :henum,:hename,:hgrade,:hcity
END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "hemum should be E2; its value is ", henum
DISPLAY "hename should be Betty; its value is ", hename
DISPLAY "hgrade should be 10; its value is ", hgrade
DISPLAY "hcity should be Vienna; its value is ", hcity
if (henum NOT = "E2" OR hgrade NOT = 10) then
MOVE 0 TO flag
END-IF
if (hcity NOT = "Vienna" OR hename NOT = "Betty")
then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE "xxx" TO henum
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hename
MOVE 0 TO hgrade
MOVE "xxxxxxxxxxxxxxx" TO hcity
*fetch third row
DISPLAY "FETCH Z INTO :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH Z INTO :henum,:hename,:hgrade,:hcity
END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "hemum should be E3; its value is ", henum
DISPLAY "hename should be Carmen; its value is ", hename
DISPLAY "hgrade should be 13; its value is ", hgrade
DISPLAY "hcity should be Vienna; its value is ", hcity
if (henum NOT = "E3" OR hgrade NOT = 13) then
MOVE 0 TO flag
END-IF
if (hcity NOT = "Vienna" OR hename NOT =
"Carmen") then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE "xxx" TO henum
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hename
MOVE 0 TO hgrade
MOVE "xxxxxxxxxxxxxxx" TO hcity
*fetch fourth row
DISPLAY "FETCH Z INTO :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH Z INTO :henum,:hename,:hgrade,:hcity
END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "hemum should be E4; its value is ", henum
DISPLAY "hename should be Don; its value is ", hename
DISPLAY "hgrade should be 12; its value is ", hgrade
DISPLAY "hcity should be Deale; its value is ", hcity
if (henum NOT = "E4" OR hgrade NOT = 12) then
MOVE 0 TO flag
END-IF
if (hcity NOT = "Deale" OR hename NOT = "Don")
then
MOVE 0 TO flag
END-IF
DISPLAY " "
*initialise host variables
MOVE "xxx" TO henum
MOVE "xxxxxxxxxxxxxxxxxxxx" TO hename
MOVE 0 TO hgrade
MOVE "xxxxxxxxxxxxxxx" TO hcity
*fetch fifth row
DISPLAY "FETCH Z INTO :henum,:hename,:hgrade,:hcity;"
EXEC SQL FETCH Z INTO :henum,:hename,:hgrade,:hcity
END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "hemum should be E5; its value is ", henum
DISPLAY "hename should be Ed; its value is ", hename
DISPLAY "hgrade should be 13; its value is ", hgrade
DISPLAY "hcity should be Akron; its value is ", hcity
if (henum NOT = "E5" OR hgrade NOT = 13) then
MOVE 0 TO flag
END-IF
if (hcity NOT = "Akron" OR hename NOT = "Ed")
then
MOVE 0 TO flag
END-IF
DISPLAY " "
DISPLAY "CLOSE Z;"
EXEC SQL CLOSE Z END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "ROLLBACK WORK;"
EXEC SQL ROLLBACK WORK END-EXEC
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*Now record results of the tests
if ( flag = 1 ) then
DISPLAY " xts737.pco *** pass *** "
EXEC SQL INSERT INTO CTS1.TESTREPORT
VALUES('7037','pass','PCO') END-EXEC
MOVE SQLCODE TO SQL-COD
else
DISPLAY " xts737.pco *** fail *** "
EXEC SQL INSERT INTO CTS1.TESTREPORT
VALUES('7037','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 TEST7037 ********************
**** 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.15 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.
|