  | 
»  | 
 | 
  
 | 
 | 
In every FORTRAN program, you embed SQL commands in the main
program unit and/or in a subprogram unit in order to:
 - 1
 
Declare the SQL Communications Area (SQLCA).
 - 2
 
Declare host variables.
 - 3
 
Start a DBE session.
 - 4 5
 
Define transactions.
 - 6
 
Implicitly check the status of SQL command execution.
 - 7
 
Terminate a DBE session.
 - 8
 
Define or manipulate data in a DBEnvironment.
 - 9
 
Explicitly check the status of SQL command execution.
 - 10
 
Obtain error and warning messages from the ALLBASE/SQL message
catalog.
 
 The program listing shown in Figure 3-1 illustrates where in a
program you can embed SQL commands to accomplish the activities
listed above.
 This chapter is a high-level road map to the logical and
physical aspects of embedding SQL commands in a program.  It
addresses the reasons for embedding commands to perform the
above activities.  It also gives general rules for how and where
to embed SQL commands for these activities.  First however, it
describes the general rules that apply when you embed any
SQL command.
 Figure 3-1 Sample Source File  
         PROGRAM forex2   
   C                      
   C     *********************************************************  
   C     *  This program illustrates the use of SQL's SELECT     *  
   C     *  command to retrieve one row or tuple of data at      *  
   C     *  a time. This program executes a BEGIN WORK command   *  
   C     *  before the SELECT command, and a COMMIT WORK command *  
   C     *  after executing the SELECT command. An indicator     *  
   C     *  variable is also used for SalesPrice.                *  
   C     *********************************************************  
   C
         EXEC SQL INCLUDE SQLCA    1
   C  
   C            (* Begin SQL Communication Area *)
   C  
              CHARACTER           Done  
              CHARACTER           Abort  
              INTEGER             MultipleRows  
              INTEGER             Deadlock  
              CHARACTER*16        Response  
   C  
   C     ****************************************************  
   C     *  Data Type Conversions :                         *  
   C     *    Character         = SQL Char(1)               *  
   C     *    Character*n       = SQL Char(n)               *  
   C     *    Character*n       = SQL VarChar               * 
   C     *    Double Precision  = SQL Float                 * 
   C     *    Double Precision  = SQL Decimal               * 
   C     *    Integer           = SQL Integer               *  
   C     *    Integer*2         = SQL SmallInt              * 
   C     **************************************************** 
   C  
   C             (* Begin Host Variable Declarations *)  
   C  
         EXEC SQL BEGIN DECLARE SECTION     2
         CHARACTER*16         PartNumber  
         CHARACTER*30         PartName  
         DOUBLE PRECISION     SalesPrice  
         SQLIND               SalesPriceInd  
         CHARACTER*80         SQLMessage  
         EXEC SQL END DECLARE SECTION   2
   C  
   C            (* End Host Variable Declarations *)  
   C  
   C  
   C  
   C  
   C
   C            (* Beginning of the Main Program *)
   C
         WRITE (*,*) CHAR(27), 'U'
         WRITE (*,*) 'Program to SELECT specified rows from the
        1Parts Table 1 -- forex2'
         WRITE (*,*) ' '
         WRITE (*,*) 'Event List:'
         WRITE (*,*) '  CONNECT TO PartsDBE'
         WRITE (*,*) '  BEGIN WORK'
         WRITE (*,*) '  SELECT specified row from the Parts
        1table until use 1r enters a "/"'
         WRITE (*,*) '  COMMIT WORK'
         WRITE (*,*) '  RELEASE PartsDBE'
   C
         CALL ConnectDBE
         CALL QueryTable
         CALL ReleaseDBE
   C
         STOP
         END
   C
   C     (* Beginning of the Sub-Routines *)
   C
         SUBROUTINE ConnectDBE
   C            (* Subroutine to Connect to PartsDBE *)
   C
         EXEC SQL INCLUDE SQLCA
   C
   C            (* Begin SQL Communication Area *)
   C
   C            (* Begin Host Variable Declarations *)
   C
         EXEC SQL BEGIN DECLARE SECTION
         EXEC SQL END DECLARE SECTION
   C
         EXEC SQL WHENEVER SQLERROR GOTO 500
   C
         WRITE (*,*) ' '
         WRITE (*,*) 'CONNECT TO PartsDBE'
         EXEC SQL CONNECT TO 'PartsDBE'   3
         GOTO 600
   500   CALL SQLStatusCheck
         CALL EndTransaction
         CALL ReleaseDBE
   C
   C
   C
   600   RETURN
         EXEC SQL WHENEVER SQLERROR CONTINUE
         END
   C     (* End of ConnectDBE Subroutine *)
   C
         SUBROUTINE BeginTransaction
   C            (* Subroutine to Begin Work *)
   C
         EXEC SQL INCLUDE SQLCA
   C
   C            (* Begin SQL Communication Area *)
   C
   C            (* Begin Host Variable Declarations *)
   C
         EXEC SQL BEGIN DECLARE SECTION
         EXEC SQL END DECLARE SECTION
   C
         EXEC SQL WHENEVER SQLERROR GOTO 500
   C
         WRITE (*,*) 'BEGIN WORK'
         EXEC SQL BEGIN WORK     4
         GOTO 600
   500   CALL SQLStatusCheck
         CALL EndTransaction
         CALL ReleaseDBE
   C
   600   RETURN
         EXEC SQL WHENEVER SQLERROR CONTINUE
         END
   C     (* End BeginTransaction Subroutine *)
   C
         SUBROUTINE EndTransaction
   C     (* Subroutine to Commit Work *)
   C
         EXEC SQL INCLUDE SQLCA
   C
   C            (* Begin SQL Communication Area *)
   C
   C            (* Begin Host Variable Declarations *)
   C
         EXEC SQL BEGIN DECLARE SECTION
         EXEC SQL END DECLARE SECTION
   C
         EXEC SQL WHENEVER SQLERROR GOTO 500
   C
         WRITE (*,*) 'COMMIT WORK'
   C
   C
         EXEC SQL COMMIT WORK   5
         GOTO 600
   500   CALL SQLStatusCheck
         CALL ReleaseDBE
   C
   600   RETURN
         EXEC SQL WHENEVER SQLERROR CONTINUE
         END
   C     (* End EndTransaction Subroutine *)
   C
         SUBROUTINE ReleaseDBE
   C     (* Subroutine to Release PartsDBE *)
   C
         EXEC SQL INCLUDE SQLCA
    
   C            (* Begin SQL Communication Area *)
   C
   C            (* Begin Host Variable Declarations *)
   C
         EXEC SQL BEGIN DECLARE SECTION
         EXEC SQL END DECLARE SECTION
   C
         EXEC SQL WHENEVER SQLERROR GOTO 500   6
   C
         WRITE (*,*) 'RELEASE PartsDBE'
         EXEC SQL RELEASE   7
         GOTO 600
   500   CALL SQLStatusCheck
         CALL EndTransaction
   C
   600   RETURN
         EXEC SQL WHENEVER SQLERROR CONTINUE   6
         END
   C     (* End ReleaseDBE Subroutine *)
   C
   C
   C
   C
   C
   C
   C
   C
   C
   C
   C
   C
   C
   C
   C
   C
         SUBROUTINE DisplayRow (PartNumber,PartName,SalesPrice,
        1SalesPriceInd)
   C     (* Subroutine to Display a Selected Row *)
   C
         EXEC SQL INCLUDE SQLCA
   C
   C            (* Begin SQL Communication Area *)
   C
   C            (* Begin Host Variable Declarations *)
   C
         EXEC SQL BEGIN DECLARE SECTION
         CHARACTER*16     PartNumber
         CHARACTER*30     PartName
         DOUBLE PRECISION SalesPrice
         SQLIND           SalesPriceInd
         CHARACTER*80     SQLMessage
         EXEC SQL END DECLARE SECTION
   C
         WRITE(*,100) PartNumber
         WRITE(*,110) PartName
         IF (SalesPriceInd .LT. 0) THEN
         WRITE (*,*) 'Sales Price is NULL'
         ELSE
         WRITE(*,120) SalesPrice
         ENDIF
         WRITE (*,*) 'Was retrieved from the PurchDB.Parts table!'
   100   FORMAT('   Part Number:    ',A16)
   110   FORMAT('   Part Name:      ',A30)
   120   FORMAT('   SalesPrice:     ',F10.2)
   C
         RETURN
         END
   C     (* End DisplayRow Subroutine *)
   C
         SUBROUTINE SQLStatusCheck
   C     (* Subroutine to Check the Status of DeadLocks *)
   C
         EXEC SQL INCLUDE SQLCA
   C
   C            (* Begin SQL Communication Area *)
   C
         LOGICAL             Abort
         INTEGER             DeadLock
   C
   C
   C
   C            (* Begin Host Variable Declarations *)
   C
         EXEC SQL BEGIN DECLARE SECTION
         CHARACTER*80        SQLMessage
         EXEC SQL END DECLARE SECTION
   C
   C            (* End Host Variable Declarations *)
   C
         DeadLock = -14024
         Abort = .TRUE.
         WRITE (*,*) Abort
         IF (SQLCode .LT. DeadLock) THEN  9
           Abort = .TRUE.
         ELSE
           Abort = .FALSE.
         ENDIF
         DO WHILE (SQLCode .NE. 0)
         EXEC SQL SQLExplain :SQLMessage  10
         WRITE (*,*) SQLMessage
         END DO
         IF (Abort) THEN
           CALL EndTransaction
           CALL ReleaseDBE
         ENDIF
         RETURN
         END
   C     (* End of SQLStatusCheck Subroutine *)
   C
         SUBROUTINE QueryTable
   C     (* Subroutine to Query the Parts table *)
   C
         EXEC SQL INCLUDE SQLCA
   C
   C            (* Begin SQL Communication Area *)
   C
         INTEGER              DeadLock
         INTEGER              MultipleRows
         INTEGER              NotFound
         INTEGER              OK
   C
   C             (* Begin Host Variable Declarations *)
         EXEC SQL BEGIN DECLARE SECTION
         CHARACTER*16         PartNumber
         CHARACTER*30         PartName
         DOUBLE PRECISION     SalesPrice
         SQLIND               SalesPriceInd
         CHARACTER*80         SQLMessage
         EXEC SQL END DECLARE SECTION
   C
   C            (* End Host Variable Declarations *)
   C
         MultipleRows = -10002
         DeadLock = -14024
         NotFound = 100
         OK = 0
   C
         DO WHILE (PartNumber .NE. '/')
            WRITE(*,100)
   100      FORMAT(/$,' Enter PartNumber from Parts table
        1or / to STOP > ')
            READ(*,110) PartNumber
   110      FORMAT (A16)
   C
            IF (PartNumber .NE. '/' ) THEN
   C
   	    CALL BeginTransaction
   	    WRITE(*,*) 'SELECT PartNumber, PartName, SalesPrice'
   C
            EXEC SQL SELECT  PartNumber, PartName, SalesPrice 8
        1                 INTO :PartNumber,
        2                      :PartName,
        3                      :SalesPrice :SalesPriceInd
        4                 FROM  PurchDB.Parts
        5                WHERE  PartNumber = :PartNumber
   C
            IF ((SQLWarn(3) .EQ. 'w') .OR. (SQLWarn(3) .EQ. 'W')) THEN
              WRITE (*,*) 'SQL WARNING has occured. The following row'
              WRITE (*,*) 'of data may not be valid!'
              CALL DisplayRow (PartNumber,PartName,SalesPrice,
        1         SalesPriceInd)
            ENDIF
   C
   C
   C
   C
   C
   C
   C
   	    IF (SQLCode .EQ. OK) THEN                    9
   	       CALL DisplayRow (PartNumber, PartName, SalesPrice)
   	    ELSEIF (SQLCode .EQ. NotFound) THEN
   	       WRITE (*,*) 'Row not found!'
   	    ELSEIF (SQLCode .EQ. MultipleRows) THEN
   	       WRITE(*,*) 'WARNING: More than one row qualifies!'
   	    ELSE
   	       CALL SQLStatusCheck
   	    ENDIF
   	    CALL EndTransaction
            ENDIF
         END DO
         RETURN
         END
   C     (* End QueryTable Subroutine *)
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
 |  
  
 |