Was this helpful?
Sample Programs
The programs in this section are examples of how to declare and use user-defined data handlers in an ESQL/COBOL program. There are examples of a handler program, a put handler program, a get handler program and a dynamic SQL handler program.
Handler
This example assumes that the book table was created with the statement:
EXEC SQL CREATE TABLE BOOK
(CHAPTER_NUM INTEGER,
CHAPTER_NAME CHAR(50),
CHAPTER_TEXT LONG VARCHAR) END-EXEC.
This program inserts a row into the table book using the data handler PUT_HANDLER to transmit the value of column chapter_text from a text file to the database. Then it selects the column chapter_text from the table book using the data handler GET-HANDLER to retrieve the chapter_text column a segment at a time.
IDENTIFICATION DIVISION.
PROGRAM-ID. HANDLER-PROG.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
 
EXEC SQL INCLUDE SQLCA END-EXEC.
* Do not declare the data handlers nor the
* datahandler argument to the ESQL preprocessor.
01 PUT-HANDLER PIC S9(9) USAGE COMP VALUE
EXTERNAL PUT-HANDLER.
01 GET-HANDLER PIC S9(9) USAGE COMP VALUE
EXTERNAL GET-HANDLER.
01 HDLR-ARG.
05 ARG-CHAR PIC X(100).
05 ARG-INT PIC S9(9) USAGE COMP.
* Argument passed through to the DATAHANDLER must be * of type POINTER.
01 ARG-ADDR USAGE POINTER.
* Null indicator for data handler must be declared to * ESQL.
EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 CHAPTER_NUM S9(9) USAGE COMP.
01 IND-VAR S9(4) USAGE COMP.
EXEC SQL END DECLARE SECTION END-EXEC.
PROCEDURE DIVISION.
BEGIN.
* INSERT a long varchar value chapter_text into the
* table book using the datahandler PUT_HANDLER.
* The argument passed to the datahandler is a pointer to the record HDLR-ARG.
...
SET ARG-ADDR TO REFERENCE HDLR-ARG.
EXEC SQL INSERT INTO book (chapter_num,
chapter_name, chapter_text)
VALUES (5, 'One dark and stormy night',
DATAHANDLER (PUT-HANDLER (ARG-ADDR)))
END-EXEC.
...
* Select the column chapter_num and the long varchar * column chapter_text from the table book.
* The Datahandler (GET-HANDLER) will be invoked for each non-null value
* of column chapter_text retrieved. For null values the indicator variable
* will be set to "-1" and the datahandler will not be called. Again, the argument
* passed to the handler is a pointer to the record HDLR-ARG.
...
EXEC SQL SELECT chapter_num, chapter_text INTO
:CHAPTER_NUM,
DATAHANDLER (GET-HANDLER(ARG-ADDR)):IND-VAR
FROM book END-EXEC
EXEC SQL BEGIN END-EXEC
process row ...
EXEC SQL END END-EXEC.
...
END PROGRAM HANDLER-PROG.
Put Handler
This example shows how to read the long varchar chapter_text from a text file and insert it into the database a segment at a time.
IDENTIFICATION DIVISION.
PROGRAM-ID. PUT-HANDLER.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
 
EXEC SQL INCLUDE SQLCA END-EXEC.
EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 SEG-BUF PIC X(1000).
01 SEG-LEN PIC s9(9) USAGE COMP.
01 DATA-END PIC s9(9) USAGE COMP.
EXEC SQL END DECLARE SECTION END-EXEC.
LINKAGE SECTION.
01 HDLR-ARG.
02 ARG-CHAR PIC X(100).
02 ARG-INT PIC S9(9) USAGE COMP.
PROCEDURE DIVISION USING ARG-ADDR.
BEGIN.
...
process information passed in via the HDLR-ARG...
open file...
...
MOVE 0 TO DATA-END.
PERFORM UNTIL DATA-END = 1
read segment of less than 1000 chars from file into segbuf...
IF end-of-file
MOVE 1 TO DATA-END
END-IF.
EXEC SQL PUT DATA (SEGMENT = :SEG-BUF,
SEGMENTLENGTH = :SEG-LEN, DATAEND = :DATA-END)
END-EXEC
END-PERFORM.
...
close file ...
set HDLR-ARG to return appropriate values...
...
END PROGRAM PUT-HANDLER.
Get Handler
This example shows how to get the long varchar chapter_text from the database and write it to a text file.
IDENTIFICATION DIVISION.
PROGRAM-ID. GET-HANDLER.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
 
