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


Quellcode-Bibliothek

© Kompilation durch diese Firma

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

Datei: tt   Sprache: Cobol

Original von: verschiedene©

      ***********************************************************************
      ** Licensed Materials - Property of IBM
      **
      ** Governed under the terms of the International
      ** License Agreement for Non-Warranted Sample Code.
      **
      ** (C) COPYRIGHT International Business Machines Corp. 1995 - 2002
      ** All Rights Reserved.
      **
      ** US Government Users Restricted Rights - Use, duplication or
      ** disclosure restricted by GSA ADP Schedule Contract with IBM Corp.
      ***********************************************************************
      **
      ** SOURCE FILE NAME: dynamic.sqb
      **
      ** SAMPLE: How to update table data with cursor dynamically
      **
      **         This sample shows how to update table data with cursor
      **         using dynamic SQL statement.  This program shows how
      **         to retrieve all the entries in the system table
      **         sysibm.systables that do not have the value "STAFF" in
      **         the "name" column.
      **
      ** SQL STATEMENTS USED:
      **         BEGIN DECLARE SECTION
      **         END DECLARE SECTION
      **         CONNECT
      **         DECLARE
      **         PREPARE
      **         FETCH
      **         OPEN
      **
      ** OUTPUT FILE: dynamic.out (available in the online documentation)
      ***********************************************************************
      **
      ** For more information on the sample programs, see the README file.
      **
      ** For information on developing COBOL applications, see the
      ** Application Development Guide.
      **
      ** For information on using SQL statements, see the SQL Reference.
      **
      ** For the latest information on programming, compiling, and running
      ** DB2 applications, visit the DB2 application development website:
      **     http://www.software.ibm.com/data/db2/udb/ad
      ***********************************************************************

       Identification Division.
       Program-ID"dynamic".

       Data Division.
       Working-Storage Section.

           copy "sqlenv.cbl".
           copy "sql.cbl".
           copy "sqlca.cbl".

           EXEC SQL BEGIN DECLARE SECTION END-EXEC.
       01 table-name      pic x(20).
       01 st              pic x(80).                                    
       01 parm-var        pic x(18).
       01 userid            pic x(8).
       01 passwd.
         49 passwd-length   pic s9(4) comp-5 value 0.
         49 passwd-name     pic x(18).
           EXEC SQL END DECLARE SECTION END-EXEC.

       77 errloc          pic x(80).

       Procedure Division.
       Main Section.
           display "Sample COBOL program: DYNAMIC".

           display "Enter your user id (default none): "
                with no advancing.
           accept userid.

           if userid = spaces
             EXEC SQL CONNECT TO sample END-EXEC
           else
             display "Enter your password : " with no advancing
             accept passwd-name.

      * Passwords in a CONNECT statement must be entered in a VARCHAR format
      * with the length of the input string.
           inspect passwd-name tallying passwd-length for characters
              before initial " ".

           EXEC SQL CONNECT TO sample USER :userid USING :passwd
               END-EXEC.
           move "CONNECT TO" to errloc.
           call "checkerr" using SQLCA errloc.

           move "SELECT TABNAME FROM SYSCAT.TABLES
      -       " ORDER BY 1
      -       " WHERE TABNAME <> ?" to st.
           EXEC SQL PREPARE s1 FROM :st END-EXEC.                       
           move "PREPARE" to errloc.
           call "checkerr" using SQLCA errloc.

           EXEC SQL DECLARE c1 CURSOR FOR s1 END-EXEC.                  

           move "STAFF" to parm-var.
           EXEC SQL OPEN c1 USING :parm-var END-EXEC.                   
           move "OPEN" to errloc.
           call "checkerr" using SQLCA errloc.

           perform Fetch-Loop thru End-Fetch-Loop
              until SQLCODE not equal 0.

           EXEC SQL CLOSE c1 END-EXEC.                                  
           move "CLOSE" to errloc.
           call "checkerr" using SQLCA errloc.

           EXEC SQL COMMIT END-EXEC.
           move "COMMIT" to errloc.
           call "checkerr" using SQLCA errloc.

           EXEC SQL CONNECT RESET END-EXEC.
           move "CONNECT RESET" to errloc.
           call "checkerr" using SQLCA errloc.

       End-Main.
           go to End-Prog.

       Fetch-Loop Section.
           EXEC SQL FETCH c1 INTO :table-name END-EXEC.                 
           if SQLCODE not equal 0
              go to End-Fetch-Loop.
           display "TABLE = ", table-name.
       End-Fetch-Loop. exit.

       End-Prog.
           stop run.


¤ Dauer der Verarbeitung: 0.0 Sekunden  (vorverarbeitet)  ¤





Kontakt
Drucken
Kontakt
sprechenden Kalenders

Eigene Datei ansehen




schauen Sie vor die Tür

Fenster


Die Firma ist wie angegeben erreichbar.

Die farbliche Syntaxdarstellung ist noch experimentell.


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