Vous êtes sur la page 1sur 55

DB2 UDB FOR Z/OS

Overview

Embedded SQL in DB2

An Introduction
DB2-DM-1

Host Languages

COBOL

PL/1
C Assembler

FORTRAN

Embedded SQL

Delimit all SQL statements

Declare a Communication Area

Describe Host Variables

Code SQL statements to access DB2 data

Handle Exceptional Conditions

DB2-AP-2

DELIMITING SQL Statements


DELIMITING SQL STATEMENTS

Coding SQL statements in a COBOL application requires beginning and ending delimiters
The delimiters are EXEC SQL & END EXEC Whether or not a period is required after the END EXEC is based on the logic of the COBOL coding.

FORMAT EXEC SQL an SQL statement END EXEC.

SQL COMMUNICATION ARE (SQLCA)

SQL COMMUNICATION ARE (SQLCA)

DB2 program communication is accomplished through the SQL Communication Area: SQLCA SQLCA provides the fields set by DB2 after the SQL statement execution;

The return code placed in the field SQLCODE indicates the success, failure or execution encountered

DECLARING SQLCA

The COBOL description of SQLCA: 01 SQLCA. 05 SQLCAID 05 SQLCABC 05 SQLCODE 05 SQLERRM. 49 SQLERRML 49 SQLERRMC 05 SQLERRP 05 SQLERRD 05 SQLWARN. 10 10 10 10 10 10 10 10 SQLEXT

PIC X(8) VALUE SQLCA. PIC S9(9) COMP. PIC S9(9) COMP. PICS9(4) COMP. PIC X(70). PIC X(8). OCCURS 6 TIMES PIC S9(9) COMP. PIC X(1). PIC X(1). PIC X(1). PIC X(1). PIC X(1). PIC X(1). PIC X(1). PIC X(1). PIC X(8).

SQLWARN0 SQLWARN1 SQLWARN2 SQLWARN3 SQLWARN4 SQLWARN5 SQLWARN6 SQLWARN7

05

DECLARING SQLCA

An SQLCA must be declared in an WORKING STORAGE SECTION of every DB2/SQL COBL program Declaration of SQLCA can be done in two ways: Coding the COBOL description of SQLCA directly Coding the SQL statement: EXEC SQL INCLUDE SQLCA END-EXEC.

SQLCA FIELDS AND THEIR PURPOSE

SQLCAID SQLCABC SQLCODE

Always set to a value SQLCA; Useful when debugging using a dump Specifies the length of the SQLCA area; A full word integer with a value of 136 A full word integer field containing the return code passed by DB2 relating to the execution of the latest SQL statement;

SQLCODE 0 <0 >0

Characteristics of different return codes: Statement executed successfully An error occurred during statement execution; The SQL statement executed successfully, but an exceptional condition occurred; No data exists to process or end of results table reached

+100

SQLCA FIELDS AND THEIR PURPOSE


SQLERRM Gives a brief message about any error condition encountered; Provides the names of object and other information

SQLERRD(n)

n takes a usual value of 6; SQLERRD (3) is the only variable in this array that is pertinent to a programs execution; The value in SQLERRD(3) is set to reflect the number of rows INSERTED, or DELETED

SQLCA WARNING FLAGS


One (or more) of these is set when an SQL statement is executed, and something out of the ordinary is detected by DB2.

SQLWARN0 SQLWARN1

Set to a W when one of the other flags is also set to a W Set to a W when column values are truncated being placed into a host variable Set to a W when a NULL value was eliminated from any built-in-functions. Set to a W when there is an unequal number of host variables between the SQL statement and the TABLE/VIEW being processed Set to a W when an UPDATE or DELETE does not contain a WHERE clause Set to a W if the program issued an SQL statement that applies only to SQL/DS Not being used

SQLWARN2

SQLWARN3

SQLWARN4

SQLWARN5

SQLWARN6 & SQLWARN7

HOST VARIABLES

