Follow

Create and Call COBOL Stored Procedures

This tutorial will show how to create, deploy and then call an Elastic COBOL stored procedure in the Apache DB (a.k.a. Derby) RDBMS engine on Windows or Linux.  It will also describe how to call a stored procedure from an Elastic COBOL program.  Of course, Elastic COBOL compiler is used to compile either the called SP code or the code invoking the SP.  The Java source code output from this process is compiled and packages as a JAR file and (in the case of COBOL as an embedded SP) installed into the database.  This applies to most databases that support Java as a stored procedure such as,

  • DB2 for z/OS (*1, *2)
  • DB2 for Linux, Windows, UNIX (*1, *2)
  • SpliceMachine (*1, *2)
  • Apache DB (*1, *2)
  • Oracle (*1)
  • Derby (*1, *2)
  • JavaDB (*1, *2)
  • PostgreSQL (*1, *3)
  • H2 (*1, *2)

For any of these databases, see the DBMS documentation on how to set up the various CLASSPATHs and other requirements when dealing with stored procedures from/to Java.  For example, the following features apply:

  1. Procedure "CALL proc-name1"-type supported
  2. Function "SELECT ... proc-name2() WHERE proc-name3()" tuple-level access-type supported
  3. Third party plug-in required for Java stored procedures

COBOL Database Stored Procedures

COBOL programs can be compiled and installed as either functions or stored procedures into databases that have native language support for the Java language.  The LINKAGE SECTION of the program defines the parameters.  The BY VALUE and BY REFERENCE attribute of each parameter should match the definition of the stored procedure in the database.  Parameters marked as IN in the CREATE PROCEDURE statement are BY VALUE and the OUT and INOUT should be marked BY REFERENCE.  By default all COBOL parameters are BY REFERENCE and this default case will also work for IN, OUT and INOUT parameters.

COBOL (as Java) stored procedures can also return one or more result sets to the program that invokes it with the SQL CALL statement.  See Invoking Database Stored Procedures from COBOL section below on how to receive those result sets.  The stored procedure must declare the cursor(s) and open it just prior to returning to the caller.  The following modified IBM example that shows how to deal with IN and OUT parameters as well as returning two result sets. See the example program in the zip file attached to this article.

      $SET DIRECTIVE "-out:cobolinjava"
      $SET DIRECTIVE "-sql:jdbc     4"
      $SET DIRECTIVE "-sql:user     admin"
      $SET DIRECTIVE "-sql:password pwd"
      $SET DIRECTIVE "-sql:driver org.apache.derby.jdbc.EmbeddedDriver"
      $SET DIRECTIVE "-sql:url    jdbc:derby:testa9"
      $SET DIRECTIVE "-sql:sp       derby"
      $SET DIRECTIVE "-sql:spname   getnames"
      $SET DIRECTIVE "-sql:spschema admin"
       IDENTIFICATION DIVISION.
       PROGRAM-ID. GETNAMES.
      *
      * the GETNAMES stored procedure
      *
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
           EXEC SQL
             INCLUDE SQLCA
           END-EXEC.

       01 WS-GEN-VAR.
          05 WS-KEY                         PIC X(10).
          05 WS-ERROR-MSG                   PIC X(32).

           EXEC SQL
              DECLARE BEFORE-CUR CURSOR WITH RETURN FOR
              SELECT NAME
              FROM ADMIN.NAMES
              WHERE NAME <  :WS-KEY
              ORDER BY NAME DESC
           END-EXEC.
           EXEC SQL
              DECLARE AFTER-CUR CURSOR WITH RETURN FOR
              SELECT NAME
              FROM ADMIN.NAMES
              WHERE NAME > :WS-KEY
              ORDER BY NAME ASC
           END-EXEC.

       LINKAGE SECTION.
       01 LK-STARTNM                        PIC X(10).
       01 LK-OUT-CODE                       PIC -9(6) COMP.

       PROCEDURE DIVISION
             USING LK-STARTNM
                  ,LK-OUT-CODE
                  .
      *    set the key for the two queries
           MOVE LK-STARTNM TO WS-KEY.

      *    open the first cursor, returning everything before the key
           EXEC SQL
              OPEN BEFORE-CUR
           END-EXEC
           IF SQLCODE NOT EQUAL 0 THEN
               DISPLAY "OPEN CURSOR 1 SQLCODE: " SQLCODE UPON SYSOUT
               MOVE 8 TO RETURN-CODE
               goback
           END-IF.

      *    open the second cursor, returning everything after the key
           EXEC SQL
              OPEN AFTER-CUR
           END-EXEC
           IF SQLCODE NOT EQUAL 0 THEN
               DISPLAY "OPEN CURSOR 2 SQLCODE: " SQLCODE UPON SYSOUT
               MOVE 8 TO RETURN-CODE
               goback
           END-IF.

      *    move the results of the last OPEN to OUT-CODE
           MOVE SQLCODE TO LK-OUT-CODE.

      *    better test ... something other than 0 to OUT-CODE
           MOVE 22 TO LK-OUT-CODE.

      *    return the 2 result sets
           MOVE 0 TO RETURN-CODE
           GOBACK
           .
       END PROGRAM GETNAMES.

