Example of GENERAL linkage convention
Specify the GENERAL linkage convention when you do not want the calling program to pass null values for input parameters (IN or INOUT) to the stored procedure.
Examples
The following examples demonstrate how an assembler, C, COBOL, or PL/I stored procedure uses the GENERAL linkage convention to receive parameters.
For these examples, assume that a COBOL application has the following parameter declarations and CALL statement:
************************************************************
* PARAMETERS FOR THE SQL STATEMENT CALL *
************************************************************
01 V1 PIC S9(9) USAGE COMP.
01 V2 PIC X(9).
⋮
EXEC SQL CALL A (:V1, :V2) END-EXEC.
In the CREATE PROCEDURE statement, the parameters are defined as follows:
IN V1 INT, OUT V2 CHAR(9)
Assembler example
The following example shows how a stored procedure that is written in assembler language receives these parameters.
*******************************************************************
* CODE FOR AN ASSEMBLER LANGUAGE STORED PROCEDURE THAT USES *
* THE GENERAL LINKAGE CONVENTION. *
*******************************************************************
A CEEENTRY AUTO=PROGSIZE,MAIN=YES,PLIST=OS
USING PROGAREA,R13
*******************************************************************
* BRING UP THE LANGUAGE ENVIRONMENT. *
*******************************************************************
⋮
*******************************************************************
* GET THE PASSED PARAMETER VALUES. THE GENERAL LINKAGE CONVENTION*
* FOLLOWS THE STANDARD ASSEMBLER LINKAGE CONVENTION: *
* ON ENTRY, REGISTER 1 POINTS TO A LIST OF POINTERS TO THE *
* PARAMETERS. *
*******************************************************************
L R7,0(R1) GET POINTER TO V1
MVC LOCV1(4),0(R7) MOVE VALUE INTO LOCAL COPY OF V1
⋮
L R7,4(R1) GET POINTER TO V2
MVC 0(9,R7),LOCV2 MOVE A VALUE INTO OUTPUT VAR V2
⋮
CEETERM RC=0
*******************************************************************
* VARIABLE DECLARATIONS AND EQUATES *
*******************************************************************
R1 EQU 1 REGISTER 1
R7 EQU 7 REGISTER 7
PPA CEEPPA , CONSTANTS DESCRIBING THE CODE BLOCK
LTORG , PLACE LITERAL POOL HERE
PROGAREA DSECT
ORG *+CEEDSASZ LEAVE SPACE FOR DSA FIXED PART
LOCV1 DS F LOCAL COPY OF PARAMETER V1
LOCV2 DS CL9 LOCAL COPY OF PARAMETER V2
⋮
PROGSIZE EQU *-PROGAREA
CEEDSA , MAPPING OF THE DYNAMIC SAVE AREA
CEECAA , MAPPING OF THE COMMON ANCHOR AREA
END A
C example
The following figure shows how a stored procedure that is written in the C language receives these parameters.
#pragma runopts(PLIST(OS))
#pragma options(RENT)
#include <stdlib.h>
#include <stdio.h>
/*****************************************************************/
/* Code for a C language stored procedure that uses the */
/* GENERAL linkage convention. */
/*****************************************************************/
main(argc,argv)
int argc; /* Number of parameters passed */
char *argv[]; /* Array of strings containing */
/* the parameter values */
{
long int locv1; /* Local copy of V1 */
char locv2[10]; /* Local copy of V2 */
/* (null-terminated) */
⋮
/***************************************************************/
/* Get the passed parameters. The GENERAL linkage convention */
/* follows the standard C language parameter passing */
/* conventions: */
/* - argc contains the number of parameters passed */
/* - argv[0] is a pointer to the stored procedure name */
/* - argv[1] to argv[n] are pointers to the n parameters */
/* in the SQL statement CALL. */
/***************************************************************/
if(argc==3) /* Should get 3 parameters: */
{ /* procname, V1, V2 */
locv1 = *(int *) argv[1];
/* Get local copy of V1 */
⋮
strcpy(argv[2],locv2);
/* Assign a value to V2 */
⋮
}
}
COBOL example
The following figure shows how a stored procedure that is written in the COBOL language receives these parameters.
CBL RENT
IDENTIFICATION DIVISION.
************************************************************
* CODE FOR A COBOL LANGUAGE STORED PROCEDURE THAT USES THE *
* GENERAL LINKAGE CONVENTION. *
************************************************************
PROGRAM-ID. A.
⋮
DATA DIVISION.
⋮
LINKAGE SECTION.
************************************************************
* DECLARE THE PARAMETERS PASSED BY THE SQL STATEMENT *
* CALL HERE. *
************************************************************
01 V1 PIC S9(9) USAGE COMP.
01 V2 PIC X(9).
⋮
PROCEDURE DIVISION USING V1, V2.
************************************************************
* THE USING PHRASE INDICATES THAT VARIABLES V1 AND V2 *
* WERE PASSED BY THE CALLING PROGRAM. *
************************************************************
⋮
****************************************
* ASSIGN A VALUE TO OUTPUT VARIABLE V2 *
****************************************
MOVE '123456789' TO V2.
PL/I example
The following figure shows how a stored procedure that is written in the PL/I language receives these parameters.
*PROCESS SYSTEM(MVS);
A: PROC(V1, V2) OPTIONS(MAIN NOEXECOPS REENTRANT);
/***************************************************************/
/* Code for a PL/I language stored procedure that uses the */
/* GENERAL linkage convention. */
/***************************************************************/
/***************************************************************/
/* Indicate on the PROCEDURE statement that two parameters */
/* were passed by the SQL statement CALL. Then declare the */
/* parameters in the following section. */
/***************************************************************/
DCL V1 BIN FIXED(31),
V2 CHAR(9);
⋮
V2 = '123456789'; /* Assign a value to output variable V2 */