Are defined in the WORKING-STORAGE section or the LINKAGE SECTION of the DATA DIVISION just like any other COBOL data items. 01 HS EMPJOB. 02 HV EMPNO PIC X(6). 02 HV JOBCODE PIC S9(3). 01 HV EMPID PIC X(6).
Are preceded by a COLON when used in SQL statements to signify that they are host variables and not SQL variables. EXEC SQL SELECT EMPNO, JOBCODE INTO ; HV EMPNO, : HV JOBCODE FROM EMPLOYEE WHERE EMPNO = : HV EMPID END EXEC. Are just regular COBOL data items when used in a non SQL COBOL statement MOVE INPUT EMPID TO HV EMPID.

SQL and COBOL Data types



SMALLINT PIC S9(04) COMP

INTEGER

PIC S9(09) COMP

DECIMAL(p,s)

PIC S9(p-s)V9(s) COMP-3

CHAR(n)

PIC X(n)

VARCHAR(n)

01

var . 49 var1 PIC S9(04) COMP. 49 var2 PIC X(n) .

HOST VARIABLES

Are just the variables of the host programming language

Are variables that provide the following functions:

Selection Criteria as part of the WHERE clause predicates

Data Receiving Area as variable with the INTO clause

Data Variables in SELECT, INSERT or UPDATE statement.

Columns and the corresponding host variables data types must be compatible

HOST STRUCTURE

Is a group level of host variables defined in the DATA DIVISION of the program.

Matches the view or table referenced in the application

Relieves the programmer from naming each variable in the SQL statement

Can only be two levels, except in case a column is defined as variable length;

In that case, the third level must be a level 49

Structure can itself be part of a structure

INDICATOR VARIABLES

A variable of SMALLINT data type associated with a host variable Must be declared. Is preceded by a colon and directly follows its associated host variables, when used in an SQL statement. EXEC SQL SELECT INTO FROM WHERE END EXEC.

HIREDATE :HV HIREDATE : IV HIREDATE EMPLOYEE EMPNO = :HV EMPNO

Note *

IV HIREDATE is the indicator variable associated with the host variable HV - HIREDATE

INDICATOR VARIABLES

DB2 returns one of the following values to an indicator variable:

if the vale returned to the associated host variable by DB2

is NOT NULL, not truncated

-1

is NULL

>0 is a truncated character string; the value in the indicator variable is the length of the character string before truncation.

INDICATOR VARIABLES

An Indicator Variables can be used to: Indicate if its associated host variable has been assigned a NULL value Indicate if a returned character string has been truncated Set NULL value in the column

MOVE 1 TO IND HIREDATE.

EXEC SQL UPDATE

EMPLOYEE

SET HIREDATE =:HV HIREDATE:IND HIREDATE WHERE EMPNO =:HV EMPNO END EXEC.

INDICATOR STRUCTURE

Is defined to support a Host Structure

01

01

H-STRUCTURE. 02 HV-EMPNO 02 HV-HIREDATE 02 HV-SALARY I-STRUCTURE. 02 IV EXEC

PIC.. PIC.. PIC.. PIC S9(4) COMP OCCURS 3 TIMES.

SQL SELECT EMPNO, HIREDATE, SALARY INTO :H-STRUCTURE:I-STRUCURE FROM EMPLOYEE WHERE EMPNO = :HV-EMPNO END-EXEC.

DECLARING DB2 TABLES

DB2 tables to be used in a COBOL program must be declared in the WORKING-STORAGE SECTION Two ways of declaring tables: Coding the table declaration directly, using the DECLARE TABLE statement EXEC SQL DECLARE TDEPT TABLE (DEPT NO CHAR(3) NOTNULL, DEPTNAME VARCHAR(36) NOTNULL, MGRNO CHAR(6) NOTNULL, ADMRDEPT CHAR(3) NOTNULL) END-EXEC. Using DCLGEN (Declare Generation) to generate the table declaration and table copying the same into the program in the WORKING-STORAGE SECTION using the INCLUDE statement EXEC SQL INCLUDE END-EXEC.

