You are on page 1of 55

Objectives

s s

COBOL Programming for the IMS Database

To create awareness about the IMS DB technology and how it is used to perform database operations, from an application programmers point of view. The target audience consists of people who are new or relatively new to the IMS DB Technology. Knowledge of COBOL Basic knowledge of database management systems An Introduction to DL/I Databases An Introduction to DL/I Programs and Control Blocks COBOL Basics for Processing a DL/I Database Using Segment Search Arguments Retrieving Data from a Database Adding and Updating Data in a Database Secondary Indexing Logical Databases Recovery and Restart Features

Prerequisites
s s

Course Outline
s s s s s s s s s

References
s

IMS for the COBOL Programmer Part 1: Database processing with IMS/VS and DL/I DOS/VS
By Steve Eckols

IBM IMS Primer By Rick Long, Mark Harrington, Robert Hain, Geoff Nicholls

Module 1 An Introduction to DL/I Databases


s s s s

Hierarchical Structures Why a Database Management System Basic DL/I Terminology Basic DL/I Database Processing

Hierarchical Structures
s s s

In a DL/I database, data elements are organized in a hierarchical structure. Some data elements are dependent on others. DL/I supports hierarchies that are difficult to implement with standard files.

Why a database management system?


01 VENDOR-RECORD. 05 VR-VENDOR-CODE 05 VR-VENDOR-NAME 05 VR-VENDOR-ADDRESS 05 VR-VENDOR-CITY 05 VR-VENDOR-STATE 05 VR-VENDOR-ZIP-CODE 05 VR-VENDOR-TELEPHONE 05 VR-VENDOR-CONTACT PIC X(3). PIC X(30). X(30). X(17). PIC XX. X(9). X(10). X(30).

PIC PIC PIC PIC PIC

Fig 1.2.a Record layout for the VENDORS dataset 01 INVENTORY-RECORD. 05 IR-ITEM-KEY. 10 IR-VENDOR-CODE PIC X(3). 10 IR-NUMBER PIC X(5). 05 IR-DESCRIPTION PIC X(35). 05 IR-UNIT-PRICE PIC S9(5)V99 COMP-3. 05 IR-AVG-UNIT-COST PIC S9(5)V99 COMP-3. 05 IR-LOCATION-QUANTITY-DATA OCCURS 20 TIMES. 10 IR-LOCATION PIC X(3). 10 IR-QUANTITY-ON-HAND PIC S9(7) COMP-3. 10 IR-REORDER-POINT PIC S9(7) COMP-3. 10 IR-QUANTITY-ON-ORDER PIC S9(7) COMP-3. 10 IR-LAST-REORDER-DATE PIC X(6). Fig 1.2.b Record layout for the Inventory Master dataset Fig 1.2 Record layouts that illustrate a hierarchical structure

Segment
x x x

Basic DL/I Terminology

A grouping of data The unit of data that DL/I transfers to and from your program in an I/O operation. Consists of one or more fields ADDRESS House Street Number Name City State Country Zip Code

Fig 1.3 The ADDRESS segment with six fields Segment Type


Note:-

A category of data There can be a maximum of 255 segment types and 15 levels in one database One specific segment of a particular type containing user data

Segment Occurrence

Within a database there is only one of each segment type- its part of the databases definition- but there can be an unlimited number of occurrences of each segment type. The word segment is used to mean either segment type or segment occurrence and usually the meaning is clear from the context

Basic DL/I Terminology (contd.)

Vendor

Item

Stock Location
Fig 1.4 The hierarchical structure of the Inventory database with three segment types * 01 INVENTORY-VENDOR-SEGMENT. 05 IVS-VENDOR-CODE PIC X(3). 05 IVS-VENDOR-NAME PIC X(30). 05 IVS-VENDOR-ADDRESS PIC X(30). 05 IVS-VENDOR-CITY PIC X (17). 05 IVS-VENDOR-STATE PIC XX. 05 IVS-VENDOR-ZIP-CODE PIC X(9). 05 IVS-VENDOR-TELEPHONE PIC X(10). 05 IVS-VENDOR-CONTACT PIC X(30). * 01 INVENTORY-ITEM-SEGMENT. 05 IIS-NUMBER PIC X(5). 05 IIS-DESCRIPTION PIC X(35). 05 IIS-UNIT-PRICE PIC S9(5)V99 COMP-3. 05 IIS-AVG-UNIT-COST PIC S9(5)V99 COMP-3. * 01 INVENTORY-STOCK-LOC-SEGMENT. 05 ISLS-LOCATION PIC X(3). 05 ISLS-QUANTITY-ON-HAND PIC S9(7) COMP-3. 05 ISLS-REORDER-POINT PIC S9(7) COMP-3. 05 ISLS-QUANTITY-ON-ORDER PIC S9(7) COMP-3. 05 ISLS-LAST-REORDER-DAT PIC X(6).
*

Fig 1.5 Segment layouts for the Inventory database

Root Segment
x

Basic DL/I Terminology (contd.)

The segment type at the top of a hierarchy Each occurrence of the root segment plus all the segment occurrences that are subordinate to it make up one database record Every database record has one and only one root segment, although it may have any number of subordinate segment occurrences

Database record
x

Vendor 1

Vendor 2

Item 2 Item 1

Item 1

Database Record 2

Database Record 1 Loc 5 Loc 4 Loc 3 Loc 2 Loc 1

Loc 2 Loc 1

Loc 2 Loc 1

Fig 1.6 Two database records from the Inventory database

Basic DL/I Terminology (contd.)


s

Dependent Segments
x x

All of the segments in a database record other than the root segment They depend on one or more segments for their complete meaning A segment that has one or more dependent segments Every dependent segment in the hierarchy Two or more segment occurrences of the same type and with the same segment occurrence as their parent are twins of one another The series of segments that lead from the top of a database record (the root segment occurrence) down to any specific segment occurrence Must be continuous- you cant skip intermediate levels

Parent Segment
x

Child Segment
x

Twin Segment
x

Path
x

Logical databases
x

Basic DL/I Terminology (contd.)

Although DL/I doesnt support multiple parent relationships in physical databases, it does let you define logical databases (or create additional relationships within one physical database)

Customer

Ship-to

Vendor

Buyer

Receivable

Item

Payment

Adjustment

Line Item

Stock Location

Fig 1.7 A logical relationship can connect two databases

In Fig 1.7, the line item segment is the logical child segment (or just logical child) of the item segment. Likewise, the item segment is the logical parent segment (or just logical parent) of the line item segment

Basic DL/I Database Processing


s

Sequential Processing
x

When you retrieve segments from a database sequentially, DL/I follows a predictable pattern: down the hierarchy, then right.
Position

At any point, a program has a position in the database. Position can affect not only how segments are retrieved, but how new segments are inserted as well

Vendor 1

Vendor 2

Item 2 Item 1

Item 1

Database Record 2

Database Record 1 Loc 5 Loc 4 Loc 3 Loc 2 Loc 1


Fig 1.8 Sequential processing

Loc 2 Loc 1

Loc 2 Loc 1

Basic DL/I Database Processing (contd.)


s

Random (Direct) Processing


x x

Many applications require that a database be processed randomly rather than sequentially Segments that you need to access randomly normally contain a key field (or sequence field)
Concatenated Key Completely identifies the path from the root segment to the segment you want to retrieve.

Vendor 1

Vendor 2

Item 2 Item 1 Loc 2 Database Record 1 Loc 5 Loc 4 Loc 3 Loc 2 Loc 1
Fig 1.9 Random Processing

Item 1

Database Record 2

Loc 2 Loc 1

Loc 1

Concatenated Key: Vendor 2 Item 1 Location 1

Module 2 An Introduction to DL/I Programs and Control Blocks


s s s s s s

The IMS Software Environment How DL/I relates to your application programs Control Blocks DBDGEN PSBGEN How to run an application program that uses DL/I

The IMS Software Environment Application Programs

IMS Control Blocks

IMS DC

Remote Terminal

DL/I

OS

Database
Fig 2.1 The IMS Software Environment

How DL/I relates to your application programs


Standard File Processing DL/I Database Processing

Application Program

Application Program

DL/I

Operating System Access Method (eg. VSAM)

Operating System Access Method (eg. VSAM)

File Dataset
Fig 2.2 Standard file processing compared to DL/I database processing

Database Dataset

How DL/I relates to your application programs (contd.)


s

Standard file processing


x x

Application programs issue standard COBOL statements like READ and WRITE These statements invoke the appropriate access method, like VSAM to transfer data between records if necessary The format of the record that is processed by your program is the same as the format of the record on disk DL/I acts as an interface between an application program and the access method To perform an operation on a DL/I database, a program doesnt issue a standard COBOL file I/O statement Instead it executes a CALL statement to invoke DL/I The parameters passed by the call tell DL/I what operation to perform Then DL/I, not the application program, invokes the access method DL/I uses a standard access method- usually VSAM- to store database data on disk In fact, the access method doesnt know that a particular dataset contains a database instead of a standard file Format of records in a database dataset probably doesnt match the layouts of the segments that make up the database As a result, the way the program sees the database differs from the way the access method sees.

DL/I database processing


x x

x x x x x

Control Blocks

s s s s

The physical structure of a DL/I database isnt specified in application programs Instead, DL/I uses a set of control blocks to define a databases structure In particular, DL/I uses two types of control blocks: DBDs and PSBs
Database Description (DBD)
x x

Describes the complete structure of a database An installation must create one DBD for each DL/I database Although each database has a single physical structure that is defined by a DBD, the application programs that process it can have different views of it These views, also called application data structures, specify

Program Specification Block (PSB)


x

The databases (one or more) a program can access, The data elements the program can see in those databases, and, The processing the program can do.

x x

This information is specified in a PSB Although each application program can have its own PSB, it is not uncommon for application programs that have similar database processing requirements to share a PSB

Creating DL/I control blocks is the responsibility of a Database Administrator (DBA)

STMT SOURCE STATEMENT 1 PRINT NOGEN 2 DBD NAME=INDBD,ACCESS=HIDAM 3 DATASET DD1=IN,DEVICE=3380 4 **/ 3380 DISK STORAGE 5 * 6 SEGM NAME=INVENSEG, PARENT=0,POINTER=TB,BYTES=131 7 LCHILD NAME=(INPXPNTR,INPXDBD),POINTER=INDX 8 FIELD NAME=(INVENCOD,SEQ),BYTES=3,START=1,TYPE=C 9 FIELD NAME=INVENNAM,BYTES=30,START=4,TYPE=C 10 FIELD NAME=INVENADR,BYTES=30,START=34,TYPE=C 11 FIELD NAME=INVENCIT,BYTES=17,START=64,TYPE=C 12 FIELD NAME=INVENSTA,BYTES=2,START=81,TYPE=C 13 FIELD NAME=INVENZIP,BYTES=9,START=83,TYPE=C 14 FIELD NAME=INVENTEL,BYTES=10,START=92,TYPE=C 15 FIELD NAME=INVENCON,BYTES=30,START=102,TYPE=C 16 * 17 SEGM NAME=INITMSEG,PARENT=INVENSEG,BYTES=48 18 FIELD NAME=(INITMNUM,SEQ),BYTES=5,START=1,TYPE=C 19 FIELD NAME=INITMDES,BYTES=35,START=6,TYPE=C 20 FIELD NAME=INITMPRC,BYTES=4,START=41,TYPE=P 21 FIELD NAME=INITMCST,BYTES=4,START=45,TYPE=P 22 * 23 SEGM NAME=INLOCSEG, PARENT=INITMSEG,BYTES=21 24 FIELD NAME=(INLOCLOC,SEQ),BYTES=3,START=1,TYPE=C 25 FIELD NAME=INLOCONH,BYTES=4,START=4,TYPE=P 26 FIELD NAME=INLOCROP,BYTES=4,START=8,TYPE=P 27 FIELD NAME=INLOCONO,BYTES=4,START=12,TYPE=P 28 FIELD NAME=INLOCDAT,BYTES=6,START=16,TYPE=C 29 * 30 DBDGEN 72 **/************************************************************************** 73 **/ RECOMMENDED VSAM DEFINE CLUSTER PARAMETERS 74 **/************************************************************************** 75 **/* *NOTE2 76 **/* DEFINE CLUSTER (NAME(IN) NONINDEXED 77 **/* RECORDSIZE (2041,2041) 78 **/* COUNTERINTERVALSIZE (2048)) 79 **/* *NOTE2 - SHOULD SPECIFY DSNNAME FOR DD IN 80 **/************************************************************************** 162 **/***********SEQUENCE FIELD*************

