Programmer's Guide to the Oracle Pro*COBOL Precompiler
Release 8.0

A54659-01

Library

Product

Contents

Index

Prev Next

10
Using Host Tables

This chapter looks at using tables to simplify coding and improve program performance. You learn how to manipulate Oracle8 data using tables, how to operate on all the elements of an table with a single SQL statement, and how to limit the number of table elements processed. Topics are:

What Is a Host Table?

An table is a set of related data items, called elements, associated with a single variable name. When declared as a host variable, the table is called a host table. Likewise, an indicator variable declared as an table is called an indicator table. An indicator table can be associated with any host table.

Why Use Tables?

Tables can ease programming and offer improved performance. When writing an application, you are usually faced with the problem of storing and manipulating large collections of data. Tables simplify the task of naming and referencing the individual items in each collection.

Using tables can boost the performance of your application. Tables let you manipulate an entire collection of data items with a single SQL statement. Thus, Oracle8 communication overhead is reduced markedly, especially in a networked environment. For example, suppose you want to insert information about 300 employees into the EMP table. Without tables your program must do 300 individual INSERTs-one for each employee. With tables, only one INSERT need be done.

Declaring Host Tables

You declare host tables in the Data Division like simple host variables. You also dimension (set the size of) host tables in the Data Division. In the following example, you declare three host tables and dimension them with 50 elements:

 ...
DATA DIVISION.
WORKING-STORAGE SECTION.
...
EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 EMP-REC-TABLES.
05 EMP-NUMBER OCCURS 50 TIMES PIC S9(4) COMP.
05 EMP-NAME OCCURS 50 TIMES PIC X(10) VARYING.
05 SALARY OCCURS 50 TIMES PIC S9(6)V99
DISPLAY SIGN LEADING SEPARATE.
EXEC SQL END DECLARE SECTION END-EXEC.
...

Dimensioning Tables

The maximum dimension of a host table is 32,767 elements. If you use a host table that exceeds the maximum, you get a "parameter out of range" runtime error. If you use multiple host tables in a single SQL statement, their dimensions should be the same. Otherwise, an "table size mismatch" warning message is issued at precompile time. If you ignore this warning, the precompiler uses the smallest dimension for the SQL operation.

Restrictions

Host tables that might be referenced in a SQL statement are limited to one dimension. So, the two-dimensional table declared in the following example is invalid:

     EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 SALARY-TABLE.
05 ROW OCCURS 25 TIMES.
10 COLUMN OCCURS 25 TIMES.
HI-LOW-SCORES PIC 9(5).
EXEC SQL END DECLARE SECTION END-EXEC.

Using Tables in SQL Statements

Pro*COBOL allows the use of host tables in data manipulation statements. You can use host tables as input variables in the INSERT, UPDATE, and DELETE statements and as output variables in the INTO clause of SELECT and FETCH statements.

The syntax used for host tables and simple host variables is nearly the same. One difference is the optional FOR clause, which lets you control table processing. Also, there are restrictions on mixing host tables and simple host variables in a SQL statement.

The following sections illustrate the use of host tables in data manipulation statements.

Selecting into Tables

You can use host tables as output variables in the SELECT statement. If you know the maximum number of rows the select will return, simply dimension the host tables with that number of elements. In the following example, you select directly into three host tables. Knowing the select will return no more than 50 rows, you dimension the tables with 50 elements:

     EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 EMP-REC-TABLES.
05 EMP-NUMBER OCCURS 50 TIMES PIC S9(4) COMP.
05 EMP-NAME OCCURS 50 TIMES PIC X(10) VARYING.
05 SALARY OCCURS 50 TIMES PIC S9(6)V99
DISPLAY SIGN LEADING SEPARATE.
EXEC SQL END DECLARE SECTION END-EXEC.
...
EXEC SQL SELECT ENAME, EMPNO, SAL
INTO :EMP-NAME, :EMP-NUMBER, :SALARY
FROM EMP
WHERE SAL > 1000
END-EXEC.

