IBM DB2 Part 2

DCLGEN (DECLARATOR GENERATOR)
Ø DCLGEN is an IBM function which generates include members for DB2 tables to use in COBOL
Ø While implementing SQL statements in COBOL all the statements must be written within ‘EXEC SQL’ and ‘END-EXEC’. It represents all the SQL statements
Ø For every COBOL program SQLCA is required
Ø By using include statement we can include SQLCA and also DCLGEN variable
STATIC SQL
Ø In STATIC SQL we can communicate with the table directly by using standard SQL statements
Ø In STATIC SQL recompilation of program is required for every change in program
EX1. USING CREATE COMMAND
ID DIVISION.                          
PROGRAM-ID. PGM. 
DATA DIVISION.                                                 
WORKING-STORAGE SECTION.
     EXEC SQL                                                   
        INCLUDE SQLCA                                            
     END-EXEC.                                                   
PROCEDURE DIVISION.                                             
     DISPLAY "TABLE CREATING".                                   
     EXEC SQL                                                   
       CREATE TABLE M3(ENO INT,ENAME CHAR(10),ESAL INT) IN      
        DBMATE01.TSMATE02                                        
     END-EXEC.                                                  
    DISPLAY SQLCODE.                                            
        STOP RUN.
EX2. INSERT
ID DIVISION.                                                  
PROGRAM-ID. PGM.                                                
DATA DIVISION.                                                   
WORKING-STORAGE SECTION.
     EXEC SQL                                                    
        INCLUDE SQLCA                                            
     END-EXEC.                                                    
    EXEC SQL                                                   
        INCLUDE M3                                               
     END-EXEC.                                                   
PROCEDURE DIVISION.                                              
     DISPLAY "TABLE INSERTION".                                  
           MOVE 1002 TO ENO.                                           
           MOVE 'SRINU' TO ENAME.                                      
           MOVE 35000 TO ESAL.                                         
     EXEC SQL                                                   
        INSERT INTO M3 VALUES(:ENO,:ENAME,:ESAL)                   
     END-EXEC.                                                   
     DISPLAY SQLCODE.                                            
       STOP RUN.                                                
NOTE
Ø We cant include more than one query within EXEC SQL and END-EXEC and also ‘ ;’ is option
Ø While working with SQL queries in COBOL we may use error handling techniques to identify the status of SQL statements effectively and efficiently
Ø If SQLCODE = 0
     DISPLAY ‘EXECUTION SUCCESS’
ELSE
     DISPLAY SQLCODE
END-IF
When you write error handling in COBOL it wont affect the program, it just notifies the SQL query
EX3. SELECT
CASE1
ID DIVISION.                                                    
PROGRAM-ID. PGM3.                                               
DATA DIVISION.                                                  
WORKING-STORAGE SECTION.                                        
     EXEC SQL                                                    
        INCLUDE SQLCA                                            
     END-EXEC.                                                  
     EXEC SQL                                                    
        INCLUDE M3                                               
     END-EXEC.                                                  
77 NUM  PIC 9(9).                                                
77 NAME PIC X(10).
PROCEDURE DIVISION.                                             
     EXEC SQL                                                   
      SELECT ENO,ENAME INTO :NUM,:NAME FROM M3                   
     END-EXEC.
If SQLCODE = 0
     DISPLAY ‘EXECUTION SUCCESS’
ELSE
     DISPLAY SQLCODE
END-IF.
STOP RUN.
CASE2
SELECT using WHERE clause
By using select we can fetch any record from the table
ID DIVISION.                                                    
PROGRAM-ID. PGM3.                                                
DATA DIVISION.                                                  
WORKING-STORAGE SECTION.                                        
     EXEC SQL                                                    
        INCLUDE SQLCA                                             
     END-EXEC.                                                  
     EXEC SQL                                                    
        INCLUDE M3                                               
     END-EXEC.                                                   