EXEC SQL INCLUDE SQLCA END-EXEC.
EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 SEG-BUF PIC X(2000).
01 SEG-LEN PIC Z9(6) USAGE COMP.
01 DATA-END PIC Z9(9) USAGE COMP.
01 MAX-LEN PIC S9(9) USAGE COMP.
EXEC SQL end DECLARE SECTION END-EXEC.
LINKAGE SECTION.
01 HDLR-ARG.
02 ARG-CHAR PIC X(100).
02 ARG-INT PIC S9(9) USAGE COMP.
PROCEDURE DIVISION USING HDLR-ARG.
BEGIN.
...
process information passed in via the HDLR-ARG...
open file...
* Get a maximum segment length of 2000 bytes.
    MOVE 0 TO DATA-END.
   MOVE 2000 TO MAX-LEN.
* seg-len: will contain the length of the segment retrieved.
* seg-buf: will contain a segment of the column chapter_text.
* data-end: will be set to '1' when the entire value in chapter_text has * been retrieved.
PERFORM UNTIL DATA-END = 1
EXEC SQL GET DATA (:SEG-BUF = SEGMENT,
:SEG-LEN = SEGMENTLENGTH,
:DATA-END = DATAEND)
WITH MAXLENGTH = :MAX-LEN
END-EXEC.
write segment to file...
END-PERFORM.
...
set HDLR-ARG to return appropriate values...
END PROGRAM GET-HANDLER.
Dynamic SQL Handler
The following is an example of a dynamic SQL handler program. This program fragment shows the declaration and usage of a datahandler in a dynamic SQL program, using the SQLDA. It uses the datahandler GET-HANDLER and the HDLR-ARG structure.
IDENTIFICATION DIVISION.
PROGRAM-ID. DYNHDLR-PROG.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
 
EXEC SQL INCLUDE SQLCA END-EXEC.
EXEC SQL INCLUDE SQLDA END-EXEC.
* Do not declare the data handlers nor the
* data handler argument to the ESQL preprocessor.
01 PUT-HANDLER PIC S9(9) USAGE COMP VALUE
EXTERNAL PUT-HANDLER.
01 GET-HANDLER PIC S9(9) USAGE COMP VALUE
EXTERNAL GET-HANDLER.
* Declare argument to be passed to datahandler.
01 HDLR-ARG.
05 ARG-CHAR PIC X(100).
05 ARG-INT PIC S9(9) USAGE COMP.
C Declare IISQLHDLR
01 IISQLHDLR EXTERNAL.
05 SQLARG USAGE POINTER.
05 SQLHDLR PIC S9(9) USAGE COMP.
EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 INDVAR PIC s9(4) USAGE COMP.
EXEC SQL END DECLARE SECTION END-EXEC.
PROCEDURE DIVISION.
BEGIN.
. . .
* Set the IISQLHDLR structure with the appropriate datahandler and
* datahandler argument.
MOVE GET-HANDLER TO SQLHDLR.
SET SQLARG TO REFERENCE HDLR-ARG.
* Describe the statement into the SQLDA.
STMT-BUF = "select * from book".
EXEC SQL PREPARE stmt FROM :STMT-BUF END-EXEC.
EXEC SQL DESCRIBE stmt INTO :SQLDA END-EXEC.
* Set the SQLDATA variables correctly.
PERFORM SETUP-COLUMN VARYING COL FROM 1 BY 1
UNTIL (COL > SQLD).
* The Datahandler (GET-HANDLER) will be invoked for
* each non-null value of column "chapter_text"
* retrieved. For null values the SQLIND will be set * to "-1" and the datahandler
* will not be called.
EXEC SQL EXECUTE IMMEDIATE :STMT-BUF USING
:SQLDA END-EXEC
EXEC SQL BEGIN END-EXEC
process row ...
EXEC SQL END END-EXEC
. . .
SETUP-COLUMN.
. . .
* The Describe statement will return 22 for long
* varchar and -22 for Nullable Long Varchar
IF (SQLTYPE(COL) = 22)
MOVE 46 TO SQLTYPE(COL)
SET SQLDATA(COL) TO REFERENCE IISQLHDLR
SET SQLIND(COL) TO REFERENCE INDVAR
ELSE
. . .
END-IF.
. . .
END PROGRAM DYNHLDR-PROG.
Last modified date: 01/30/2023