DBDGEN

211 236 325 326


s

**/***********SEQUENCE FIELD************* **/***********SEQUENCE FIELD************* FINISH END Fig 2.3 Assembler source listing for the Inventory database DBDGEN Explanation of Fig 2.3
x x

x x

x x

x x

The first macro DBD identifies the database The DBD macro names the database (NAME=INDBD) and specifies the DL/I access method that will be used for it (ACCESS=HIDAM) The second macro, DATASET, identifies the file that will contain the database In this case, its symbolic name will be IN (DD1=IN), and it will reside on a 3380 disk unit (DEVICE=3380) The symbolic name is used in the JCL to identify the dataset at execution time Lines 72 through 80 are produced at assembly time and give recommendations for the VSAM file that will contain the inventory database The segment types are defined using the SEGM macro The hierarchical relationships among the segments are specified by coding the PARENT parameter on each SEGM macro

PARENT= 0 or absence of PARENT parameter specifies root segment

The POINTER parameter in the first SEGM macro and the LCHILD macro that follows are required because the DBA specified HIDAM in the DBD macro DBA does not have to define each field in the segment, because application programs identify fields within it in a segment layout. Only search fields need to be specified To define a field in the DBD, the DBA codes a FIELD macro, which can contain the following parameters

DBDGEN (contd.)

NAME START LENGTH TYPE

name of the field (1 to 8 characters long) position of field within segment length of the field data type of the field Data Type Character Packed decimal Zoned decimal Hexadecimal Half word Binary Full word Binary Fig 2.4 FIELD macro TYPE parameter codes

FIELD Macro TYPE Codes C P Z X H F

The SEQ parameter is used to specify a sequence field

When occurrences of these segments are added to the database, they are added in sequence by values in these fields

STMT SOURCE STATEMENT 1 PRINT NOGEN 2 PCB TYPE=DB,DBDNAME=INDBD,KEYLEN=11,PROCOPT=LS 3 SENSEG NAME=INVENSEG 4 SENSEG NAME=INITMSEG,PARENT=INVENSEG 5 SENSEG NAME=INLOCSEG,PARENT=INITMSEG

PSBGEN

6 PSBGEN 87 END

PSBNAME=INLOAD,LANG=COBOL

Fig 2.5 Assembler source listing for the Inventory database load programs PSBGEN
s

Explanation of Fig 2.5


x x x x

The first macro in the PSBGEN job stream is PCB PCB (Program Communication Block) describes one database. A PSBGEN job contains one PCB macro for each database the application program can access. The PSB in the figure is one for a program that accesses a single database with segment level sensitivity Segment Level Sensitivity

The programs access to parts of the database is identified at the segment level Within the segments to which it is sensitive, the program has access to all fields Within sensitive segments, only specific fields are identified as sensitive fields When the program accesses that segment, only sensitive fields are presented

A program can also have field level sensitivity


The DBDNAME parameter on the PCB macro specifies the name of the DBD for the database to which the PCB corresponds The KEYLEN parameter specifies the length of the longest concatenated key the program can process in the database The PROCOPT parameter specifies the programs processing options

Indicate what processing the program is allowed to perform on the database LS The program can perform only load operations Other values can authorize programs to retrieve, insert, replace, and delete segments This parameter can be used by the DBA to control access to the database more selectively than is possible at the database level

For each PCB macro, subordinate SENSEG macros identify the segments in the database to which the application program is sensitive

The names specified in the SENSEG macros must be segment names from the DBDGEN for the database named in the DBDNAME parameter of the PCB macro

x x

All SENSEG macros for segments other than the root segment must include the PARENT parameter The last PSBGEN macro in the figure is PSBGEN

Indicates that there are no more statements in the PSBGEN job Its PSBNAME parameter specifies the name to be given to the output PSB module The LANG parameter specifies the language in which the related application program will be written.

How to run an application program that uses DL/I


s s s s

A batch program that processes a DL/I database is not run directly Instead, the programmer supplies JCL to invoke the DL/I batch initialization module, which in turn loads the application program and the DL/I modules required to service it. Under IMS, the batch initialization module is DFSRRC00 The program and DL/I modules execute together

s s s

The ENTRY and GO BACK Statements The DL/I Call The PCB Mask

Module 3 COBOL Basics for Processing a DL/I Database

The ENTRY and GO BACK Statements


ENTRY DLITCBL USING PCB-name1 [PCB-name2...]

Fig 3.1 Format of the DL/I ENTRY Statement s s s s s s s s s

The application program is invoked under the control of the batch initialization module DL/I first loads the appropriate control blocks and modules, then loads the application program and passes control to it DLITCBL, which stands for DL/I to COBOL is declared as the entry point to the program by coding the ENTRY statement When DL/I passes control to the program, it also supplies the address of each PCB defined in the programs PSB, in much the same way as parameters are passed to a called subprogram Since these PCBs reside outside the program they must be defined in the Linkage Section, just like passed parameters would be defined in a subprogram The Linkage Section definition of a PCB is called a PCB Mask Addressability to PCBs- that is, the way the programmer relates PCB masks in your programs Linkage Section to actual PCBs in storage- is established by listing the PCB Masks on the ENTRY statement Although the order in which the PCB Masks are coded in the Linkage Section does not matter, you must list them on the ENTRY statement in the same sequence as they appear in your programs PSBGEN The GO BACK Statement
x x x x x

The ENTRY statement provides a mechanism for DL/I to transfer control to your program When your program ends, it must pass control back to the DL/I so that DL/I can deallocate its resources and close your database datasets To do that, you code a GO BACK statement, not a STOP RUN statement If you end a DL/I program with a STOP RUN statement, control returns directly to the operating system; DL/I never has a chance to perform its termination functions So always use GO BACK rather than STOP RUN in your DL/I programs

s s

CALL statements are used to request DL/I services The parameters you code on the CALL statement specify, among other things, the operation you want DL/I to perform

The DL/I Call

CALL CBLTDLI USING DLI-function PCB-mask Segment-io-area [Segment-search-argument]


Fig 3.2 Format of the DL/I call
s s s

CBLTDLI, which stands for COBOL to DL/I, is the name of an interface module that is link edited with your programs object module. If you work on PL/I, you would specify PLITDLI and for assembler language, you would specify ASMTDLI The DL/I Function
x x

The first parameter coded on any DL/I call For this parameter, you supply the name of a four character working storage field that contains the code for the function you want

01 DLI-FUNCTIONS. 05 DLI-GU 05 DLI-GHU 05 DLI-GN 05 DLI-GHN 05 DLI-GNP 05 DLI-GHNP 05 DLI-ISRT 05 DLI-DLET 05 DLI-REPL 05 DLI-CHKP 05 DLI-XRST 05 DLI-PCB Fig 3.3 DL/I function codes
x

PIC PIC PIC PIC PIC PIC

PIC PIC PIC PIC PIC X(4) X(4) X(4) X(4) X(4) X(4) PIC

X(4) X(4) X(4) X(4) X(4) VALUE VALUE VALUE VALUE VALUE VALUE X(4)

VALUE GU . VALUE GHU . VALUE GN . VALUE GHN . VALUE GNP . GHNP. ISRT. DLET. REPL. CHKP. XRST. VALUE PCB .

For specifying the DL/I function, the programmer would code one of the 05 level data names (like DLI-GN) in a DL/I call, since COBOL doesnt let you code literals on a CALL statement Get functions

The first six 05-level items in Fig 3.3 are get functions They are used to retrieve segments from a DL/I database GU get unique function causes DL/I to retrieve a specific segment occurrence based on field values that you specify. GN get next function used to retrieve segment occurrences in sequence GNP get next within parent function lets you retrieve segment occurrences in sequence, but only subordinate to an established parent segment The three get function codes that contain an H are get hold functions and are used to specify an intent to update a segment after you retrieve it GHU or the get hold unique function corresponds to GU GHN or the get hold next function corresponds to GN GHNP or the get hold next within parent function corresponds to GNP Used to change data in the database ISRT or the insert function is used to add a new segment occurrence to a database whether it be change an existing database or to load a new one DLET or the delete function is used to remove a segment from a database REPL or the replace function is used to replace a segment occurrence

Update functions

Other functions

Functions CHKP (the checkpoint function) and XRST (the restart function) are used in programs to take advantage of IMSs recovery and restart features The last function code PCB is used in CICS programs The PCB mask
x x x

The second parameter on the DL/I call The name of the PCB mask defined in the programs Linkage Section The ENTRY statement establishes a correspondence between PCB masks in the Linkage Section and the PCBs within the programs PSB So, when you code a particular PCB mask on a DL/I call, you tell DL/I which database to use for the operation you are requesting After each DL/I call, DL/I stores a status code in the PCB mask, which the programmer can use to determine whether the call succeeded or failed The third parameter on the DL/I call The name of the working storage field into which DL/I will return retrieved data or from which it will get data for an update operation Optional parameter on the DL/I call An SSA identifies the segment occurrence you want to access

Segment I/O Area


x x

Segment search arguments


x x

x x x x

Depending on the call you are issuing and the structure of the database, you may have to code several SSAs on a single DL/I call The structure of the SSAs can vary from simple to complex You can code as many SSAs as required There are two kinds of SSAs unqualified and qualified An unqualified SSA

Supplies the name of the next segment type that you want to operate on For instance, if you issue a GN call with an unqualified SSA, DL/I will return the next occurrence of the segment type you specify Combines a segment name with additional information that specifies the segment occurrence to be processed For example, a GU call with a qualified SSA might request a particular occurrence of a named segment type by providing a key value

A qualified SSA

The PCB Mask


s s s

For each database your program accesses, DL/I maintains an area of storage called the program communication block (PCB) You define masks for those areas of storage in the Linkage Section of your program Then, after establishing the proper linkage to them at the start of your program, you can evaluate data DL/I stores there for information about the databases your program can process

01 INVENTORY-PCB-MASK. 05 IPCB-DBD-NAME PIC X(8). 05 IPCB-SEGMENT-LEVEL PIC 05 IPCB-STATUS-CODE PIC 05 IPCB-PROC-OPTIONS PIC 05 FILLER PIC S9(5) 05 IPCB-SEGMENT-NAME PIC 05 IPCB-KEY-LENGTH PIC S9(5) 05 IPCB-NUMB-SENS-SEGS PIC 05 IPCB-KEY PIC X(11).
Fig 3.4 PCB mask for the Inventory database
s