DCLDEPT

DCLTDEPT is the member of a partitioned data set generated by DCLGEN and contains the declaration of TDEPT

DECLARING DB2 TABLES


DCLGEN

The DCLGEN panel is used to generate the table or view program declarations DCLGEN can be accessed from ISPF through DB21, directly from TSO with the DCLGEN command or in a batch mode with JCL The 1st part of the output is the TABLE declaration. Declaration the table in the program is optional, but it gives the following advantages: DOCUMENTATION the structure of the TABLE and the data type of the columns are specified The DB2 precompiler validates that the correct column names and data types are used in the SQL statements. Otherwise, this validation will not occur until BIND time. The 2nd part of the output is the host language data structure. DCLGEN generates this structure with appropriate data types and therefore reduces the chances of error while coding

CODING SQL TO MANIPULATE DB2 DATA

Considering the following SELECT statement:


EXEC SQL SELECT EMPNO, SALARY INTO :HV-EMPNO, :HV-SALARY FROM EMPLOYEE WHERE EMPNO =:HV-EMPID END-EXEC. * Each evaluation of the statement returns at most ONE row from the table EMPLOYEE DB2 places the retrieved data directly into the host variables The retrieved data is now ready for the program to use

* *

Note One can include the INTO clause in a select statement and set up host variables to receive data directly from DB2 only when the SELECT returns at most one row at a time.

HANDLING EXCEPTIONAL CONDITIONS


Exceptional conditions, returns after the execution of an SQL statement, can be handled by the SQL WHENEVER declarative statements in general EXEC SQL WHENEVER

{SQLWARNING /SQLERROR /NOT FOUND}

{GOTO LABEL /GOTO LABEL /CONTINUE}

END EXEC. * * * * * SQLWARNING Condition exists when SQLWARN0=W SQLERROR Condition exists when SQLCODE<0 NOTFOUND Condition exists when SQLCODE=100 GO TO LABEL Passes control to COBOL routine label CONTINUE Passes control to next program instruction The WHENEVER statement MUST precede the SQL statements it is to affect

NOTE

ALTERNATE ERROR HANDLING ECHNIQUES

Omitting a WHENEVER statement is the same as coding it with CONTINUE; the next program instruction gets the control One may explicitly test the data fields in SQLCA

EXAMPLE
Explicitly testing the value of SQLCODE: IF SQLCODE = 100 PERFORM OUTPUT ROUTINE.

Explicitly testing the value of SQLWARN1: IF SQLWARN1 = W DISPLAY VALUE US TRUNCATED.

A SIMPLE DB2/SQL COBOL PROGRAM

IDENTIFICATION DIVISION. PROGRAM-ID. SAMPLE1. * ENVIRONMENT DIVISION. * DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-VARS. 05 CNAME PIC X(20). 05 FAT-NAME PIC X(20). 05 M-NAME PIC X(20). 05 DOB PIC 9(6). 05 STATE PIC X(10). * EXEC SQL INCLUDE SQLCA END-EXEC. * EXEC SQL INCLUDE ORPHAN END-EXEC.

A SIMPLE DB2/SQL COBOL PROGRAM


PROCEDURE DIVISION. 0001-MAIN-PARA. DISPLAY Enter the Name of the Child. ACCEPT CNAME. DISPLAY Enter the Childs Fathers Name; Enter Blank if Unknown. ACCEPT FAT-NAME. DISPLAY Enter the Childs Mothers Name. ACCEPT DOB. DISPLAY Enter the State to which the Child belongs. ACCEPT STATE. * EXEC SQL INSERT INTO ORPHAN (NAME,FNAME,MNAME,DOB,STATE) VALUES(:CNAME,:FAT-NAME,:M-NAME, :DOB,:STATE) END-EXEC.
IF ELSE DISPLAY ERROR OCCURRED. SQLCODE = 0 DISLAY RECORD ADDED

