Although you cannot dynamically preprocess a query
(SELECT command) in COBOL,
you can call a C subprogram
which can dynamically preprocess a query.
COBOL Call Example |
 |
In the example program used in this section, a COBOL program
calls a subprogram named performcommand to dynamically preprocess
an SQL command.
Parameters are passed by reference to performcommand.
For more information on
passing parameters to non-COBOL programs, please refer to the
COBOL/HP-UX Operating Guide.
The following example shows the COBOL parameter declarations and
CALL statement:
.
.
WORKING-STORAGE SECTION.
.
.
DYNAMIC-CMD contains the SQL command to be executed by the subprogram.
01 DYNAMIC-CMD PIC X(1014).
SQLCA is the data structure that contains current information about a program's DBE session.
EXEC SQL INCLUDE SQLCA END-EXEC.
.
.
PROCEDURE DIVISION.
.
.
Connect to the DBEnvironment.
.
.
Load DYNAMIC-CMD with the SQL command to be executed.
.
.
CALL "performcommand" USING DYNAMIC-CMD,
SQLCA.
.
.
|
C Subprogram Example |
 |
This section describes the C version of a
subprogram called by a COBOL program to dynamically preproccess
SQL commands.
The C routines that actually perform the dynamic preproccessing
are similar to those used in cex10a, a sample C program
described in the ALLBASE/SQL C Application Programming Guide.
The performcommand subprogram includes the following steps:
Copy the parameters passed from the calling COBOL program
into the C global variables needed by the SQL calls.
Issue the SQL PREPARE and DESCRIBE statements.
Parse the data buffer and display the rows.
Copy the C global SQLCA variable back into the sqlcaparm parameter
before returning to the COBOL program.
The source code of the performcommand subprogram is summarized below:
Global variable declarations needed by the C routines for dynamic preprocessing:
EXEC SQL BEGIN DECLARE SECTION;
char DynamicCommand[1014];
EXEC SQL END DECLARE SECTION;
EXEC SQL INCLUDE SQLCA;
EXEC SQL INCLUDE SQLDA;
.
.
performcommand (dynamicparm, sqlcaparm)
The COBOL program has passed the parameters to performcommand by reference, so
the formal parameters are declared here as addresses.
char dynamicparm[];
char sqlcaparm[];
{
int k;
char *destptr;
char *sourceptr;
DynamicCommand must be declared as host variable in this subprogram. Copy the
formal parameter into the host variable.
for (k = 0; k < sizeof(DynamicCommand); k++ )
DynamicCommand[k] = dynamicparm[k];
The sqlcaparm passed to this subprogram is an address pointing to the SQLCA
area of the calling program, and the SQLCA used by this subprogram is a global
variable. Since the formal parameters in performcommand cannot be global
(i.e.-- extern), copy the sqlcaparm parameter to the SQLCA.
Use pointers (addresses) to copy the sqlcaparm to SQLCA because the SQLCA is
a structure. Sourceptr is set to sqlcaparm, the address of the SQLCA passed to
the subprogram.
Destptr is assigned the address of the SQLCA used by this subprogram. Then,
assign the contents of the sourceptr to the contents of the destptr and increment
the values of both pointers until the entire sqlcaparm has been copied.
sourceptr = sqlcaparm;
destptr = &sqlca;
for (k = 1; k <= sizeof(sqlca); k++) {
*destptr = *sourceptr;
sourceptr++;
destptr++;
}
Issue the SQL PREPARE and DESCRIBE commands. Parse the data buffer and
display the rows fetched by the query. See the cex10a program in the ALLBASE/SQL
C Application Programming Guide for more information.
Before returning to the COBOL program copy SQLCA to sqlcaparm. This permits
the COBOL program to access the information in the SQLCA.
sourceptr = &sqlca;
destptr = sqlcaparm;
for (k = 1; k <= sizeof(sqlca); k++) {
*destptr = *sourceptr;
sourceptr++;
destptr++;
}
} /* End of performcommand */
|
Assigning a Call Number to a Non-COBOL Subprogram |
 |
COBOL/HP-UX requires a call number in the range of 0 to 127 for
each non-COBOL subprogram. ALLBASE/SQL uses call number 120, as
defined in files /usr/include/sqlcall.h and
/usr/include/sqlcall.cbl. If other non-COBOL subprograms are
incorporated in the COBOL application, /usr/include/sqlcall.c must be
modified to include a call number for each non-COBOL subroutine.
The call number 30 was assigned to the performcommand
example subprogram. The following example shows the call number 30
in /usr/include/sqlcall.h.
#define SQLXCBL 120
#define SQLDYN 30
|
In /usr/include/sqlcall.cbl, the call number 30 is assigned as follows:
01 SQLXCBL PIC X(3) VALUE "120".
01 SQLDYN PIC X(3) VALUE "30".
|
The switch statement in the /usr/include/sqlcall.c file must be modified
to include the performcommand subprogram call, as shown in the following
example.
.
.
xequcall( callnum )
{
switch( callnum )
{
case SQLXCBL: sqlxcbl();
break;
case SQLDYN: performcommand();
break;
default: execerr( ER_CALL );
break;
}
}
|
How To Preprocess, Compile, Link, and Run the Example Programs |
 |
In the example below, the COBOL source code is in cobex.sql, the
C source code is in cex.sql, and the DBEnvironment is
PartsDBE.
Preprocess the COBOL source code.
% psqlcbl ../sampledb/PartsDBE -i cobex.sql -d
|
Preprocess the C source code.
% psqlc ../sampledb/PartsDBE -i cex.sql -d
|
Compile and link the COBOL and C code into an executable program.
% cob cobex.cbl sqlcall.c cex.c -lsql -lportnls +lcl -x
|
Run the executable program.