XX. XX. X(4). COMP. X(8). COMP. S9(5) COMP.

Database name
x

The name of the database being processed Specifies the current segment level in the database After a successful call, DL/I stores the level of the segment just processed in this field Contains the DL/I status code When DL/I successfully completes the processing you request in a call, it indicates that to your program by moving spaces to the status code field in the PCB On the other hand, if a call is unsuccessful or raises some condition that isnt normal, DL/I moves some non-blank value to the status code field It is good programming practice to evaluate the status code after you issue a DL/I call Indicates the processing a program is allowed to do on the database The name of the segment is stored by DL/I in this field after each DL/I call. The field DL/I uses to report the length of the concatenated key of the lowest level segment processed during the previous call Used with the key feedback area Contains the number of SENSEG macros subordinate to the PCB macro for this database

Segment level
x x

Status code
x x

Processing options
x

Segment name feedback area


x

Key length feedback area


x

Number of sensitive segments


x

Key feedback area

x x

Varies in length from one PCB to another As long as the longest possible concatenated key that can be used with the programs view of the database After a database operation, DL/I returns the concatenated key of he lowest level segment processed in this field, and it returns the keys length in the key length feedback area

s s s s s s

Types of SSAs Basic Unqualified SSA Basic Qualified SSA Command Codes The Null Command Code Multiple Qualifications

Module 4 Segment Search Arguments

Types of SSAs
s s

An SSA identifies the segment occurrence you want to access It can be either
x x

Qualified, or, Unqualified

s s

An unqualified SSA simply names the type of segment you want to use A qualified SSA, on the other hand, specifies not only the segment type, but also a database specific occurrence of it.
x x

Includes a field value DL/I uses to search for the segment you request Any field to which the program is sensitive to can be used in an SSA

s s s

Because of the hierarchical structure DL/I uses, you often have to specify several levels of SSAs to access a segment at a low level in a database You can code as many SSAs on a single call as you need You can combine qualified and unqualified SSAs on a single call

Basic Unqualified SSA

01 UNQUALIFIED-SSA. * 05 UNQUAL-SSA-SEGMENT-NAME PIC X(8). 05 FILLER PIC X VALUE SPACE. *


Fig 4.1 A basic unqualified SSA
s s s s

A basic unqualified SSA is 9 bytes long The first eight bytes contain the name of the segment you want to process If the segment name is less than eight characters long, you must pad it on the right with blanks The ninth position of a basic unqualified SSA always contains a blank
x

The DL/I uses the value in position 9 to decide what kind of SSA you are providing

Unqualified SSA shown in Fig 4.1 was generalized


x

To access a particular segment type, you must modify the segment name during program execution, by moving an appropriate eight-character segment name to the field UNQUAL-SSA-SEGMENTNAME

For example,
MOVE INVENSEG TO UNQUAL-SSA-SEGMENT-NAME MOVE INITMSEG TO UNQUAL-SSA-SEGMENT-NAME

Alternatively, you can code the segment name as a literal when you define a qualified SSA
x

For example,

01 UNQUAL-VENDOR-SSA PIC X(9) VALUE INVENSEG . * 01 UNQUAL-ITEM-SSA PIC X(9) VALUE INITMSEG . * 01 UNQUAL-STOCK-LOC-SSA PIC X(9) VALUE INVENSEG .

Basic Qualified SSA

01 VENDOR-SSA. * 05 FILLER PIC X(9) VALUE INVENSEG(. 05 FILLER PIC X(10) VALUE INVENCOD =. 05 VENDOR-SSA-CODE PIC X(3). 05 FILLER PIC X VALUE ). *
Fig 4.2 A basic qualified SSA
s s s s s

A qualified SSA lets you specify a particular segment occurrence based on a condition that a field within the segment must meet The first eight characters of a basic qualified SSA is the eight character segment name The ninth byte is a left parenthesis: ( Immediately following the left parenthesis in positions 10 through 17 is an eight character field name After the field name, in positions 18 and 19, you code a two-character relational operator to indicate the kind of checking DL/I should do on the field in the segment
x

The qualified SSA relational operators are shown below

Equal to EQ = = Not equal to NE = = Greater Than GT > > Greater than or Equal to GE >= => Less Than LT < <

Less than or Equal to

LE

<=

=<

stands for a sing le blank space


s s s

After the relational operator, you code a variable field into which you move the search value you want to use for the call The length of the search value field can vary depending on the size of the field in the segment it is the only part of a basic qualified SSA that doesnt have a fixed length The last character in the qualified SSA is a right parenthesis: )

Command Codes

Fig 4.3 Unqualified SSA format with a single command code

Fig 4.4 Qualified SSA format with a single command code


s

Command codes are used in SSAs for three purposes


x x x

To extend DL/I functionality To simplify programs by reducing the number of DL/I calls For performance improvement resulting from the reduced number of DL/I calls

s s s s s s

To use command codes, code an asterisk in position 9 of the SSA Then code your command codes starting from position 10. When DL/I finds an asterisk in position 9, it knows command codes will follow From position 10 onwards, DL/I considers all characters to be command codes until it encounters a space (for an unqualified SSA) or a left parenthesis (for a qualified SSA) It is unusual to use more than one command code in a single SSA A basic unqualified SSA with a single variable command code is shown below

01 UNQUALIFIED-SSA. * 05 UNQUAL-SSA-SEGMENT-NAME PIC X(8). 05 FILLER PIC X VALUE *. 05 UNQUAL-SSA-COMMAND-CODE PIC X. 05 FILLER PIC X VALUE SPACE. *

Command Code C D F L N P Q U V

Meaning Concatenated Key Path Call First Occurrence Last Occurrence Path Call Ignore Set Parentage Enqueue Segment Maintain position at this level Maintain position at this and all superior levels Null command codes

s s s s

Value is a hyphen () Although command code position is present, DL/I ignores it Particularly useful if you would like to use the same SSA with and without command codes An SSA with the null command code is shown below

The Null Command Code

01 UNQUALIFIED-SSA. * 05 UNQUAL-SSA-SEGMENT-NAME PIC X(8). 05 FILLER PIC X VALUE *. 05 UNQUAL-SSA-COMMAND-CODE PIC X VALUE -. 05 FILLER PIC X VALUE SPACE. *

Multiple Qualifications
s

There are two cases in which you would use multiple qualification
x x

When you want to process a segment based on the contents of two or more fields within it When you want to process a segment based on a range of possible values for a single field

s s s s

To use multiple qualification, you connect two or more qualification statements (a field name, a relational operator, and a comparison value) within the parentheses of the SSA. To connect them, you use the Boolean operators AND and OR Either of the two symbols shown in the table below may be used for AND or OR The independent AND operator is used for special operations with secondary indexes and will be discussed later

01 VENDOR-SSA. * 05 FILLER PIC X(9) VALUE INVENSEG(. 05 FILLER PIC X(10) VALUE INVENCOD>=. 05 VENDOR-SSA-LOW-CODE PIC X(3). 05 FILLER PIC X VALUE &. 05 FILLER PIC X(10) VALUE INVENCOD<=. 05 VENDOR-SSA-HIGH-CODE PIC X(3). 05 FILLER PIC X VALUE ).
s

The above SSA, which uses multiple qualifications can be used to retrieve vendor segments whose vendor codes fall within a certain range
x

The first qualification statement specifies that the vendor code field must be greater than or equal to a particular value; that is the low end of the range The second qualification statement specifies that the vendor code field must be less than or equal to a particular value; that is the high end of the range To retrieve segments that fall within this range, you would first move values for low and high ends of the range to VENDOR-SSA- LOW-CODE and VENDOR-SSA- HIGH-CODE Then you would execute GN calls that include VENDOR-SSA

s s s s s s

The GU Call The GN Call The GNP Call Status Codes Expected during Sequential Processing Using Command Codes with Retrieval Calls Multiple Processing

Module 5 Retrieving Data from a Database

s s

Used for random processing Applications of random processing


x x

The GU Call

When a relatively small number of updates are posted to a large database To establish position in a database for subsequent sequential retrieval

s s

You know what data you want to retrieve and you want to get to it directly Independent of the position established by the previous calls

CALL CBLTDLI USING

DLI-GU INVENTORY-PCB-MASK INVENTORY-STOCK-LOC-SEGMENT VENDOR-SSA ITEM-SSA STOCK-LOCATION-SSA.

s s

A typical GU call like the one above, wherein a complete set of qualified SSAs to retrieve a segment, includes one for each level in the hierarchical path to the segment you want to retrieve is called a fully qualified call Usually, GU processing is based on sequence (key) fields with unique values However, for some applications you may find it necessary to either
x x x

Access a segment whose sequence field allows non-unique values, or, Access a segment based on a field that is not the segments key field In the above cases, DL/I returns the first segment occurrence with the specified search value When you use an unqualified SSA in a GU call, DL/I accesses the first segment occurrence in the database that meets the criteria you specify If you issue a GU call without any SSAs, DL/I returns the first occurrence of the root segment in the database If you omit some SSAs for intermediate levels in a hierarchical path, the action DL/I takes depends on your current position and on the SSAs that are missing

Special considerations for GU calls without a full set of qualified SSAs


x

DL/I either uses the established position or defaults to an unqualified SSA for the segment Recommended style of coding
x

Code a qualified or unqualified SSA for each level in the path from the root segment to the segment you want to retrieve Only two status code values need to be considered spaces and GE Spaces means the call was successful and the requested segment was returned in your programs segment I/O area A GE status code indicates that DL/I couldnt find a segment that met the criteria you specified in the call

Status codes you can expect during random processing with GU calls
x x

CALL CBLTDLI USING DLI-GN INVENTORY-PCB-MASK INVENTORY-STOCK-LOC-SEGMENT STOCK-LOCATION-SSA.


s s

The GN Call

Used for basic sequential processing After any successful database call, your database position is immediately before the next segment occurrence in the normal hierarchical sequence Before your program issues any calls, position is before the root segment of the first database record The GN call moves forward through the database from the position established by the previous call If a GN call is unqualified (that is, if it does not employ an SSA), it returns the next segment occurrence in the database regardless of type, in hierarchical sequence If a GN call includes SSAs qualified or unqualified DL/I retrieves only segments that meet requirements of all SSAs you specify If you include an unqualified SSA or omit an SSA altogether for a segment type, DL/I allows any occurrence of that segment type to satisfy the call But when you specify a qualified SSA, DL/I selects only those segment occurrences that meet the criteria you specify

s s s

CALL CBLTDLI USING DLI-GNP INVENTORY-PCB-MASK INVENTORY-STOCK-LOC-SEGMENT UNQUALIFIED-SSA.


s s

The GNP Call

Used for sequential processing within parentage Works like the GN call, except it retrieves only segments that are subordinate to the currently established parent To establish parentage, your program MUST issue either a GU call or a GN call, and the call must be successful
x

Parentage is never automatically established, in spite of the hierarchical structure of the database

s s s

The segment returned by the call becomes the established parent Subsequent GNP calls return only segment occurrences that are dependent on that parent When there are no more segments within the established parentage DL/I returns GE as the status code

Vendor 1

Item 2 Established Parent Item 1 Loc 2 Loc 1 Established Vendor 1