77 NUM  PIC 9(9).                                               
77 NAME PIC X(10).
77 ADDR PIC X(15).
PROCEDURE DIVISION.
     MOVE ‘HYD’ TO :ADDR.                                        
     EXEC SQL                                                    
           SELECT ENO,ENAME INTO :NUM,:NAME FROM M3 WHERE EADDR = :ADDR                  
     END-EXEC.
If SQLCODE = 0
     DISPLAY ‘EXECUTION SUCCESS’
ELSE
     DISPLAY SQLCODE
END-IF.
     STOP RUN.
EX3. DELETE
ID DIVISION.                                                    
PROGRAM-ID. PGM4.                                               
DATA DIVISION.
WORKING-STORAGE SECTION.
     EXEC SQL
        INCLUDE SQLCA
     END-EXEC.                                                    
     EXEC SQL                                                    
       INCLUDE M3                                               
     END-EXEC.                                                   
PROCEDURE DIVISION.                                  
     EXEC SQL                                                    
           DELETE FROM M3 WHERE ENO=1002                              
     END-EXEC.                                                   
     DISPLAY SQLCODE.                                             
       STOP RUN.     
EX4. UPDATE
CASE1.
ID DIVISION.                                                   
PROGRAM-ID. PGM5.                                               
DATA DIVISION.                                                  
WORKING-STORAGE SECTION.                                        
     EXEC SQL                                                    
        INCLUDE SQLCA                                            
     END-EXEC.                                                    
     EXEC SQL                                                    
        INCLUDE M3                                             
     END-EXEC.                                                   
PROCEDURE DIVISION.                                              
     EXEC SQL                                                    
          UPDATE M3 SET ESAL=80000 WHERE ENO=1001                    
     END-EXEC.
     If SQLCODE = 0
     DISPLAY ‘EXECUTION SUCCESS’
ELSE
     DISPLAY SQLCODE
END-IF.
     STOP RUN.


CASE2
ID DIVISION.                                                   
PROGRAM-ID. PGM5.                                               
DATA DIVISION.                                                 
WORKING-STORAGE SECTION.                                        
     EXEC SQL                                                    
        INCLUDE SQLCA                                            
     END-EXEC.                                                   
     EXEC SQL                                                    
        INCLUDE M3                                             
     END-EXEC.                                                   
PROCEDURE DIVISION.                                             
     EXEC SQL                                                    
          UPDATE M3 SET ESAL=15000                    
     END-EXEC.
     If SQLCODE = 0
     DISPLAY ‘EXECUTION SUCCESS’
ELSE
     DISPLAY SQLCODE
END-IF.
     STOP RUN.
NOTE
          When table contains same value in the column we cant update a value by taking the reference of that column
CASE3
ID DIVISION.                                                   
PROGRAM-ID. PGM5.                                               
DATA DIVISION.                                                  
WORKING-STORAGE SECTION.                                        
     EXEC SQL                                                    
        INCLUDE SQLCA                                            
     END-EXEC.                                                    
     EXEC SQL                                                    
        INCLUDE M3                                             
     END-EXEC.                                                   
PROCEDURE DIVISION.                                             
     EXEC SQL                                                    
          ALTER TABLE M3 ADD EADDR CHAR(15)
     END-EXEC.
     If SQLCODE = 0
     DISPLAY ‘EXECUTION SUCCESS’
ELSE
     DISPLAY SQLCODE
END-IF.
     STOP RUN.
Ø During the DB2 read in the COBOL program, if where condition retrieves more than one row then the programmer needs to handle the scenario by validating SQL CODE.
Ø To do this, programmer need to include SQLCA to retrieve the SQL CODE from the executed query.
Ø If the query returns more than one row, then it will return -811 as SQL CODE.
Ø In most of the cases it will return the first retrieved row data and throw the error -811.
Ø Programmer cant able to retrieve the further rows which satisfy the same condition.
Ø If the programmer requirement is to retrieve the first row even though the where condition coded retrieving more than one row and handling the SQL CODE is sufficient.
Ø But if the programmer needs to handle the multiple rows one by one then there is only one solution.   