The comprehensive example using the Apache DB (Derby) database management system shown above must be compiled, packaged and installed into the DB.  Other databases will have other techniques for installing Java-based stored procedures.

Depending on your circumstance, the database stored procedure signature can be pre-defined to the database and then the COBOL program is compiled to match it, or use Elastic COBOL to compile a program and suggest a signature.  In this example we'll assume we're trying to construct a COBOL program that matches a stored procedure definition.

 

1. Define the Stored Procedure to the Database.  If you have the DDL of a stored procedure start with this step, otherwise swap steps 1 & 2.  Start the database in such a way that embedded stored procedures are allowed to access external files and system properties.  With Apache DB (Derby) this is done with -noSecurityManager start-up option.  Use a database command line interpreter to create the signature in the database.  For Apache DB use either Derby ij or SQuirreL.  Connect to the database (possibly creating the database.  For the example attached to this article, also create a table used by the stored procedure and add data to it.  The procedure definition defies the EXTERNAL NAME in the form of the Java class name and method to invoke.  It also shows that two result sets are returned.

$DERBY_HOME/bin/startNetworkServer -noSecurityManager
$DERBY_HOME/bin/ij
ij> CONNECT 'jdbc:derby://localhost:1527/sample;create=true;user=ADMIN;password=PWD';
ij> CREATE PROCEDURE ADMIN.GETNAMES (
                  IN  STARTNM CHAR(10),
                  OUT OUT_CODE INTEGER
    )
    LANGUAGE JAVA PARAMETER STYLE JAVA READS SQL DATA DYNAMIC  
    RESULT SETS 2  
    EXTERNAL NAME 'getnames.callSp';

ij> CREATE TABLE NAMES(NAME CHAR(10));
ij> INSERT INTO NAMES VALUES('fred');
ij> INSERT INTO NAMES VALUES('barney');
ij> INSERT INTO NAMES VALUES('wilma');
ij> INSERT INTO NAMES VALUES('betty');

 

2. Compile your Elastic COBOL program in such a way that the stored procedure signature (as well as embedded SQL statements) can be checked against the database definitions.  This is accomplished with a select group of compiler directives that provide connection attributes to the database. 

Directive Description Example
-sql:sp Create a method named callSP() that can invoked directly by a database manager. Register this along with the Java class name as the EXTERNAL NAME in the CREATE PROCEDURE database DDL statement. db2 | derby | splice | apache | oracle | postgres
-sql:spname The name of the stored procedure if different from the program ID. getnames
-sql:spschema The schema containing the stored procedure if different from the user connection attribute. admin
-sql:jdbc Stored procedures that return result sets require JDBC level 4 4
-sql:url The database connection attribute to verify the embedded SQL statements jdbc:derby://localhost:1527/derbyDB
-sql:user The database connection attribute to verify the embedded SQL statements admin
-sql:password The database connection attribute to verify the embedded SQL statements pwd
-sql:driver The database connection attribute to verify the embedded SQL statements org.apache.derby.jdbc.ClientDriver 

The example GETNAMES COBOL program above contains these compiler directives within the source.  Alternatively, they can be provided in an ecobol.dir file or on the command line.  Also required when using these compiler directives the Elastic COBOL runtime (ecobol.jar) and the specific database JDBC driver must be present on the CLASSPATH.  Set this up in advance of invoking Eclipse (interactive IDE compilation) or ecobol command.  On Linux systems this is accomplished with the commands,

export CLASSPATH=/path/to/ecobol.jar:/path/to/derbyclient.jar
ecobol GetNames.cbl

 

2. Compile the Java source code generated as part of the Elastic COBOL compiler (Eclipse or ecobol) into a class file, then package as jar using the Elastic COBOL Deployment Wizard within Eclipse or with the jar command.  When using the Wizard the contents of the ecobol.jar can be combined into the destination jar.  If not, ecobol.jar must be in the CLASSPATH before the database is started.

javac getnames.java
jar cf getnames.jar getnames.class

 

3. Install stored procedure into the with database-appropriate procedures.  With Apache DB (Derby) this involves invoking built-in stored procedures to install the jar and tell Derby to search for that path when looking up stored procedures.

ij> CONNECT 'jdbc:derby://localhost:1527/sample;user=admin;password=pwd';
ij> CALL SQLJ.INSTALL_JAR('/path/to/getnames.jar', 'ADMIN.GETNAMES', 0);
or
ij> CALL SQLJ.REPLACE_JAR('/path/to/getnames.jar', 'ADMIN.GETNAMES');
ij> CALL SYSCS_UTIL.SYSCS_SET_DATABASE_PROPERTY
         ('derby.database.classpath','ADMIN.GETNAMES');

 

Invoking Database Stored Procedures from COBOL

The typical fashion of invoking stored procedures from a COBOL program is to incllude the CALL statement within an EXEC SQL block:

EXEC SQL
    CALL SCHEMANAME.PROCNAME(:PARM1, :PARM2, :PARM3);
END-EXEC

From the earlier CREATE PROCEDURE example we saw that parameters are defined to the database as either IN, OUT or INOUT variety.  However that information is not on the CALL statement or in the definition of the COBOL elements passed as parameters.  JDBC is defined in such a way that these parameter types must be known before invoking a stored procedure: Attempting to "set" an OUT parameter or "get" and IN parameter will throw a SQLException.

For the Elastic COBOL compiler to be made aware of the definition of stored procedure parameter the SQL Syntax Checking options must be specified at compile time to invoke the JDBC prepare statement operation.  This is also useful in general to verify at compile time that the tables your COBOL program will be accessing are in the database.  The information Elastic COBOL learns during this syntax checking process also helps optimize and eliminate semantic errors by implying a USAGE IS SQL TYPE IS sql-data-type for COBOL elements used in WHERE clauses, INSERT and UPDATE statements.  See Elastic COBOL Compiler Options for more details and the table above in the prior section. If the compiler cannot check SQL syntax for a CALL statement it will generate one or more of the following warnings:

Database JDBC driver not on CLASSPATH prior to starting Eclipse:

Multiple markers at this line
    -SQL Check: Class not found on CLASSPATH - org.apache.derby.jdbc.ClientDriver
    -SQL Check: Assuming all stored procedure parameters are INOUT; use '-sql:url' compiler directive to
     determine otherwise
    -SQL Check: No suitable driver found for jdbc:derby://localhost:1527/derbyDB

Elastic COBOL runtime not on CLASSPATH prior to starting Eclipse:

Multiple markers at this line
    -SQL Check: Error: Could not find or load main class com.heirloomcomputing.ecs.sql.execJDBC
    -SQL Check: Could not invoke JDBC SQL checker as requested by '-sql:url' directive. Check CLASSPATH for
     'ecobol.jar' and PATH for 'java'.
    -SQL Check: Assuming all stored procedure parameters are INOUT; use '-sql:url' compiler directive to
     determine otherwise

Database not running or incorrect JDBC URL at compile time:

Multiple markers at this line
    -SQL Check: Assuming all stored procedure parameters are INOUT; use '-sql:url' compiler directive to
     determine otherwise
    -SQL Check: java.net.ConnectException : Error connecting to server localhost on port 1527 with message
     Connection refused.:

One or more result sets may be returned from a stored procedure.  In the COBOL EXEC SQL syntax the stored procedure is associated with LOCATOR variables which themselves may be returned in a linkage section to the calling COBOL program or passed to a COBOL subprogram.  At that point SQL cursors are allocated to the locators at which point  retrieval is performed with the standard FETCH statement.  The following examples invokes the stored procedure  installed above.  The app will dump the results of the two result sets returned.

      $SET DIRECTIVE "-out:cobolinjava"
      $SET DIRECTIVE "-sql:jdbc     4"
      $SET DIRECTIVE "-sql:user     admin"
      $SET DIRECTIVE "-sql:password pwd"
      $SET DIRECTIVE "-sql:driver org.apache.derby.jdbc.EmbeddedDriver"
      $SET DIRECTIVE "-sql:url jdbc:derby:testa9"
       IDENTIFICATION DIVISION.
       PROGRAM-ID.    ExecName.
      *
      * invoke a stored procedure within Apache DB that
      * returns 2 result sets
      *
      * test setup:  install ADMIN.GETNAMES stored procedure
      * into Apache DB (Derby) as indicated in GETNAMES.CBL.
      * run this with the appropriate connection URL that matches
      * the above compile-directives, e.g.,
      *   java -cp /path/to/ecobol.jar:/path/to/derby.jar:this.jar \
      *      -Dsql.default.url=jdbc:derby:testa9 \
      *      -Dsql.default.user=admin -Dsql.default.password=pwd \
      *      -Dsql.default.driver=org.apache.derby.jdbc.EmbeddedDriver \
      *      ExecName
      * or from a jar that contains the drivers and a deploy_settings
      * file that contains the connection information, e.g.,
      *   java -jar this.jar
      *
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       INPUT-OUTPUT SECTION.       
       DATA DIVISION.
       
       WORKING-STORAGE SECTION.
       01  WS-NAME            PIC X(10).
       01  WS-OUT-CODE        PIC S9(6).
       01  WS-RESULT          PIC X(10).
       01  I                  PIC S9(9).

      * DECLARE A RESULT SET LOCATOR FOR THE RESULT SET   *
      * THAT IS RETURNED.                                 *
       01  LOC1               USAGE SQL TYPE IS
                              RESULT-SET-LOCATOR VARYING.
       01  LOC2               USAGE SQL TYPE IS
                              RESULT-SET-LOCATOR VARYING.
       
           EXEC SQL INCLUDE SQLCA  END-EXEC.
       
       PROCEDURE DIVISION.
      *------------------
       PROG-START.
      *     Connect to the DB (make sure derbyclient.jar is on
      *     the classpath)
      *     connect to the DB.  Alternative to CONNECT statement
      *     is to start the program with
      *     -Dsql.default.url=www,      -Dsql.default.user=xxx,
      *     -Dsql.default.password=yyy, -Dsql.default.driver=zzz
            IF SQLCODE NOT EQUAL 0 THEN
                DISPLAY "KNOWN - can't connect" UPON SYSOUT
                DISPLAY "SQLCODE " SQLCODE UPON SYSOUT
                DISPLAY "SQLERRMC " SQLERRMC UPON SYSOUT
                MOVE 8 TO RETURN-CODE
                GOBACK
            END-IF.
            
      *     set key to middle of the names
            MOVE 'gggggggggg' TO WS-NAME.

      *     invoke the SP which returns two result sets,
      *     tuples before the WS-NAME key and those after it
            EXEC SQL
               CALL ADMIN.GETNAMES(
                          :WS-NAME,
                          :WS-OUT-CODE)
            END-EXEC.

      *     Note:  IBM DB2 returns +466 for "OK", Derby 0
            IF SQLCODE not equal to 0 THEN
                DISPLAY 'CALL GETNAMES() FAILED WITH SQLCODE '
                    SQLCODE " - " SQLERRMC UPON SYSOUT
                display "fail" upon sysout
                MOVE 8 TO RETURN-CODE
                goback
            ELSE
                PERFORM GET-PARMS
                PERFORM GET-RESULT-SET
            END-IF.

       PROG-END.
            display "pass" upon sysout.
            MOVE 0 TO RETURN-CODE.
            GOBACK.

       GET-PARMS.
      *     verify the call worked
            IF WS-OUT-CODE NOT EQUAL TO 22 THEN
                DISPLAY 'CALL GETNAMES() FAILED WITH OUT-CODE '
                    WS-OUT-CODE UPON SYSOUT
                MOVE 8 TO RETURN-CODE
                GOBACK
            ELSE
                DISPLAY 'CALL GETNAMES() PASSED WITH OUT-CODE '
                    WS-OUT-CODE UPON SYSOUT
            END-IF.

       GET-RESULT-SET.
      *    Associate "locator" variables with the stored proc
           EXEC SQL
               ASSOCIATE LOCATORS (:LOC1, :LOC2)
               WITH PROCEDURE ADMIN.GETNAMES
           END-EXEC.
      *    Link the ResultSet to the Locator
           EXEC SQL
               ALLOCATE C1 CURSOR FOR RESULT SET :LOC1
           END-EXEC.
           IF SQLCODE NOT EQUAL TO 0 THEN
               DISPLAY "FAIL TO ALLOCATE 1st CURSOR "
                   SQLCODE " - " SQLERRMC UPON SYSOUT
               MOVE 8 TO RETURN-CODE
               GOBACK
           END-IF.
      *
           DISPLAY "" UPON SYSOUT.
           DISPLAY "RECORDS BEFORE '" WS-NAME "':" UPON SYSOUT.
           PERFORM GET-ROWS VARYING I
               FROM 1 BY 1 UNTIL SQLCODE EQUAL TO +100.
      *
           EXEC SQL
               CLOSE C1
           END-EXEC.
           IF SQLCODE NOT EQUAL TO 0 THEN
               DISPLAY "FAIL TO CLOSE 1st CURSOR "
                   SQLCODE " - " SQLERRMC UPON SYSOUT
               MOVE 8 TO RETURN-CODE
               GOBACK
           END-IF

      *    Link the ResultSet to the Locator (note cursor reuse)
           EXEC SQL
               ALLOCATE C1 CURSOR FOR RESULT SET :LOC2
           END-EXEC.
           IF SQLCODE NOT EQUAL TO 0 THEN
               DISPLAY "FAIL TO ALLOCATE 2nd CURSOR"
                   SQLCODE " - " SQLERRMC UPON SYSOUT
               MOVE 8 TO RETURN-CODE
               GOBACK
           END-IF
      *
           DISPLAY "" UPON SYSOUT.
           DISPLAY "RECORDS AFTER '" WS-NAME "':" UPON SYSOUT.
           PERFORM GET-ROWS VARYING I
               FROM 1 BY 1 UNTIL SQLCODE EQUAL TO +100.
      *
           EXEC SQL
               CLOSE C1
           END-EXEC.
           IF SQLCODE NOT EQUAL TO 0 THEN
               DISPLAY "FAIL TO CLOSE 2nd CURSOR"
                   SQLCODE " - " SQLERRMC UPON SYSOUT
               MOVE 8 TO RETURN-CODE
               GOBACK
           END-IF
           
       GET-ROWS.
           EXEC SQL
               FETCH C1 INTO :WS-RESULT
           END-EXEC.
           IF SQLCODE = 0 then
               DISPLAY "  " WS-RESULT UPON SYSOUT
           ELSE IF SQLCODE NOT EQUAL TO +100 THEN
               DISPLAY "  ** ERROR SQLCODE: "
                   SQLCODE " - " SQLERRMC UPON SYSOUT
               MOVE 8 TO RETURN-CODE
               GOBACK
           END-IF END-IF.
       END PROGRAM.

For more information on COBOL stored procedure syntax, see individual database documentation.

A comprehensive, single file demonstration of COBOL stored procedures is attached below as an EBP JCL deck.

 

Was this article helpful?
1 out of 1 found this helpful
Have more questions? Submit a request

1 Comments

  • 0
    Avatar
    John

    This would have been far more useful if you had shown how a java client or a C# client would call the stored procedure.  This is a more likely real world scenario.

Please sign in to leave a comment.
Powered by Zendesk