DataDirect ODBC Drivers | The CP Preprocessor |
>>---EXEC SQL---BEGIN DECLARE SECTION---END-EXEC---><
The BEGIN DECLARE SECTION statement can be included anywhere that COBOL permits variable declaration. Use END DECLARE SECTION to identify the end of a COBOL declaration section.
If data structures are defined within a declaration section then, in general, only the bottom-level items (with PIC clauses) can be used as host variables. Two exceptions are arrays specified in FETCH statements and record structures specified in SELECT INTO statements.
WORKING-STORAGE SECTION. EXEC SQL BEGIN DECLARE SECTION END-EXEC 01 staff-id pic x(4). 01 last-name pic x(30). EXEC SQL END DECLARE SECTION END-EXEC
>>--EXEC SQL--.-BEGIN TRAN--------.-.------------------.--> +-BEGIN TRANSACTION-+ +-transaction_name-+ >--END-EXEC--><
transaction_name | An optional identifier that is ignored. |
Use the BEGIN TRAN statement in AUTOCOMMIT mode to open a transaction. After you have opened the transaction in AUTOCOMMIT mode, you should execute a COMMIT or ROLLBACK statement to close the transaction and cause a return to AUTOCOMMIT mode.
The BEGIN TRAN statement provides compatibility with Embedded SQL implementations that do not conform to the ANSI SQL standard with respect to transaction management and, in particular, the Micro Focus Embedded SQL Toolkit for Microsoft SQL Server.
If you are not opening a transaction in AUTOCOMMIT mode this statement has no effect.
EXEC SQL BEGIN TRANSACTION END-EXEC
>>--EXEC SQL---.----------------.--.--------------.--> +-FOR :row_count-+ +-:result_hvar-+ >--CALL stored_procedure_name--.-------------.---> | +-- , --+ | | v + | +-(parameter)-+ >--END-EXEC--><
:row_count | An integer host variable that specifies the number of rows to be used if the result and parameter host variables are all arrays of the same size, and not all elements should be used. You cannot use the FOR clause if the CALL is part of a DECLARE CURSOR statement. |
:result_hvar | A host variable to receive the procedure result. |
stored_procedure_name | The name of the stored procedure. |
parameter | A literal, the keyword CURSOR or a host variable
parameter of the form:
[keyword=] :param_hvar [IN | INPUT | INOUT | OUT | OUTPUT] where: keyword is the formal parameter name for a keyword parameter. :param_hvar is a host variable. IN specifies an input parameter. INPUT specifies an input parameter. INOUT specifies an input/output parameter. OUT specifies an output parameter. OUTPUT specifies an output parameter. CURSOR is used only for Oracle 8 stored procedures which return a result set. Its use causes the corresponding parameter to be unbound. |
For more details about stored procedures, see the section Stored Procedures in the chapter OpenESQL.
The CALL statement is used to execute a stored procedure.
EXEC SQL CALL myProc(param1,param2) END-EXEC EXEC SQL :myResult = CALL myFunction(namedParam=:paramValue) END-EXEC EXEC SQL CALL getDept(:empName IN, :deptName OUT) END-EXEC EXEC SQL DECLARE cities CURSOR FOR CALL locateStores(:userState) END-EXEC
>>--EXEC SQL--CLOSE--cursor_name--END-EXEC--><
cursor_name | A previously declared and opened cursor. |
The CLOSE statement discards unprocessed rows and frees any locks held by the cursor. The cursor must be declared and opened before it can be closed. All open cursors are closed automatically at the end of the program.
* Declare the cursor... EXEC SQL DECLARE C1 CURSOR FOR SELECT staff_id, last_name FROM staff END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not declare cursor.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF EXEC SQL OPEN C1 END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not open cursor.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT CURRENT END-EXEC STOP RUN END-IF PERFORM UNTIL sqlcode NOT = ZERO * SQLCODE will be zero as long as it has successfully * fetched data EXEC SQL FETCH C1 INTO :staff-staff-id, :staff-last-name END-EXEC IF SQLCODE = ZERO DISPLAY "Staff ID: " staff-staff-id DISPLAY "Staff member's last name: " staff-last-name END-IF END-PERFORM EXEC SQL CLOSE C1 END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not close cursor.' DISPLAY SQLERRMC DISPLAY SQLERRML END-IF
>>--EXEC SQL--COMMIT--.-------------.--.---------.--> +-WORK--------+ +-RELEASE-+ +-TRAN--------+ +-TRANSACTION-+ >--END-EXEC--><
WORK | WORK, TRAN and TRANSACTION are optional and synonymous. |
RELEASE | If RELEASE is specified and the transaction was successfully committed, the current connection is closed. |
The COMMIT statement makes any changes made by the current transaction on the current connection permanent in the database.
* Ensure that multiple records are not inserted for a * member of staff whose staff_id is 99 EXEC SQL DELETE FROM staff WHERE staff_id = 99 END-EXEC * Insert dummy values into table EXEC SQL INSERT INTO staff (staff_id ,last_name ,first_name ,age ,employment_date) VALUES (99 ,'Lee' ,'Phil' ,19 ,'1992-01-02') END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not insert dummy values.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF EXEC SQL COMMIT END-EXEC * Check it was committed OK IF SQLCODE = ZERO DISPLAY 'Error: Could not commit values.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT CURRENT END-EXEC STOP RUN END-IF DISPLAY 'Values committed.' * Delete previously inserted data EXEC SQL DELETE FROM staff WHERE staff_id = 99 END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not delete dummy values.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF * Check data deleted OK, commit and release the connection IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not delete values.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF EXEC SQL COMMIT WORK RELEASE END-EXEC * Check data committed OK and release the connection. IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not commit and release.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT CURRENT END-EXEC END-IF DISPLAY 'Values committed and connection released.'
>>--EXEC SQL--CONNECT TO--.-------------.---------------> +-data_source-+ >--.------------.--USER--.------------------.----------> +-AS db_name-+ +-user-.-----------+ +-.password-+ >--.--------------------.------------------------------> +-WITH-.----.-PROMPT-+ +-NO-+ >--.-----------------------------.--END-EXEC-->< +-RETURNING output_connection-+
>>--EXEC SQL--CONNECT user--.------------------------.--> +-IDENTIFIED BY password-+ +-------"/"password------+ >--.--------------.--.--------------------.------------> +--AT db_name--+ +--USING data_source-+ >--.--------------------.------------------------------> +-WITH-.----.-PROMPT-+ +-NO-+ >--.-----------------------------.--END-EXEC-->< +-RETURNING output_connection-+
>>--EXEC SQL--CONNECT WITH PROMPT----------------------> >--.-----------------------------.--END-EXEC-->< +-RETURNING output_connection-+
>>--EXEC SQL--CONNECT RESET-.------.--END-EXEC-->< +-name-+
>>--EXEC SQL--CONNECT DSN input_connection------------> >--.-----------------------------.--END-EXEC-->< +-RETURNING output_connection-+
>>--EXEC SQL--CONNECT USING input_connection----------> >--.------------.--.--------------------.------------> +-AT db_name-+ +-WITH-.----.-PROMPT-+ +-NO-+ >--.------------------------------.--END-EXEC-->< +-RETURNING output_connection--+
data_source | The name of the ODBC data source. If you omit data_source, the default ODBC data source is assumed. The data source can be specified as a literal or as a host variable. |
db_name | A name for the connection. Connection names can have as many as 30 characters, and can include alphanumeric characters and any symbols legal in filenames. The first character must be a letter. Do not use Embedded SQL keywords or CURRENT or DEFAULT or ALL for the connection name; they are invalid. If db_name is omitted, DEFAULT is assumed. db_name can be specified as a literal or a host variable. |
user | A valid user-id at the specified data source. |
password | A valid password for the specified user-id. |
output_connection | A PIC X(n) text string defined by ODBC as the connection string used to connect to a particular data source. Subsequently, you can specify this string as the input_connection in a CONNECT USING statement. |
input_connection | A PIC X(n) text string containing connection information used by ODBC to connect to the data source. The test string can be either a literal or a host variable. |
RESET | Resets (disconnects) the specified connection. |
name | You can specify name as CURRENT, DEFAULT or ALL. |
The CONNECT statement attaches to a specific database using the supplied user-id and password.
If you use only one connection, you do not need to supply a name for the connection. When you use more than one connection, you must specify a name for each connection. Connection names are global within a process. Named connections are shared by separately compiled programs that are linked into a single executable module.
After a successful CONNECT statement, all database transactions other than CONNECT RESET work through this most recently declared current connection. To use a different connection, use the SET CONNECTION statement.
Use CONNECT DSN and CONNECT USING to simplify administration.
With CONNECT TO, CONNECT, CONNECT DSN and CONNECT USING, you can return connection information to the application.
Notes:
* Connection method 1 MOVE 'servername' TO svr MOVE 'username.password' TO usr EXEC SQL CONNECT TO :svr USER :usr END-EXEC * Connection method 2 EXEC SQL CONNECT 'username.password' USING 'servername' END-EXEC * Connection method 3 EXEC SQL CONNECT WITH PROMPT END-EXEC
* Connection method 4 EXEC SQL CONNECT RESET END-EXEC * Connection method 5 EXEC SQL CONNECT USING FileDSN=Oracle8;PWD=tiger' END-EXEC
The example above uses a File DSN.
* Connection method 6 01 connectString PIC X(72) value 'DRIVER={Microsoft Excel Driver (*.xls)}; '&'DBQ=c:\demo\demo.xls;' &'DRIVERID=22'. procedure division. EXEC SQL CONNECT USING :connectString END-EXEC
The example above connects to an Excel spreadsheet without setting up a data source.
>>--EXEC SQL--.------------.--DECLARE cursor_name-----> +-AT db_name-+ >--.-------------.--.-----------.--.-------------.---> +-SENSITIVE---+ +-FORWARD---+ +-LOCK--------+ +-INSENSITIVE-+ +-KEYSET----+ +-LOCKCC------+ +-DYNAMIC---+ +-OPTIMISTICD-+ +-STATIC----+ +-OPTCC-------+ +-SCROLL----+ +-OPTCCVAL----+ +-READ ONLY---+ +-READONLY----+ >--CURSOR--.-----------.-----------------------------> +-WITH HOLD-+ >--FOR--.----------------------------.---------------> +-select_stmt----------------+ +-stored_procedure_call_stmt-+ +-prepared_stmt_name---------+ >--.-------------------------------.--END-EXEC-->< +-FOR READ ONLY-----------------+ +-FOR UPDATE-.----------------.-+ +-OF column_list-+
db_name | The name of a database that has been declared using DECLARE DATABASE. |
cursor_name | Cursor name used to identify the cursor in subsequent statements. Cursor names can contain any legal filename character and be up to 30 characters in length. The first character must be a letter. |
select_stmt | Any valid SQL SELECT statement, or a QUERY ODBC statement or a CALL statement for a stored procedure that returns a result set. |
prepared_stmt_name | The name of a prepared SQL SELECT statement or QUERY ODBC statement. |
stored_procedure_call_stmt | A valid stored procedure call which returns a result set. |
column_list | A list of column names, separated by commas |
The DECLARE CURSOR statement associates the cursor name with the specified SELECT statement and enables you to retrieve rows of data using the FETCH statement.
Two separately compiled programs cannot share the same cursor. All statements that reference a particular cursor must be compiled together.
The DECLARE CURSOR statement must appear before the first reference to the cursor. The SELECT statement runs when the cursor is opened. The following rules apply to the SELECT statement:
Notes:
EXEC SQL DECLARE C1 CURSOR FOR SELECT last_name, first_name FROM staff END-EXEC EXEC SQL DECLARE C2 CURSOR FOR QUERY ODBC COLUMNS TABLENAME 'staff' END-EXEC
>>--EXEC SQL--DECLARE db_name--DATABASE--END-EXEC--><
db_name | A name associated with a database. It must be an identifier and not a host variable. It cannot contain quotation marks. |
The DECLARE DATABASE statement declares the name of a database. You must DECLARE db_name before using a CONNECT AT db_name statement.
Note: You cannot use DECLARE DATABASE with EXECUTE IMMEDIATE or with PREPARE and EXECUTE.
>>--EXEC SQL--DELETE--FROM--table_name----------------> >--WHERE CURRENT OF--cursor_name--END-EXEC--><
table_name | The same table used in the SELECTFROM option (see DECLARE CURSOR). |
cursor_name | A previously declared, opened, and fetched cursor. |
ODBC supports positioned delete, which deletes the row most recently fetched by using a cursor, in the Extended Syntax (it was in the Core Syntax for ODBC 1.0 but was moved to the Extended Syntax for ODBC 2.0). Not all drivers provide support for positioned delete, although OpenESQL sets ODBC cursor names to be the same as COBOL cursor names to facilitate positioned update and delete.
With some ODBC drivers, the select statement used by the cursor must contain a "FOR UPDATE" clause to enable positioned delete.
You cannot use host arrays with positioned delete.
The other form of DELETE used in standard SQL statements is known as a searched delete.
Most data sources require specific combinations of SCROLLOPTION and CONCURRENCY to be specified either by SET statements or in the DECLARE CURSOR statement.
The ODBC cursor libray provides a restricted implementation of positioned delete which can be enabled by compiling with SQL(USECURLIB=YES) and using SCROLLOPTION STATIC and CONCURRENCY OPTCCVAL (or OPTIMISTIC).
* Declare a cursor for update EXEC SQL DECLARE C1 CURSOR FOR SELECT staff_id, last_name FROM staff FOR UPDATE END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not declare cursor for update.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF * Open the cursor EXEC SQL OPEN C1 END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not open cursor for update.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF * Display staff member's details and give user the * opportunity to delete particular members. PERFORM UNTIL SQLCODE NOT = ZERO EXEC SQL FETCH C1 INTO :staff-id,:last-name END-EXEC IF SQLCODE = ZERO DISPLAY 'Staff ID: ' staff-id DISPLAY 'Last name: ' last-name DISPLAY 'Delete <y/n>? ' WITH NO ADVANCING ACCEPT usr-input IF usr-input = 'y' EXEC SQL DELETE FROM staff WHERE CURRENT OF C1 END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not delete record.' DISPLAY SQLERRMC DISPLAY SQLERRML END-IF END-IF END-IF END-PERFORM
>>--EXEC SQL--.-------------------.--DELETE--.------.--> +-FOR :host_integer-+ +-FROM-+ >--.-table_name-.--.-------------------------.--------> +-view_name--+ +-WHERE search_conditions-+ >--END-EXEC--><
:host_integer | A host variable that specfies the maximum number of host array elements processed. Must be declared as PIC S9(4) COMP-5. |
FROM | An optional keyword. It is required for ANSI SQL 92 conformance. |
table_name | The target table for the delete operation. |
view_name | The target view for the delete operation. |
WHERE | A standard SQL WHERE clause identifying the row to be deleted. |
search_conditions | Any valid expression that can follow the standard SQL WHERE clause. |
DELETE is a standard SQL statement. See the documentation supplied with your ODBC driver for the exact syntax.
You cannot mix simple host variables with host arrays in the WHERE clause. If one of the host variables is an array, they must all be arrays.
The DELETE (SEARCHED) statement removes table rows that meet the search criteria. If you do not specify a WHERE clause, all of the rows in the named table are removed.
EXEC SQL DELETE FROM staff WHERE staff_id = 99 END-EXEC
>>--EXEC SQL--DESCRIBE--.---------------------.-------> +-SELECT LIST FOR-----+ +-BIND VARIABLES FOR--+ >--prepared_stmt_name--INTO--:sqlda_struct--END-EXEC--><
prepared_stmt_name | The name of a prepared SQL SELECT statement or QUERY ODBC statement. |
:sqlda_struct | A host variable specifying the output SQLDA data structure to be populated. The colon is optional to provide compatibility with other embedded SQL implementations. |
The DESCRIBE statement provides information on prepared dynamic SQL statements. This statement populates the specified SQLDA data structure with the data type, length, and column name of each column returned by the specified prepared statement.
If neither SELECT LIST FOR or BIND VARIABLES FOR is specified, SELECT LIST is used by default. If BIND VARIABLES FOR is specified, information about input parameters is returned in the SQLDA rather than information about results columns.
The DESCRIBE statement inserts the number of columns into the sqld field of the SQLDA structure. If a non-select statement was prepared, sqld is set to 0. Before DESCRIBE is called, the following fields in the SQLDA data structure must be initialised by the application:
sqln | The maximum number of sqlvar (column descriptor) entries that the structure can accommodate. |
sqldabc | The maximum size of the SQLDA. This is calculated as sqln * 44 + 16 |
If sqln is set to 0, no column descriptor entries are constructed, but sqld is set to the number of entries required. The DESCRIBE statement works in a similar way to a PREPARE statement with an INTO clause.
Note:
Few drivers fully implement the ODBC calls necessary for DESCRIBE BIND VARIABLES
EXEC SQL INCLUDE SQLDA END-EXEC EXEC SQL BEGIN DECLARE SECTION END-EXEC 01 statement pic x(80). EXEC SQL END DECLARE SECTION END-EXEC EXEC SQL DECLARE C1 CURSOR FOR stmt1 END-EXEC move "select * from dept" into statement move 20 to sqln compute sqldabc = 16 + 44 * sqln EXEC SQL PREPARE stmt1 FROM :statement END-EXEC EXEC SQL DESCRIBE stmt1 INTO :sqlda END-EXEC * The data structure "sqlda" now contains a * description of the dynamic SQL statement. EXEC SQL OPEN C1 END-EXEC * Complete the SQLDA, by adding buffer addresses and lengths EXEC SQL FETCH C1 USING DESCRIPTOR :sqlda END-EXEC
>>--EXEC SQL--DISCONNECT--.-name----.--END-EXEC-->< +-ALL-----+ +-CURRENT-+ +-DEFAULT-+
name | The connection name. |
ALL | Disconnects all connections (including automatic connections made when the INIT option of the SQL Compiler directive is used). |
CURRENT | Disconnects the current connection. The current connection is either the most recent connection established by a CONNECT statement or a subsequent connection set by a SET CONNECTION statement. |
DEFAULT | Disconnects the default connection. This is the connection made by a CONNECT statement which did not specify a connection name. |
The DISCONNECT statement closes the connection(s) to a database. In addition, all cursors opened for that connection are automatically closed.
EXEC SQL CONNECT TO "srv1" AS server1 USER "sa." END-EXEC EXEC SQL CONNECT TO "srv2" AS server2 USER "sa." END-EXEC EXEC SQL DISCONNECT server1 END-EXEC EXEC SQL DISCONNECT server2 END-EXEC.
>>--EXEC SQL--END DECLARE SECTION--END-EXEC--><
The END DECLARE SECTION statement terminates a host variable declaration section begun by a BEGIN DECLARE SECTION statement.
WORKING-STORAGE SECTION. EXEC SQL BEGIN DECLARE SECTION END-EXEC 01 staff-id pic x(4). 01 last-name pic x(30). EXEC SQL END DECLARE SECTION END-EXEC
>>--EXEC SQL-.----------------.--EXECSP-.--------------.--> +-FOR :row_count-+ +-:result_hvar-+ >--stored_procedure_name--.-------------.----------------> | +-- , --+ | | v | | +-(parameter)-+ >--.----------------.--END-EXEC-->< +-WITH RECOMPILE-+
:row_count | An integer host variable which specifies the number of elements to be used if the result and parameter host variables are all arrays of the same size, and not all elements should be used. The FOR clause cannot be used if the EXECSP is part of a DECLARE CURSOR statement. |
:result_hvar | A host variable to receive the procedure result. |
stored_procedure_name | The name of the stored procedure. |
parameter | A literal or a host variable parameter of the form:
[keyword=] :param_hvar [OUT | OUTPUT] where: keyword is the formal parameter name for a keyword parameter. :param_hvar is a host variable. OUT specifies an output parameter. OUTPUT specifies an output parameter. |
WITH RECOMPILE | Is ignored and has no effect. It is allowed for syntax compatibility only. |
For more details about stored procedures, see the section Stored Procedures in the chapter OpenESQL.
The EXECSP statement is used to execute a stored procedure. It is an alternative to the CALL statement and provides backwards compatibility with the Micro Focus Embedded SQL Toolkit for Microsoft SQL Server. Wherever possible, the CALL statement should be used in preference to EXECSP.
EXEC SQL EXECSP myProc param1,param2 END-EXEC EXEC SQL EXECSP :myResult = myFunction namedParam = :paramValue END-EXEC EXEC SQL EXECSP getDept :empName, :deptName OUT END-EXEC EXEC SQL DECLARE cities CURSOR FOR EXECSP locateStores :userState END-EXEC
>>--EXEC SQL--.----------------.--EXECUTE------------------> +-FOR :row_count-+ >--prepared_stmt_name-.---------------------------------.-> +--USING DESCRIPTOR :sqlda_struct-+ | +--- , -----+ | | v | | +--USING :hvar--------------------+ >--END-EXEC--><
:row_count | An integer host variable that specifies the number of rows to be used if the result and parameter host variables are all arrays of the same size, and not all elements should be used. You cannot use the FOR clause if the EXECUTE is part of a DECLARE CURSOR statement. |
prepared_stmt_name | A previously prepared SQL statement. |
:sqlda_struct | A host variable that specifies a previously declared SQLDA data structure containing a description of the input values. The colon is optional to provide compatibility with other embedded SQL implementations. |
:hvar | One or more input host variables. |
The EXECUTE statement processes dynamic SQL statements. It runs the specified prepared SQL statement after substituting values for any parameter markers. (Prepared statements are created using the PREPARE statement.) Only statements that do not return results are permitted.
If the prepared statement contains parameter markers, the EXECUTE statement must include either the USING :hvar option with the same number of host variables or the USING DESCRIPTOR :sqlda_struct option identifying a SQLDA data structure already populated by the application.
The number of parameter markers in the prepared statement must match the number of sqldata entries (USING DESCRIPTOR :sqlda) or host variables (using :hvar).
* Store statement to be dynamically executed... MOVE "INSERT INTO staff VALUES(?,?,?,?,?)" TO stmtbuf. * Ensure attempt is not made to insert an existing record EXEC SQL DELETE FROM staff WHERE staff_id = 99 END-EXEC * Prepare the statement EXEC SQL PREPARE st FROM :stmtbuf END-EXEC. MOVE 99 TO staff-id MOVE 'Lee' TO last-name MOVE 'Phil' TO first-name MOVE 19 TO age MOVE '1997-01-01' TO employment-date * Execute the statement with current values. EXEC SQL EXECUTE st USING :staff-id, :last-name ,:first-name, :age, :employment-date END-EXEC IF SQLCODE = ZERO DISPLAY 'Statement executed.' ELSE DISPLAY 'Error: Could not execute statement.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF * Finally, remove the entry EXEC SQL DELETE FROM staff where staff_id = 99 END-EXEC IF SQLCODE = ZERO DISPLAY 'Values deleted.' ELSE DISPLAY 'Error: Could not delete inserted values.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF
>>--EXEC SQL--.-------------------.--EXECUTE IMMEDIATE--> +-FOR :row_count----+ >--:stmt_hvar--END-EXEC-><
:row_count | An integer host variable that specifies the number of rows to be used if the result and parameter host variables are all arrays of the same size, and not all elements should be used. You cannot use the FOR clause if the EXECUTE IMMEDIATE is part of a DECLARE CURSOR statement. |
:stmt_hvar | A character string host variable. |
The EXECUTE IMMEDIATE statement cannot contain input parameter markers or host variables. It cannot return results; any results returned from this statement are discarded. Additionally, the statement cannot contain SQL keywords that pertain exclusively to Embedded SQL.
If any rows are returned, SQLCODE is set to +1.
EXECUTE IMMEDIATE must be used for SET statements specific to the Microsoft SQL Server (that is, those that are intended to execute at that server).
EXEC SQL DELETE FROM staff WHERE staff_id = 99 END-EXEC * Put the required SQL statement in prep. MOVE "insert into staff (staff_id, last_name, " & "first_name, age, employment_date) VALUES (99, " & "'Lee', 'Phillip',19, '1992-01-02')" TO prep * Note EXECUTE IMMEDIATE does not require the statement to * be prepared EXEC SQL EXECUTE IMMEDIATE :prep END-EXEC * Check it worked... IF SQLCODE = ZERO DISPLAY 'Statement executed OK.' ELSE DISPLAY 'Error: Statement not executed.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF * Run through the same procedure again, this time deleting * the values just inserted MOVE "delete from staff where staff_id = 99" TO prep EXEC SQL EXECUTE IMMEDIATE :prep END-EXEC IF SQLCODE = ZERO DISPLAY 'Statement executed OK.' ELSE DISPLAY 'Error: Statement not executed.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF
>>--EXEC SQL-.-------------------.--------------------> +-FOR :host_integer-+ >--FETCH--.----------.--cursor_name------------------> +-PREVIOUS-+ +-LAST-----+ +-PRIOR----+ +-FIRST----+ +-NEXT-----+ >--.--------------------------------.--END-EXEC-->< +-USING DESCRIPTOR :sqlda_struct-+ | +-- , ----+ | | v | | +--INTO :hvar--------------------+
:host_integer | A host variable that specifies the maximum number of host array elements processed. Must be declared as PIC S9(4) COMP-5 |
cursor_name | A previously declared and opened cursor. |
:sqlda_struct | A host variable that specifies an SQLDA data structure previously populated by the DESCRIBE statement and containing output value addresses. This option is used only with a cursor declared by a prepared SELECT statement. (SELECT statements are prepared using the PREPARE statement.) The colon is optional to provide compatibility with other embedded SQL implementations. |
:hvar | Identifies one or more host variables to receive the data. |
The FETCH statement retrieves a row from the cursor's results set and writes the values of the columns in that row to the corresponding host variables (or to addresses specified in the SQLDA data structure). By default, the FETCH statement retrieves the next row, but you can also specify the previous row, last row, prior row or first row. If there are no more rows to fetch, SQLCODE is set to 100 and SQLSTATE is set to "02000".
An OPEN cursor_name statement must precede a FETCH statement, and the cursor must be open while FETCH runs. If you use PREVIOUS, LAST, PRIOR, FIRST, or NEXT, you must also set the appropriate cursor options via the DECLARE CURSOR statement or the SET SCROLLOPTION and SET CONURRENCY statements. Also, the data type of the host variable must be compatible with the data type of the corresponding database column.
If the number of columns is less than the number of host variables, the value of SQLWARN3 is set to W. If an error occurs, no further columns are processed. (Processed columns are not undone.)
Alternatively, the :hvar variable can specify a COBOL record that contains several fields, each corresponding to a column in the select list of the cursor declaration statement. To use this form, you must specify the DB2 option of the SQL Compiler directive. (Note that this will cause PREPARE INTO and DESCRIBE statements to be rejected by the COBOL compiler).
If ANSI92ENTRY is set, then attempting to fetch a null value will set SQLCODE to -19425 if there is no null indicator. If ANSI92ENTRY is not set, SQLCODE will be 0. In both cases, SQLSTATE will be 22002 and SQLWARN2 will be W.
If one of the host variables in the INTO clause is an array, they must all be arrays.
* Declare a cursor for a given SQL statement. EXEC SQL DECLARE C1 CURSOR FOR SELECT last_name, first_name FROM staff END-EXEC EXEC SQL OPEN C1 END-EXEC * Fetch the current values from the cursor into the host * variables and if everything goes ok, display the values * of the host variables PERFORM UNTIL SQLCODE NOT = ZERO EXEC SQL FETCH C1 INTO :lname,:fname END-EXEC IF SQLCODE NOT = ZERO AND SQLCODE NOT = 100 DISPLAY 'Error: Could not perform fetch' DISPLAY SQLERRML DISPLAY SQLERRMC EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF DISPLAY 'First name: 'fname DISPLAY 'Last name : 'lname DISPLAY SPACES END-PERFORM
>>--EXEC SQL--INCLUDE--.-SQLCA----.--END-EXEC-->< +-SQLDA----+ +-filename-+
SQLCA | Indicates that a SQLCA data structure is accessed. |
SQLDA | Indicates that a SQLDA data structure is accessed. |
filename | Indicates that a file should be included in the source at this point (this is equivalent to the COBOL COPY facility). |
This statement includes the definition of the specified SQL data structure or source file in the COBOL program.
This statement uses the corresponding .cpy file. Ensure that sqlca.cpy and sqlda.cpy are in the current directory or that the COBCPY environment variable specifies the directory that contains them.
EXEC SQL INCLUDE SQLCA END-EXEC EXEC SQL INCLUDE SQLDA END-EXEC EXEC SQL INCLUDE MYFILE END-EXEC
>>--EXEC SQL-.-------------------.--.------------.-------> +-FOR :host_integer-+ +-AT db_name-+ >--INSERT--.------.--.-table_name-.--.---------------.--> +-INTO-+ +-view_name--+ +-(column_list)-+ +-------- , ------+ v | >--VALUES (constant_expression)--END-EXEC--><
:host_integer | A host variable that specifies the maximum number of host array elements processed. Must be declared as PIC S9(4) COMP-5 |
db_name | The name of a database that has been declared using DECLARE DATABASE. |
table_name | The table into which rows are to be inserted. |
view_name | The view into which rows are to be inserted. |
INTO | An optional keyword. Required for ANSI SQL 92 conformance. |
column_list | A list of one or more columns to which data is to be
added. The columns can be in any order, but the incoming data must be in
the same order as the columns. The column list is necessary only when
some, but not all, columns in the table are to receive data. Enclose the
items in the column list in parentheses. If no column list is given, all
the columns in the receiving table (in CREATE TABLE order) are assumed.
The column list determines the order in which values are entered. |
VALUES | Introduces a list of constant expressions. |
constant_expression | Constant or null values for the indicated columns. The values list must be enclosed in parentheses and must match the explicit or implicit columns list. Enclose non-numeric constants in single or quotation marks. |
The INSERT statement is passed directly to the ODBC driver. See the documentation supplied with your ODBC driver for the exact syntax.
If the host variables in the WHERE clause are arrays, the INSERT statement is executed once for each set of array elements.
The INSERT statement adds new rows to a table; use UPDATE to modify column values in an existing row.
You can omit items in the column list and VALUES list providing that the omitted columns are defined to allow null values.
You can select rows from a table and insert them into the same table in a single statement.
*Declare the cursor... EXEC SQL DECLARE C1 CURSOR FOR SELECT staff_id, last_name FROM staff END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not declare cursor.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF EXEC SQL OPEN C1 END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not open cursor.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT CURRENT END-EXEC STOP RUN END-IF PERFORM UNTIL sqlcode NOT = ZERO * SQLCODE will be zero as long as it has successfully * fetched data EXEC SQL FETCH C1 INTO :staff-staff-id, :staff-last-name END-EXEC IF SQLCODE = ZERO DISPLAY "Staff ID: " staff-staff-id DISPLAY "Staff member's last name: " staff-last-name END-IF END-PERFORM EXEC SQL CLOSE C1 END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not close cursor.' DISPLAY SQLERRMC DISPLAY SQLERRML END-IF
>>--EXEC SQL--OPEN--cursor_name------------------------> >--.---------------------------------.--END-EXEC-->< +--USING DESCRIPTOR :sqlda_struct-+ | +---- , ----+ | | v | | +--USING :hvar--------------------+
cursor_name | A previously declared cursor. |
:sqlda_struct | A host variable that specifies an SQLDA data structure previously constructed by the application. The SQLDA data structure contains the address, data type, and length of each input parameter. This option is used only with a cursor that references a prepared SQL statement in the DECLARE statement. The colon is optional to provide compatibility with other embedded SQL implementations. |
:hvar | One or more input host variables corresponding to parameter markers in the SELECT statement. This option is used only with a cursor that references a prepared SQL statement in the DECLARE statement. |
The OPEN statement runs the SELECT statement specified in the corresponding DECLARE CURSOR statement to produce the results set that is accessed one row at a time by the FETCH statement.
If the cursor is declared with a static SELECT statement (that is, one that was not prepared), the SELECT statement can contain host variables but not parameter markers. The current values of the host variables are substituted when the OPEN statement runs. For a statically declared cursor, the OPEN statement cannot contain the USING :hvar or USING DESCRIPTOR :sqlda_struct option.
If the cursor is declared with a dynamic SELECT statement (that is, one that was prepared), the SELECT statement can contain parameter markers but not host variables. Parameter markers can appear wherever column values are allowed in the SELECT statement. If the SELECT statement has parameter markers, the OPEN statement must include either the USING :hvar option with the same number of host variables or the USING DESCRIPTOR :sqlda_struct option identifying an SQLDA data structure already populated by the application.
With the USING DESCRIPTOR :sqlda_struct option, values of the program variables are substituted for parameter markers in the SELECT statement. These program variables are addressed by corresponding sqldata entries in the SQLDA data structure.
The number of parameter markers in the SELECT statement must match the number of sqldata entries (USING DESCRIPTOR :sqlda_struct) or host variables (USING :hvar) in the OPEN statement.
*Declare the cursor... EXEC SQL DECLARE C1 CURSOR FOR SELECT staff_id, last_name FROM staff END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not declare cursor.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF EXEC SQL OPEN C1 END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not open cursor.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT CURRENT END-EXEC STOP RUN END-IF PERFORM UNTIL sqlcode NOT = ZERO * SQLCODE will be zero as long as it has successfully * fetched data EXEC SQL FETCH C1 INTO :staff-staff-id, :staff-last-name END-EXEC IF SQLCODE = ZERO DISPLAY "Staff ID: " staff-staff-id DISPLAY "Staff member's last name: " staff-last-name END-IF END-PERFORM EXEC SQL CLOSE C1 END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not close cursor.' DISPLAY SQLERRMC DISPLAY SQLERRML END-IF
>>--EXEC SQL--PREPARE--stmt_name--.-------------.-----> +-INTO :sqlda-+ >--FROM--:hvar--END-EXEC--><
stmt_name | The prepared statement name. This can be used by a subsequent EXECUTE or OPEN statement, and/or a previous DECLARE CURSOR statement. |
:sqlda | A host variable that specifies the output SQL descriptor area (SQLDA) data structure to be populated. The colon is optional to provide compatibility with other embedded SQL implementations. |
:hvar | The host variable that contains the SQL statement. |
The PREPARE statement processes dynamic SQL statements.
You can use a prepared statement in one of two ways:
If the prepared statement is used by an EXECUTE statement, :hvar cannot contain a SQL statement that returns results.
Because singleton select statements (SELECT INTO) are not allowed in dynamic SQL statements, they cannot be prepared.
When using PREPARE, the SQL statement in :hvar cannot contain host variables or comments, but it can contain parameter markers. Also, the SQL statement cannot contain SQL keywords that pertain exclusively to Embedded SQL.
The INTO :sqlda option merges the functionality of DESCRIBE and PREPARE so that this example code:
EXEC SQL PREPARE stmt1 INTO :sqlda FROM :stmt-buf END-EXEC
is identical to:
EXEC SQL PREPARE stmt1 FROM :stmt-buf END-EXEC EXEC SQL DESCRIBE stmt1 INTO :sqlda END-EXEC
For more details about using the PREPARE statement, see the section Preparing Dynamic SQL Statements in the chapter Dynamic SQL.
PROGRAM-ID. progname. WORKING-STORAGE SECTION. EXEC SQL INCLUDE SQLCA END-EXEC EXEC SQL BEGIN DECLARE SECTION END-EXEC 01 prep PIC X(80). 01 nme PIC X(20). 01 car PIC X(20). 01 n60 PIC x(5). EXEC SQL END DECLARE SECTION END-EXEC PROCEDURE DIVISION. EXEC SQL CONNECT TO 'srv1' USER 'sa' END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not connect to database.' DISPLAY SQLERRMC DISPLAY SQLERRMC STOP RUN END-IF * Ensure attempt is not made to recreate an existing table.. EXEC SQL DROP TABLE mf_table END-EXEC * Create a table... EXEC SQL CREATE TABLE mf_table (owner char(20) ,car_col char(20) ,nought_to_60 char(5)) END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not create table' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT CURRENT END-EXEC STOP RUN END-IF * Insert an SQL statement into host variable prep... MOVE "insert into mf_table values(?,?,?)" TO prep * Prepare the statement... EXEC SQL PREPARE prep_stat FROM :prep END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not prepare statement' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT CURRENT END-EXEC STOP RUN END-IF MOVE "Owner" TO nme MOVE "Lamborghini" TO car MOVE "4.9" TO n60 * Execute the prepared statement using the above * host variables... EXEC SQL EXECUTE prep_stat USING :nme, :car, :n60 END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not execute prepared statement.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT CURRENT END-EXEC STOP RUN END-IF * Finally, drop the now unwanted table... EXEC SQL DROP TABLE mf_table END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not drop table.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT CURRENT END-EXEC STOP RUN END-IF DISPLAY 'All statements executed.' EXEC SQL DISCONNECT CURRENT END-EXEC STOP RUN.
>>--EXEC SQL--QUERY ODBC--.-COLUMN--.---------------------> +-COLUMNS-+ >--.--------------------------.--.------------------.----> +-QUALIFIER qualifier_name-+ +-OWNER owner_name-+ >--.----------------------.--.------------------------.--> +-TABLENAME table_name-+ +-COLUMNNAME column_name-+ >--END-EXEC--><
>>--EXEC SQL--QUERY ODBC--.-DATATYPE--.-------------------> +-DATATYPES-+ >--.--------------------------.--END-EXEC-->< +-TYPE--.-datatype_name--.-+ +-BIGINT---------+ +-BINARY---------+ +-BIT------------+ +-CHAR-----------+ +-DATE-----------+ +-DECIMAL--------+ +-DOUBLE---------+ +-FLOAT----------+ +-INTEGER--------+ +-LONG VARBINARY-+ +-LONG VARCHAR---+ +-NUMERIC--------+ +-REAL-----------+ +-SMALLINT-------+ +-TIME-----------+ +-TIMESTAMP------+ +-TINYINT--------+ +-VARBINARY------+ +-VARCHAR--------+
>>--EXEC SQL--QUERY ODBC--.-TABLE--.----------------------> +-TABLES-+ >--.--------------------------.--.------------------.----> +-QUALIFIER qualifier_name-+ +-OWNER owner_name-+ >--.----------------------.--.------------------------.--> +-TABLENAME table_name-+ +-TYPE tabletype_name----+ >--END-EXEC--><
qualifier_name | A host variable, identifier or literal which specifies a qualifier to be used to select tables. Not all ODBC drivers support qualifiers, and those that do may use them in different ways. For example, if a data source supports multiple databases, a qualifier can be used to specify which database to use. Alternatively, for drivers providing access to file-based data sources, a qualifier can be used to specify a particular directory to be searched. |
owner_name | A host variable, identifier or literal which specifies a table owner to be used to select tables. Not all ODBC drivers support table ownership. |
table_name | A host variable, identifier or literal which specifies tables to be included in the query. |
datatype_name | A host variable, identifier or literal which specifies a data type to be queried. |
tabletype_name | A host variable, identifier or literal which specifies a list of table types to be included in the query. |
The QUERY ODBC statement delivers a results set in the same way as a SELECT statement, and must therefore be associated with a cursor via DECLARE and OPEN, or DECLARE, PREPARE and OPEN.
Search patterns consist of the legal characters for SQL identifiers plus underscore (_) which matches any single character, percent (%) which matches any sequence of zero or more characters, or a driver defined escape character which can be used to allow underscore or percent in a pattern to represent themselves rather than a wildcard.
If a search pattern parameter is not supplied, a pattern of % is used, which will match all relevant dictionary entries.
For table queries the following special rules apply:
The results set for a column query is:
TABLE_QUALIFIER |
VARCHAR(128) |
|
TABLE_OWNER |
VARCHAR(128) |
|
TABLE_NAME |
VARCHAR(128) NOT NULL |
|
COLUMN_NAME |
VARCHAR(128) NOT NULL |
|
DATA_TYPE |
SMALLINT NOT NULL |
See odbcext.cpy and odbc.cpy for
constants representing the ODBC data type codes. |
TYPE_NAME |
VARCHAR(128) NOT NULL |
Driver-dependent name for the column's data type. |
PRECISION |
INTEGER |
|
LENGTH |
INTEGER |
Amount of memory required for a column value in its
native representation. |
SCALE |
SMALLINT |
|
RADIX |
SMALLINT |
For numeric columns either 10 or 2 depending on the
data type; otherwise null |
NULLABLE |
SMALLINT NOT NULL |
|
REMARKS |
VARCHAR(254) |
The results set for a data type entry is:
TYPE_NAME |
VARCHAR(128) NOT NULL |
Driver-dependent name for the column's data type |
DATA_TYPE |
SMALLINT NOT NULL |
See odbcext.cpy and odbc.cpy for
constants representing the ODBC data type codes. |
PRECISION |
INTEGER |
Maximum precision for columns of this type. |
LITERAL_PREFIX |
VARCHAR(128) |
Character or characters required to prefix literal
values for this type. |
LITERAL_SUFFIX |
VARCHAR(128) |
Character or characters required to suffix literal
values for this type. |
CREATE_PARAMS |
VARCHAR(128) |
Parameters required when creating a column of this
type, for example, "precision,scale" for decimal types. |
NULLABLE |
SMALLINT NOT NULL |
|
CASE_SENSITIVE |
SMALLINT NOT NULL |
Specifies case sensitivity in comparisons for character
data types. |
SEARCHABLE |
SMALLINT NOT NULL |
SQL_UNSEARCHABLE, SQL_LIKE_ONLY or SQL_ALL_EXCEPT_LIKE
(these are defined in odbc_cpy). |
UNSIGNED_ATTRIBUTE |
SMALLINT |
Specifies if a numeric type is signed or unsigned. |
MONEY |
SMALLINT NOT NULL |
Specifies if a numeric type is a money data type. |
AUTO_INCREMENT |
SMALLINT |
Specifies if the data type is auto incrementing. |
LOCAL_TYPE_NAME |
VARCHAR(128) |
Localized version of the data type name. |
MINIMUM_SCALE |
SMALLINT |
|
MAXIMUM_SCALE |
SMALLINT |
The results set for a table query is:
TABLE_QUALIFIER |
VARCHAR(128) |
|
TABLE_OWNER |
VARCHAR(128) |
|
TABLE_NAME |
VARCHAR(128) |
|
TABLE_TYPE |
VARCHAR(128) |
One of TABLE, VIEW, SYSTEM TABLE, GLOBAL TEMPORARY,
LOCAL TEMPORARY, ALIAS, SYNONYM or a data source specific type
identifier |
REMARKS |
VARCHAR(254) |
EXEC SQL DECLARE tcurs CURSOR FOR QUERY ODBC TABLES END-EXEC EXEC SQL DECLARE C1 CURSOR FOR QUERY ODBC TABLES OWNER :tab-owner TABLETYPE 'TABLE,VIEW' END-EXEC MOVE 'staff' to tab-name EXEC SQL DECLARE C2 CURSOR FOR QUERY ODBC COLUMNS TABLENAME :tab-name END-EXEC EXEC SQL DECLARE C3 CURSOR FOR QUERY ODBC DATATYPES END-EXEC
>>--EXEC SQL--ROLLBACK--.-WORK---------.--------------> +-TRAN---------+ +-TRANSACTION--+ >--.-----------.--END-EXEC-->< +--RELEASE--+
The ROLLBACK statement undoes any changes made to the database by the current transaction on the current connection.
If RELEASE is specified and the transaction was successfully rolled back, the current connection is closed.
EXEC SQL ROLLBACK END-EXEC EXEC SQL ROLLBACK WORK RELEASE END-EXEC
>>--EXEC SQL--.------------.--DECLARE cursor_name---------> +-AT db_name-+ >--CURSOR FOR--SELECT DISTINCT--select_list--------------> >--FROM--table_list--.----------------.--END-EXEC-->< +-select_options-+
db_name | The name of a database that has been declared using DECLARE DATABASE. |
cursor_name | Cursor name used to identify the cursor in subsequent statements. Cursor names can contain any legal filename character and be up to 30 characters in length. The first character must be a letter. |
select_list | The name of the columns to retrieve. |
table_list | The name of the tables that contain the columns to be retrieved, as specified in select_list. |
select_options | The options specified to limit the number of rows retrieved and/or order the rows retrieved. |
The DECLARE CURSOR statement associates the cursor name with the SELECT DISTINCT statement and enables you to retrieve rows of data using the FETCH statement.
Two separately compiled programs cannot share the same cursor. All statements that reference a particular cursor must be compiled together.
The SELECT DISTINCT statement runs when the cursor is opened. The following rules apply to the SELECT DISTINCT statement:
Note: Use SELECT DISTINCT instead of SELECT INTO to remove duplicate rows in the row set.
01 age-array pic s9(09) comp-5 occurs 10 times. 01 lname-array pic x(32) occurs 10 times. MOVE 5 TO staff-id EXEC SQL SELECT DISTINCT last_name INTO :lname-array FROM staff WHERE staff_id > :staff-id END-EXEC EXEC SQL SELECT DISTINCT age INTO :age-array FROM staff WHERE first_name > 'George' END-EXEC
>>--EXEC SQL--.-------------------.--.------------.---> +-FOR :host_integer-+ +-AT db_name-+ +-- ,-+ v | >--SELECT--.-------------.--INTO--:hvar--------------> +-select_list-+ >--select_options--END-EXEC--><
:host_integer | A host variable that specifies the maximum number of host array elements processed. Must be declared as PIC S9(4) COMP-5 |
db_name | The name of a database that has been declared using DECLARE DATABASE. |
select_list | The portion of the table to retrieve data from. |
:hvar | One or more host variables to receive the select_list items. |
select_options | One or more statements or other options that can be used with the SQL SELECT statement (for example, a FROM or WHERE clause). |
A singleton SELECT must contain a FROM clause.
The SELECT INTO statement retrieves one row of results and assigns the values of the items in select_list to the host variables specified in the INTO list. If more columns are selected than the number of receiving host variables, the value of SQLWARN3 is set to 'W'. The data type and length of the host variable must be compatible with the value assigned to it. If data is truncated, the value of SQLWARN1 is set to 'W'.
If a SELECT INTO statement returns more than one row from the database, all rows except the first one will be discarded and SQLWARN4 will be set to 'W'. If you want to return more than the first row, you should use a cursor. Alternatively, you can specify array items in the INTO clause. The array will be populated up to either the maximum size of the array, the value of host_integer or the number of rows returned, whichever is the smallest.
If ANSI92ENTRY is set and a singleton SELECT retrieves more than 1 row, SQLCODE will be -1, SQLSTATE will be 21000 and SQLWARN4 will be W. If ANSI92ENTRY is not set, no error or warning conditions will be set.
Note: If any one of the host variables in the INTO clause is an array, then they all must be arrays.
MOVE 99 TO staff-id EXEC SQL SELECT last_name INTO :lname FROM staff WHERE staff_id=:staff-id END-EXEC EXEC SQL SELECT staff_id INTO :staff-id FROM staff WHERE first_name = 'Phil' END-EXEC
>>--EXEC SQL--SET AUTOCOMMIT--.-ON--.--END-EXEC-->< +-OFF-+
ON | Changes to AUTOCOMMIT mode, whereby each SQL statement is treated as a separate transaction and is committed immediately upon execution. |
OFF | Switches off AUTOCOMMIT mode. If the ODBC driver you are using supports transactions, statements must be explicitly committed (or rolled back) as part of a transaction. |
The SET AUTOCOMMIT statement enables you to control ODBC Autocommit mode at run time. This is useful for data sources which can only execute DDL statements, such as CREATE and DROP, in AUTOCOMMIT mode. This statement overrides the AUTOCOMMIT SQL compiler directive.
EXEC SQL SET AUTOCOMMIT ON END-EXEC
Notes:
>>--EXEC SQL--SET CONCURRENCY--.-READONLY-.--END-EXEC-->< +-LOCKCC---+ +-OPTCC----+ +-OPTCCVAL-+
READONLY | Specifies read-only cursors. Data cannot be modified. |
LOCKCC | Places an update intent lock on the data page that contains each row as it is fetched. If not inside an open transaction, the locks are released when the next fetch is performed. If inside an open transaction, the locks are released when the transaction is closed. |
OPTCC | Optimistic concurrency control using timestamp or values. Changes to a row through the cursor succeed only if the row remains unchanged since the last fetch. Changes are detected by comparing timestamps or by comparing all non-text, non-image values if timestamps are not available. |
OPTCCVAL | Optimistic concurrency control using values. Changes to a row through the cursor succeed only if the row remains unchanged since the last fetch. Changes are detected by comparing all non-text, non-image values. |
The SET CONCURRENCY statement sets the concurrency option for cursors.
The default is LOCKCC unless:
If you try to set an option which is not supported by the ODBC driver, you will get an error (-19512).
Note: If you are using the Microsoft Access driver, the default for CONCURRENCY is set to READONLY. If you want to use an updateable cursor with Microsoft Access, you must set the SCROLLOPTION to KEYSET first and then set CONCURRENCY to LOCKCC.
If the OPTCC or OPTCCVAL option is used, an UPDATE WHERE CURRENT OF statement can fail, with a value in SQLCODE of -532 (SQLSTATE = "01001"), if the row has been changed since the last FETCH statement. Your application needs to contain code to handle this situation.
EXEC SQL SET CONCURRENCY READONLY END-EXEC
>>--EXEC SQL--SET CONNECTION--.-name----.--END-EXEC-->< +-DEFAULT-+
name | Specifies the name of a database connection. Must match the connection name specified in a previous CONNECT statement. The name can be either the connection's literal name or the name of a host variable containing character values. |
DEFAULT | If you have established a connection using the CONNECT statement but omitting the connection name, you can refer to the connection established as DEFAULT. |
The SET CONNECTION statement makes the named connection the current connection.
Note: If you are using connections across compilation modules you must use named connections.
EXEC SQL CONNECT TO "srv1" AS server1 USER "sa." END-EXEC EXEC SQL CONNECT TO "srv2" AS server2 USER "sa." END-EXEC * server2 is the current connection EXEC SQL CREATE TABLE phil1 (charbit CHAR(5)) END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not create table.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF EXEC SQL INSERT INTO phil1 VALUES('hello') END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not insert data.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF * set the current connection to server1 EXEC SQL SET CONNECTION server1 END-EXEC EXEC SQL SELECT first_name INTO :fname FROM staff WHERE staff_id = 10 END-EXEC DISPLAY fname ' says ' WITH NO ADVANCING * set the current connection back to server2 EXEC SQL SET CONNECTION server2 END-EXEC EXEC SQL SELECT charbit INTO :fname WHERE charbit = 'hello' FROM phil1 END-EXEC DISPLAY fname EXEC SQL DISCONNECT server1 END-EXEC EXEC SQL DISCONNECT server2 END-EXEC STOP RUN
Note: The SET OPTION statement is not supported by all ODBC drivers.
>>--EXEC SQL--SET OPTION--.-QUERYTIME---.--> +-LOGINTIME---+ +-APPLICATION-+ +-HOST--------+ >--value--END-EXEC--><
value | A literal or the name of a host variable. The host variable must contain character values for application or host and numeric values for LOGINTIME or QUERYTIME. |
QUERYTIME | Sets the number of seconds that the program waits for a response to an OpenESQL statement. The default is 0, meaning forever. This option does not override existing network timeout settings. |
LOGINTIME | Sets the number of seconds that the program waits for a response to a CONNECT TO statement. The default is 10 seconds. A value of 0 indicates an infinite timeout period |
APPLICATION | Sets the application name which is passed by OpenESQL to the data source when a CONNECT TO statement is executed. |
HOST | Sets the host workstation name which is passed by OpenESQL when a CONNECT TO statement is executed. |
EXEC SQL SET OPTION logintime 5 END-EXEC EXEC SQL CONNECT TO "srv2" USER "sa." END-EXEC * If the CONNECT statement cannot log in to the server * "srv2" within five seconds, it will time out and return * to the program. EXEC SQL SET OPTION querytime 2 END-EXEC EXEC SQL SELECT name FROM sysobjects INTO :name END-EXEC * If the SELECT statement does not respond within 2 seconds, * the query will time out and return to the program.
Notes:
>>--EXEC SQL--SET SCROLLOPTION--.-KEYSET----.--END-EXEC->< +-DYNAMIC---+ +-FORWARD---+ +-STATIC----+
KEYSET | In a keyset cursor, the membership and order of rows in the cursor result set is determined when the cursor is opened. A row will not be fetched if it is deleted or if it is updated such that it no longer meets the WHERE clause criteria. A row appears in the cursor result set only if it is inserted through a cursor based on a single table. Any updates made by the cursor owner and committed changes made by other users to any of the rows in the results set are visible. |
DYNAMIC | With a dynamic cursor, membership of rows in the cursor result set is determined at fetch time and it can change between each fetch. A row will disappear from the cursor result set if it is deleted or if it is updated such that it no longer meets the WHERE clause criteria. A row appears in the result set if it is inserted or updated such that it meets the WHERE clause criteria. Any updates made by the cursor owner and committed changes made by other users to any of the rows in the result set are visible. |
FORWARD | Equivalent to DYNAMIC, but the application can only move forward through the result set. |
STATIC | In a static cursor, the result set appears to be static. Changes to the membership, order or values of the result set after the cursor is opened are not usually detected. |
The default is DYNAMIC unless:
If you try to set an option which is not supported by the ODBC driver, you will get an error (-19512).
PROGRAM-ID. progname. WORKING-STORAGE SECTION. EXEC SQL INCLUDE SQLCA END-EXEC 01 buffer PIC x(32). 01 cnt PIC 9 COMP-5. PROCEDURE DIVISION. EXEC SQL CONNECT TO 'srv1' USER 'sa' END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not connect to database.' DISPLAY SQLERRMC DISPLAY SQLERRML END-IF * Any cursors declared hereafter can be updated dynamically EXEC SQL SET SCROLLOPTION DYNAMIC END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not set scroll option.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF * Ensure multiple tables are not created ... EXEC SQL DROP TABLE phil1 END-EXEC * Create a table... EXEC SQL CREATE TABLE phil1 (ident char(3) ,textbit char(3)) END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not create table.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF * Insert some values into it... EXEC SQL INSERT INTO phil1 (ident ,textbit) VALUES ('AAA' ,'BBB') END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not insert values.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF EXEC SQL INSERT INTO phil1 (ident ,textbit) VALUES ('CCC' ,'---') END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not insert values.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF * Declare a cursor... EXEC SQL DECLARE C1 CURSOR FOR SELECT ident FROM phil1 WHERE textbit = 'BBB' END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not declare cursor.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF * Open it... EXEC SQL OPEN C1 END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not open cursor.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF * Update one of the rows in the table such that it now meets * the cursor requirements... EXEC SQL UPDATE phil1 SET textbit = 'BBB' WHERE ident = 'CCC' END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not update row.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF * Despite the row being updated to meet cursor requirement * after the cursor was opened, SET SCROLLOPTION DYNAMIC * should ensure that it is pointed to by the cursor. Check * the displayed output to be sure... MOVE 0 TO cnt PERFORM UNTIL SQLCODE NOT = ZERO EXEC SQL FETCH C1 INTO :buffer END-EXEC IF SQLCODE = ZERO DISPLAY buffer END-IF END-PERFORM EXEC SQL CLOSE C1 END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not close cursor.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF EXEC SQL DROP TABLE phil1 END-EXEC IF SQLCODE NOT = ZERO DISPLAY 'Error: Could not drop table.' DISPLAY SQLERRMC DISPLAY SQLERRML EXEC SQL DISCONNECT ALL END-EXEC STOP RUN END-IF EXEC SQL DISCONNECT CURRENT END-EXEC STOP RUN.
>>--EXEC SQL--SET TRANSACTION ISOLATION---------------> >--.-READ UNCOMMITTED-.--END-EXEC-->< +-READ COMMITTED---+ +-REPEATABLE READ--+ +-SERIALIZABLE-----+
The SET TRANSACTION ISOLATION statement sets the transaction isolation level for the current connection to one of the isolation level modes specified by ODBC.
Transactions can affect each other in the following ways, depending on the setting of the transaction isolation level:
These situations can be controlled by locking, which means that a transaction might have to wait until another transaction completes, which limits concurrency (sometimes called pessimistic concurrency), or by forcing a transaction to rollback if the situation occurs, which has less of an impact on concurrency but may force work to be repeated (this is sometimes called optimistic concurrency).
In READ UNCOMMITED mode, dirty reads, nonrepeatable reads and phantoms are all possible.
In READ COMMITED mode, dirty reads are not possible but nonrepeatable reads and phantoms are.
In REPEATABLE READ mode, dirty reads and nonrepeatable reads are not possible, but phantoms are.
In SERIALIZABLE mode, dirty reads, nonrepeatable reads and phantoms are all impossible.
Note:
A driver might not support all the isolation levels defined by ODBC. If you set a mode that the driver does not support, SQLCODE and SQLSTATE are set accordingly.
EXEC SQL SET TRANSACTION ISOLATION READ UNCOMMITTED END-EXEC
>>--EXEC SQL--.----------------.--.------------.------> +-FOR :row_count-+ +-AT db_name-+ +----- ,----------+ v | >--UPDATE--table_name--SET---column=expression-------> >--WHERE CURRENT OF--cursor_name--END-EXEC--><
:row_count | An integer host variable that specifies the number of rows to be used if the result and parameter host variables are all arrays of the same size, and not all elements should be used. You cannot use the FOR clause if the UPDATE is part of a DECLARE CURSOR statement. |
db_name | The name of a database that has been declared using DECLARE DATABASE. |
table_name | The table to be updated. |
column=expression | A value for a particular column name. This value can be an expression or a null value. |
cursor_name | A previously declared, opened, and fetched cursor. |
ODBC supports positioned update, which updates the row most recently fetched by using a cursor, in the Extended Syntax (it was in the Core Syntax for ODBC 1.0 but was moved to the Extended Syntax for ODBC 2.0). Not all drivers provide support for positioned update, although OpenESQL sets ODBC cursor names to be the same as COBOL cursor names to facilitate positioned update and delete.
With some ODBC drivers, the SELECT statement used by the cursor must contain a FOR UPDATE clause to enable positioned update.
The other form of UPDATE used in standard SQL statements is known as a searched update.
You cannot use host arrays with positioned update.
Most data sources require specific combinations of SCROLLOPTION and CONCURRENCY to be specified either by SET statements or in the DECLARE CURSOR statement.
The ODBC cursor libray provides a restricted implementation of positioned update which can be enabled by compiling with SQL(USECURLIB=YES) and using SCROLLOPTION STATIC and CONCURRENCY OPTCCVAL (or OPTIMISTIC).
EXEC SQL CONNECT TO 'srv1' USER 'sa' END-EXEC EXEC SQL DECLARE C1 CURSOR FOR SELECT last_name, first_name FROM staff FOR UPDATE END-EXEC EXEC SQL OPEN C1 END-EXEC PERFORM UNTIL SQLCODE NOT = ZERO EXEC SQL FETCH C1 INTO :fname,:lname END-EXEC IF SQLCODE = ZERO DISPLAY fname " " lname DISPLAY "Update?" ACCEPT reply IF reply = "y" DISPLAY "New last name?" ACCEPT lname EXEC SQL UPDATE staff SET last_name=:lname WHERE CURRENT OF c1 END-EXEC DISPLAY "update sqlcode=" SQLCODE END-IF END-IF END-PERFORM EXEC SQL DISCONNECT ALL END-EXEC STOP RUN.
>>--EXEC SQL-.-------------------.--.------------.----> +-FOR :host_integer-+ +-AT db_name-+ +---- ,-----------+ v | >--UPDATE-.-table_name-.--SET---column=expression----> +-view_name--+ >--.-------------------------.--END-EXEC-->< +-WHERE search_conditions-+
:host_integer | A host variable that specifies the maximum number of host array elements processed. Must be declared as PIC S9(4) COMP-5 |
db_name | The name of a database that has been declared using DECLARE DATABASE. |
table_name | The table to be updated. |
view_name | The view to be updated. |
column=expression | A value for a particular column name. This value can be an expression or a null value. |
search_conditions | Any valid expression that can follow the standard SQL WHERE clause. |
UPDATE is a standard SQL statement which is passed directly to the ODBC driver. See the documentation supplied with your ODBC driver for the exact syntax.
If you do not specify a WHERE clause, all the rows in the named table are updated.
If one of the host variables used in the WHERE clause or SET clause is an array, they must all be arrays.
EXEC SQL UPDATE staff SET first_name = 'Jonathan' WHERE staff_id = 1 END-EXEC MOVE 'Phil' TO NewName MOVE 1 TO targetID EXEC SQL UPDATE staff SET first_name = :NewName WHERE staff_id = :targetID END-EXEC
>>--EXEC SQL--WHENEVER--.-NOT FOUND--.----------------> +-SQLERROR---+ +-SQLWARNING-+ >--.-CONTINUE--------.--END-EXEC-->< +-PERFORM label---+ +-GOTO stmt_label-+
CONTINUE | Causes the next sequential statement in the source program to run. |
PERFORM label | Identifies a paragraph or section of code to be performed when a certain error level is detected. |
GOTO stmt_label | Identifies the place in the program that takes control when a certain error level is detected. |
The WHENEVER statement specifies the default action after running an Embedded SQL statement on each of the following conditions: NOT FOUND, SQLERROR, SQLWARNING.
Condition |
SQLCODE |
No error |
0 |
NOT FOUND |
100 |
SQLWARNING |
+1 |
SQLERROR |
< 0 (negative) |
The scope of a WHENEVER statement is related to the position of statements in the source program, not in the run sequence. The default is CONTINUE for all three conditions.
EXEC SQL WHENEVER sqlerror PERFORM errormessage1 END-EXEC EXEC SQL DELETE FROM staff WHERE staff_id = 'hello' END-EXEC EXEC SQL DELETE FROM students WHERE student_id = 'hello' END-EXEC EXEC SQL WHENEVER sqlerror CONTINUE END-EXEC EXEC SQL INSERT INTO staff VALUES ('hello') END-EXEC DISPLAY 'Sql Code is: ' SQLCODE EXEC SQL WHENEVER sqlerror PERFORM errormessage2 END-EXEC EXEC SQL INSERT INTO staff VALUES ('hello again') END-EXEC STOP RUN. errormessage1 SECTION. display "SQL DELETE error: " sqlcode EXIT. errormessage2 SECTION. display "SQL INSERT error: " sqlcode EXIT.
Copyright © 2000 MERANT International Limited. All rights reserved.
This document and the proprietary marks and names
used herein are protected by international law.
DataDirect ODBC Drivers | The CP Preprocessor |