Quellcode-Bibliothek
© Kompilation durch diese Firma
[Weder Korrektheit noch Funktionsfähigkeit der Software werden zugesichert.]
Datei:
ist001.cob
Sprache: Cobol
|
|
IDENTIFICATION DIVISION.
PROGRAM-ID. XTS733.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. xyz.
OBJECT-COMPUTER. xyz.
DATA DIVISION.
WORKING-STORAGE SECTION.
* Standard COBOL (file "XTS733.SCO") calling SQL
* procedures in file "XTS733.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
*
* XTS733.SCO
* WRITTEN BY: Manolis Megaloikonomou
* TRANSLATED AUTOMATICALLY FROM EMBEDDED COBOL BY CHRIS SCHANZLE
*
* FULL OUTER JOIN <table ref> ON <search condition> -- static.
*
* REFERENCES
* 7.10 -- <query expression>
* 7.10 LR.2c -- Raised. Entry SQL restriction which
* prohibited the use of a <joined table>
* within a <query expression>.
* 6.3 -- <Table reference>.
* 6.3 LR.2a -- Raised. Entry SQL restriction which
* prohibited the use of a <joined table>
* in a <table reference>.
* 7.5 -- <joined table>.
* 7.5 GR.1.c
* 7.5 GR.5.d
* 7.5 GR.6.b
* 7.5 LR.2a -- Raised. Entry SQL restriction which
* prohibited the use of a <joined table>
* in a <table reference>.
* F#4 -- Joined table.
* F#24 -- Keyword relaxations.
* F#40 -- Full outer join.
*
* DATE LAST ALTERED 18/12/95 CTS5 Hand-over Test
*
* Cleanups and fixes by V. Kogakis 06/12/95
*
* QA STATUS :
*
* Revised by DWF 1996-02-06
* Removed status checks after cursor definition
* Fixed expected results & allowed nulls to be sorted first
* Fixed null value no indicator parms
* Check indicators instead of expecting data not to change
****************************************************************
* 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 coun PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
01 xtnum1 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
01 xtnum2 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
01 xtnum3 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
01 xtnum4 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
01 xtchar1 PIC X(10).
01 xtchar2 PIC X(10).
01 xtchar3 PIC X(10).
01 xtchar4 PIC X(10).
01 indic1 PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
01 indic2 PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
01 indic3 PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
01 indic4 PIC S9(4) 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 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, xts733.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 TEST7033 *******************
MOVE 1 TO flag
DISPLAY " TEST7033 "
DISPLAY " FULL OUTER JOIN ON
- " condition> --static."
DISPLAY "References:"
DISPLAY " 7.10 -- "
DISPLAY " 7.10 LR.2c -- Raised. Entry SQL restriction
- " which"
DISPLAY " prohibited the use of a
- " table>"
DISPLAY " within a ."
DISPLAY " 6.3 -- ."
DISPLAY " 6.3 LR.2a -- Raised. Entry SQL restriction
- " which"
DISPLAY " prohibited the use of a
- " table>"
DISPLAY " in a ."
DISPLAY " 7.5 -- ."
DISPLAY " 7.5 GR.1.c"
DISPLAY " 7.5 GR.5.d"
DISPLAY " 7.5 GR.6.b"
DISPLAY " 7.5 LR.2a -- Raised. Entry SQL restriction
- " which"
DISPLAY " prohibited the use of a
- " table>"
DISPLAY " in a ."
DISPLAY " F#4 -- Joined table."
DISPLAY " F#24 -- Keyword relaxations."
DISPLAY " F#40 -- Full outer join."
DISPLAY " - - - - - - - - - - - - - - - - - - -"
*Initialise error reporting variables
COMPUTE SQLCODE = -1
MOVE "xxxxx" TO SQLSTATE
*Ensure that the tables TEST6840A, TEST6840B, TEST6840C are empt
* EXEC SQL DELETE FROM TEST6840A;
CALL "SUB3" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
* EXEC SQL DELETE FROM TEST6840B;
CALL "SUB4" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
* EXEC SQL DELETE FROM TEST6840C;
CALL "SUB5" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
*Insert two rows of non null values into TEST6840A
DISPLAY "INSERT INTO TEST6840A VALUES (1,'A');"
* EXEC SQL INSERT INTO TEST6840A VALUES (1,'A');
CALL "SUB6" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "INSERT INTO TEST6840A VALUES (2,'B');"
* EXEC SQL INSERT INTO TEST6840A VALUES (2,'B');
CALL "SUB7" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*Insert two rows of non null values into TEST6840B
DISPLAY "INSERT INTO TEST6840B VALUES (2,'C');"
* EXEC SQL INSERT INTO TEST6840B VALUES (2,'C');
CALL "SUB8" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "INSERT INTO TEST6840B VALUES (3,'A');"
* EXEC SQL INSERT INTO TEST6840B VALUES (3,'A');
CALL "SUB9" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "DECLARE a CURSOR"
DISPLAY "FOR SELECT * FROM TEST6840A FULL OUTER JOIN
- " TEST6840B"
DISPLAY "ON NUM_A = NUM_B ORDER BY NUM_A;"
* EXEC SQL DECLARE a CURSOR
* FOR SELECT * FROM TEST6840A FULL OUTER JOIN TEST6840B
* ON NUM_A = NUM_B ORDER BY NUM_A END-EXEC
*Result should be:
*NUM_A CH_A NUM_B CH_B
*----- ---- ----- ----
* 1 A NULL NULL
* 2 B 2 C
*NULL NULL 3 A
*Except that the last row might actually be the first:
*13.1 GR.3.b: Whether nulls sort above or below non-nulls is
*implementation-defined!
*flag2 will be set if the null row is first.
MOVE 0 TO flag2
DISPLAY "OPEN a;"
* EXEC SQL OPEN a;
CALL "SUB10" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "There are two possible sorting orders for this
- " cursor,"
DISPLAY "because the sort column contains a NULL. (13.1
- " GR.3.b)"
.
P102.
*Initialise host variables
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE 99 TO indic1
MOVE 99 TO indic2
MOVE 99 TO indic3
MOVE 99 TO indic4
DISPLAY "FETCH a INTO :xtnum1:indic1, :xtchar1:indic2,"
DISPLAY " :xtnum2:indic3, :xtchar2:indic4;"
* EXEC SQL FETCH a INTO :xtnum1:indic1, :xtchar1:indic2,
* :xtnum2:indic3, :xtchar2:indic4;
CALL "SUB11" USING SQLCODE SQLSTATE xtnum1 indic1 xtchar1
indic2 xtnum2 indic3 xtchar2 indic4
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
if (indic1 = -1 AND flag2 = 0) then
DISPLAY "Sorting order is nulls-first."
MOVE 1 TO flag2
GO TO P100
END-IF
if (indic1 NOT = -1 AND flag2 = 0) then
DISPLAY "Sorting order is nulls-last."
END-IF
DISPLAY "xtnum1 should be 1; its value is ", xtnum1
DISPLAY "xtchar1 should be A; its value is ", xtchar1
DISPLAY "indic3 should be -1; its value is ", indic3
DISPLAY "indic4 should be -1; its value is ", indic4
if (xtnum1 NOT = 1 OR xtchar1 NOT = "A") then
MOVE 0 TO flag
END-IF
if (indic3 NOT = -1 OR indic4 NOT = -1) then
MOVE 0 TO flag
END-IF
DISPLAY " "
*Initialise host variables
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
DISPLAY "FETCH a INTO :xtnum1, :xtchar1, :xtnum2,
- " :xtchar2;"
* EXEC SQL FETCH a INTO :xtnum1, :xtchar1, :xtnum2, :xtchar2
* ;
CALL "SUB12" USING SQLCODE SQLSTATE xtnum1 xtchar1 xtnum2
xtchar2
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "xtnum1 should be 2; its value is ", xtnum1
DISPLAY "xtchar1 should be B; its value is ", xtchar1
DISPLAY "xtnum2 should be 2; its value is ", xtnum2
DISPLAY "xtchar2 should be C; its value is ", xtchar2
if ( xtnum1 NOT = 2 OR xtchar1 NOT = "B") then
MOVE 0 TO flag
END-IF
if ( xtnum2 NOT = 2 OR xtchar2 NOT = "C") then
MOVE 0 TO flag
END-IF
DISPLAY " "
if (flag2 = 1) then
GO TO P101
END-IF
*Initialise host variables
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE 99 TO indic1
MOVE 99 TO indic2
MOVE 99 TO indic3
MOVE 99 TO indic4
DISPLAY "FETCH a INTO :xtnum1:indic1, :xtchar1:indic2,"
DISPLAY " :xtnum2:indic3, :xtchar2:indic4;"
* EXEC SQL FETCH a INTO :xtnum1:indic1, :xtchar1:indic2,
* :xtnum2:indic3, :xtchar2:indic4;
CALL "SUB13" USING SQLCODE SQLSTATE xtnum1 indic1 xtchar1
indic2 xtnum2 indic3 xtchar2 indic4
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
.
P100.
DISPLAY "indic1 should be -1; its value is ", indic1
DISPLAY "indic2 should be -1; its value is ", indic2
DISPLAY "xtnum2 should be 3; its value is ", xtnum2
DISPLAY "xtchar2 should be A; its value is ", xtchar2
if (indic1 NOT = -1 OR indic2 NOT = -1) then
MOVE 0 TO flag
END-IF
if ( xtnum2 NOT = 3 OR xtchar2 NOT = "A") then
MOVE 0 TO flag
END-IF
DISPLAY " "
if (flag2 = 1) then
GO TO P102
END-IF
.
P101.
DISPLAY "CLOSE a;"
* EXEC SQL CLOSE a;
CALL "SUB14" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "DECLARE b CURSOR"
DISPLAY "FOR SELECT * FROM TEST6840A FULL JOIN TEST6840B"
DISPLAY "ON CH_A = CH_B ORDER BY NUM_A;"
* EXEC SQL DECLARE b CURSOR
* FOR SELECT * FROM TEST6840A FULL JOIN TEST6840B
* ON CH_A = CH_B ORDER BY NUM_A END-EXEC
*Result should be:
*NUM_A CH_A NUM_B CH_B
*----- ---- ----- ----
* 1 A 3 A
* 2 B NULL NULL
* NULL NULL 2 C
*Again, the sorting order is uncertain because of the null.
DISPLAY "OPEN b;"
* EXEC SQL OPEN b;
CALL "SUB15" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*Branch if nulls first
if (flag2 = 1) then
GO TO P103
END-IF
.
P104.
*Initialise host variables
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
DISPLAY "FETCH b INTO :xtnum1, :xtchar1, :xtnum2,
- " :xtchar2;"
* EXEC SQL FETCH b INTO :xtnum1, :xtchar1, :xtnum2, :xtchar2
* ;
CALL "SUB16" USING SQLCODE SQLSTATE xtnum1 xtchar1 xtnum2
xtchar2
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "xtnum1 should be 1; its value is ", xtnum1
DISPLAY "xtchar1 should be A; its value is ", xtchar1
DISPLAY "xtnum2 should be 3; its value is ", xtnum2
DISPLAY "xtchar2 should be A; its value is ", xtchar2
if ( xtnum1 NOT = 1 OR xtchar1 NOT = "A" ) then
MOVE 0 TO flag
END-IF
if ( xtnum2 NOT = 3 OR xtchar2 NOT = "A" ) then
MOVE 0 TO flag
END-IF
DISPLAY " "
*Initialise host variables
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE 99 TO indic1
MOVE 99 TO indic2
* EXEC SQL FETCH b INTO :xtnum1, :xtchar1,
* :xtnum2:indic1, :xtchar2:indic2;
CALL "SUB17" USING SQLCODE SQLSTATE xtnum1 xtchar1 xtnum2
indic1 xtchar2 indic2
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "xtnum1 should be 2; its value is ", xtnum1
DISPLAY "xtchar1 should be B; its value is ", xtchar1
DISPLAY "indic1 should be -1; its value is ", indic1
DISPLAY "indic2 should be -1; its value is ", indic2
if ( xtnum1 NOT = 2 OR xtchar1 NOT = "B" ) then
MOVE 0 TO flag
END-IF
if (indic1 NOT = -1 OR indic2 NOT = -1) then
MOVE 0 TO flag
END-IF
DISPLAY " "
if (flag2 = 1) then
GO TO P105
END-IF
.
P103.
*Initialise host variables
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
DISPLAY "FETCH b INTO :xtnum1:indic1, :xtchar1:indic2,"
DISPLAY " :xtnum2, :xtchar2;"
* EXEC SQL FETCH b INTO :xtnum1:indic1, :xtchar1:indic2,
* :xtnum2, :xtchar2;
CALL "SUB18" USING SQLCODE SQLSTATE xtnum1 indic1 xtchar1
indic2 xtnum2 xtchar2
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "indic1 should be -1; its value is ", indic1
DISPLAY "indic2 should be -1; its value is ", indic2
DISPLAY "xtnum2 should be 2; its value is ", xtnum2
DISPLAY "xtchar2 should be C; its value is ", xtchar2
if (indic1 NOT = -1 OR indic2 NOT = -1) then
MOVE 0 TO flag
END-IF
if ( xtnum2 NOT = 2 OR xtchar2 NOT = "C" ) then
MOVE 0 TO flag
END-IF
DISPLAY " "
if (flag2 = 1) then
GO TO P104
END-IF
.
P105.
DISPLAY "CLOSE b;"
* EXEC SQL CLOSE b;
CALL "SUB19" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "INSERT INTO TEST6840C"
DISPLAY "TEST6840A FULL OUTER JOIN TEST6840B ON NUM_A = 2;"
* EXEC SQL INSERT INTO TEST6840C
* TEST6840A FULL OUTER JOIN TEST6840B ON NUM_A = 2;
CALL "SUB20" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*TEST6840C is now:
*NUM_C1 CH_C1 NUM_C2 CH_C2
*------ ----- ------ -----
* 2 B 2 C
* 2 B 3 A
* 1 A NULL NULL
MOVE 99 TO coun
DISPLAY "SELECT COUNT(*) INTO :coun FROM TEST6840C;"
* EXEC SQL SELECT COUNT(*) INTO :coun FROM TEST6840C
* ;
CALL "SUB21" USING SQLCODE SQLSTATE coun
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "coun should be 3; its value is ", coun
if (coun NOT = 3) then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE 99 TO coun
DISPLAY "SELECT COUNT(*) INTO :coun FROM TEST6840C"
DISPLAY "WHERE NUM_C1 = 1 AND CH_C1 = 'A' "
DISPLAY "AND NUM_C2 IS NULL AND CH_C2 IS NULL;"
* EXEC SQL SELECT COUNT(*) INTO :coun FROM TEST6840C
* WHERE NUM_C1 = 1 AND CH_C1 = 'A' AND NUM_C2 IS NULL AND
* CH_C2 IS NULL;
CALL "SUB22" USING SQLCODE SQLSTATE coun
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "coun should be 1; its value is ", coun
if (coun NOT = 1) then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE 99 TO coun
DISPLAY "SELECT COUNT(*) INTO :coun FROM TEST6840C"
DISPLAY "WHERE NUM_C1 = 2 AND CH_C1 = 'B' AND NUM_C2 = 2
- " AND CH_C2 = 'C';"
* EXEC SQL SELECT COUNT(*) INTO :coun FROM TEST6840C
* WHERE NUM_C1 = 2 AND CH_C1 = 'B' AND NUM_C2 = 2 AND CH_C2
* = 'C';
CALL "SUB23" USING SQLCODE SQLSTATE coun
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "coun should be 1; its value is ", coun
if (coun NOT = 1) then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE 99 TO coun
DISPLAY "SELECT COUNT(*) INTO :coun FROM TEST6840C"
DISPLAY "WHERE NUM_C1 = 2 AND CH_C1 = 'B' AND NUM_C2 = 3
- " AND CH_C2 = 'A';"
* EXEC SQL SELECT COUNT(*) INTO :coun FROM TEST6840C
* WHERE NUM_C1 = 2 AND CH_C1 = 'B' AND NUM_C2 = 3 AND
* CH_C2 = 'A';
CALL "SUB24" USING SQLCODE SQLSTATE coun
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "coun should be 1; its value is ", coun
if (coun NOT = 1) then
MOVE 0 TO flag
END-IF
DISPLAY " "
DISPLAY "DECLARE c CURSOR FOR SELECT * FROM"
DISPLAY "(TEST6840B FULL JOIN TEST6840A AS CN1 ON
- " TEST6840B.CH_B = CN1.CH_A)"
DISPLAY "FULL JOIN TEST6840A AS CN2 ON TEST6840B.NUM_B =
- " CN2.NUM_A"
DISPLAY "ORDER BY TEST6840B.NUM_B, CN1.NUM_A;"
* EXEC SQL DECLARE c CURSOR
* FOR SELECT * FROM
* (TEST6840B FULL JOIN TEST6840A AS CN1 ON TEST6840B.CH_B =
* CN1.CH_A)
* FULL JOIN TEST6840A AS CN2 ON TEST6840B.NUM_B = CN2.NUM_A
* ORDER BY TEST6840B.NUM_B, CN1.NUM_A END-EXEC
*TEST6840B is
*NUM_B CH_B
*----- ----
* 2 C
* 3 A
*TEST6840A is
*NUM_A CH_A
*----- ----
* 1 A
* 2 B
*TEST6840B FULL JOIN TEST6840A AS CN1 ON TEST6840B.CH_B = CN1.CH
*NUM_B CH_B NUM_A CH_A
*----- ---- ----- ----
* 3 A 1 A
* 2 C NULL NULL
* NULL NULL 2 B
*... FULL JOIN TEST6840A AS CN2 ON TEST6840B.NUM_B = CN2.NUM_A
*Result should be (nulls last):
*NUM_B CH_B CN1.NUM_A CN1.CH_A CN2.NUM_A CN2.CH_A
*----- ---- --------- -------- --------- --------
* 2 C NULL NULL 2 B
* 3 A 1 A NULL NULL
*NULL NULL 2 B NULL NULL
*NULL NULL NULL NULL 1 A
*or (nulls first):
*NUM_B CH_B CN1.NUM_A CN1.CH_A CN2.NUM_A CN2.CH_A
*----- ---- --------- -------- --------- --------
*NULL NULL NULL NULL 1 A
*NULL NULL 2 B NULL NULL
* 2 C NULL NULL 2 B
* 3 A 1 A NULL NULL
DISPLAY "OPEN c;"
* EXEC SQL OPEN c;
CALL "SUB25" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if (flag2 = 1) then
GO TO P106
END-IF
*This is the nulls-last branch
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE 999 TO xtnum3
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE "xxxxxxxxxx" TO xtchar3
MOVE 99 TO indic1
MOVE 99 TO indic2
DISPLAY "FETCH c INTO :xtnum1, :xtchar1, :xtnum2:indic1,"
DISPLAY ":xtchar2:indic2, :xtnum3, :xtchar3;"
* EXEC SQL FETCH c INTO :xtnum1, :xtchar1, :xtnum2:indic1,
* :xtchar2:indic2, :xtnum3, :xtchar3;
CALL "SUB26" USING SQLCODE SQLSTATE xtnum1 xtchar1 xtnum2
indic1 xtchar2 indic2 xtnum3 xtchar3
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "xtnum1 should be 2; its value is ", xtnum1
DISPLAY "xtchar1 should be C; its value is ", xtchar1
DISPLAY "indic1 should be -1; its value is ", indic1
DISPLAY "indic2 should be -1; its value is ", indic2
DISPLAY "xtnum3 should be 2; its value is ", xtnum3
DISPLAY "xtchar3 should be B; its value is ", xtchar3
if (xtnum1 NOT = 2 OR xtchar1 NOT = "C" OR
indic1 NOT = -1) then
MOVE 0 TO flag
END-IF
if (indic2 NOT = -1 OR xtnum3 NOT = 2 OR xtchar3 NOT
= "B") then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE 999 TO xtnum3
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE "xxxxxxxxxx" TO xtchar3
MOVE 99 TO indic1
MOVE 99 TO indic2
DISPLAY "FETCH c INTO :xtnum1, :xtchar1, :xtnum2,
- " :xtchar2,"
DISPLAY ":xtnum3:indic1, :xtchar3:indic2;"
* EXEC SQL FETCH c INTO :xtnum1, :xtchar1, :xtnum2, :xtchar2,
* :xtnum3:indic1, :xtchar3:indic2;
CALL "SUB27" USING SQLCODE SQLSTATE xtnum1 xtchar1 xtnum2
xtchar2 xtnum3 indic1 xtchar3 indic2
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "xtnum1 should be 3; its value is ", xtnum1
DISPLAY "xtchar1 should be A; its value is ", xtchar1
DISPLAY "xtnum2 should be 1; its value is ", xtnum2
DISPLAY "xtchar2 should be A; its value is ", xtchar2
DISPLAY "indic1 should be -1; its value is ", indic1
DISPLAY "indic2 should be -1; its value is ", indic2
if ( xtnum1 NOT = 3 OR xtchar1 NOT = "A" OR
xtnum2 NOT = 1) then
MOVE 0 TO flag
END-IF
if (xtchar2 NOT = "A" OR indic1 NOT = -1 OR
indic2 NOT = -1) then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE 999 TO xtnum3
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE "xxxxxxxxxx" TO xtchar3
MOVE 99 TO indic1
MOVE 99 TO indic2
MOVE 99 TO indic3
MOVE 99 TO indic4
* EXEC SQL FETCH c INTO :xtnum1:indic1, :xtchar1:indic2,
* :xtnum2, :xtchar2, :xtnum3:indic3, :xtchar3:indic4
* ;
CALL "SUB28" USING SQLCODE SQLSTATE xtnum1 indic1 xtchar1
indic2 xtnum2 xtchar2 xtnum3 indic3 xtchar3 indic4
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "indic1 should be -1; its value is ", indic1
DISPLAY "indic2 should be -1; its value is ", indic2
DISPLAY "xtnum2 should be 2; its value is ", xtnum2
DISPLAY "xtchar2 should be B; its value is ", xtchar2
DISPLAY "indic3 should be -1; its value is ", indic3
DISPLAY "indic4 should be -1; its value is ", indic4
if (indic1 NOT = -1 OR indic2 NOT = -1 OR xtnum2
NOT = 2) then
MOVE 0 TO flag
END-IF
if (xtchar2 NOT = "B" OR indic3 NOT = -1 OR
indic4 NOT = -1) then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE 999 TO xtnum3
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE "xxxxxxxxxx" TO xtchar3
MOVE 99 TO indic1
MOVE 99 TO indic2
MOVE 99 TO indic3
MOVE 99 TO indic4
DISPLAY "FETCH c INTO :xtnum1:indic1, :xtchar1:indic2,"
DISPLAY ":xtnum2:indic3, :xtchar2:indic4, :xtnum3,
- " :xtchar3;"
* EXEC SQL FETCH c INTO :xtnum1:indic1, :xtchar1:indic2,
* :xtnum2:indic3, :xtchar2:indic4, :xtnum3, :xtchar3
* ;
CALL "SUB29" USING SQLCODE SQLSTATE xtnum1 indic1 xtchar1
indic2 xtnum2 indic3 xtchar2 indic4 xtnum3 xtchar3
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "indic1 should be -1; its value is ", indic1
DISPLAY "indic2 should be -1; its value is ", indic2
DISPLAY "indic3 should be -1; its value is ", indic3
DISPLAY "indic4 should be -1; its value is ", indic4
DISPLAY "xtnum3 should be 1; its value is ", xtnum3
DISPLAY "xtchar3 should be A; its value is ", xtchar3
if (indic1 NOT = -1 OR indic2 NOT = -1 OR indic3
NOT = -1) then
MOVE 0 TO flag
END-IF
if (indic4 NOT = -1 OR xtnum3 NOT = 1 OR xtchar3 NOT
= "A") then
MOVE 0 TO flag
END-IF
DISPLAY " "
GO TO P107
*nulls-first branch
.
P106.
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE 999 TO xtnum3
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE "xxxxxxxxxx" TO xtchar3
MOVE 99 TO indic1
MOVE 99 TO indic2
MOVE 99 TO indic3
MOVE 99 TO indic4
DISPLAY "FETCH c INTO :xtnum1:indic1, :xtchar1:indic2,"
DISPLAY ":xtnum2:indic3, :xtchar2:indic4, :xtnum3,
- " :xtchar3;"
* EXEC SQL FETCH c INTO :xtnum1:indic1, :xtchar1:indic2,
* :xtnum2:indic3, :xtchar2:indic4, :xtnum3, :xtchar3
* ;
CALL "SUB30" USING SQLCODE SQLSTATE xtnum1 indic1 xtchar1
indic2 xtnum2 indic3 xtchar2 indic4 xtnum3 xtchar3
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "indic1 should be -1; its value is ", indic1
DISPLAY "indic2 should be -1; its value is ", indic2
DISPLAY "indic3 should be -1; its value is ", indic3
DISPLAY "indic4 should be -1; its value is ", indic4
DISPLAY "xtnum3 should be 1; its value is ", xtnum3
DISPLAY "xtchar3 should be A; its value is ", xtchar3
if (indic1 NOT = -1 OR indic2 NOT = -1 OR indic3
NOT = -1) then
MOVE 0 TO flag
END-IF
if (indic4 NOT = -1 OR xtnum3 NOT = 1 OR xtchar3 NOT
= "A") then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE 999 TO xtnum3
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE "xxxxxxxxxx" TO xtchar3
MOVE 99 TO indic1
MOVE 99 TO indic2
MOVE 99 TO indic3
MOVE 99 TO indic4
* EXEC SQL FETCH c INTO :xtnum1:indic1, :xtchar1:indic2,
* :xtnum2, :xtchar2, :xtnum3:indic3, :xtchar3:indic4
* ;
CALL "SUB31" USING SQLCODE SQLSTATE xtnum1 indic1 xtchar1
indic2 xtnum2 xtchar2 xtnum3 indic3 xtchar3 indic4
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "indic1 should be -1; its value is ", indic1
DISPLAY "indic2 should be -1; its value is ", indic2
DISPLAY "xtnum2 should be 2; its value is ", xtnum2
DISPLAY "xtchar2 should be B; its value is ", xtchar2
DISPLAY "indic3 should be -1; its value is ", indic3
DISPLAY "indic4 should be -1; its value is ", indic4
if (indic1 NOT = -1 OR indic2 NOT = -1 OR xtnum2
NOT = 2) then
MOVE 0 TO flag
END-IF
if (xtchar2 NOT = "B" OR indic3 NOT = -1 OR
indic4 NOT = -1) then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE 999 TO xtnum3
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE "xxxxxxxxxx" TO xtchar3
MOVE 99 TO indic1
MOVE 99 TO indic2
DISPLAY "FETCH c INTO :xtnum1, :xtchar1, :xtnum2:indic1,"
DISPLAY ":xtchar2:indic2, :xtnum3, :xtchar3;"
* EXEC SQL FETCH c INTO :xtnum1, :xtchar1, :xtnum2:indic1,
* :xtchar2:indic2, :xtnum3, :xtchar3;
CALL "SUB32" USING SQLCODE SQLSTATE xtnum1 xtchar1 xtnum2
indic1 xtchar2 indic2 xtnum3 xtchar3
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "xtnum1 should be 2; its value is ", xtnum1
DISPLAY "xtchar1 should be C; its value is ", xtchar1
DISPLAY "indic1 should be -1; its value is ", indic1
DISPLAY "indic2 should be -1; its value is ", indic2
DISPLAY "xtnum3 should be 2; its value is ", xtnum3
DISPLAY "xtchar3 should be B; its value is ", xtchar3
if (xtnum1 NOT = 2 OR xtchar1 NOT = "C" OR
indic1 NOT = -1) then
MOVE 0 TO flag
END-IF
if (indic2 NOT = -1 OR xtnum3 NOT = 2 OR xtchar3 NOT
= "B") then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE 999 TO xtnum3
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE "xxxxxxxxxx" TO xtchar3
MOVE 99 TO indic1
MOVE 99 TO indic2
DISPLAY "FETCH c INTO :xtnum1, :xtchar1, :xtnum2,
- " :xtchar2,"
DISPLAY ":xtnum3:indic1, :xtchar3:indic2;"
* EXEC SQL FETCH c INTO :xtnum1, :xtchar1, :xtnum2, :xtchar2,
* :xtnum3:indic1, :xtchar3:indic2;
CALL "SUB33" USING SQLCODE SQLSTATE xtnum1 xtchar1 xtnum2
xtchar2 xtnum3 indic1 xtchar3 indic2
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "xtnum1 should be 3; its value is ", xtnum1
DISPLAY "xtchar1 should be A; its value is ", xtchar1
DISPLAY "xtnum2 should be 1; its value is ", xtnum2
DISPLAY "xtchar2 should be A; its value is ", xtchar2
DISPLAY "indic1 should be -1; its value is ", indic1
DISPLAY "indic2 should be -1; its value is ", indic2
if ( xtnum1 NOT = 3 OR xtchar1 NOT = "A" OR
xtnum2 NOT = 1) then
MOVE 0 TO flag
END-IF
if (xtchar2 NOT = "A" OR indic1 NOT = -1 OR
indic2 NOT = -1) then
MOVE 0 TO flag
END-IF
DISPLAY " "
.
P107.
DISPLAY "CLOSE c;"
* EXEC SQL CLOSE c;
CALL "SUB34" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "DECLARE d CURSOR FOR SELECT * FROM"
DISPLAY "(TEST6840A AS CN3 FULL OUTER JOIN TEST6840A AS
- " CN4"
DISPLAY " ON CN3.NUM_A = CN4.NUM_A) FULL OUTER JOIN"
DISPLAY "(TEST6840B AS CN5 FULL OUTER JOIN TEST6840B AS
- " CN6"
DISPLAY " ON CN5.CH_B = CN6.CH_B) ON CN3.NUM_A = CN5.NUM_B"
DISPLAY "ORDER BY CN3.NUM_A;"
* EXEC SQL DECLARE d CURSOR
* FOR SELECT * FROM
* (TEST6840A AS CN3 FULL OUTER JOIN TEST6840A AS CN4
* ON CN3.NUM_A = CN4.NUM_A)
* FULL OUTER JOIN
* (TEST6840B AS CN5 FULL OUTER JOIN TEST6840B AS CN6
* ON CN5.CH_B = CN6.CH_B)
* ON CN3.NUM_A = CN5.NUM_B
* ORDER BY CN3.NUM_A END-EXEC
*TEST6840A is
*NUM_A CH_A
*----- ----
* 1 A
* 2 B
*TEST6840B is
*NUM_B CH_B
*----- ----
* 2 C
* 3 A
*TEST6840A AS CN3 FULL OUTER JOIN TEST6840A AS CN4
* ON CN3.NUM_A = CN4.NUM_A
*CN3.NUM_A CN3.CH_A CN4.NUM_A CN4.CH_A
*--------- -------- --------- --------
* 1 A 1 A
* 2 B 2 B
*TEST6840B AS CN5 FULL OUTER JOIN TEST6840B AS CN6
* ON CN5.CH_B = CN6.CH_B
*CN5.NUM_B CN5.CH_B CN6.NUM_B CN6.CH_B
*--------- -------- --------- --------
* 2 C 2 C
* 3 A 3 A
*... OUTER JOIN ... ON CN3.NUM_A = CN5.NUM_B ORDER BY CN3.NUM_A
*Result should be
*CN3.NUM_ACN3.CH_ACN4.NUM_ACN4.CH_ACN5.NUM_BCN5.CH_BCN6.NUM_BCN6
*---------------------------------------------------------------
* 1 A 1 A NULL NULL NULL
* 2 B 2 B 2 C 2
* NULL NULL NULL NULL 3 A 3
*Or last row can be first for nulls-first sorting.
DISPLAY "OPEN d;"
* EXEC SQL OPEN d;
CALL "SUB35" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if (flag2 = 1) then
GO TO P109
END-IF
*nulls-last branch
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE 999 TO xtnum3
MOVE 999 TO xtnum4
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE "xxxxxxxxxx" TO xtchar3
MOVE "xxxxxxxxxx" TO xtchar4
MOVE 99 TO indic1
MOVE 99 TO indic2
MOVE 99 TO indic3
MOVE 99 TO indic4
DISPLAY "FETCH d INTO :xtnum1, :xtchar1, :xtnum2,
- " :xtchar2,"
DISPLAY ":xtnum3:indic1, :xtchar3:indic2, :xtnum4:indic3,
- " :xtchar4:indic4;"
* EXEC SQL FETCH d INTO :xtnum1, :xtchar1, :xtnum2, :xtchar2,
* :xtnum3:indic1, :xtchar3:indic2, :xtnum4:indic3,
* :xtchar4:indic4;
CALL "SUB36" USING SQLCODE SQLSTATE xtnum1 xtchar1 xtnum2
xtchar2 xtnum3 indic1 xtchar3 indic2 xtnum4 indic3 xtchar4
indic4
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "xtnum1 should be 1; its value is ", xtnum1
DISPLAY "xtchar1 should be A; its value is ", xtchar1
DISPLAY "xtnum2 should be 1; its value is ", xtnum2
DISPLAY "xtchar2 should be A; its value is ", xtchar2
DISPLAY "indic1 should be -1; its value is ", indic1
DISPLAY "indic2 should be -1; its value is ", indic2
DISPLAY "indic3 should be -1; its value is ", indic3
DISPLAY "indic4 should be -1; its value is ", indic4
if ( xtnum1 NOT = 1 OR xtchar1 NOT = "A") then
MOVE 0 TO flag
END-IF
if ( xtnum2 NOT = 1 OR xtchar2 NOT = "A") then
MOVE 0 TO flag
END-IF
if (indic1 NOT = -1 OR indic2 NOT = -1) then
MOVE 0 TO flag
END-IF
if (indic3 NOT = -1 OR indic4 NOT = -1) then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE 999 TO xtnum3
MOVE 999 TO xtnum4
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE "xxxxxxxxxx" TO xtchar3
MOVE "xxxxxxxxxx" TO xtchar4
DISPLAY "FETCH d INTO :xtnum1, :xtchar1, :xtnum2,
- " :xtchar2,"
DISPLAY ":xtnum3, :xtchar3, :xtnum4, :xtchar4;"
* EXEC SQL FETCH d INTO :xtnum1, :xtchar1, :xtnum2, :xtchar2,
* :xtnum3, :xtchar3, :xtnum4, :xtchar4;
CALL "SUB37" USING SQLCODE SQLSTATE xtnum1 xtchar1 xtnum2
xtchar2 xtnum3 xtchar3 xtnum4 xtchar4
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "xtnum1 should be 2; its value is ", xtnum1
DISPLAY "xtchar1 should be B; its value is ", xtchar1
DISPLAY "xtnum2 should be 2; its value is ", xtnum2
DISPLAY "xtchar2 should be B; its value is ", xtchar2
DISPLAY "xtnum3 should be 2; its value is ", xtnum3
DISPLAY "xtchar3 should be C; its value is ", xtchar3
DISPLAY "xtnum4 should be 2; its value is ", xtnum4
DISPLAY "xtchar4 should be C; its value is ", xtchar4
if ( xtnum1 NOT = 2 OR xtchar1 NOT = "B") then
MOVE 0 TO flag
END-IF
if ( xtnum2 NOT = 2 OR xtchar2 NOT = "B") then
MOVE 0 TO flag
END-IF
if ( xtnum3 NOT = 2 OR xtchar3 NOT = "C") then
MOVE 0 TO flag
END-IF
if ( xtnum4 NOT = 2 OR xtchar4 NOT = "C") then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE 999 TO xtnum3
MOVE 999 TO xtnum4
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE "xxxxxxxxxx" TO xtchar3
MOVE "xxxxxxxxxx" TO xtchar4
MOVE 99 TO indic1
MOVE 99 TO indic2
MOVE 99 TO indic3
MOVE 99 TO indic4
DISPLAY "FETCH d INTO :xtnum1, :xtchar1, :xtnum2,
- " :xtchar2,"
DISPLAY ":xtnum3, :xtchar3, :xtnum4, :xtchar4;"
* EXEC SQL FETCH d INTO :xtnum1:indic1, :xtchar1:indic2,
* :xtnum2:indic3, :xtchar2:indic4,
* :xtnum3, :xtchar3, :xtnum4, :xtchar4;
CALL "SUB38" USING SQLCODE SQLSTATE xtnum1 indic1 xtchar1
indic2 xtnum2 indic3 xtchar2 indic4 xtnum3 xtchar3 xtnum4
xtchar4
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "indic1 should be -1; its value is ", indic1
DISPLAY "indic2 should be -1; its value is ", indic2
DISPLAY "indic3 should be -1; its value is ", indic3
DISPLAY "indic4 should be -1; its value is ", indic4
DISPLAY "xtnum3 should be 3; its value is ", xtnum3
DISPLAY "xtchar3 should be A; its value is ", xtchar3
DISPLAY "xtnum4 should be 3; its value is ", xtnum4
DISPLAY "xtchar4 should be A; its value is ", xtchar4
if (indic1 NOT = -1 OR indic2 NOT = -1) then
MOVE 0 TO flag
END-IF
if (indic3 NOT = -1 OR indic4 NOT = -1) then
MOVE 0 TO flag
END-IF
if ( xtnum3 NOT = 3 OR xtchar3 NOT = "A") then
MOVE 0 TO flag
END-IF
if ( xtnum4 NOT = 3 OR xtchar4 NOT = "A") then
MOVE 0 TO flag
END-IF
DISPLAY " "
GO TO P108
.
P109.
*nulls-first branch
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE 999 TO xtnum3
MOVE 999 TO xtnum4
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE "xxxxxxxxxx" TO xtchar3
MOVE "xxxxxxxxxx" TO xtchar4
MOVE 99 TO indic1
MOVE 99 TO indic2
MOVE 99 TO indic3
MOVE 99 TO indic4
DISPLAY "FETCH d INTO :xtnum1, :xtchar1, :xtnum2,
- " :xtchar2,"
DISPLAY ":xtnum3, :xtchar3, :xtnum4, :xtchar4;"
* EXEC SQL FETCH d INTO :xtnum1:indic1, :xtchar1:indic2,
* :xtnum2:indic3, :xtchar2:indic4,
* :xtnum3, :xtchar3, :xtnum4, :xtchar4;
CALL "SUB39" USING SQLCODE SQLSTATE xtnum1 indic1 xtchar1
indic2 xtnum2 indic3 xtchar2 indic4 xtnum3 xtchar3 xtnum4
xtchar4
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "indic1 should be -1; its value is ", indic1
DISPLAY "indic2 should be -1; its value is ", indic2
DISPLAY "indic3 should be -1; its value is ", indic3
DISPLAY "indic4 should be -1; its value is ", indic4
DISPLAY "xtnum3 should be 3; its value is ", xtnum3
DISPLAY "xtchar3 should be A; its value is ", xtchar3
DISPLAY "xtnum4 should be 3; its value is ", xtnum4
DISPLAY "xtchar4 should be A; its value is ", xtchar4
if (indic1 NOT = -1 OR indic2 NOT = -1) then
MOVE 0 TO flag
END-IF
if (indic3 NOT = -1 OR indic4 NOT = -1) then
MOVE 0 TO flag
END-IF
if ( xtnum3 NOT = 3 OR xtchar3 NOT = "A") then
MOVE 0 TO flag
END-IF
if ( xtnum4 NOT = 3 OR xtchar4 NOT = "A") then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE 999 TO xtnum3
MOVE 999 TO xtnum4
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE "xxxxxxxxxx" TO xtchar3
MOVE "xxxxxxxxxx" TO xtchar4
MOVE 99 TO indic1
MOVE 99 TO indic2
MOVE 99 TO indic3
MOVE 99 TO indic4
DISPLAY "FETCH d INTO :xtnum1, :xtchar1, :xtnum2,
- " :xtchar2,"
DISPLAY ":xtnum3:indic1, :xtchar3:indic2, :xtnum4:indic3,
- " :xtchar4:indic4;"
* EXEC SQL FETCH d INTO :xtnum1, :xtchar1, :xtnum2, :xtchar2,
* :xtnum3:indic1, :xtchar3:indic2, :xtnum4:indic3,
* :xtchar4:indic4;
CALL "SUB40" USING SQLCODE SQLSTATE xtnum1 xtchar1 xtnum2
xtchar2 xtnum3 indic1 xtchar3 indic2 xtnum4 indic3 xtchar4
indic4
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "xtnum1 should be 1; its value is ", xtnum1
DISPLAY "xtchar1 should be A; its value is ", xtchar1
DISPLAY "xtnum2 should be 1; its value is ", xtnum2
DISPLAY "xtchar2 should be A; its value is ", xtchar2
DISPLAY "indic1 should be -1; its value is ", indic1
DISPLAY "indic2 should be -1; its value is ", indic2
DISPLAY "indic3 should be -1; its value is ", indic3
DISPLAY "indic4 should be -1; its value is ", indic4
if ( xtnum1 NOT = 1 OR xtchar1 NOT = "A") then
MOVE 0 TO flag
END-IF
if ( xtnum2 NOT = 1 OR xtchar2 NOT = "A") then
MOVE 0 TO flag
END-IF
if (indic1 NOT = -1 OR indic2 NOT = -1) then
MOVE 0 TO flag
END-IF
if (indic3 NOT = -1 OR indic4 NOT = -1) then
MOVE 0 TO flag
END-IF
DISPLAY " "
MOVE 999 TO xtnum1
MOVE 999 TO xtnum2
MOVE 999 TO xtnum3
MOVE 999 TO xtnum4
MOVE "xxxxxxxxxx" TO xtchar1
MOVE "xxxxxxxxxx" TO xtchar2
MOVE "xxxxxxxxxx" TO xtchar3
MOVE "xxxxxxxxxx" TO xtchar4
DISPLAY "FETCH d INTO :xtnum1, :xtchar1, :xtnum2,
- " :xtchar2,"
DISPLAY ":xtnum3, :xtchar3, :xtnum4, :xtchar4;"
* EXEC SQL FETCH d INTO :xtnum1, :xtchar1, :xtnum2, :xtchar2,
* :xtnum3, :xtchar3, :xtnum4, :xtchar4;
CALL "SUB41" USING SQLCODE SQLSTATE xtnum1 xtchar1 xtnum2
xtchar2 xtnum3 xtchar3 xtnum4 xtchar4
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "xtnum1 should be 2; its value is ", xtnum1
DISPLAY "xtchar1 should be B; its value is ", xtchar1
DISPLAY "xtnum2 should be 2; its value is ", xtnum2
DISPLAY "xtchar2 should be B; its value is ", xtchar2
DISPLAY "xtnum3 should be 2; its value is ", xtnum3
DISPLAY "xtchar3 should be C; its value is ", xtchar3
DISPLAY "xtnum4 should be 2; its value is ", xtnum4
DISPLAY "xtchar4 should be C; its value is ", xtchar4
if ( xtnum1 NOT = 2 OR xtchar1 NOT = "B") then
MOVE 0 TO flag
END-IF
if ( xtnum2 NOT = 2 OR xtchar2 NOT = "B") then
MOVE 0 TO flag
END-IF
if ( xtnum3 NOT = 2 OR xtchar3 NOT = "C") then
MOVE 0 TO flag
END-IF
if ( xtnum4 NOT = 2 OR xtchar4 NOT = "C") then
MOVE 0 TO flag
END-IF
DISPLAY " "
.
P108.
DISPLAY "CLOSE d;"
* EXEC SQL CLOSE d;
CALL "SUB42" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "ROLLBACK WORK;"
* EXEC SQL ROLLBACK WORK;
CALL "SUB43" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
if ( flag = 1 ) then
DISPLAY " xts733.mco *** pass *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7033','pass','MCO');
CALL "SUB44" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
else
DISPLAY " xts733.mco *** fail *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7033','fail','MCO');
CALL "SUB45" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
COMPUTE errcnt = errcnt + 1
DISPLAY "========================================"
* EXEC SQL COMMIT WORK;
CALL "SUB46" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
******************** END TEST7033 ********************
END-IF
**** 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.89 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.
|
| |