Anforderungen  |   Konzepte  |   Entwurf  |   Entwicklung  |   Qualitätssicherung  |   Lebenszyklus  |   Steuerung
 
 
 
 


Quellcode-Bibliothek

© Kompilation durch diese Firma

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

Datei: yts788.cob   Sprache: Cobol

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

      * EMBEDDED COBOL (file "COB006.PCO")

      **************************************************************
      *
      *                  COMMENT SECTION
      *
      * DATE  1988/09/14 EMBEDDED 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.
      *  
      *  COB006.PCO
      *  WRITTEN BY: S Hurwitz
      *
      *  This routine tests how the SQL language handles
      *  the placement of comments within SQL statements.
      *
      * 
      *  REFERENCES
      *         AMERICAN NATIONAL STANDARD database language - SQL
      *                   X3.135-1989
      *         SECTION ANNEX A. <embedded SQL host program>
      *                 Snytax Rule 3.
      ***************************************************************

            EXEC SQL BEGIN DECLARE SECTION END-EXEC.
       01  OUT132      pic  x(132).
       01  uid PIC X(18).
       01  uidx PIC X(18).
            EXEC SQL END DECLARE SECTION END-EXEC
       01  SQLCODE PIC S9(9) COMP.
       01  errcnt PIC S9(4) DISPLAY SIGN LEADING SEPARATE.
  
       01  TT132      pic  x(132) value  is "TEST0207 TESTS SQL WITH COM
      -               "MENTS INTERSPERSED".

      * date_time declaration *
       01  TO-DAY PIC 9(6).
       01  THE-TIME PIC 9(8).
    
       PROCEDURE DIVISION.
       P0.

      *log into database
           move "HU" to uid.
           CALL "AUTHID" USING uid.
           MOVE "not logged in, not" TO uidx
           EXEC SQL SELECT 
                 USER INTO :uidx FROM HU.ECCO END-EXEC
           if (uid NOT = uidx) then
             DISPLAY "ERROR: User " uid " expected."
             DISPLAY "User " uidx " connected."
             DISPLAY " "
             STOP RUN
           END-IF

           MOVE 0 TO errcnt
           DISPLAY
           "SQL Test Suite, V6.0, Embedded COBOL, cob006.pco"
           DISPLAY " "
           DISPLAY
           "59-byte ID"
           DISPLAY "TEd Version #"
           DISPLAY " "
      * date_time print *
           ACCEPT TO-DAY FROM DATE
           ACCEPT THE-TIME FROM TIME
           DISPLAY "Date run YYMMDD: " TO-DAY " at hhmmssff: " THE-TIME
 
      ******************** BEGIN TEST0207 ********************
             display " ".
             display " TEST0207 ".
             display " **** Testing SQL with comments interspersed.".
             display " **** Reference: Annex A. Syntax Rule 3).".
             display " - - - - - - - - - - - - - - - - - - - - - "
             display " ".

             EXEC SQL DELETE
      *********** comment comment comment *****************
             FROM TEXT132
      *********** comment comment comment *****************
             END-EXEC.
  
             EXEC SQL INSERT
      ************ comment comment comment *******************
                  INTO TEXT132
      *********** This is a test for the rules ****************
             VALUES ('TEST0207 TESTS SQL WITH COMMENTS INTERSPERSED')
      *********** of SQL statements and comments ***********
             END-EXEC.
      *********** interspersed in the SQL language. ***********

             EXEC SQL SELECT
      *********** comment comment comment *********************
                 TEXXT INTO :OUT132 FROM TEXT132
      *********** comment comment comment *********************
             END-EXEC.
 
             display " OUT132= " OUT132.
 
            EXEC SQL ROLLBACK WORK END-EXEC.

           if OUT132 = TT132
           display " "

           display " *** pass *** "
           display " "
           display "================================================"

           EXEC SQL INSERT INTO TESTREPORT
               VALUES('0207','pass','PCO'END-EXEC
           else
            display " "
            display " cob006.pco *** fail *** "
            display " "
            display "=============================================="
           EXEC SQL INSERT INTO TESTREPORT
               VALUES ('0207','fail','PCO'END-EXEC
             ADD 1 TO errcnt
           END-IF
    
           EXEC SQL COMMIT WORK END-EXEC.
 
      ******************** END TEST0207 ********************* 
      ********************************************************
      **** TESTER MAY CHOOSE TO INSERT CODE FOR errcnt > 0
            STOP RUN
      *********************************************************

¤ Diese beiden folgenden Angebotsgruppen bietet das Unternehmen0.19Angebot  Wie Sie bei der Firma Beratungs- und Dienstleistungen beauftragen können  ¤





Druckansicht
unsichere Verbindung
Druckansicht
Hier finden Sie eine Liste der Produkte des Unternehmens

Mittel




Lebenszyklus

Die hierunter aufgelisteten Ziele sind für diese Firma wichtig


Ziele

Entwicklung einer Software für die statische Quellcodeanalyse


Bot Zugriff



                                                                                                                                                                                                                                                                                                                                                                                                     


Neuigkeiten

     Aktuelles
     Motto des Tages

Software

     Produkte
     Quellcodebibliothek

Aktivitäten

     Artikel über Sicherheit
     Anleitung zur Aktivierung von SSL

Muße

     Gedichte
     Musik
     Bilder

Jenseits des Üblichen ....
    

Besucherstatistik

Besucherstatistik