21. 4GL Statement Glossary : Callproc : Coding COBOL Procedures
 
Share this page                  
Coding COBOL Procedures
Use the format below when coding a COBOL procedure:
IDENTIFICATION DIVISION.
PROGRAM-ID. Procname.
ENVIRONMENT DIVISION.
DATA DIVISION.
  Processing statement
LINKAGE SECTION.
  Processing statements 
PROCEDURE DIVISION
  processing statements
In COBOL, you pass integers as four bytes by reference (by name), floats are passed as double format floats by name and characters are passed by name, as the address of the character argument. You can pass decimals as double format floats by name, or as packed decimals. Specify whether you want to pass decimals as floats or decimals on the ABF or Vision procedure definition frame. Passing decimal values as floats allows compatibility with previous versions of Ingres, which did not support the decimal data type.
The length for a character string, as specified in the COBOL procedure, must be the length of the actual argument. In the example below, z is given a PICTURE of X(16) because the actual argument ('This is a string') is 16 characters long. In general, COBOL only has fixed-length strings. When passing string values from 4GL to COBOL you must use one of the fixed-length types, c or char. This guarantees that a blank-padded string of a known length is passed.
For example, in the initialize section of a frame, declare the local variable to_cobol with the following format:
to_cobol = char(16)
Consider this call to a procedure q:
to_cobol = 'This is a string';
callproc q(1+2, 2.3, to_cobol);
The following declarations are required:
IDENTIFICATION DIVISION.
PROGRAM-ID. Q.
ENVIRONMENT DIVISION.
DATA DIVISION.
LINKAGE SECTION.
01 x PICTURE S9(8) USAGE COMP.
01 y USAGE COMP-2.
01 z PICTURE X(16).
PROCEDURE DIVISION USING x,y,z
In the previous declarations, the decimal values for decimal literals as well as variables are passed as floats. To declare the decimal value as a packed decimal, use declarations similar to the following for a 4GL decimal(5,2):
IDENTIFICATION DIVISION.
PROGRAM-ID. Q.
ENVIRONMENT DIVISION.
DATA DIVISION.
LINKAGE SECTION.
01 x PICTURE S9(8) USAGE COMP.
01 y PICTURE S9(3) V9(2) USAGE COMP-3.
01 z PICTURE X(16).
PROCEDURE DIVISION USING x,y,z
In COBOL, you can return an integer value only, as shown below:
IDENTIFICATION DIVISION.
PROGRAM-ID. Reti.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 r PICTURE S9(8) USAGE COMP.
LINKAGE SECTION.
PROCEDURE DIVISION GIVING r.
sbegin.
  MOVE 10 TO r.
EXIT PROGRAM reti.
Note that the PICTURE S9(8) data type in COBOL corresponds to the 4‑byte integer data type in 4GL.