products/Sources/formale Sprachen/Cobol/Test-Suite/SQL M image not shown  

Quellcode-Bibliothek

© Kompilation durch diese Firma

[Weder Korrektheit noch Funktionsfähigkeit der Software werden zugesichert.]

Datei: yts781.mco   Sprache: Unknown

       IDENTIFICATION DIVISION.
       PROGRAM-ID.  DML148.
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SOURCE-COMPUTER.  xyz.
       OBJECT-COMPUTER.  xyz.
       DATA DIVISION.
       WORKING-STORAGE SECTION.


      * Standard COBOL (file "DML148.SCO") calling SQL
      * procedures in file "DML148.MCO".


      ****************************************************************
      *                                                              
      *                 COMMENT SECTION                              
      *                                                              
      * DATE 1995/2/6 STANDARD COBOL LANGUAGE                            
      * NIST 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.
      *                                                              
      * DML148.SCO                                                    
      * WRITTEN BY:  Joan Sullivan (mostly)                          
      * TRANSLATED AUTOMATICALLY FROM EMBEDDED COBOL BY CHRIS SCHANZLE
      * Standard COBOL by David Flater                                   
      *                                                              
      * This routine tests the ordering of columns in joins.         
      *                                                              
      * REFERENCES                                                   
      *   FIPS PUB 127-2 14.1 Transitional 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  en PIC  X(3).
       01  pn PIC  X(3).
       01  pn2 PIC  X(3).
       01  ename PIC  X(20).
       01  pname PIC  X(20).
       01  pt PIC  X(6).
       01  ct PIC  X(15).
       01  tc PIC  X(10).
       01  hr PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
       01  gr PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
       01  bu PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
       01  int1 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
       01  int2 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
       01  indic1 PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
       01  indic2 PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
       01  flt1 PIC S9(4)V9(4) DISPLAY SIGN LEADING SEPARATE.
       01  flt2 PIC S9(4)V9(4) DISPLAY SIGN LEADING SEPARATE.
      *  EXEC SQL END DECLARE SECTION END-EXEC
       01  FLT-1 PIC -(5).9999.
       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, dml148.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 TEST0843 *******************
             MOVE 1 TO flag

             DISPLAY " TEST0843 "
             DISPLAY " Ordering of column names in joins"
             DISPLAY "References:"
             DISPLAY " F# 4 -- Joined table"
             DISPLAY " 7.5 SR.6.f -- Ordering of columns"
             DISPLAY " 7.5 SR.5 -- Ordering of columns"
             DISPLAY " - - - - - - - - - - - - - - - - - - -"

             COMPUTE SQLCODE = -1
             MOVE "xxxxx" TO SQLSTATE

             DISPLAY "DECLARE C14811 CURSOR FOR"
             DISPLAY " SELECT * FROM HU.WORKS NATURAL LEFT JOIN
      -    " HU.PROJ"
             DISPLAY " ORDER BY EMPNUM DESC, PNUM;"
      *  EXEC SQL DECLARE C14811 CURSOR FOR
      *    SELECT * FROM HU.WORKS NATURAL LEFT JOIN HU.PROJ
      *    ORDER BY EMPNUM DESC, PNUM END-EXEC

             DISPLAY "OPEN C14811;"
      *  EXEC SQL OPEN C14811;
             CALL "SUB3" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             MOVE "xxx" TO pn
             MOVE "xxx" TO en
             COMPUTE hr = -1
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxx" TO pt
             COMPUTE bu = -1
             MOVE "xxxxxxxxxxxxxxx" TO ct
             DISPLAY "FETCH C14811 INTO :pn, :en, :hr, :pname, :pt, :bu,
      -    " :ct;"
      *  EXEC SQL FETCH C14811 INTO :pn, :en, :hr, :pname, :pt, :bu,
      *  :ct;
             CALL "SUB4" USING SQLCODE SQLSTATE pn en hr pname pt 
             bu ct
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "pn should be P2; its value is ", pn
             DISPLAY "en should be E4; its value is ", en
             DISPLAY "hr should be 20; its value is ", hr
             DISPLAY "pname should be CALM; its value is ", pname
             DISPLAY "pt should be Code; its value is ", pt
             DISPLAY "bu should be 30000; its value is ", bu
             DISPLAY "ct should be Vienna; its value is ", ct
             if (pn  NOT  =   "P2"  OR  en  NOT  =   "E4"then
               MOVE 0 TO flag
             END-IF
             if (hr  NOT =  20  OR  pname  NOT  =   "CALM"then
               MOVE 0 TO flag
             END-IF
             if (pt  NOT  =   "Code"  OR  bu  NOT =  30000) then
               MOVE 0 TO flag
             END-IF
             if (ct  NOT  =   "Vienna"then
               MOVE 0 TO flag
             END-IF

             MOVE "xxx" TO pn
             MOVE "xxx" TO en
             COMPUTE hr = -1
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxx" TO pt
             COMPUTE bu = -1
             MOVE "xxxxxxxxxxxxxxx" TO ct
             DISPLAY "FETCH C14811 INTO :pn, :en, :hr, :pname, :pt, :bu,
      -    " :ct;"
      *  EXEC SQL FETCH C14811 INTO :pn, :en, :hr, :pname, :pt, :bu,
      *  :ct;
             CALL "SUB5" USING SQLCODE SQLSTATE pn en hr pname pt 
             bu ct
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "pn should be P4; its value is ", pn
             DISPLAY "en should be E4; its value is ", en
             DISPLAY "hr should be 40; its value is ", hr
             DISPLAY "pname should be SDP; its value is ", pname
             DISPLAY "pt should be Design; its value is ", pt
             DISPLAY "bu should be 20000; its value is ", bu
             DISPLAY "ct should be Deale; its value is ", ct
             if (pn  NOT  =   "P4"  OR  en  NOT  =   "E4"then
               MOVE 0 TO flag
             END-IF
             if (hr  NOT =  40  OR  pname  NOT  =   "SDP"then
               MOVE 0 TO flag
             END-IF
             if (pt  NOT  =   "Design"  OR  bu  NOT =  20000) then
               MOVE 0 TO flag
             END-IF
             if (ct  NOT  =   "Deale"then
               MOVE 0 TO flag
             END-IF

             DISPLAY "CLOSE C14811;"
      *  EXEC SQL CLOSE C14811;
             CALL "SUB6" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             DISPLAY "DECLARE C14812 CURSOR FOR"
             DISPLAY " SELECT * FROM HU.WORKS JOIN HU.PROJ USING
      -    " (PNUM)"
             DISPLAY " ORDER BY EMPNUM DESC, PNUM;"
      *  EXEC SQL DECLARE C14812 CURSOR FOR
      *    SELECT * FROM HU.WORKS JOIN HU.PROJ USING (PNUM)
      *    ORDER BY EMPNUM DESC, PNUM END-EXEC

             DISPLAY "OPEN C14812;"
      *  EXEC SQL OPEN C14812;
             CALL "SUB7" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             MOVE "xxx" TO pn
             MOVE "xxx" TO en
             COMPUTE hr = -1
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxx" TO pt
             COMPUTE bu = -1
             MOVE "xxxxxxxxxxxxxxx" TO ct
             DISPLAY "FETCH C14812 INTO :pn, :en, :hr, :pname, :pt, :bu,
      -    " :ct;"
      *  EXEC SQL FETCH C14812 INTO :pn, :en, :hr, :pname, :pt, :bu,
      *  :ct;
             CALL "SUB8" USING SQLCODE SQLSTATE pn en hr pname pt 
             bu ct
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "pn should be P2; its value is ", pn
             DISPLAY "en should be E4; its value is ", en
             DISPLAY "hr should be 20; its value is ", hr
             DISPLAY "pname should be CALM; its value is ", pname
             DISPLAY "pt should be Code; its value is ", pt
             DISPLAY "bu should be 30000; its value is ", bu
             DISPLAY "ct should be Vienna; its value is ", ct
             if (pn  NOT  =   "P2"  OR  en  NOT  =   "E4"then
               MOVE 0 TO flag
             END-IF
             if (hr  NOT =  20  OR  pname  NOT  =   "CALM"then
               MOVE 0 TO flag
             END-IF
             if (pt  NOT  =   "Code"  OR  bu  NOT =  30000) then
               MOVE 0 TO flag
             END-IF
             if (ct  NOT  =   "Vienna"then
               MOVE 0 TO flag
             END-IF

             MOVE "xxx" TO pn
             MOVE "xxx" TO en
             COMPUTE hr = -1
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxx" TO pt
             COMPUTE bu = -1
             MOVE "xxxxxxxxxxxxxxx" TO ct
             DISPLAY "FETCH C14812 INTO :pn, :en, :hr, :pname, :pt, :bu,
      -    " :ct;"
      *  EXEC SQL FETCH C14812 INTO :pn, :en, :hr, :pname, :pt, :bu,
      *  :ct;
             CALL "SUB9" USING SQLCODE SQLSTATE pn en hr pname pt 
             bu ct
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "pn should be P4; its value is ", pn
             DISPLAY "en should be E4; its value is ", en
             DISPLAY "hr should be 40; its value is ", hr
             DISPLAY "pname should be SDP; its value is ", pname
             DISPLAY "pt should be Design; its value is ", pt
             DISPLAY "bu should be 20000; its value is ", bu
             DISPLAY "ct should be Deale; its value is ", ct
             if (pn  NOT  =   "P4"  OR  en  NOT  =   "E4"then
               MOVE 0 TO flag
             END-IF
             if (hr  NOT =  40  OR  pname  NOT  =   "SDP"then
               MOVE 0 TO flag
             END-IF
             if (pt  NOT  =   "Design"  OR  bu  NOT =  20000) then
               MOVE 0 TO flag
             END-IF
             if (ct  NOT  =   "Deale"then
               MOVE 0 TO flag
             END-IF

             DISPLAY "CLOSE C14812;"
      *  EXEC SQL CLOSE C14812;
             CALL "SUB10" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             DISPLAY "DECLARE C14813 CURSOR FOR"
             DISPLAY " SELECT * FROM HU.WORKS RIGHT JOIN HU.PROJ"
             DISPLAY " ON HU.WORKS.PNUM = HU.PROJ.PNUM"
             DISPLAY " ORDER BY 1 DESC, 2;"
      *  EXEC SQL DECLARE C14813 CURSOR FOR
      *    SELECT * FROM HU.WORKS RIGHT JOIN HU.PROJ
      *    ON HU.WORKS.PNUM = HU.PROJ.PNUM
      *    ORDER BY 1 DESC, 2 END-EXEC

             DISPLAY "OPEN C14813;"
      *  EXEC SQL OPEN C14813;
             CALL "SUB11" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD

             MOVE "xxx" TO pn
             MOVE "xxx" TO pn2
             MOVE "xxx" TO en
             COMPUTE hr = -1
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxx" TO pt
             COMPUTE bu = -1
             MOVE "xxxxxxxxxxxxxxx" TO ct
             DISPLAY "FETCH C14813 INTO :en, :pn, :hr, :pn2, :pname,
      -    " :pt, :bu, :ct;"
      *  EXEC SQL FETCH C14813 INTO :en, :pn, :hr, :pn2, :pname,
      *  :pt, :bu, :ct;
             CALL "SUB12" USING SQLCODE SQLSTATE en pn hr pn2 pname pt 
             bu ct
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "en should be E4; its value is ", en
             DISPLAY "pn should be P2; its value is ", pn
             DISPLAY "hr should be 20; its value is ", hr
             DISPLAY "pn2 should be P2; its value is ", pn2
             DISPLAY "pname should be CALM; its value is ", pname
             DISPLAY "pt should be Code; its value is ", pt
             DISPLAY "bu should be 30000; its value is ", bu
             DISPLAY "ct should be Vienna; its value is ", ct
             if (en  NOT  =   "E4"  OR  pn  NOT  =   "P2"then
               MOVE 0 TO flag
             END-IF
             if (hr  NOT =  20  OR  pname  NOT  =   "CALM"then
               MOVE 0 TO flag
             END-IF
             if (pt  NOT  =   "Code"  OR  bu  NOT =  30000) then
               MOVE 0 TO flag
             END-IF
             if (ct  NOT  =   "Vienna"  OR  pn2  NOT  =   "P2"then
               MOVE 0 TO flag
             END-IF

             MOVE "xxx" TO pn
             MOVE "xxx" TO pn2
             MOVE "xxx" TO en
             COMPUTE hr = -1
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxx" TO pt
             COMPUTE bu = -1
             MOVE "xxxxxxxxxxxxxxx" TO ct
             DISPLAY "FETCH C14813 INTO :en, :pn, :hr, :pn2, :pname,
      -    " :pt, :bu, :ct;"
      *  EXEC SQL FETCH C14813 INTO :en, :pn, :hr, :pn2, :pname,
      *  :pt, :bu, :ct;
             CALL "SUB13" USING SQLCODE SQLSTATE en pn hr pn2 pname pt 
             bu ct
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "en should be E4; its value is ", en
             DISPLAY "pn should be P4; its value is ", pn
             DISPLAY "hr should be 40; its value is ", hr
             DISPLAY "pn2 should be P4; its value is ", pn2
             DISPLAY "pname should be SDP; its value is ", pname
             DISPLAY "pt should be Design; its value is ", pt
             DISPLAY "bu should be 20000; its value is ", bu
             DISPLAY "ct should be Deale; its value is ", ct
             if (en  NOT  =   "E4"  OR  pn  NOT  =   "P4"then
               MOVE 0 TO flag
             END-IF
             if (hr  NOT =  40  OR  pname  NOT  =   "SDP"then
               MOVE 0 TO flag
             END-IF
             if (pt  NOT  =   "Design"  OR  bu  NOT =  20000) then
               MOVE 0 TO flag
             END-IF
             if (ct  NOT  =   "Deale"  OR  pn2  NOT  =   "P4"then
               MOVE 0 TO flag
             END-IF

             DISPLAY "ROLLBACK WORK;"
      *  EXEC SQL ROLLBACK WORK;
             CALL "SUB14" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "


             if ( flag  =  1 ) then
               DISPLAY " *** pass *** "
      *    EXEC SQL INSERT INTO HU.TESTREPORT
      *      VALUES('0843','pass','MCO');
               CALL "SUB15" USING SQLCODE SQLSTATE
               MOVE SQLCODE TO SQL-COD
             else
               DISPLAY " dml148.sco *** fail *** "
      *    EXEC SQL INSERT INTO HU.TESTREPORT
      *      VALUES('0843','fail','MCO');
               CALL "SUB16" USING SQLCODE SQLSTATE
               MOVE SQLCODE TO SQL-COD
               COMPUTE errcnt = errcnt + 1
             END-IF

             DISPLAY "==============================================="

      *  EXEC SQL COMMIT WORK;
             CALL "SUB17" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
      ******************** END TEST0843 ********************
      ******************** BEGIN TEST0844 *******************
             MOVE 1 TO flag

             DISPLAY " TEST0844 "
             DISPLAY " Outer join predicates"
             DISPLAY "References:"
             DISPLAY " F# 4 -- Joined table"
             DISPLAY " - - - - - - - - - - - - - - - - - - -"

             COMPUTE SQLCODE = -1
             MOVE "xxxxx" TO SQLSTATE

             DISPLAY "CREATE TABLE SEVEN_TYPES ("
             DISPLAY " T_INT INTEGER,"
             DISPLAY " T_CHAR CHAR(10),"
             DISPLAY " T_SMALL SMALLINT,"
             DISPLAY " T_DECIMAL DECIMAL(10,2),"
             DISPLAY " T_REAL REAL,"
             DISPLAY " T_NUMERIC NUMERIC(8,4),"
             DISPLAY " DECIMAL6_6 DECIMAL (12,6));"
      *  EXEC SQL CREATE TABLE SEVEN_TYPES (
      *    T_INT     INTEGER,
      *    T_CHAR    CHAR(10),
      *    T_SMALL   SMALLINT,
      *    T_DECIMAL DECIMAL(10,2),
      *    T_REAL    REAL,
      *    T_NUMERIC   NUMERIC(8,4),
      *    DECIMAL6_6  DECIMAL (12,6));
             CALL "SUB18" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             DISPLAY "COMMIT WORK;"
      *  EXEC SQL COMMIT WORK;
             CALL "SUB19" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             DISPLAY "DELETE FROM SEVEN_TYPES;"
      *  EXEC SQL DELETE FROM SEVEN_TYPES;
             CALL "SUB20" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD

             DISPLAY "INSERT INTO SEVEN_TYPES VALUES (1, 'E1',-11, 2,
      -    " 3, 4, 5);"
      *  EXEC SQL INSERT INTO SEVEN_TYPES VALUES (1, 'E1',-11,   2, 
      *  3,   4,   5);
             CALL "SUB21" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             DISPLAY "INSERT INTO SEVEN_TYPES VALUES (2, 'E2', -5, 13,
      -    " 33,-444, -55);"
      *  EXEC SQL INSERT INTO SEVEN_TYPES VALUES (2, 'E2', -5,  13,
      *  33,-444, -55);
             CALL "SUB22" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             DISPLAY "INSERT INTO SEVEN_TYPES VALUES (3, 'E6',
      -    " -3,-222,333, 44, 555);"
      *  EXEC SQL INSERT INTO SEVEN_TYPES VALUES (3, 'E6',
      *  -3,-222,333,  44, 555);
             CALL "SUB23" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             DISPLAY "INSERT INTO SEVEN_TYPES VALUES (12,'DUP', 0, 0,
      -    " -1, 1,1E+1);"
      *  EXEC SQL INSERT INTO SEVEN_TYPES VALUES (12,'DUP', 0,   0,
      *  -1,   1,1E+1);
             CALL "SUB24" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             DISPLAY "INSERT INTO SEVEN_TYPES VALUES (12,'DUP', 0, 0,
      -    " -1, 1,1E+1);"
      *  EXEC SQL INSERT INTO SEVEN_TYPES VALUES (12,'DUP', 0,   0,
      *  -1,   1,1E+1);
             CALL "SUB25" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

      *Subtest number one 
      *BETWEEN predicate 

             DISPLAY "DECLARE C14821 CURSOR FOR"
             DISPLAY " SELECT EMPNAME, CITY, T_DECIMAL"
             DISPLAY " FROM HU.STAFF LEFT OUTER JOIN SEVEN_TYPES "
             DISPLAY " ON -GRADE / 11 BETWEEN T_REAL AND T_DECIMAL"
             DISPLAY " ORDER BY EMPNAME;"
      *  EXEC SQL DECLARE C14821 CURSOR FOR
      *    SELECT EMPNAME, CITY, T_DECIMAL
      *    FROM HU.STAFF LEFT OUTER JOIN SEVEN_TYPES 
      *    ON -GRADE / 11 BETWEEN T_REAL AND T_DECIMAL
      *    ORDER BY EMPNAME END-EXEC

             DISPLAY "OPEN C14821;"
      *  EXEC SQL OPEN C14821;
             CALL "SUB26" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 48 TO int1
             MOVE 48 TO indic1
             DISPLAY "FETCH C14821 INTO :ename, :ct, :int1:indic1;"
      *  EXEC SQL FETCH C14821 INTO :ename, :ct, :int1:indic1
      * ;
             CALL "SUB27" USING SQLCODE SQLSTATE ename ct int1 
             indic1
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ename should be Alice; its value is ", ename
             DISPLAY "ct should be Deale; its value is ", ct
             DISPLAY "indic1 should be -1; its value is ", indic1
             if (ename  NOT  =   "Alice"  OR  ct  NOT  =   "Deale"then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 48 TO int1
             MOVE 48 TO indic1
             DISPLAY "FETCH C14821 INTO :ename, :ct, :int1:indic1;"
      *  EXEC SQL FETCH C14821 INTO :ename, :ct, :int1:indic1
      * ;
             CALL "SUB28" USING SQLCODE SQLSTATE ename ct int1 
             indic1
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ename should be Betty; its value is ", ename
             DISPLAY "ct should be Vienna; its value is ", ct
             DISPLAY "int1 should be 0; its value is ", int1
             DISPLAY "indic1 should be 0; its value is ", indic1
             if (ename  NOT  =   "Betty"  OR  ct  NOT  =   "Vienna")
             then
               MOVE 0 TO flag
             END-IF
             if (int1  NOT =  0  OR  indic1  NOT =  0) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 48 TO int1
             MOVE 48 TO indic1
             DISPLAY "FETCH C14821 INTO :ename, :ct, :int1:indic1;"
      *  EXEC SQL FETCH C14821 INTO :ename, :ct, :int1:indic1
      * ;
             CALL "SUB29" USING SQLCODE SQLSTATE ename ct int1 
             indic1
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ename should be Betty; its value is ", ename
             DISPLAY "ct should be Vienna; its value is ", ct
             DISPLAY "int1 should be 0; its value is ", int1
             DISPLAY "indic1 should be 0; its value is ", indic1
             if (ename  NOT  =   "Betty"  OR  ct  NOT  =   "Vienna")
             then
               MOVE 0 TO flag
             END-IF
             if (int1  NOT =  0  OR  indic1  NOT =  0) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 48 TO int1
             MOVE 48 TO indic1
             DISPLAY "FETCH C14821 INTO :ename, :ct, :int1:indic1;"
      *  EXEC SQL FETCH C14821 INTO :ename, :ct, :int1:indic1
      * ;
             CALL "SUB30" USING SQLCODE SQLSTATE ename ct int1 
             indic1
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ename should be Carmen; its value is ", ename
             DISPLAY "ct should be Vienna; its value is ", ct
             DISPLAY "indic1 should be -1; its value is ", indic1
             if (ename  NOT  =   "Carmen"  OR  ct  NOT  =   "Vienna")
             then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 48 TO int1
             MOVE 48 TO indic1
             DISPLAY "FETCH C14821 INTO :ename, :ct, :int1:indic1;"
      *  EXEC SQL FETCH C14821 INTO :ename, :ct, :int1:indic1
      * ;
             CALL "SUB31" USING SQLCODE SQLSTATE ename ct int1 
             indic1
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ename should be Don; its value is ", ename
             DISPLAY "ct should be Deale; its value is ", ct
             DISPLAY "indic1 should be -1; its value is ", indic1
             if (ename  NOT  =   "Don"  OR  ct  NOT  =   "Deale"then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 48 TO int1
             MOVE 48 TO indic1
             DISPLAY "FETCH C14821 INTO :ename, :ct, :int1:indic1;"
      *  EXEC SQL FETCH C14821 INTO :ename, :ct, :int1:indic1
      * ;
             CALL "SUB32" USING SQLCODE SQLSTATE ename ct int1 
             indic1
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ename should be Ed; its value is ", ename
             DISPLAY "ct should be Akron; its value is ", ct
             DISPLAY "indic1 should be -1; its value is ", indic1
             if (ename  NOT  =   "Ed"  OR  ct  NOT  =   "Akron"then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             DISPLAY "FETCH C14821 INTO :ename, :ct, :int1:indic1;"
      *  EXEC SQL FETCH C14821 INTO :ename, :ct, :int1:indic1
      * ;
             CALL "SUB33" USING SQLCODE SQLSTATE ename ct int1 
             indic1
             MOVE SQLCODE TO SQL-COD
             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  " "

             DISPLAY "CLOSE C14821;"
      *  EXEC SQL CLOSE C14821;
             CALL "SUB34" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

      *Subtest number two 
      *Comparable CHAR types 
      *IN predicate, with literals and variable value 

             DISPLAY "int1 = 10;"
             MOVE 10 TO int1
             DISPLAY "DECLARE C14822 CURSOR FOR"
             DISPLAY " SELECT T_INT, T_CHAR, EMPNAME, EMPNUM, GRADE "
             DISPLAY " FROM SEVEN_TYPES RIGHT JOIN HU.STAFF"
             DISPLAY " ON GRADE IN (:int1, 11, 13) AND EMPNUM = T_CHAR"
             DISPLAY " ORDER BY EMPNAME, T_INT;"
      *  EXEC SQL DECLARE C14822 CURSOR FOR
      *    SELECT T_INT, T_CHAR, EMPNAME, EMPNUM, GRADE 
      *    FROM SEVEN_TYPES RIGHT JOIN HU.STAFF
      *    ON GRADE IN (:int1, 11, 13) AND EMPNUM = T_CHAR
      *    ORDER BY EMPNAME, T_INT END-EXEC

             DISPLAY "OPEN C14822;"
      *  EXEC SQL OPEN C14822;
             CALL "SUB35" USING SQLCODE SQLSTATE int1
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             MOVE 49 TO int1
             MOVE 49 TO indic1
             MOVE "xxxxxxxxxx" TO tc
             MOVE 49 TO indic2
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxx" TO en
             MOVE 49 TO gr
             DISPLAY "FETCH C14822 INTO :int1:indic1, :tc:indic2,
      -    " :ename, :en, :gr;"
      *  EXEC SQL FETCH C14822 INTO :int1:indic1, :tc:indic2,
      *  :ename, :en, :gr;
             CALL "SUB36" USING SQLCODE SQLSTATE int1 indic1 tc 
             indic2 ename en gr
             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 "ename should be Alice; its value is ", ename
             DISPLAY "en should be E1; its value is ", en
             DISPLAY "gr should be 12; its value is ", gr
             if (indic1  NOT =  -1  OR  indic2  NOT =  -1) then
               MOVE 0 TO flag
             END-IF
             if (ename  NOT  =   "Alice"  OR  en  NOT  =   "E1"then
               MOVE 0 TO flag
             END-IF
             if (gr  NOT =  12) then
               MOVE 0 TO flag
             END-IF

             MOVE 49 TO int1
             MOVE 49 TO indic1
             MOVE "xxxxxxxxxx" TO tc
             MOVE 49 TO indic2
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxx" TO en
             MOVE 49 TO gr
             DISPLAY "FETCH C14822 INTO :int1:indic1, :tc:indic2,
      -    " :ename, :en, :gr;"
      *  EXEC SQL FETCH C14822 INTO :int1:indic1, :tc:indic2,
      *  :ename, :en, :gr;
             CALL "SUB37" USING SQLCODE SQLSTATE int1 indic1 tc 
             indic2 ename en gr
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "indic1 should be 0; its value is ", indic1
             DISPLAY "indic2 should be 0; its value is ", indic2
             DISPLAY "int1 should be 2; its value is ", int1
             DISPLAY "tc should be E2; its value is ", tc
             DISPLAY "ename should be Betty; its value is ", ename
             DISPLAY "en should be E2; its value is ", en
             DISPLAY "gr should be 10; its value is ", gr
             if (indic1  NOT =  0  OR  indic2  NOT =  0) then
               MOVE 0 TO flag
             END-IF
             if (int1  NOT =  2  OR  tc  NOT  =   "E2"then
               MOVE 0 TO flag
             END-IF
             if (ename  NOT  =   "Betty"  OR  en  NOT  =   "E2"then
               MOVE 0 TO flag
             END-IF
             if (gr  NOT =  10) then
               MOVE 0 TO flag
             END-IF

             MOVE 49 TO int1
             MOVE 49 TO indic1
             MOVE "xxxxxxxxxx" TO tc
             MOVE 49 TO indic2
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxx" TO en
             MOVE 49 TO gr
             DISPLAY "FETCH C14822 INTO :int1:indic1, :tc:indic2,
      -    " :ename, :en, :gr;"
      *  EXEC SQL FETCH C14822 INTO :int1:indic1, :tc:indic2,
      *  :ename, :en, :gr;
             CALL "SUB38" USING SQLCODE SQLSTATE int1 indic1 tc 
             indic2 ename en gr
             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 "ename should be Carmen; its value is ", ename
             DISPLAY "en should be E3; its value is ", en
             DISPLAY "gr should be 13; its value is ", gr
             if (indic1  NOT =  -1  OR  indic2  NOT =  -1) then
               MOVE 0 TO flag
             END-IF
             if (ename  NOT  =   "Carmen"  OR  en  NOT  =   "E3"then
               MOVE 0 TO flag
             END-IF
             if (gr  NOT =  13) then
               MOVE 0 TO flag
             END-IF

             DISPLAY "CLOSE C14822;"
      *  EXEC SQL CLOSE C14822;
             CALL "SUB39" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

      *Subtest number three 
      *Subquery with outer reference and correlation names 

             DISPLAY "DECLARE C14823 CURSOR FOR"
             DISPLAY " SELECT XX.PNUM, BUDGET, HOURS, EMPNUM"
             DISPLAY " FROM HU.PROJ XX LEFT JOIN HU.WORKS YY"
             DISPLAY " ON XX.PNUM = YY.PNUM AND"
             DISPLAY " HOURS * BUDGET / 160000 > (SELECT GRADE FROM
      -    " HU.STAFF"
             DISPLAY " WHERE YY.EMPNUM = HU.STAFF.EMPNUM)"
             DISPLAY " ORDER BY 1;"
      *  EXEC SQL DECLARE C14823 CURSOR FOR
      *    SELECT XX.PNUM, BUDGET, HOURS, EMPNUM
      *    FROM HU.PROJ XX LEFT JOIN HU.WORKS YY
      *    ON  XX.PNUM = YY.PNUM AND
      *    HOURS * BUDGET / 160000 > (SELECT GRADE FROM HU.STAFF
      *    WHERE YY.EMPNUM = HU.STAFF.EMPNUM)
      *    ORDER BY 1 END-EXEC

             DISPLAY "OPEN C14823;"
      *  EXEC SQL OPEN C14823;
             CALL "SUB40" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             MOVE "xxx" TO pn
             MOVE "xxx" TO en
             MOVE 5 TO bu
             MOVE 5 TO hr
             MOVE 5 TO indic1
             MOVE 5 TO indic2
             DISPLAY "FETCH C14823 INTO :pn, :bu, :hr:indic1,
      -    " :en:indic2;"
      *  EXEC SQL FETCH C14823 INTO :pn, :bu, :hr:indic1, :en:indic2
      * ;
             CALL "SUB41" USING SQLCODE SQLSTATE pn bu hr 
             indic1 en indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "pn should be P1; its value is ", pn
             DISPLAY "bu should be 10000; its value is ", bu
             DISPLAY "indic1 should be -1; its value is ", indic1
             DISPLAY "indic2 should be -1; its value is ", indic2
             if (pn  NOT  =   "P1"  OR  bu  NOT =  10000) then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1  OR  indic2  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxx" TO pn
             MOVE "xxx" TO en
             MOVE 5 TO bu
             MOVE 5 TO hr
             MOVE 5 TO indic1
             MOVE 5 TO indic2
             DISPLAY "FETCH C14823 INTO :pn, :bu, :hr:indic1,
      -    " :en:indic2;"
      *  EXEC SQL FETCH C14823 INTO :pn, :bu, :hr:indic1, :en:indic2
      * ;
             CALL "SUB42" USING SQLCODE SQLSTATE pn bu hr indic1 
             en indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "pn should be P2; its value is ", pn
             DISPLAY "bu should be 30000; its value is ", bu
             DISPLAY "hr should be 80; its value is ", hr
             DISPLAY "en should be E2; its value is ", en
             DISPLAY "indic1 should be 0; its value is ", indic1
             DISPLAY "indic2 should be 0; its value is ", indic2
             if (pn  NOT  =   "P2"  OR  bu  NOT =  30000) then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  0  OR  indic2  NOT =  0) then
               MOVE 0 TO flag
             END-IF
             if (hr  NOT =  80  OR  en  NOT  =   "E2"then
               MOVE 0 TO flag
             END-IF

             MOVE "xxx" TO pn
             MOVE "xxx" TO en
             MOVE 5 TO bu
             MOVE 5 TO hr
             MOVE 5 TO indic1
             MOVE 5 TO indic2
             DISPLAY "FETCH C14823 INTO :pn, :bu, :hr:indic1,
      -    " :en:indic2;"
      *  EXEC SQL FETCH C14823 INTO :pn, :bu, :hr:indic1, :en:indic2
      * ;
             CALL "SUB43" USING SQLCODE SQLSTATE pn bu hr indic1 
             en indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "pn should be P3; its value is ", pn
             DISPLAY "bu should be 30000; its value is ", bu
             DISPLAY "hr should be 80; its value is ", hr
             DISPLAY "en should be E1; its value is ", en
             DISPLAY "indic1 should be 0; its value is ", indic1
             DISPLAY "indic2 should be 0; its value is ", indic2
             if (pn  NOT  =   "P3"  OR  bu  NOT =  30000) then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  0  OR  indic2  NOT =  0) then
               MOVE 0 TO flag
             END-IF
             if (hr  NOT =  80  OR  en  NOT  =   "E1"then
               MOVE 0 TO flag
             END-IF

             MOVE "xxx" TO pn
             MOVE "xxx" TO en
             MOVE 5 TO bu
             MOVE 5 TO hr
             MOVE 5 TO indic1
             MOVE 5 TO indic2
             DISPLAY "FETCH C14823 INTO :pn, :bu, :hr:indic1,
      -    " :en:indic2;"
      *  EXEC SQL FETCH C14823 INTO :pn, :bu, :hr:indic1, :en:indic2
      * ;
             CALL "SUB44" USING SQLCODE SQLSTATE pn bu hr indic1 
             en indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "pn should be P4; its value is ", pn
             DISPLAY "bu should be 20000; its value is ", bu
             DISPLAY "indic1 should be -1; its value is ", indic1
             DISPLAY "indic2 should be -1; its value is ", indic2
             if (pn  NOT  =   "P4"  OR  bu  NOT =  20000) then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1  OR  indic2  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxx" TO pn
             MOVE "xxx" TO en
             MOVE 5 TO bu
             MOVE 5 TO hr
             MOVE 5 TO indic1
             MOVE 5 TO indic2
             DISPLAY "FETCH C14823 INTO :pn, :bu, :hr:indic1,
      -    " :en:indic2;"
      *  EXEC SQL FETCH C14823 INTO :pn, :bu, :hr:indic1, :en:indic2
      * ;
             CALL "SUB45" USING SQLCODE SQLSTATE pn bu hr indic1 
             en indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "pn should be P5; its value is ", pn
             DISPLAY "bu should be 10000; its value is ", bu
             DISPLAY "indic1 should be -1; its value is ", indic1
             DISPLAY "indic2 should be -1; its value is ", indic2
             if (pn  NOT  =   "P5"  OR  bu  NOT =  10000) then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1  OR  indic2  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxx" TO pn
             MOVE "xxx" TO en
             MOVE 5 TO bu
             MOVE 5 TO hr
             MOVE 5 TO indic1
             MOVE 5 TO indic2
             DISPLAY "FETCH C14823 INTO :pn, :bu, :hr:indic1,
      -    " :en:indic2;"
      *  EXEC SQL FETCH C14823 INTO :pn, :bu, :hr:indic1, :en:indic2
      * ;
             CALL "SUB46" USING SQLCODE SQLSTATE pn bu hr 
             indic1 en indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "pn should be P6; its value is ", pn
             DISPLAY "bu should be 50000; its value is ", bu
             DISPLAY "indic1 should be -1; its value is ", indic1
             DISPLAY "indic2 should be -1; its value is ", indic2
             if (pn  NOT  =   "P6"  OR  bu  NOT =  50000) then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1  OR  indic2  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             DISPLAY "FETCH C14823 INTO :pn, :bu, :hr:indic1,
      -    " :en:indic2;"
      *  EXEC SQL FETCH C14823 INTO :pn, :bu, :hr:indic1, :en:indic2
      * ;
             CALL "SUB47" USING SQLCODE SQLSTATE pn bu hr 
             indic1 en indic2
             MOVE SQLCODE TO SQL-COD
             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  " "

             DISPLAY "CLOSE C14823;"
      *  EXEC SQL CLOSE C14823;
             CALL "SUB48" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

      *Subtest number four 

             DISPLAY "DECLARE C14824 CURSOR FOR"
             DISPLAY " SELECT HU.STAFF.CITY,EMPNAME,PNAME,BUDGET"
             DISPLAY " FROM HU.STAFF LEFT JOIN HU.PROJ"
             DISPLAY " ON HU.STAFF.CITY = HU.PROJ.CITY"
             DISPLAY " AND HU.STAFF.CITY <> 'Vienna'"
             DISPLAY " AND EMPNAME <> 'Don'"
             DISPLAY " WHERE BUDGET > 15000 OR BUDGET IS NULL"
             DISPLAY " ORDER BY HU.STAFF.CITY, EMPNAME, BUDGET;"
      *  EXEC SQL DECLARE C14824 CURSOR FOR
      *    SELECT HU.STAFF.CITY,EMPNAME,PNAME,BUDGET
      *    FROM HU.STAFF LEFT JOIN HU.PROJ
      *    ON HU.STAFF.CITY = HU.PROJ.CITY
      *    AND HU.STAFF.CITY <> 'Vienna'
      *    AND EMPNAME <> 'Don'
      *    WHERE BUDGET > 15000 OR BUDGET IS NULL
      *    ORDER BY HU.STAFF.CITY, EMPNAME, BUDGET END-EXEC

             DISPLAY "OPEN C14824;"
      *  EXEC SQL OPEN C14824;
             CALL "SUB49" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 28 TO bu
             DISPLAY "FETCH C14824 INTO :ct, :ename, :pname:indic1,
      -    " :bu:indic2;"
      *  EXEC SQL FETCH C14824 INTO :ct, :ename, :pname:indic1,
      *  :bu:indic2;
             CALL "SUB50" USING SQLCODE SQLSTATE ct ename pname 
             indic1 bu indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ct should be Akron; its value is ", ct
             DISPLAY "ename should be Ed; its value is ", ename
             DISPLAY "indic1 should be -1; its value is ", indic1
             DISPLAY "indic2 should be -1; its value is ", indic2
             if (ct  NOT  =   "Akron"  OR  ename  NOT  =   "Ed"then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1  OR  indic2  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 28 TO bu
             DISPLAY "FETCH C14824 INTO :ct, :ename, :pname:indic1,
      -    " :bu:indic2;"
      *  EXEC SQL FETCH C14824 INTO :ct, :ename, :pname:indic1,
      *  :bu:indic2;
             CALL "SUB51" USING SQLCODE SQLSTATE ct ename pname 
             indic1 bu indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ct should be Deale; its value is ", ct
             DISPLAY "ename should be Alice; its value is ", ename
             DISPLAY "pname should be SDP; its value is ", pname
             DISPLAY "bu should be 20000; its value is ", bu
             DISPLAY "indic1 should be 0; its value is ", indic1
             DISPLAY "indic2 should be 0; its value is ", indic2
             if (ct  NOT  =   "Deale"  OR  ename  NOT  =   "Alice"then
               MOVE 0 TO flag
             END-IF
             if (pname  NOT  =   "SDP"  OR  bu  NOT =  20000) then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  0  OR  indic2  NOT =  0) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 28 TO bu
             DISPLAY "FETCH C14824 INTO :ct, :ename, :pname:indic1,
      -    " :bu:indic2;"
      *  EXEC SQL FETCH C14824 INTO :ct, :ename, :pname:indic1,
      *  :bu:indic2;
             CALL "SUB52" USING SQLCODE SQLSTATE ct ename pname 
             indic1 bu indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ct should be Deale; its value is ", ct
             DISPLAY "ename should be Alice; its value is ", ename
             DISPLAY "pname should be PAYR; its value is ", pname
             DISPLAY "bu should be 50000; its value is ", bu
             DISPLAY "indic1 should be 0; its value is ", indic1
             DISPLAY "indic2 should be 0; its value is ", indic2
             if (ct  NOT  =   "Deale"  OR  ename  NOT  =   "Alice"then
               MOVE 0 TO flag
             END-IF
             if (pname  NOT  =   "PAYR"  OR  bu  NOT =  50000) then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  0  OR  indic2  NOT =  0) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 28 TO bu
             DISPLAY "FETCH C14824 INTO :ct, :ename, :pname:indic1,
      -    " :bu:indic2;"
      *  EXEC SQL FETCH C14824 INTO :ct, :ename, :pname:indic1,
      *  :bu:indic2;
             CALL "SUB53" USING SQLCODE SQLSTATE ct ename pname 
             indic1 bu indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ct should be Deale; its value is ", ct
             DISPLAY "ename should be Don; its value is ", ename
             DISPLAY "indic1 should be -1; its value is ", indic1
             DISPLAY "indic2 should be -1; its value is ", indic2
             if (ct  NOT  =   "Deale"  OR  ename  NOT  =   "Don"then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1  OR  indic2  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 28 TO bu
             DISPLAY "FETCH C14824 INTO :ct, :ename, :pname:indic1,
      -    " :bu:indic2;"
      *  EXEC SQL FETCH C14824 INTO :ct, :ename, :pname:indic1,
      *  :bu:indic2;
             CALL "SUB54" USING SQLCODE SQLSTATE ct ename 
             pname indic1 bu indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ct should be Vienna; its value is ", ct
             DISPLAY "ename should be Betty; its value is ", ename
             DISPLAY "indic1 should be -1; its value is ", indic1
             DISPLAY "indic2 should be -1; its value is ", indic2
             if (ct  NOT  =   "Vienna"  OR  ename  NOT  =   "Betty")
             then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1  OR  indic2  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 28 TO bu
             DISPLAY "FETCH C14824 INTO :ct, :ename, :pname:indic1,
      -    " :bu:indic2;"
      *  EXEC SQL FETCH C14824 INTO :ct, :ename, :pname:indic1,
      *  :bu:indic2;
             CALL "SUB55" USING SQLCODE SQLSTATE ct ename pname 
             indic1 bu indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ct should be Vienna; its value is ", ct
             DISPLAY "ename should be Carmen; its value is ", ename
             DISPLAY "indic1 should be -1; its value is ", indic1
             DISPLAY "indic2 should be -1; its value is ", indic2
             if (ct  NOT  =   "Vienna"  OR  ename  NOT  =   "Carmen")
             then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1  OR  indic2  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             DISPLAY "FETCH C14824 INTO :ct, :ename, :pname:indic1,
      -    " :bu:indic2;"
      *  EXEC SQL FETCH C14824 INTO :ct, :ename, :pname:indic1,
      *  :bu:indic2;
             CALL "SUB56" USING SQLCODE SQLSTATE ct ename pname 
             indic1 bu indic2
             MOVE SQLCODE TO SQL-COD
             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  " "

             DISPLAY "CLOSE C14824;"
      *  EXEC SQL CLOSE C14824;
             CALL "SUB57" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

      *Subtest number five 
      *Difference between WHERE and ON 

             DISPLAY "DECLARE C14825 CURSOR FOR"
             DISPLAY " SELECT HU.STAFF.CITY,EMPNAME,PNAME,BUDGET"
             DISPLAY " FROM HU.STAFF LEFT JOIN HU.PROJ"
             DISPLAY " ON HU.STAFF.CITY = HU.PROJ.CITY"
             DISPLAY " AND HU.STAFF.CITY <> 'Vienna'"
             DISPLAY " WHERE (BUDGET > 15000 OR BUDGET IS NULL)"
             DISPLAY " AND EMPNAME <> 'Don'"
             DISPLAY " ORDER BY HU.STAFF.CITY, EMPNAME, BUDGET;"
      *  EXEC SQL DECLARE C14825 CURSOR FOR
      *    SELECT HU.STAFF.CITY,EMPNAME,PNAME,BUDGET
      *    FROM HU.STAFF LEFT JOIN HU.PROJ
      *    ON HU.STAFF.CITY = HU.PROJ.CITY
      *    AND HU.STAFF.CITY <> 'Vienna'
      *    WHERE (BUDGET > 15000 OR BUDGET IS NULL)
      *    AND EMPNAME <> 'Don'
      *    ORDER BY HU.STAFF.CITY, EMPNAME, BUDGET END-EXEC

             DISPLAY "OPEN C14825;"
      *  EXEC SQL OPEN C14825;
             CALL "SUB58" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 28 TO bu
             DISPLAY "FETCH C14825 INTO :ct, :ename, :pname:indic1,
      -    " :bu:indic2;"
      *  EXEC SQL FETCH C14825 INTO :ct, :ename, :pname:indic1,
      *  :bu:indic2;
             CALL "SUB59" USING SQLCODE SQLSTATE ct ename pname 
             indic1 bu indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ct should be Akron; its value is ", ct
             DISPLAY "ename should be Ed; its value is ", ename
             DISPLAY "indic1 should be -1; its value is ", indic1
             DISPLAY "indic2 should be -1; its value is ", indic2
             if (ct  NOT  =   "Akron"  OR  ename  NOT  =   "Ed"then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1  OR  indic2  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 28 TO bu
             DISPLAY "FETCH C14825 INTO :ct, :ename, :pname:indic1,
      -    " :bu:indic2;"
      *  EXEC SQL FETCH C14825 INTO :ct, :ename, :pname:indic1,
      *  :bu:indic2;
             CALL "SUB60" USING SQLCODE SQLSTATE ct ename pname 
             indic1 bu indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ct should be Deale; its value is ", ct
             DISPLAY "ename should be Alice; its value is ", ename
             DISPLAY "pname should be SDP; its value is ", pname
             DISPLAY "bu should be 20000; its value is ", bu
             DISPLAY "indic1 should be 0; its value is ", indic1
             DISPLAY "indic2 should be 0; its value is ", indic2
             if (ct  NOT  =   "Deale"  OR  ename  NOT  =   "Alice"then
               MOVE 0 TO flag
             END-IF
             if (pname  NOT  =   "SDP"  OR  bu  NOT =  20000) then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  0  OR  indic2  NOT =  0) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 28 TO bu
             DISPLAY "FETCH C14825 INTO :ct, :ename, :pname:indic1,
      -    " :bu:indic2;"
      *  EXEC SQL FETCH C14825 INTO :ct, :ename, :pname:indic1,
      *  :bu:indic2;
             CALL "SUB61" USING SQLCODE SQLSTATE ct ename pname 
             indic1 bu indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ct should be Deale; its value is ", ct
             DISPLAY "ename should be Alice; its value is ", ename
             DISPLAY "pname should be PAYR; its value is ", pname
             DISPLAY "bu should be 50000; its value is ", bu
             DISPLAY "indic1 should be 0; its value is ", indic1
             DISPLAY "indic2 should be 0; its value is ", indic2
             if (ct  NOT  =   "Deale"  OR  ename  NOT  =   "Alice"then
               MOVE 0 TO flag
             END-IF
             if (pname  NOT  =   "PAYR"  OR  bu  NOT =  50000) then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  0  OR  indic2  NOT =  0) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 28 TO bu
             DISPLAY "FETCH C14825 INTO :ct, :ename, :pname:indic1,
      -    " :bu:indic2;"
      *  EXEC SQL FETCH C14825 INTO :ct, :ename, :pname:indic1,
      *  :bu:indic2;
             CALL "SUB62" USING SQLCODE SQLSTATE ct ename pname indic1 
             bu indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ct should be Vienna; its value is ", ct
             DISPLAY "ename should be Betty; its value is ", ename
             DISPLAY "indic1 should be -1; its value is ", indic1
             DISPLAY "indic2 should be -1; its value is ", indic2
             if (ct  NOT  =   "Vienna"  OR  ename  NOT  =   "Betty")
             then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1  OR  indic2  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             MOVE "xxxxxxxxxxxxxxxxxxxx" TO ename
             MOVE "xxxxxxxxxxxxxxxxxxxx" TO pname
             MOVE "xxxxxxxxxxxxxxx" TO ct
             MOVE 28 TO bu
             DISPLAY "FETCH C14825 INTO :ct, :ename, :pname:indic1,
      -    " :bu:indic2;"
      *  EXEC SQL FETCH C14825 INTO :ct, :ename, :pname:indic1,
      *  :bu:indic2;
             CALL "SUB63" USING SQLCODE SQLSTATE ct ename pname 
             indic1 bu indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "ct should be Vienna; its value is ", ct
             DISPLAY "ename should be Carmen; its value is ", ename
             DISPLAY "indic1 should be -1; its value is ", indic1
             DISPLAY "indic2 should be -1; its value is ", indic2
             if (ct  NOT  =   "Vienna"  OR  ename  NOT  =   "Carmen")
             then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1  OR  indic2  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             DISPLAY "FETCH C14825 INTO :ct, :ename, :pname:indic1,
      -    " :bu:indic2;"
      *  EXEC SQL FETCH C14825 INTO :ct, :ename, :pname:indic1,
      *  :bu:indic2;
             CALL "SUB64" USING SQLCODE SQLSTATE ct ename pname indic1 
             bu indic2
             MOVE SQLCODE TO SQL-COD
             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  " "

             DISPLAY "CLOSE C14825;"
      *  EXEC SQL CLOSE C14825;
             CALL "SUB65" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

      *Subtest number six 
      *Correlation name with self-JOIN 

             DISPLAY "DECLARE C14826 CURSOR FOR"
             DISPLAY " SELECT XX.T_INT, YY.T_INT"
             DISPLAY " FROM SEVEN_TYPES XX RIGHT OUTER JOIN SEVEN_TYPES
      -    " YY"
             DISPLAY " ON XX.T_INT = YY.T_INT +1"
             DISPLAY " ORDER BY YY.T_INT;"
      *  EXEC SQL DECLARE C14826 CURSOR FOR
      *    SELECT XX.T_INT, YY.T_INT
      *    FROM SEVEN_TYPES XX RIGHT OUTER JOIN SEVEN_TYPES YY
      *    ON XX.T_INT = YY.T_INT +1
      *    ORDER BY YY.T_INT END-EXEC

             DISPLAY "OPEN C14826;"
      *  EXEC SQL OPEN C14826;
             CALL "SUB66" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             MOVE 0 TO int1
             MOVE 40 TO indic1
             MOVE 0 TO int2
             DISPLAY "FETCH C14826 INTO :int1:indic1, :int2;"
      *  EXEC SQL FETCH C14826 INTO :int1:indic1, :int2;
             CALL "SUB67" USING SQLCODE SQLSTATE int1 indic1 int2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "int1 should be 2; its value is ", int1
             DISPLAY "indic1 should be 0; its value is ", indic1
             DISPLAY "int2 should be 1; its value is ", int2
             if (int1  NOT =  2  OR  indic1  NOT =  0) then
               MOVE 0 TO flag
             END-IF
             if (int2  NOT =  1) then
               MOVE 0 TO flag
             END-IF

             MOVE 0 TO int1
             MOVE 40 TO indic1
             MOVE 0 TO int2
             DISPLAY "FETCH C14826 INTO :int1:indic1, :int2;"
      *  EXEC SQL FETCH C14826 INTO :int1:indic1, :int2;
             CALL "SUB68" USING SQLCODE SQLSTATE int1 indic1 int2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "int1 should be 3; its value is ", int1
             DISPLAY "indic1 should be 0; its value is ", indic1
             DISPLAY "int2 should be 2; its value is ", int2
             if (int1  NOT =  3  OR  indic1  NOT =  0) then
               MOVE 0 TO flag
             END-IF
             if (int2  NOT =  2) then
               MOVE 0 TO flag
             END-IF

             MOVE 0 TO int1
             MOVE 40 TO indic1
             MOVE 0 TO int2
             DISPLAY "FETCH C14826 INTO :int1:indic1, :int2;"
      *  EXEC SQL FETCH C14826 INTO :int1:indic1, :int2;
             CALL "SUB69" USING SQLCODE SQLSTATE int1 indic1 int2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "indic1 should be -1; its value is ", indic1
             DISPLAY "int2 should be 3; its value is ", int2
             if (indic1  NOT =  -1  OR  int2  NOT =  3) then
               MOVE 0 TO flag
             END-IF

             DISPLAY "CLOSE C14826;"
      *  EXEC SQL CLOSE C14826;
             CALL "SUB70" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

      *Subtest number seven 
      *Nested booleans 
      *Data types are merely comparable 

             DISPLAY "DECLARE C14827 CURSOR FOR"
             DISPLAY " SELECT GRADE, T_NUMERIC, DECIMAL6_6"
             DISPLAY " FROM HU.STAFF LEFT JOIN SEVEN_TYPES T7"
             DISPLAY " ON GRADE * -40 > T7.T_NUMERIC"
             DISPLAY " OR (DECIMAL6_6 -542.5 < GRADE AND DECIMAL6_6
      -    " -541.5 > GRADE)"
             DISPLAY " ORDER BY GRADE;"
      *  EXEC SQL DECLARE C14827 CURSOR FOR
      *    SELECT GRADE, T_NUMERIC, DECIMAL6_6
      *    FROM HU.STAFF LEFT JOIN SEVEN_TYPES T7
      *    ON GRADE * -40 > T7.T_NUMERIC
      *    OR (DECIMAL6_6 -542.5 < GRADE
      *           AND DECIMAL6_6 -541.5 > GRADE)
      *    ORDER BY GRADE END-EXEC

             DISPLAY "OPEN C14827;"
      *  EXEC SQL OPEN C14827;
             CALL "SUB71" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             MOVE 0 TO gr
             MOVE 0.0 TO flt1
             MOVE 0.0 TO flt2
             MOVE 40 TO indic1
             MOVE 40 TO indic2
             DISPLAY "FETCH C14827 INTO :gr, :flt1:indic1,
      -    " :flt2:indic2;"
      *  EXEC SQL FETCH C14827 INTO :gr, :flt1:indic1, :flt2:indic2
      * ;
             CALL "SUB72" USING SQLCODE SQLSTATE gr flt1 indic1 
             flt2 indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "gr should be 10; its value is ", gr
             MOVE flt1 TO FLT-1
             DISPLAY "flt1 should be -444 +- 0.1; its value is ", FLT-1
             MOVE flt2 TO FLT-1
             DISPLAY "flt2 should be -55 +- 0.1; its value is ", FLT-1
             if (gr  NOT =  10) then
               MOVE 0 TO flag
             END-IF
             if (flt1  <  -444.1  OR  flt1  >  -443.9) then
               MOVE 0 TO flag
             END-IF
             if (flt2  <  -55.1  OR  flt2  >  -54.9) then
               MOVE 0 TO flag
             END-IF

             MOVE 0 TO gr
             MOVE 0.0 TO flt1
             MOVE 0.0 TO flt2
             MOVE 40 TO indic1
             MOVE 40 TO indic2
             DISPLAY "FETCH C14827 INTO :gr, :flt1:indic1,
      -    " :flt2:indic2;"
      *  EXEC SQL FETCH C14827 INTO :gr, :flt1:indic1, :flt2:indic2
      * ;
             CALL "SUB73" USING SQLCODE SQLSTATE gr flt1 indic1 
             flt2 indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "gr should be 12; its value is ", gr
             DISPLAY "indic1 should be -1; its value is ", indic1
             DISPLAY "indic2 should be -1; its value is ", indic2
             if (gr  NOT =  12) then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1  OR  indic2  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             MOVE 0 TO gr
             MOVE 0.0 TO flt1
             MOVE 0.0 TO flt2
             MOVE 40 TO indic1
             MOVE 40 TO indic2
             DISPLAY "FETCH C14827 INTO :gr, :flt1:indic1,
      -    " :flt2:indic2;"
      *  EXEC SQL FETCH C14827 INTO :gr, :flt1:indic1, :flt2:indic2
      * ;
             CALL "SUB74" USING SQLCODE SQLSTATE gr flt1 indic1 
             flt2 indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "gr should be 12; its value is ", gr
             DISPLAY "indic1 should be -1; its value is ", indic1
             DISPLAY "indic2 should be -1; its value is ", indic2
             if (gr  NOT =  12) then
               MOVE 0 TO flag
             END-IF
             if (indic1  NOT =  -1  OR  indic2  NOT =  -1) then
               MOVE 0 TO flag
             END-IF

             MOVE 0 TO gr
             MOVE 0.0 TO flt1
             MOVE 0.0 TO flt2
             MOVE 40 TO indic1
             MOVE 40 TO indic2
             DISPLAY "FETCH C14827 INTO :gr, :flt1:indic1,
      -    " :flt2:indic2;"
      *  EXEC SQL FETCH C14827 INTO :gr, :flt1:indic1, :flt2:indic2
      * ;
             CALL "SUB75" USING SQLCODE SQLSTATE gr flt1 indic1 
             flt2 indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "gr should be 13; its value is ", gr
             MOVE flt1 TO FLT-1
             DISPLAY "flt1 should be 44 +- 0.1; its value is ", FLT-1
             MOVE flt2 TO FLT-1
             DISPLAY "flt2 should be 555 +- 0.1; its value is ", FLT-1
             if (gr  NOT =  13) then
               MOVE 0 TO flag
             END-IF
             if (flt1  <  43.9  OR  flt1  >  44.1) then
               MOVE 0 TO flag
             END-IF
             if (flt2  <  554.9  OR  flt2  >  555.1) then
               MOVE 0 TO flag
             END-IF

             MOVE 0 TO gr
             MOVE 0.0 TO flt1
             MOVE 0.0 TO flt2
             MOVE 40 TO indic1
             MOVE 40 TO indic2
             DISPLAY "FETCH C14827 INTO :gr, :flt1:indic1,
      -    " :flt2:indic2;"
      *  EXEC SQL FETCH C14827 INTO :gr, :flt1:indic1, :flt2:indic2
      * ;
             CALL "SUB76" USING SQLCODE SQLSTATE gr flt1 indic1 
             flt2 indic2
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "gr should be 13; its value is ", gr
             MOVE flt1 TO FLT-1
             DISPLAY "flt1 should be 44 +- 0.1; its value is ", FLT-1
             MOVE flt2 TO FLT-1
             DISPLAY "flt2 should be 555 +- 0.1; its value is ", FLT-1
--> --------------------

--> maximum size reached

--> --------------------

¤ Dauer der Verarbeitung: 0.151 Sekunden  (vorverarbeitet)  ¤





vermutete Sprache:
Sekunden
vermutete Sprache:
sprechenden Kalenders

in der Quellcodebibliothek suchen




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.


Bot Zugriff