ims 02.ppt

download ims 02.ppt

of 129

Transcript of ims 02.ppt

  • 7/27/2019 ims 02.ppt

    1/129

    IMS DB

  • 7/27/2019 ims 02.ppt

    2/129

    Objectives

    To create awareness about the IMS DB

    technology and how it is used to

    perform data base operations. Target audience :- people who are

    relatively new to the IMS DB

    Technology.

  • 7/27/2019 ims 02.ppt

    3/129

    Prerequisites

    Knowledge of COBOL

    Basic knowledge of data base management concepts

  • 7/27/2019 ims 02.ppt

    4/129

    Course Outline

    1. An Introduction to DL/I Data Bases

    2. DL/I Programs and Control Blocks

    3. COBOL Basics for Processing a DL/I Data Base

    4. Segment Search Arguments : How to use them

    5. Data retrieval from an IMS Data Base6. Adding and Updating Data to a Data Base

    7. Secondary Indexing

    8. Logical Data Bases

    9. Recovery and Restart

    10. DL/I Data Base Organizations11. Advanced DL/I features

  • 7/27/2019 ims 02.ppt

    5/129

    References

    IMS for the COBOL Programmer

    Part 1: Data base processing with IMS/VS and DL/I

    DOS/VS

    By Steve Eckols IBM Redbooks : IMS Primer

    By Rick Long, Mark Harrington, Robert Hain, Geoff

    Nicholls MVS Quick Ref Ver. 5.5

  • 7/27/2019 ims 02.ppt

    6/129

    Module 1

    An Introduction to DL/I Data

    BasesHierarchical StructuresWhy a Data Base Management System

    Basic DL/I TerminologyBasic DL/I Data Base Processing

  • 7/27/2019 ims 02.ppt

    7/129

    Hierarchical Structures

    In a DL/I data base, data elements are organized in a hierarchical structure.

    Some data elements are dependent on others.

    Fig 1.1 A hierarch ical struc ture

    DL/I sup po rts hierarchies that are dif f icu l t to implement w ith standard f i les.

  • 7/27/2019 ims 02.ppt

    8/129

    Why a data base management system?

    01 VENDOR-RECORD.05 VR-VENDOR-CODE PIC X(3).

    05 VR-VENDOR-NAME PIC X(30).

    05 VR-VENDOR-ADDRESS PIC X(30).

    05 VR-VENDOR-CITY PIC X(17).

    05 VR-VENDOR-STATE PIC XX.

    05 VR-VENDOR-ZIP-CODE PIC X(9).

    05 VR-VENDOR-TELEPHONE PIC X(10).

    05 VR-VENDOR-CONTACT PIC X(30).

    Fig 1.2.a Record layout for the VENDORS data set

    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 data set

    Fig 1.2 Record layouts that illustrate a hierarchical structure

  • 7/27/2019 ims 02.ppt

    9/129

    Basic DL/I Terminology Segment

    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

    Number

    Street

    Name

    City State Country Zip Code

    Fig 1.3 The ADDRESS segment w ith six fields

    Segment Type

    A category of data

    There can be a maximum of 255 segment types and 15 levels in o ne data base

    Segment Occurrence

    One speci f ic segment o f a particu lar type contain ing user data

    Note:-

    Within a data base there is only one of each segment type- its part of the data bases definition-

    but there can be an unl imited number of occ urrences 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 con text

  • 7/27/2019 ims 02.ppt

    10/129

    Basic DL/I Terminology (contd.)*

    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).

    *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.

    *

    Fig 1.5 Segment layouts for the Inventory data base

    Vendor

    Item

    Stock Locat ion

    Fig 1.4 The hierarchical structu re of the Inventory

    data base with three segment types

  • 7/27/2019 ims 02.ppt

    11/129

    Basic DL/I Terminology (contd.)

    Root Segment

    The segment type at the top of a hierarchy Data base record

    Each occurrence of the root segment plus all thesegment occurrences that are subordinate to it

    make up one data base record. Every data base

    record has one and only one root segment,

    although it may have any number of subordinatesegment occurrences

    Data base

    Record 1

    Data base Record

    2

    Vendo r 1

    Item 1

    Item 2

    Loc 5

    Loc 4

    Loc 3

    Loc 2

    Loc 1

    Loc 2

    Loc 1

    Vendo r 2

    Item 1

    Loc 2

    Loc 1

    Fig 1.6 Two data base records from the Inventory data base

  • 7/27/2019 ims 02.ppt

    12/129

    Basic DL/I Terminology (contd.)

    Dependent Segment

    A segment other than the root segment in a data

    base record

    Accessible only through one or more parentsegments

    Parent Segment

    A segment that has one or more dependent

    segments Child Segment

    Every dependent segment in a hierarchy Twin Segment

    Two or more segment occurrences of the same

  • 7/27/2019 ims 02.ppt

    13/129

    Basic DL/I Terminology (contd.)

    Key or Sequence Field

    The field DLI uses to maintain segments in

    ascending sequence

    Only a single field within a segment

    Segments need not necessarily require a key field

    If in a root segment, key field uniquely identifies

    the record

    Additional Search fields

    Used to search through the DB for particular

    values

  • 7/27/2019 ims 02.ppt

    14/129

    Basic DL/I Terminology (contd.) Logical data bases

    Additional relationships within one physical data base

    Fig 1.7 A logical relationship can connect two data bases

    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

    Customer

    Ship-to

    Buyer Receivable

    Payment Adjustment Line ItemStock Locat ion

    Item

    Vendor

  • 7/27/2019 ims 02.ppt

    15/129

    Basic DL/I Data Base Processing Sequential Processing

    Top> Down, Left -> Right

    Position At any point, a program has a position in the data base.

    Position reflects not only on retrieved segments, but on new segments inserted as well

    Data base

    Record 1

    Data base Record 2

    Vendo r 1

    Item 1

    Item 2

    Loc 5

    Loc 4

    Loc 3

    Loc 2

    Loc 1

    Loc 2

    Loc 1

    Vendor 2

    Item 1

    Loc 2

    Loc 1

    Fig 1.8 Sequential proc essing

  • 7/27/2019 ims 02.ppt

    16/129

    Basic DL/I Data Base Processing

    (contd.) Random (Direct) Processing Key (sequence) field required

    Concatenated Key Completely identifies the path from the root segment to the segment you want to

    retrieve.

    Concatenated Key:

    Vendor 2

    Item 1

    Location 1

    Fig 1.9 Random Processing

    Data base

    Record 1

    Data base Record 2

    Vendo r 1

    Item 1

    Item 2

    Loc 5Loc 4

    Loc 3

    Loc 2

    Loc 1

    Loc 2

    Loc 1

    Vendor 2

    Item 1

    Loc 2

    Loc 1

  • 7/27/2019 ims 02.ppt

    17/129

    Module 2

    DL/I Programs and Control BlocksThe IMS Software Environment

    How DL/I relates to your application programs

    Control Blocks

    DBDGEN

    PSBGENIMS Processing Options

    ACB & ACBGEN

    Running an application program under DL/I

  • 7/27/2019 ims 02.ppt

    18/129

    The IMS Software EnvironmentAppl icat ion

    Programs

    IMS Contr ol

    B locks

    DL/I

    OS

    Data Base

    IMS DC Remote

    Terminal

    Fig 2.1 The IMS Software Envir onm ent

  • 7/27/2019 ims 02.ppt

    19/129

    How DL/I relates to

    your application programsAppl icat ion

    Program

    Operating System

    Access Method

    (eg. VSAM)

    File

    Data Set

    Standard File Process ing

    Appl icat ion

    Program

    DL/I Data Base Processing

    DL/I

    Operating Sys tem

    Access Method

    (eg. VSAM)

    Data Base

    Data SetFig 2.2 Standard fi le proc essing c ompared to DL/I data base proc essing

  • 7/27/2019 ims 02.ppt

    20/129

    How DL/I relates

    to your application programs (contd.) Standard file processing

    Standard COBOL statements (like READ / WRITE) invoke theappropriate access method (like VSAM)

    Format of the record as processed by the program should be the sameas the format of the record in the file

    DL/I data base processing

    DLI - Interface between application program and the access method CALL statement to invoke DL/I

    Parameters passed by the CALL tell DL/I what operation to perform

    DL/I invokes a standard access method- usually VSAM- to store database data on disk

    Format of records in a data base data set need not match the layoutsof the segments that make up the data base

    The way the program sees the data base is different from the way theaccess method sees it.

  • 7/27/2019 ims 02.ppt

    21/129

    Control Blocks Physical structure of a DL/I data base isnt specified in an application program

    DL/I uses a set of control blocks(DBDs and PSBs) to define a data bases structure

    Data Base Descriptor (DBD)

    Describes the complete structure of a data base

    A unique DBD for each DL/I data base Program Specification Block (PSB)

    Application programs view of the Database PSB Specifies

    Data bases (one or more) a program can access,

    Data elements a program can see in those data bases

    The processing a program can do with the data elements

    Application programs that have similar data baseprocessing requirements can share a PSB

    Data Base Administrator (DBA) has to create DL/I control blocks

    DBDGEN and PSBGEN Control Statements

  • 7/27/2019 ims 02.ppt

    22/129

    slide)STMT SOURCE STATEMENT1 PRINT NOGEN

    2 DBD NAME=INDBD,ACCESS=HIDAM3 DATASET DD1=IN,DEVICE=33804 **/ 3380 DISK STORAGE5 *6 SEGM NAME=INVENSEG, PARENT=0,POINTER=TB,BYTES=1317 LCHILD NAME=(INPXPNTR,INPXDBD),POINTER=INDX8 FIELD NAME=(INVENCOD,SEQ),BYTES=3,START=1,TYPE=C9 FIELD NAME=INVENNAM,BYTES=30,START=4,TYPE=C10 FIELD NAME=INVENADR,BYTES=30,START=34,TYPE=C11 FIELD NAME=INVENCIT,BYTES=17,START=64,TYPE=C12 FIELD NAME=INVENSTA,BYTES=2,START=81,TYPE=C13 FIELD NAME=INVENZIP,BYTES=9,START=83,TYPE=C14 FIELD NAME=INVENTEL,BYTES=10,START=92,TYPE=C15 FIELD NAME=INVENCON,BYTES=30,START=102,TYPE=C16 *17 SEGM NAME=INITMSEG,PARENT=INVENSEG,BYTES=4818 FIELD NAME=(INITMNUM,SEQ),BYTES=5,START=1,TYPE=C19 FIELD NAME=INITMDES,BYTES=35,START=6,TYPE=C20 FIELD NAME=INITMPRC,BYTES=4,START=41,TYPE=P21 FIELD NAME=INITMCST,BYTES=4,START=45,TYPE=P22 *23 SEGM NAME=INLOCSEG, PARENT=INITMSEG,BYTES=2124 FIELD NAME=(INLOCLOC,SEQ),BYTES=3,START=1,TYPE=C25 FIELD NAME=INLOCONH,BYTES=4,START=4,TYPE=P26 FIELD NAME=INLOCROP,BYTES=4,START=8,TYPE=P27 FIELD NAME=INLOCONO,BYTES=4,START=12,TYPE=P28 FIELD NAME=INLOCDAT,BYTES=6,START=16,TYPE=C29 *30 DBDGEN72 **/**************************************************************************73 **/ RECOMMENDED VSAM DEFINE CLUSTER PARAMETERS74 **/**************************************************************************75 **/* *NOTE276 **/* DEFINE CLUSTER (NAME(IN) NONINDEXED -77 **/* RECORDSIZE (2041,2041) -78 **/* COUNTERINTERVALSIZE (2048))79 **/* *NOTE2 - SHOULD SPECIFY DSNNAME FOR DD IN80 **/**************************************************************************162 **/***********SEQUENCE FIELD*************211 **/***********SEQUENCE FIELD*************325 FINISH

    326 END Fig 2.3 Assembler source listing for the Inventory data base DBDGEN

  • 7/27/2019 ims 02.ppt

    23/129

    SAMPLE DBDGEN (contd.)

    Explanation of Fig 2.3

    First macroDBDidentifies the data base and specifies theDL/I access method

    Second macroDATASET- identifies the file that would containthe data base

    Symbolic name (IN) identifies the data set in the JCL atexecution time

    Segment types are defined using the SEGM macro

    Segment hierarchical relationships are specified by the PARENTparameter on a SEGM macro

    PARENT= 0 or absence of PARENT parameter specifies root segment

    POINTER parameter and LCHILD macro are needed for HIDAMDatabases

    Only search fields need be specified in the DB

  • 7/27/2019 ims 02.ppt

    24/129

    DBDGEN (contd.) FIELD macro defines a field in the DB

    START position of field within segment

    NAME name of the field LENGTH length of the field

    TYPE data type of the field

    FIELD Macro TYPE Codes Data Type

    C Character

    P Packed decim al

    Z Zoned decim al

    X Hexadecimal

    H Half word Binary

    F Ful l word Binary

    SEQ parameter specif ies a sequenc e fieldsegment oc currences are added in sequence by v alues in these f ields

    Fig 2.4 FIELD macro TYPE parameter codes

  • 7/27/2019 ims 02.ppt

    25/129

    SAMPLE PSBGENSTMT SOURCE STATEMENT1 PRINT NOGEN2 PCB TYPE=DB,DBDNAME=INDBD,PROCOPT=LS

    3 SENSEG NAME=INVENSEG4 SENSEG NAME=INITMSEG,PARENT=INVENSEG5 SENSEG NAME=INLOCSEG,PARENT=INITMSEG6 PSBGEN PSBNAME=INLOAD,LANG=COBOL87 END

    Fig 2.5 Assembler source listing for the Inventory data base load programs PSBGEN

    Explanation of Fig 2.5

    PCB (Program Communication Block) refers to one database.

    One PCB macro for each database accessed

    Segment Level Sensitivity A programs access to parts of the data base identified at the segment level

    Within sensitive segments, the program has access to all fields

    Field level sensitivity When the program accesses that segment, only sensitive fields are presented

  • 7/27/2019 ims 02.ppt

    26/129

    PSBGEN (contd.)

    DBDNAME parameter on the PCB macro specifies the name ofthe DBD

    KEYLEN parameter specifies the length of the longestconcatenated key the program can process in the data base

    PROCOPT parameter specifies the programs processing options

    For each PCB macro, subordinate SENSEG macros identify thesensitive segments in the data base

    Names specified in the SENSEG macros must be segment namesfrom the DBDGEN for the data base named in the DBDNAMEparameter of the PCB macro

    PSBGEN macro Indicates that there are no more statements in the PSBGEN job PSBNAME parameter specifies the name to be given to the output PSB module

    LANG parameter specifies the language in which the related application program will bewritten.

  • 7/27/2019 ims 02.ppt

    27/129

    IMS Processing Options

    Indicates to IMS the type of access allowed for a sensitive segment (SENSEG)

    Commonly used Processing Options PROCOPT=G means only read-only access

    PROCOPT=R means read/replace access

    PROCOPT=I means insert access allowed

    PROCOPT=D means Read/Delete access

    PROCOPT=A means all the above options present

    For GSAM DBs PROCOPT=LS for output and GS (Get Sequential) for input

    PROCOPT=L allows a 'load' into the DB. If VSAM DB, it should be empty prior to theload

    The PROCOPT given for a Sensitive segment would override the one given forthe DB

    Example : -PCB TYPE=DB,NAME=LDB42F,PROCOPT=G,

    KEYLEN=200 SENSEG NAME=SEGL4201,

    PARENT=0,PROCOPT=A

    WARNING : Indiscriminate use of PROCOPTS can lead to inexplicable results !

  • 7/27/2019 ims 02.ppt

    28/129

    ACB & ACBGEN

    ACB(Application Control Blocks) : It is created by merging and expanding PSBs and

    DBDs into an IMS internal format when an application program is scheduled for

    execution.

    ACBGEN : The process of building ACB is called Block Building and is done by

    means of ACBGEN.

    IMS can build ACBs either dynamically or it can prebuild them using ACBmaintenance utility.

    ACBs cannot be prebuilt for GSAM DBDs.

    ACBs can be prebuild for PSBs that reference GSAM databases.

    ACBs save instruction, execution and direct-access wait time and improves

    performance in application scheduling. ACBs are maintained in IMS.ACBLIB library.

  • 7/27/2019 ims 02.ppt

    29/129

    Running an application program under

    DL/I Batch program does not access IMS directly

    JCL invokes the DL/I batch initialization module DFSRRC00 which loadsthe application program and the required DL/I modules

    The program and DL/I modules execute together

    Sample JCL :

  • 7/27/2019 ims 02.ppt

    30/129

    //JOBNAME JOB (ACCT),'PGMR NAME',

    // CLASS=J,

    // MSGCLASS=Z,

    // NOTIFY=&SYSUID

    //JOBLIB DD DSN=YOUR.PROGRAM.LOAD.LIBRARY,

    // DISP=SHR

    // DD DSN=YOUR.SYSTEM.RESLIB.LIBRARY,

    // DISP=SHR

    //PROC EXEC PROCNAME, SYMBOLIC PARAMETERS

    //*********************************************************

    //PROCNAME PROC

    //********************************************************

    //* THIS PROC LOADS AN IMS VSAM DATABASE

    //* A PROGRAM 'LOAD' IS USED FOR THIS PURPOSE

    //* THE PSB USED FOR LOADING IS LOADPSB

    //********************************************************

    //LOAD EXEC PGM=DFSRRC00,

    // PARM='DLI,LOAD,LOADPSB'

  • 7/27/2019 ims 02.ppt

    31/129

    SAMPLE JCL (Contd.)

    //DFSRESLB DD DSN=YOUR.DFRESLIB.LIBRARY,

    // DISP=SHR

    //IMS DD DSN=YOUR.DBD.LIBRARY,

    // DISP=SHR

    // DD DSN=YOUR.PSB.LIBRARY,

    // DISP=SHR

    //IMSLOGR DD DSN=YOUR.IMSRLOG.DATASET,

    // DISP=SHR

    //IEFRDER DD DSN=YOUR.IEFRDER.DATASET,

    // DISP=OLD//* DD NAMES ARE AS SPECIFIED IN THE DATABASE

    //DATA DD DSN=VSAMDB.DATA.PART,DISP=SHR

    //INDEX DD DSN=VSAMDB.INDEX.PART,DISP=SHR

    //INPUT DD DSN=FILE.USED.FOR.LOADING,

    // DISP=SHR

    //DFSVSAMP DD DSN=IMSVS.PROCLIB(DFSVSAMP),

    // DISP=SHR

    //CPXMOPTS DD DSN=PARMLIB.LIBRARY(LOAD),

    // DISP=SHR

    //CPXMRPTS DD SYSOUT=*//SYSOUT DD SYSOUT=*

    //SYSPRINT DD SYSOUT=*

    //SYSUDUMP DD SYSOUT=*

    //IMSERR DD SYSOUT=*

    //IMSPRINT DD SYSOUT=*

  • 7/27/2019 ims 02.ppt

    32/129

    Module 3

    COBOL Basics for Processing a

    DL/I Data BaseThe ENTRY and GO BACK Statements

    The DL/I Call

    The PCB Mask

  • 7/27/2019 ims 02.ppt

    33/129

    ENTRY and

    GO BACK StatementsENTRY DLITCBL USING PCB-name1

    [PCB-name2...]

    Fig 3.1 Format of the DL/I ENTRY Statement

    Application program is invoked under the control of the batch initialization module DLITCBL => DL/I to COBOL is the entry point to the program

    DL/I supplies the address of each PCB defined in the programs PSB

    PCBs must be defined in the Linkage Section

    Linkage Section definition of a PCB is called a PCB Mask

    Addressability to PCBs established by listing the PCB Masks on the ENTRYstatement

    PCB masks should be listed on the ENTRY statement in the same sequence as they appear in

    your programs PSBGEN

    GO BACK Statement

    When a program ends, it passes control back to the DL/I

    DL/I reallocates resources and closes the data base data sets

    Use GO BACK and not a STOP RUN statement

  • 7/27/2019 ims 02.ppt

    34/129

    The DL/I Call

    CALL statements are used to request DL/I services

    Parameters you code on the CALL statement specify, among other things, the

    operation you want DL/I to perform

    CALL CBLTDLI USING DLI-functionPCB-mask

    segment-io-area

    [segment-search-argument(s)]

    Fig 3.2 Format of the DL/I call

    CBLTDLI => COBOL to DL/I, is an interface module that is link edited with yourprograms object module

    PLITDLI, ASMTDLI are other options

  • 7/27/2019 ims 02.ppt

    35/129

    The DL/I Call (contd.)

    The DL/I Function

    First parameter coded on any DL/I call

    Four character working storage field containing the function code

    01 DLI-FUNCTIONS.

    05 DLI-GU PIC X(4) VALUE GU .

    05 DLI-GHU PIC X(4) VALUE GHU .

    05 DLI-GN PIC X(4) VALUE GN .

    05 DLI-GHN PIC X(4) VALUE GHN .

    05 DLI-GNP PIC X(4) VALUE GNP .

    05 DLI-GHNP PIC X(4) VALUE GHNP.

    05 DLI-ISRT PIC X(4) VALUE ISRT.05 DLI-DLET PIC X(4) VALUE DLET.

    05 DLI-REPL PIC X(4) VALUE REPL.

    05 DLI-CHKP PIC X(4) VALUE CHKP.

    05 DLI-XRST PIC X(4) VALUE XRST.

    05 DLI-PCB PIC X(4) VALUE PCB .

  • 7/27/2019 ims 02.ppt

    36/129

    The DL/I Call (contd.)

    Get functions First six 05-level items in Fig 3.3

    Used to retrieve segments from a DL/I data base

    GUget unique function causes DL/I to retrieve a specific segment

    occurrence based on field values that you specify GNget next function used to retrieve segment occurrences in

    sequence

    GNPget 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

    U date functions

  • 7/27/2019 ims 02.ppt

    37/129

    The DL/I Call (contd.)

    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

    Function PCB is used in CICS programs

    Function SYNC is used for releasing resources that IMS has locked for the

    program (applicable only in a BMP)

    Function INIT allows an application to receive status codes

    regarding deadlock and data availability (from DB PCBs)

  • 7/27/2019 ims 02.ppt

    38/129

    The DL/I Call (contd.)

    PCB mask

    Second parameter on the DL/I call

    The name of the PCB mask defined in the

    programs Linkage Section ENTRY statement establishes a correspondence

    between PCB masks in the Linkage Section and

    the PCBs within the programs PSB

    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 Segment I/O Area

    Third arameter on the DL I call

  • 7/27/2019 ims 02.ppt

    39/129

    The DL/I Call (contd.)

    Segment search argument

    Optional parameter on the DL/I call

    Identifies the segment occurrence you wish to

    access Multiple SSAs on a single DL/I call

    Two kinds of SSAsunqualified and qualified

    An unqualified SSA Supplies the name of the next segment type that you want to operate on

    If you issue a GN call with an unqualified SSA, DL/I will return the next

    occurrence of the segment type you specify

    A qualified SSA Combines a segment name with additional information that specifies the

  • 7/27/2019 ims 02.ppt

    40/129

    The PCB Mask

    For each data base your program accesses, DL/I maintains an area of storage called

    the program communication block (PCB)

    Masks are defined for those areas of storage in the Linkage Section of your

    program

    01 INVENTORY-PCB-MASK.

    05 IPCB-DBD-NAME PIC X(8).05 IPCB-SEGMENT-LEVEL PIC XX.

    05 IPCB-STATUS-CODE PIC XX.

    05 IPCB-PROC-OPTIONS PIC X(4).

    05 FILLER PIC S9(5) COMP.

    05 IPCB-SEGMENT-NAME PIC X(8).

    05 IPCB-KEY-LENGTH PIC S9(5) COMP.

    05 IPCB-NUMB-SENS-SEGS PIC S9(5) COMP.

    05 IPCB-KEY PIC X(11).

    Fig 3.4 PCB mask for an Inventory data base

  • 7/27/2019 ims 02.ppt

    41/129

    The PCB Mask (contd.)

    Data base name

    The name of the data base being processed Segment level

    Specifies the current segment level in the data

    base

    After a successful call, DL/I stores the level of the

    segment just processed in this field

    Status code

    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

  • 7/27/2019 ims 02.ppt

    42/129

    The PCB Mask (contd.)

    Key length feedback area

    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 Number of sensitive segments

    Contains the number of SENSEG macros

    subordinate to the PCB macro for this data base Key feedback area

    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

  • 7/27/2019 ims 02.ppt

    43/129

    Module 4

    Segment Search ArgumentsTypes of SSAs

    Basic Unqualified SSA

    Basic Qualified SSA

    Command Codes

    The Null Command Code

    Path Call

    Multiple Qualifications

  • 7/27/2019 ims 02.ppt

    44/129

    Types of SSAs

    SSA identifies the segment occurrence you want to access

    It can be either

    Qualified

    Unqualified An unqualified SSA simply names the type of segment you want to use

    A qualified SSA specifies not only the segment type, but also a specific occurrence

    of it

    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 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 data base

  • 7/27/2019 ims 02.ppt

    45/129

    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

    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

    The DL/I uses the value in position 9 to decide what

  • 7/27/2019 ims 02.ppt

    46/129

    Basic Unqualified SSA (contd.)

    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-SEGMENT-NAME

    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

  • 7/27/2019 ims 02.ppt

    47/129

    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

    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

  • 7/27/2019 ims 02.ppt

    48/129

    Basic Qualified SSA (contd.)

    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

    The qualified SSA relational operators are shown

    below(stands for a single blank space)

    Equal to EQ = =

    Not equal to NE

    Greater Than GT > >Greater than or Equal to GE >= =>

    Less Than LT

  • 7/27/2019 ims 02.ppt

    49/129

    Command Codes

    Fig 4.4 Qualified SSA format with a single command code

    Command are used in SSAs for three purposes

    To extend DL/I functionality

    To simplify programs by reducing the number of DL/I

    calls

    Fig 4.3 Unqual i fied SSA format with a single command code

  • 7/27/2019 ims 02.ppt

    50/129

    Command Codes (contd.)

    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.

    *

  • 7/27/2019 ims 02.ppt

    51/129

    Command Codes (contd.)Command Code Meaning

    C Concatenated Key

    D Path Call

    F First Occurr ence

    L Last Occurrence

    N Path Call Ignore

    P Set Parentage

    Q Enqueue Segment

    U Maintain pos it ion at this level

    V Maintain pos it ion at this and all

    super ior levels

    Nul l comm and code

    Fig 4.5 SSA Comm and Codes

  • 7/27/2019 ims 02.ppt

    52/129

    The Null Command Code

    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

    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.*

  • 7/27/2019 ims 02.ppt

    53/129

    Path Call

    A DB call with an SSA that includes the 'D' Command code is a "PATH CALL . Its afacility where in we can retrieve an entire path of the segment

    Consider a sample GU call

    CALL 'CBLTDLI' USING DLI-GU

    INVEN-PCB-MASK

    INVEN-STOCK-LOC-SEG

    VENDOR-SSAITEM-SSA

    STOCK-LOC-SSA

    Normally, DL/I operates on the lowest level segment that is specified in anSSA(STOCK-LOC-SSA in the above E.g.)

    In case if we need data from not just from the lowest level but from other levels as

    well we normally have to give 3 separate GU calls.This will reduce the efficiency ofthe program

    Such a call operates on two or more segments rather than just one segment.

    If a program has to use "Path call" then "P" should be one of the values specifiedin the PROCOPT parameter of the PCB in the programs PSBGEN.

    If path call is not explicitly enabled in the PSBGEN job there will be an 'AM' status

    code.

  • 7/27/2019 ims 02.ppt

    54/129

    Multiple Qualifications There are two cases in which you would use multiple qualification

    When you want to process a segment based on thecontents of two or more fields within it

    When you want to process a segment based on arange of possible values for a single field

    To use multiple qualification, you connect two or more qualification statements (a fieldname, a relational operator, and a comparison value) within the parentheses of theSSA.

    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 indexesand will be discussed later

  • 7/27/2019 ims 02.ppt

    55/129

    Multiple Qualifications (contd.)

    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

  • 7/27/2019 ims 02.ppt

    56/129

    Module 5

    Retrieving Data from a Data BaseThe GU Call

    The GN Call

    The GNP Call

    Status Codes Expected during Sequential Processing

    Using Command Codes with Retrieval Calls

    Multiple Processing

  • 7/27/2019 ims 02.ppt

    57/129

    The GU Call

    Used for random processing

    Applications of random processing

    When a relatively small number of updates are

    posted to a large data base

    To establish position in a data base for subsequent

    sequential retrieval 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.

  • 7/27/2019 ims 02.ppt

    58/129

    The GU Call (contd.) Usually, GU processing is based on sequence (key) fields with unique values

    However, for some applications you may find it necessary to either

    Access a segment whose sequence field allows non-unique values

    Access a segment based on a field that is not thesegments key field

    In the above cases, DL/I returns the first segmentoccurrence with the specified search value

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

    1.When you use an unqualified SSA in a GU call, DL/Iaccesses the first segment occurrence in the database that meets the criteria you specify

    2.If you issue a GU call without any SSAs, DL/I returnsthe first occurrence of the root segment in the database

  • 7/27/2019 ims 02.ppt

    59/129

    The GU Call (contd.)

    Status codes you can expect during random processing with GU calls

    Only two status code values need to be

    consideredspaces and GE

    Spaces means the call was successful and therequested 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 thecall

  • 7/27/2019 ims 02.ppt

    60/129

    The GN Call

    CALL CBLTDLI USING DLI-GNINVENTORY-PCB-MASK

    INVENTORY-STOCK-LOC-SEGMENT

    STOCK-LOCATION-SSA.

    Used for basic sequential processing

    After any successful data base call, your data base position is immediately beforethe next segment occurrence in the normal hierarchical sequence

    Before your program issues any calls, position is before the root segment of thefirst data base record

    The GN call moves forward through the data base from the position established bythe previous call

    If a GN call is unqualified (that is, if it does not employ an SSA), it returns the nextsegment occurrence in the data base regardless of type, in hierarchical sequence

    If a GN call includes SSAsqualified or unqualifiedDL/I retrieves only segmentsthat 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 occurrencesthat meet the criteria ou s ecif

  • 7/27/2019 ims 02.ppt

    61/129

    The GNP Call

    CALL CBLTDLI USING DLI-GNPINVENTORY-PCB-MASK

    INVENTORY-STOCK-LOC-SEGMENT

    UNQUALIFIED-SSA.

    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

    Parentage is never automatically established, in

    spite of the hierarchical structure of the data base 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 returnsGE as the status code

  • 7/27/2019 ims 02.ppt

    62/129

    The GNP Call (contd.)

    Established

    Parent

    Vendo r 1

    Item 1

    Item 2

    Loc 5

    Loc 4

    Loc 3

    Loc 2

    Loc 1

    Loc 2

    Loc 1

    Established

    ParentVendo r 1

    Item 1

    Item 2

    Loc 5

    Loc 4

    Loc 3

    Loc 2

    Loc 1

    Loc 2

    Loc 1Fig 5.1 Sequential retr ieval with GNP call

    Status Codes you can expect during

  • 7/27/2019 ims 02.ppt

    63/129

    Status Codes you can expect during

    Sequential Processing

    Using Command Codes with

  • 7/27/2019 ims 02.ppt

    64/129

    Using Command Codes with

    Retrieval Calls The F command code

    When you issue a call with an SSA that includesthe F command code, the call processes the firstoccurrence 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 GNPcalls

    Meaningless with GU calls, because GU normallyretrieves the first segment occurrence that meets

    the criteria you specify

    Us ng Comman Co es w t

  • 7/27/2019 ims 02.ppt

    65/129

    gRetrieval Calls

    (contd.)

    The usage of the D command code is illustrated below

    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-GUINVENTORY-PCB-MASK

    Us ng Comman Co es w t

  • 7/27/2019 ims 02.ppt

    66/129

    gRetrieval Calls

    (contd.) The C command code

    If you are developing a program that retrieves justlower-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 theconcatenated key for the segment you areinterested in

    An illustration of the use of the C command code

    is shown below

    Us ng Comman Co es w t

  • 7/27/2019 ims 02.ppt

    67/129

    gRetrieval Calls

    (contd.) The P command code

    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 The U command code

    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

    Us ng Comman Co es w t

  • 7/27/2019 ims 02.ppt

    68/129

    gRetrieval Calls

    (contd.) The Q command code

    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 andthe time you are finished with it

  • 7/27/2019 ims 02.ppt

    69/129

    Multiple Processing

    Multiple processing is a general term that means a program can have more thanone position in a single physical data base at the same time

    DL/I lets the programmer implement multiple processing in two ways

    1.Through multiple PCBs

    2.Through multiple positioning Multiple PCBs

    The DBA can define multiple PCBs for a single data

    base

    Then, the program has two (or more) views of the

    data base

    As with PCBs for different data bases, each has its

    own mask in the Linkage Section and is specified

  • 7/27/2019 ims 02.ppt

    70/129

    Multiple Processing (contd.) Multiple positioning

    Lets a program maintain more than one position

    within a data base 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 toaccess segments of two or more types sequentially at

    the same time

    Fig 5.2 Two d ata base records to il lustrate mult iple po sit ion ing

    A1

    B13B12

    B11

    Data base Record 1

    C13C12

    C11

    A2

    B22

    B21

    Data base

    Record 2

    C22

    C21

  • 7/27/2019 ims 02.ppt

    71/129

    Multiple Processing (contd.)

    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.

    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

  • 7/27/2019 ims 02.ppt

    72/129

    Module 6

    Adding and Updating Data

    to a Data BaseThe ISRT Call

    The Get Hold CallsThe REPL Call

    The DLET Call

    Common IMS Status Codes

  • 7/27/2019 ims 02.ppt

    73/129

    The ISRT Call

    The ISRT call is used to add a segment occurrence to a data base, either duringupdate processing of an existing data base or during load processing of a new data

    base

    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: anunqualified SSA for the segment type you want to add

    Consider the example below

    CALL CBLTDLI USING DLI-ISRT

    INVENTORY-PCB-MASK

    INVENTORY-STOCK-LOC-SEGMENTUNQUALIFIED-SSA.

    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 data base

    As a result, you need to be careful about position when you issue an ISRT call that

    specifies only a single unqualified SSA

  • 7/27/2019 ims 02.ppt

    74/129

    The ISRT Call (contd.)

    A safer technique is to specify a qualified SSA for each hierarchical level above theone where you want to insert the segment, as illustrated below

    CALL CBLTDLI USING DLI-ISRT

    INVENTORY-PCB-MASK

    INVENTORY-STOCK-LOC-SEGMENT

    VENDOR-SSAITEM-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 data base

    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 data base

    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

  • 7/27/2019 ims 02.ppt

    75/129

    The ISRT Call (contd.)

    Where inserted segments are stored

    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 data bases have non-unique sequence fields

    or dont have sequence fields at all

    When thats the case, where the segmentoccurrence is added depends on the rules the DBA

    specifies for the data base

    For a segment without a sequence field, the insert

    rule determines how the new se ment is

  • 7/27/2019 ims 02.ppt

    76/129

    The ISRT Call (contd.)

    Status codes you can expect during insert processing

    GEWhen you use multiple SSAs and DL/I

    cannot satisfy the call with the specified path

    I IWhen you try to add a segment occurrence

    that is already present in the data base

    For load processing you might get status codes LB,

    LC, LD or LE.

    In most cases they indicate that you are not inserting segments in exacthierarchical sequence

    That means there is an error in your program or the files from which you

    are loading the data base contain incorrect data

  • 7/27/2019 ims 02.ppt

    77/129

    The Get Hold Calls

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

    1.GHU (Get hold unique)

    2.GHN (Get hold next), and,

    3.GHNP (Get hold next within parent) 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

  • 7/27/2019 ims 02.ppt

    78/129

    The REPL Call

    After you have retrieved a segment with one of the get hold calls, you can makechanges 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:

    1.You cant change the length of the segment

    2.You cant change the value of the sequence field

    (if the segment has one) 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 belowCALL 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

    h ll ( d )

  • 7/27/2019 ims 02.ppt

    79/129

    The REPL Call (contd.)

    Status codes you can expect during replace processing

    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 returnsa DA status code

    h ll

  • 7/27/2019 ims 02.ppt

    80/129

    The DLET Call

    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 data base

    For example, to delete a stock location that is no longer active, youd code a seriesof statements like the ones below

    CALL CBLTDLI USING DLI-GHUINVENTORY-PCB-MASK

    INVENTORY-STOCK-LOC-SEGMENT

    VENDOR-SSA

    ITEM-SSA

    LOCATION-SSA.

    CALL CBLTDLI USING DLI-DLET

    INVENTORY-PCB-MASK

    INVENTORY-STOCK-LOC-SEGMENT.

    Notice that the DLET call does not include any SSAs

    There is one important point you must keep in mind whenever you use the DLETcallwhen you delete a segment, you automatically delete all segmentoccurrences subordinate to it

    The status codes you might get after a DLET call are the same as those you can get

    C S S C d

  • 7/27/2019 ims 02.ppt

    81/129

    Common IMS Status Codes

    Returned by IMS after each DB call

    Field STATUS-CODE X(02)in the PCB-MASK definition Acceptable and unacceptable status codes

    GE record occurrence not found

    GB End of DB reached

    Status codes relate to the type of IMS call

    GHN, GHNP, GHU, GUAB, AK, GE, GB

    AKInvalid field name in SSA

    ISRTAB, AC, AD, AJ, AK, II

    ACSegment not found

    IMS Ab d

  • 7/27/2019 ims 02.ppt

    82/129

    IMS Abends

    U0456 -- PSB stopped

    U0456 -- IMS Compile option DLITCBL not set to Y

    U0458 -- DB Stopped

    U0844 -- DB being updated is full

    S013 -- Error opening the DB

    A few tips on resolving IMS abends:

    Confirm that the Abend is caused by IMScheck the job log for IMS return code

    Check the JCLif modified from another JCL, verify that changes are correct

    Check the SYSOUT dump for IMS diagnostic messages

    Use MVS/QW to get further information on the abend

    S l IMS P

  • 7/27/2019 ims 02.ppt

    83/129

    Sample IMS Program

    IDENTIFICATION DIVISION.PROGRAM-ID. PATGET2.

    ENVIRONMENT DIVISION.

    CONFIGURATION SECTION.

    SOURCE-COMPUTER. IBM-370.

    OBJECT-COMPUTER. IBM-370.

    INPUT-OUTPUT SECTION.

    FILE-CONTROL.

    DATA DIVISION.

    FILE SECTION.

    WORKING-STORAGE SECTION.

    77 TOP-PAGE PIC X VALUE '1'.

    77 GET-UNIQUE PIC X(4) VALUE 'GU'.

    01 HOSPITAL-SSA.

    05 FILLER PIC X(19) VALUE 'HOSPITAL(HOSPNAME ='.

    05 HOSPNAME-SSA PIC X(20).

    05 FILLER PIC X VALUE ')'.

    01 WARD-SSA.

    05 FILLER PIC X(19) VALUE 'WARD (WARDNO ='.

    05 WARDNO-SSA PIC X(04).

    05 FILLER PIC X VALUE ')'.

    01 PATIENT-SSA.

    05 FILLER PIC X(19) VALUE 'PATIENT (PATNAME ='.

    05 PATNAME-SS PIC X(20).

    05 FILLER PIC X VALUE ')'.

    01 UNQUAL-HOSPITAL-SSA PIC X(9) VALUE 'HOSPITAL '.

    01 UNQUAL-WARD-SSA PIC X(9) VALUE 'WARD '.

    01 UNQUAL-PATIENT-SSA PIC X(9) VALUE 'PATIENT '.

    01 WS-ISRT PIC X(4) VALUE 'ISRT'.

    01 WS-GHU PIC X(4) VALUE 'GHU '.

    01 HOSP-I-O-AREA.05 HOSP-NAME PIC X(20).

    S l P ( d )

  • 7/27/2019 ims 02.ppt

    84/129

    Sample Program (contd.)

    01 PATIENT-I-O-AREA.03 PATIENT-NAME PIC X(20).

    03 PATIENT-ADDRESS PIC X(30).

    03 PATIENT-PHONE PIC X(10).

    03 BEDINDENT PIC X(4).

    03 DATEADMT PIC X(8).

    03 PREV-STAY-FLAG PIC X.

    LINKAGE SECTION.

    01 PCB-MASK.

    02 DBD-NAME-1 PIC X(8).

    02 SEG-LEVEL-1 PIC XX.

    02 STATUS-CODE-1 PIC XX.02 PROCESS-OPTIONS-1 PIC X(4).

    02 KEY-LENGTH PIC S9(5) COMP.

    02 SEG-NAME-FDBK-1 PIC X(8).

    02 LENGTH-FB-KEY-1 PIC S9(5) COMP.

    02 NUMB-SENS-SEGS-1 PIC S9(5) COMP.

    02 KEY-FB-AREA-1 PIC X(26).

    PROCEDURE DIVISION.

    ENTRY 'DLITCBL' USING PCB-MASK.

    PERFORM INSERT-HOSP-PARA THRU INSERT-HOSP-EXIT.

    PERFORM INSERT-WARD-01-PARA THRU INSERT-WARD-01-EXIT.

    PERFORM INSERT-PATIENTS-PARA THRU INSERT-PATIENTS-EXIT.

    GOBACK.

    INSERT-HOSP-PARA.

    MOVE 'MACNEAL TO HOSP-NAME.

    MOVE 'ABC DDDD' TO HOSP-ADDRESS.

    MOVE '12345' TO HOSP-PHONE.

    CALL 'CBLTDLI' USING WS-ISRT

    PCB-MASK

    HOSP-I-O-AREA

    UNQUAL-HOSPITAL-SSA.

    S l P ( td )

  • 7/27/2019 ims 02.ppt

    85/129

    Sample Program (contd.)

    IF STATUS-CODE-1 NOT EQUAL SPACESEXIT.

    INSERT-HOSP-EXIT.

    EXIT.

    INSERT-WARD-01-PARA.

    MOVE '01' TO WARD-NO.

    MOVE 10 TO TOT-ROOMS.

    MOVE 20 TO TOT-BEDS.

    MOVE '03' TO BEDAVAIL

    MOVE 'INTENSIVE' TO WARD-TYPE.

    CALL 'CBLTDLI' USING WS-ISRT

    PCB-MASKWARD-I-O-AREA

    UNQUAL-HOSPITAL-SSA

    UNQUAL-WARD-SSA.

    IF STATUS-CODE-1 NOT EQUAL SPACES

    EXIT.

    INSERT-WARD-01-EXIT.

    EXIT.

    INSERT-PATIENTS-PARA.

    MOVE 'MACNEAL' TO WARDNO-SSA.

    MOVE 'JOHN SMITH' TO PATIENT-NAME.

    MOVE '123 HAMILTON STR' TO PATIENT-ADDRESS.

    MOVE '12345 ' TO PATIENT-PHONE.

    MOVE '1111' TO BEDINDENT.

    MOVE '02021999' TO DATEADMT.

    MOVE 'N' TO PREV-STAY-FLAG.

    CALL 'CBLTDLI' USING WS-ISRT

    PCB-MASK

    PATIENT-I-O-AREA

    HOSPITAL-SSA

    WARD-SSA

    UNQUAL-PATIENT-SSA.

  • 7/27/2019 ims 02.ppt

    86/129

    Module 7

    Secondary Indexing

    The Need for Secondary Indexing

    A Customer Data Base

    Secondary Indexes

    Secondary Keys

    Secondary Data Structures

    DBDGEN Requirements for Secondary IndexesPSBGEN Requirements for Secondary Indexing

    Indexing a Segment based on a Dependent Segment

    The Independent AND Operator

    Sparse Sequencing

    Duplicate Data Fields

    Th N d f S d I d i

  • 7/27/2019 ims 02.ppt

    87/129

    The Need for Secondary Indexing

    Often you need to be able to access a data base in an order other than its primaryhierarchical sequence

    Or, you may need to access a segment in a data base directly, without supplying its

    complete concatenated key

    With secondary indexing both are possible

    A C t D t B

  • 7/27/2019 ims 02.ppt

    88/129

    A Customer Data BaseCustomer

    Ship-to

    Buyer Receivable

    Payment Adjustment Line Item

    Fig 7.1 The customer data base

    Th C t D t B ( td )

  • 7/27/2019 ims 02.ppt

    89/129

    The Customer Data Base (contd.)

    01 CUSTOMER-SEGMENT.05 CS-CUSTOMER-NUMBER PIC X(6).

    05 CS-CUSTOMER-NAME PIC X(31).

    05 CS-ADDRESS-LINE-1 PIC X(31).

    05 CS-ADDRESS-LINE-2 PIC X(31).

    05 CS-CITY PIC X(18).

    05 CS-STATE PIC XX.

    05 CS-ZIP-CODE PIC X(9).

    *

    01 SHIP-TO-SEGMENT.05 STS-SHIP-TO-SEQUENCE PIC XX.

    05 STS-SHIP-TO-NAME PIC X(31).

    05 STS-ADDRESS-LINE-1 PIC X(31).

    05 STS-ADDRESS-LINE-2 PIC X(31).

    05 STS-CITY PIC X(18).

    05 STS-STATE PIC XX.

    05 STS-ZIP-CODE PIC X(9).

    *

    01 BUYER-SEGMENT.05 BS-BUYER-NAME PIC X(31).

    05 BS-TITLE PIC X(31).

    05 BS-TELEPHONE PIC X(10).

    *

    01 RECEIVABLE-SEGMENT.

    05 RS-INVOICE-NUMBER PIC X(6).

    05 RS-INVOICE-DATE PIC X(6).

    05 RS-PO-NUMBER PIC X(25).

    05 RS-PRODUCT-TOTAL PIC S9(5)V99 COMP-3.

    - - -

    Th C t D t B ( td )

  • 7/27/2019 ims 02.ppt

    90/129

    The Customer Data Base (contd.)

    01 PAYMENT-SEGMENT.05 PS-CHECK-NUMBER PIC X(16).

    05 PS-BANK-NUMBER PIC X(25).

    05 PS-PAYMENT-DATE PIC X(6).

    05 PS-PAYMENT-AMOUNT PIC S9(5)V99 COMP-3.

    *

    01 ADJUSTMENT-SEGMENT.

    05 AS-REFERENCE-NUMBER PIC X(16).

    05 AS-ADJUSTMENT-DATE PIC X(6).

    05 AS-ADJUSTMENT-TYPE PIC X.05 AS-ADJUSTMENT-AMOUNT PIC S9(5)V99 COMP-3.

    *

    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.

    *

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

    S d I d

  • 7/27/2019 ims 02.ppt

    91/129

    Secondary IndexesCustomer

    Ship-to

    Buyer Receivable

    Payment Adjustment Line Item

    Prefix Data

    Rec. Seg.

    Addr.

    Invoice

    No.

    Index

    PointerSegment

    Invoice number index data base

    Secondary Index

    Data BaseCustomer Data Base

    Indexed Data Base

    Index Target

    SegmentIndex Source

    Segment

    Fig 7.3 Secon dary Indexin g Examp le in which t he Index Sour ce Segment and the Index Target Segment are the same

    Secondary Indexes (contd )

  • 7/27/2019 ims 02.ppt

    92/129

    Secondary Indexes (contd.) DL/I maintains the alternate sequence by storing pointers to segments of the indexed

    data base in a separate index data base

    A secondary index data base has just one segment type, called the index pointersegment

    The index pointer segment contains two main elementsa prefix element and a data

    element

    The data element contains the key value from the segment in the indexed data base

    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

    segmentthe 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 data basethough the index is transparent to application

    programs that use it

    So, even if a program that is not sensitive to a

    secondary index updates a data base record in a way

    that would affect the index, DL/I automatically

    Secondary Indexes (contd )

  • 7/27/2019 ims 02.ppt

    93/129

    Secondary Indexes (contd.)

    If multiple access paths are required into the same data base, the DBA can defineas many different secondary indexes as necessaryeach stored in a separate index

    data base

    In practice, the number of secondary indexes for a

    given data base is kept low because each imposes

    additional processing overhead on DL/I

    Secondary Keys

  • 7/27/2019 ims 02.ppt

    94/129

    Secondary Keys

    The field in the index source segment over which the secondary index is built iscalled the secondary key

    The secondary key need not be the segments sequence fieldany 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

    These fields need not even lie adjacent to each

    other Secondary key values do not have to be unique

    Secondary Data Structures

  • 7/27/2019 ims 02.ppt

    95/129

    Secondary Data Structures A secondary index changes the apparent hierarchical structure of the data base

    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 data base structure is called a secondary data

    structure

    Customer

    Receivable

    Ship-to Payment Adjustment Line Item

    Buyer

    Fig 7.4 Secondary Data Structure for the Second ary Index

    Secondary Data Structures (contd )

  • 7/27/2019 ims 02.ppt

    96/129

    Secondary Data Structures (contd.)

    Secondary data structures dont change the way the data base segments arestored on disk

    They just alter the way DL/I presents those

    segments to application programs

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

    logic

    DBDGEN Requirements for

  • 7/27/2019 ims 02.ppt

    97/129

    Secondary Indexes Because a secondary index relationship involves two data bases, two DBDGENs arerequiredone for the indexed data base and the other for the secondary index data

    base

    Fig 7.5 Part ial DBDGEN outpu t for the custom er data base showing the code to implem ent the secondary index

    DBDGEN Requirements for

  • 7/27/2019 ims 02.ppt

    98/129

    Secondary Indexes (contd.)

    Fig 7.6 DBDGEN output for the Secondary Index Data Base

    In the DBDGEN for the indexed data base, an LCHILD macro relates an index target segment to its

    associated secondary index data base

    In the DBDGEN for the secondary index data base, an LCHILD macro relates the index pointer

    segment to the index target segment

    DBDGEN Requirements for

  • 7/27/2019 ims 02.ppt

    99/129

    Secondary Indexes (contd.) ACCESS=INDEX in the DBD macro in Fig 7.6 tells DL/I that an index data base is

    being defined

    The INDEX parameter of the LCHILD macro in Fig 7.6 specifies the name of the

    secondary key fieldCRRECXNO

    The XDFLD macro in Fig 7.5 supplies a field name (CRRECXNO) that is used to

    access the data base via the secondary key

    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

  • 7/27/2019 ims 02.ppt

    100/129

    Secondary Indexing Just because a secondary index exists for a data base doesnt mean DL/I willautomatically use it when one of your programs issues calls for that data base

    You need to be sure that the PSBGEN for the program specifies the proper processingsequence for the data base on the PROCSEQ parameter of the PSB macro

    If it doesnt, processing is done using the normal hierarchical sequence for the data

    base

    For the PROCSEQ parameter, the DBA codes the DBD name for the secondary index

    data base that will be used

    Fig 7.7 PSBGEN Outp ut

    PSBGEN Requirements for

  • 7/27/2019 ims 02.ppt

    101/129

    Secondary Indexing (contd.) 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 data base 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

  • 7/27/2019 ims 02.ppt

    102/129

    based on a Dependent Segment

    Fig 7.8 Secondary Indexing Ex ample in which the Index Source Segment and th e Index Target

    Segment are different

    Customer

    Ship-to

    Buyer Receivable

    Payment Adjustment Line Item

    Prefix Data

    Cust. Seg.Addr.

    ItemNo.

    IndexPointer

    Segment

    Invoice number index data base

    Secondary Index Data BaseCustomer Data Base

    Indexed Data Base

    Index Target

    Segment

    Index Source

    Segment

    In ex ng a Segmentbased on a Dependent Segment

  • 7/27/2019 ims 02.ppt

    103/129

    based on a Dependent Segment

    (contd.)

    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

    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 acustomer 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

    Thus, in the example shown in Fig 7.8, it wouldnt

    The Independent AND Operator

  • 7/27/2019 ims 02.ppt

    104/129

    The Independent AND Operator

    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 X(9) VALUE CRCUSSEG(.

    05 FILLER PIC X(10) VALUE CRLINXNO =.

    05 SSA-ITEM-KEY-1 PIC X(8).

    05 FILLER PIC X VALUE #.

    05 FILLER PIC X(10) VALUE CRLINXNO =.

    05 SSA-ITEM-KEY-2 PIC X(8).

    05 FILLER PIC X VALUE ).

    Sparse Sequencing

  • 7/27/2019 ims 02.ppt

    105/129

    Sparse Sequencing When the DBA implements a secondary index data base with sparse sequencing (also

    called sparse indexing), it is possible to omit some index source segments from theindex

    Sparse sequencing can improve performance when some occurrences of the indexsource segment must be indexed but others need not be

    DL/I uses a suppression value, a suppression routine, or both to determine whether asegment should be indexed (either when inserting a new segment or processing anexisting one)

    If the value of the sequence field(s) in the index source segment matches a suppressionvalue specified by the DBA, no index relationship is established (for an insert) orexpected (for any other call)

    The DBA can also specify a suppression routine that DL/I invokes to determine the indexstatus for the segment

    The suppression routine is a user-written program that evaluates the segment anddetermines whether or not it should be indexed

    Note:

    When sparse indexing is used, its functions arehandled by DL/I

    You dont need to make special provisions for it in

    Duplicate Data Fields

  • 7/27/2019 ims 02.ppt

    106/129

    Duplicate Data Fields

    For some applications, it might be desirable to store user data from the indexsource 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 data base, and DL/I maintains

    them automatically

    Duplicate data fields are useful only when the index data base is processed as aseparate data base

    Note:

    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

  • 7/27/2019 ims 02.ppt

    107/129

    Module 8

    Logical Data BasesIntroduction to Logical Data Bases

    Logical Data Base Terminology

    DBDGENs for Logical Data Bases

    An Introduction to Logical Data

  • 7/27/2019 ims 02.ppt

    108/129

    Bases

    Inter related databases.

    Inter related databases

    A logica l chi ld s egment has 2 parent segments

    One physical parent and on e log ical parent

    DB1

    DB2

    Logic al Parent

    Physical

    Parent

    Virtual

    Logical Chi ld

    C2

    SEG-1

    LP

    VLC

    Real

    Logical

    Child

    SEG-a SEG-b RLC

    PP

    Logical Data Base Terminology

  • 7/27/2019 ims 02.ppt

    109/129

    Logical Data Base Terminology

    Real Logical Child

    The child under consideration

    Physical Parent

    Original parent of the child

    Logical Parent

    The parent in the other data base

    Virtual Logical Child

    The child as seen from the other data base

    Three types of Logical data bases

    Unidirectional.

    DBDGENs for a Logical Data Base

  • 7/27/2019 ims 02.ppt

    110/129

    DBDGENs for a Logical Data Base

    ******DBD1******

    .

    .

    .

    6 SEGM NAME=RLC,

    7 PARENT=(PP,PTR), (LP,DBD2),

    8 POINTER=(TWIN,LTWIN), RULES=(LLV,LAST),BYTES=16

    9 FIELD NAME=********************************

    10 FIELD NAME=********************************

    .

    .

    .

    ******DBD2*******

    .

    .

    .

    6 SEGM NAME=LP, PARENT=SEG-1, BYTES=48

    7 LCHILD NAME= (RLC,DBD1), POINTER=PTR, PAIR=VLC

    8 FIELD NAME=********************************

    9 FIELD NAME=********************************

    10 FIELD NAME=********************************

  • 7/27/2019 ims 02.ppt

    111/129

    Module 9

    Recovery and RestartIntroduction to Data Base Recovery

    Introduction to Checkpointing

    Types of Checkpointing

    Extended Restart

    Database Image Copy

    Introduction to Data Base Recovery

  • 7/27/2019 ims 02.ppt

    112/129

    Introduction to Data Base Recovery

    The process of recovering the data base in case of application program failure

    Back out changes made by the abended program, correct the error and rerun the

    program.

    Types of recoveries

    Forward recovery

    Backward recovery Forward Recovery

    Data base changes for a time period is

    accumulated A copy of the data base is created

    The changes are applied to this data base copy

    DL/I uses change-data stored in DL/I logs for

    Introduction to Checkpointing

  • 7/27/2019 ims 02.ppt

    113/129

    Introduction to Checkpointing

    Synonyms: synchronization point, sync point, commit point and point of integrity

    Program execution point at which the DB changes are complete and accurate

    DB changes made before the most recent checkpoint are not reversed by recovery

    Normally the start of the pgm is considered as a default checkpoint

    In case of a number of DB updates, explicit checkpoints can be specified

    Explicit checkpoints can be established using checkpoint call(CHKP) inside theprogram

    CHKP creates a checkpoint record on DL/I log which prevents recovery before that

    point

    Types of Checkpointing

  • 7/27/2019 ims 02.ppt

    114/129

    Types of Checkpointing

    Types of checkpointing

    Basic checkpointing

    Symbolic checkpointing Basic checkpointing

    Simple form of checkpointing.

    Issues checkpoint calls that the DL/I recovery

    utilities use during recovery processing Symbolic checkpointing

    More advanced type of checkpointing

    Used in combination with extended restart

    Programs resume from the point following the

    Extended Restart (XRST)

  • 7/27/2019 ims 02.ppt

    115/129

    Extended Restart (XRST)

    The XRST call is used in connection with the symbolic checkpoint call

    It is used to restart your program

    The XRST call precedes a symbolic checkpoint call

    The XRST call must be issued only once

    It should be issued early in the execution of the program

    It must precede any CHKP call The program is restarted from a symbolic CHKP taken during a previous execution

    of the program

    The CHKP used to perform the restart can be identified by entering the checkpoint

    ID

    CHKP ID can be specified in 2 ways

    In the I/O area pointed to by the XRST call

    Specifying ID in the CKPTID= field of EXEC

    statement in the program's JCL

    Database Image Copy

  • 7/27/2019 ims 02.ppt

    116/129

    Database Image Copy

    Job which is run to take backup copies of IMS database datasets at periodicintervals

    Traditionally, batch cycle starts at 7 pm and ends

    at 7 am

    Image Copy jobs are usually run before and after abatch cycle

    If abend occurs, revert to the DB generated by

    image copy job and rerun

    Commonly used image copy utility is BMC

    Softwares ICPUMAIN

    Database and Image copy DD names specified in

    the ICPSYSIN card

  • 7/27/2019 ims 02.ppt

    117/129

    Module 10

    DL/I Data Base OrganizationsDL/I Organizations & Access Methods

    Hierarchical Sequential Organization

    Hierarchical Direct Organization

    Additional IMS Access Methods

    DL/I Organizations & Access

    h d

  • 7/27/2019 ims 02.ppt

    118/129

    Methods

    File Organization is a description of how a file is processed & Access Method is thesoftware used to implement that processing.

    DL/I provides two basic data base organizations :

    Hierarchic Sequential: In this the segments that

    make up the database record are related to one

    another by their physical locations.

    Hierarchic Direct : In this the segment occurrences

    include prefixes that contain direct pointers to

    related segments.

    Hierarchic Sequential Organizations

    h d

  • 7/27/2019 ims 02.ppt

    119/129

    Access Methods

    HS Organizations provide four types of Access Methods

    HSAM ( Hierarchic Sequential Access Method) :

    The program in HSAM database works through it

    sequentially from beginning to end.The

    application programs cannot replace or deletesegments without copying the entire database.

    HISAM (Hierarchic Indexed Sequential Access

    Method): In HISAM the data is stored with

    hierarchic sequential organization. An index is also

    maintained to allow random access to any

    database record.

    SHSAM( Simple Hierarchical Sequential Access

    Hierarchic Direct Organization

    A M h d

  • 7/27/2019 ims 02.ppt

    120/129

    Access Method

    HDAM ( Hierarchic Direct Access Method ):

    HDAM stores root segment occurrences based on

    a randomizing routine.

    Occurrences of dependent segments are related

    to root and one another by a system of pointers

    the HD Organization is based upon.

    HDAM databases are not appropriate for

    sequential processing.

    HIDAM (Hierarchic Indexed Direct Access Method) :

    Segment data in HIDAM is stored in the same way

    like that in HDAM

    Additional IMS Access Methods

  • 7/27/2019 ims 02.ppt

    121/129

    Additional IMS Access Methods

    GSAM( Generalized Sequential Access Methods):

    GSAM lets application files to be treat OS

    sequential files as databases.

    Data is processed on a record to record to basis

    but through DL/I calls.

    Processing of database is sequential , ISRT add

    data only at the end of database & REPL and DLET

    calls are not supported. They are typically used during conversion from a

    system that uses standard files to one that uses

    data bases.

    Additional IMS Access Methods

    ( d )

  • 7/27/2019 ims 02.ppt

    122/129

    (contd..)

    DEDB( Data Entry Data Base ) :

    DEBD is stored in disk and has a hierarchical

    structure

    They are organized in typical DL/I fashion, as

    direct dependent segment types.

    DEBDs use a complicated storage scheme that

    involves separating the data base into as many as

    240 areas and this allows very large data bases.

  • 7/27/2019 ims 02.ppt

    123/129

    Module 11

    Advanced DL/I featuresVariable Length Segments

    DBD for GSAMs

    PCB for GSAMs

    Variable Length Segments

  • 7/27/2019 ims 02.ppt

    124/129

    g g

    When a field length that is stored in a segment type varies, for exampleDescription or Explanatory text, then we define those fields as variable length

    fields

    The segment with such a field defined in it is called Variable Length Segment

    For description and explanatory fields, if we define them long enough to

    accommodate the longest possible text, then a lot of space is wasted in cases

    where it contains shorter strings.

    The SEGM macro in DBD is defined as

    SEGM NAME=INVENSEG,PARENT=0,POINTER=TR,BYTES=m,n

    m=maximum length of the segment + 2 bytes

    n=minimum length of the segment + 2 bytes

    The extra two bytes is used to store the length field of the occurrence of thevariable length segment

    In Application Program :

    The length field has to be included in the I-O Area

    for the segment Length PIC S 9(4)

    Variable Length Segments (contd.)

  • 7/27/2019 ims 02.ppt

    125/129

    g g ( )

    Variable Length Segments are appropriate when segment occurrence length varybut once created and made stabilized.

    Disadvantage:

    If the occurrence of the segment type grows inlength then Variable length segment will drop

    performance

    When segment type occurrences grow in size then

    it split's into 2 parts which are not stored in the

    same physical record, so we require two I/O

    operations to fetch the segment therefore the

    DBD for GSAMs

  • 7/27/2019 ims 02.ppt

    126/129

    During DBD generation for a GSAM database we should specify one dataset group The DD name of the input dataset that is used when the application retrieves data

    from the database

    The DD name of the output dataset used when loading the database.

    The DBD for a GSAM is shown belowDBD NAME=CARDS,ACCESS=(GSAM,BSAM)

    DATASET D1=ICARDS,DD2=OCARDS,RECFM=F,RECORD=80

    DBDGEN

    FINISH

    END

    In GSAM DBD's you can't specify

    SEGM and FIELD statements

    The use of logical or index relationships between

    segments IMS adds 2 b tes to the record len th value s ecified in the DBD in order to

    DBD for GSAMs (contd.)

  • 7/27/2019 ims 02.ppt

    127/129

    ( )

    Whenever the database is GSAM/BSAM and the records are variable (V or VB), IMSadds 2 bytes.

    The record size of the GSAM database is 2 bytes greater than the longest segment

    that is passed to IMS by the application program.

    A database if defined as GSAM has the advantage of the usage of CHECKPOINT and

    RESTART

    Disadvantage of GSAM database : Only inserts can be done to the DB which is

    defined as GSAM, no delete operation can be performed on GSAM Database.

    PCB for GSAMs

  • 7/27/2019 ims 02.ppt

    128/129

    The PCB for a GSAM database is coded as shown belowPCB TYPE=GSAM,DBDNAME=REPORT,PROCOPT=LS

    The GSAM PCB statement must follow the PCB statements with TYPE=TP or DB if

    any exist in the PSB generation, the rule is:

    TP PCBs First

    DB PCBs Second

    GSAM PCBs Last A sample PSB is shown below

    PCB TYPE=TP,NAME=OUTPUT1

    PCB TYPE=DB,DBDNAME=PARTMSTR,PROCOPT=A,KEYLEN=100

    SENSEG NAME=PARTMAST,PARENT=0,PROCOPT=A

    SENSEG NAME=CPWS,PARENT=PARTMAST,PROCOPT=A

    PCB TYPE=GSAM,DBDNAME=REPORT,PROCOPT=LS

    PSBGEN LANG=COBOL,PSBNAME=APPLPGM3

    END

  • 7/27/2019 ims 02.ppt

    129/129

    Thank You