CURSORS
Ø CURSOR is used to process set of rows one by one from table(s).
Ø CURSOR is used to retrieve and process one row from set of rows retrieved by the application program.
Ø It will process the rows one by one sequentially after retrieved. Its like the sequential access of the file.
Ø The rows can be retrieved based on the search condition
LIFE CYCLE OF A CURSOR
1.     DECLARE CURSOR
2.     OPEN CURSOR
3.     FETCH CURSOR
4.     CLOSE CURSOR
NOTE
Ø In CURSORS insertion is not possible.
Ø We can declare a cursor with ‘ WITHHOLD’ option. It is important if you want to pass commit inside the fetch loop. If you omit the keyword ‘WITHHOLD’ then you have to reopen the Cursor after each COMMIT. Because its position will be last due to COMMIT
1. DECLARE CURSOR
Ø DECLARE CURSOR is used to declare a cursor in the application program.
Ø SELECT statement must be used within the DECLARE CURSOR.
Ø SELECT statement should not use INTO clause.
Ø The cursor name provided with DECLARE CURSOR will act as a result table.
Ø DECLARE CURSOR will not create any result table by declaring it.
Ø DECLARE CURSOR only identifies the set of rows to retrieve with SELECT during execution.
Ø DECLARE CURSOR can be coded in DATA DIVISION and PROCEDURE DIVISION.
Ø The SQL SELECT statement that required in retrieving the data from table(s) will be declared in DECLARE CURSOR.
Ø DECLARE CURSOR may have GROUPBY, ORDERBY in it.
SYNTAX
              EXEC SQL
                             DECLARE CURSOR-NAME [NOSCROLL/SCROLL][DYNAMIC/STATIC] CURSOR [WITH/WITHOUT HOLD] FOR SELECT-STATEMENT FOR UPDATE OF COLUMN-LIST/FOR FETCH ONLY
              END-EXEC.
          Lets discuss the parameters one by one
a. CURSOR-NAME
Ø CURSOR-NAME is the name of the cursor which is used in application program to refer the cursor.
Ø The length of CURSOR-NAME is 30 characters for the cursors declared WITH RETURN.
Ø The length of CURSOR-NAME is 128 characters for the normal cursors
b. SCROLL/NOSCROLL
Ø Specifies the cursor is SCROLLABLE or NON SCROLLABLE
Ø NOSROLL specifies the cursor is NON SCROLLABLE.
Ø NOSCROLL is default.
Ø SCROLL specifies the cursor is SCROLLABLE
c. WITH/WITHHOUT HOLD
Ø Specifies the cursor should be closed or not during the COMMIT operation performed.
Ø WITHOUT HOLD specifies the cursor can be closed if any COMMIT operation is performed before CLOSE CURSOR
Ø WITHOUT HOLD is DEFAULT
Ø WITH HOLD specifies the cursor should not be closed even though COMMIT operation is performed before CLOSE CURSOR
Ø If WITH HOLD option specifies, COMMIT only commits the current unit of work
Ø If no option specified or WITHOUT HOLD is specified, COMMIT closes the CURSOR along with commit of current work
FOR UPDATE OF
Ø Used to declare the updatable cursors.
Ø Positioned UPDATE and positioned DELETE can be allowed in UPDATABLE CURSORS.
Ø WHERE CURRENT of used to update or delete the rows in updatable cursors
FOR FETCH ONLY
Ø Specifies when declaring READ ONLY cursors.
Ø Positioned UPDATE and positioned DELETE not allowed in READ ONLY cursors
2. OPEN CURSOR
Ø The opening of the declared cursor will retrieve the data from the table and make it ready for processing.
Ø If GROUPBY, ORDERBY was coded in declare cursor, then the temporary result table will be built to process it.
Ø On opening of CURSOR, DB2 system will perform two tasks. They are…….
1.     Uses the SELECT statement in DECLARE CURSOR to identify the set of rows
2.     Stores the data in a temporary location and make it ready for processing
Ø If any HOST VARIABLES used in the DECLARE CURSOR, the HOST VARIABLES should have the value before OPEN CURSOR performed
Ø Otherwise DB2 will use the current value of the HOST VARIABLES which may be LOW-VALUES also
SYNTAX
              EXEC SQL
                   OPEN CURSOR-NAME
              END-EXEC.