In this example, the SELECT statement returns up to 50 rows. If there are fewer than 50 eligible rows or you want to retrieve only 50 rows, this method will suffice. However, if there are more than 50 eligible rows, you cannot retrieve all of them this way. If you re-execute the SELECT statement, it just returns the first 50 rows again, even if more are eligible. You must either dimension a larger table or declare a cursor for use with the FETCH statement.

If a SELECT INTO statement returns more rows than the number of elements you dimensioned, Oracle8 issues the error message

SQL-02112: SELECT...INTO returns too many rows

unless you specify SELECT_ERROR=NO. For more information about the option SELECT_ERROR, see "SELECT_ERROR" on page 7-31.

Batch Fetches

If you do not know the maximum number of rows a select will return, you can declare and open a cursor, then fetch from it in "batches." Batch fetches within a loop let you retrieve a large number of rows with ease. Each fetch returns the next batch of rows from the current active set. In the following example, you fetch in 20-row batches:

     EXEC SQL BEGIN DECLARE SECTION END-EXEC.           
01 EMP-REC-TABLES.
05 EMP-NUMBER OCCURS 20 TIMES PIC S9(4) COMP.
05 EMP-NAME OCCURS 20 TIMES PIC X(10) VARYING.
05 SALARY OCCURS 20 TIMES PIC S9(6)V99
DISPLAY SIGN LEADING SEPARATE.
...
EXEC SQL END DECLARE SECTION END-EXEC.
...
EXEC SQL DECLARE EMPCURSOR CURSOR FOR
SELECT EMPNO, SAL FROM EMP
END-EXEC.
...
EXEC SQL OPEN EMPCURSOR END-EXEC.
...
EXEC SQL WHENEVER NOT FOUND DO PERFORM ...
LOOP.
EXEC SQL FETCH EMPCURSOR INTO :EMP-NUMBER, :SALARY END-EXEC.
* -- process batch of rows
...
GO TO LOOP.

Number of Rows Fetched

Each fetch returns, at most, the number of rows in the table dimension. Fewer rows are returned in the following cases:

The cumulative number of rows returned can be found in the third element of SQLERRD in the SQLCA, called SQLERRD(3) in this guide. This applies to each open cursor. In the following example, notice how the status of each cursor is maintained separately:

     EXEC SQL OPEN CURSOR1 END-EXEC.
EXEC SQL OPEN CURSOR2 END-EXEC.
EXEC SQL FETCH CURSOR1 INTO :TABLE-OF-20 END-EXEC.
* -- now running total in SQLERRD(3) is 20
EXEC SQL FETCH CURSOR2 INTO :TABLE-OF-30 END-EXEC.
* -- now running total in SQLERRD(3) is 30, not 50
EXEC SQL FETCH CURSOR1 INTO :TABLE-OF-20 END-EXEC.
* -- now running total in SQLERRD(3) is 40 (20 + 20)
EXEC SQL FETCH CURSOR2 INTO :TABLE-OF-30 END-EXEC.
* -- now running total in SQLERRD(3) is 60 (30 + 30)

Restrictions

Using host tables in the WHERE clause of a SELECT statement is allowed only in a subquery. (For an example, see "Using the WHERE Clause" on page 10-13.) Also, you cannot mix simple host variables with host tables in the INTO clause of a SELECT or FETCH statement; if any of the host variables is a table, all must be tables.

Table 10-1 shows which uses of host tables are valid in a SELECT INTO statement:

Table 10-1: Host Tables Valid in SELECT INTO
INTO Clause   WHERE Clause   Valid?  

table  

table  

no  

scalar  

scalar  

yes  

table  

scalar  

yes  

scalar  

table  

no  

Fetching Nulls

