In this appendix, the term COBOL implies OS/VS COBOL, VS COBOL II, IBM COBOL for MVS and VM, or VSE IBM COBOL for VSE.
Figure 118 shows how SQL statements can be coded
Figure 118. Coding SQL Statements in COBOL Program Sections
SQL Statement | Program Section |
---|---|
BEGIN DECLARE SECTION
|
WORKING STORAGE or
|
INCLUDE SQLCA | WORKING-STORAGE SECTION |
INCLUDE text_file_name |
PROCEDURE DIVISION or
|
Other | PROCEDURE DIVISION SQL statements are coded between columns 12 and 72 inclusive. |
The system checks that SQL statements are not used in nested programs. Also if one program immediately follows another program, the second program must not contain SQL statements.
The rules for continuation of tokens from one line to the next are the same as the COBOL rules for the continuation of words and constants. If a string-constant is continued from one line to the next, the first non-blank character in that next line must be a single quotation mark (') or a double quotation mark ("). If a delimited SQL identifier (such as "EMP TABLE") is continued from one line to the next, the first non-blank character in that next line must be a double quotation mark. COBOL comment lines, identified by an asterisk * in column 7, can be coded within an embedded statement.
Delimiters are required on all SQL statements to distinguish them from regular COBOL statements. You must precede each SQL statement with EXEC SQL, and terminate each one with END-EXEC. Any desired COBOL punctuation, such as a period, can be placed after the END-EXEC.
For example, suppose an SQL statement occurs as one of several statements nested inside a COBOL IF-statement. In this instance, the SQL statement should not be followed by a period.
EXEC SQL must be specified within one line; the same is true for END-EXEC. A separator (such as a blank space, SQL comment, or end-of-line) must precede the END-EXEC that terminates an SQL statement; however, no punctuation is required after the END-EXEC.
If an SQL statement appears within an IF sentence such that a COBOL ELSE clause immediately follows the SQL statement, the clause must begin with the word ELSE. In addition, this ELSE must be contained entirely on one line. (No continuation is allowed for the word ELSE).
SQL WHENEVER and DECLARE CURSOR statements should not be the only contents of COBOL IF or ELSE clauses as the preprocessor does not generate COBOL code for these statements.
If an SQL statement terminates a COBOL IF sentence, a period should immediately follow END-EXEC with no intervening blanks. A blank should follow the period.
Because a COBOL statement can be immediately preceded by a paragraph name, so can an embedded SQL statement. Similarly, an embedded SQL statement in the Procedure Division can be immediately followed by a separator period.
Mixed case can be used in your COBOL program. The SQL preprocessor will change the lowercase into uppercase, except for text within quotation marks, which will be left in the original case.
You must declare all host variables in an SQL declare section. For a description of an SQL declare section, refer to "Declaring Variables That Interact with the Database Manager".
Declare host variables in the source file before the first use of the variable in an SQL statement. All SQL declare sections must be located in the Working-Storage Section, the File Section, or the Linkage Section of the Data Division. You can use the following types of variables in an SQL statement:
For information on the use of these variables in an SQL statement, refer to Using Host Variables and Using Host Structures.
Note: | You can declare non-host variables in an SQL declare section; however, declarations that do not conform to DB2 Server for VSE & VM declaration rules may return errors. |
The declaration of a host variable is subject to the following rules:
01 IND_ARRAY. 05 IND-ELEMENT OCCURS 15 TIMES PIC S9(4) COMP.
The COBOL preprocessor recognizes IND-ELEMENT as the indicator array.
You cannot use indicator array elements as main variables or indicator variables.
01 VARCHAR-FIELD. 49 LEN-FIELD PIC S9(4) COMP. 49 TXT-FIELD PIC X(25).
This structure defines a VARCHAR host variable with the name VARCHAR-FIELD and a length of 25. You cannot use this group item as a host structure; you cannot use the elementary items in the structure as host variables.
For the rules for varying-length string variables, refer to Figure 120.
01 PROJ-STRCT. 05 PROJNO PIC X(6). 05 ACTNO PIC S9(4) COMP. 05 ACSTAFF PIC S9(9) COMP. 05 ACSTDATE PIC X(10). 05 ACENDATE PIC X(10).
This structure represents the following list of host variables when used in an SQL statement:
PROJNO, ACTNO, ACSTAFF, ACSTDATE, ACENDATE
The two following SQL statements are equivalent:
EXEC SQL SELECT PROJNO, ACTNO, ACSTAFF, ACSTDATE, ACENDATE INTO :PROJ-STRCT FROM PROJ_ACT WHERE PROJNO = '100000'
EXEC SQL SELECT PROJNO, ACTNO, ACSTAFF, ACSTDATE, ACENDATE INTO :PROJNO, :ACTNO, : ACSTAFF, :ACSTDATE, :ACENDATE FROM PROJ_ACT WHERE PROJNO = '100000'
A host structure can be a stand-alone group item or a substructure of a more complex group item. The following example is a complex group item that contains a host structure:
01 EMPLOYEE. 05 EMPNO PIC X(6). 05 EMPNAME. 10 FIRSTNAME PIC X(12). 10 MIDINIT PIC X(1). 10 LASTNAME PIC X(15). 05 WORKDEPT PIC X(3). 05 PHONENO PIC X(4).
The group item EMPNAME is a host structure.
You can use the elementary items in the host structure and the elementary items in the group item containing a host structure as host variables. In the previous example, the following elementary items can be used as host variables:
EMPNO, FIRSTNAME, MIDINIT, LASTNAME, WORKDEPT, PHONENO
You can include a subordinate group item in the host structure to represent a varying-length string element if that group item conforms to the rules for a varying-length string definition. All of the rules previously stated for the definition of varying-length strings also apply in this situation. The following example is a host structure that contains a VARCHAR element:
01 EMPNAME. 05 FIRSTNAME. 49 FNLEN PIC S9(4) COMP. 49 FNTEXT PIC X(12). 05 MIDINIT PIC X(1). 05 LASTNAME. 49 LNLEN PIC S9(4)COMP. 49 LNTEXT PIC X(15).
The COBOL preprocessor interprets the structure EMPNAME as a host structure containing three elements: FIRSTNAME with data type VARCHAR and length 12, MIDINIT with data type CHAR and length 1, and LASTNAME with data type VARCHAR and length 15.
Note: | Any structure that matches the description of a varying-length string definition is interpreted as a varying-length definition and cannot be used as a host structure. |
WORKING-STORAGE SECTION. EXEC SQL BEGIN DECLARE SECTION END-EXEC. 01 EMPNAME. 05 FIRST-NM PIC X(8). 05 LAST-NM PIC X(8). 05 ADDRESS. 49 ADD-LEN PIC S9(4) COMP. 49 ADD-TXT PIC X(200). EXEC SQL END DECLARE SECTION END-EXEC. PROCEDURE DIVISION. EXEC SQL SELECT FIRSTNAME, LASTNAME, ADDRESS INTO :EMPNAME FROM EMPLOYEE WHERE LASTNAME = 'JOHANSON' END-EXEC
In this example, empname is considered by the COBOL preprocessor to be a two-level structure because the structure of address matches that of a VARCHAR data type. As a result, empname may be used in the SELECT statement. If, for example, addlen was changed from "PIC S9(4) COMP" to "PIC S9(9) COMP", the structure of address would no longer match a VARCHAR data type and empname would be considered a three-level structure. As a result, empname could NOT be used in a SELECT statement.
In the declaration below, only DATES and PRODUCT may be used as host structures. ORDERNO and CUSTNUM may be used as scalar host host variables, and may be qualified as CUSTORD.ORDERNO and ORDINFO.CUSTNUM or CUSTORD.ORDINFO.CUSTNUM.
WORKING-STORAGE SECTION. EXEC SQL BEGIN DECLARE SECTION END-EXEC. 01 CUSTORD. 03 ORDERNO PIC X(10). 03 ORDINFO. 05 CUSTNUM PIC X(10). 05 DATES. 10 ORDDATE PIC X(6). 10 DELIVDTE PIC X(6). 03 PRODUCT. 05 STOCKNO PIC X(10). 05 QUANTITY PIC X(3). EXEC SQL END DECLARE SECTION END-EXEC. PROCEDURE DIVISION. EXEC SQL SELECT STOCKNO, QUANTITY INTO :PRODUCT FROM ORDER WHERE STOCKNO = '1234567890' END-EXEC.
Note: | Due to the restriction on the number of host variables in a statement, host structures with greater than 256 fields will not be allowed, |
When you reference host variables, host structures, structures fields, or indicator arrays in an SQL statement, you must precede each reference by a colon (:). The colon distinguishes these variables from SQL identifiers (such as column names). The colon is not required outside an SQL statement.
When you code on-line command level application programs in COBOL, be aware of the following CICS/VSE restriction. The length of the working storage plus the length of the TGT (TARGET GLOBAL TABLE) must not exceed 64K bytes.
This restriction only applies when using Long VARCHAR Host Variables because the length of a single long VARCHAR host variable can be up to 32K bytes.
DB2 Server for VSE |
---|
If the COBOL compiler QUOTE option is used or if the QUOTE option has been specified in the CBL statement of COBOL, then the QUOTE (or Q) option of the preprocessor should also be specified. You should use a single quotation mark (') to delineate constants used in embedded SQL statements, regardless of the COBOL compiler QUOTE option. |
DB2 Server for VM |
---|
If the COBOL compiler QUOTE option is used, the QUOTE (or Q) option of the preprocessor should also be specified. Use a single quotation mark (') to delineate constants used in embedded SQL statements, regardless of the COBOL compiler QUOTE option. |
When the COB2 parameter is specified, certain functions supported by the COBOL II Release 3 compiler, and later, are also supported by the database manager. These functions include:
In order to make use of these features, you must specify the COB2 option when preprocessing your application. Existing applications that use these features must be repreprocessed and recompiled.
When the COB2 parameter is specified, certain functions supported by the COBOL II Release 3 compiler, and later, are also supported by the database manager. These functions include:
Picture S9(4) USAGE BINARY and Picture S9(p)[V9(s)] USAGE PACKED-DECIMAL
where "p" is the precision and "s" is the scale.
01 HEADING2. 03 FILLER Pic x(6) VALUE 'ITEM NUMBER'. 03 FILLER Pic x(5) VALUE SPACES. 03 FILLER Pic x(11) VALUE 'DESCRIPTION'. 03 Pic x(4) VALUE SPACES. 03 FILLER Pic x(8) VALUE 'QUANTITY'.
In order to make use of these features, you must specify the COB2 option when preprocessing your application. Existing applications that are to make use of these features must be repreprocessed and recompiled.
You should not use the COBOL COPY verb to invoke COPYBOOKS that involve SQL host variables. Instead, use the SQL INCLUDE statement to invoke such COPYBOOKs. This arrangement is necessary because the preprocessor is run before the COBOL compiler.
When the COBRC parameter is specified, the preprocessor will generate the statement 'MOVE ZEROS TO RETURN-CODE' after it generates a call to ARIPRDI. This solves the problem of unexpected or invalid return codes being reported after a COBOL II (IBM COBOL for MVS and VM or IBM COBOL for VSE) application ends. For example, a REXX EXEC may contain several steps which each execute based on a return code from the previous step. If the application programmer has not set the COBOL special register, RETURN-CODE, the return code is not reliable. This new parameter may be used instead of explicitly setting the special register.
Limitations:
MOVE 4 TO RETURN-CODE. EXEC SQL INSERT INTO MYTABLE VALUES (1,2). STOP RUN.
The application will end with return code 0 instead of 4 because when the EXEC SQL statement is expanded the last line generated is 'MOVE ZEROS TO RETURN-CODE'.
For Version 3.2 of COBOL II or later, use the TRUNC(BIN) compiler option, because the system is half-word boundary sensitive. Under this option, receiving fields are truncated only at halfword, fullword, or doubleword boundaries.
To include the external secondary input, specify the following at the point in the source code where the secondary input is to be included:
EXEC SQL INCLUDE text_file_name END-EXEC.
The text_file_name is a C-Type source member of a VSE library. Text_file_name is the file name of a CMS file, with a "COBCOPY" file type, located on a CMS minidisk accessed by the user.
The INCLUDE statement can appear anywhere within the File, Linkage, or Working Storage Sections of the Data Division, and anywhere within the Procedure Division, including the Declaratives Section, if one is used. Note that the INCLUDE statement is the only type of SQL statement that is allowed within the Declaratives Section of a Procedure Division.
COBOL variables used in SQL statements must be type-compatible with the columns of the tables with which they are to be used (stored, retrieved, or compared). Of course, an overflow condition may occur if, for example, an INTEGER data item is retrieved into a PICTURE S9(4) variable, and its current value is too large to fit.
The database manager recognizes the DISPLAY SIGN LEADING SEPARATE (DSLS) attribute for COBOL host variables. It converts input host variables in the DSLS format to the required column format, and output host variables from the column format to DSLS format.
The character data types CHAR, VARCHAR, and LONG VARCHAR are considered compatible. The graphic data types GRAPHIC, VARGRAPHIC, and LONG VARGRAPHIC are considered compatible. A varying-length string is automatically converted to a fixed-length string, and a fixed-length string is automatically converted to a varying-length string when necessary. If a varying-length string is converted to a fixed-length string, it is truncated or padded on the right with blanks to the correct length. The system also truncates or pads with blanks if a fixed-length string is assigned to another fixed-length string of a different size (for example, a variable of PICTURE X(12) is stored in a column of type CHAR(18)).
The system also considers the datetime data types to be compatible with character data types (fixed or varying, but not LONG VARCHAR and VARCHAR > 254).
Refer to Converting Data for a data conversion summary.
You may want to consider the following points when coding SQL statements and host variable declarations:
blanks | | V V QUANT - :ORDER-AMOUNT
DB2 Server for VSE |
---|
If your program contains DBCS characters, the following sequence of processing is necessary:
|
The rules for the format and use of DBCS characters in SQL statements are the same for COBOL as for other host languages supported by the system. For a discussion of these rules, see Using a Double-Byte Character Set (DBCS).
When coding graphic constants in SQL statements, use the SQL format of the graphic constant:
G'<(XXXX)>'
Note: | N is a synonym for G. |
See Using Graphic Constants for a discussion of graphic constants.
The COBOL preprocessor does not support options for changing the encoding for the < and > characters.
You can declare the SQLCA return code structure that is required for the system in two ways:
EXEC SQL INCLUDE SQLCA END-EXEC.
in the Working-Storage Section of your source program. The preprocessor replaces this with a declaration of the SQLCA structure.
Figure 119. SQLCA Structure (in COBOL)
01 SQLCA. 05 SQLCAID PIC X(8). 05 SQLCABC S9(9) COMPUTATIONAL. 05 SQLCODE PIC S9(9) COMPUTATIONAL. 05 SQLERRM. 49 SQLERRML PIC S9(4) COMPUTATIONAL. 49 SQLERRMC PIC X(70). 05 SQLERRP PIC X(8). 05 SQLERRD OCCURS 6 TIMES PIC S9(9) COMPUTATIONAL. 05 SQLWARN. 10 SQLWARN0 PIC X(1). 10 SQLWARN1 PIC X(1). 10 SQLWARN2 PIC X(1). 10 SQLWARN3 PIC X(1). 10 SQLWARN4 PIC X(1). 10 SQLWARN5 PIC X(1). 10 SQLWARN6 PIC X(1). 10 SQLWARN7 PIC X(1). 10 SQLWARN8 PIC X(1). 10 SQLWARN9 PIC X(1). 10 SQLWARNA PIC X(1). 05 SQLSTATE PIC X(5). |
A COBOL program containing SQL statements must have a Working-Storage Section. The meanings of the fields within the SQLCA are discussed in the DB2 Server for VSE & VM SQL Reference manual.
In COBOL, the object of a GO TO in the SQL WHENEVER statement must be a section name or an unqualified paragraph name.
You may find that the only variable in the SQLCA you really need is SQLCODE. If this is the case, declare just the SQLCODE variable and invoke NOSQLCA support at preprocessor time.
The number of SQLCODE declarations is not limited by the preprocessor. If a stand-alone SQLCODE is specified, the code inserted by the preprocessor into the COBOL code to expand an EXEC SQL statement will refer to the address of that SQLCODE. The COBOL compiler determines if multiple declarations within a program section are not acceptable. In addition, the COBOL compiler determines which region of the code an SQLCODE declaration refers to.
DB2 Server for VSE & VM does not pass the return code in register 15 on completion of SQL statement processing. The return code and any other information is passed in the SQLCA. Furthermore, if the COBRC preprocessor parameter was not specified, DB2 Server for VSE & VM does not set the return code to zeros on completion of SQL statement processing. If IBM COBOL for MVS and VM, IBM COBOL for VSE, or COBOL II is being used, this can cause register 15 to be uninitialized and can contain unpredictable data. This appears as very large return codes when the COBOL application ends. This does not occur with the DOS/VS COBOL compiler. It is the responsibility of the application programmer to set the return code to something meaningful. The COBOL special register RETURN-CODE should be set before the application program ends.
The simplest method is to code the following lines just before a STOP RUN or a GOBACK statement.
MOVE ZERO TO RETURN-CODE. STOP RUN.
Any return code meaningful to the application can be set. It can also be set to the SQLCODE if desired.
The COBOL preprocessor lets you use a descriptor area, the SQLDA, to execute dynamically defined SQL statements. (See Chapter 7, Using Dynamic Statements for more information on dynamic SQL statements and for more information on dynamic SQL statements and the SQLDA.) However, the COBOL preprocessor will not replace the statement EXEC SQL INCLUDE SQLDA with a declaration of the SQLDA structure, as is done with the SQLCA. Instead, EXEC SQL INCLUDE SQLDA would just include the secondary input file SQLDA, as described in "Using the INCLUDE Statement".
Before you can use the descriptor area you must properly allocate and initialize it, and you must manage all its address variables. The following example shows how you could define a descriptor area in the COBOL Working-Storage section for five fields:
01 DASQL. 02 DAID PIC X(8) VALUE 'SQLDA '. 02 DABC PIC S9(8) COMP VALUE 13216. 02 DAN PIC S9(4) COMP VALUE 5. 02 DAD PIC S9(4) COMP VALUE 0. 02 DAVAR OCCURS 1 TO 300 TIMES DEPENDING ON DAN. 03 DATYPE PIC S9(4) COMP. 03 DALEN PIC S9(4) COMP. 03 FILLER REDEFINES DALEN. 15 SQLPRCSN PIC X. 15 SQLSCALE PIC X. 03 DADATA POINTER. 03 DAIND POINTER. 03 DANAME. 49 DANAMEL PIC S9(4) COMP. 49 DANAMEC PIC X(30). |
Note: | DOS/VS COBOL 3.1 users cannot use the "USAGE IS POINTER" clause implied in this example for the DADATA and DAIND areas. Instead, these areas must be defined with the characteristics of PIC X(4). |
The descriptor area must not be declared within the SQL declare section.
The following pseudocode illustrates a use of the descriptor area, adequate for three fields:
- allocate storage for a Descriptor Area of at least size = 3 - set DAN = 3 (number of fields) - set DAD = 3 - set the rest of the values and pointers in the Descriptor Area EXEC SQL EXECUTE S1 USING DESCRIPTOR dasql |
When decimal data is used, the values of the SQLPRCSN and SQLSCALE field can be determined by declaring additional variables. For example:
01 PRCSNN PIC S9(4) COMP. 01 PRCSNC REDEFINES PRCSNN. 15 FILLCHAR1 PIC X. 15 PRCSNCHAR PIC X. 01 SCALEN PIC S9(4) COMP. 01 SCALEC REDEFINES SCALEN. 15 FILLCHAR2 PIC X. 15 SCALECHAR PIC X.
The following MOVE statements would move the precision and scale of the nth selected item into PRCSNN and SCALEN, respectively:
MOVE SQLPRCSN(n) TO PRCSNCHAR. MOVE SQLSCALE(n) TO SCARECHAR.
For COBOL, the string-spec in PREPARE and EXECUTE IMMEDIATE must be in the same format as the SQL VARCHAR data type (you must set the proper length) or a quoted string. If a quoted string is used, its length is limited to 120 characters (the maximum length allowed for COBOL constants). In addition, you cannot use a single (') or double (") quotation mark within a COBOL constant that is the object of a PREPARE or EXECUTE IMMEDIATE statement.
Figure 120. DB2 Server for VSE & VM Data Types for COBOL
Description |
DB2 Server for VSE & VM Keyword |
Equivalent COBOL Declaration |
---|---|---|
A binary integer of 31 bits, plus sign. | INTEGER or INT |
01 PICTURE S9(9) COMPUTATIONAL. |
A binary integer of 15 bits, plus sign. | SMALLINT |
01 PICTURE S9(4) COMPUTATIONAL. |
A packed decimal number, precision p, scale s (1 <= p <= 31 and 0 <= s<= p). In storage the number occupies a maximum of 16 bytes. Precision is the total number of digits. Scale is the number of those digits that are to the right of the decimal point. |
DECIMAL[(p[,s])]
|
01 PICTURE S9(x)[V9(y)] COMPUTATIONAL-3. or 01 PICTURE S9(x)[V9(y)] PACKED-DECIMAL. or 01 PICTURE S9(x)[V9(y)] DISPLAY SIGN LEADING SEPARATE Where x + y = p and y = s |
A single-precision (4-byte) floating-point number, in short System/390 floating-point format. |
REAL or
| COMPUTATIONAL-1. |
A double-precision (8-byte) floating-point number, in long System/390 floating-point format. |
FLOAT or
| COMPUTATIONAL-2. |
A fixed-length character string of length n where 0 < n <= 254. |
CHARACTER[(n)]
| 01 S PICTURE X(n). |
A varying-length character string of maximum length n. If n > 254 or <= 32 767, this data type is considered a long field. (See Using Long Strings for more information.) (Only the actual length is stored in the database.) | VARCHAR(n) |
01 S. 49 S-LENGTH PICTURE S9(4) COMPUTATIONAL. 49 S-VALUE PICTURE X(n). |
A varying-length character string of maximum length 32 767 bytes. | LONG VARCHAR |
01 S. 49 S-LENGTH PICTURE S9(4) COMPUTATIONAL. 49 S-VALUE PICTURE X(n). |
A fixed-length string of n DBCS characters where 0 < n <= 127. | GRAPHIC[(n)] |
01 GNAME PICTURE G(n) [DISPLAY-1]. |
A varying-length string of n DBCS characters. If n > 127 or <= 16383, this data type is considered a long field. (See Using Long Strings for more information.) | VARGRAPHIC(n) |
01 GNAME. 49 GGLEN PICTURE S9(4) COMPUTATIONAL. 49 GGVAL PICTURE G(n) [DISPLAY-1]. |
A varying-length string of DBCS characters of maximum length 16383. | LONG VARGRAPHIC |
01 XNAME. 49 XNAMLEN PICTURE S9(4) COMPUTATIONAL. 49 XNAMVAL PICTURE G(n) [DISPLAY-1]. |
A fixed or varying-length character string representing a date. The minimum and maximum lengths vary with both the format used and whether it is an input or output operation. See the DB2 Server for VSE & VM SQL Reference manual for more information. | DATE |
01 S PICTURE X(n). or 01 S. 49 S-LENGTH PICTURE S9(4) COMPUTATIONAL. 49 S-VALUE PICTURE X(n). |
A fixed or varying-length character string representing a time. The minimum and maximum lengths vary with both the format used and whether it is an input or output operation. See the DB2 Server for VSE & VM SQL Reference manual for more information. | TIME |
01 S PICTURE X(n). or 01 S. 49 S-LENGTH PICTURE S9(4) COMPUTATIONAL. 49 S-VALUE PICTURE X(n). |
A fixed or varying-length character string representing a timestamp. The lengths can vary on input and output. See the DB2 Server for VSE & VM SQL Reference manual for more information. | TIMESTAMP |
01 S PICTURE X(n). or 01 S. 49 S-LENGTH PICTURE S9(4) COMPUTATIONAL. 49 S-VALUE PICTURE X(n). |
A reentrant program has the characteristic of dynamic allocation of space for data and save areas. This reentrant characteristic can be used in COBOL programs that use the database manager.
DB2 Server for VSE |
---|
Such programs must follow the COBOL compiler's rules for producing reentrant programs, and must be repreprocessed, recompiled, and relinked with the OBJECT file ARIPADR4. Existing COBOL programs may continue to use ARIPADR until they are recompiled. Thereafter, they must link-edit the OBJECT file ARIPADR4. |
DB2 Server for VM |
---|
Such programs must follow the COBOL compiler's rules for producing reentrant programs, and must be repreprocessed, recompiled, and relinked with the TEXT file ARIPADR4. Existing COBOL programs (preprocessed prior to SQL/DS Version 2 Release 2) may continue to use ARIPADR until they are recompiled. Thereafter, they must link-edit the TEXT file ARIPADR4. After programs are recompiled, ARIPADR4 must be in their link or load step. |
The DYNAM option of the IBM COBOL for MVS and VM, IBM COBOL for VSE, and VS COBOL II compilers can be used by applications.
If the DYNAM option is used, then it is not necessary to include any of the linkage modules listed for COBOL programs in Link-Editing and Loading the Program (DB2 Server for VM) or Link-Editing and Loading the Program (DB2 Server for VSE.
DB2 Server for VSE |
---|
Applications using the DYNAM option must have access to the DB2 Server for VSE production library at run time. CICS/VSE programs do not support the DYNAM option; they must continue to be link-edited with the required extra linkage modules. |
DB2 Server for VM |
---|
COBOL applications that use the DYNAM option must have access to the DB2 Server for VM production disk at run time. |
The following example shows how to define the parameters in a stored procedure that uses the GENERAL linkage convention.
Figure 121. Stored Procedure - Using GENERAL Linkage Convention
IDENTIFICATION DIVISION. . . DATA DIVISION. . . LINKAGE SECTION. 01 PARM1 ... 01 PARM2 ... . . PROCEDURE DIVISION USING PARM1, PARM2. . . |
The following example shows how to define the parameters in a stored procedure that uses the GENERAL WITH NULLS linkage convention.
Figure 122. Stored Procedure - Using GENERAL WITH NULLS Linkage Convention
IDENTIFICATION DIVISION. . . DATA DIVISION. . . LINKAGE SECTION. 01 PARM1 ... 01 PARM2 ... 01 INDARRAY PIC S9(4) USAGE COMP OCCURS 2 TIMES. . . PROCEDURE DIVISION USING PARM1, PARM2, INDARRAY. . . |