Top
NetCOBOL V11.0 Getting Started
FUJITSU Software

3.2 Integrating COBOL Programs with Visual Basic

This section contains detailed information regarding the integration of NetCOBOL programs with Visual Basic applications.

COBOL DLL Interaction with Visual Basic

To access any COBOL routines from Visual Basic, you need to first declare the COBOL PROGRAM-ID or the COBOL ENTRY routine using the Basic DECLARE statement with the special LIB keyword to specify the path name of the COBOL DLL. These declarations can be made in the declaration section of any form module or in the global module, and must be declared as Private. You can then call these routines from your Visual Basic code like any other function call.

When a Visual Basic program calls a COBOL routine, you should call JMPCINT2 before calling the first COBOL routine, and call JMPCINT3 after calling the last COBOL routine. JMPCINT2 is a subroutine that initializes the COBOL Run Time Environment and JMPCINT3 is a subroutine that exits the COBOL Run Time Environment.

Calling COBOL routines without calling JMPCINT2 and JMPCINT3 may degrade performance because the COBOL Run Time Environments will be initialized and exited on every COBOL routine called.


Visual Basic Declarations of COBOL Modules

Private Declare Sub PROG Lib "c:\mycobol.dll" (vbInteger as Integer, ByVal vbString as String)
Private Declare Sub JMPCINT2 Lib "C:\Program Files\Fujitsu NetCOBOL for Windows\F3BIPRCT.DLL" ()
Private Declare Sub JMPCINT3 Lib "C:\Program Files\Fujitsu NetCOBOL for Windows\F3BIPRCT.DLL" ()

NOTE: The above Declare statements should all be on a single line, they have beenwrapped in this text to fit the width of the page.


Visual Basic Call to a COBOL Program

Sub Form_Click ( )
Dim vbInteger as Integer
Dim vbString as string * 15
Call JMPCINT2 ‘ Initialize COBOL Runtime Environment
Call PROG (vbInteger, vbString)
Call JMPCINT3 ‘ Terminate COBOL Runtime Environment
End Sub

COBOL LINKAGE SECTION and PROCEDURE DIVISION

Identification Division.
Program-ID. "PROG".
Data Division.
Linkage Section.
01 vbInteger pic s9(4) comp-5.
01 vbString pic x(15).
Procedure Division with STDCALL Linkage Using vbInteger, vbString.
     move 100 to vbInteger
     move "NetCOBOL" to vbString
     exit program.

Parameter Passing Between Visual Basic and NetCOBOL

Visual Basic treats a COBOL DLL as a “black box.” It only needs to know the COBOL program's LINKAGE SECTION parameter list to pass data to and from the COBOL DLL. Parameters can only be passed from Visual Basic to COBOL BY REFERENCE, except strings which must be passed using the ByVal keyword in the DECLARE statement. Passing parameters BY REFERENCE is the default in Visual Basic.

Parameter names need not be the same between Visual Basic and COBOL, however, attribute, length, and number of corresponding data items must be identical.

Visual Basic declarations must exactly match the COBOL parameter lists defined in the USING statement of the COBOL PROCEDURE DIVISION or ENTRY statements. No parameter checking is done because the two are separate compilation units.

Visual Basic incorporates a rich assortment of data types, some of which are currently not supported by NetCOBOL. These data types include variable-length strings, Variants, and objects.

Similarly not all COBOL data types are supported by Visual Basic.


Visual Basic Strings

All strings passed between Visual Basic and COBOL must be declared as fixed-length strings and passed using the ByVal keyword in the DECLARE statement. To avoid possible memory corruption, ensure that all strings passed between Visual Basic and COBOL occupy the same size.

Dim vbString as string * 15 ‘ Equivalent to PIC X(15)

Corresponding Visual Basic and COBOL Data Types

When passing parameters, associate the data types as follows:

The table below lists the classes and encoding forms.

Visual Basic

COBOL

Type Name

Storage Size

PICTURE Clause

Boolean (16bit)

Boolean (32bit)

Byte

Currency

Double

Integer

Long

Single

String

2 Bytes

4 Bytes

1 Byte

8 bytes

8 Bytes

2 Bytes

4 Bytes

4 Bytes

1 Byte per Character

S9(4) COMP-5

S9(9) COMP-5

X

S9(10)V9(4) COMP-5

COMP-2

S9(4) COMP-5

S9(9) COMP-5

COMP-1

X(n)


Passing Arrays

Visual Basic and COBOL can pass numeric arrays. This works because numeric array data is always laid out sequentially in memory. A COBOL routine, if given the first element of an array, has access to all of its elements.


Passing the Currency Data Type

The Currency data type in Visual Basic equates to

PIC S9(14)V9(4) COMP-5.

You can pass Currency parameters if the receiving Linkage Section item has this picture clause.

A Visual Basic declaration of a COBOL subroutine receiving the Currency data type would look like the following:

Private Declare Sub CSPRINT Lib "c:\CSPRINT.dll" (cc As Currency)
Private Declare Sub JMPCINT2 Lib "c:\Program Files\Fujitsu NetCOBOL for Windows\f3biprct.dll" ()
Private Declare Sub JMPCINT3 Lib "c:\Program Files\Fujitsu NetCOBOL for Windows\f3biprct.dll" ()

NOTE: The above Declare statements should all be on a single line, they have been wrapped in this text to fit the width of the page.


CSPRINT is the COBOL subroutine; JMPCINT2 and JMPCINT3 are required for mixed language applications including Visual Basic and COBOL.

The code leading to, and including the subroutine call would look like this:

Dim cc As Currency
cc = 100.0001
Call CSPRINT(cc)

The COBOL program processing the COMP-5 equivalent of Currency would look the following:

000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. CSPRINT.
000030 ENVIRONMENT DIVISION.
000061 DATA DIVISION.
000101 LINKAGE SECTION.
000102 01 CC PIC S9(14)V9(4) COMP-5.
000110 PROCEDURE DIVISION WITH STDCALL USING CC.
000150      ADD 1 TO CC.
000160 EXIT PROGRAM.

NOTE: If the data type is converted (for instance, if it is moved to a PACKED-DECIMAL field, or DISPLAYed), then the value of the data may be truncated.


Returning Control and Exiting Programs

To return control from COBOL to Visual Basic, execute the EXIT PROGRAM statement. When the EXIT PROGRAM statement is executed, control returns immediately to the calling program.


Compiling and Linking the COBOL Programs

To build the COBOL DLL, you must tell the linker which entry points are to be made external (i.e. those entry points that will be called from Visual Basic). You can do this by:

  1. Specifying the /ENTRY:entry-name linker option for each entry point, or:

  2. Creating a module definition file (.DEF) that lists the attributes of the DLL library. You can modify the example below, changing the “PROG” to match the COBOL PROGRAM-ID (or other ENTRY name that you call).

    LIBRARY "dll-name"
    EXPORTS PROG

You then save this file as “prog-name.DEF”, where prog-name is the name of your program.

Add it to your project by right clicking on the DLL file node and select New Folder, Module Definition File, from the pop-up menu. You then add the .DEF file to that folder.