When UNSAFE_NULL=YES, if you select or fetch a null into a host table that lacks an indicator table, no error is generated. So, when doing table selects and fetches, always use indicator tables. That way, you can find nulls in the associated output host table. (To learn how to find nulls and truncated values, see "Using Indicator Variables" on page 5-3.)

When UNSAFE_NULL=NO, if you select or fetch a null into a host table that lacks an indicator table, Oracle8 stops processing, sets SQLERRD(3) to the number of rows processed, and issues the following error message:

ORA-01405: fetched column value is NULL 

Fetching Truncated Values

When DBMS=V7 or V8, if you select or fetch a truncated column value into a host table that lacks an indicator table, Oracle8 stops processing, sets SQLERRD(3) to the number of rows processed, and issues the following error message:

ORA-01406: fetched column value was truncated 

You can check SQLERRD(3) for the number of rows processed before the truncation occurred. The rows-processed count includes the row that caused the truncation error.

When MODE=ANSI, truncation is not considered an error, so Oracle8 continues processing.

Again, when doing table selects and fetches, always use indicator tables. That way, if Oracle8 assigns one or more truncated column values to an output host table, you can find the original lengths of the column values in the associated indicator table.

Inserting with Tables

You can use host tables as input variables in an INSERT statement. Just make sure your program populates the tables with data before executing the INSERT statement. If some elements in the tables are irrelevant, you can use the FOR clause to control the number of rows inserted. See "Using the FOR Clause" on page 10-11.

An example of inserting with host tables follows:

     EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 EMP-REC-TABLES.
05 EMP-NUMBER OCCURS 50 TIMES PIC S9(4) COMP.
05 EMP-NAME OCCURS 50 TIMES PIC X(10) VARYING.
05 SALARY OCCURS 50 TIMES PIC S9(6)V99
DISPLAY SIGN LEADING SEPARATE.
EXEC SQL END DECLARE SECTION END-EXEC.
* -- populate the host tables
EXEC SQL INSERT INTO EMP (ENAME, EMPNO, SAL)
VALUES (:EMP-NAME, :EMP-NUMBER, :SALARY)
END-EXEC.

The cumulative number of rows inserted can be found in SQLERRD(3).

Although functionally equivalent to the following statement, the INSERT statement in the last example is much more efficient because it issues only one call to Oracle8:

     PERFORM VARYING I FROM 1 BY 1 UNTIL I = TABLE-DIMENSION.
EXEC SQL INSERT INTO EMP (ENAME, EMPNO, SAL)
VALUES (:EMP-NAME[I], :EMP-NUMBER[I], :SALARY[I])
END_EXEC
END-PERFORM.

In this imaginary example (imaginary because host variables cannot be subscripted in a SQL statement), you use a FOR loop to access all table elements in sequential order.

Restrictions

Mixing simple host variables with host tables in the VALUES clause of an INSERT statement is not allowed; if any of the host variables is a table, all must be tables.

Updating with Tables

You can also use host tables as input variables in an UPDATE statement, as the following example shows:

     EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 EMP-REC-TABLES.
05 EMP-NUMBER OCCURS 50 TIMES PIC S9(4) COMP.
05 SALARY OCCURS 50 TIMES PIC S9(6)V99
DISPLAY SIGN LEADING SEPARATE.

EXEC SQL END DECLARE SECTION END-EXEC.
* -- populate the host tables
EXEC SQL
UPDATE EMP SET SAL = :SALARY WHERE EMPNO = :EMP-NUMBER
END-EXEC.

The cumulative number of rows updated can be found in SQLERRD(3). The number does not include rows processed by an update cascade.

If some elements in the tables are irrelevant, you can use the FOR clause to limit the number of rows updated.

The last example showed a typical update using a unique key (EMP-NUMBER). Each table element qualified just one row for updating. In the following example, each table element qualifies multiple rows:

     EXEC SQL BEGIN DECLARE SECTION END-EXEC.