STOP RUN.
* 0001-MAIN-PARA-EXIT. EXIT.

MULTIPLE-ROW TABLE MANIPULATION

Considering the following SELECT statement: EXEC SQL SELECT FROM WHERE END-EXEC. * * *

* TDEPT DEPTNO LIKE D%

This SELECT returns many rows from table TDEPT The rows are not ready for the application program to use because COBOL manipulates data only one row at a time Manipulation of many rows of returning data from a DB2 database is done by using the CURSOR facility.

CURSOR FACILITY

The CUROR facility allows a COBOL program to gain address ability to individual row occurrences of a many-rows Result table. The following is the sequence for cursor processing. DECLARE CURSOR either in WORKING STORAGE or ROCEUDRE DIVISION

Move the values for any host variables used in the WHERE clause criteria used to access the DB2 table
OPEN the CURSOR (Do this only when the program is ready to use the data) FETCH rows until the end of result table condition occurs CLOSE the CURSOR

DECLARE CURSOR STATEMENT

An SQL DECLARE statement Defines and associates a CURSOR with a SELECT statement and WHERE clause criteria used to access a DB2 table Names the cursor and its specific SELECT which, when the cursor is OPENed, will retrieve a Result Table whose rows satisfy the WHERE clause in the DECLARE CURSOR statement.

* *

FORMAT

EXEC