3. FETCH CURSOR
Ø FETCH CURSOR retrieved the data to HOST VARIABLES in the order how it got retrieved from tables based on the conditions coded in decleration of cursor and fetch it one by one.
Ø It fetches the one row at a time.
Ø To fetch the data from table, the HOST VARIABLES need to be coded in the FETCH CURSOR.
Ø FETCH CURSOR always fetches only one row and makes it as a current row.
Ø When next fetch executed, the next row will be fetched and makes that one as current one.
Ø Updatable cursors will use the concept of current row.
Ø FETCH will move the fetched data to the HOST VARIABLES coded along with INTO.
Ø The order of HOST VARIABLES should be the same as the columns or attributes declared with the DECLARE CURSOR.
Ø FETCH statement retrieves the rows from temporary result table
              EXEC SQL
                   FETCH CURSOR-NAME INTO :HOST VARIABLE
              END-EXEC.
Ø While fetching the data, there might be chance of data not available in the table
Ø The column contains the value which is other than the actual data called as NULL
Ø If any NULL valued column existed in the retrieved columns list, the null indicator should be coded along with HOST VARIABLE
Ø If the NULL INDICATOR is not coded with FETCH and column returns the NULL value then the FETCH will fail with -305
Ø The NULL variables can be declared always with –NI at end of field name
Ø The decleration of NULL INDICATOR is S9(04) COMP
Ø The NULL INDICATOR handling in FETCH statement syntax was shown below
SYNTAX
          EXEC SQL
              FETCH CURSOR-NAME
              INTO    
              :HOST-VARIABLE-COL1
              :HOST-VARIABLE-COL1-NI,
              :HOST-VARIABLE-COL2
              :HOST-VARIABLE-COL2-NI,
              .
              .   
          END-EXEC.
The NULL INDICATOR will be validated like below
IF NULL INDICATOR VALUE = -1 (NULL EXISTED IN RETRIEVED COLUMN)
                                                  = 0 (RETRIEVED COLUMN HAS THE PROPER VALUE)
                                                  = 2 (TRUNCATED VALUE RETRIEVED)
4. CLOSE CURSOR
Ø CLOSE CURSOR closes the cursor specified with it
Ø CLOSE CURSOR releases all the resources used by the cursor
              EXEC SQL
                   CLOSE CURSORNAME
              END-EXEC.


NOTE
Ø If any COMMIT performed in the middle of cursor processing, the cursor will be closed automatically.
Ø If the control returns from the executing program, all the cursors will be closed automatically.
Ø If the cursor declared WITH HOLD option, then ROLLBACK command needs to be coded at the end of the program. That closes all WITH HOLD cursors coded in the program
EX1. CURSOR USING SELECT
ID DIVISION.                                                   
PROGRAM-ID. PGM7.                                               
DATA DIVISION.                                                  
WORKING-STORAGE SECTION.                                        
      EXEC SQL                                                   
        INCLUDE SQLCA                                             
      END-EXEC.                                                  
      EXEC SQL                                                   
       INCLUDE EMP2                                             
      END-EXEC.                                                   
PROCEDURE DIVISION.                                             
      EXEC SQL                                                  
       DECLARE C1 CURSOR FOR SELECT EMPNO,ENAME,SAL             
          FROM EMP2 WHERE SAL=25000                              
      END-EXEC.                                                  
      EXEC SQL                                                   
        OPEN C1                                                  
      END-EXEC.                                                  
      PERFORM FETCH-PARA UNTIL SQLCODE=100                       