...
05 JOB-TITLE OCCURS 10 TIMES PIC X(10) VARYING.
05 COMMISSION OCCURS 50 TIMES PIC S9(6)V99
DISPLAY SIGN LEADING SEPARATE.
EXEC SQL END DECLARE SECTION END-EXEC.
* -- populate the host tables
EXEC SQL
UPDATE EMP SET COMM = :COMMISSION WHERE JOB = :JOB-TITLE
END-EXEC.

Restrictions

Mixing simple host variables with host tables in the SET or WHERE clause of an UPDATE statement is not allowed. If any of the host variables is an table, all must be tables. Furthermore, if you use a host table in the SET clause, you must use one in the WHERE clause. However, their dimensions and datatypes need not match.

You cannot use host tables with the CURRENT OF clause in an UPDATE statement. For an alternative, see "Mimicking the CURRENT OF Clause" on page 10-14.

Table 10-2 shows which uses of host tables are valid in an UPDATE statement:

Table 10-2: Host Tables Valid in UPDATE
SET Clause   WHERE Clause   Valid?  

table  

table  

yes  

scalar  

scalar  

yes  

table  

scalar  

no  

scalar  

table  

no  

Deleting with Tables

You can also use host tables as input variables in a DELETE statement. It is like executing the DELETE statement repeatedly using successive elements of the host table in the WHERE clause. Thus, each execution might delete zero, one, or more rows from the table. An example of deleting with host tables follows:

     EXEC SQL BEGIN DECLARE SECTION END-EXEC.
...
05 EMP-NUMBER OCCURS 50 TIMES PIC S9(4) COMP.
EXEC SQL END DECLARE SECTION END-EXEC.
* -- populate the host table
EXEC SQL
DELETE FROM EMP WHERE EMPNO = :EMP-NUMBER
END-EXEC.

The cumulative number of rows deleted can be found in SQLERRD(3). That number does not include rows processed by a delete cascade.

The last example showed a typical delete using a unique key (EMP-NUMBER). Each table element qualified just one row for deletion. In the following example, each table element qualifies multiple rows:

     EXEC SQL BEGIN DECLARE SECTION END-EXEC.
...
05 JOB-TITLE OCCURS 10 TIMES PIC X(10) VARYING.
EXEC SQL END DECLARE SECTION END-EXEC.
* -- populate the host table
EXEC SQL
DELETE FROM EMP WHERE JOB = :JOB-TITLE
END-EXEC.

Restrictions

Mixing simple host variables with host tables in the WHERE clause of a DELETE statement is not allowed; if any of the host variables is a table, all must be tables. Also, you cannot use host tables with the CURRENT OF clause in a DELETE statement. For an alternative, see "Mimicking CURRENT OF" on "Mimicking the CURRENT OF Clause" on page 10-14.

Using Indicator Tables

You use indicator tables to assign nulls to input host tables and to detect null or truncated values in output host tables. The following example shows how to insert with indicator tables:

     EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 EMP-REC-VARS.
05 EMP-NUMBER OCCURS 50 TIMES PIC S9(4) COMP.
05 DEPT-NUMBER OCCURS 50 TIMES PIC S9(4) COMP.
05 COMMISSION OCCURS 50 TIMES PIC S9(6)V99
DISPLAY SIGN LEADING SEPARATE.
* -- indicator table:
05 COMM-IND OCCURS 50 TIMES PIC S9(4) COMP.
EXEC SQL END DECLARE SECTION END-EXEC.
* -- populate the host tables
* -- populate the indicator table; to insert a null into
* -- the COMM column, assign -1 to the appropriate element in
* -- the indicator table
EXEC SQL
INSERT INTO EMP (EMPNO, DEPTNO, COMM)
VALUES (:EMP_NUMBER, :DEPT-NUMBER, :COMMISSION:COMM-IND)
END-EXEC.

The dimension of the indicator table cannot be smaller than the dimension of the host table.

Using the FOR Clause

You can use the optional FOR clause to set the number of table elements processed by any of the following SQL statements:

