 |
» |
|
|
|
The SQL commands used for BULK table processing are:
BULK SELECT
BULK FETCH
BULK INSERT
|
BULK SELECT |  |
The BULK SELECT command is useful when the maximum number of
rows in the query result is known at programming time and when the
query result is not too large.
For example, this command might be used in
an application that retrieves a query result containing
a row for each month of the year. The syntax of the BULK SELECT command is:
BULK SELECT SelectList
INTO ArrayName [,StartIndex [,NumberOfRows]]
FROM TableNames
WHERE SearchCondition1
GROUP BY ColumnName
HAVING SearchCondition2
ORDER BY ColumnID
|
Remember, the WHERE, GROUP BY, HAVING, and ORDER BY clauses are
optional.
Note that the order of the select list items must match
the order of the corresponding host variables in the array. In the following example, parts are counted at one of three frequencies or
cycles: 30, 60, or 90 days.
The host variable array needs to contain
only three records, since the query result will never exceed three rows.
EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 PARTSPERCYCLE.
05 EACH-ROW OCCURS 3 TIMES.
01 COUNTCYCLE PIC S9(4) COMP.
01 PARTCOUNT PIC S9(9) COMP.
.
.
.
EXEC SQL BULK SELECT COUNTCYCLE, COUNT(PARTNUMBER)
INTO :PARTSPERCYCLE
FROM PURCHDB.INVENTORY
END-EXEC.
|
The query result is a three row table that describes how many
parts are counted per count cycle. Multiple query results can be retrieved into the same
host variable array by using StartIndex and
NumberOfRows values and executing a BULK SELECT
command multiple times:
EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 PARTSPERCYCLE.
05 EACH-ROW OCCURS 3 TIMES.
01 COUNTCYCLE PIC S9(4) COMP.
01 PARTCOUNT PIC S9(9) COMP.
01 STARTINDEX PIC S9(4) COMP.
01 NUMBEROFROWS PIC S9(4) COMP.
01 LOWBINNUMBER PIC X(16).
01 HIGHBINNUMBER PIC X(16).
.
.
.
EXEC SQL END DECLARE SECTION END-EXEC.
01 COUNTCYCLEFORMAT PIC ZZZZZ9.
01 PARTCOUNTFORMAT PIC ZZZZZ9.
01 I PIC S9(4) COMP.
01 PROMPT PIC X(37).
01 PROMPT1 PIC X(25).
01 RESPONSE.
05 RESPONSE-PREFIX PIC X(1) VALUE SPACE.
05 FILLER PIC X(15) VALUE SPACE.
77 ENTRY-DONE-FLAG PIC X VALUE SPACE.
88 ENTRY-NOT-DONE VALUE SPACE.
88 ENTRY-DONE VALUE "X".
.
.
.
Several variables are initialized:
MOVE 1 TO STARTINDEX.
MOVE 3 TO NUMBEROFROWS.
MOVE SPACE TO ENTRY-DONE-FLAG.
PERFORM SELECT-ROWS UNTIL ENTRY-DONE.
IF STARTINDEX > 1 THEN
PERFORM DISPLAY-ROWS VARYING I FROM 1 BY 1 UNTIL I > STARTINDEX.
.
.
.
.
SELECT-ROWS.
.
The user is prompted for a range of bin numbers or a 0. If bin numbers are entered,
they are used in a BETWEEN predicate in the BULK SELECT command. This WHILE loop can
be executed as many as five times, at which time the array would be filled.
.
MOVE "ENTER A LOW BIN NUMBER OR / TO STOP> " TO PROMPT.
WRITE PROMPT AFTER ADVANCING 1 LINE.
ACCEPT RESPONSE.
IF RESPONSE-PREFIX NOT = "/"
MOVE RESPONSE TO LOWBINNUMBER
MOVE "ENTER A HIGH BIN NUMBER> " TO PROMPT1
WRITE PROMPT1 AFTER ADVANCING 1 LINE
ACCEPT HIGHBINNUMBER
EXEC SQL BULK SELECT COUNTCYCLE, COUNT(PARTNUMBER)
INTO :PARTSPERCYCLE,
:STARTINDEX,
:NUMBEROFROWS
FROM PURCHDB.INVENTORY
WHERE BINNUMBER
BETWEEN :LOWBINNUMBER AND :HIGHBINNUMBER
END-EXEC
COMPUTE STARTINDEX = STARTINDEX + NUMBEROFROWS
IF STARTINDEX = 16 THEN MOVE "X" TO ENTRY-DONE-FLAG
ELSE
MOVE "X" TO ENTRY-DONE-FLAG.
DISPLAY-ROWS.
The final STARTINDEX value can be used to display the final contents of the host variable array:
DISPLAY " ".
MOVE COUNTCYCLE(I) TO COUNTCYCLEFORMAT.
DISPLAY " CountCycle: " COUNTCYCLEFORMAT.
MOVE PARTCOUNT(I) TO PARTCOUNTFORMAT.
DISPLAY " PartCount: " PARTCOUNTFORMAT.
|
The following example illustrates the use of SQLERRD(3) to display
rows stored in the host variable array. It also checks
SQLCODE in conjunction with SQLERRD(3), to determine
whether or not the BULK SELECT executed without error and whether there
may be additional qualified rows for which there was not room in the
array. In each case, an appropriate message is displayed.
The variable MAXIMUMROWS is set to the number of records in the host variable array.
MOVE 25 TO MAXIMUMROWS.
EXEC SQL BULK SELECT ORDERNUMBER, VENDORNUMBER
INTO :ORDERSARRAY
FROM PURCHDB.ORDERS
END-EXEC.
IF SQLCODE = 0
IF SQLERRD(3) = 25
DISPLAY "There may be additional rows "
"that cannot be displayed."
PERFORM DISPLAY-ROWS VARYING I FROM 1 BY 1
UNTIL I > SQLERRD(3)
ELSE
PERFORM DISPLAY-ROWS VARYING I FROM 1 BY 1
UNTIL I > SQLERRD(3).
IF SQLCODE = 100
DISPLAY "No rows were found.".
IF SQLCODE < 0
IF SQLERRD(3) > 0
DISPLAY "The following rows were retrieved "
"before an error occurred:"
PERFORM DISPLAY-ROWS VARYING I FROM 1 BY 1
UNTIL I > SQLERRD(3)
PERFORM SQL-STATUS-CHECK
ELSE
PERFORM SQL-STATUS-CHECK.
DISPLAY-ROWS.
DISPLAY " ".
MOVE ORDERNUMBER (I) TO ORDERNUMBERFORMAT.
DISPLAY " OrderNumber: " ORDERNUMBERFORMAT.
MOVE VENDORNUMBER(I) TO VENDORNUMBERFORMAT.
DISPLAY " VendorNumber: " VENDORNUMBERFORMAT.
|
BULK FETCH |  |
The BULK FETCH command is useful for reporting applications that
operate on large query results or query results whose maximum
size is unknown at programming time.
The syntax of the BULK FETCH command is:
BULK FETCH CursorName
INTO ArrayName [,StartIndex [,NumberOfRows]]
|
You use this command in conjunction with the following cursor commands: DECLARE CURSOR: defines a cursor and associates with it a
query. The cursor declaration should not contain a FOR UPDATE clause,
however, because the BULK FETCH command is designed to be
used for active set retrieval only. The order of the select
list items in the embedded SELECT command must match the order
of the corresponding host variables in the host variable array.
OPEN: defines the active set.
BULK FETCH: delivers rows into the host variable
array and advances the cursor to the last row delivered.
If a single execution of this command does not retrieve
the entire active set, you re-execute it to retrieve subsequent
rows in the active set.
CLOSE: releases ALLBASE/SQL internal buffers used to handle cursor
operations.
To retrieve all the rows in an active set larger than the
host variable array, you can test for a value of 100 in
SQLCODE to determine when you have fetched the last
row in the active set:
EXEC SQL BEGIN DECLARE SECTION END-EXEC.
.
.
.
01 SUPPLIERBUFFER.
05 EACH-ROW OCCURS 20 TIMES.
10 PARTNUMBER PIC X(16).
10 VENDORNAME PIC X(30).
10 DELIVERYDAYS PIC S9(4) COMP.
10 DELIVERYDAYSIND SQLIND.
EXEC SQL END DECLARE SECTION END-EXEC.
RESPONSE PIC X(3).
77 FETCH-FLAG PIC X VALUE SPACE.
88 FETCH-NOT-DONE VALUE SPACE.
88 FETCH-DONE VALUE "X".
.
.
.
EXEC SQL DECLARE SUPPLIERINFO
CURSOR FOR
SELECT PARTNUMBER,
VENDORNAME,
DELIVERYDAYS
FROM PURCHDB.VENDORS,
PURCHDB.SUPPLYPRICE
WHERE PURCHDB.VENDORS.VENDORNUMBER =
PURCHDB.SUPPLYPRICE.VENDORNUMBER
ORDER BY PARTNUMBER
END-EXEC.
EXEC SQL OPEN SUPPLIERINFO END-EXEC.
MOVE SPACE TO FETCH-FLAG.
PERFORM FETCH-ROWS UNTIL FETCH-DONE.
EXEC-SQL CLOSE SUPPLIERINFO END-EXEC.
FETCH-ROWS.
EXEC SQL BULK FETCH SUPPLIERINFO
INTO SUPPLIERBUFFER
END-EXEC.
IF SQLCODE = 0 THEN PERFORM DISPLAY-ROWS.
IF SQLCODE = 100 THEN
DISPLAY "No rows were found."
MOVE "X" TO FETCH-FLAG.
IF SQLCODE < 0 THEN
PERFORM DISPLAY-ROWS
PERFORM SQL-STATUS-CHECK
MOVE "X" TO FETCH-FLAG.
DISPLAY-ROWS.
PERFORM SHOW-FETCH VARYING I FROM 1 BY 1
UNTIL I > SQLERRD(3).
IF SQLCODE = 0 THEN
MOVE "Do you want to see additional rows? (YES/NO)> "
TO PROMPT
WRITE PROMPT AFTER ADVANCING 1 LINE
ACCEPT RESPONSE
IF RESPONSE = "N" OR "n" THEN
MOVE "X" TO FETCH-FLAG.
SHOW-FETCH.
This paragraph displays the values in each row returned by the BULK FETCH command.
|
Each time the BULK FETCH command is executed, the CURRENT row is the
last row put by ALLBASE/SQL into the host variable array.
When the last row in the active set has been fetched, ALLBASE/SQL
sets SQLCODE to 100 the next time the BULK FETCH
command is executed. BULK INSERT |  |
The BULK INSERT command is useful for multiple-row insert operations.
The syntax of the BULK INSERT command is:
BULK INSERT INTO TableName
(ColumnNames)
VALUES (ArrayName [,StartIndex [,NumberOfRows]]
|
As in the case of the simple INSERT command
you can omit ColumnNames when you provide values for all columns
in the target table. ALLBASE/SQL attempts to assign a null value to any
unnamed column. In the following example, a user is prompted
for multiple rows. When the host
variable array is full and/or when the user is finished specifying values,
the BULK INSERT command is executed:
EXEC SQL BEGIN DECLARE SECTION END-EXEC.
.
The user is prompted for three column values, and
the values are assigned to the appropriate record
in the host variable array; then the array row
counter (NumberOfRows)is incremented and the user
asked whether s/he wants to specify another line item:
.
01 NEWPARTS.
05 EACH-ROW OCCURS 20 TIMES.
10 PARTNUMBER PIC X(16).
10 PARTNAME PIC X(30).
10 PARTNAMEIND SQLIND.
10 SALESPRICE PIC S9(8)V99 COMP-3.
10 SALESPRICEIND SQLIND.
01 STARTINDEX PIC S9(4) COMP.
01 NUMBEROFROWS PIC S9(4) COMP.
EXEC SQL END DECLARE SECTION END-EXEC.
01 RESPONSE PIC X(4).
77 ENTRY-DONE-FLAG PIC X VALUE SPACE.
88 ENTRY-NOT-DONE VALUE SPACE.
88 ENTRY-DONE VALUE "X".
.
.
.
MOVE 1 TO STARTINDEX.
MOVE 0 TO NUMBEROFROWS.
MOVE SPACE TO ENTRY-DONE-FLAG.
PERFORM PART-ENTRY UNTIL ENTRY-DONE.
PART-ENTRY.
.
.
.
COMPUTE NUMBEROFROWS = NUMBEROFROWS + 1.
MOVE "Do you want to specify another line item (Y/N)?> "
TO PROMPT.
WRITE PROMPT AFTER ADVANCING 1 LINE.
ACCEPT RESPONSE.
IF RESPONSE = "N" OR "n" THEN
MOVE "X" TO ENTRY-DONE-FLAG
PERFORM BULK-INSERT
ELSE
IF NUMBEROFROWS = 20 THEN
PERFORM BULK-INSERT
MOVE 0 TO NUMBEROFROWS.
BULK-INSERT.
EXEC SQL BULK INSERT INTO PURCHDB.PARTS
(PARTNUMBER,
PARTNAME,
SALESPRICE)
VALUES (:NEWPARTS,
:STARTINDEX,
:NUMBEROFROWS)
END-EXEC.
|
|