Pro*COBOL Precompiler Programmer's Guide Release 8.1.5 A68023-01 |
|
This chapter looks at using tables to simplify coding and improve program performance. You learn how to manipulate Oracle data using host tables, how to operate on all the elements of a host table with a single SQL statement, how to limit the number of table elements processed, and how to use tables of group items.
The main sections are:
A host table is a set of related data items, called elements, associated with a single variable. An indicator variable defined as a table is called an indicator table. An indicator table can be associated with any host table that is NULLABLE.
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.
Tables let you manipulate an entire collection of data items with a single SQL statement. Thus, communications 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.
With few exceptions, you can use host tables wherever scalar host variables are allowed. Also, you can associate an indicator table with any host table.
You declare and dimension host tables in the Data Division. In the following example, three host tables are declared, each dimensioned with 50 elements:
.... 01 EMP-TABLES. 05 EMP-NUMBER OCCURS 50 TIMES PIC S9(4) COMP. 05 EMP-NAME OCCURS 50 TIMES PIC X(10. 05 SALARY OCCURS 50 TIMES PIC S9(5)V99 COMP-3. ....
You can use the INDEXED BY phrase in the OCCURS clause to specify an index, as the next example shows:
... 01 EMP-TABLES. 05 EMP-NUMBER PIC X(10) OCCURS 50 TIMES INDEXED BY EMP-INDX. ... ...
The INDEXED BY phrase implicitly declares the index item EMP-INDX.
Multi-dimensional host tables are not allowed. Thus, the two-dimensional host table declared in the following example is invalid:
... 01 NATION. 05 STATE OCCURS 50 TIMES. 10 STATE-NAME PIC X(25). 10 COUNTY OCCURS 25 TIMES. 15 COUNTY-NAME PIX X(25). ...
Variable-length host tables are not allowed either. For example, the following declaration of EMP-REC is invalid for a host variable:
... 01 EMP-FILE. 05 REC-COUNT PIC S9(3) COMP. 05 EMP-REC OCCURS 0 TO 250 TIMES DEPENDING ON REC-COUNT. ...
The maximum number of bytes accessable by a host table in one fetch is dependent on resources used. If you define 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 number of entries should be the same. Otherwise, a "table size mismatch" warning message is issued at precompile time. If you ignore this warning, the precompiler uses the smallest number of entries for the SQL operation.
If you use multiple host tables in a single SQL statement, their dimensions should be the same. This is not a requirement, however, because Pro*COBOL always uses the smallest dimension for the SQL operation. In the following example, only 25 rows are INSERTed:
WORKING-STORAGE SECTION. EXEC SQL BEGIN DECLARE SECTION END-EXEC. 01 EMP-TABLES. 05 EMP-NUMBER PIC S9(4) COMP OCCURS 50 TIMES. 05 EMP-NAME PIC X(10) OCCURS 50 TIMES. 05 DEPT-NUMBER PIC S9(4) COMP OCCURS 25 TIMES. EXEC SQL END DECLARE SECTION END-EXEC. ... PROCEDURE DIVISION. ... * Populate host tables here. ... EXEC SQL INSERT INTO EMP (EMPNO, ENAME, DEPTNO) VALUES (:EMP-NUMBER, :EMP-NAME, :DEPT-NUMBER) END-EXEC.
Host tables must not be subscripted in SQL statements. For example, the following INSERT statement is invalid:
WORKING-STORAGE SECTION. EXEC SQL BEGIN DECLARE SECTION END-EXEC. 01 EMP-TABLES. 05 EMP-NUMBER PIC S9(4) COMP OCCURS 50 TIMES. 05 EMP-NAME PIC X(10) OCCURS 50 TIMES. 05 DEPT-NUMBER PIC S9(4) COMP OCCURS 50 TIMES. EXEC SQL END DECLARE SECTION END-EXEC. ... PROCEDURE DIVISION. ... PERFORM LOAD-EMP VARYING J FROM 1 BY 1 UNTIL J > 50. ... LOAD-EMP. EXEC SQL INSERT INTO EMP (EMPNO, ENAME, DEPTNO) VALUES (:EMP-NUMBER(J), :EMP-NAME(J), :DEPT-NUMBER(J)) END-EXEC.
You need not process host tables in a PERFORM VARYING statement. Instead, use the un-subscripted table names in your SQL statement. Pro*COBOL treats a SQL statement containing host tables of dimension n like the same statement executed n times with n different scalar host variables, but more efficiently.
You can use indicator tables to assign NULLs to elements in input host tables and to detect NULLs or truncated values (of character columns only) in output host tables. The following example shows how to INSERT with indicator tables:
WORKING-STORAGE SECTION. EXEC SQL BEGIN DECLARE SECTION END-EXEC. 01 EMP-TABLES. 05 EMP-NUMBER PIC S9(4) COMP OCCURS 50 TIMES. 05 DEPT-NUMBER PIC S9(4) COMP OCCURS 50 TIMES. 05 COMMISSION PIC S9(5)V99 COMP-3 OCCURS 50 TIMES. 05 COMM-IND PIC S9(4) COMP OCCURS 50 TIMES. EXEC SQL END DECLARE SECTION END-EXEC. ... PROCEDURE DIVISION. ... * Populate the host and indicator tables. * Set indicator table to all zeros. ... EXEC SQL INSERT INTO EMP (EMPNO, DEPTNO, COMM) VALUES (:EMP-NUMBER, :DEPT-NUMBER, :COMMISSION:COMM-IND) END-EXEC.
The dimension of the indicator table must be greater than, or equal to, the dimension of the host table.
Mixing scalar host variables with host arrays in the VALUES, SET, INTO, or WHERE clause is not allowed. If any of the host variables is an array, all must be arrays.
You cannot use host arrays with the CURRENT OF clause in an UPDATE or DELETE statement.
The array interface is an Oracle extension to the ANSI/ISO embedded SQL standard. However, when you precompile with MODE=ANSI, array SELECTs and FETCHes are still allowed. The use of arrays can be flagged using the FIPS flagger precompiler option, if desired.
When doing array SELECTs and FETCHes, always use indicator arrays. That way, you can test for NULLs in the associated output host array.
When you precompile with the precompiler option DBMS=V7 or V8, if a NULL is selected or fetched into a host variable that has no associated indicator variable, Oracle stops processing, sets sqlca.sqlerrd(3) to the number of rows processed, and returns an error.
When DBMS=V7 or V8, Oracle does not consider truncation to be an error.
Note: If you have a host group item containing tables, you cannot use a table of half-word integer variables for an indicator. You must use a corresponding group item of tables for an indicator. For example, if your group item is the following:
01 DEPARTURE. 05 HOUR PIC X(2) OCCURS 3 TIMES. 05 MINUTE PIC X(2) OCCURS 3 TIMES.
the following indicator variable cannot be used:
01 DEPARTURE-IND PIC S9(4) COMP OCCURS 6 TIMES.
The indicator variable you use with the group item of tables must itself be a group item of tables such as the following:
01 DEPARTURE-IND. 05 HOUR-IND PIC S9(4) COMP OCCURS 3 TIMES. 05 MINUTE-IND PIC S9(4) COMP OCCURS 3 TIMES.
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.
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 define 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 defined the tables with 50 elements:
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 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 define a larger table or declare a cursor for use with the FETCH statement.
If a SELECT INTO statement returns more rows than the size of the table you defined, Oracle8i issues an error message unless you specify SELECT_ERROR=NO. For more information about the option see "SELECT_ERROR".
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:
... 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 DECLARE EMPCURSOR CURSOR FOR SELECT EMPNO, SAL FROM EMP END-EXEC. ... EXEC SQL OPEN EMPCURSOR END-EXEC. ... EXEC SQL WHENEVER NOT FOUND DO PERFORM END-IT. LOOP. EXEC SQL FETCH EMPCURSOR INTO :EMP-NUMBER, :SALARY END-EXEC. * -- process batch of rows ... GO TO LOOP. END-IT. ...
Do not forget to check how many rows were actually returned in the last fetch, and process them.
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.
Each fetch returns, at most, the number of entries in the table. 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)
Using host tables in the WHERE clause of a SELECT statement is allowed only in a sub-query. (For an example, see "Using the WHERE Clause".) 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 7-1 shows which uses of host tables are valid in a SELECT INTO statement:
INTO Clause | WHERE Clause | Valid? |
---|---|---|
table |
table |
no |
scalar |
scalar |
yes |
table |
scalar |
yes |
scalar |
table |
no |
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".)
When UNSAFE_NULL=NO, if you select or fetch a NULL into a host table that lacks an indicator table, Oracle8i stops processing, sets SQLERRD(3) to the number of rows processed, and issues an error message:
When DBMS=V7 or V8, if you select or fetch a truncated column value into a host table that lacks an indicator table, Oracle8i sets SQLWARN(2).
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 doing table selects and fetches, always use indicator tables. That way, if Oracle8i 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.
The following host table sample program can be found in the demo directory.
***************************************************************** * Sample Program 3: Host Tables * * * * This program logs on to ORACLE, declares and opens a cursor, * * fetches in batches using host tables, and prints the results. * ***************************************************************** 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.
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".
An example of inserting with host tables follows:
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. * -- 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).
Host tables must not be subscripted in SQL statements. For example the following INSERT statement is invalid:
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.
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.
You can also use host tables as input variables in an UPDATE statement, as the following example shows:
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. ... * -- 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.
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 a 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 number of entries 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".
Table 7-2 shows which uses of host tables are valid in an UPDATE statement:
SET Clause | WHERE Clause | Valid? |
---|---|---|
table |
table |
yes |
scalar |
scalar |
yes |
table |
scalar |
no |
scalar |
table |
no |
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.
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 the CURRENT OF Clause".
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:
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. * -- 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 number of entries of the indicator table cannot be smaller than the number of entries of the host table.
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. Internally, the value is treated as an unsigned quantity. An attempt to pass a negative value through the use of a signed host variable will result in unpredictable behavior.
Two restrictions keep FOR clause semantics clear: you cannot use the FOR clause in a SELECT statement or with the CURRENT OF clause.
If you use the FOR clause in a SELECT statement, you receive an error message.
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 ...
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.
Pro*COBOL treats a SQL statement containing host tables of number of entries n like the same SQL statement executed n times with n different scalar variables (the individual table elements). The precompiler issues an error message only when such treatment is ambiguous:
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.
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:
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 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.
Pro*COBOL allows the use of tables of group items (also called records) in embedded SQL statements. The tables of group items can be referenced in the INTO clause of a SELECT or a FETCH statement, and in the VALUES list of an INSERT statement.
For example, given the following declaration:
01 TABLES. 05 EMP-TABLE OCCURS 20 TIMES. 10 EMP-NUMBER PIC S9(4) COMP. 10 EMP-NAME PIC X(10). 10 DEPT-NUMBER PIC S9(4) COMP.
the following statement is valid:
EXEC SQL INSERT INTO EMP(EMPNO, ENAME, DEPTNO) VALUES(:EMP-TABLE) END-EXEC.
Assuming that the group item has been filled with data already, the statement bulk inserts 20 rows consisting of the employee number, employee name, and department number into the EMP table.
Make sure that the order of the group items corresponds to the order in the SQL statement.
When using tables of group items, it is also possible to specify individual elementary items of the group. For example, the following statement is also valid. Twenty rows of employee numbers are inserted into the EMPNO column of the EMP table:
EXEC SQL INSERT INTO EMP (EMPNO) VALUES (:EMP-TABLE.EMP-NUMBER) END-EXEC.
When using VARCHAR=YES, if the group item declaration resembles a VARCHAR host variable, then the group item is treated like an elementary item. Therefore, referencing this group item in SQL statements must be done using the group name, but not the elementary item names.
To use an indicator variable, setup a second table of a group item that contains an indicator variable for each variable in the group item:
01 TABLES-IND. 05 EMP-TABLE-IND OCCURS 20 TIMES. 10 EMP-NUMBER-IND PIC S9(4) COMP. 10 EMP-NAME-IND PIC S9(4) COMP. 10 DEPT-NUMBER_IND PIC S9(4) COMP.
The host indicator table of a group item could be used as follows:
EXEC SQL INSERT INTO EMP (EMPNO, ENAME, DEPTNO) VALUES (:EMP-TABLE:EMP-TABLE-IND) END-EXEC.
You can use an individual element of the indicator group item. with a component of the group item when inserting:
EXEC SQL INSERT INTO EMP (EMPNO) VALUES (:EMP-TABLE.EMP-NUMBER:EMP-TABLE-IND.EMP-NUMBER-IND) END-EXEC.
If the exact characteristics of the data are known, it is convenient to specify an elementary item indicator for a group item:
05 EMP-TABLE-IND PIC S9(4) COMP OCCURS 20 TIMES.
Host tables of group items cannot have group items that are tables. For example:
01 TABLES. 05 EMP-TABLE OCCURS 20 TIMES. 10 EMP-NUMBER PIC S9(4) COMP OCCURS 10 TIMES. 10 EMP-NAME PIC X(10). 10 DEPT-NUMBER PIC S9(4) COMP.
EMP-TABLE
cannot be used as a host variable because EMP-NUMBER
is a table.
Host tables of nested group items are not allowed. For example:
01 TABLES. 05 TEAM-TABLE OCCURS 20 TIMES 10 EMP-TABLE 15 EMP-NUMBER PIC S9(4) COMP. 15 EMP-NAME PIC X(10). 10 DEPT-TABLE. 15 DEPT-NUMBER PIC S9(4) COMP. 15 DEPT-NAME PIC X(10).
TEAM-TABLE
cannot be used as a host variable because its members (EMP-TABLE
and DEPT-TABLE
) are group items themselves.
Finally, the restrictions that apply to host tables in Pro*COBOL also apply to tables of group items:
This program logs on, declares and opens a cursor, fetches in batches using a table of group items. Read the initial comments for details.
***************************************************************** * Sample Program 14: Tables of group items * * * * This program logs on to ORACLE, declares and opens a cursor, * * fetches in batches using a table of group items , and prints * * the results. This sample is identical to sample3 except that * * instead of using three separate host tables of five elements * * each, it uses a five-element table of three group items. * * The output should be identical. * ***************************************************************** IDENTIFICATION DIVISION. PROGRAM-ID. TABLE-OF-GROUP-ITEMS. 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-TABLE OCCURS 5 TIMES. 05 EMP-NUMBER PIC S9(4) COMP. 05 SALARY PIC S9(6)V99 DISPLAY SIGN LEADING SEPARATE. 05 EMP-NAME PIC X(10) VARYING. 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-REC-TABLE 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.