The FOR clause is especially useful in UPDATE, INSERT, and DELETE statements. With these statements you might not want to use the entire table. The FOR clause lets you limit the elements used to just the number you need, as the following example shows:

     EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 EMP-REC-VARS.
05 EMP-NAME OCCURS 1000 TIMES PIC X(20) VARYING.
05 SALARY OCCURS 100 TIMES PIC S9(6)V99
DISPLAY SIGN LEADING SEPARATE.
01 ROWS-TO-INSERT PIC S9(4) COMP.
EXEC SQL END DECLARE SECTION END-EXEC.
* -- populate the host tables
MOVE 25 TO ROWS-TO-INSERT.
* -- set FOR-clause variable
* -- will process only 25 rows
EXEC SQL FOR :ROWS-TO-INSERT
INSERT INTO EMP (ENAME, SAL)
VALUES (:EMP-NAME, :SALARY)
END-EXEC.

The FOR clause must use an integer host variable to count table elements. For example, the following statement is illegal:

* -- illegal
EXEC SQL FOR 25
INSERT INTO EMP (ENAME, EMPNO, SAL)
VALUES (:EMP-NAME, :EMP-NUMBER, :SALARY)
END-EXEC.

The FOR-clause variable specifies the number of table elements to be processed. Make sure the number does not exceed the smallest table dimension. Also, the number must be positive. If it is negative or zero, no rows are processed.

Restrictions

Two restrictions keep FOR clause semantics clear: you cannot use the FOR clause in a SELECT statement or with the CURRENT OF clause.

In a SELECT Statement

If you use the FOR clause in a SELECT statement, you get the following error message:

PCC-E-0056:  FOR clause not allowed on SELECT statement at ...

The FOR clause is not allowed in SELECT statements because its meaning is unclear. Does it mean "execute this SELECT statement n times"? Or, does it mean "execute this SELECT statement once, but return n rows"? The problem in the former case is that each execution might return multiple rows. In the latter case, it is better to declare a cursor and use the FOR clause in a FETCH statement, as follows:

     EXEC SQL FOR :LIMIT FETCH EMPCURSOR INTO ...

With the CURRENT OF Clause

You can use the CURRENT OF clause in an UPDATE or DELETE statement to refer to the latest row returned by a FETCH statement, as the following example shows:

     EXEC SQL DECLARE EMPCURSOR CURSOR FOR 
SELECT ENAME, SAL FROM EMP WHERE EMPNO = :EMP-NUMBER
END-EXEC.
...
EXEC SQL OPEN EMPCURSOR END-EXEC.
...
EXEC SQL FETCH emp_cursor INTO :EM-NAME, :SALARY END-EXEC.
...
EXEC SQL UPDATE EMP SET SAL = :NEW-SALARY
WHERE CURRENT OF EMPCURSOR
END-EXEC.

However, you cannot use the FOR clause with the CURRENT OF clause. The following statements are invalid because the only logical value of LIMIT is 1 (you can only update or delete the current row once):

     EXEC SQL FOR :LIMIT UPDA-CURSOR END-EXEC.
...
EXEC SQL FOR :LIMIT DELETE FROM EMP
WHERE CURRENT OF EMP-CURSOR
END-EXEC.

Using the WHERE Clause

Oracle8 treats a SQL statement containing host tables of dimension n like the same SQL statement executed n times with n different scalar variables (the individual table elements). The precompiler issues the following error message only when such treatment is ambiguous:

PCC-S-0055: Array <name> not allowed as bind variable at ...

For example, assuming the declarations

     EXEC SQL BEGIN DECLARE SECTION END-EXEC.
...
05 MGRP-NUMBER OCCURS 50 TIMES PIC S9(4) COMP.
05 JOB-TITLE OCCURS 50 TIMES PIC X(20) VARYING.
01 I PIC S9(4) COMP.
EXEC SQL END DECLARE SECTION END-EXEC.

