IDENTIFICATION DIVISION.
PROGRAM-ID. DML173.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. xyz.
OBJECT-COMPUTER. xyz.
DATA DIVISION.
WORKING-STORAGE SECTION.
* Standard COBOL (file "DML173.SCO") calling SQL
* procedures in file "DML173.MCO".
****************************************************************
*
* COMMENT SECTION
*
* DATE 1996-05-13 Module COBOL LANGUAGE
* SQL VALIDATION TEST SUITE V6.0
* DISCLAIMER:
* This program was written by employees of NIST to test SQL
* implementations for conformance to the SQL standards.
* NIST assumes no responsibility for any party's use of
* this program.
*
* DML173.SCO
* WRITTEN BY: David Flater
* TRANSLATED AUTOMATICALLY FROM EMBEDDED COBOL BY CHRIS SCHANZLE
*
* This routine tests Intermediate SQL.
*
* REFERENCES
* FIPS PUB 127-2 14.2 Intermediate SQL
* ANSI SQL-1992
*
****************************************************************
* 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 int1 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 "FLATER " TO uid
CALL "AUTHID" USING uid
MOVE "not logged in, not" TO uidx
* EXEC SQL SELECT USER INTO :uidx FROM HU.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, dml173.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 TEST0885 *******************
MOVE 1 TO flag
DISPLAY " FIPS sizing TEST0885"
DISPLAY " FIPS sizing, CHAR (1000)"
DISPLAY "References:"
DISPLAY " FIPS 16.6 -- Sizing #2, CHARACTER max length"
DISPLAY " - - - - - - - - - - - - - - - - - - -"
COMPUTE SQLCODE = -1
MOVE "xxxxx" TO SQLSTATE
DISPLAY "CREATE TABLE CONTACTS ("
DISPLAY " NAME CHAR (20),"
DISPLAY " DESCRIPTION CHAR (1000),"
DISPLAY " KEYWORDS CHAR (1000));"
* EXEC SQL CREATE TABLE CONTACTS (
* NAME CHAR (20),
* DESCRIPTION CHAR (1000),
* KEYWORDS CHAR (1000));
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 CONTACTS VALUES ('Harry',"
DISPLAY "'Harry works in the Redundancy Automation Division
- " of the '"
DISPLAY "'Materials '"
DISPLAY "'Blasting Laboratory in the National Cattle
- " Acceleration '"
DISPLAY "'Project of '"
DISPLAY "'lower Michigan. His job is to document the
- " trajectory of '"
DISPLAY "'cattle and '"
DISPLAY "'correlate the loft and acceleration versus the
- " quality of '"
DISPLAY "'materials '"
DISPLAY "'used in the trebuchet. He served ten years as
- " the '"
DISPLAY "'vice-president in '"
DISPLAY "'charge of marketing in the now defunct milk trust
- " of the '"
DISPLAY "'Pennsylvania '"
DISPLAY "'Coalition of All Things Bovine. Prior to that he
- " '"
DISPLAY "'established himself '"
DISPLAY "'as a world-class graffiti artist and source of
- " all good '"
DISPLAY "'bits related '"
DISPLAY "'to channel dredging in poor weather. He is
- " author of over '"
DISPLAY "'ten thousand '"
DISPLAY "'paperback novels, including such titles as ""How
- " Many '"
DISPLAY "'Pumpkins will Fit '"
DISPLAY "'on the Head of a Pin,"" ""A Whole Bunch of
- " Useless Things '"
DISPLAY "'that you Don''t '"
DISPLAY "'Want to Know,"" and ""How to Lift Heavy Things
- " Over your '"
DISPLAY "'Head without '"
DISPLAY "'Hurting Yourself or Dropping Them."" He attends
- " ANSI and '"
DISPLAY "'ISO standards '"
DISPLAY "'meetings in his copious free time and funds the
- " development '"
DISPLAY "'of test '"
DISPLAY "'suites with his pocket change.',"
DISPLAY "'aardvark albatross nutmeg redundancy '"
DISPLAY "'automation materials blasting '"
DISPLAY "'cattle acceleration trebuchet catapult '"
DISPLAY "'loft coffee java sendmail SMTP '"
DISPLAY "'FTP HTTP censorship expletive senility '"
DISPLAY "'extortion distortion conformity '"
DISPLAY "'conformance nachos chicks goslings '"
DISPLAY "'ducklings honk quack melatonin tie '"
DISPLAY "'noose circulation column default '"
DISPLAY "'ionic doric chlorine guanine Guam '"
DISPLAY "'invasions rubicon helmet plastics '"
DISPLAY "'recycle HDPE nylon ceramics plumbing '"
DISPLAY "'parachute zeppelin carbon hydrogen '"
DISPLAY "'vinegar sludge asphalt adhesives '"
DISPLAY "'tensile magnetic Ellesmere Greenland '"
DISPLAY "'Knud Rasmussen precession '"
DISPLAY "'navigation positioning orbit altitude '"
DISPLAY "'resistance radiation levitation '"
DISPLAY "'yoga demiurge election violence '"
DISPLAY "'collapsed fusion cryogenics gravity '"
DISPLAY "'sincerity idiocy budget accounting '"
DISPLAY "'auditing titanium torque pressure '"
DISPLAY "'fragile hernia muffler cartilage '"
DISPLAY "'graphics deblurring headache eyestrain '"
DISPLAY "'interlace bandwidth resolution '"
DISPLAY "'determination steroids barrel oak wine '"
DISPLAY "'ferment yeast brewing bock siphon '"
DISPLAY "'clarity impurities SQL RBAC data '"
DISPLAY "'warehouse security integrity feedback');"
* EXEC SQL INSERT INTO CONTACTS VALUES ('Harry',
* 'Harry works in the Redundancy Automation Division '
* 'clarity impurities SQL RBAC data '
* 'warehouse security integrity feedback');
CALL "SUB5" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
MOVE 0 TO int1
DISPLAY "SELECT COUNT(*) INTO :int1"
DISPLAY " FROM CONTACTS"
DISPLAY " WHERE DESCRIPTION ="
DISPLAY "'Harry works in the Redundancy Automation Division
- " of the ' ||"
DISPLAY "'Materials ' ||"
DISPLAY "'Blasting Laboratory in the National Cattle
- " Acceleration ' ||"
DISPLAY "'Project of ' ||"
DISPLAY "'lower Michigan. His job is to document the
- " trajectory of ' ||"
DISPLAY "'cattle and ' ||"
DISPLAY "'correlate the loft and acceleration versus the
- " quality of ' ||"
DISPLAY "'materials ' ||"
DISPLAY "'used in the trebuchet. He served ten years as
- " the ' ||"
DISPLAY "'vice-president in ' ||"
DISPLAY "'charge of marketing in the now defunct milk trust
- " of the ' ||"
DISPLAY "'Pennsylvania ' ||"
DISPLAY "'Coalition of All Things Bovine. Prior to that he
- " ' ||"
DISPLAY "'established himself ' ||"
DISPLAY "'as a world-class graffiti artist and source of
- " all good ' ||"
DISPLAY "'bits related ' ||"
DISPLAY "'to channel dredging in poor weather. He is
- " author of over ' ||"
DISPLAY "'ten thousand ' ||"
DISPLAY "'paperback novels, including such titles as ""How
- " Many ' ||"
DISPLAY "'Pumpkins will Fit ' ||"
DISPLAY "'on the Head of a Pin,"" ""A Whole Bunch of
- " Useless Things ' ||"
DISPLAY "'that you Don''t ' ||"
DISPLAY "'Want to Know,"" and ""How to Lift Heavy Things
- " Over your ' ||"
DISPLAY "'Head without ' ||"
DISPLAY "'Hurting Yourself or Dropping Them."" He attends
- " ANSI and ' ||"
DISPLAY "'ISO standards ' ||"
DISPLAY "'meetings in his copious free time and funds the
- " development ' ||"
DISPLAY "'of test ' ||"
DISPLAY "'suites with his pocket change.'"
DISPLAY " AND KEYWORDS ="
DISPLAY "'aardvark albatross nutmeg redundancy ' ||"
DISPLAY "'automation materials blasting ' ||"
DISPLAY "'cattle acceleration trebuchet catapult ' ||"
DISPLAY "'loft coffee java sendmail SMTP ' ||"
DISPLAY "'FTP HTTP censorship expletive senility ' ||"
DISPLAY "'extortion distortion conformity ' ||"
DISPLAY "'conformance nachos chicks goslings ' ||"
DISPLAY "'ducklings honk quack melatonin tie ' ||"
DISPLAY "'noose circulation column default ' ||"
DISPLAY "'ionic doric chlorine guanine Guam ' ||"
DISPLAY "'invasions rubicon helmet plastics ' ||"
DISPLAY "'recycle HDPE nylon ceramics plumbing ' ||"
DISPLAY "'parachute zeppelin carbon hydrogen ' ||"
DISPLAY "'vinegar sludge asphalt adhesives ' ||"
DISPLAY "'tensile magnetic Ellesmere Greenland ' ||"
DISPLAY "'Knud Rasmussen precession ' ||"
DISPLAY "'navigation positioning orbit altitude ' ||"
DISPLAY "'resistance radiation levitation ' ||"
DISPLAY "'yoga demiurge election violence ' ||"
DISPLAY "'collapsed fusion cryogenics gravity ' ||"
DISPLAY "'sincerity idiocy budget accounting ' ||"
DISPLAY "'auditing titanium torque pressure ' ||"
DISPLAY "'fragile hernia muffler cartilage ' ||"
DISPLAY "'graphics deblurring headache eyestrain ' ||"
DISPLAY "'interlace bandwidth resolution ' ||"
DISPLAY "'determination steroids barrel oak wine ' ||"
DISPLAY "'ferment yeast brewing bock siphon ' ||"
DISPLAY "'clarity impurities SQL RBAC data ' ||"
DISPLAY "'warehouse security integrity feedback';"
* EXEC SQL SELECT COUNT(*) INTO :int1
* FROM CONTACTS
* WHERE DESCRIPTION =
* 'Harry works in the Redundancy Automation Division ' ||
* 'warehouse security integrity feedback';
CALL "SUB6" USING SQLCODE SQLSTATE int1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "int1 should be 1; its value is ", int1
if (int1 NOT = 1) then
MOVE 0 TO flag
END-IF
MOVE 99 TO int1
DISPLAY "SELECT COUNT(*) INTO :int1"
DISPLAY " FROM CONTACTS"
DISPLAY " WHERE DESCRIPTION LIKE '%change.'"
DISPLAY " AND KEYWORDS LIKE '%feedback';"
* EXEC SQL SELECT COUNT(*) INTO :int1
* FROM CONTACTS
* WHERE DESCRIPTION LIKE '%change.'
* AND KEYWORDS LIKE '%feedback';
CALL "SUB7" USING SQLCODE SQLSTATE int1
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "int1 should be 1; its value is ", int1
if (int1 NOT = 1) then
MOVE 0 TO flag
END-IF
DISPLAY "COMMIT WORK;"
* EXEC SQL COMMIT WORK;
CALL "SUB8" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "DROP TABLE CONTACTS CASCADE;"
* EXEC SQL DROP TABLE CONTACTS CASCADE;
CALL "SUB9" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "COMMIT WORK;"
* EXEC SQL COMMIT WORK;
CALL "SUB10" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if ( flag = 1 ) then
DISPLAY " *** pass *** "
* EXEC SQL INSERT INTO HU.TESTREPORT
* VALUES('0885','pass','MCO');
CALL "SUB11" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
else
DISPLAY " dml173.mco *** fail *** "
* EXEC SQL INSERT INTO HU.TESTREPORT
* VALUES('0885','fail','MCO');
CALL "SUB12" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
COMPUTE errcnt = errcnt + 1
END-IF
DISPLAY "==============================================="
* EXEC SQL COMMIT WORK;
CALL "SUB13" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
******************** END TEST0885 ********************
**** 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.
[ Verzeichnis aufwärts0.43unsichere Verbindung
Übersetzung europäischer Sprachen durch Browser
]
|