Loc 5 Loc 4 Loc 3 Loc 2 Loc 1 Item 1

Parent

Item 2

Loc 2 Loc 1

Loc 5 Loc 4 Loc 3 Loc 2 Loc 1

Fig 5.1 Sequential retrieval with GNP call

Status Codes you can expect during Sequential Processing

Using Command Codes with Retrieval Calls


s

The F command code


x

When you issue a call with an SSA that includes the F command code, the call processes the first occurrence of the segment named by the SSA, subject to the calls other qualifications Can be used when you are doing sequential processing and you need to back up in the database, or in other words, the F command code can be used for sequential retrieval using GN and GNP calls Meaningless with GU calls, because GU normally retrieves the first segment occurrence that meets the criteria you specify

The L command code

When you issue a call with an SSA that includes the L command code, the call processes the last occurrence of the segment named by the SSA, subject to the calls other qualifications Used to retrieve more than one segment occurrence using just one call Normally DL/I operates on the lowest level segment you specify in an SSA, but in many cases, you want data not just from the lowest level in the call, but from other levels as well Makes it easy to retrieve an entire path of segments
The usage of the D command code is illustrated below

The D command code


x x

01 VENDOR-SSA. 05 FILLER PIC X(11) VALUE INVENSEG*D(. 05 FILLER PIC X(10) VALUE INVENCOD =. 05 VENDOR-SSA-CODE PIC X(3). 05 FILLER PIC X VALUE ). * 01 ITEM-SSA. 05 FILLER PIC X(11) VALUE INITMSEG*D(. 05 FILLER PIC X(10) VALUE INITMNUM =. 05 ITEM-SSA-NUMBER PIC X(5). 05 FILLER PIC X VALUE ). * 01 LOCATION-SSA. 05 FILLER PIC X(11) VALUE INLOCSEG*D(. 05 FILLER PIC X(10) VALUE INLOCLOC =. 05 LOCATION-SSA-CODE PIC X(3). 05 FILLER PIC X VALUE ). * 01 PATH-CALL-I-O-AREA. 05 INVENTORY-VENDOR-SEGMENT PIC X(131). 05 INVENTORY-ITEM-SEGMENT PIC X(48). 05 INVENTORY-STOCK-LOC-SEGMENT PIC X(21). * ... * CALL CBLTDLI USING DLI-GU INVENTORY-PCB-MASK PATH-CALL-I-O-AREA VENDOR-SSA ITEM-SSA LOCATION-SSA.
s

The C command code


x

x x

If you are developing a program that retrieves just lower-level segment occurrences from a database, you dont have to code separate SSAs for each level in the hierarchical path Instead you can use a single SSA with the C command code Then, rather than coding a field name, relational operator, and search value, you specify the concatenated key for the segment you are interested in An illustration of the use of the C command code is shown below

* 01 LOCATION-SSA. * 05 FILLER PIC X(11) VALUE INLOCSEG*C(. 05 LOCATION-SSA-VENDOR PIC X(3). 05 LOCATION-SSA-ITEM PIC X(5). 05 LOCATION-SSA-LOCATION PIC X(3). 05 FILLER PIC X VALUE ).

* . . . CALL CBLTDLI USING DLI-GU INVENTORY-PCB-MASK INVENTORY-STOCK-LOC-SEGMENT LOCATION-SSA.

The P command code


x

When you issue a GU or GN call, DL/I normally establishes parentage at the lowest level segment that is retrieved However, if you want to override that and cause parentage to be established at a higher-level segment in the hierarchical path, you can use the P command code in its SSA When you use an unqualified SSA that specifies the U command code in a GN call, DL/I restricts the search for the segment you request to dependents of the segments with the U command code Has the same effect as a call which contains a qualified SSA for the current position Is ignored if used with a qualified SSA Effect is same as coding the U command code at that level and all levels above it in the hierarchy Is ignored if used with a qualified SSA This command code is used to enqueue, or reserve for exclusive use, a segment or path of segments You only need to use the Q command code in an interactive environment where there is a chance that another program might make a change to a segment between the time you first access it and the time you are finished with it

The U command code


x

x x

The V command code


x x

The Q command code


x

Multiple Processing
s

Multiple processing is a general term that means a program can have more than one position in a single physical database at the same time DL/I lets the programmer implement multiple processing in two ways
x x

Through multiple PCBs Through multiple positioning The DBA can define multiple PCBs for a single database Then, the program has two (or more) views of the database As with PCBs for different databases, each has its own mask in the Linkage Section and is specified in the ENTRY statement It is up to the programs logic to decide when to use a particular PCB to access the database This method for implementing multiple processing, though flexible, is inefficient because of the overhead imposed by the extra PCBs Lets a program maintain more than one position within a database using a single PCB To do that, DL/I maintains a distinct position for each hierarchical path the program processes Most of the time, multiple positioning is used to access segments of two or more types sequentially at the same time

Multiple PCBs
x x x

x x

Multiple positioning
x x x

A1 Database Record 1

C13 C12 B13 B12 B11 C22 B22 C11 A2 Database Record 2

C21

B21 Fig 5.2 Two database records to illustrate multiple positioning MOVE SEGB TO UNQUAL-SSA-SEGMENT-NAME. CALL CBLTDLI USING DLI-GN SAMPLE-DB-PCB SEGMENT-B-I-O-AREA UNQUALIFIED-SSA. MOVE SEGC TO UNQUAL-SSA-SEGMENT-NAME. CALL CBLTDLI USING DLI-GN SAMPLE-DB-PCB SEGMENT-C-I-O-AREA UNQUALIFIED-SSA.
x x

x x

x x

When you use multiple positioning, DL/I maintains its separate positions based on segment type As a result you include an unqualified SSA in the call that names the segment type whose position you want to use It is the DBA who decides whether single or multiple positioning will be in effect in the programs PSB As a result multiple positioning is not the characteristic of the database but instead, its how DL/I allows a program to view a database The same program can be processed with either single or multiple positioning by different programs The technique a program uses is determined by the programs PSB

s s s s

The ISRT Call The Get Hold Calls The REPL Call The DLET Call

Module 6 Adding and Updating Data in a Database

s s s s

The ISRT call is used to add a segment occurrence to a database, either during update processing of an existing database or during load processing of a new database Before an ISRT call is issued, you should first build the segment occurrence by moving data to the fields of the segment description After formatting the segment, you issue the ISRT call with at least one SSA: an unqualified SSA for the segment type you want to add Consider the example below

The ISRT Call

CALL CBLTDLI USING

DLI-ISRT INVENTORY-PCB-MASK INVENTORY-STOCK-LOC-SEGMENT UNQUALIFIED-SSA.

s s s s

Here UNQUALIFIED-SSA specifies the segment name Because the SSA is unqualified, DL/I tries to satisfy the call based on the current position in the database As a result, you need to be careful about position when you issue an ISRT call that specifies only a single unqualified SSA A safer technique is to specify a qualified SSA for each hierarchical level above the one where you want to insert the segment, as illustrated below

CALL CBLTDLI USING

DLI-ISRT INVENTORY-PCB-MASK INVENTORY-STOCK-LOC-SEGMENT VENDOR-SSA ITEM-SSA UNQUALIFIED-SSA.

If SSAs for vendor and item are initialized with the proper key values, DL/I inserts the new segment occurrence in the correct position in the database When you issue a fully qualified ISRT call like this, DL/I returns a status code of GE if any segment occurrence you specify in an SSA isnt present in the database As a result, you can issue an ISRT call with qualified SSAs instead of first issuing GU calls to find out if higher-level segments in the path are present By issuing one call instead of two (or more), you can save system resources Where inserted segments are stored
x

s s

If the new segment has a unique sequence field, as most segment types do, it is added in its proper sequential position However, some lower-level segment types in some databases have non-unique sequence fields or dont have sequence fields at all When thats the case, where the segment occurrence is added depends on the rules the DBA specifies for the database For a segment without a sequence field, the insert rule determines how the new segment is positioned relative to existing twin segments

If the rule is first, the new segment is added before any existing twins If the rule is last, the new segment is added after all existing twins If the rule is here, it is added at the current position relative to existing twins, which may be first, last, or anywhere in the middle

For a segment with non-unique sequence fields, the rules are similar, but they determine where the new segment is positioned relative to existing twin segments that have the same key value GE When you use multiple SSAs and DL/I cannot satisfy the call with the specified path When you try to add a segment occurrence that is already present in the database For load processing you might get status codes LB, LC, LD or LE.

Status codes you can expect during insert processing


x

x
x

II

In most cases they indicate that you are not inserting segments in exact hierarchical sequence That means there is an error in your program or the files from which you are loading the database contain incorrect data

There are three get hold functions you can specify in a DL/I call:
x x x

The Get Hold Calls

GHU (Get hold unique) GHN (Get hold next), and, GHNP (Get hold next within parent)

s s s

These calls parallel the three retrieval calls earlier discussed Before you can replace or delete a segment, you must declare your intent to do so, by retrieving the segment with one of these three calls Then you must issue the replace or delete call before you do another DL/I processing in your program After you have retrieved a segment with one of the get hold calls, you can make changes to the data in that segment, then issue an REPL call to replace the original segment with the new data There are two restrictions on the changes you can make:
x x

The REPL Call

s s

You cant change the length of the segment You cant change the value of the sequence field (if the segment has one)

s s

Never code a qualified SSA on an REPL call: if you do, the call will fail An example of a typical replace operation is shown below

CALL CBLTDLI USING

DLI-GHU INVENTORY-PCB-MASK INVENTORY-STOCK-LOC-SEGMENT VENDOR-SSA ITEM-SSA LOCATION-SSA.

ADD TRANS-RECEIPT-QTY TO ISLS-QUANTITY-ON-HAND. SUBTRACT TRANS-RECEIPT-QTY FROM ISLS-QUANTITY-ON-ORDER. CALL CBLTDLI USING DLI-REPL INVENTORY-PCB-MASK INVENTORY-STOCK-LOC-SEGMENT.

Status codes you can expect during replace processing


x x

If you try to use a qualified SSA on an REPL call, you will get an AJ status code If your program issues a replace call without an immediately preceding get hold call, DL/I returns a DJ status code If your program makes a change to the segments key field before issuing the REPL call, DL/I returns a DA status code

s s s s

The DLET call works much like REPL You must first issue a get hold call to indicate that you intend to make a change to the segment you are retrieving Then you issue a DLET call to delete the segment occurrence from the database For example, to delete a stock location that is no longer active, youd code a series of statements like the ones below

The DLET Call

CALL CBLTDLI USING

DLI-GHU

INVENTORY-PCB-MASK INVENTORY-STOCK-LOC-SEGMENT VENDOR-SSA ITEM-SSA LOCATION-SSA. CALL CBLTDLI USING DLI-DLET INVENTORY-PCB-MASK INVENTORY-STOCK-LOC-SEGMENT.

s s s

Notice that the DLET call does not include any SSAs There is one important point you must keep in mind whenever you use the DLET call when you delete a segment, you automatically delete all segment occurrences subordinate to it The status codes you might get after a DLET call are the same as those you can get after an REPL call

s s s s s s s s s s s s

The Need for Secondary Indexing A Customer Database Secondary Indexes Secondary Keys Secondary Data Structures DBDGEN Requirements for Secondary Indexes PSBGEN Requirements for Secondary Indexing Indexing a Segment based on a Dependent Segment The Independent AND Operator Sparse Sequencing Duplicate Data Fields

