IDENTIFICATION DIVISION.
PROGRAM-ID. YTS803.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. xyz.
OBJECT-COMPUTER. xyz.
DATA DIVISION.
WORKING-STORAGE SECTION.
* Standard COBOL (file "YTS803.SCO") calling SQL
* procedures in file "YTS803.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
*
* YTS803.SCO
* WRITTEN BY: Susan Watters
* TRANSLATED AUTOMATICALLY FROM EMBEDDED COBOL BY CHRIS SCHANZLE
*
* Support of SQL_SIZING table in documentation schema
*
*
* REFERENCES
* FIPS15.2 SQL_Sizing table
* F# 50 Documentation schema
*
* DATE LAST ALTERED 02.01.96 CTS5 Hand-over Test
*
* QA Status: Full FC
*
* Revised by DWF 1996-03-27
* Added rollback after authid
* Removed EXEC SQL from printf
* Added FIPS printout
* Reduced severity of coding rule violations
* Fixed logic errors
* Added check for existence of all columns
* Fixed typos in feature names
* Removed extraneous code
* Fixed syntax errors (C language)
* Fixed pass criteria
****************************************************************
* EXEC SQL BEGIN DECLARE SECTION END-EXEC
01 SQLCODE PIC S9(9) COMP.
01 SQLSTATE PIC X(5).
01 co1 PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
01 sid PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
01 desc PIC X(50).
01 entv PIC S9(5) DISPLAY SIGN LEADING SEPARATE.
01 intv PIC S9(5) DISPLAY SIGN LEADING SEPARATE.
01 indic1 PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
01 indic2 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 i PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
01 S1 PIC X(50).
01 S2 PIC X(50).
01 S3 PIC X(50).
01 S4 PIC X(50).
01 S5 PIC X(50).
01 S6 PIC X(50).
01 S7 PIC X(50).
01 S8 PIC X(50).
01 S9 PIC X(50).
01 S10 PIC X(50).
01 S11 PIC X(50).
01 S12 PIC X(50).
01 S13 PIC X(50).
01 S14 PIC X(50).
01 S15 PIC X(50).
01 S16 PIC X(50).
01 S17 PIC X(50).
01 S18 PIC X(50).
01 S19 PIC X(50).
01 S20 PIC X(50).
01 S21 PIC X(50).
01 S22 PIC X(50).
01 S23 PIC X(50).
01 S24 PIC X(50).
01 S25 PIC X(50).
01 S26 PIC X(50).
01 S27 PIC X(50).
01 S28 PIC X(50).
01 S29 PIC X(50).
01 S30 PIC X(50).
01 S31 PIC X(50).
01 S32 PIC X(50).
01 S33 PIC X(50).
01 S34 PIC X(50).
01 S35 PIC X(50).
01 S36 PIC X(50).
01 S37 PIC X(50).
01 S38 PIC X(50).
01 S39 PIC X(50).
01 S40 PIC X(50).
01 S41 PIC X(50).
01 S42 PIC X(50).
01 S43 PIC X(50).
01 S44 PIC X(50).
01 S45 PIC X(50).
01 S46 PIC X(50).
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, yts803.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 TEST7549 *******************
MOVE 1 TO flag
DISPLAY " FIPS TEST7549"
DISPLAY " Support SQL_SIZING table in documentation
- " schema"
DISPLAY "References:"
DISPLAY " FIPS15.2 SQL_Sizing table"
DISPLAY " F# 50 Documentation schema"
DISPLAY " - - - - - - - - - - - - - - - - - - -"
COMPUTE SQLCODE = -1
MOVE "xxxxx" TO SQLSTATE
*initialise variables
MOVE 1 TO i
*set up the comparison arrays for SQL_SIZING.Description
MOVE "Length of an identifier "
TO S1
MOVE "CHARACTER max length "
TO S2
MOVE "CHARACTER VARYING max length "
TO S3
MOVE "BIT max length in bits "
TO S4
MOVE "BIT VARYING max length in bits "
TO S5
MOVE "NATIONAL CHARACTER max length "
TO S6
MOVE "NATIONAL CHAR VARYING max length "
TO S7
MOVE "NUMERIC decimal precision "
TO S8
MOVE "DECIMAL decimal precision "
TO S9
MOVE "INTEGER decimal precision "
TO S10
MOVE "INTEGER binary precision "
TO S11
MOVE "SMALLINT decimal precision "
TO S12
MOVE "SMALLINT binary precision "
TO S13
MOVE "FLOAT binary mantissa precision "
TO S14
MOVE "FLOAT binary exponent precision "
TO S15
MOVE "REAL binary mantissa precision "
TO S16
MOVE "REAL binary exponent precision "
TO S17
MOVE "DOUBLE PRECISION binary mantissa precision "
TO S18
MOVE "DOUBLE PRECISION binary exponent precision "
TO S19
MOVE "TIME decimal fractional second precision "
TO S20
MOVE "TIMESTAMP decimal fractional second precision "
TO S21
MOVE "INTERVAL decimal fractional second precision "
TO S22
MOVE "INTERVAL decimal leading field precision "
TO S23
MOVE "Columns in a table "
TO S24
MOVE "Values in an INSERT statement "
TO S25
MOVE "Set clauses in UPDATE statement "
TO S26
MOVE "Length of a row "
TO S27
MOVE "Columns in UNIQUE constraint "
TO S28
MOVE "Length of UNIQUE columns "
TO S29
MOVE "Columns in GROUP BY column list "
TO S30
MOVE "Length of GROUP BY column list "
TO S31
MOVE "Sort items in ORDER BY clause "
TO S32
MOVE "Length of ORDER BY column list "
TO S33
MOVE "Referencing columns in FOREIGN KEY "
TO S34
MOVE "Length of FOREIGN KEY column list "
TO S35
MOVE "Table references in an SQL statement "
TO S36
MOVE "Cursors simultaneously open "
TO S37
MOVE "WHEN clauses in a CASE expression "
TO S38
MOVE "Columns in a named columns JOIN "
TO S39
MOVE "Length of JOIN column list "
TO S40
MOVE "Items in a SELECT list "
TO S41
MOVE "Length of SQL "
TO S42
MOVE "Length of "
TO S43
MOVE "Length of "
TO S44
MOVE "Occurrences in an ALLOCATE DESCRIPTOR "
TO S45
MOVE "Default occurrences in ALLOCATE DESCRIPTOR "
TO S46
*declare cursor to return SIZING_FEATURES
DISPLAY "DECLARE data803 CURSOR FOR;"
DISPLAY "SELECT SIZING_ID, DESCRIPTION, ENTRY_VALUE,"
DISPLAY "INTERMEDIATE_VALUE"
DISPLAY "FROM FIPS_DOCUMENTATION.SQL_SIZING"
DISPLAY "ORDER BY SIZING_ID;"
* EXEC SQL DECLARE data803 CURSOR FOR
* SELECT SIZING_ID, DESCRIPTION, ENTRY_VALUE,
* INTERMEDIATE_VALUE
* FROM FIPS_DOCUMENTATION.SQL_SIZING
* ORDER BY SIZING_ID END-EXEC
DISPLAY "OPEN data803;"
* EXEC SQL OPEN data803;
CALL "SUB3" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*check all 46 items in 16.6 of FIPS 127-2 appear
MOVE 0 TO co1
DISPLAY "SELECT COUNT (*) INTO :co1"
DISPLAY "FROM FIPS_DOCUMENTATION.SQL_SIZING;"
* EXEC SQL SELECT COUNT (*) INTO :co1
* FROM FIPS_DOCUMENTATION.SQL_SIZING;
CALL "SUB4" USING SQLCODE SQLSTATE co1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "co1 should be 46; its value is ", co1
if (co1 NOT = 46) then
MOVE 0 TO flag
END-IF
*Check existence of all columns
MOVE 0 TO co1
DISPLAY "SELECT COUNT (*) INTO :co1"
DISPLAY "FROM FIPS_DOCUMENTATION.SQL_SIZING"
DISPLAY "WHERE VALUE_SUPPORTED IS NOT NULL"
DISPLAY "OR SIZING_COMMENTS IS NOT NULL"
DISPLAY "OR SIZING_ID IS NOT NULL;"
* EXEC SQL SELECT COUNT (*) INTO :co1
* FROM FIPS_DOCUMENTATION.SQL_SIZING
* WHERE VALUE_SUPPORTED IS NOT NULL
* OR SIZING_COMMENTS IS NOT NULL
* OR SIZING_ID IS NOT NULL;
CALL "SUB5" USING SQLCODE SQLSTATE co1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "co1 should be 46; its value is ", co1
if (co1 NOT = 46) then
MOVE 0 TO flag
END-IF
*return and check all values of cursor
.
P100.
*initialise all host variables before FETCH
MOVE 0 TO sid
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx"
TO desc
COMPUTE entv = -10
COMPUTE intv = -10
MOVE 99 TO indic1
MOVE 99 TO indic2
DISPLAY "FETCH data803 "
DISPLAY "INTO :sid,:desc,:entv:indic1,:intv:indic2;"
* EXEC SQL FETCH data803
* INTO :sid,:desc,:entv:indic1,:intv:indic2;
CALL "SUB6" USING SQLCODE SQLSTATE sid desc entv indic1
intv indic2
MOVE SQLCODE TO SQL-COD
if (SQLCODE NOT = 0) then
GO TO P102
END-IF
PERFORM CHCKOK
*check the next sizing identifier returned was the one anticipat
.
P101.
if (sid NOT = i AND i < 47) then
DISPLAY "********** ERROR -- FEATURE NUMBER ", i, " IS
- " MISSING"
COMPUTE i = i + 1
MOVE 0 TO flag
GO TO P101
END-IF
*check correct values are returned for each SIZING constraint
if (sid = 1) then
if (desc NOT = S1 OR entv NOT = 18 OR intv NOT
= 128) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #1 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 2) then
if (desc NOT = S2 OR entv NOT = 240 OR intv
NOT = 1000) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #2 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 3) then
if (desc NOT = S3 OR entv NOT = 254 OR intv
NOT = 1000) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #3 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 4) then
if (desc NOT = S4 OR indic1 NOT = -1 OR intv
NOT = 8000) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #4 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 5) then
if (desc NOT = S5 OR indic1 NOT = -1 OR intv
NOT = 8000) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #5 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 6) then
if (desc NOT = S6 OR indic1 NOT = -1 OR intv
NOT = 500) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #6 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 7) then
if (desc NOT = S7 OR indic1 NOT = -1 OR intv
NOT = 500) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #7 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 8) then
if (desc NOT = S8 OR entv NOT = 15 OR intv NOT
= 15) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #8 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 9) then
if (desc NOT = S9 OR entv NOT = 15 OR intv NOT
= 15) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #9 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 10) then
if (desc NOT = S10 OR entv NOT = 9 OR indic2
NOT = -1) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #10 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 11) then
if (desc NOT = S11 OR indic1 NOT = -1 OR intv
NOT = 31) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #11 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 12) then
if (desc NOT = S12 OR entv NOT = 4 OR indic2
NOT = -1) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #12 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 13) then
if (desc NOT = S13 OR indic1 NOT = -1 OR intv
NOT = 15) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #13 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 14) then
if (desc NOT = S14 OR entv NOT = 20 OR intv
NOT = 47) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #14 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 15) then
if (desc NOT = S15 OR indic1 NOT = -1 OR intv
NOT = 9) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #15 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 16) then
if (desc NOT = S16 OR entv NOT = 20 OR intv
NOT = 23) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #16 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 17) then
if (desc NOT = S17 OR indic1 NOT = -1 OR intv
NOT = 7) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #17 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 18) then
if (desc NOT = S18 OR entv NOT = 30 OR intv
NOT = 47) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #18 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 19) then
if (desc NOT = S19 OR indic1 NOT = -1 OR intv
NOT = 9) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #19 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 20) then
if (desc NOT = S20 OR indic1 NOT = -1 OR intv
NOT = 0) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #20 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 21) then
if (desc NOT = S21 OR indic1 NOT = -1 OR intv
NOT = 6) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #21 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 22) then
if (desc NOT = S22 OR indic1 NOT = -1 OR intv
NOT = 6) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #22 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 23) then
if (desc NOT = S23 OR indic1 NOT = -1 OR intv
NOT = 7) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #23 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 24) then
if (desc NOT = S24 OR entv NOT = 100 OR intv
NOT = 250) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #24 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 25) then
if (desc NOT = S25 OR entv NOT = 100 OR intv
NOT = 250) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #25 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 26) then
if (desc NOT = S26 OR entv NOT = 20 OR intv
NOT = 250) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #26 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 27) then
if (desc NOT = S27 OR entv NOT = 2000 OR intv
NOT = 8000) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #27 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 28) then
if (desc NOT = S28 OR entv NOT = 6 OR intv NOT
= 15) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #28 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 29) then
if (desc NOT = S29 OR entv NOT = 120 OR intv
NOT = 750) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #29 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 30) then
if (desc NOT = S30 OR entv NOT = 6 OR intv NOT
= 15) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #30 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 31) then
if (desc NOT = S31 OR entv NOT = 120 OR intv
NOT = 750) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #31 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 32) then
if (desc NOT = S32 OR entv NOT = 6 OR intv NOT
= 15) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #32 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 33) then
if (desc NOT = S33 OR entv NOT = 120 OR intv
NOT = 750) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #33 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 34) then
if (desc NOT = S34 OR entv NOT = 6 OR intv NOT
= 15) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #34 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 35) then
if (desc NOT = S35 OR entv NOT = 120 OR intv
NOT = 750) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #35 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 36) then
if (desc NOT = S36 OR entv NOT = 15 OR intv
NOT = 50) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #36 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 37) then
if (desc NOT = S37 OR entv NOT = 10 OR intv
NOT = 100) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #37 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 38) then
if (desc NOT = S38 OR indic1 NOT = -1 OR intv
NOT = 50) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #38 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 39) then
if (desc NOT = S39 OR indic1 NOT = -1 OR intv
NOT = 15) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #39 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 40) then
if (desc NOT = S40 OR indic1 NOT = -1 OR intv
NOT = 750) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #40 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 41) then
if (desc NOT = S41 OR entv NOT = 100 OR intv
NOT = 250) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #41 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 42) then
if (desc NOT = S42 OR indic1 NOT = -1 OR intv
NOT = 30000) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #42 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 43) then
if (desc NOT = S43 OR indic1 NOT = -1 OR intv
NOT = 4000) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #43 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 44) then
if (desc NOT = S44 OR indic1 NOT = -1 OR intv
NOT = 4000) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #44 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 45) then
if (desc NOT = S45 OR indic1 NOT = -1 OR intv
NOT = 100) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #45 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid = 46) then
if (desc NOT = S46 OR indic1 NOT = -1 OR intv
NOT = 100) then
DISPLAY "********** ERROR -- Reference to
- " SIZING_FEATURE #46 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (sid < 1 OR sid > 46) then
DISPLAY "Incorrect value for SIZING_ID"
MOVE 0 TO flag
END-IF
COMPUTE i = i + 1
GO TO P100
.
P102.
DISPLAY "SQLCODE should be 100; its value is ", SQL-COD
DISPLAY "SQLSTATE should be 02000; its value is ", SQLSTATE
PERFORM NOSUBCLASS THRU EXIT-NOSUBCLASS
if (SQLCODE NOT = 100 OR 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 " "
if (i NOT = 47) then
DISPLAY "Incorrect number of rows returned!"
MOVE 0 TO flag
END-IF
DISPLAY "CLOSE data803"
* EXEC SQL CLOSE data803;
CALL "SUB7" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "ROLLBACK WORK;"
* EXEC SQL ROLLBACK WORK;
CALL "SUB8" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if ( flag = 1 ) then
DISPLAY " yts803.mco *** pass *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7549','pass','MCO');
CALL "SUB9" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
else
DISPLAY " yts803.mco *** fail *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7549','fail','MCO');
CALL "SUB10" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
COMPUTE errcnt = errcnt + 1
END-IF
DISPLAY "==============================================="
* EXEC SQL COMMIT WORK;
CALL "SUB11" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
******************** END TEST7549 ********************
**** 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.43 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.
|