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: dml175.cob   Sprache: Cobol

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


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


      ****************************************************************
      *                                                              
      *                 COMMENT SECTION                              
      *                                                              
      * DATE 1996-05-14 Module COBOL LANGUAGE                          
      * SQL VALIDATION TEST SUITE V6.0                          
      *  DISCLAIMER:                                                  
      *  This program was written by employees of NIST to test SQL    
      *  implementations for conformance to the SQL standards.        
      *  NIST assumes no responsibility for any party's use of        
      *  this program.
      *                                                              
      * DML175.SCO                                                    
      * WRITTEN BY:  David Flater                                    
      * TRANSLATED AUTOMATICALLY FROM EMBEDDED COBOL BY CHRIS SCHANZLE
      *                                                              
      * This routine tests Intermediate SQL.                         
      *                                                              
      * REFERENCES                                                   
      *   FIPS PUB 127-2 14.2 Intermediate SQL                       
      *   ANSI SQL-1992                                              
      *                                                              
      ****************************************************************




      * EXEC SQL BEGIN DECLARE SECTION END-EXEC
       01  SQLCODE PIC S9(9) COMP.
       01  SQLSTATE PIC  X(5).
       01  uid PIC  X(18).
       01  uidx PIC  X(18).
       01  int1 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
      *  EXEC SQL END DECLARE SECTION END-EXEC
       01  norm1 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
       01  norm2 PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
       01  ALPNUM-TABLE VALUE IS
               "01234ABCDEFGH56789IJKLMNOPQRSTUVWXYZ".
           05  ALPNUM PIC X OCCURS 36 TIMES.
       01  NORMSQ.
           05  NORMSQX PIC X OCCURS 5 TIMES.
       01  errcnt PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
      *date_time declaration 
       01  TO-DAY PIC 9(6).
       01  THE-TIME PIC 9(8).
       01  flag PIC S9(9) DISPLAY SIGN LEADING SEPARATE.

       01  SQL-COD PIC S9(9) DISPLAY SIGN LEADING SEPARATE.

       PROCEDURE DIVISION.
       P0.

             MOVE "FLATER " TO uid
             CALL "AUTHID" USING uid
             MOVE "not logged in, not" TO uidx
      *  EXEC SQL SELECT USER INTO :uidx FROM HU.ECCO;
             CALL "SUB1" USING SQLCODE SQLSTATE uidx
             MOVE SQLCODE TO SQL-COD
      *  EXEC SQL ROLLBACK WORK;
             CALL "SUB2" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
             if (uid  NOT  =   uidx) then
               DISPLAY "ERROR: User ", uid, " expected. User ", uidx, "
      -    " connected"
            STOP RUN
             END-IF
             MOVE 0 TO errcnt

             DISPLAY
           "SQL Test Suite, V6.0, Module COBOL, dml175.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 TEST0887 *******************
             MOVE 1 TO flag

             DISPLAY " FIPS sizing TEST0887"
             DISPLAY " FIPS sizing, NCHAR (500)"
             DISPLAY "References:"
             DISPLAY " FIPS 16.6 -- Sizing #6, NATIONAL CHARACTER max
      -    " length"
             DISPLAY " - - - - - - - - - - - - - - - - - - -"

             COMPUTE SQLCODE = -1
             MOVE "xxxxx" TO SQLSTATE

             DISPLAY "CREATE TABLE CONTACTS ("
             DISPLAY " NAME CHAR (20),"
             DISPLAY " DESCRIPTION NCHAR (500),"
             DISPLAY " KEYWORDS NCHAR (500));"
      *  EXEC SQL CREATE TABLE CONTACTS (
      *    NAME CHAR (20),
      *    DESCRIPTION NCHAR (500),
      *    KEYWORDS NCHAR (500));
             CALL "SUB3" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD

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

             DISPLAY "INSERT INTO CONTACTS VALUES ('Harry',"
             DISPLAY "N'Harry works in the Redundancy Automation
      -    " Division of the '"
             DISPLAY "'Materials '"
             DISPLAY "'Blasting Laboratory in the National Cattle
      -    " Acceleration '"
             DISPLAY "'Project of '"
             DISPLAY "'lower Michigan. His job is to document the
      -    " trajectory of '"
             DISPLAY "'cattle and '"
             DISPLAY "'correlate the loft and acceleration versus the
      -    " quality of '"
             DISPLAY "'materials '"
             DISPLAY "'used in the trebuchet. He served ten years as
      -    " the '"
             DISPLAY "'vice-president in '"
             DISPLAY "'charge of marketing in the now defunct milk trust
      -    " of the '"
             DISPLAY "'Pennsylvania '"
             DISPLAY "'Coalition of All Things Bovine. Prior to that he
      -    " '"
             DISPLAY "'established himself '"
             DISPLAY "'as a world-class gra',"
             DISPLAY "N'aardvark albatross nutmeg redundancy '"
             DISPLAY "'automation materials blasting '"
             DISPLAY "'cattle acceleration trebuchet catapult '"
             DISPLAY "'loft coffee java sendmail SMTP '"
             DISPLAY "'FTP HTTP censorship expletive senility '"
             DISPLAY "'extortion distortion conformity '"
             DISPLAY "'conformance nachos chicks goslings '"
             DISPLAY "'ducklings honk quack melatonin tie '"
             DISPLAY "'noose circulation column default '"
             DISPLAY "'ionic doric chlorine guanine Guam '"
             DISPLAY "'invasions rubicon helmet plastics '"
             DISPLAY "'recycle HDPE nylon ceramics plumbing '"
             DISPLAY "'parachute zeppelin carbon hydrogen '"
             DISPLAY "'vinegar sludge asphalt adhesives '"
             DISPLAY "'tensile magnetic');"
      *  EXEC SQL INSERT INTO CONTACTS VALUES ('Harry',
      *    N'Harry works in the Redundancy Automation Division '
      *    'of the Materials '
      *    'Blasting Laboratory in the National Cattle '
      *    'acceleration Project of '
      *    'lower Michigan.  His job is to document the '
      *    'trajectory of '
      *    'cattle and '
      *    'correlate the loft and acceleration versus the '
      *    'quality of materials '
      *    'used in the trebuchet.  He served ten years as '
      *    'the vice-president in '
      *    'charge of marketing in the now defunct milk '
      *    'trust of the Pennsylvania '
      *    'Coalition of All Things Bovine.  Prior to that '
      *    'he established himself as a world-class gra',
      *    N'aardvark albatross nutmeg redundancy '
      *    'automation materials blasting '
      *    'cattle acceleration trebuchet catapult '
      *    'loft coffee java sendmail SMTP '
      *    'FTP HTTP censorship expletive senility '
      *    'extortion distortion conformity '
      *    'conformance nachos chicks goslings '
      *    'ducklings honk quack melatonin tie '
      *    'noose circulation column default '
      *    'ionic doric chlorine guanine Guam '
      *    'invasions rubicon helmet plastics '
      *    'recycle HDPE nylon ceramics plumbing '
      *    'parachute zeppelin carbon hydrogen '
      *    'vinegar sludge asphalt adhesives '
      *    'tensile magnetic');
             CALL "SUB5" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

             MOVE 0 TO int1
      *  EXEC SQL SELECT COUNT(*) INTO :int1
      *    FROM CONTACTS
      *    WHERE DESCRIPTION =
      *    N'Harry works in the Redundancy Automation Division '
      *    'of the Materials ' ||
      *    'Blasting Laboratory in the National Cattle '
      *    'acceleration Project of ' ||
      *    'lower Michigan.  His job is to document the '|| 
      *    'trajectory of cattle and ' ||
      *    'correlate the loft and acceleration versus the '
      *    'quality of materials ' ||
      *    'used in the trebuchet.  He served ten years as ' ||
      *    'the vice-president in ' ||
      *    'charge of marketing in the now defunct milk '||
      *    'trust of the Pennsylvania ' ||
      *    'Coalition of All Things Bovine.  Prior to that ' ||
      *    'he established himself ' ||
      *    'as a world-class gra'
      *    AND KEYWORDS =
      *    N'aardvark albatross nutmeg redundancy ' ||
      *    'automation materials blasting ' ||
      *    'cattle acceleration trebuchet catapult ' ||
      *    'loft coffee java sendmail SMTP ' ||
      *    'FTP HTTP censorship expletive senility ' ||
      *    'extortion distortion conformity ' ||
      *    'conformance nachos chicks goslings ' ||
      *    'ducklings honk quack melatonin tie ' ||
      *    'noose circulation column default ' ||
      *    'ionic doric chlorine guanine Guam ' ||
      *    'invasions rubicon helmet plastics ' ||
      *    'recycle HDPE nylon ceramics plumbing ' ||
      *    'parachute zeppelin carbon hydrogen ' ||
      *    'vinegar sludge asphalt adhesives ' ||
      *    'tensile magnetic'
      *   ;
             CALL "SUB6" USING SQLCODE SQLSTATE int1
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "int1 should be 1; its value is ", int1
             if (int1  NOT =  1) then
               MOVE 0 TO flag
             END-IF

             MOVE 99 TO int1
             DISPLAY "SELECT COUNT(*) INTO :int1"
             DISPLAY " FROM CONTACTS"
             DISPLAY " WHERE DESCRIPTION LIKE N'%gra'"
             DISPLAY " AND KEYWORDS LIKE N'%magnetic';"
      *  EXEC SQL SELECT COUNT(*) INTO :int1
      *    FROM CONTACTS
      *    WHERE DESCRIPTION LIKE N'%gra'
      *    AND KEYWORDS LIKE N'%magnetic';
             CALL "SUB7" USING SQLCODE SQLSTATE int1
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "int1 should be 1; its value is ", int1
             if (int1  NOT =  1) then
               MOVE 0 TO flag
             END-IF

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

             DISPLAY "DROP TABLE CONTACTS CASCADE;"
      *  EXEC SQL DROP TABLE CONTACTS CASCADE;
             CALL "SUB9" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

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

             if ( flag  =  1 ) then
               DISPLAY " *** pass *** "
      *    EXEC SQL INSERT INTO HU.TESTREPORT
      *      VALUES('0887','pass','MCO');
               CALL "SUB11" USING SQLCODE SQLSTATE
               MOVE SQLCODE TO SQL-COD
             else
               DISPLAY " dml175.mco *** fail *** "
      *    EXEC SQL INSERT INTO HU.TESTREPORT
      *      VALUES('0887','fail','MCO');
               CALL "SUB12" USING SQLCODE SQLSTATE
               MOVE SQLCODE TO SQL-COD
               COMPUTE errcnt = errcnt + 1
             END-IF

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

      *  EXEC SQL COMMIT WORK;
             CALL "SUB13" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
      ******************** END TEST0887 ********************
      **** 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.36 Sekunden  (vorverarbeitet)  ¤





Download des
Quellennavigators
Download des
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