SQL DECLARE
SELECT FROM WHERE [FOR UPDATE OF

cursor-name CURSOR FOR column name list data source(s) conditions to be met (if any) column name list

END-EXEC.

DECLARE CURSOR STATEMENT


EXAMPLE EXEC SQL DECLARE SELECT FROM WHERE [FOR UPDATE OF END-EXEC.

C1 CURSOR FOR EMPNO,LASTNAME,JOBCODE EMPLOYEE WORKDEPT=:HV-WORKDEPT JOBCODE]

The associated SELECT in this example returns all rows with WORKDEPT equal to the value of the host variable HV-WORKDEPT; The cursor C1 is a pointer to the Result Table of these rows * * The Result Table is accessed a row at a time through the FETCH statement The FOR UPDATE OF clause must be specified to allow a row retrieved through a cursor to be changed by the DML UPDATE statement, if desire; the columns to be updated must be named in the column list Multiple unique cursors can be DECLARED in a program.

DECLARE CURSOR STATEMENT


* Besides the WHERE feature, the SELECT statement can utilize any or all of the following SQL features: Built-in Functions HAVING clause GROUP BY clause ORDER BY clause If the SELECT within DECLARE CURSOR statement utilizes any of the following features, the result table becomes read-only UNION operator DISTINCT keyword GROUP BY clause ORDR BY clause HAVING clause The Result Table will be read-only if the SELECT statement. References Identifies Identifies a read-only table/view more than one table/view a table/view accessed in a Sub SELECT

OPEN STATEMENT

Opens the cursor

EXAMPLE The following statement opens the cursor C1 previously declared and associated with the SELECT that build a Result Table

EXEC SQL OPEN END-EXEC.

C1

* When a cursor is open, DB2/SQL makes available the Result Table associated with the cursor; The cursor is positioned before the first row of the Result Table and no data is returned at this point

FETCH STATEMENT
* Returns a row from the Result Table to the programs data area FORMAT

EXEC SQL FETCH INTO END-EXEC.

cursor-name host-variable

* Host-variable(s) correspond to the parameters in the associated cursor statement EXAMPLE EXEC SQL FETCH INTO END-EXEC. *

C1 :HV-EMPNO,:HV-JCOD

Advances the cursor position to the next row of the Result Table making it the current row; DB2 then retrieves data from the current row into the program variables identified in the INTO clause

FETCH STATEMENT
*

Advances the position of the current row pointer in the forward direction only

Note No facility presently exists for moving the current pointer backward, to the top, or bottom of the Result Table * Can be executed on an OPEN cursor only; If an error occurs during the processing, the cursor is CLOSED and an error code is returned * If issued causing the cursor position to point after the last result table row, DB2 will set the SQLCODE field to + 100 and no data will be transferred to the host variables

CLOSE STATEMENT
* EXAMPLE EXEC SQL CLOSE END-EXEC. * Tells the DB2 system that the accessing of the Result Table is completed

C1

The cursor can be CLOSED at any time but it gets automatically CLOSED when: An Application Terminates

* *

A Program encounters an ABEND


A Program issues a Commit or Rollback All OPEND cursors will be CLOSED at the program termination, but a CLOSE statement is recommended for performance reasons. The CLOSE statement should be executed for the previously OPENED cursors only

A SKELETAL CURSOR PROGRAM SEGMENT


EXEC SQL DECLARE SELECT FROM WHERE END-EXEC. EXEC SQL OPEN END-EXEC. EXEC SQL FETCH INTO END-EXEC. C1 CURSOR FOR EMPNO, JOBCODE EMPLOYEE WORKDEPT=C01

C1

C1 :HV-EMPNO,:HV-JCOD

EXEC SQL CLOSE END-EXEC.

C1

Intermediate Results
FETCH HV-EMPNO 1 000030 2 000130 3 000140 HV-JCOD 60 55 56

A DB2/SQL COBOL PROGRAM WITH CURSOR

Problem Definition
To list the Name of the Child, its Date of Birth and the State to which it belongs, for those orphans whose Fathers name is unknown IDENTIFICATION DIVISION. PROGRAM-ID. SAMPLE1. * ENVIRONMENT DIVISION. * DATA DIVISION. WORKING STORAGE SECTION. 01 WS-VARS. 05 CNAME PIC X(20). 05 FAT-NAME PIC X(20). 05 M-NAME PIC X(20). 05 DOB PIC 9(6). 05 STATE PIC X(10). * EXEC SQL INCLUDE SQLCA END-EXEC. * EXEC SQL INCLUDE ORPHAN END-EXEC. *

A DB2/SQL COBOL PROGRAM WITH CURSOR

* EXEC SQL DECLARE NOPOP CURSOR FOR SELECT NAME, DOB, STATE FROM ORPHAN WHERE FNAME = END-EXEC. * PROCEDURE DIVISION. 0001-MAIN-PARA. EXEC SQL OPEN CURSOR NOPOP END-EXEC. PERFORM 0011-CULL-PARA UNTIL SQLCODE = 100. EXEC SQL CLOSE NOPOP END-EXEC. STOP RUN.

A DB2/SQL COBOL PROGRAM WITH CURSOR


0001-MAIN-PARA-EXIT. EXIT. 0011-CULL-PARA EXEC SQL FETCH INTO END-EXEC. IF

NOPOP :CNAME, :DOB, :STATE

SQLCODE NOT EQUAL TO 100 DISPLAY CNAME, DOB, STATE. 0011-CULL-PARA-EXIT. EXIT.

Preparation Phase

PREPARING A DB2/SQL COBOL PROGRAM FOR EXECUTION


Steps involved in preparing a DB2/SQL program for execution (to translate from the programmers environment into computer readable code)
* * * Precompile Compile & Link-Edit Bind

PRE-COMPILER
DB2 precompile analyzes all of the embedded SQL statements. SQL statements are placed in a data base request module (DBRM). SQL statements are commented out in source and replaced with the host language caLL
statement.

DB2 precompile timestamps the DBRM modules and the program source code. This
timestamp is passed down to the program load module, and is also tied to the plan by the DB2 catalog.

A Data Base Request Module (DBRM) that will be used later when the program goes to the
BIND process is created

BIND
Info about DB2 tables, indexes, etc.

*Has an its objective the creation of an Application Access Plan in the DB2 environment.

DB2 CATALOG DBRM1 SYSIBM.SYSTABLESPACE SYSIBM.SYSTABLES SYSIBM.SYSCOLUMNS SYSIBM.SYSINDEXES SYSIBM.SYSCOLDIST

*Bind

Extracted SQL statements from program

determines access paths in the following ways:

D
DBRM2

Data access strategy (plan)

B 2

DB2 DIRECTORY DSNDB01.SCT02 Information about bind

Identifying which indexes will be used


Defining sorting that will

Package List DB2 CATALOG SYSIBM.SYSDBRM SYSIBM.SYSPLAN SYSIBM.SYSPLANAUTH SYSIBM.SYSPLANDEP SYSIBM.SYSPACKLIST SYSIBM.SYSPLSYSTEM SYSIBM.SYSSTMT SYSIBM.SYSPACKAUTH SYSIBM.SYSTABAUTH Optimizer

BIND
Info about DB2 tables, indexes, etc.

COMPILE AND LINK-EDIT


DB2 CATALOG

* As the program is compiled, the various source modules become object modules. * These object modules are then link edited into load modules BIND *Has an its objective the creation of an Application Access Plan in the DB2 environment. *Analyzing the DBRMs, it develops an Application Access plan based on the access requested and the database components present. *This plan is retrieved and executed every time the program is run

DBRM1

Extracted SQL statements from program

SYSIBM.SYSTABLESPACE SYSIBM.SYSTABLES SYSIBM.SYSCOLUMNS SYSIBM.SYSINDEXES SYSIBM.SYSCOLDIST

D
DBRM2

Data access strategy (plan)

B 2

DB2 DIRECTORY DSNDB01.SCT02 Information about bind

Package List DB2 CATALOG SYSIBM.SYSDBRM SYSIBM.SYSPLAN SYSIBM.SYSPLANAUTH SYSIBM.SYSPLANDEP SYSIBM.SYSPACKLIST SYSIBM.SYSPLSYSTEM SYSIBM.SYSSTMT SYSIBM.SYSPACKAUTH SYSIBM.SYSTABAUTH Optimizer

PREPARING A DB2/SQL COBOL PROGRAM FOR EXECUTION


Precompiler
*
*

Is a preprocessor for the host programming languages (PL/I,COBOL, etc.) Analyzes a host language source module, stripping out
all the SQL statements, it finds and replacing them by host language CALL statements;

(At run time those Calls will pass control-indirectly- to


the Runtime Supervisor) * * Constructs with this information, a DBRM which becomes input to the Bind component Produces a source listing, showing the original source

code, diagnostics, cross-reference information, etc.


DBRM * * Constructed by the Precompiler from the SQL statements it encounters One per source module

*
*

Stored a member of an MVS Partitioned Data Set


Contains an edited form of the original SQL statements, together with certain additional information

PREPARING A DB2/SQL COBOL PROGRAM FOR EXECUTION


PACKAGE * Produced by binding the DBRMs

*
*

Consists of a set of internal structures, representing the compiled from of the original SQL statements in the corresponding DBRMs
Physically stored in the DB2 directory

COLLECTION * * * A name given to a logically related set of packages Does not have nay physical existence of its own Typically (but not necessarily) all of the packages used in a given application would be assigned to the same collection

Packages and Collections


* Each package is assigned to exactly one collection when it is created

Collections provide a useful level of indirection

PREPARING A DB2/SQL COBOL PROGRAM FOR EXECUTION


PLAN (Application Plan)

Consists simply of a lit of the (names of the ) packages needed to execute that application Is produced by binding together the specified packages and/or DBRMs The packages concerned are specified either by individual package name or by collection name (meaning, all packages in the specified collection)

* *

PREPARING A DB2/SQL COBOL PROGRAM FOR EXECUTION


*

Is an optimizing compiler Converts high-level database requests (SQL statements) into optimized internal form * Compiles SQL statements into CODE even though that code is not true machine code per se Code Set of internal control structures, that are used to drive a set of generalized I/O routines within the Data Manager

* that * * plan

Has as its input, a DBRM and as its output, a package (the compiled form of DBRM) BINDs a given DBRM to produce a Package BINDs together a list of packages to produce an Application Plan or simply

If a DBRM is thought of as a SQL source module, then the package produced by binding that DBRM can be though of as the corresponding object module
DB2 is thus a compiling system and Bind perform a compiling function for SQL statements, much as the host language compiler provides a compiling function for the host language statements in which those SQL statements are embedded

PREPARING A DB2/SQL COBOL PROGRAM FOR EXECUTION


Syntax Checking

* Bind examines the SQL statements in the input DBRM, parses them, and reports on errors it finds.

any syntax

Note Even though the Precompiler has already performed similar checks, as the Precompiler is decoupled from the rest of DB2, Bind cant assume that its input is a valid precompiler output the user might have constructed an invalid DBRM via some other mechanism The Precompiler can run even when DB2 is not available. It can even run on a different machine and its output is not automatically protected. DataBase Request Validation * Validates all the tables, views, and columns used in the program terminate

* If any of the above objects is not present in the DB2 system, the BIND process will abnormally

PREPARING A DB2/SQL COBOL PROGRAM FOR EXECUTION


Optimization
* * Note Bind includes an Optimizer as an important subcomponent The optimizer chooses, for each SQL statement it processes, an optional access strategy for implementing that statement Data manipulation statements such as SELECT specify only what data the user, wants, not how to get to that data; The access path for getting to that data will be chosen by the optimizer. Programs independent of such access paths. * Even in a very simple case, there could be at least two ways of performing the optimizer will choose one of the two available strategies to adopt are thus

desired retrieval. The the

* In general, the optimizer will make its choice on the basis of such considerations as following: Which tables are referenced in the SQL statement? How big those tables are? How selective those indices are? How the data is physically clustered on the disk? The form of the data WHERE clause in the request and so on.

Optimization
* Bind will generate code that is tightly bound to the optimizer's choice of strategy package will include

Eg If the optimizer decides to make use of an index called X, then the generated explicit references to index X Q Where does the optimizer get its information from? How does it know how big the tables are, or what indexes exist?

A This information is kept in the catalog, in the form of database statistics. A special utility, RUNSTATS is provided for gathering such statistics and storing them in the catalog for the optimizers use

Package Generation * Is the actual process of building the package

Verifying Authorization
* Checks whether the user who is to be the owner of the bound package is allowed to perform the operations requested in the DBRM to be bound and to assign packages to the applicable package collection

Plan Bind
* * Has as its input, a list of packages and/or package collections and as its output, the bound application plan Also does some authorization checking. Specifically, it checks that the user who is to be

the owner of the bound plan is authorized to execute all of the applicable

packages

FINAL EXECUTION

* Since the original program has now effectively been broken into two pieces (Load Module and Application Plan), those two pieces must somehow be brought back together again at execution time * First, the COBOL load module is loaded into memory; it starts to execute in the usual way

* Sooner or later it reaches the first call to the DB2 Languages Interface module. That module gets control and passes control in turn to the Runtime Supervisor

*The Runtime Supervisor then retrieves the application plan (and associated packages) from the DB2 directory, loads them into the memory, and uses the information they contain to request the desired function on the part of the Data Manager
*The Data Manager in turn performs the necessary operations on the actual stored data and passes results back (as appropriate) to the COBOL program

RUN TIME SUPERVISOR * * * Is resident in main memory when the appln. Program is executing, to oversee that execution Is the firs to get the control, when the appln. Program requests some database operation to be performed Uses the control information to request the appropriate operations on the part of the Data Manager.

DATA MANAGER * Is the component that manages the physical databases by performing all of the normal access method functions like search, retrieval, update, index maintenance. * Invites other system components as necessary in order to perform detailed functions as locking, logging, I/O operations, etc. during the performance of its basic task BUFFER MANAGER * Is the component responsible for physically s data between external storage and memory * Employs sophisticated techniques such as read-ahead buffering and look-aside buffering to get the best performance out of the buffer pools under its care and to minimize the amount of physical I/O actually performed.

Vous aimerez peut-être aussi