HP 3000 Manuals

Preprocessor Input and Output (cont.) [ ALLBASE/SQL FORTRAN Application Programming Guide ] MPE/iX 5.0 Documentation


ALLBASE/SQL FORTRAN Application Programming Guide

Preprocessor Input and Output (cont.) 
___________________________________________________________________
|                                                                 |
|     C**** Start SQL Preprocessor ****\                          |
|     C     EXEC SQL INCLUDE SQLCA\                               |
|     C\                                                          |
|     C            (* Begin SQL Communication Area *)\            |
|     C\                                                          |
|     C            (* Begin Host Variable Declarations *)\        |
|     C\                                                          |
|     C**** Start Inserted Statements ****\                       |
|           CHARACTER SQLCAID*8\                                  |
|           INTEGER   SQLCABC\                                    |
|           INTEGER   SQLCODE\                                    |
|           INTEGER   SQLERRL\                                    |
|           CHARACTER SQLERRM*256\                                |
|           CHARACTER SQLERRP*8\                                  |
|           INTEGER   SQLERRD(6)\                                 |
|           CHARACTER SQLWARN(0:7)\                               |
|           INTEGER   SQLEXT(2)\                                  |
|           CHARACTER SQLWARN0,SQLWARN1,SQLWARN2,SQLWARN3,\       |
|          1          SQLWARN4,SQLWARN5,SQLWARN6,SQLWARN7\        |
|           EQUIVALENCE (SQLWARN0,SQLWARN(0)),\                   |
|          1            (SQLWARN1,SQLWARN(1)),\                   |
|          2            (SQLWARN2,SQLWARN(2)),\                   |
|          3            (SQLWARN3,SQLWARN(3)),\                   |
|          4            (SQLWARN4,SQLWARN(4)),\                   |
|          5            (SQLWARN5,SQLWARN(5)),\                   |
|          6            (SQLWARN6,SQLWARN(6)),\                   |
|          7            (SQLWARN7,SQLWARN(7))\                    |
|           COMMON /SQLCA/ SQLCAID,SQLCABC,SQLCODE,SQLERRL,\      |
|          1               SQLERRM,SQLERRP,SQLERRD,SQLWARN,SQLEXT\|
|     C**** End SQL Preprocessor   ****\                          |
|     C**** Start SQL Preprocessor ****\                          |
|     C     EXEC SQL BEGIN DECLARE SECTION\                       |
|     C**** End SQL Preprocessor   ****\                          |
|     C**** Start SQL Preprocessor ****\                          |
|     C     EXEC SQL END DECLARE SECTION\                         |
|     C\                                                          |
|     C**** End SQL Preprocessor   ****\                          |
|           INCLUDE 'SQLVAR'\                                     |
|     C**** Start SQL Preprocessor ****\                          |
|     C     EXEC SQL WHENEVER SQLERROR GOTO 500\                  |
|     C\                                                          |
|     C**** Start Inserted Statements ****\                       |
|     C**** End SQL Preprocessor   ****                           |
|           WRITE (*,*) 'BEGIN WORK'                              |
|     C**** Start SQL Preprocessor ****\                          |
|     C     EXEC SQL BEGIN WORK\                                  |
|     C**** Start Inserted Statements ****\                       |
|           CALL SQLXCO(SQLCAID,16,'00A6007F00110061')            |
___________________________________________________________________

          Figure 2-7.  Modified Source File for Program forex2 (page 5 of 13) 
___________________________________________________________________
|                                                                 |
|           IF (SQLCODE .LT. 0) THEN\                             |
|             GO TO 500\                                          |
|           END IF\                                               |
|     C**** End SQL Preprocessor   ****                           |
|           GOTO 600                                              |
|     500   CALL SQLStatusCheck                                   |
|           CALL EndTransaction                                   |
|           CALL ReleaseDBE                                       |
|     600   RETURN                                                |
|     C**** Start SQL Preprocessor ****\                          |
|     C     EXEC SQL WHENEVER SQLERROR CONTINUE\                  |
|     C**** Start Inserted Statements ****\                       |
|     C**** End SQL Preprocessor   ****                           |
|           END                                                   |
|     C     (* End BeginTransaction Subroutine *)                 |
|     C                                                           |
|           SUBROUTINE EndTransaction                             |
|     C     (* Subroutine to Commit Work *)                       |
|     C**** Start SQL Preprocessor ****\                          |
|     C     EXEC SQL INCLUDE SQLCA\                               |
|     C\                                                          |
|     C            (* Begin SQL Communication Area *)\            |
|     C\                                                          |
|     C            (* Begin Host Variable Declarations *)\        |
|     C\                                                          |
|     C**** Start Inserted Statements ****\                       |
|           CHARACTER SQLCAID*8\                                  |
|           INTEGER   SQLCABC\                                    |
|           INTEGER   SQLCODE\                                    |
|           INTEGER   SQLERRL\                                    |
|           CHARACTER SQLERRM*256\                                |
|           CHARACTER SQLERRP*8\                                  |
|           INTEGER   SQLERRD(6)\                                 |
|           CHARACTER SQLWARN(0:7)\                               |
|           INTEGER   SQLEXT(2)\                                  |
|           CHARACTER SQLWARN0,SQLWARN1,SQLWARN2,SQLWARN3,\       |
|          1          SQLWARN4,SQLWARN5,SQLWARN6,SQLWARN7\        |
|           EQUIVALENCE (SQLWARN0,SQLWARN(0)),\                   |
|          1            (SQLWARN1,SQLWARN(1)),\                   |
|          2            (SQLWARN2,SQLWARN(2)),\                   |
|          3            (SQLWARN3,SQLWARN(3)),\                   |
|          4            (SQLWARN4,SQLWARN(4)),\                   |
|          5            (SQLWARN5,SQLWARN(5)),\                   |
|          6            (SQLWARN6,SQLWARN(6)),\                   |
|          7            (SQLWARN7,SQLWARN(7))\                    |
|           COMMON /SQLCA/ SQLCAID,SQLCABC,SQLCODE,SQLERRL,\      |
|          1               SQLERRM,SQLERRP,SQLERRD,SQLWARN,SQLEXT\|
|     C**** End SQL Preprocessor   ****                           |
___________________________________________________________________

          Figure 2-7.  Modified Source File for Program forex2 (page 6 of 13) 
