Quellcode-Bibliothek
© Kompilation durch diese Firma
[Weder Korrektheit noch Funktionsfähigkeit der Software werden zugesichert.]
Datei:
yts790.cob
Sprache: Cobol
|
|
IDENTIFICATION DIVISION.
PROGRAM-ID. XTS748.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. xyz.
OBJECT-COMPUTER. xyz.
DATA DIVISION.
WORKING-STORAGE SECTION.
* Standard COBOL (file "XTS748.SCO") calling SQL
* procedures in file "XTS748.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
*
* XTS748.SCO
* WRITTEN BY: Manolis Megaloikonomou
* TRANSLATED AUTOMATICALLY FROM EMBEDDED COBOL BY CHRIS SCHANZLE
*
* Named constraint in column definition in schema definition.
*
* REFERENCES
* 11.1 -- <schema definition>
* 11.3 -- <table definition>
* 11.4 -- <column definition>
* 11.4 SR.9
* 11.4 LR.2c -- Raised. Entry SQL restriction which
* prohibited the specification of
* <constraint name definition>.
* 10.6 -- <constraint name definition> and
* <constraint attributes>
* 10.6 SR.1
* 10.6 SR.2
* 10.6 LR.2a -- Raised. Entry SQL restriction which
* prohibited the specification of
* <constraint name definition>.
* 11.7 -- <unique constraint definition>
* 11.8 -- <referential constraint definition>
* 11.9 -- <check constraint definition>
* F#2 -- Basic information schema.
* F#1 -- Dynamic SQL.
* F#3 -- Basic schema manipulation.
* F#33 -- Constraint tables.
* F#31 -- Schema definition.
* F#49 -- Constraint management.
*
* DATE LAST ALTERED 18/12/95 CTS5 Hand-over Test
*
* Cleanups and fixes by V. Kogakis 08/12/95
* Print timestamp
* Include Files
* Define NOSUBCLASS/CHCKOK at test beginning
* Include host variable initialisation
* Clean-up database at the end of test
*
* QA STATUS :
*
* Revised by DWF 1996-02-15
* Cleanups
* Removed status checks after cursor definitions
* Fixed SDL transactions
* Make variable names 6 chars
* Removed field widths from printfs
* Initialized vars
****************************************************************
* EXEC SQL BEGIN DECLARE SECTION END-EXEC
01 SQLCODE PIC S9(9) COMP.
01 SQLSTATE PIC X(5).
01 uid PIC X(18).
01 uidx PIC X(18).
01 coun PIC S9(9) DISPLAY SIGN LEADING SEPARATE.
01 cname PIC X(29).
01 tname PIC X(29).
01 ctype PIC X(29).
01 longst PIC X(240).
* 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 "CTS1 " TO uid
CALL "AUTHID" USING uid
MOVE "not logged in, not" TO uidx
* EXEC SQL SELECT USER INTO :uidx FROM CTS1.ECCO;
CALL "SUB1" USING SQLCODE SQLSTATE uidx
MOVE SQLCODE TO SQL-COD
* EXEC SQL ROLLBACK WORK;
CALL "SUB2" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
if (uid NOT = uidx) then
DISPLAY "ERROR: User ", uid, " expected. User ", uidx, "
- " connected"
STOP RUN
END-IF
MOVE 0 TO errcnt
DISPLAY "SQL Test Suite, V6.0, Module COBOL, xts748.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 TEST7048 *******************
MOVE 1 TO flag
DISPLAY " TEST7048 "
DISPLAY " Named constraint in column definition in
- " schema definition."
DISPLAY " References:"
DISPLAY " 11.1 -- "
DISPLAY " 11.3 -- "
DISPLAY " 11.4 -- "
DISPLAY " 11.4 SR.9"
DISPLAY " 11.4 LR.2c -- Raised. Entry SQL restriction
- " which"
DISPLAY " prohibited the specification of"
DISPLAY " ."
DISPLAY " 10.6 -- and"
DISPLAY " "
DISPLAY " 10.6 SR.1"
DISPLAY " 10.6 SR.2"
DISPLAY " 10.6 LR.2a -- Raised. Entry SQL restriction
- " which"
DISPLAY " prohibited the specification of"
DISPLAY " ."
DISPLAY " 11.7 -- "
DISPLAY " 11.8 -- "
DISPLAY " 11.9 -- "
DISPLAY " F#2 -- Basic information schema."
DISPLAY " F#1 -- Dynamic SQL."
DISPLAY " F#3 -- Basic schema manipulation."
DISPLAY " F#33 -- Constraint tables."
DISPLAY " F#31 -- Schema definition."
DISPLAY " F#49 -- Constraint management."
DISPLAY " - - - - - - - - - - - - - - - - - - -"
*Create schema with one table definition
*Initialise error reporting variables
COMPUTE SQLCODE = -1
MOVE "xxxxx" TO SQLSTATE
DISPLAY "CREATE SCHEMA T12549PC"
DISPLAY "CREATE TABLE TEST12549"
DISPLAY "(TNUM1 NUMERIC(5)"
DISPLAY " CONSTRAINT CND12549A NOT NULL,"
DISPLAY " TNUM2 NUMERIC(5)"
DISPLAY " CONSTRAINT CND12549B UNIQUE,"
DISPLAY " TNUM3 NUMERIC(5)"
DISPLAY " CONSTRAINT CND12549C CHECK(TNUM3 > 0));"
* EXEC SQL CREATE SCHEMA T12549PC
* CREATE TABLE TEST12549
* (TNUM1 NUMERIC(5)
* CONSTRAINT CND12549A NOT NULL,
* TNUM2 NUMERIC(5)
* CONSTRAINT CND12549B UNIQUE,
* TNUM3 NUMERIC(5)
* CONSTRAINT CND12549C CHECK(TNUM3 > 0));
CALL "SUB3" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "COMMIT WORK;"
* EXEC SQL COMMIT WORK;
CALL "SUB4" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
COMPUTE coun = -1
DISPLAY "SELECT COUNT(*) INTO :coun "
DISPLAY "FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS"
DISPLAY "WHERE CONSTRAINT_SCHEMA = 'T12549PC' AND
- " TABLE_SCHEMA = 'T12549PC';"
* EXEC SQL SELECT COUNT(*) INTO :coun FROM
* INFORMATION_SCHEMA.TABLE_CONSTRAINTS
* WHERE CONSTRAINT_SCHEMA = 'T12549PC' AND TABLE_SCHEMA =
* 'T12549PC';
CALL "SUB5" USING SQLCODE SQLSTATE coun
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "Count should be 3; its value is ", coun
if ( coun NOT = 3 ) then
MOVE 0 TO flag
END-IF
DISPLAY " "
DISPLAY "DECLARE a CURSOR"
DISPLAY "FOR SELECT CONSTRAINT_NAME, TABLE_NAME,
- " CONSTRAINT_TYPE"
DISPLAY "FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS"
DISPLAY "WHERE CONSTRAINT_SCHEMA = 'T12549PC' AND
- " TABLE_SCHEMA = 'T12549PC'"
DISPLAY "ORDER BY CONSTRAINT_NAME;"
* EXEC SQL DECLARE a CURSOR
* FOR SELECT CONSTRAINT_NAME, TABLE_NAME, CONSTRAINT_TYPE
* FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS
* WHERE CONSTRAINT_SCHEMA = 'T12549PC' AND TABLE_SCHEMA =
* 'T12549PC'
* ORDER BY CONSTRAINT_NAME END-EXEC
DISPLAY "OPEN a;"
* EXEC SQL OPEN a;
CALL "SUB6" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*Initialise host variables
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO cname
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO tname
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO ctype
DISPLAY "FETCH a INTO :cname, :tname, :ctype;"
* EXEC SQL FETCH a INTO :cname, :tname, :ctype;
CALL "SUB7" USING SQLCODE SQLSTATE cname tname ctype
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "cname should be CND12549A; its value is ", cname
DISPLAY "tname should be TEST12549; its value is ", tname
DISPLAY "ctype should be CHECK; its value is ", ctype
if (cname NOT = "CND12549A" OR tname NOT =
"TEST12549" ) then
MOVE 0 TO flag
END-IF
if (ctype NOT = "CHECK") then
MOVE 0 TO flag
END-IF
DISPLAY " "
*Initialise host variables
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO cname
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO tname
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO ctype
DISPLAY "FETCH a INTO :cname, :tname, :ctype;"
* EXEC SQL FETCH a INTO :cname, :tname, :ctype;
CALL "SUB8" USING SQLCODE SQLSTATE cname tname ctype
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "cname should be CND12549B; its value is ", cname
DISPLAY "tname should be TEST12549; its value is ", tname
DISPLAY "ctype should be UNIQUE; its value is ", ctype
if (cname NOT = "CND12549B" OR tname NOT =
"TEST12549") then
MOVE 0 TO flag
END-IF
if (ctype NOT = "UNIQUE") then
MOVE 0 TO flag
END-IF
DISPLAY " "
*Initialise host variables
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO cname
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO tname
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO ctype
DISPLAY "FETCH a INTO :cname, :tname, :ctype;"
* EXEC SQL FETCH a INTO :cname, :tname, :ctype;
CALL "SUB9" USING SQLCODE SQLSTATE cname tname ctype
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "cname should be CND12549C; its value is ", cname
DISPLAY "tname should be TEST12549; its value is ", tname
DISPLAY "ctype should be CHECK; its value is ", ctype
if (cname NOT = "CND12549C" OR tname NOT =
"TEST12549") then
MOVE 0 TO flag
END-IF
if (ctype NOT = "CHECK") then
MOVE 0 TO flag
END-IF
DISPLAY " "
DISPLAY "CLOSE a;"
* EXEC SQL CLOSE a;
CALL "SUB10" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
* EXEC SQL DELETE FROM CONCATBUF;
CALL "SUB11" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
* EXEC SQL INSERT INTO CONCATBUF VALUES (
* 'CREATE SCHEMA DT12549PC CREATE TABLE TEST12549'
* ||
* ' (TNUM1 NUMERIC(5) CONSTRAINT CND12549D UNIQUE,'
* ||
* ' TNUM2 NUMERIC(5) CONSTRAINT CND12549E CHECK(TNUM2 >
* 1000),' ||
* ' TNUM3 NUMERIC(5) CONSTRAINT CND12549F NOT NULL)'
* );
CALL "SUB12" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
* EXEC SQL SELECT ZZ INTO :longst FROM CONCATBUF;
CALL "SUB13" USING SQLCODE SQLSTATE longst
MOVE SQLCODE TO SQL-COD
DISPLAY "longst=""", longst, """"
DISPLAY "COMMIT WORK;"
* EXEC SQL COMMIT WORK;
CALL "SUB14" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "EXECUTE IMMEDIATE :longst;"
* EXEC SQL EXECUTE IMMEDIATE :longst;
CALL "SUB15" USING SQLCODE SQLSTATE longst
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "COMMIT WORK;"
* EXEC SQL COMMIT WORK;
CALL "SUB16" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
COMPUTE coun = -1
DISPLAY "SELECT COUNT(*) INTO :coun "
DISPLAY "FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS"
DISPLAY "WHERE CONSTRAINT_SCHEMA = 'DT12549PC' "
DISPLAY "AND TABLE_SCHEMA = 'DT12549PC';"
* EXEC SQL SELECT COUNT(*) INTO :coun FROM
* INFORMATION_SCHEMA.TABLE_CONSTRAINTS
* WHERE CONSTRAINT_SCHEMA = 'DT12549PC' AND TABLE_SCHEMA =
* 'DT12549PC';
CALL "SUB17" USING SQLCODE SQLSTATE coun
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "Count should be 3; its value is ", coun
if ( coun NOT = 3 ) then
MOVE 0 TO flag
END-IF
DISPLAY " "
DISPLAY "DECLARE b CURSOR"
DISPLAY "FOR SELECT CONSTRAINT_NAME, TABLE_NAME,
- " CONSTRAINT_TYPE"
DISPLAY "FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS"
DISPLAY "WHERE CONSTRAINT_SCHEMA = 'DT12549PC'"
DISPLAY "AND TABLE_SCHEMA = 'DT12549PC'"
DISPLAY "ORDER BY CONSTRAINT_NAME;"
* EXEC SQL DECLARE b CURSOR
* FOR SELECT CONSTRAINT_NAME, TABLE_NAME, CONSTRAINT_TYPE
* FROM INFORMATION_SCHEMA.TABLE_CONSTRAINTS
* WHERE CONSTRAINT_SCHEMA = 'DT12549PC' AND TABLE_SCHEMA =
* 'DT12549PC'
* ORDER BY CONSTRAINT_NAME END-EXEC
DISPLAY "OPEN b;"
* EXEC SQL OPEN b;
CALL "SUB18" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*Initialise host variables
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO cname
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO tname
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO ctype
DISPLAY "FETCH b INTO :cname, :tname, :ctype;"
* EXEC SQL FETCH b INTO :cname, :tname, :ctype;
CALL "SUB19" USING SQLCODE SQLSTATE cname tname ctype
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "cname should be CND12549D; its value is ", cname
DISPLAY "tname should be TEST12549; its value is ", tname
DISPLAY "ctype should be UNIQUE; its value is ", ctype
if ( cname NOT = "CND12549D" OR tname NOT =
"TEST12549" ) then
MOVE 0 TO flag
END-IF
if ( ctype NOT = "UNIQUE") then
MOVE 0 TO flag
END-IF
DISPLAY " "
*Initialise host variables
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO cname
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO tname
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO ctype
DISPLAY "FETCH b INTO :cname, :tname, :ctype;"
* EXEC SQL FETCH b INTO :cname, :tname, :ctype;
CALL "SUB20" USING SQLCODE SQLSTATE cname tname ctype
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "cname should be CND12549E; its value is ", cname
DISPLAY "tname should be TEST12549; its value is ", tname
DISPLAY "ctype should be CHECK; its value is ", ctype
if (cname NOT = "CND12549E" OR tname NOT =
"TEST12549") then
MOVE 0 TO flag
END-IF
if (ctype NOT = "CHECK") then
MOVE 0 TO flag
END-IF
DISPLAY " "
*Initialise host variables
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO cname
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO tname
MOVE "xxxxxxxxxxxxxxxxxxxxxxxxxxxxx" TO ctype
DISPLAY "FETCH b INTO :cname, :tname, :ctype;"
* EXEC SQL FETCH b INTO :cname, :tname, :ctype;
CALL "SUB21" USING SQLCODE SQLSTATE cname tname ctype
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY "cname should be CND12549F; its value is ", cname
DISPLAY "tname should be TEST12549; its value is ", tname
DISPLAY "ctype should be CHECK; its value is ", ctype
if (cname NOT = "CND12549F" OR tname NOT =
"TEST12549") then
MOVE 0 TO flag
END-IF
if (ctype NOT = "CHECK") then
MOVE 0 TO flag
END-IF
DISPLAY " "
DISPLAY "CLOSE b;"
* EXEC SQL CLOSE b;
CALL "SUB22" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "ROLLBACK WORK;"
* EXEC SQL ROLLBACK WORK;
CALL "SUB23" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*Clean up database
DISPLAY "DROP SCHEMA T12549PC CASCADE;"
* EXEC SQL DROP SCHEMA T12549PC CASCADE;
CALL "SUB24" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "COMMIT WORK;"
* EXEC SQL COMMIT WORK;
CALL "SUB25" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "DROP SCHEMA DT12549PC CASCADE;"
* EXEC SQL DROP SCHEMA DT12549PC CASCADE;
CALL "SUB26" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
DISPLAY "COMMIT WORK;"
* EXEC SQL COMMIT WORK;
CALL "SUB27" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
PERFORM CHCKOK
DISPLAY " "
*Now record results
if ( flag = 1 ) then
DISPLAY " xts748.mco *** pass *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7048','pass','MCO');
CALL "SUB28" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
else
DISPLAY " xts748.mco *** fail *** "
* EXEC SQL INSERT INTO CTS1.TESTREPORT
* VALUES('7048','fail','MCO');
CALL "SUB29" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
COMPUTE errcnt = errcnt + 1
END-IF
DISPLAY "========================================"
* EXEC SQL COMMIT WORK;
CALL "SUB30" USING SQLCODE SQLSTATE
MOVE SQLCODE TO SQL-COD
******************** END TEST7048 ********************
**** 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.35 Sekunden
(vorverarbeitet)
¤
Haftungshinweis
Die Informationen auf dieser Webseite wurden
nach bestem Wissen sorgfältig zusammengestellt. Es wird jedoch weder Vollständigkeit, noch Richtigkeit,
noch Qualität der bereit gestellten Informationen zugesichert.
Bemerkung:
Die farbliche Syntaxdarstellung ist noch experimentell.
|
|
|