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

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


      * Standard COBOL (file "XTS724.SCO") calling SQL
      * procedures in file "XTS724.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                               
      *                                                              
      * XTS724.SCO                                                   
      * WRITTEN BY: Nickos Backalidis                                
      * TRANSLATED AUTOMATICALLY FROM EMBEDDED COBOL BY CHRIS SCHANZLE
      *                                                              
      * Access to COLUMN_DOMAIN_USAGE view                           
      *                                                              
      * REFERENCES                                                   
      *   21.2.25 -- COLUMN_DOMAIN_USAGE view                        
      *   11.21   -- <domain definition>                             
      *   11.27   -- <drop domain statement>                         
      *   F#25    -- Domain definition                               
      *   F#2     -- Basic information schema                        
      *   F#3     -- Basic schema manipulation                       
      *   F#34    -- Usage tables                                    
      *                                                              
      * DATE LAST ALTERED  14/12/95 CTS5 Hand-over Test              
      *                                                              
      * Cleanups and fixes by V. Kogakis 04/12/95:                   
      *      Respect length of strings in variable initialization.   
      *                                                              
      * QA Status: QA Check                                          
      *                                                              
      * Revised by DWF 1/30/96                                       
      *   Fixed SDL transactions                                     
      *   Fixed SQL syntax errors                                    
      *   Removed extraneous SQL syntax                              
      *   Removed status checks after cursor definition              
      *   Upcased information schema identifiers                     
      ****************************************************************



      * 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  counok PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
       01  domsch PIC  X(128).
       01  colnam PIC  X(128).
       01  tabnam PIC  X(128).
      *  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.
       01  i PIC S9(4) 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 "CTS4 " 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, xts724.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 TEST7024 *******************
             MOVE 1 TO flag
             DISPLAY " TEST7024"
             DISPLAY " Access to COLUMN_DOMAIN_USAGE view "
             DISPLAY " References "
             DISPLAY " 21.2.25 -- COLUMN_DOMAIN_USAGE view"
             DISPLAY " 11.21 -- "
             DISPLAY " 11.27 -- "
             DISPLAY " F#25 -- Domain definition "
             DISPLAY " F#2 -- Basic information schema "
             DISPLAY " F#3 -- Basic schema manipulation "
             DISPLAY " F#34 -- Usage tables "
             DISPLAY " - - - - - - - - - - - - - - - - - - -"

      *initialise error reporting variables 
             COMPUTE SQLCODE = -1
             MOVE "xxxxx" TO SQLSTATE

      *initialise host variable 
      *we expect a zero so initialise it to a value <> 0 
             MOVE 9 TO counok

      *Access the COLUMN_DOMAIN_USAGE view 
             DISPLAY "SELECT COUNT(*) INTO :counok"
             DISPLAY "FROM INFORMATION_SCHEMA.COLUMN_DOMAIN_USAGE"
             DISPLAY "WHERE DOMAIN_SCHEMA = 'CTS4';"
      *  EXEC SQL SELECT COUNT(*) INTO :counok
      *    FROM INFORMATION_SCHEMA.COLUMN_DOMAIN_USAGE
      *    WHERE DOMAIN_SCHEMA = 'CTS4';
             CALL "SUB3" USING SQLCODE SQLSTATE counok
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "counok should be 0; its value is : ", counok
             if (counok  NOT =  0) then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

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

      *Now create a domain under the current schema 
             DISPLAY "CREATE DOMAIN TESTDOM AS NUMERIC(5)"
             DISPLAY "CONSTRAINT CONSD724 CHECK (VALUE > 500);"
      *  EXEC SQL CREATE DOMAIN TESTDOM AS NUMERIC(5)
      *    CONSTRAINT CONSD724 CHECK (VALUE > 500);
             CALL "SUB5" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

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

             DISPLAY "CREATE TABLE TAB724a"
             DISPLAY " (COLNUM1 TESTDOM,"
             DISPLAY " COLNUM2 TESTDOM,"
             DISPLAY " COLNUM3 TESTDOM,"
             DISPLAY " COLNUM4 TESTDOM);"
      *  EXEC SQL CREATE TABLE TAB724a 
      *    (COLNUM1 TESTDOM,
      *    COLNUM2 TESTDOM,
      *    COLNUM3 TESTDOM,
      *    COLNUM4 TESTDOM);
             CALL "SUB7" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

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

      *Current contents of COLUMN_DOMAIN_USAGE: 
      *TESTDOM TAB724A.COLNUM1 
      *TESTDOM TAB724A.COLNUM2 
      *TESTDOM TAB724A.COLNUM3 
      *TESTDOM TAB724A.COLNUM4 

      *now access the COLUMN_DOMAIN_USAGE view and check that
      *the columns of TAB724a are visible 

             DISPLAY "DECLARE ALPHA CURSOR FOR SELECT
      -    " DOMAIN_SCHEMA,COLUMN_NAME,"
             DISPLAY "TABLE_NAME FROM
      -    " INFORMATION_SCHEMA.COLUMN_DOMAIN_USAGE"
             DISPLAY "WHERE DOMAIN_NAME = 'TESTDOM'"
             DISPLAY "ORDER BY COLUMN_NAME;"
      *  EXEC SQL DECLARE ALPHA CURSOR
      *    FOR SELECT DOMAIN_SCHEMA,COLUMN_NAME, TABLE_NAME
      *    FROM INFORMATION_SCHEMA.COLUMN_DOMAIN_USAGE
      *    WHERE DOMAIN_NAME = 'TESTDOM'
      *    ORDER BY COLUMN_NAME END-EXEC

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

      *initialise host variables 
             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO colnam

             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO tabnam

             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO domsch

      *four rows should be returned by the cursor 
      *fetch first row 
             DISPLAY "FETCH ALPHA INTO :domsch,:colnam,:tabnam;"
      *  EXEC SQL FETCH ALPHA INTO :domsch,:colnam,:tabnam;
             CALL "SUB10" USING SQLCODE SQLSTATE domsch colnam tabnam
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "DOMAIN_SCHEMA should be CTS4; it is ", domsch
             DISPLAY "COLUMN_NAME should be COLNUM1; it is ", colnam
             DISPLAY "TABLE_NAME should be TAB724A; it is ", tabnam
             if (domsch  NOT  =   "CTS4"  OR  colnam  NOT  =  
             "COLNUM1"then
               MOVE 0 TO flag
             END-IF
             if (tabnam  NOT  =   "TAB724A"then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

      *re-initialise host variables 
             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO colnam

             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO tabnam

             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO domsch

      *fetch the second row 
             DISPLAY "FETCH ALPHA INTO :domsch,:colnam,:tabnam;"
      *  EXEC SQL FETCH ALPHA INTO :domsch,:colnam,:tabnam;
             CALL "SUB11" USING SQLCODE SQLSTATE domsch colnam tabnam
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "DOMAIN_SCHEMA should be CTS4; it is ", domsch
             DISPLAY "COLUMN_NAME should be COLNUM2; it is ", colnam
             DISPLAY "TABLE_NAME should be TAB724A; it is ", tabnam
             if (domsch  NOT  =   "CTS4"  OR  colnam  NOT  =  
             "COLNUM2"then
               MOVE 0 TO flag
             END-IF
             if (tabnam  NOT  =   "TAB724A"then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

      *re-initialise host variables 
             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO colnam

             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO tabnam

             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO domsch

      *fetch third row 
             DISPLAY "FETCH ALPHA INTO :domsch,:colnam,:tabnam;"
      *  EXEC SQL FETCH ALPHA INTO :domsch,:colnam,:tabnam;
             CALL "SUB12" USING SQLCODE SQLSTATE domsch colnam tabnam
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "DOMAIN_SCHEMA should be CTS4; it is ", domsch
             DISPLAY "COLUMN_NAME should be COLNUM3; it is ", colnam
             DISPLAY "TABLE_NAME should be TAB724A; it is ", tabnam
             if (domsch  NOT  =   "CTS4"  OR  colnam  NOT  =  
             "COLNUM3"then
               MOVE 0 TO flag
             END-IF
             if (tabnam  NOT  =   "TAB724A"then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

      *re-initialise host variables 
             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO colnam

             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO tabnam

             MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxxx
      -      "xxxxxxxx" TO domsch

      *fetch fourth and final row 
             DISPLAY "FETCH ALPHA INTO :domsch,:colnam,:tabnam;"
      *  EXEC SQL FETCH ALPHA INTO :domsch,:colnam,:tabnam;
             CALL "SUB13" USING SQLCODE SQLSTATE domsch colnam tabnam
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "DOMAIN_SCHEMA should be CTS4; it is ", domsch
             DISPLAY "COLUMN_NAME should be COLNUM4; it is ", colnam
             DISPLAY "TABLE_NAME should be TAB724A; it is ", tabnam
             if (domsch  NOT  =   "CTS4"  OR  colnam  NOT  =  
             "COLNUM4"then
               MOVE 0 TO flag
             END-IF
             if (tabnam  NOT  =   "TAB724A"then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

      *close the cursor 
             DISPLAY "CLOSE ALPHA;"
      *  EXEC SQL CLOSE ALPHA;
             CALL "SUB14" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

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

      *now drop the created domain 
             DISPLAY "DROP DOMAIN TESTDOM CASCADE;"
      *  EXEC SQL DROP DOMAIN TESTDOM CASCADE;
             CALL "SUB16" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY  " "

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

      *now drop the created table 
             DISPLAY "DROP TABLE TAB724a CASCADE;"
      *  EXEC SQL DROP TABLE TAB724a CASCADE;
             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  " "

      *Now access the COLUMN_DOMAIN_USAGE_VIEW 
      *and check that there exist no references 
      *to the above <schema elements> 
      *First initialise host variable 
      *we expect a zero so initialise it to a value <> 0 
             MOVE 9 TO counok
             DISPLAY "SELECT COUNT(*) INTO :counok"
             DISPLAY " FROM INFORMATION_SCHEMA.COLUMN_DOMAIN_USAGE"
             DISPLAY " WHERE DOMAIN_SCHEMA = 'CTS4';"
      *  EXEC SQL SELECT COUNT(*) INTO :counok
      *    FROM INFORMATION_SCHEMA.COLUMN_DOMAIN_USAGE
      *    WHERE DOMAIN_SCHEMA = 'CTS4';
             CALL "SUB20" USING SQLCODE SQLSTATE counok
             MOVE SQLCODE TO SQL-COD
           PERFORM CHCKOK
             DISPLAY "counok should be 0; its value is : ", counok
             if (counok  NOT =  0) then
               MOVE 0 TO flag
             END-IF
             DISPLAY  " "

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

      *record results 

             if ( flag  =  1 ) then
               DISPLAY " xts724.mco *** pass *** "
      *    EXEC SQL INSERT INTO CTS1.TESTREPORT
      *      VALUES('7024','pass','MCO');
               CALL "SUB22" USING SQLCODE SQLSTATE
               MOVE SQLCODE TO SQL-COD
             else
               DISPLAY " xts724.mco *** fail *** "
      *    EXEC SQL INSERT INTO CTS1.TESTREPORT
      *      VALUES('7024','fail','MCO');
               CALL "SUB23" USING SQLCODE SQLSTATE
               MOVE SQLCODE TO SQL-COD
               COMPUTE errcnt = errcnt + 1
             END-IF

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

      *  EXEC SQL COMMIT WORK;
             CALL "SUB24" USING SQLCODE SQLSTATE
             MOVE SQLCODE TO SQL-COD
      ******************** END TEST7024 ********************

      **** 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.29 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