Module 7 Secondary Indexing

s s s

Often you need to be able to access a database in an order other than its primary hierarchical sequence Or, you may need to access a segment in a database directly, without supplying its complete concatenated key With secondary indexing both are possible

The Need for Secondary Indexing

01 LINE-ITEM-SEGMENT. 05 LIS-ITEM-KEY. 10 LIS-ITEM-KEY-VENDOR PIC X(3). 10 LIS-ITEM-KEY-NUMBER PIC X(3). 05 LIS-UNIT-PRICE PIC S9(5)V99 COMP-3. 05 LIS-QUANTITY PIC S9(7) COMP-3.

01 ADJUSTMENT-SEGMENT. 05 AS-REFERENCE-NUMBER 05 AS-ADJUSTMENT-DATE 05 AS-ADJUSTMENT-TYPE 05 AS-ADJUSTMENT-AMOUNT

PIC PIC PIC PIC

X(16). X(6). X. S9(5)V99 COMP-3.

01 05 05 05 05

PAYMENT-SEGMENT. PS-CHECK-NUMBER PS-BANK-NUMBER PS-PAYMENT-DATE PS-PAYMENT-AMOUNT

01 SHIP-TOSEGMENT. 05 STS-SHIPTO-SEQUENCE PIC XX. 05 STS-SHIPTO-NAME PIC X(31). 05 STSADDRESS-LINE-1 PIC X(31). 05 STSADDRESS-LINE-2 PIC X(31). 05 STS-CITY PIC X(18). 05 STS-STATE PIC XX. 05 STS-ZIPCODE PIC X(9).

01 CUSTOMER-SEGMENT. 05 CS-CUSTOMER-NUMBER 05 CS-CUSTOMER-NAME 05 CS-ADDRESS-LINE-1 05 CS-ADDRESS-LINE-2 05 CS-CITY 05 CS-STATE 05 CS-ZIP-CODE

Payment

Fig 7.1 The customer database

01 CUSTOMER-SEGMENT.
PIC PIC PIC PIC X(16). X(25). X(6). S9(5)V99 COMP-3. 01 BUYER-SEGMENT. 05 BS-BUYER-NAME 05 BS-TITLE 05 BS-TELEPHONE

PIC PIC PIC PIC PIC PIC PIC

X(6). X(31). X(31). X(31). X(18). XX. X(9).

Customer

Ship-to

A Customer Database

01 RECEIVABLE-SEGMENT. 05 RS-INVOICE-NUMBER 05 RS-INVOICE-DATE 05 RS-PO-NUMBER 05 RS-PRODUCT-TOTAL 05 RS-CASH-DISCOUNT 05 RS-SALES-TAX 05 RS-FREIGHT 05 RS-BALANCE-DUE 3. PIC X(6). PIC X(6). PIC X(25). PIC S9(5)V99 COMP-3. PIC S9(5)V99 COMP-3. PIC S9(5)V99 COMP-3. PIC S9(5)V99 COMP-3. PIC S9(5)V99 COMP-

Buyer

The Customer Database (contd.)

Adjustment Receivable

Line Item

PIC X(31). PIC X(31). PIC X(10).

05 05 05 05 05 05 05

CS-CUSTOMER-NUMBER CS-CUSTOMER-NAME CS-ADDRESS-LINE-1 CS-ADDRESS-LINE-2 CS-CITY CS-STATE CS-ZIP-CODE

PIC PIC PIC PIC PIC X(18). PIC XX. PIC PIC XX. PIC PIC PIC PIC X(18). PIC PIC

X(6). X(31). X(31). X(31). X(9).

* 01 SHIP-TO-SEGMENT. 05 STS-SHIP-TO-SEQUENCE 05 STS-SHIP-TO-NAME 05 STS-ADDRESS-LINE-1 05 STS-ADDRESS-LINE-2 05 STS-CITY 05 STS-STATE 05 STS-ZIP-CODE * 01 BUYER-SEGMENT. 05 BS-BUYER-NAME 05 BS-TITLE 05 BS-TELEPHONE * 01 RECEIVABLE-SEGMENT. 05 RS-INVOICE-NUMBER 05 RS-INVOICE-DATE 05 RS-PO-NUMBER 05 RS-PRODUCT-TOTAL 05 RS-CASH-DISCOUNT 05 RS-SALES-TAX 05 RS-FREIGHT 05 RS-BALANCE-DUE *

X(31). X(31). X(31). XX. X(9).

PIC X(31). PIC X(31). PIC X(10). PIC PIC X(6). PIC PIC PIC PIC PIC PIC X(6). X(25). S9(5)V99 S9(5)V99 S9(5)V99 S9(5)V99 S9(5)V99 COMP-3. COMP-3. COMP-3. COMP-3. COMP-3.

Fig 7.2 Segment Layouts for the Customer Database (Part 1 of 2) 01 PAYMENT-SEGMENT. 05 PS-CHECK-NUMBER 05 PS-BANK-NUMBER 05 PS-PAYMENT-DATE 05 PS-PAYMENT-AMOUNT * 01 ADJUSTMENT-SEGMENT. 05 AS-REFERENCE-NUMBER 05 AS-ADJUSTMENT-DATE 05 AS-ADJUSTMENT-TYPE 05 AS-ADJUSTMENT-AMOUNT * 01 LINE-ITEM-SEGMENT. 05 LIS-ITEM-KEY. 10 LIS-ITEM-KEY-VENDOR 10 LIS-ITEM-KEY-NUMBER 05 LIS-UNIT-PRICE 05 LIS-QUANTITY * PIC X(16). PIC X(25). PIC X(6). PIC S9(5)V99 COMP-3. PIC PIC PIC PIC X(16). X(6). X. S9(5)V99

COMP-3.

PIC PIC PIC PIC

X(3). X(3). S9(5)V99 S9(7)

COMP-3. COMP-3.

Fig 7.2 Segment Layouts for the Customer Database (Part 2 of 2)

Secondary Indexes

Secondary Index Database Customer Database Customer Invoice number index database Prefix Data Rec. Seg. Addr. Invoice No. Index Pointer Segment

Ship-to

Index Target Segment

Index Source Segment

Buyer

Receivable

Payment

Adjustment

Line Item

Indexed Database
Fig 7.3 Secondary Indexing Example in which the Index Source Segment and the Index Target Segment are the same

Secondary Indexes (contd.)


s s s s s s s

DL/I maintains the alternate sequence by storing pointers to segments of the indexed database in a separate index database A secondary index database has just one segment type, called the index pointer segment The index pointer segment contains two main elements a prefix element and a data element The data element contains the key value from the segment in the indexed database over which the index is built, called the index source segment The prefix part of the index pointer segment contains a pointer to the index target segment the segment that is accessible via the secondary index The index source and target segments need not be the same After a secondary index has been set up, DL/I maintains it automatically as changes are made to the indexed database though the index is transparent to application programs that use it
x

So, even if a program that is not sensitive to a secondary index updates a database record in a way that would affect the index, DL/I automatically updates the index That can also result in performance degradation In practice, the number of secondary indexes for a given database is kept low because each imposes additional processing overhead on DL/I

If multiple access paths are required into the same database, the DBA can define as many different secondary indexes as necessary each stored in a separate index database
x

Secondary Keys
s s s

The field in the index source segment over which the secondary index is built is called the secondary key The secondary key need not be the segments sequence field any field can be used as a secondary key Though usually, a single field within the index source segment is designated as the secondary key for a secondary index, the DBA can combine as many as five fields in the source segment to form the complete secondary key
x

These fields need not even lie adjacent to each other

Secondary key values do not have to be unique

Secondary Data Structures


s s s

A secondary index changes the apparent hierarchical structure of the database The index target segment is presented to your program as if it were a root segment, even if it isnt actually the root segment As a result, the hierarchical sequence of the segments in the path from the index target segment to the root segment is inverted: those segments appear to be subordinate to the index target segment, even though they are actually superior to it The resulting rearrangement of the database structure is called a secondary data structure

Receivable

Ship-to

Payment

Adjustment

Line Item

Customer

Buyer

s s

Secondary data structures dont change the way the database segments are stored on disk
x

Secondary Data Structures (contd.)

They just alter the way DL/I presents those segments to application programs

When you code an application program that processes a database via a secondary index, you must consider how the secondary data structure affects your programs logic

DBDGEN Requirements for Secondary Indexes


s

Because a secondary index relationship involves two databases, two DBDGENs are required one for the indexed database and the other for the secondary index database

DBDGEN Requirements for Secondary Indexes (contd.)

Fig 7.6 DBDGEN output for the Secondary Index Database


s s

In the DBDGEN for the indexed database, an LCHILD macro relates an index target segment to its associated secondary index database In the DBDGEN for the secondary index database, an LCHILD macro relates the index pointer segment to the index target segment

DBDGEN Requirements for Secondary Indexes (contd.)


s s s

ACCESS=INDEX in the DBD macro in Fig 7.6 tells DL/I that an index database is being defined The INDEX parameter of the LCHILD macro in Fig 7.6 specifies the name of the secondary key field CRRECXNO The XDFLD macro in Fig 7.5 supplies a field name (CRRECXNO) that is used to access the database via the secondary key
x x

This key field does not become a part of the segment Instead, its value is derived from up to five fields defined within the segment with FIELD macros

The SRCH parameter defines the field(s) that constitute the secondary index

PSBGEN Requirements for Secondary Indexing


s s s s

Just because a secondary index exists for a database doesnt mean DL/I will automatically use it when one of your programs issues calls for that database You need to be sure that the PSBGEN for the program specifies the proper processing sequence for the database on the PROCSEQ parameter of the PSB macro If it doesnt, processing is done using the normal hierarchical sequence for the database For the PROCSEQ parameter, the DBA codes the DBD name for the secondary index database that will be used

Fig 7.7 PSBGEN Output


s s s

The SENSEG macros in Fig 7.7 reflect the secondary data structure imposed by the secondary index When the PROCSEQ parameter is present, processing is done based on the secondary index sequence If a program needs to access the same indexed database using different processing sequences, the programs PSBGEN will contain more than one PCB macro, each specifying a different value for the PROCSEQ parameter

Indexing a Segment based on a Dependent Segment


Secondary Index Database Customer Database Index Target Segment Customer Prefix Data Invoice number index database Item Index Cust. Seg. No. Pointer Addr. Segment

Ship-to

Buyer

Receivable

Index Source Segment Payment Adjustment Line Item

Indexed Database
Fig 7.8 Secondary Indexing Example in which the Index Source Segment and the Index Target Segment are different
s s

The Index Source Segment and the Index Target Segment need not be the same Some applications require that a particular segment be indexed by a value that is derived from a dependent segment
x x x

In such a case, the Index Target Segment and the Index Source Segment are different For example, in Fig 7.8, you can retrieve customers based on items they have purchased In other words, the SSA for a get call would specify an item number, but the call would retrieve a customer segment Thus, in the example shown in Fig 7.8, it wouldnt be possible to index the buyer segment based on values in the line item segment, because the line item segment isnt dependent on the buyer segment Similarly , you couldnt index the line item segment based in the customer segment, because the customer segment is superior to the line item segment

The only restriction you need to be aware of here is that the Index Source Segment must be a dependent of the Index Target Segment
x

The Independent AND Operator

s s s s s s