FETCH-PARA.                                                     
      EXEC SQL                                                    
            FETCH C1 INTO :DCLEMP2                               
      END-EXEC.                                                  
     IF SQLCODE = 0                                             
        DISPLAY ':DCLEMP2'                                        
     ELSE                                                       
       EXEC SQL                                                 
          CLOSE C1.                                             
       END-EXEC.                                                 
      DISPLAY SQLCODE.                                           
     STOP RUN. 
EX2. UPDATE USING CURSOR
ID DIVISION.                                                   
PROGRAM-ID. PGM7.                                               
DATA DIVISION.                                                  
WORKING-STORAGE SECTION.                                        
      EXEC SQL                                                   
        INCLUDE SQLCA                                             
      END-EXEC.                                                  
      EXEC SQL                                                   
       INCLUDE EMP2                                             
      END-EXEC.                                                   
PROCEDURE DIVISION.                                             
      EXEC SQL                                                  
        DECLARE C2 CURSOR FOR SELECT EMPNO,ENAME,SAL             
          FROM EMP2 FOR UPDATE OF SAL                              
      END-EXEC.                                                  
      EXEC SQL                                                   
        OPEN C2                                               
      END-EXEC.                                                   
      PERFORM FETCH-PARA UNTIL SQLCODE=100
      EXEC SQL                                                   
            CLOSE C2                               
      END-EXEC.  
      STOPRUN.                                                                     
FETCH-PARA.                                                     
      EXEC SQL                                                   
            FETCH C2 INTO :DCLEMP2                               
      END-EXEC.                                                  
     IF SQLCODE = 0
        EXEC SQL
             UPDATE EMP2 SET SAL=15890 WHERE CURRENT OF C2
        END-EXEC.                                             
STOP RUN. 

EX3. DELETE USING CURSORS
ID DIVISION.                                                   
PROGRAM-ID. PGM7.                                              
DATA DIVISION.                                                  
WORKING-STORAGE SECTION.                                         
      EXEC SQL                                                   
        INCLUDE SQLCA                                            
      END-EXEC.                                                  
      EXEC SQL                                                    
       INCLUDE TABLE5                                             
      END-EXEC.                                                  
PROCEDURE DIVISION.                                             
      EXEC SQL                                                   
        DECLARE C2 CURSOR FOR SELECT EMPNO,ENAME,SAL             
          FROM TABLE5 FOR DELETE OF SAL                              
      END-EXEC.                                                  
      EXEC SQL                                                   
        OPEN C3                                               
      END-EXEC.                                                  
      PERFORM PARA1 UNTIL SQLCODE NOT EQUAL TO 100
CLOSE-PARA.
      EXEC SQL                                                   
            CLOSE C3                               
      END-EXEC.
      DISPLAY SQLCODE  
      STOPRUN.                                                               
PARA1.                                                      
      EXEC SQL                                                   
            FETCH C3 INTO :NAME,:AGE,:SALARY                               
      END-EXEC.                                                  
     IF SQLCODE = 0
        EXEC SQL
             DELETE FROM TABLE5 WHERE SAL>15000
        END-EXEC.                                             


EX4. IDENTIFYING NULL VALUES IN THE TABLE
ID DIVISION.                                                  
PROGRAM-ID. PGM10.
DATA DIVISION.                                                 
WORKING-STORAGE SECTION.                                        
     EXEC SQL
        INCLUDE TABLE1                                           
     END-EXEC.                                                    
     EXEC SQL                                                    
        INCLUDE TABLE1.                                          
     END-EXEC.                                                   
01 NLIND PIC S9(4) USAGE OF COMP.                               
     EXEC SQL                                                    
       DECLARE C5 CURSOR FOR SELECT NO,SAL,NAME                  
       FROM TABLE1                                               
     END-EXEC.                                                   
PROCEDURE DIVISION.
     EXEC SQL                                                  
       OPEN C5                                                  
     END-EXEC.
     PERFORM FETCH-PARA UNTIL SQLCODE NOT EQUAL TO 0             
