HP 3000 Manuals

Preprocessing of Dynamic Queries with C or Pascal Routines [ ALLBASE/SQL COBOL Application Programming Guide ] MPE/iX 5.0 Documentation


ALLBASE/SQL COBOL Application Programming Guide

Preprocessing of Dynamic Queries with C or Pascal Routines 

Although you cannot dynamically preprocess a query (SELECT command) in
COBOL, you can call a Pascal or 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.
The same COBOL code is used when calling both the Pascal or C versions of
performcommand.  Parameters are passed by reference to performcommand.
For more information on passing parameters to non-COBOL programs, please
refer to the HP COBOL II/XL Programmer's 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:

   1.  Copy the parameters passed from the calling COBOL program into the
       C global variables needed by the SQL calls.

   2.  Issue the SQL PREPARE and DESCRIBE statements.

   3.  Parse the data buffer and display the rows.

   4.  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 */

Pascal Subprogram Example 

The Pascal version of the subprogram is described in this section.  The
Pascal procedures that actually perform the dynamic preprocessing are
similar to those used in the pasex10a Pascal sample program, which is
described in the ALLBASE/SQL Pascal Application Programming Guide. 

The PerformCommand subprogram includes the following steps:

   1.  Copy the DynamicParm parameter passed from the calling COBOL
       program into the global Pascal host variable needed by the SQL
       calls.  The SQLCA parameter does not need to be copied because it
       is not declared as a host variable, and because it may be accessed
       by other procedures nested within PerformCommand. 

   2.  Issue the SQL PREPARE and DESCRIBE statements.

   3.  Parse the data buffer and display the rows.

The source code of the PerformCommand subprogram is summarized below:

     Type
        Dynamic_Type = Packed Array [1..1014] of char;
     .
     .
     Global variable declarations needed by the Pascal routines for dynamic 
     preprocessing: 

     EXEC SQL BEGIN DECLARE SECTION;
      DynamicCommand : Packed Array [1..1014] of char;
     EXEC SQL END DECLARE SECTION;

     EXEC SQL INCLUDE  SQLDA;
     .
     .
     Procedure PerformCommand (Var  DynamicParm    : Dynamic_Type;
                               Var  SQLCA          : SQLCA_Type);
     .
     .
     Begin  (* Procedure PerformCommand *)

     Because the outer block is a non-Pascal program, the stdlist and stdin must be
     opened explicitly. 

     Rewrite (output,'$stdlist');
     Reset   (input, '$stdin','shared');

     DynamicCommand must be declared as a host variable in the Pascal subprogram.
     Copy the DynamicParm parameter to the DynamicCommand host variable before
     proceeding. 

     DynamicCommand := '';
     strmove (1014,DynamicParm,1,DynamicCommand,1);

     Issue the SQL PREPARE and DESCRIBE commands.  Parse the data buffer and
     display the rows fetched by the query.  See the pasex10a program in the
     ALLBASE/SQL Pascal Application Programming Guide for more information. 

     End; (* Procedure PerformCommand *)

How To Preprocess, Compile, Link and Run the Example Programs 

COBOL Calling a C Subprogram.   

In the example below, the COBOL source code is in COBEXS, the C source
code is in CEXS, and the DBEnvironment is PartsDBE.

   1.  Preprocess the COBOL source code.

            :PCOB COBEXS,PARTSDBE

   2.  Compile the COBOL source code generated by the preprocessor.

            :COB85XL SQLOUT,COBEXO,$NULL

   3.  Preprocess the C source code.

            :PC CEXS,PARTSDBE

   4.  Compile the C source code generated by the preprocessor.

            :CCXL SQLOUT,CEXO,$NULL

   5.  Link the COBOL and C object code into an executable program.

            :LINK FROM=COBEXO,CEXO;TO=COBEXP

   6.  Run the executable program.

            :RUN COBEXP

COBOL Calling a Pascal Subprogram.   

In the example below, the COBOL source code is in COBEXS, the Pascal
source code is in PASEXS, and the DBEnvironment is PartsDBE.

   1.  Preprocess the COBOL source code.

            :PCOB COBEXS,PARTSDBE

   2.  Compile the COBOL source code generated by the preprocessor.

            :COB85XL SQLOUT,COBEXO,$NULL

   3.  Preprocess the Pascal source code.

            :PPAS PASEXS,PARTSDBE

   4.  Compile the Pascal source code generated by the preprocessor.

            :PASXL SQLOUT,PASEXO,$NULL

   5.  Link the COBOL and Pascal object code into an executable program.

            :LINK FROM=COBEXO,PASEXO;TO=COBEXP

   6.  Run the executable program.

            :RUN COBEXP



MPE/iX 5.0 Documentation