When used with secondary indexes, AND ( * or & ) is called the dependent AND operator The independent AND (#) lets you specify qualifications that would be impossible with the dependent AND This operator can be used only for secondary indexes where the index source segment is a dependent of the index target segment Then, you can code an SSA with the independent AND to specify that an occurrence of the target segment be processed based on fields in two or more dependent source segments In contrast, a dependent AND requires that all fields you specify in the SSA be in the same segment occurrence An SSA that uses the independent AND operator is shown below

01 ITEM-SELECTION-SSA. * 05 FILLER PIC 05 FILLER PIC 05 SSA-ITEM-KEY-1 PIC X(8). 05 FILLER PIC 05 FILLER PIC 05 SSA-ITEM-KEY-2 PIC 05 FILLER PIC

X(9) X(10)

VALUE CRCUSSEG(. VALUE CRLINXNO =.

X VALUE #. X(10) VALUE CRLINXNO =. X(8). X VALUE ).

Sparse Sequencing
s s s s s s s

When the DBA implements a secondary index database with sparse sequencing (also called sparse indexing), it is possible to omit some index source segments from the index Sparse sequencing can improve performance when some occurrences of the index source segment must be indexed but others need not be DL/I uses a suppression value, a suppression routine, or both to determine whether a segment should be indexed (either when inserting a new segment or processing an existing one) If the value of the sequence field(s) in the index source segment matches a suppression value specified by the DBA, no index relationship is established (for an insert) or expected (for any other call) The DBA can also specify a suppression routine that DL/I invokes to determine the index status for the segment The suppression routine is a user-written program that evaluates the segment and determines whether or not it should be indexed Note:
x x

When sparse indexing is used, its functions are handled by DL/I You dont need to make special provisions for it in your application program

Duplicate Data Fields


s s s s s

For some applications, it might be desirable to store user data from the index source segment in the index pointer segment When the DBA specifies that some fields are duplicate data fields, this is possible Up to five data fields can be stored in the index database, and DL/I maintains them automatically Duplicate data fields are useful only when the index database is processed as a separate database Note:
x x

Duplicate data fields impose extra DL/I overhead and require extra DASD storage It is the DBAs responsibility to decide whether the advantages of using duplicate data fields outweigh the extra DL/I overhead and DASD storage requirements mentioned above

s s

Necessity of Logical Relationships Physical Databases with Logical Relationships


x x x

Module 8 Logical Databases

Types DBDGENs Programming Considerations Concatenated Segments and Inverted Hierarchies DBDGENs Programming Considerations

Logical Databases
x x x

Necessity of Logical Relationships


s s s s

The basic rule that each segment type can have only one parent, limits the complexity of a physical database Many DL/I applications require a more complex structure that allows a segment to have two parent segment types As a result DL/I allows the DBA to implement logical relationships in which a segment can have both a physical parent and a logical parent Then, new data structures called logical databases can be built around those logical relationships

Logical Relationships
s

A logical relationship is a path between segments that would otherwise be unrelated


x x

Always between two segments Usually in separate databases, but could also be between two segments in the same database

Customer Vendor Ship-to Item

Buyer

Receivable Stock Location

Payment

Adjustment

Line Item

Figure 8.1 The Customer and Inventory Databases without logical relationships DBDGEN code for the Line Item segment in the Customer Database SEGM FIELD FIELD FIELD NAME=CRLINSEG,PARENT=CRRECSEG,BYTES=16 NAME=CRLININO,BYTES=8,START=1,TYPE=C NAME=CRLINPRC,BYTES=4,START=9,TYPE=P NAME=CRLINQTY,BYTES=4,START=13,TYPE=P

DBDGEN code for the Item segment in the Inventory Database SEGM FIELD FIELD FIELD FIELD NAME=INITMSEG,PARENT=INVENSEG,BYTES=48 NAME=(INITMNUM,SEQ),BYTES=5,START=1,TYPE=C NAME=INITMDES,BYTES=35,START=6,TYPE=C NAME=INITMPRC,BYTES=4,START=41,TYPE=P NAME=INITMCST,BYTES=4,START=45,TYPE=P

Figure 8.2 Partial DBDGEN for the Customer and Inventory databases without a logical relationship

Logical Relationship Vendor Customer Logical Parent Ship-to Physical Parent Buyer Receivable Stock Location Line Item Item

Virtual Logical Child Payment Adjustment Line Item Real Logical Child Figure 8.3 The Customer and Inventory Databases with a logical relationship
s

Logical Child Segment


x x

Is the basis of a logical relationship Is a physical data segment, but DL/I looks at it as if it had two parent segments

s s

The physical parent, and The logical parent One logical child segment occurrence has only one logical parent segment occurrence One logical parent segment occurrence can have many logical child segment occurrences
x

Such logical child segment occurrences are called logical twins Occurrences of a logical child segment type that are all subordinate to a single occurrence of the logical parent segment type This segment, called the Virtual Logical Child segment, does not exist physically The kind of relationship the DBA specifies determines the existence of a virtual logical child segment

Logical twins
x

DL/I makes the logical child segment appear to be like an actual physical child segment
x

However, all logical child segments need not be implemented as virtual logical child segments
x

Types of Logical Relationships


s

There are three kinds of logical relationships the DBA can specify
x x x

Unidirectional Bidirectional Virtual Bidirectional Physical Logical connection goes from the logical child to the logical parent and not the other way around Allows access in both directions However, the segment actually exists only in its physical database The logical child in its physical structure and the corresponding virtual logical child are said to be paired Logical child would be physically stored subordinate to both its physical and logical parents To application programs, it appears the same way as a bidirectional virtual logical child Though it introduces redundancy in the databases, it may be desirable for some applications DBDGENs for Physical Databases with Logical Relationships

Unidirectional
x

Bidirectional Virtual
x x x

Bidirectional Physical
x x x

Deciding what kind of logical database to use for a particular situation is the responsibility of the DBA

DBDGEN code for the real logical child segment (the Line Item segment CRLINSEG) in the Customer database (CRDBD)
SEGM NAME=CRLINSEG, PARENT=((CRRECSEG,DBLE),(INITMSEG,V,INDBD)), POINTER=(TWIN,LTWIN),RULES=(LLV,LAST) ,BYTES=16 FIELD NAME=CRLININO,BYTES=8,START=1,TYPE=C FIELD NAME=CRLINPRC,BYTES=4,START=9,TYPE=P FIELD NAME=CRLINQTY,BYTES=4,START=13,TYPE=P

DBDGEN code for the logical parent segment (the Item segment INITMSEG) and the virtual logical child segment (the Line Item segment INLINSEG) in the Inventory database (INDBD)
SEGM NAME=INITMSEG,PARENT=INVENSEG,BYTES=48 LCHILD NAME=(CRLINSEG,CRDBD),POINTER=DBLE,PAIR=INLINSEG, RULES=LAST FIELD NAME=(INITMNUM,SEQ),BYTES=5,START=1,TYPE=C FIELD NAME=INITMDES,BYTES=35,START=6,TYPE=C FIELD NAME=INITMPRC,BYTES=4,START=41,TYPE=P FIELD NAME=INITMCST,BYTES=4,START=45,TYPE=P SEGM NAME=INLINSEG,PARENT=INITMSEG,POINTER=PAIRED, SOURCE=(CRLINSEG,D,CRDBD)

Figure 8.4 Partial DBDGEN code for the Customer and Inventory databases with a logical relationship
s

To implement a logical relationship, the DBA has to specify it in the DBDGENs for the involved physical databases

DBDGENs for Physical Databases with Logical Relationships (contd.)


s

In the DBDGEN code for the Customer database, two parent segments have been specified for the Line Item segment
x x

The first is its physical parent CRRECSEG The second is its logical parent INITMSEG

Because INITMSEG is in another database, its DBD is also named

In the DBDGEN code for the Inventory database, INITMSEG is specified as the logical parent of the CRLINSEG segment in the Customer database, CRDBD
x x x

The LCHILD macro is used for this purpose The PAIR parameter indicates that the virtual logical child segment is INLINSEG For a unidirectional relationship, the DBA would have omitted the PAIR parameter

The DBDGEN for the database that contains a logical parent in a bidirectional virtual logical relationship also must contain an SEGM for the virtual logical child segment
x

The SOURCE parameter in this SEGM macro specifies that the data that will appear to be in the virtual logical child will actually be stored in the Line Item segment in the Customer database

Programming Considerations for Physical Databases with Logical Relationships


s s

To process segments involved in a logical relationship, you issue calls just as you would if the segments werent involved in the logical relationship Program specifications will indicate the structure of the database you will be using
x

In some cases, you may not even know that you are processing a segment that is involved in a logical relationship

s s s

However, logical relationships add a new dimension to database programming In cases where two databases are integrated through a logical relationship, changes to one database can affect the other The DBA has to anticipate the results of possible database processing on segments involved in a logical relationship
x

The DBA can control processing by specifying appropriate processing options for involved databases and segments At a finer level, the DBA can specify rules that determine what operations are allowed for segments involved in the logical relationship If a processing rule is violated, you will get a non-blank status code As an application programmer, you dont have to worry about all their ramifications

Program specifications should indicate what processing is allowed


x

The potential problems of updating databases involved in logical relationships are extensive
x

* 01 LINE-ITEM-LOG-CHILD-SEGMENT. * 05 LILCS-DEST-PARENT-CONCAT-KEY. 10 LILCS-DPCK-CUSTOMER-NUMBER PIC X(6). 10 LILCS-DPCK-SHIP-TO-SEQUENCE PIC XX. 10 LILCS-DPCK-INVOICE-NUMBER PIC X(6). 05 LILCS-LINE-ITEM-SEGMENT. 10 LILCS-LIS-ITEM-KEY. 15 LILCS-LIS-ITEM-KEY-VENDOR PIC X(3). 15 LILCS-LIS-ITEM-KEY-NUMBER PIC X(5). 10 LILCS-LIS-UNIT-PRICE PIC S9(5)V99 COMP-3. 10 LILCS-LIS-QUANTITY PIC S9(7) COMP-3.

Figure 8.5 Layout of the Line Item segment when accessed from its logical path
* 01 LINE-ITEM-SEGMENT. * 05 LIS-DEST-PARENT-CONCAT-KEY. 10 LIS-ITEM-KEY-VENDOR PIC X(3). 10 LIS-ITEM-KEY-NUMBER PIC X(5). 05 LIS-UNIT-PRICE PIC S9(5)V99 COMP-3. 05 LIS-QUANTITY PIC S9(7) COMP-3.

Figure 8.6 Layout of the Line Item Segment when accessed from its physical path

What you do need to know is that the Segment I/O area you use for a logical child segment always begins with the complete concatenated key of the destination parent
x x

This is called the Destination Parent Concatenated Key (DPCK) The destination parent is the parent other than the one from which the logical child was accessed

Although you must always code the DPCK at the start of your Segment I/O area for a logical child, the data that is actually stored in the database doesnt necessarily include the DPCK
x

Whether it does or not depends on how the DBA defined the segment

s s s s s

Using logical relationships when you process physical databases is useful, but limiting In many application programs, the DBA defines logical databases, which is a single structure based on logical relationships specified in the physical databases The logical database is not a separate entity, though it appears to the application programmer to be so The logical database is instead, an alternative view of one or more physical databases To create a logical database, the DBA has to perform the DBDGEN process
x

Logical Databases

For each physical database that will be involved in the logical structure, with all segments involved in the logical relationship so indicated For the logical database itself

s s

Then, PSBs for programs that will use the logical database have to be created Just as with PSBs that specify physical databases, a PSB that specifies a logical database can selectively present parts of it.

Concatenated Segments and Inverted Hierarchies

A logical database usually has two peculiarities


x

A logical database usually contains a Concatenated Segment


x

A concatenated segment is a single segment type in the logical database, but DL/I builds it by combining a logical child segment with one of its destination parents

In a logical database, segment types from more than one physical database can be combined into a single hierarchical structure, even if they arent directly involved in a logical relationship
x x

Even segment types from the destination parents database that dont participate directly in the logical relationship are still part of the logical database However, the structure may be changed

In a logical database, the concatenated segment makes the connection between segments that are defined in different physical databases
x

As a result, you can generate two different logical database structures from a single logical relationship, by concatenating both possible destination parent segments with the logical child

Customer Vendor Ship-to Item Buyer Receivable Stock Location

Payment

Adjustment

Line Item

Figure 8.8 A possible logical database using the Customer and Inventory physical databases

DBDGENs for Logical Databases


STMT 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 SOURCE STATEMENT PRINT DBD DATASET * SEGM * SEGM * SEGM * SEGM * SEGM * SEGM * SEGM * SEGM * SEGM NAME=INLOCSEG, PARENT=CRLINSEG, SOURCE=((INLOCSEG,D,INDBD)) NAME=INVENSEG, PARENT=CRLINSEG, SOURCE=((INVENSEG,D,INDBD)) NAME=CRLINSEG, PARENT=CRRECSEG, SOURCE=((CRLINSEG,D,CRDBD),(INITMSEG,D,INDBD)) NAME=CRADJSEG, PARENT=CRRECSEG, SOURCE=((CRADJSEG,D,CRDBD)) NAME=CRPAYSEG, PARENT=CRRECSEG, SOURCE=((CRPAYSEG,D,CRDBD)) NAME=CRRECSEG, PARENT=CRSHPSEG, SOURCE=((CRRECSEG,D,CRDBD)) NAME=CRBUYSEG, PARENT=CRSHPSEG, SOURCE=((CRBUYSEG,D,CRDBD)) NAME=CRSHPSEG, PARENT=CRCSTSEG, SOURCE=((CRSHPSEG,D,CRDBD)) NAME=CRCSTSEG, PARENT=0, SOURCE=((CRCSTSEG,D,CRDBD)) NOGEN NAME=LICRDBD,ACCESS=LOGICAL LOGICAL

22 301 302

DBDGEN FINISH END

Figure 8.9 DBDGEN output for the customer inventory logical database
s

In the DBDGEN for a logical database, all of the segment types the DBA names must have already been defined in a physical database DBDGEN
x

As a result, the DBA doesnt have to describe their sizes or the fields they contain in a logical database DBDGEN Instead, the SEGM macro in a logical database DBDGEN specifies the SOURCE parameter to identify the related physical database segment and the database that it is a part of Its SOURCE parameter specifies that it is actually stored in the physical database CRDBD as the segment CRCSTSEG Although the segment names in this logical database and the associated physical databases are the same, they dont have to be An example of how the DBA specifies a concatenated segment In this case, the segment CRLINSEG will be a concatenation of the physical segment CRLINSEG from CRDBD and the physical segment INITMSEG from INDBD

In Figure 8.9, the segment at the top of the logical data structure is CRCSTSEG
x

Notice the SOURCE parameter in the SEGM macro for CRLINSEG


x x

Notice that subordinate to this concatenated segment are two segment types from the inventory database: INVENSEG and INLOCSEG
x x

Both specify the PARENT=CLINSEG This name refers to CRLINSEG defined as a segment in the logical database, not to CRLINSEG in the customer physical database

Programming Considerations for Logical Databases


Concatenated Segment

Logical Child Segment

Destination Parent Segment

Destination Parent Concatenated Key

Logical Child User Data

Destination Parent User Data

Note: Destination parent concatenated key and the sequence field in the logical child user data may overlap Figure 8.10 Format of a concatenated segment
s s s s

There is no mystery to coding programs that process logical databases You issue DL/I calls against the PCB mask for the database, and you evaluate the PCB status code to determine whether or not the calls were successful When you process a concatenated segment, you need to keep in mind that DL/I presents it to your program as a single segment, although it actually contains data from two segments You process the concatenated segment with a single call, and the I/O area you specify must be properly defined to contain the concatenated segment

01 *

CONCATENATED-SEGMENT. 05 CS-DEST-PARENT-CONCAT-KEY. 10 CS-DPCK-CUSTOMER-NUMBER 10 CS-DPCK-SHIP-TO-SEQUENCE 10 CS-DPCK-INVOICE-NUMBER CS-LINE-ITEM-SEGMENT. 10 CS-LIS-ITEM-KEY. 15 CS-LIS-ITEM-KEY-VENDOR 15 CS-LIS-ITEM-KEY-NUMBER 10 CS-LIS-UNIT-PRICE 10 CS-LIS-QUANTITY CS-RECEIVABLE-SEGMENT. 10 CS-RS-INVOICE-NUMBER 10 CS-RS-INVOICE-DATE 10 CS-RS-PO-NUMBER 10 CS-RS-PRODUCT-TOTAL 10 CS-RS-CASH-DISCOUNT 10 CS-RS-SALES-TAX 10 CS-RS-FREIGHT 10 CS-RS-BALANCE-DUE PIC X(6). PIC XX. PIC X(6). PIC PIC PIC PIC PIC PIC PIC PIC PIC PIC PIC PIC X(3). X(5). S9(5)V99 S9(7) X(6). X(6). X(25). S9(5)V99 S9(5)V99 S9(5)V99 S9(5)V99 S9(5)V99

05

COMP-3. COMP-3.

05

COMP-3. COMP-3. COMP-3. COMP-3. COMP-3.

* Format 8.11 Format of the concatenated segment that combines the line item and inventory item segments
s

The concatenated segment consists of two parts, in this order: x x

The logical child segment The destination parent segment The full DPCK, followed by, The logical child user data

The logical child segment consists of two parts


x x

s s

The Segment I/O areas mentioned in DL/I calls must reflect this structure When you work with concatenated segments during update processing, it may be possible to add or change data in both logical child and the destination parent with a single call
x

This also depends on the rules the DBA specified for the database

s s

For an insert, be sure to provide the DPCK in the right position For a replace or delete, dont change the DPCK or sequence field data in either part of the concatenated segment

s s s s

Introduction Abnormal Termination Routines Logging Recovery


x x

Module 9 Recovery and Restart Features

Forward Recovery Backward Recovery Basic Symbolic

Checkpointing
x x

Introduction to Database Recovery

DBAs have to make sure that problems with the system have as little impact on the integrity of the database and the efficiency of operations as possible
x

As a result, the DBA has to devote a lot of attention to planning for database recovery and program restart in the even of failure Failures can be of many kinds, including application abends, system software errors, hardware errors, and power failures

Simple approach to recovery


x x x x

Periodically make backup copies of important datasets From the time the backup copy is made, all transactions posted against the datasets are retained If a dataset is damaged due to a system failure, that problem is corrected Then, accumulated transactions are re-posted to the backup copy to bring it up to date Even in a simple file-based application, this approach can be inappropriate, because it can take a long time to re-post all accumulated transactions Other applications have to wait until the file is restored and work backlog grows Database recovery takes much more time than file recovery, particularly if logical and secondary index relationships are involved

Disadvantages of this approach


x

x x

Abnormal Termination Routines


s

A DL/I program crashes in a way that is different from the way a standard program crashes
x

This is because standard programs are executed directly by the operating system, while DL/I programs are not This is done by employing the abnormal termination routine Makes sure that database datasets are properly closed Cancels the jobs Based on whether you had requested it, the routine produces a storage dump that you can use to find out what caused the abend imitation: Does not insure that data in the databases in use is accurate

When a DL/I program crashes, the system intervenes so that the damage to the database is contained
x

The abnormal termination routine does the following things


x x x

It is usually necessary to back out the changes made by the abending program, correct the error, and rerun the program
x

To do this, a DL/I log is required

Logging
s s s s s s s

DL/I records all the changes a program makes to its databases in a special file called a log When a program changes a segment, DL/I logs both a before image and an after image of it These segment images can be used to restore a database to its proper condition in the even of a program or system failure DL/I uses a technique called write-ahead logging to record database changes With write-ahead logging, a database change is written to the log dataset before it is written to the actual database dataset Because the log is always ahead of the database, the recovery utilities can determine the status of any database change Basic logging operations are transparent to the application programmer
x

When a program executes a call to change a database segment, DL/I takes care of the logging For example, a change made in a segment can cause changes in that segments parent, twins and dependents

Logging often extends beyond the programs view of the database


x

All these changes have to be logged

Changes to segments involved in logical relationships or secondary indexes can cause even more log activity In a complex data structure, even the simplest call to change a segment can cause extensive logging

So, when a DBA plans a database, he has to consider not only the database structure itself, but also the effects that structure will have on logging performance

Recovery- Forward and Backward


s s

When a batch DL/I program abends, two approaches are available for recovering the damaged databases: forward recovery and backward recovery Forward Recovery
x

Change data over a period of time is accumulated, then applied to a copy of the database as it existed before the changes began DL/I uses DL/I logs to store the change data

Backward Recovery (Backout)


x

x x

DL/I uses the database at the time of an application programs failure and reverses all changes made to it since the program began (or since the program issued the last checkpoint) Log records for the program are read backwards and their effects are reversed in the database When the backout is complete, the databases are in the same state they were in before the failure (assuming another application program hasnt altered the database in the meantime)

Forward Recovery

Programs run before change accumulation

Programs run after change accumulation

Fig 9.1 The Forward Recovery Process

Normally used only when a database is physically damaged in some way


x

Example: If a device error makes the current version of a database inaccessible, forward recovery is the technique the operations staff will use to restore it An old copy of the database has to be available All the changes posted to the database since the copy was made must be available

For forward recovery to be an option, two requirements have to be met: x x

To meet the first requirement, the operations staff can periodically run the Database Image Copy Utility (Section 1 of the Fig. 9.1 illustrates this) After the image copy of the database has been made, many application programs can be run that change the database (Section 2 of Figure 9.1 illustrates this)
x x

As the figure indicates, each program writes its own log That meets the second requirement of forward recovery: that all changes made since the previous image copy was taken are saved

Because every execution of a batch DL/I application program produces its own log file, it is efficient to periodically combine them, in case they have to be used to recover the database
x x

The Database Change Accumulation Utility is used for this It consolidates multiple logs and organizes the logged data so that it can be used most efficiently in a recovery operation The output of this program is called an accumulated change log (or change accumulation log) which may be stored either on disk or on tape (Section 3 of Figure 9.1 shows this process)

s s

After the Database Change Accumulation Utility has been run, application programs that change the database are still executed and each one of them writes its own log (Section 4 of Figure 9.1 illustrates this) If something happens to make the database unusable (like a head crash on the DASD that contains the database dataset), it has to be forward recovered The Dataset Recovery Utility is used to restore the database
x

This utility works forward through the changes made to the database and applies them to the original image copy of the database The program accepts logged changes from any combination of DL/I or accumulated change logs Forward Recovery can be an awkward and time consuming process Application is limited to hardware crashes Backward recovery, a simpler process is more appropriate for most situations

Disadvantages
x x x

Backout

Backout is appropriate when an application program ends in a controlled fashion


x

For example, if a program encounters an invalid situation it cant handle, such as an unexpected status code, it can end in such a way as to cause an abend

It can do this by invoking an installation-standard termination routine that records and reports the problem, then abends This is called a pseudo-abend

s s s s s

Then backout can be performed to restore the databases to their previous condition After the application program or input data is corrected, the job can be run again The backout process is carried out by the Batch Backout Utility (named DFSBBO00) Under IMS, a database in use by a batch program that abends can be backward-recovered through dynamic backout If the JCL that invokes the program specifies dynamic backout and the program fails, IMS automatically backs out all database changes made since the program began, or since it issued its last checkpoint - - - - - - - - - - - EXEC PGM=SORT - - - - - - - - - - - EXEC PGM=DFSRRC00, PARM='DLI,GNC230,GNC230,,,,,,,,,,,Y', COND=(0,NE,GNC23005) - - - - - - - - - - - EXEC PGM=DFSRRC00, PARM='DLI,DFSBBO00,GNC230', COND=((0,EQ,GNC23010),EVEN) - - - - - - - - - - - EXEC PGM=SORT, COND=(0,NE) - - - - - - - - - - - EXEC PGM=GNCAJERR, COND=(0,NE) - - - - - - - - - - - -

- - - //GNC23005 - - - //GNC23010 // // - - - //BACKOUT1 // // - - - //GNC23015 // - - - //GNC23020 // - - - -

//GNC23025 // - - - //ABENDCHK // - - - -

EXEC PGM=PSUTDUMP, COND=(0,NE) - - - - - - - - - EXEC PGM=ABENDCHK, COND=((0,EQ,GNC23010),EVEN) - - - - - - - - - -

Fig 9.3 Extract from an actual production proc


s s

In addition, an application program under IMS can invoke dynamic backout by issuing a rollback call (ROLB) There is seldom cause to use ROLB in a typical batch program and only in rare cases will an application programmer be called upon to code such a call

Checkpointing
s

A checkpoint is a point in the execution of a program where the database changes the program has made are considered complete and accurate
x x

Database changes made before the most recent checkpoint are not reversed by backward recovery Database changes logged after the most recent checkpoint are not applied to an image copy of the database during forward recovery

s s s s s s

So, whether backward or forward recovery is used, the database is restored to its condition at the most recent checkpoint when the recovery process completes The default for batch programs is that the checkpoint is the beginning of the program However, in a program that will process many update transactions, it is useful to be able to tell DL/I at intervals, that what has been done so far is okay Then, is the program later abends, there is no need to backout the database changes that have been made upto that point A checkpoint can be established using a checkpoint call (CHKP) The checkpoint call causes a checkpoint record to be written on the DL/I log
x

It is the presence of a checkpoint record in a log that tells the DL/I recovery utilities to stop their recovery processing Basic Checkpointing

Depending on your programs requirements, you can use two different types of checkpointing, namely
x

Lets the programmer issue checkpoint calls that the DL/I recovery utilities use during recovery processing An advanced form of checkpointing that is used in combination with the extended restart facility Together, symbolic checkpointing and extended restart let the application programmer code programs so they can resume processing at the point following a checkpoint

Symbolic Checkpointing

Basic Checkpointing
s s

To use basic checkpointing, a program is coded so that it periodically issues checkpoint calls Frequency of issuing checkpoints
x

x x

In a simple implementation, one checkpoint is issued for every transaction performed, but this method is uncommon Most programs issue checkpoints at intervals like every 100 or 1000 transactions Some applications also issue checkpoints based on elapsed time, perhaps every 10 or 15 minutes

For basic checkpointing, the checkpoint call is coded like this:

CALL

CBLTDLI

USING

DLI-CHKP I-O-PCB-MASK CHECKPOINT-ID.

Here, three parameters are specified


x x x

The CALL function The PCB Name An eight-character working storage field that contains a checkpoint ID

s s s

For the CHKP call under IMS, the programmer supplies the name of a special PCB called the I/O PCB The I/O PCB, normally used for data communication programs, has a format that is different from a database PCB The structure of the I/O PCB mask is like this: 01 * 05 05 FILLER I-O-PCB-STATUS-CODE PIC X(10). PIC XX. I-O-PCB-MASK.

s s s s s s s

The I/O PCB mask must be listed as the first PCB mask on the ENTRY statement in the PROCEDURE DIVISION Instead of the Segment I/O Area, an eight byte checkpoint ID field is used In it, the program places a value that identifies the checkpoint record Then, during recovery, the operations staff can use the checkpoint ID to restart the program, assuming the program is coded to work that way With basic checkpointing, it is easy to keep track of where a program fails and to restore the database back to that point However, picking up the execution of the program at the intermediate point is difficult The program has to provide a facility to accept the checkpoint ID, and then must decide what to do with it
x

Typically this involves reading through any transaction files to skip transactions that were posted before the last checkpoint It may also involve resetting working storage fields (such as total fields) to the values they had when the checkpoint was taken In a database update program that prepares reports and updates non-DL/I datasets, recovery will be very complex However, if a program simply changes a database according to input transactions, recovery will be much simpler As a result, it is practical to limit the function of a database update program that uses checkpointing to database operations; then restart is simpler

Generally, the more functions the program performs, the more complex the considerations are for restart
x

Symbolic Checkpointing
. . . 01 * 05 05 05 * 01 * 05 05 05 05 * 01 * 01 * 01 * 05 05 05 LENGTH-COUNT-FIELDS LENGTH-PRINT-FIELDS LENGTH-LONGEST-SEGMENT PIC S9(5) PIC S9(5) PIC S9(5) COMP COMP COMP VALUE +11. VALUE +9. VALUE +128. LENGTH-FIELDS. RETSTART-WORK-AREA PIC X(12) VALUE SPACE. CHECKPOINT-ID PIC S9(8) VALUE ZERO. PAGE-NUMBER SPACE-CONTROL LINE-COUNT LINES-ON-PAGE PIC PIC PIC PIC S9(5) S9(3) S9(3) S9(3) COMP-3 COMP-3 COMP-3 COMP-3 VALUE VALUE VALUE VALUE +1. +1. +99. +50. PRINT-FIELDS. CASH-RECEIVED VALID-TRANSACTION-COUNT INVALID-TRANSACTION-COUNT PIC S9(7)V99 COMP-3 VALUE ZERO. PIC S9(5) COMP-3 VALUE ZERO. PIC S9(5) COMP-3 VALUE ZERO.

COUNT-FIELDS.

. . . * LINKAGE SECTION. * 01 * 05 05 . . . * PROCEDURE DIVISION. * ENTRY 'DLITCBL' USING I-O-PCB . . . FILLER I-O-PCB-STATUS-CODE PIC X(10). PIC XX. I-O-PCB.

* 000-POST-CASH-RECEIPTS. * CALL USING DLI-XRST I-O-PCB LENGTH-LONGEST-SEGMENT RESTART-WORK-AREA LENGTH-COUNT-FIELDS COUNT-FIELDS LENGTH-PRINT-FIELDS PRINT-FIELDS. IF I-O-PCB-STATUS-CODE NOT = SPACE DISPLAY 'CR1000 I 1 RESTART FAILED -- STATUS CODE ' I-O-PCB-STATUS-CODE ELSE IF RESTART-WORK-AREA NOT = SPACE PERFORM 100-REPOSITION-DATA-BASE. . . . * 230-ISSUE-CHECKPOINT-CALL. * ADD 1 TO CHECKPOINT-ID. CALL 'CBLTDLI' USING DLI-CHKP I-O-PCB LENGTH-LONGEST-SEGMENT CHECKPOINT-ID LENGTH-COUNT-FIELDS COUNT-FIELDS LENGTH-PRINT-FIELDS PRINT-FIELDS. IF I-O-PCB-STATUS-CODE NOT = SPACE DISPLAY 'CR1000 I 2 CHECKPOINT FAILED -- STATUS CODE ' I-O-PCB-STATUS-CODE . . . Symbolic checkpointing is similar to basic checkpointing in that a CHKP call is used to write checkpoint records to a DL/I log 'CBLTDLI'

However, symbolic checkpointing, along with extended restart, provide an advantage: they let the program store program data along with the checkpoint records and retrieve that data when it is necessary to restart the program after a failure While using symbolic checkpointing, the checkpoint call begins with the same three parameters as the basic checkpoint call:
x x x

The CHKP function code The PCB Mask, and, The eight byte checkpoint ID field

s s

After these, the programmer can code upto seven pairs of field names to specify the WORKING-STORAGE areas he wants to have saved along with the checkpoint record In each pair,
x

The first item is the name of a full word binary field, PIC S9(05) COMP, that contains the length of the data area to be saved The second is the name of the data area itself

s s s

A program that uses extended restart should always issue an XRST call before it issues any other DL/I calls On the XRST call, the same working storage fields that are listed in the CHKP call are used During normal execution, the XRST call does nothing
x

It leaves the specified WORKING-STORAGE fields as they are

But when the program is being restarted, DL/I retrieves the values stored in the checkpoint record and restores the specified fields

Illustrative Program
x

Has two data areas (COUNT-FIELDS and PRINT-FIELDS) that are to be saved by the checkpoint calls and restored during restart processing The first two length fields (LENGTH-COUNT-FIELDS and LENGTH-PRINT-FIELDS) correspond to the two data areas that need to be saved and are initialized with the sizes of those areas The third length field, LENGTH-LONGEST-SEGMENT is a PIC S9(5) binary field that contains the length of the longest I/O area the program uses (in other words, the length of the longest segment or path of segments the program processes) DL/I uses this value to acquire a buffer area
As the program executes, it periodically increments the CHECKPOINT-ID field and issues the checkpoint call This call uses the specified areas to be saved on the log along with the checkpoint record If the program fails, the problem that caused the failure is corrected and the affected databases are restored using forward or backward recovery The program is then restarted The operator supplies the last checkpoint ID on the PARM for the EXEC that invokes the program

x x x x x

//GNC890BD PROC //* //****************************************** //GNC890BD EXEC PGM=DFSRRC00, // PARM=(BMP,GNC9030,GNC9030,,,W10028,,,&CHKPTID, // ,,,,&ENV1,AGNALL,,,,,5) //******************************************
x

Then the XRST call, which is the first call in the program, knows the program should restart rather than begin a normal execution Instead of specifying the CHECKPOINT-ID field, the XRST call specifies a 12-byte work area This field named, RESTART-WORK-AREA must be initialized with spaces If the program is being restarted, DL/I places the checkpoint ID value in this field; otherwise DL/I leaves this field blank After these items, the XRST call specifies the length and data fields for any saved data in the same sequence as they appeared in the CHKP call

In the illustrative program, there is one difference between the XRST call and the CHKP call
x x x x

x x

If the program is being restarted, DL/I retrieves the values for those fields from the checkpoint record If not, DL/I doesnt change the values of those fields First, it checks to see if the restart call was successful

After the XRST call, the program checks for two conditions
x

If the status code field in the I/O PCB mask is not spaces, the restart call failed- so an appropriate message is displayed

If the call didnt fail, the program then tests to see if this is a normal execution or a restart execution by checking the restart work area

If that field isnt spaces, the program is being restarted, so a module is invoked to reestablish position in the database

Thank You

You might also like