CLOSE-PARA.                                                     
     EXEC-SQL                                                    
      CLOSE C5                                                   
     END-EXEC.                                                   
     STOP RUN.                                                   
FETCH-PARA.                                                     
     EXEC SQL                                                    
        FETCH C5 INTO :NO,:SAL,:NAME,:NLIND                      
     END-EXEC.                                                   
     IF SQLCODE=100 GO TO CLOSE-PARA.                            
     IF NLIND = -1                                                
        MOVE 'NOSAL' TO SAL.                                     
        DISPLAY NAME.                                           
        DISPLAY NO.                                             
        DISPLAY SAL.
     END-IF.                                                      
     END-IF.   
DYNAMIC SQL
Ø In DYNAMIC SQL we can write the DB2 dynamically without recompiling the application program
Ø In DYNAMIC SQL we have mainly two types. They are
1.     NON-SELECT STATEMENT
2.     SELECT STATEMENT
Ø In NON-SELECT STATEMENT we have two types. They are
1.     EXECUTE IMMEDIATE
2.     PREPARE EXECUTE
1. EXECUTE IMMEDIATE
A program executing SQL statement by means of a EXECUTE IMMEDIATE flavor of DYNAMIC SQL is limited to a sub-set of SQL statements. The most important are DELETE, INSERT, UPDATE and COMMIT. If these are the only types of SQL statements a program need to execute, the code could be simple. Load the DYNAMIC SQL into HOST VARIABLE and issue an EXECUTE IMMEDIATE. The statement will be automatically prepared and executed
2. PREPARE EXECUTE
All SQL statements can be logically broken down into two steps, PREPARE and EXECUTE. The flavor of DYNAMIC SQL accomplishes this breakdown. A useful feature of DYNAMIC SQL, known as PARAMETER MARKER is used as a place holder for HOST VARIABLES in DYNAMIC SQL statement.
EX
DELETE FROM TABLE2 WHERE DEPTNO=?
          In the above example ‘?’ is a PARAMETER MARKER. When the statement is executed, a value is moved into the HOST VARIABLE and coded as a parameter to the CURSOR by means of USING clause
Ø In SELECT STATEMENT we have two types. They are
1.     FIXED-LIST SELECT
2.     VARIABLE LIST SELECT
1. FIXED-LIST SELECT
FIXED LIST SELECT is flavor of DYNAMIC SQL that allows SELECT statements to be issued. To use a FIXED-LIST SELECT, the exact columns to be returned must be known and unchanging. This is necessary to create the proper WORKING-STORAGE SECTION declaration for HOST VARIABLES in COBOL program. If user does not know in advance exact columns to be accessed, he cannot use FIXED-LIST SELECT.
2. VARIABLE-LIST SELECT
VARIABLE-LIST SELECT provides the most flexibility for DYNAMIC SELECT statements. Changes can be made ‘on the fly’ to the tables, columns and predicates. Because everything about the query can change during invocation of the program, the number and type of HOST VARIABLES needed to store the retrieved rows cannot be known before hand. This will add considerable complexity to application program. The vehicle for communicating information about DYNAMIC SQL between DB2 and the application program is called the SQLDA. It will contain the information about the type of SQL statement to be executed, the data type of each column accessed and the address of each HOST VARIABLE needed to retrieve the columns


EX1. EXECUTE IMMEDIATE
ID DIVISION.                                                    
PROGRAM-ID. PGM11.                                             
DATA DIVISION.                                                  
WORKING-STORAGE SECTION.                                        
      EXEC SQL                                                    
         INCLUDE SQLCA.                                         
     END-EXEC.                                                  
     EXEC SQL                                                   
         INCLUDE DEPT                                            
      END-EXEC.                                                
01 DCL.                                                         
      49 DCL-LEN PIC S9(4) USAGE COMP.                               
      49 DCL-TEXT PIC X(50).                                         
