You are wrong in thinking you need to use dynamic SQL for this type of conversion.
I work on a company that has gone through such a conversion a few years ago. They were using COBOL with standard files/reads/writes, and all such parts were replaced with a common call to a single program "DBCALL" using a set of parameters, of which one was the type of operation "read next/read prior/write/rewrite/delete", and another was was the dataset(db2 table) to be used on the operation.
Without all the details, the linkage of this program is
Operation PIC X(20).
ERROR-CODE PIC X(10)
DATASET PIC X(20)
DATASET-DATA
And a few more fields. The above are the most important ones.
DBCALL will determine which sub-program to call based on the value on DATASET, and will supply the same parameters to that called program.
SET ADDRESS OF is extensively used to allow for variable sized parameters, namely on the DATASET-DATA field, as this will vary according to the table being accessed.
The I/O Modules (your DBI modules) perform all required operations using static SQL. Performance is poor though, and if you use Dynamic SQL it will be even worst.
As a quick example of what you can do.
Working storage
EXEC SQL
DECLARE MYTBL-FORWARD CURSOR FOR
SELECT
FIELD1
,FIELD2
,FIELD3
,FIELD4
,FIELD5
,FIELD6
FROM MY_TABLE
WHERE
FIELD1 = :HV-FIELD1-VALUE
AND FIELD2 = :HV-FIELD2-VALUE
AND FIELD3 > :HV-FIELD3-VALUE
END-EXEC.
EXEC SQL
DECLARE MYTBL-REVERSE CURSOR FOR
SELECT
FIELD1
,FIELD2
,FIELD3
,FIELD4
,FIELD5
,FIELD6
FROM MY_TABLE
WHERE
FIELD1 = :HV-FIELD1-VALUE
AND FIELD2 = :HV-FIELD2-VALUE
AND FIELD3 < :HV-FIELD3-VALUE
END-EXEC.
Procedure
EVALUATE Operation
WHEN “READ-NEXT”
PERFORM READ-NEXT-REC
WHEN “UPDATE”
PERFORM UPDATE-REC
WHEN “READ-PRIOR”
PERFORM READ-PRIOR-REC
WHEN “DELETE”
PERFORM DELETE-REC
WHEN “ADD”
PERFORM ADD-REC
END-EVALUATE
READ-NEXT-REC
IF MYTBL-FORWARD-OPEN = “N”
MOVE LINKAGE-KEY-FIELD1 TO HV-FIELD1-VALUE
MOVE LINKAGE-KEY-FIELD2 TO HV-FIELD2-VALUE
MOVE LINKAGE-KEY-FIELD3 TO HV-FIELD3-VALUE
EXEC SQL
OPEN MYTBL-FORWARD
END-EXEC
IF SQLCODE > 0
PERFORM ERROR-HANDLING
END-IF
MOVE “Y” TO MYTBL-FORWARD-OPEN
ELSE
IF LINKAGE-REC-LAST-READ NOT = REC-LAST-READ (this means calling program changed key to read
MOVE “N” TO MYTBL-FORWARD-OPEN
GO TO READ-NEXT-REC
END-IF
END-IF
EXEC SQL
FETCH MYTBL-FORWARD
INTO
:HV-FIELD1-VALUE
,:HV-FIELD2-VALUE
,:HV-FIELD3-VALUE
,:HV-FIELD4-VALUE
,:HV-FIELD5-VALUE
,:HV-FIELD6-VALUE
END-EXEC.
IF SQLCODE > 0
PERFORM ERROR-HANDLING
END-IF
ADD-REC
EXEC SQL
INSERT INTO MY_TABLE
(
FIELD1
,FIELD2
,FIELD3
,FIELD4
,FIELD5
,FIELD6
)
VALUES
(
:HV-FIELD1-VALUE
,:HV-FIELD2-VALUE
,:HV-FIELD3-VALUE
,:HV-FIELD4-VALUE
,:HV-FIELD5-VALUE
,:HV-FIELD6-VALUE
)
END-EXEC.
Now, and this is really important.
CHANGE all existing extract programs so that they use SQL on them, using proper joins where applicable, and selecting ONLY the fields that are required for the program.
Not doing so will mean that program you have now taking 1 hour to run, will take 4-5 hours instead if you replace all the file reads those programs have now with calls to DB2 I/O modules.
Also, and in all cases where it can be done, define the programs and/or the DB2 I/O modules in a way that if running in batch mode they will load all the DB2 table records into memory, and then use a search all within those programs. This obviously needs to be evaluated on a case per case.
If you really wish to use dynamic SQL, then the following is a sample program with what you need to do. Use of parameter markers should be used when the SQL will be used several times, but where the parameters will vary.
e.g. program should prepare the statement once first time its called, but on following calls, only the open/fetch/close cursor should be done. Or only the fetch.
*************************************************************************
**
** Source File Name = dynamic.sqb
**
** Licensed Materials - Property of IBM
**
** (C) COPYRIGHT International Business Machines Corp. 1995, 2000
** All Rights Reserved.
**
** US Government Users Restricted Rights - Use, duplication or
** disclosure restricted by GSA ADP Schedule Contract with IBM Corp.
**
**
** PURPOSE: This sample program demonstrates the use of a CURSOR.
** The CURSOR is processed using dynamic SQL. This program
** will list all the entries in the system table
** sysibm.systables that do not have the value "STAFF" in
** the "name" column.
**
** For more information about these samples see the README file.
**
** For more information on programming in COBOL, see the:
** - "Programming in COBOL" section of the Application Development Guide.
**
** For more information on building COBOL applications, see the:
** - "Building COBOL Applications" section of the Application Building Guide.
**
** For more information on the SQL language see the SQL Reference.
**
*************************************************************************
Identification Division.
Program-ID. "dynamic".
Data Division.
Working-Storage Section.
copy "sqlenv.cbl".
copy "sql.cbl".
copy "sqlca.cbl".
EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 table-name pic x(20).
01 st pic x(80). 1
01 parm-var pic x(18).
01 userid pic x(8).
01 passwd.
49 passwd-length pic s9(4) comp-5 value 0.
49 passwd-name pic x(18).
EXEC SQL END DECLARE SECTION END-EXEC.
Procedure Division.
Main Section.
display "Sample COBOL program: DYNAMIC".
display "Enter your user id (default none): "
with no advancing.
accept userid.
if userid = spaces
EXEC SQL CONNECT TO sample END-EXEC
else
display "Enter your password : " with no advancing
accept passwd-name.
* Passwords in a CONNECT statement must be entered in a VARCHAR format
* with the length of the input string.
inspect passwd-name tallying passwd-length for characters
before initial " ".
EXEC SQL CONNECT TO sample USER :userid USING

asswd
END-EXEC.
if SQLCODE not equal 0 DISPLAY "SQL ERROR" SQLCODE.
move "SELECT TABNAME FROM SYSCAT.TABLES
- " ORDER BY 1
- " WHERE TABNAME <> ?" to st.
EXEC SQL PREPARE s1 FROM :st END-EXEC. 2
if SQLCODE not equal 0 DISPLAY "SQL ERROR" SQLCODE.
EXEC SQL DECLARE c1 CURSOR FOR s1 END-EXEC. 3
move "STAFF" to parm-var.
EXEC SQL OPEN c1 USING

arm-var END-EXEC. 4
if SQLCODE not equal 0 DISPLAY "SQL ERROR" SQLCODE.
perform Fetch-Loop thru End-Fetch-Loop
until SQLCODE not equal 0.
EXEC SQL CLOSE c1 END-EXEC. 6
if SQLCODE not equal 0 DISPLAY "SQL ERROR" SQLCODE.
EXEC SQL COMMIT END-EXEC.
if SQLCODE not equal 0 DISPLAY "SQL ERROR" SQLCODE.
EXEC SQL CONNECT RESET END-EXEC.
if SQLCODE not equal 0 DISPLAY "SQL ERROR" SQLCODE.
End-Main.
go to End-Prog.
Fetch-Loop Section.
EXEC SQL FETCH c1 INTO :table-name END-EXEC. 5
if SQLCODE not equal 0
go to End-Fetch-Loop.
display "TABLE = ", table-name.
End-Fetch-Loop. exit.
End-Prog.
stop run.
Regards
Frederico Fonseca
SysSoft Integrated Ltd