__________________________________________________________
|                                                        |
|     C**** Start SQL Preprocessor ****\                 |
|     C     EXEC SQL BEGIN DECLARE SECTION\              |
|     C**** End SQL Preprocessor   ****\                 |
|     C**** Start SQL Preprocessor ****\                 |
|     C     EXEC SQL END DECLARE SECTION\                |
|     C\                                                 |
|     C**** End SQL Preprocessor   ****\                 |
|           INCLUDE 'SQLVAR'\                            |
|     C**** Start SQL Preprocessor ****\                 |
|     C     EXEC SQL WHENEVER SQLERROR GOTO 500\         |
|     C\                                                 |
|     C**** Start Inserted Statements ****\              |
|     C**** End SQL Preprocessor   ****\                 |
|           WRITE (*,*) 'COMMIT WORK'\                   |
|     C**** Start SQL Preprocessor ****\                 |
|     C     EXEC SQL COMMIT WORK\                        |
|     C**** Start Inserted Statements ****\              |
|           CALL SQLXCO(SQLCAID,8,'00A10000')\           |
|           IF (SQLCODE .LT. 0) THEN\                    |
|             GO TO 500\                                 |
|           END IF\                                      |
|     C**** End SQL Preprocessor   ****                  |
|           GOTO 600                                     |
|     500   CALL SQLStatusCheck                          |
|           CALL ReleaseDBE                              |
|     600   RETURN                                       |
|     C**** Start SQL Preprocessor ****\                 |
|     C     EXEC SQL WHENEVER SQLERROR CONTINUE\         |
|     C**** Start Inserted Statements ****\              |
|     C**** End SQL Preprocessor   ****                  |
|           END                                          |
|     C     (* End EndTransaction Subroutine *)          |
|     C                                                  |
|           SUBROUTINE ReleaseDBE                        |
|     C     (* Subroutine to Release PartsDBE *)         |
|     C**** Start SQL Preprocessor ****\                 |
|     C     EXEC SQL INCLUDE SQLCA                       |
|     C                                                  |
|     C            (* Begin SQL Communication Area *)    |
|     C            (* Begin Host Variable Declarations *)|
|     C                                                  |
|     C**** Start Inserted Statements ****\              |
|           CHARACTER SQLCAID*8\                         |
|           INTEGER   SQLCABC\                           |
|           INTEGER   SQLCODE\                           |
|           INTEGER   SQLERRL\                           |
|           CHARACTER SQLERRM*256\                       |
|           CHARACTER SQLERRP*8                          |
__________________________________________________________

          Figure 2-7.  Modified Source File for Program forex2 (page 7 of 13) 