PROCEDURE DIVISION.                                            
     ACCEPT DCL-TEXT.                                           
     MOVE LENGTH OF DCL-TEXT TO DCL-LEN.                          
     EXEC SQL                                                    
       EXECUTE IMMEDIATE :DCL                                   
     END-EXEC.                                                   
     IF SQLCODE=0                                               
        DISPLAY 'SUCESS'                                         
     ELSE                                                        
        DISPLAY SQLCODE                                          
     END-IF.
     STOP RUN. 
EX2. PREPARE AND EXECUTE
ID DIVISION.                                                    
PROGRAM-ID. PGM11.                                             
DATA DIVISION.                                                  
WORKING-STORAGE SECTION.                                       
      EXEC SQL                                                   
         INCLUDE SQLCA.                                         
      END-EXEC.                                                  
      EXEC SQL                                                   
         INCLUDE DEPT                                           
      END-EXEC.                                                 
01 DCL.                                                        
       77 A PIC X(6).                                                  
       77 B PIC 9(5).                                                
PROCEDURE DIVISION.                                             
     ACCEPT DCL-TEXT.                                          
     MOVE LENGTH OF DCL-TEXT TO DCL-LEN.                         
     EXEC SQL                                                    
       PREPARE P1 FOR :DCL                                     
     END-EXEC.                                                    
     ACCEPT A.                                                  
     ACCEPT B.                                                  
     EXEC SQL                                                    
       EXECUTE P1 USING :A, :B                                   
     END-EXEC.                                                 
     STOP RUN.
EX3. ON FIXED SELECT
ID DIVISION.                                                   
PROGRAM-ID. PGM11.                                             
DATA DIVISION.                                                  
WORKING-STORAGE SECTION.                                        
      EXEC SQL                                                   
         INCLUDE SQLCA.                                         
     END-EXEC.                                                  
     EXEC SQL                                                   
         INCLUDE DEPT                                            
      END-EXEC.                                                 
01 DCL.                                                         
     49 DCL-LEN PIC S9(4) USAGE COMP.                            
     49 DCL-TEXT PIC X(50).                                      
77 ENO PIC X(3).                                                 
77 ENAME PIC X(15).                                            
77 ESAL PIC 9(5).                                              
PROCEDURE DIVISION.                                             
     ACCEPT DCL-TEXT.                                            
     MOVE LENGTH OF DCL-TEXT TO DCL-GEN.                        
       EXEC SQL                                                 
         DECLARE C6 CURSOR FOR DEPT                             
       END-EXEC.                                                  
       EXEC SQL                                                  
        PREPARE P1 FROM :DCL
       END-EXEC.                                                
       ACCEPT DNAME.                                              
       EXEC SQL                                                 
         OPEN C6 USING :DNAME                                    
       END-EXEC.                                                 
       PERFORM UNTIL SQLCODE=100.
       EXEC SQL                                                   
          FETCH C6 INTO :DEPTNO,:DNAME,:DLOC                     
       END-EXEC.                                                 
       STOP RUN.                                                    





 DB2 PRECOMPILATON PROCESS
  PRECOMPILER
 
1. SOURCE CODE
2. DCLGEN
 
 


                                                                                                              DSNHPC      
 


                                                  TIMESTAMP
                    T1                                                                        T2                                                                                          
 





                                         IGYCRCTL                   IKJEFT01                                   OPTIMIZER
                                                                                                                  
 







                                                                             T1
LINK-EDIT PROCESS     T2    
                                     
IEWL
Ø DB2 BIND converts the DBRM into an executable format
Ø DB2 catalog stores the information about the PLAN and PACKAGE
Ø DB2 directory stores the Actual PLAN and PACKAGE
Ø DB2 pre-compiler produces a DBRM and a modified source program with commented SQL statements
PRE-COMPILER
Ø Pre-Compiler is mainly responsible for to divide the COBOL, DB2 statements separately
Ø It takes COBOL+DB2 source code as input and seperates the COBOL and DB2 statements
Pre-compiler is responsible to check syntax errors 

No comments:

Post a Comment