IDENTIFICATION DIVISION.
PROGRAM-ID. YTS802.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. xyz.
OBJECT-COMPUTER. xyz.
DATA DIVISION.
WORKING-STORAGE SECTION.
* Standard COBOL (file "YTS802.SCO") calling SQL
* procedures in file "YTS802.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
*
* YTS802.SCO
* WRITTEN BY: Susan Watters
* TRANSLATED AUTOMATICALLY FROM EMBEDDED COBOL BY CHRIS SCHANZLE
*
* Support of SQL_FEATURES table in documentation schema
*
*
* REFERENCES
* Support of SQL_FEATURES table in documentation schema
* F# 50 Documentation schema
*
* DATE LAST ALTERED 02.01.96 CTS5 Hand-over Test
*
* QA Status: Full FC
*
* Revised by DWF 1996-03-26
* Added rollback after authid
* Removed EXEC SQL from printf
* Added FIPS printout
* Removed syntax errors (C language and SQL)
* Reduced severity of coding rule violations
* Removed reference to non-existent table
* Fixed logic errors
* Added check for existence of FEATURE_COMMENTS column
* Fixed typos in feature names
****************************************************************
* EXEC SQL BEGIN DECLARE SECTION END-EXEC
01 SQLCODE PIC S9(9) COMP.
01 SQLSTATE PIC X(5).
01 co PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
01 co2 PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
01 fid PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
01 fnam PIC X(50).
01 iss PIC X(3).
01 isv PIC X(3).
01 clas PIC X(12).
01 uid PIC X(18).
01 uidx PIC X(18).
* EXEC SQL END DECLARE SECTION END-EXEC
01 tr PIC X(12).
01 ntrm PIC X(12).
01 rd1 PIC X(3).
01 fl PIC X(4).
*The arrays below are required for storing feature name text
*for comparison with FEATURE_NAME values fetched by cursor data8
01 FIPS1 PIC X(50).
01 FIPS2 PIC X(50).
01 FIPS3 PIC X(50).
01 FIPS4 PIC X(50).
01 FIPS5 PIC X(50).
01 FIPS6 PIC X(50).
01 FIPS7 PIC X(50).
01 FIPS8 PIC X(50).
01 FIPS9 PIC X(50).
01 FIPS10 PIC X(50).
01 FIPS11 PIC X(50).
01 FIPS12 PIC X(50).
01 FIPS13 PIC X(50).
01 FIPS14 PIC X(50).
01 FIPS15 PIC X(50).
01 FIPS16 PIC X(50).
01 FIPS17 PIC X(50).
01 FIPS18 PIC X(50).
01 FIPS19 PIC X(50).
01 FIPS20 PIC X(50).
01 FIPS21 PIC X(50).
01 FIPS22 PIC X(50).
01 FIPS23 PIC X(50).
01 FIPS24 PIC X(50).
01 FIPS25 PIC X(50).
01 FIPS26 PIC X(50).
01 FIPS27 PIC X(50).
01 FIPS28 PIC X(50).
01 FIPS29 PIC X(50).
01 FIPS30 PIC X(50).
01 FIPS31 PIC X(50).
01 FIPS32 PIC X(50).
01 FIPS33 PIC X(50).
01 FIPS34 PIC X(50).
01 FIPS35 PIC X(50).
01 FIPS36 PIC X(50).
01 FIPS37 PIC X(50).
01 FIPS38 PIC X(50).
01 FIPS39 PIC X(50).
01 FIPS40 PIC X(50).
01 FIPS41 PIC X(50).
01 FIPS42 PIC X(50).
01 FIPS43 PIC X(50).
01 FIPS44 PIC X(50).
01 FIPS45 PIC X(50).
01 FIPS46 PIC X(50).
01 FIPS47 PIC X(50).
01 FIPS48 PIC X(50).
01 FIPS49 PIC X(50).
01 FIPS50 PIC X(50).
01 FIPS51 PIC X(50).
01 FIPS52 PIC X(50).
01 FIPS53 PIC X(50).
01 FIPS54 PIC X(50).
01 FIPS55 PIC X(50).
01 FIPS56 PIC X(50).
01 FIPS57 PIC X(50).
01 FIPS58 PIC X(50).
01 FIPS59 PIC X(50).
01 FIPS60 PIC X(50).
01 FIPS61 PIC X(50).
01 FIPS62 PIC X(50).
01 FIPS63 PIC X(50).
01 FIPS64 PIC X(50).
01 FIPS65 PIC X(50).
01 FIPS66 PIC X(50).
01 FIPS67 PIC X(50).
01 FIPS68 PIC X(50).
01 FIPS69 PIC X(50).
01 FIPS70 PIC X(50).
01 FIPS71 PIC X(50).
01 FIPS72 PIC X(50).
01 FIPS73 PIC X(50).
01 FIPS74 PIC X(50).
01 FIPS75 PIC X(50).
01 FIPS76 PIC X(50).
01 FIPS77 PIC X(50).
01 FIPS78 PIC X(50).
01 FIPS79 PIC X(50).
01 FIPS80 PIC X(50).
01 FIPS81 PIC X(50).
01 FIPS82 PIC X(50).
01 FIPS83 PIC X(50).
01 FIPS84 PIC X(50).
01 FIPS85 PIC X(50).
01 FIPS86 PIC X(50).
01 FIPS87 PIC X(50).
01 FIPS88 PIC X(50).
01 FIPS89 PIC X(50).
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 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 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;
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, yts802.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 TEST7548 *******************
MOVE 1 TO flag
MOVE 1 TO flag2
DISPLAY " FIPS TEST7548 "
DISPLAY " Support of SQL_FEATURES tab. in documentatn
- " schema"
DISPLAY "References:"
DISPLAY " FIPS15.1 SQL_FEATURES table"
DISPLAY " F# 50 Documentation schema"
DISPLAY " - - - - - - - - - - - - - - - - - - -"
*This test will need modification if the list of features is eve
*extended for SQL3.
COMPUTE SQLCODE = -1
MOVE "xxxxx" TO SQLSTATE
*initialise variables
MOVE 0 TO co
MOVE 99 TO co2
MOVE 1 TO i
*set up classification types
MOVE "TRANSITIONAL" TO tr
MOVE "INTERMEDIATE" TO ntrm
MOVE "RDA" TO rd1
MOVE "FULL" TO fl
*set up arrays for FIPS Feature Names
MOVE "Dynamic SQL "
TO FIPS1
MOVE "Basic information schema "
TO FIPS2
MOVE "Basic schema manipulation "
TO FIPS3
MOVE "Joined table "
TO FIPS4
MOVE "DATETIME data types "
TO FIPS5
MOVE "VARCHAR data type "
TO FIPS6
MOVE "TRIM function "
TO FIPS7
MOVE "UNION in views "
TO FIPS8
MOVE "Implicit numeric casting "
TO FIPS9
MOVE "Implicit character casting "
TO FIPS10
MOVE "Transaction isolation "
TO FIPS11
MOVE "Get diagnostics "
TO FIPS12
MOVE "Grouped operations "
TO FIPS13
MOVE "Qualified * in select list "
TO FIPS14
MOVE "Lowercase identifiers "
TO FIPS15
MOVE "PRIMARY KEY enhancement "
TO FIPS16
MOVE "Multiple schemas per user "
TO FIPS17
MOVE "Multiple module support "
TO FIPS18
MOVE "Referential delete actions "
TO FIPS19
MOVE "CAST functions "
TO FIPS20
MOVE "INSERT expressions "
TO FIPS21
MOVE "Explicit defaults "
TO FIPS22
MOVE "Privilege tables "
TO FIPS23
MOVE "Keyword relaxations "
TO FIPS24
MOVE "Domain definition "
TO FIPS25
MOVE "CASE expression "
TO FIPS26
MOVE "Compound character literals "
TO FIPS27
MOVE "LIKE enhancements "
TO FIPS28
MOVE "UNIQUE predicate "
TO FIPS29
MOVE "Table operations "
TO FIPS30
MOVE "Schema definition statement "
TO FIPS31
MOVE "User authorization "
TO FIPS32
MOVE "Constraint tables "
TO FIPS33
MOVE "Usage tables "
TO FIPS34
MOVE "Intermediate information schema "
TO FIPS35
MOVE "Subprogram support "
TO FIPS36
MOVE "Intermediate SQL Flagging "
TO FIPS37
MOVE "Schema manipulation "
TO FIPS38
MOVE "Long identifiers "
TO FIPS39
MOVE "Full outer join "
TO FIPS40
MOVE "Time zone specification "
TO FIPS41
MOVE "National character "
TO FIPS42
MOVE "Scrolled cursors "
TO FIPS43
MOVE "Intermediate set function "
TO FIPS44
MOVE "Character set definition "
TO FIPS45
MOVE "Named character sets "
TO FIPS46
MOVE "Scalar subquery values "
TO FIPS47
MOVE "Expanded null predicate "
TO FIPS48
MOVE "Constraint management "
TO FIPS49
MOVE "Documentation schema "
TO FIPS50
MOVE "BIT data type "
TO FIPS51
MOVE "Assertion constraints "
TO FIPS52
MOVE "Temporary tables "
TO FIPS53
MOVE "Full dynamic SQL "
TO FIPS54
MOVE "Full DATETIME "
TO FIPS55
MOVE "Full value expressions "
TO FIPS56
MOVE "Truth value tests "
TO FIPS57
MOVE "Full character functions "
TO FIPS58
MOVE "Derived tables in FROM "
TO FIPS59
MOVE "Trailing underscore "
TO FIPS60
MOVE "Indicator data types "
TO FIPS61
MOVE "Referential name order "
TO FIPS62
MOVE "Full SQL Flagging "
TO FIPS63
MOVE "Row and table constructors "
TO FIPS64
MOVE "Catalog name qualifiers "
TO FIPS65
MOVE "Simple tables "
TO FIPS66
MOVE "Subqueries in CHECK "
TO FIPS67
MOVE "Union and Cross join "
TO FIPS68
MOVE "Collation and translation "
TO FIPS69
MOVE "Referential update actions "
TO FIPS70
MOVE "ALTER domain "
TO FIPS71
MOVE "Deferrable constraints "
TO FIPS72
MOVE "INSERT column privileges "
TO FIPS73
MOVE "Referential MATCH types "
TO FIPS74
MOVE "View CHECK enhancements "
TO FIPS75
MOVE "Session management "
TO FIPS76
MOVE "Connection management "
TO FIPS77
MOVE "Self-referencing operations "
TO FIPS78
MOVE "Insensitive cursors "
TO FIPS79
MOVE "Full set function "
TO FIPS80
MOVE "Catalog flagging "
TO FIPS81
MOVE "Local table references "
TO FIPS82
MOVE "Full cursor update "
TO FIPS83
MOVE "RDA/SQL-Client "
TO FIPS84
MOVE "RDA/SQL-Server "
TO FIPS85
MOVE "RDA Stored Execution "
TO FIPS86
MOVE "RDA Cancel "
TO FIPS87
MOVE "RDA Status "
TO FIPS88
MOVE "RDA TP Application Context "
TO FIPS89
DISPLAY "DECLARE data802 CURSOR FOR"
DISPLAY "SELECT FEATURE_ID, FEATURE_NAME, CLASSIFICATION,"
DISPLAY "IS_SUPPORTED, IS_VERIFIED"
DISPLAY "FROM FIPS_DOCUMENTATION.SQL_FEATURES"
DISPLAY "ORDER BY FEATURE_ID;"
* EXEC SQL DECLARE data802 CURSOR FOR
* SELECT FEATURE_ID, FEATURE_NAME, CLASSIFICATION,
* IS_SUPPORTED, IS_VERIFIED
* FROM FIPS_DOCUMENTATION.SQL_FEATURES
* ORDER BY FEATURE_ID END-EXEC
DISPLAY "OPEN data802;"
* EXEC SQL OPEN data802;
CALL "SUB3" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*ensure there are 89 rows i.e. one for each feature
DISPLAY "SELECT COUNT (*) INTO :co"
DISPLAY "FROM FIPS_DOCUMENTATION.SQL_FEATURES;"
* EXEC SQL SELECT COUNT (*) INTO :co
* FROM FIPS_DOCUMENTATION.SQL_FEATURES;
CALL "SUB4" USING SQLCODE SQLSTATE co
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "co should be 89; its value is ", co
if (co NOT = 89) then
MOVE 0 TO flag
END-IF
*Make sure that FEATURE_COMMENTS exists
MOVE 0 TO co
DISPLAY "SELECT COUNT (*) INTO :co"
DISPLAY "FROM FIPS_DOCUMENTATION.SQL_FEATURES"
DISPLAY "WHERE FEATURE_COMMENTS IS NOT NULL"
DISPLAY "OR FEATURE_ID BETWEEN 1 AND 89;"
* EXEC SQL SELECT COUNT (*) INTO :co
* FROM FIPS_DOCUMENTATION.SQL_FEATURES
* WHERE FEATURE_COMMENTS IS NOT NULL
* OR FEATURE_ID BETWEEN 1 AND 89;
CALL "SUB5" USING SQLCODE SQLSTATE co
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "co should be 89; its value is ", co
if (co NOT = 89) then
MOVE 0 TO flag
END-IF
*return and check all values of the cursor
*The feature id, name and classification are checked
.
P100.
*initialise all host variables before fetch
MOVE 0 TO fid
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx"
TO fnam
MOVE "xxxxxxxxxxxx" TO clas
MOVE "xxx" TO iss
MOVE "xxx" TO isv
DISPLAY "FETCH data802 INTO :fid, :fnam, :clas, :iss,
- " :isv;"
* EXEC SQL FETCH data802
* INTO :fid, :fnam, :clas, :iss, :isv;
CALL "SUB6" USING SQLCODE SQLSTATE fid fnam clas iss isv
MOVE SQLCODE TO SQL-COD
if (SQLCODE NOT = 0) then
GO TO P102
END-IF
PERFORM CHCKOK
*check the Feature referenced was the one expected
.
P101.
if (fid NOT = i AND i < 90) 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 FIPS feature
if (fid = 1) then
if (fnam NOT = FIPS1 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #1 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 2) then
if (fnam NOT = FIPS2 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #2 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 3) then
if (fnam NOT = FIPS3 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #3 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 4) then
if (fnam NOT = FIPS4 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #4 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 5) then
if (fnam NOT = FIPS5 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #5 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 6) then
if (fnam NOT = FIPS6 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #6 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 7) then
if (fnam NOT = FIPS7 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #7 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 8) then
if (fnam NOT = FIPS8 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #8 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 9) then
if (fnam NOT = FIPS9 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #9 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 10) then
if (fnam NOT = FIPS10 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #10 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 11) then
if (fnam NOT = FIPS11 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #11 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 12) then
if (fnam NOT = FIPS12 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #12 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 13) then
if (fnam NOT = FIPS13 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #13 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 14) then
if (fnam NOT = FIPS14 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #14 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 15) then
if (fnam NOT = FIPS15 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #15 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 16) then
if (fnam NOT = FIPS16 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #16 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 17) then
if (fnam NOT = FIPS17 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #17 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 18) then
if (fnam NOT = FIPS18 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #18 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 19) then
if (fnam NOT = FIPS19 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #19 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 20) then
if (fnam NOT = FIPS20 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #20 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 21) then
if (fnam NOT = FIPS21 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #21 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 22) then
if (fnam NOT = FIPS22 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #22 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 23) then
if (fnam NOT = FIPS23 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #23 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 24) then
if (fnam NOT = FIPS24 OR clas NOT = tr) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #24 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 25) then
if (fnam NOT = FIPS25 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #25 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 26) then
if (fnam NOT = FIPS26 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #26 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 27) then
if (fnam NOT = FIPS27 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #27 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 28) then
if (fnam NOT = FIPS28 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #28 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 29) then
if (fnam NOT = FIPS29 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #29 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 30) then
if (fnam NOT = FIPS30 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #30 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 31) then
if (fnam NOT = FIPS31 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #31 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 32) then
if (fnam NOT = FIPS32 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #32 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 33) then
if (fnam NOT = FIPS33 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #33 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 34) then
if (fnam NOT = FIPS34 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #34 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 35) then
if (fnam NOT = FIPS35 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #35 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 36) then
if (fnam NOT = FIPS36 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #36 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 37) then
if (fnam NOT = FIPS37 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #37 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 38) then
if (fnam NOT = FIPS38 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #38 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 39) then
if (fnam NOT = FIPS39 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #39 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 40) then
if (fnam NOT = FIPS40 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #40 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 41) then
if (fnam NOT = FIPS41 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #41 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 42) then
if (fnam NOT = FIPS42 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #42 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 43) then
if (fnam NOT = FIPS43 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #43 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 44) then
if (fnam NOT = FIPS44 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #44 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 45) then
if (fnam NOT = FIPS45 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #45 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 46) then
if (fnam NOT = FIPS46 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #46 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 47) then
if (fnam NOT = FIPS47 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #47 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 48) then
if (fnam NOT = FIPS48 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #48 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 49) then
if (fnam NOT = FIPS49 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #49 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 50) then
if (fnam NOT = FIPS50 OR clas NOT = ntrm) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #50 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 51) then
if (fnam NOT = FIPS51 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #51 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 52) then
if (fnam NOT = FIPS52 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #52 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 53) then
if (fnam NOT = FIPS53 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #53 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 54) then
if (fnam NOT = FIPS54 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #54 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 55) then
if (fnam NOT = FIPS55 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #55 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 56) then
if (fnam NOT = FIPS56 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #56 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 57) then
if (fnam NOT = FIPS57 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #57 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 58) then
if (fnam NOT = FIPS58 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #58 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 59) then
if (fnam NOT = FIPS59 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #59 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 60) then
if (fnam NOT = FIPS60 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #60 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 61) then
if (fnam NOT = FIPS61 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #61 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 62) then
if (fnam NOT = FIPS62 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #62 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 63) then
if (fnam NOT = FIPS63 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #63 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 64) then
if (fnam NOT = FIPS64 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #60 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 65) then
if (fnam NOT = FIPS65 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #65 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 66) then
if (fnam NOT = FIPS66 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #66 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 67) then
if (fnam NOT = FIPS67 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #67 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 68) then
if (fnam NOT = FIPS68 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #68 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 69) then
if (fnam NOT = FIPS69 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #69 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 70) then
if (fnam NOT = FIPS70 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #70 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 71) then
if (fnam NOT = FIPS71 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #71 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 72) then
if (fnam NOT = FIPS72 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #72 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 73) then
if (fnam NOT = FIPS73 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #73 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 74) then
if (fnam NOT = FIPS74 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #74 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 75) then
if (fnam NOT = FIPS75 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #75 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 76) then
if (fnam NOT = FIPS76 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #76 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 77) then
if (fnam NOT = FIPS77 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #77 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 78) then
if (fnam NOT = FIPS78 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #78 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 79) then
if (fnam NOT = FIPS79 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #79 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 80) then
if (fnam NOT = FIPS80 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #80 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 81) then
if (fnam NOT = FIPS81 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #80 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 82) then
if (fnam NOT = FIPS82 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #82 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 83) then
if (fnam NOT = FIPS83 OR clas NOT = fl) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #83 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 84) then
if (fnam NOT = FIPS84 OR clas NOT = rd1) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #84 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 85) then
if (fnam NOT = FIPS85 OR clas NOT = rd1) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #85 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 86) then
if (fnam NOT = FIPS86 OR clas NOT = rd1) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #86 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 87) then
if (fnam NOT = FIPS87 OR clas NOT = rd1) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #87 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 88) then
if (fnam NOT = FIPS88 OR clas NOT = rd1) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #88 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid = 89) then
if (fnam NOT = FIPS89 OR clas NOT = rd1) then
DISPLAY "********** ERROR -- Reference to FIPS FEATURE
- " #89 incorrect"
MOVE 0 TO flag
END-IF
END-IF
if (fid < 1 OR fid > 89) then
DISPLAY "Incorrect value for FEATURE_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 = 90) then
DISPLAY "Incorrect number of rows returned!"
MOVE 0 TO flag
END-IF
DISPLAY "SELECT COUNT (*) INTO :co2"
DISPLAY "FROM FIPS_DOCUMENTATION.SQL_FEATURES"
DISPLAY "WHERE IS_VERIFIED = 'YES' AND"
DISPLAY "NOT IS_SUPPORTED = 'YES';"
* EXEC SQL SELECT COUNT (*) INTO :co2
* FROM FIPS_DOCUMENTATION.SQL_FEATURES
* WHERE IS_VERIFIED = 'YES' AND
* NOT IS_SUPPORTED = 'YES';
CALL "SUB7" USING SQLCODE SQLSTATE co2
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "co2 should be 0; its value is ", co2
if (co2 NOT = 0) then
MOVE 0 TO flag
END-IF
DISPLAY "CLOSE data802"
* EXEC SQL CLOSE data802;
CALL "SUB8" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "ROLLBACK WORK;"
* EXEC SQL ROLLBACK WORK;
CALL "SUB9" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if ( flag = 1 ) then
DISPLAY " yts802.mco *** pass *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7548','pass','MCO');
CALL "SUB10" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
else
DISPLAY " yts802.mco *** fail *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7548','fail','MCO');
CALL "SUB11" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
COMPUTE errcnt = errcnt + 1
END-IF
DISPLAY "==============================================="
* EXEC SQL COMMIT WORK;
CALL "SUB12" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
******************** END TEST7548 ********************
**** 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.68 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.
|