________________________________________________________________________________
|                                                                              |
|           INTEGER   SQLERRD(6)\                                              |
|           CHARACTER SQLWARN(0:7)\                                            |
|           INTEGER   SQLEXT(2)\                                               |
|           CHARACTER SQLWARN0,SQLWARN1,SQLWARN2,SQLWARN3,\                    |
|          1          SQLWARN4,SQLWARN5,SQLWARN6,SQLWARN7\                     |
|           EQUIVALENCE (SQLWARN0,SQLWARN(0)),\                                |
|          1            (SQLWARN1,SQLWARN(1)),\                                |
|          2            (SQLWARN2,SQLWARN(2)),\                                |
|          3            (SQLWARN3,SQLWARN(3)),\                                |
|          4            (SQLWARN4,SQLWARN(4)),\                                |
|          5            (SQLWARN5,SQLWARN(5)),\                                |
|          6            (SQLWARN6,SQLWARN(6)),\                                |
|          7            (SQLWARN7,SQLWARN(7))\                                 |
|           COMMON /SQLCA/ SQLCAID,SQLCABC,SQLCODE,SQLERRL,\                   |
|          1               SQLERRM,SQLERRP,SQLERRD,SQLWARN,SQLEXT\             |
|     C**** End SQL Preprocessor   ****\                                       |
|     C**** Start SQL Preprocessor ****\                                       |
|     C     EXEC SQL BEGIN DECLARE SECTION\                                    |
|     C**** End SQL Preprocessor   ****\                                       |
|     C**** Start SQL Preprocessor ****\                                       |
|     C     EXEC SQL END DECLARE SECTION\                                      |
|     C\                                                                       |
|     C**** End SQL Preprocessor   ****\                                       |
|           INCLUDE 'SQLVAR'\                                                  |
|     C**** Start SQL Preprocessor ****\                                       |
|     C     EXEC SQL WHENEVER SQLERROR GOTO 500\                               |
|     C**** Start Inserted Statements ****\                                    |
|     C**** End SQL Preprocessor   ****\                                       |
|           WRITE (*,*) 'RELEASE PartsDBE'\                                    |
|     C**** Start SQL Preprocessor ****\                                       |
|     C     EXEC SQL RELEASE\                                                  |
|     C**** Start Inserted Statements ****\                                    |
|           CALL SQLXCO(SQLCAID,56,'00B200002020202020202020202020202020202020\|
|          1202020FFFFFFFF')\                                                  |
|           IF (SQLCODE .LT. 0) THEN\                                          |
|             GO TO 500\                                                       |
|           END IF\                                                            |
|     C**** End SQL Preprocessor   ****                                        |
|           GOTO 600                                                           |
|     500   CALL SQLStatusCheck                                                |
|           CALL EndTransaction                                                |
|     600   RETURN                                                             |
|     C**** Start SQL Preprocessor ****\                                       |
|     C     EXEC SQL WHENEVER SQLERROR CONTINUE\                               |
|     C**** Start Inserted Statements ****\                                    |
|     C**** End SQL Preprocessor   ****                                        |
|           END                                                                |
|     C     (* End ReleaseDBE Subroutine *)                                    |
________________________________________________________________________________

          Figure 2-7.  Modified Source File for Program forex2 (page 8 of 13) 
___________________________________________________________________
|                                                                 |
|           SUBROUTINE DisplayRow (PartNumber,PartName,SalesPrice,|
|          1SalesPriceInd)                                        |
|     C     (* Subroutine to Display a Selected Row *)            |
|     C                                                           |
|     C**** Start SQL Preprocessor ****\                          |
|     C     EXEC SQL INCLUDE SQLCA\                               |
|     C\                                                          |
|     C            (* Begin SQL Communication Area *)\            |
|     C            (* Begin Host Variable Declarations *)\        |
|     C\                                                          |
|     C**** Start Inserted Statements ****\                       |
|           CHARACTER SQLCAID*8\                                  |
|           INTEGER   SQLCABC\                                    |
|           INTEGER   SQLCODE\                                    |
|           INTEGER   SQLERRL\                                    |
|           CHARACTER SQLERRM*256\                                |
|           CHARACTER SQLERRP*8\                                  |
|           INTEGER   SQLERRD(6)\                                 |
|           CHARACTER SQLWARN(0:7)\                               |
|           INTEGER   SQLEXT(2)\                                  |
|           CHARACTER SQLWARN0,SQLWARN1,SQLWARN2,SQLWARN3,\       |
|          1          SQLWARN4,SQLWARN5,SQLWARN6,SQLWARN7\        |
|           EQUIVALENCE (SQLWARN0,SQLWARN(0)),\                   |
|          1            (SQLWARN1,SQLWARN(1)),\                   |
|          2            (SQLWARN2,SQLWARN(2)),\                   |
|          3            (SQLWARN3,SQLWARN(3)),\                   |
|          4            (SQLWARN4,SQLWARN(4)),\                   |
|          5            (SQLWARN5,SQLWARN(5)),\                   |
|          6            (SQLWARN6,SQLWARN(6)),\                   |
|          7            (SQLWARN7,SQLWARN(7))\                    |
|           COMMON /SQLCA/ SQLCAID,SQLCABC,SQLCODE,SQLERRL,\      |
|          1               SQLERRM,SQLERRP,SQLERRD,SQLWARN,SQLEXT\|
|     C**** End SQL Preprocessor   ****\                          |
|     C**** Start SQL Preprocessor ****\                          |
|     C     EXEC SQL BEGIN DECLARE SECTION\                       |
|     C**** End SQL Preprocessor   ****                           |
|           CHARACTER*16     PartNumber                           |
|           CHARACTER*30     PartName                             |
|           DOUBLE PRECISION SalesPrice                           |
|           INTEGER*2 SalesPriceInd\                              |
|     C     SQLIND           SalesPriceInd                        |
|           CHARACTER*80     SQLMessage                           |
|     C**** Start SQL Preprocessor ****\                          |
|     C     EXEC SQL END DECLARE SECTION\                         |
|     C\                                                          |
|     C**** End SQL Preprocessor   ****\                          |
|           INCLUDE 'SQLVAR'\                                     |
|           WRITE(6,100) PartNumber                               |
___________________________________________________________________

          Figure 2-7.  Modified Source File for Program forex2 (page 9 of 13) 
______________________________________________________________________
|                                                                    |
|           WRITE(6,110) PartName                                    |
|           IF (SalesPriceInd .LT. 0) THEN                           |
|           WRITE (*,*) 'Sales Price is NULL'                        |
|           ELSE                                                     |
|           WRITE(6,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                                                              |
|     C**** Start SQL Preprocessor ****\                             |
|     C     EXEC SQL INCLUDE SQLCA\                                  |
|     C\                                                             |
|     C            (* Begin SQL Communication Area *)\               |
|     C\                                                             |
|     C**** Start Inserted Statements ****\                          |
|           CHARACTER SQLCAID*8\                                     |
|           INTEGER   SQLCABC\                                       |
|           INTEGER   SQLCODE\                                       |
|           INTEGER   SQLERRL\                                       |
|           CHARACTER SQLERRM*256\                                   |
|           CHARACTER SQLERRP*8\                                     |
|           INTEGER   SQLERRD(6)\                                    |
|           CHARACTER SQLWARN(0:7)\                                  |
|           INTEGER   SQLEXT(2)\                                     |
|           CHARACTER SQLWARN0,SQLWARN1,SQLWARN2,SQLWARN3,\          |
|          1          SQLWARN4,SQLWARN5,SQLWARN6,SQLWARN7\           |
|           EQUIVALENCE (SQLWARN0,SQLWARN(0)),\                      |
|          1            (SQLWARN1,SQLWARN(1)),\                      |
|          2            (SQLWARN2,SQLWARN(2)),\                      |
|          3            (SQLWARN3,SQLWARN(3)),\                      |
|          4            (SQLWARN4,SQLWARN(4)),\                      |
|          5            (SQLWARN5,SQLWARN(5)),\                      |
|          6            (SQLWARN6,SQLWARN(6)),\                      |
|          7            (SQLWARN7,SQLWARN(7))\                       |
|           COMMON /SQLCA/ SQLCAID,SQLCABC,SQLCODE,SQLERRL,\         |
|          1               SQLERRM,SQLERRP,SQLERRD,SQLWARN,SQLEXT\   |
|     C**** End SQL Preprocessor   ****                              |
|           LOGICAL             Abort                                |
|           INTEGER             DeadLock                             |
______________________________________________________________________

          Figure 2-7.  Modified Source File for Program forex2 (page 10 of 13) 
__________________________________________________________
|                                                        |
|     C            (* Begin Host Variable Declarations *)|
|     C**** Start SQL Preprocessor ****\                 |
|     C     EXEC SQL BEGIN DECLARE SECTION\              |
|     C**** End SQL Preprocessor   ****                  |
|           CHARACTER*80        SQLMessage               |
|     C**** Start SQL Preprocessor ****\                 |
|     C     EXEC SQL END DECLARE SECTION\                |
|     C            (* End Host Variable Declarations *)\ |
|     C\                                                 |
|     C**** End SQL Preprocessor   ****\                 |
|           INCLUDE 'SQLVAR'                             |
|           DeadLock = -14024                            |
|           Abort = .TRUE.                               |
|           WRITE (*,*) Abort                            |
|           IF (SQLCode .LT. DeadLock) THEN              |
|             Abort = .TRUE.                             |
|           ELSE                                         |
|             Abort = .FALSE.                            |
|           ENDIF                                        |
|           DO WHILE (SQLCode .NE. 0)                    |
|     C**** Start SQL Preprocessor ****\                 |
|     C     EXEC SQL SQLExplain :SQLMessage\             |
|     C**** Start Inserted Statements ****\              |
|            CALL SQLXPLNF(SQLCAID,SQLTMP,80,0)\         |
|             READ(SQLTMP,'(A80)')SQLMessage\            |
|     C**** End SQL Preprocessor   ****                  |
|           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                                                  |
|     C**** Start SQL Preprocessor ****\                 |
|     C     EXEC SQL INCLUDE SQLCA\                      |
|     C\                                                 |
|     C            (* Begin SQL Communication Area *)\   |
|     C\                                                 |
|     C**** Start Inserted Statements ****\              |
|           CHARACTER SQLCAID*8\                         |
|           INTEGER   SQLCABC\                           |
|           INTEGER   SQLCODE                            |
__________________________________________________________

          Figure 2-7.  Modified Source File for Program forex2 (page 11 of 13) 
_______________________________________________________________________________
|                                                                             |
|           INTEGER   SQLERRL\                                                |
|           CHARACTER SQLERRM*256\                                            |
|           CHARACTER SQLERRP*8\                                              |
|           INTEGER   SQLERRD(6)\                                             |
|           CHARACTER SQLWARN(0:7)\                                           |
|           INTEGER   SQLEXT(2)\                                              |
|           CHARACTER SQLWARN0,SQLWARN1,SQLWARN2,SQLWARN3,\                   |
|          1          SQLWARN4,SQLWARN5,SQLWARN6,SQLWARN7\                    |
|           EQUIVALENCE (SQLWARN0,SQLWARN(0)),\                               |
|          1            (SQLWARN1,SQLWARN(1)),\                               |
|          2            (SQLWARN2,SQLWARN(2)),\                               |
|          3            (SQLWARN3,SQLWARN(3)),\                               |
|          4            (SQLWARN4,SQLWARN(4)),\                               |
|          5            (SQLWARN5,SQLWARN(5)),\                               |
|          6            (SQLWARN6,SQLWARN(6)),\                               |
|          7            (SQLWARN7,SQLWARN(7))\                                |
|           COMMON /SQLCA/ SQLCAID,SQLCABC,SQLCODE,SQLERRL,\                  |
|          1               SQLERRM,SQLERRP,SQLERRD,SQLWARN,SQLEXT\            |
|     C**** End SQL Preprocessor   ****                                       |
|           INTEGER              DeadLock                                     |
|           INTEGER              MultipleRows                                 |
|           INTEGER              NotFound                                     |
|           INTEGER              OK                                           |
|     C             (* Begin Host Variable Declarations *)                    |
|     C**** Start SQL Preprocessor ****\                                      |
|     C     EXEC SQL BEGIN DECLARE SECTION\                                   |
|     C**** End SQL Preprocessor   ****                                       |
|           CHARACTER*16         PartNumber                                   |
|           CHARACTER*30         PartName                                     |
|           DOUBLE PRECISION     SalesPrice                                   |
|           INTEGER*2 SalesPriceInd\                                          |
|     C     SQLIND               SalesPriceInd                                |
|           CHARACTER*80         SQLMessage                                   |
|     C**** Start SQL Preprocessor ****\                                      |
|     C     EXEC SQL END DECLARE SECTION\                                     |
|     C            (* End Host Variable Declarations *)\                      |
|     C\                                                                      |
|     C**** End SQL Preprocessor   ****\                                      |
|           INCLUDE 'SQLVAR'                                                  |
|           MultipleRows = -10002                                             |
|           DeadLock = -14024                                                 |
|           NotFound = 100                                                    |
|           OK = 0                                                            |
|           DO WHILE (PartNumber .NE. '/')                                    |
|            WRITE(6,100)                                                     |
|     100      FORMAT(/$,' Enter PartNumber from Parts table or / to STOP > ')|
|              READ(5,110) PartNumber                                         |
_______________________________________________________________________________

          Figure 2-7.  Modified Source File for Program forex2 (page 12 of 13) 
________________________________________________________________________________
|                                                                              |
|     110      FORMAT (A16)                                                    |
|     C                                                                        |
|              IF (PartNumber .NE. '/' ) THEN                                  |
|     C                                                                        |
|                 CALL BeginTransaction                                        |
|                 WRITE(*,*) 'SELECT PartNumber, PartName, SalesPrice'         |
|     C                                                                        |
|     C**** Start SQL Preprocessor ****\                                       |
|     C           EXEC SQL SELECT  PartNumber, PartName, SalesPrice\           |
|     C    1                 INTO :PartNumber,\                                |
|     C    2                      :PartName,\                                  |
|     C    3                      :SalesPrice :SalesPriceInd\                  |
|     C    4                 FROM  PurchDB.Parts\                              |
|     C    5                WHERE  PartNumber = :PartNumber\                   |
|     C\                                                                       |
|     C**** Start Inserted Statements ****\                                    |
|           WRITE(SQLTMP,'(A16)')PartNumber\                                   |
|           CALL SQLXFE(SQLCAID,SQLOWN,SQLMDN,1,SQLTMP,16,56,1)\               |
|           IF (SQLCODE .EQ. 0) THEN\                                          |
|           READ(SQLTMP,'(A16,A30,A8,A2)')PartNumber,PartName,SalesPrice,Sales\|
|          1PriceInd\                                                          |
|           ELSE\                                                              |
|           END IF\                                                            |
|     C**** End SQL Preprocessor   ****                                        |
|                 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                                                                        |
|                 IF (SQLCode .EQ. OK) THEN                                    |
|                    CALL DisplayRow (PartNumber, PartName, SalesPrice,        |
|          1           SalesPriceInd)                                          |
|                 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 *)                                    |
________________________________________________________________________________

          Figure 2-7.  Modified Source File for Program forex2 (page 13 of 13) 

Variable Declaration Include File 

The preprocessor generated include file (SQLVAR), contains declarations
for variables referenced in preprocessor generated statements in the
modified source file.  Figure 2-8  illustrates the variable
declaration include file that corresponds to the modified source file in
Figure 2-7.  Note in Figure 2-7 that just after inserting the EXEC SQL
END DECLARE SECTION declaration into the modified source file, the
preprocessor inserted the following FORTRAN compiler directive to
reference the variable declaration include file:

     $INCLUDE 'SQLVAR'

This directive is always inserted after the Host Variable Type
Declaration Section.

When you use file equations to redirect the include files, remember that
the preprocessor always inserts the same $INCLUDE directive.  Therefore,
insure that the applicable file equations are in effect when you
preprocess and when you compile.  When the preprocessor is invoked, the
following file equation must be in effect.

     :FILE SQLVAR = MYVAR 

Then when the FORTRAN compiler is invoked, the following file equation
must be in effect:

     :FILE SQLVAR = MYVAR 
     :FTNC MYSQLPRG, $NEWPASS, $NULL  
_________________________________________________
|                                               |
|     C  temporary area                         |
|           CHARACTER*112 SQLTMP                |
|     C  ownership information                  |
|           CHARACTER*20 SQLOWN                 |
|           CHARACTER*20 SQLMDN                 |
|           DATA SQLOWN /'JOANN@HPSQL         '/|
|           DATA SQLMDN /'FOREX2              '/|
|     C                                         |
_________________________________________________

          Figure 2-8.  Sample Variable Declaration Include File 

ALLBASE/SQL Message File 

Messages placed in SQLMSG come from the ALLBASE/SQL message catalog.  The
default catalog is SQLCTxxx.PUB.SYS. For native language users, the name
of the catalog is SQLCT000.PUB.SYS, where NATIVE-3000 is the message
catalog.

If the default catalog cannot be opened, ALLBASE/SQL returns an error
message indicating that the catalog file is not available.  If the native
language catalog is available, ALLBASE/SQL returns a warning message,
indicating that the default catalog is being used.  SQLMSG messages come
in four four parts:

   1.  A banner:

               MON, JUL 10, 1991,  4:48 PM
            HP36216-02A.E1.16         FORTRAN Preprocessor/3000        ALLBASE/SQL
            (C) COPYRIGHT HEWLETT-PACKARD CO.  1982,1983,1984,1985,1986,1987,1988,
            1989,1990,1991.   ALL RIGHTS RESERVED

       Banners are displayed when ISQL, SQLUtil, or a preprocessor is
       invoked.

   2.  A summary of the preprocessor invocation conditions:

            SQLIN                = FOREX2.SOMEGROUP.SOMEACCT
            DBEnvironment        = PartsDBE
            Module Name          = FOREX2

   3.  Warnings and errors encountered during preprocessing:

                   SELECT PartNumber, PartName, SalesPrice INTO :PartNumber, :SalesPrice
                   :SalesPriceInd FROM PurchDB.Parts WHERE PartNumber = :PartNumber;

            ****** ALLBASE/SQL errors  (DBERR 10952)
            ****** in SQL statement ending in line 290
            *** Selectlist has 3 items and host variable buffer has 2.  (DBERR 2762)

            There are errors.  No sections stored.

   4.  A summary of the results of preprocessing:

             1 ERRORS   0 WARNINGS
            END OF PREPROCESSING.

Both the banner and the preprocessing summary output are echoed to the
standard output, the terminal.

As illustrated in Figure 2-9 , a line number is often provided in
SQLMSG. This line number references the line in the modified source file
containing the command in question.  A message accompanied by a number
may also appear.  You can refer to the ALLBASE/SQL Message Manual for
additional information on the exception condition when these numbered
messages appear.
_______________________________________________________________________________
|                                                                             |
|     :EDITOR                                                                 |
|     HP32201A.07.20  EDIT/3000  MON, JUL 10, 1990, 4:49 PM                   |
|     (C) HEWLETT-PACKARD CO. 1990                                            |
|     /T SQLMSG; L ALL UNN                                                    |
|     FILE UNNUMBERED                                                         |
|                                                                             |
|     SQLIN                = FOREX2.SOMEGROUP.SOMEACCT                        |
|     DBEnvironment        = PartsDBE                                         |
|     Module Name          = FOREX2                                           |
|                                                                             |
|                                                                             |
|     SELCT PartNumber, PartName, SalesPrice INTO :PartNumber,                |
|     :SalesPrice :SalesPriceInd FROM PurchDB.Parts WHERE PartNumber =        |
|     :PartNumber;                                                            |
|                                                                             |
|     ******  ALLBASE/SQL errors (DBERR 10952)                                |
|     ******  in SQL statement ending in line 290                             |
|     *** Selectlist has 3 items and host variable buffer has 2.  (DBERR 2762)|
|                                                                             |
|     There are errors.  No sections stored.                                  |
|       1 ERRORS   0 WARNINGS                                                 |
|      END OF PROCESSING.                                                     |
|      :                                                                      |
_______________________________________________________________________________

          Figure 2-9.  Sample SQLMSG Showing Error 

As Figure 2-10  illustrates, the preprocessor can terminate with the
warning message:

     ****** ALLBASE/SQL warnings. (DBWARN 10602)

when the name of an object in the source file does not match the name of
any object in the system catalog.  Although a section is stored for the
semantically incorrect command, the section is marked as invalid and will
not execute at runtime if it cannot be validated.
___________________________________________________________________________
|                                                                         |
|     :EDITOR                                                             |
|     HP32201A.07.20  EDIT/3000  MON, JUL 10, 1991, 4:49 PM               |
|     (C) HEWLETT-PACKARD CO. 1990                                        |
|     /T SQLMSG; L ALL UNN                                                |
|     FILE UNNUMBERED                                                     |
|                                                                         |
|           .                                                             |
|           .                                                             |
|           .                                                             |
|                                                                         |
|     SQLIN                = FOREX2.SOMEGROUP.SOMEACCT                    |
|     DBEnvironment        = PartsDBE                                     |
|     Module Name          = FOREX2                                       |
|                                                                         |
|            SELECT ParNumber, PartName, SalesPrice INTO :PartNumber,     |
|            :PartName :SalesPrice :SalesPriceInd FROM PurchDB.Parts WHERE|
|            ParNumber = :PartNumber;                                     |
|                                                                         |
|     ****** ALLBASE/SQL warnings. (DBWARN 10602)                         |
|     ****** in SQL statement ending in line 290                          |
|     *** Column PARNUMBER not found. (DBERR 2211)                        |
|                                                                         |
|       1 Sections stored in DBEnvironment.                               |
|                                                                         |
|      0 ERRORS   1 WARNINGS                                              |
|     END OF PREPROCESSING                                                |
|                                                                         |
___________________________________________________________________________

          Figure 2-10.  Sample SQLMSG Showing Warning 

Installable Module File 

When the FORTRAN preprocessor stores a module in the system catalog of a
DBEnvironment at preprocessing time, it places a copy of the module in an
installable module file.  The name of this file is SQLMOD. The module in
this file can be installed into a DBEnvironment different from the
DBEnvironment accessed at preprocessing time by using the INSTALL command
in ISQL. For example:

          :RUN PSQLFOR.PUB.SYS;INFO = "DBEnvironmentName& 
          (MODULE (InstalledModuleName) DROP)"  

       If you want to preserve the SQLMOD file after 
       preprocessing, you must keep it as a permanent 
       file.  Rename SQLMOD after making it permanent. 

          :SAVE SQLMOD 
          :RENAME SQLMOD, MYMOD 

       Before invoking ISQL to install this module file, 
       you may have to transport it and its related 
       program file to the machine containing the target 
       DBEnvironment.  After all the files are restored 
       on the target machine, you invoke ISQL on the 
       machine containing the target DBEnvironment. 

          : isql 

       In order to install the module, you need CONNECT 
       or DBA authority in the target DBEnvironment: 

          isql=> CONNECT TO 'PartsDBE.SOMEGROUP.SOMEACCT'; 
          isql=> INSTALL; 

          File name> MYMOD.SOMEGROUP.SOMEACCT; 
          Name of module in this file:  JOANN@SOMEACCT.FOREX2
          Number of sections installed:  1
          COMMIT WORK to save to DBEnvironment.

          isql=> COMMIT WORK; 
          isql=>

Stored Sections 

In full preprocessing mode, the preprocessor stores a section for each
embedded command except:

     BEGIN DECLARE SECTION      OPEN
     BEGIN WORK                 PREPARE
     CLOSE                      RELEASE
     COMMIT WORK                ROLLBACK WORK
     CONNECT                    SAVEPOINT
     DECLARE                    START DBE
     DELETE WHERE CURRENT       STOP DBE
     END DECLARE SECTION        SQLEXPLAIN
     EXECUTE                    TERMINATE USER
     EXECUTE IMMEDIATE          UPDATE WHERE CURRENT
     FETCH                      WHENEVER
     INCLUDE

The commands listed above either require no authorization to execute or
are executed based on information contained in the compilable
preprocessor output files.

When the preprocessor stores a section, it actually stores what are known
as an input tree and a run tree.  The input tree consists of an
uncompiled command.  The run tree is the compiled, executable form of the
command.

If at runtime a section is valid, ALLBASE/SQL executes the appropriate
run tree when the SQL command is encountered in the application program.
If a section is invalid, ALLBASE/SQL determines whether the objects
referenced in the sections exist and whether current authorization
criteria are satisfied.  When an invalid section can be validated,
ALLBASE/SQL dynamically recompiles the input tree to create an executable
run tree and executes the command.  When a section cannot be validated,
the command is not executed, and an error condition is returned to the
program.

There are three types of sections:

   *   Sections for executing the SELECT command associated with a
       DECLARE CURSOR command.

   *   Sections for executing the SELECT command associated with a CREATE
       VIEW command.

   *   Sections for all other commands for which the preprocessor stores
       a section.

Figure 2-11  illustrates the kind of information in the system catalog
that describes each type of stored section.  The query result illustrated
was extracted from the system view named SYSTEM.SECTION by using ISQL.
The columns in Figure 2-11  have the following meanings:

   *   NAME: This column contains the name of the module to which a
       section belongs.  You specify a module name when you invoke the
       preprocessor; the module name is by default the program name from
       the PROGRAM Statement.  If you are supplying a module name in a
       language other than NATIVE-3000 (ASCII), be sure it is in the same
       language as that of the DBEnvironment.

   *   OWNER: This column identifies the owner of the module.  You
       specify an owner name when you invoke the preprocessor; the owner
       name is by default the userid associated with the preprocessing
       session.  If you are supplying an owner name in a native language
       other than NATIVE-3000 (ASCII), be sure it is in the same language
       as that of the DBEnvironment.

   *   DBEFILESET: This column indicates the DBEFileSet with which
       DBEFiles housing the section are associated.

   *   SECTION: This column gives the section number.  Each section
       associated with a module is assigned a number by the preprocessor
       as it parses the related SQL command at preprocessing time.

   *   TYPE: This column identifies the type of section:
              1 = SELECT associated with a cursor.
              2 = SELECT defining a view.
              0 = All other sections.

   *   VALID: This column identifies whether a section is valid or
       invalid:
              0 = invalid
              1 = valid
__________________________________________________________________________________
|                                                                                |
|     isql=> SELECT NAME,OWNER,DBEFILESET,SECTION,TYPE,VALID FROM SYSTEM.SECTION;|
|                                                                                |
|     ---------------------------------------------------------------------------|
|     NAME                |OWNER       |DBEFILESET       |SECTION  |TYPE  |VALID |
|     --------------------|------------|-----------------|---------|------|------|
|     TABLE               |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     COLUMN              |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     INDEX               |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     SECTION             |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     DBEFILESET          |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     DBEFILE             |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     SPECAUTH            |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     TABAUTH             |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     COLAUTH             |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     MODAUTH             |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     GROUP               |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     VIEWDEF             |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     HASH                |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     CONSTRAINT          |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     CONSTRAINTCOL       |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     CONSTRAINTINDEX     |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     COLDEFAULT          |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     TEMPSPACE           |SYSTEM      |SYSTEM           |       0 |     2|     0|
|     PARTINFO            |PURCHDB     |SYSTEM           |       0 |     2|     0|
|     VENDORSTATISTICS    |PURCHDB     |SYSTEM           |       0 |     2|     0|
|     FOREX2              |JOANN@ACCT  |SYSTEM           |       1 |     0|     1|
|     FOREX7              |BILL@SOMEACT|SYSTEM           |       1 |     1|     1|
|     FOREX7              |BILL@SOMEACT|SYSTEM           |       2 |     0|     1|
|     ---------------------------------------------------------------------------|
|     Number of rows selected is 16.                                             |
|     U[p], d[own], l[eft], r[ight], t[op], b[ottom], pr[int] <n>,or e[nd]>      |
|     ---------------------------------------------------------------------------|
__________________________________________________________________________________

          Figure 2-11.  Information in SYSTEM.SECTION on Stored Sections 

The first eleven rows in this query result describe the sections stored
for the system views.  The next two rows describe the two views in the
sample database:  PurchDB.PartInfo and PurchDB.VendorStatistics.  Views
are always stored as invalid sections, because the run tree is always
generated at run time.

The remaining rows describe sections associated with two preprocessed
programs.  FOREX2 contains only one section, for executing the SELECT
command in the program illustrated in Figure 2-5 .  Another program
may contain two sections, one for executing the SELECT command associated
with a DECLARE CURSOR command and one for executing a FETCH command.

Stored sections remain in the system catalog until they are deleted with
the DROP MODULE command or by invoking the preprocessor with the DROP
option:

     isql=> DROP MODULE FOREX2; 

         or

     : RUN PSQLFOR.PUB.SYS;INFO = "PartsDBE (MODULE (FOREX2) DROP) 

Stored sections are marked invalid when:

   *   The UPDATE STATISTICS command is executed.

   *   Tables accessed in the program are dropped, altered, or assigned
       new owners.

   *   Indexes or DBEFileSets related to tables accessed in the program
       are changed.

   *   Module owner authorization changes occur that affect the execution
       of embedded commands.

When an invalid section is validated at run time, the validated section
is committed when the program issues a COMMIT WORK command.  If a COMMIT
WORK command is not executed, ALLBASE/SQL must re-validate the section
again the next time the program is executed.  For this reason, you should
embed COMMIT WORK commands following SELECT commands since COMMIT WORK
may be needed to commit a section, even when data is not changed by a
program.



MPE/iX 5.0 Documentation