it would be ambiguous if the statement

     EXEC SQL SELECT MGR INTO :MGR-NUMBER FROM EMP
WHERE JOB = :JOB-TITLE
END-EXEC.

were treated like the imaginary statement

     PERFORM VARYING I FROM 1 BY 1 UNTIL I = 50
SELECT MGR INTO :MGR-NUMBER[I] FROM EMP
WHERE JOB = :JOB_TITLE[I]
END-EXEC
END-PERFORM.

because multiple rows might meet the WHERE-clause search condition, but only one output variable is available to receive data. Therefore, an error message is issued.

On the other hand, it would not be ambiguous if the statement

     EXEC SQL
UPDATE EMP SET MGR = :MGR_NUMBER
WHERE EMPNO IN (SELECT EMPNO FROM EMP WHERE
JOB = :JOB-TITLE)
END-EXEC.

were treated like the imaginary statement

     PERFORM VARYING I FROM 1 BY 1 UNTIL I = 50
UPDATE EMP SET MGR = :MGR_NUMBER[I]
WHERE EMPNO IN
(SELECT EMPNO FROM EMP WHERE JOB = :JOB-TITLE[I])
END-EXEC
END-PERFORM.

because there is a MGR-NUMBER in the SET clause for each row matching JOB-TITLE in the WHERE clause, even if each JOB-TITLE matches multiple rows. All rows matching each JOB-TITLE can be SET to the same MGR-NUMBER. So, no error message is issued.

Mimicking the CURRENT OF Clause

You use the CURRENT OF cursor clause in a DELETE or UPDATE statement to refer to the latest row fetched from the cursor. However, you cannot use CURRENT OF with host tables. Instead, select the ROWID of each row, then use that value to identify the current row during the update or delete. An example follows:

     EXEC SQL BEGIN DECLARE SECTION END-EXEC.
05 EMP-NAME OCCURS 25 TIMES PIC X(20) VARYING.
05 JOB-TITLE OCCURS 25 TIMES PIC X(15) VARYING.
05 OLD-TITLE OCCURS 25 TIMES PIC X(15) VARYING.
05 ROW-ID OCCURS 25 TIMES PIC X(18) VARYING.
EXEC SQL END DECLARE SECTION END-EXEC.
...
EXEC SQL DECLARE EMPCURSOR CURSOR FOR
SELECT ENAME, JOB, ROWID FROM EMP
END-EXEC.
...
EXEC SQL OPEN EMPCURSOR END-EXEC.
...
EXEC SQL WHENEVER NOT FOUND GOTO ...
...
PERFORM
EXEC SQL
FETCH EMPCURSOR
INTO :EMP-NAME, :JOB-TITLE, :ROW-I
END-EXEC
...
EXEC SQL
DELETE FROM EMP
WHERE JOB = :OLD-TITLE AND ROWID = :ROW-ID
END-EXEC
EXEC SQL COMMIT WORK END-EXEC
END-PERFORM.

However, the fetched rows are not locked because no FOR UPDATE OF clause is used. So, you might get inconsistent results if another user changes a row after you read it but before you delete it.

Using SQLERRD(3)

For INSERT, UPDATE, and DELETE statements, SQLERRD(3) records the number of rows processed.

SQLERRD(3) is also useful when an error occurs during a table operation. Processing stops at the row that caused the error, so SQLERRD(3) gives the number of rows processed successfully.

Sample Program 3: Fetching in Batches

This program logs on to Oracle8, declares and opens a cursor, fetches in batches using host tables, and prints the results using the PRINT-IT paragraph.

 IDENTIFICATION DIVISION.
PROGRAM-ID. HOST-TABLES.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.

EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 USERNAME PIC X(15) VARYING.
01 PASSWD PIC X(15) VARYING.
01 EMP-REC-TABLES.
05 EMP-NUMBER OCCURS 5 TIMES PIC S9(4) COMP.
05 EMP-NAME OCCURS 5 TIMES PIC X(10) VARYING.
05 SALARY OCCURS 5 TIMES PIC S9(6)V99
DISPLAY SIGN LEADING SEPARATE.
EXEC SQL VAR SALARY IS DISPLAY(8,2) END-EXEC.
EXEC SQL END DECLARE SECTION END-EXEC.

EXEC SQL INCLUDE SQLCA END-EXEC.
01 NUM-RET PIC S9(9) COMP VALUE ZERO.
01 PRINT-NUM PIC S9(9) COMP VALUE ZERO.
01 COUNTER PIC S9(9) COMP.
01 DISPLAY-VARIABLES.
05 D-EMP-NAME PIC X(10).
05 D-EMP-NUMBER PIC 9(4).
05 D-SALARY PIC Z(4)9.99.

PROCEDURE DIVISION.

BEGIN-PGM.
EXEC SQL
WHENEVER SQLERROR DO PERFORM SQL-ERROR
END-EXEC.
PERFORM LOGON.
EXEC SQL
DECLARE C1 CURSOR FOR
SELECT EMPNO, SAL, ENAME FROM EMP
END-EXEC.
EXEC SQL
OPEN C1
END-EXEC.

FETCH-LOOP.
EXEC SQL
WHENEVER NOT FOUND DO PERFORM SIGN-OFF
END-EXEC.
EXEC SQL
FETCH C1 INTO :EMP-NUMBER, :SALARY, :EMP-NAME
END-EXEC.
SUBTRACT NUM-RET FROM SQLERRD(3) GIVING PRINT-NUM.
PERFORM PRINT-IT.
MOVE SQLERRD(3) TO NUM-RET.
GO TO FETCH-LOOP.

LOGON.
MOVE "SCOTT" TO USERNAME-ARR.
MOVE 5 TO USERNAME-LEN.
MOVE "TIGER" TO PASSWD-ARR.
MOVE 5 TO PASSWD-LEN.
EXEC SQL
CONNECT :USERNAME IDENTIFIED BY :PASSWD
END-EXEC.
DISPLAY " ".
DISPLAY "CONNECTED TO ORACLE AS USER: ", USERNAME-ARR.

PRINT-IT.
DISPLAY " ".
DISPLAY "EMPLOYEE NUMBER SALARY EMPLOYEE NAME".
DISPLAY "--------------- ------ -------------".
PERFORM PRINT-ROWS
VARYING COUNTER FROM 1 BY 1 UNTIL COUNTER > PRINT-NUM.

PRINT-ROWS.
MOVE EMP-NUMBER(COUNTER) TO D-EMP-NUMBER.
MOVE SALARY(COUNTER) TO D-SALARY.
DISPLAY D-EMP-NUMBER, " ", D-SALARY, " ",
EMP-NAME-ARR IN EMP-NAME(COUNTER).
MOVE SPACES TO EMP-NAME-ARR IN EMP-NAME(COUNTER).

SIGN-OFF.
SUBTRACT NUM-RET FROM SQLERRD(3) GIVING PRINT-NUM.
IF (PRINT-NUM > 0) PERFORM PRINT-IT.
EXEC SQL CLOSE C1 END-EXEC.
EXEC SQL COMMIT WORK RELEASE END-EXEC.
DISPLAY " ".
DISPLAY "HAVE A GOOD DAY.".
DISPLAY " ".
STOP RUN.

SQL-ERROR.
EXEC SQL WHENEVER SQLERROR CONTINUE END-EXEC.
DISPLAY " ".
DISPLAY "ORACLE ERROR DETECTED:".
DISPLAY " ".
DISPLAY SQLERRMC.
EXEC SQL
ROLLBACK WORK RELEASE
END-EXEC.
STOP RUN.




Prev

Next
Oracle
Copyright © 1997 Oracle Corporation.

All Rights Reserved.

Library

Product

Contents

Index