COBOL Programming For IMS
COBOL Programming For IMS
I I
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. nowledge of !"B"# Basic $nowledge of database management systems %n Introduction to D#&I Databases %n Introduction to D#&I 'rograms and !ontrol Bloc$s !"B"# Basics for 'rocessing a D#&I Database (sing Segment Search %rguments )etrieving Data from a Database %dding and (pdating Data in a Database Secondary Inde*ing #ogical Databases )ecovery and )estart +eatures
Prerequisites
I I
Course Outline
I I I I I I I I I
References
I
IMS for the COBOL Programmer Part 1: Database processing with IMS/VS and DL/I DOS/VS
B Ste!e "c#o$s
IBM IMS Primer B %ic# Long& Mar# 'arrington& %obert 'ain& (eoff )icho$$s
,ierarchical Structures -hy a Database Management System Basic D#&I Terminology Basic D#&I Database 'rocessing
#ierarchical Structures
I I I
In a D#&I database, data elements are organi.ed in a hierarchical structure. Some data elements are dependent on others. D#&I supports hierarchies that are difficult to implement with standard files.
*ig 1+,+a %ecord $a o-t for the V")DO%S dataset 01 INVENTORY-RECORD. 05 IR-ITEM-KEY. 10 IR-VENDOR-CODE PIC X(3). 10 IR-NUM ER PIC X(5). 05 IR-DESCRIPTION PIC X(35). 05 IR-UNIT-PRICE PIC S9(5)V99 COMP-3. 05 IR-AV!-UNIT-COST PIC S9(5)V99 COMP-3. 05 IR-LOCATION-"UANTITY-DATA OCCURS #0 TIMES. 10 IR-LOCATION PIC X(3). 10 IR-"UANTITY-ON-HAND PIC S9(7) COMP-3. 10 IR-REORDER-POINT PIC S9(7) COMP-3. 10 IR-"UANTITY-ON-ORDER PIC S9(7) COMP-3. 10 IR-LAST-REORDER-DATE PIC X($). *ig 1+,+b %ecord $a o-t for the In!entor Master dataset *ig 1+, %ecord $a o-ts that i$$-strate a hierarchica$ str-ct-re
Segment
N N N
% grouping of data The unit of data that D#&I transfers to and from your program in an I&" operation. !onsists of one or more fields ADDRESS House Street Number Name City State Country Zip Code
*ig 1+. /he 0DD%"SS segment with si1 fie$ds Segment Type
 
Note:-
% category of data There can be a ma*imum of /00 segment types and 10 levels in one database "ne specific segment of a particular type containing user data
Segment Occurrence
-ithin a database there is only one of each segment type2 its part of the databases definition2 but there can be an unlimited number of occurrences of each segment type. The word 3segment is used to mean either 3segment type or 3segment occurrence and usually the meaning is clear from the conte*t
Vendor
tem
Stoc! "ocation
*ig 1+2 /he hierarchica$ str-ct-re of the In!entor database with three segment t pes * 01 INVENTORY-VENDOR-SE!MENT. 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-SE!MENT. 05 IIS-NUM ER PIC X(5). 05 IIS-DESCRIPTION PIC X(35). 05 IIS-UNIT-PRICE PIC S9(5)V99 COMP-3. 05 IIS-AV!-UNIT-COST PIC S9(5)V99 COMP-3. * 01 INVENTORY-STOCK-LOC-SE!MENT. 05 ISLS-LOCATION PIC X(3). 05 ISLS-"UANTITY-ON-HAND PIC S9(7) COMP-3. 05 ISLS-REORDER-POINT PIC S9(7) COMP-3. 05 ISLS-"UANTITY-ON-ORDER PIC S9(7) COMP-3. 05 ISLS-LAST-REORDER-DAT PIC X($).
*
Root Segment
N
The segment type at the top of a hierarchy 4ach occurrence of the root segment plus all the segment occurrences that are subordinate to it ma$e up one database record 4very database record has one and only one root segment, although it may have any number of subordinate segment occurrences
Database record
N
Vendor #
Vendor $
tem $ tem #
tem #
Database Record $
"oc $ "oc #
"oc $ "oc #
Dependent Segments
N N
%ll of the segments in a database record other than the root segment They depend on one or more segments for their complete meaning % segment that has one or more dependent segments 4very 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 5the root segment occurrence6 down to any specific segment occurrence Must be continuous2 you cant s$ip intermediate levels
(arent Segment
N
C)i*d Segment
N
T+in Segment
N
(at)
N
"ogica* databases
N
%lthough D#&I doesnt support multiple parent relationships in physical databases, it does let you define logical databases 5or create additional relationships within one physical database6
Customer
S)ip-to
Vendor
,uyer
Recei-ab*e
tem
(ayment
Ad.ustment
"ine tem
Stoc! "ocation
In +ig 1.7, the line item segment is the logical child segment 5or 8ust logical child6 of the item segment. #i$ewise, the item segment is the logical parent segment 5or 8ust logical parent6 of the line item segment
Se/uentia* (rocessing
N
-hen you retrieve segments from a database se9uentially, D#&I follows a predictable pattern: down the hierarchy, then right.
(osition
 
%t any point, a program has a position in the database. 'osition can affect not only how segments are retrieved, but how new segments are inserted as well
Vendor #
Vendor $
tem $ tem #
tem #
Database Record $
"oc $ "oc #
"oc $ "oc #
Many applications re9uire that a database be processed randomly rather than se9uentially Segments that you need to access randomly normally contain a $ey field 5or se9uence field6
Concatenated 2ey  !ompletely identifies the path from the root segment to the segment you want to retrieve.
Vendor #
Vendor $
tem $ tem # "oc $ Database Record # "oc % "oc & "oc ' "oc $ "oc #
*ig 1+8 %andom Processing
tem #
Database Record $
"oc $ "oc #
"oc #
The IMS Software 4nvironment ,ow D#&I relates to your application programs !ontrol Bloc$s DBD;4< 'SB;4< ,ow to run an application program that uses D#&I
3S Contro* ,*oc!s
3S DC
Remote Termina*
D"4
OS
Database
Fig 2.1 The IMS Software Environment
App*ication (rogram
App*ication (rogram
D"4
7i*e Dataset
*ig ,+, Standard fi$e processing compared to DL/I database processing
Database Dataset
%pplication programs issue standard !"B"# statements li$e )4%D and -)IT4 These statements invo$e the appropriate access method, li$e =S%M 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 dis$ D#&I acts as an interface between an application program and the access method To perform an operation on a D#&I database, a program doesnt issue a standard !"B"# file I&" statement Instead it e*ecutes a !%## statement to invo$e D#&I The parameters passed by the call tell D#&I what operation to perform Then D#&I, not the application program, invo$es the access method D#&I uses a standard access method2 usually =S%M2 to store database data on dis$ In fact, the access method doesnt $now that a particular dataset contains a database instead of a standard file +ormat of records in a database dataset probably doesnt match the layouts of the segments that ma$e up the database %s a result, the way the program sees the database differs from the way the access method sees.
N N N N N
Control Bloc,s
I I I I
The physical structure of a D#&I database isnt specified in application programs Instead, D#&I uses a set of control bloc$s to define a databases structure In particular, D#&I uses two types of control bloc$s: DBDs and 'SBs
Database Description 0D,D1
N N
Describes the complete structure of a database %n installation must create one DBD for each D#&I database %lthough 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
  
The databases 5one or more6 a program can access, The data elements the program can >see? in those databases, and, The processing the program can do.
N N
This information is specified in a 'SB %lthough each application program can have its own 'SB, it is not uncommon for application programs that have similar database processing re9uirements to share a 'SB
STMT SOURCE STATEMENT 1 PRINT NO!EN # D D NAME%IND D&ACCESS%HIDAM 3 DATASET DD1%IN&DEVICE%33'0 ( ))* 33'0 DISK STORA!E 5 ) $ SE!M NAME%INVENSE!& PARENT%0&POINTER%T & YTES%131 7 LCHILD NAME%(INPXPNTR&INPXD D)&POINTER%INDX ' +IELD NAME%(INVENCOD&SE")& YTES%3&START%1&TYPE%C 9 +IELD NAME%INVENNAM& YTES%30&START%(&TYPE%C 10 +IELD NAME%INVENADR& YTES%30&START%3(&TYPE%C 11 +IELD NAME%INVENCIT& YTES%17&START%$(&TYPE%C 1# +IELD NAME%INVENSTA& YTES%#&START%'1&TYPE%C 13 +IELD NAME%INVENZIP& YTES%9&START%'3&TYPE%C 1( +IELD NAME%INVENTEL& YTES%10&START%9#&TYPE%C 15 +IELD NAME%INVENCON& YTES%30&START%10#&TYPE%C 1$ ) 17 SE!M NAME%INITMSE!&PARENT%INVENSE!& YTES%(' 1' +IELD NAME%(INITMNUM&SE")& YTES%5&START%1&TYPE%C 19 +IELD NAME%INITMDES& YTES%35&START%$&TYPE%C #0 +IELD NAME%INITMPRC& YTES%(&START%(1&TYPE%P #1 +IELD NAME%INITMCST& YTES%(&START%(5&TYPE%P ## ) #3 SE!M NAME%INLOCSE!& PARENT%INITMSE!& YTES%#1 #( +IELD NAME%(INLOCLOC&SE")& YTES%3&START%1&TYPE%C #5 +IELD NAME%INLOCONH& YTES%(&START%(&TYPE%P #$ +IELD NAME%INLOCROP& YTES%(&START%'&TYPE%P #7 +IELD NAME%INLOCONO& YTES%(&START%1#&TYPE%P #' +IELD NAME%INLOCDAT& YTES%$&START%1$&TYPE%C #9 ) 30 D D!EN 7# ))*)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))) 73 ))* RECOMMENDED VSAM DE+INE CLUSTER PARAMETERS 7( ))*)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))) 75 ))*) )NOTE# 7$ ))*) DE+INE CLUSTER (NAME(IN) NONINDEXED 77 ))*) RECORDSIZE (#0(1�(1) 7' ))*) COUNTERINTERVALSIZE (#0(')) 79 ))*) )NOTE# - SHOULD SPECI+Y DSNNAME +OR DD IN '0 ))*)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))) 1$# ))*)))))))))))SE"UENCE +IELD)))))))))))))
DBD0.1
))*)))))))))))SE"UENCE +IELD))))))))))))) ))*)))))))))))SE"UENCE +IELD))))))))))))) +INISH END *ig ,+. 0ssemb$er so-rce $isting for the In!entor database DBD(") E8p*anation o5 7ig $6'
N N
N N
N N
N N
The first macro@ DBD@ identifies the database The DBD macro names the database 5<%M4AI<DBD6 and specifies the D#&I access method that will be used for it 5%!!4SSA,ID%M6 The second macro, D%T%S4T, identifies the file that will contain the database In this case, its symbolic name will be I< 5DD1AI<6, and it will reside on a BBCD dis$ unit 5D4=I!4ABBCD6 The symbolic name is used in the E!# to identify the dataset at e*ecution time #ines 7/ through CD are produced at assembly time and give recommendations for the =S%M file that will contain the inventory database The segment types are defined using the S4;M macro The hierarchical relationships among the segments are specified by coding the '%)4<T parameter on each S4;M macro
The '"I<T4) parameter in the first S4;M macro and the #!,I#D macro that follows are re9uired because the DB% specified ,ID%M in the DBD macro DB% does not have to define each field in the segment, because application programs identify fields within it in a segment layout. "nly search fields need to be specified To define a field in the DBD, the DB% codes a +I4#D macro, which can contain the following parameters
   
DBD0.1 (contd)*
name of the field 51 to C characters long6 position of fie$d within segment length of the field data type of the field Data Type C)aracter (ac!ed decima* Zoned decima* He8adecima* Ha*5 +ord ,inary 7u** +ord ,inary *ig ,+2 *I"LD macro /9P" parameter codes
-hen occurrences of these segments are added to the database, they are added in se9uence by values in these fields
STMT SOURCE STATEMENT 1 PRINT NO!EN # PC TYPE%D &D DNAME%IND D&KEYLEN%11&PROCOPT%LS 3 SENSE! NAME%INVENSE! ( SENSE! NAME%INITMSE!&PARENT%INVENSE! 5 SENSE! NAME%INLOCSE!&PARENT%INITMSE!
PSB0.1
PS NAME%INLOAD&LAN!%CO OL
*ig ,+3 0ssemb$er so-rce $isting for the In!entor database $oad program:s PSB(")
I
The first macro in the 'SB;4< 8ob stream is '!B '!B 5'rogram !ommunication Bloc$6 describes one database. % 'SB;4< 8ob contains one '!B macro for each database the application program can access. The 'SB 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 -ithin the segments to which it is sensitive, the program has access to all fields -ithin sensitive segments, only specific fields are identified as sensitive fields -hen the program accesses that segment, only sensitive fields are presented
The DBD<%M4 parameter on the '!B macro specifies the name of the DBD for the database to which the '!B corresponds The 4F#4< parameter specifies the length of the longest concatenated $ey the program can process in the database The ')"!"'T parameter specifies the programs processing options
   
Indicate what processing the program is allowed to perform on the database #S The program can perform only load operations "ther values can authori.e programs to retrieve, insert, replace, and delete segments This parameter can be used by the DB% to control access to the database more selectively than is possible at the database level
+or each '!B macro, subordinate S4<S4; macros identify the segments in the database to which the application program is sensitive
The names specified in the S4<S4; macros must be segment names from the DBD;4< for the database named in the DBD<%M4 parameter of the '!B macro
N N
%ll S4<S4; macros for segments other than the root segment must include the '%)4<T parameter The last 'SB;4< macro in the figure is 'SB;4<
  
Indicates that there are no more statements in the 'SB;4< 8ob Its 'SB<%M4 parameter specifies the name to be given to the output 'SB module The #%<; parameter specifies the language in which the related application program will be written.
A batc) program t)at processes a D"4 database is not run direct*y nstead< t)e programmer supp*ies =C" to in-o!e t)e D"4 >batc) initia*i?ation modu*e@< +)ic) in turn *oads t)e app*ication program and t)e D"4 modu*es re/uired to ser-ice it6 Ander 3S< t)e batc) initia*i?ation modu*e is D7SRRCBB T)e program and D"4 modu*es e8ecute toget)er
I I I
The 4<T)F and ;" B%! Statements The D#&I !all The '!B Mas$
The application program is invo$ed under the control of the batch initiali.ation module D#&I first loads the appropriate control bloc$s and modules, then loads the application program and passes control to it D#IT!B#, which stands for 3D#&I to !"B"# is declared as the entry point to the program by coding the 4<T)F statement -hen D#&I passes control to the program, it also supplies the address of each '!B defined in the programs 'SB, in much the same way as parameters are passed to a called subprogram Since these '!Bs reside outside the program they must be defined in the #in$age Section, 8ust li$e passed parameters would be defined in a subprogram The #in$age Section definition of a '!B is called a 3'!B Mas$ %ddressability to '!Bs2 that is, the way the programmer relates '!B mas$s in your programs #in$age Section to actual '!Bs in storage2 is established by listing the '!B Mas$s on the 4<T)F statement %lthough the order in which the '!B Mas$s are coded in the #in$age Section does not matter, you must list them on the 4<T)F statement in the same se9uence as they appear in your programs 'SB;4< The ;" B%! Statement
N N N N N
The 4<T)F statement provides a mechanism for D#&I to transfer control to your program -hen your program ends, it must pass control bac$ to the D#&I so that D#&I can deallocate its resources and close your database datasets To do that, you code a ;" B%! statement, not a ST"' )(< statement If you end a D#&I program with a ST"' )(< statement, control returns directly to the operating systemG D#&I never has a chance to perform its termination functions So always use ;" B%! rather than ST"' )(< in your D#&I programs
I I
CA"" statements are used to re/uest D"4 ser-ices T)e parameters you code on t)e CA"" statement speci5y< among ot)er t)ings< t)e operation you +ant D"4 to per5orm
C,"TD" < +)ic) stands 5or >CO,O" to D"4 @< is t)e name o5 an inter5ace modu*e t)at is *in! edited +it) your program@s ob.ect modu*e6 5 you +or! on ("4 < you +ou*d speci5y (" TD" and 5or assemb*er *anguage< you +ou*d speci5y AS3TD" T)e D"4 7unction
N N
The first parameter coded on any D#&I call +or this parameter, you supply the name of a four character wor$ing storage field that contains the code for the function you want
01 DLI-+UNCTIONS. 05 DLI-!U 05 DLI-!HU 05 DLI-!N 05 DLI-!HN 05 DLI-!NP 05 DLI-!HNP 05 DLI-ISRT 05 DLI-DLET 05 DLI-REPL 05 DLI-CHKP 05 DLI-XRST 05 DLI-PC *ig .+. DL/I f-nction codes
N
PIC PIC PIC PIC PIC X(() X(() X(() X(() X(() X(() PIC
X(() X(() X(() X(() X(() VALUE VALUE VALUE VALUE VALUE VALUE X(()
VALUE ,!U -. VALUE ,!HU -. VALUE ,!N -. VALUE ,!HN -. VALUE ,!NP -. ,!HNP-. ,ISRT-. ,DLET-. ,REPL-. ,CHKP-. ,XRST-. VALUE ,PC -.
+or specifying the D#&I function, the programmer would code one of the D0 level data names 5li$e D#I2;<6 in a D#&I call, since !"B"# doesnt let you code literals on a !%## statement ;et functions
        
The first si* D02level items in +ig B.B are get functions They are used to retrieve segments from a D#&I database ;( 3get uni9ue function causes D#&I to retrieve a specific segment occurrence based on field values that you specify. ;< 3get ne*t function used to retrieve segment occurrences in se9uence ;<' 3get ne*t within parent function lets you retrieve segment occurrences in se9uence, but only subordinate to an established parent segment The three get function codes that contain an , are 3get hold functions and are used to specify an intent to update a segment after you retrieve it ;,( or the 3get hold uni9ue function corresponds to ;( ;,< or the 3get hold ne*t function corresponds to ;< ;,<' or the 3get hold ne*t within parent function corresponds to ;<' (sed to change data in the database IS)T or the 3insert function is used to add a new segment occurrence to a database@ whether it be change an e*isting database or to load a new one D#4T or the 3delete function is used to remove a segment from a database )4'# or the 3replace function is used to replace a segment occurrence
(pdate functions
   
"ther functions
+unctions !, ' 5the 3chec$point function6 and H)ST 5the 3restart function6 are used in programs to ta$e advantage of IMSs recovery and restart features  The last function code '!B is used in !I!S programs T)e (C, mas!
N N N
The second parameter on the D#&I call The name of the '!B mas$ defined in the programs #in$age Section The 4<T)F statement establishes a correspondence between '!B mas$s in the #in$age Section and the '!Bs within the programs 'SB So, when you code a particular '!B mas$ on a D#&I call, you tell D#&I which database to use for the operation you are re9uesting %fter each D#&I call, D#&I stores a status code in the '!B mas$, which the programmer can use to determine whether the call succeeded or failed The third parameter on the D#&I call The name of the wor$ing storage field into which D#&I will return retrieved data or from which it will get data for an update operation "ptional parameter on the D#&I call %n SS% identifies the segment occurrence you want to access
Segment 4O Area
N N
N N N N
Depending on the call you are issuing and the structure of the database, you may have to code several SS%s on a single D#&I call The structure of the SS%s can vary from simple to comple* Fou can code as many SS%s as re9uired There are two $inds of SS%s@ un9ualified and 9ualified %n un9ualified SS%
 
Supplies the name of the ne*t segment type that you want to operate on +or instance, if you issue a ;< call with an un9ualified SS%, D#&I will return the ne*t occurrence of the segment type you specify !ombines a segment name with additional information that specifies the segment occurrence to be processed +or e*ample, a ;( call with a 9ualified SS% might re9uest a particular occurrence of a named segment type by providing a $ey value
% 9ualified SS%
 
7or eac) database your program accesses< D"4 maintains an area o5 storage ca**ed t)e program communication b*oc! 0(C,1 9ou de5ine mas!s 5or t)ose areas o5 storage in t)e "in!age Section o5 your program T)en< a5ter estab*is)ing t)e proper *in!age to t)em at t)e start o5 your program< you can e-a*uate data D"4 stores t)ere 5or in5ormation about t)e databases your program can process
01 INVENTORY-PC -MASK. 05 IPC -D D-NAME PIC X('). 05 IPC -SE!MENT-LEVEL PIC 05 IPC -STATUS-CODE PIC 05 IPC -PROC-OPTIONS PIC 05 +ILLER PIC S9(5) 05 IPC -SE!MENT-NAME PIC 05 IPC -KEY-LEN!TH PIC S9(5) 05 IPC -NUM -SENS-SE!S PIC 05 IPC -KEY PIC X(11).
*ig .+2 PCB mas# for the In!entor database
I
Database name
N
The name of the database being processed Specifies the current segment level in the database %fter a successful call, D#&I stores the level of the segment 8ust processed in this field !ontains the D#&I status code -hen D#&I successfully completes the processing you re9uest in a call, it indicates that to your program by moving spaces to the status code field in the '!B "n the other hand, if a call is unsuccessful or raises some condition that isnt normal, D#&I moves some non2blan$ value to the status code field It is good programming practice to evaluate the status code after you issue a D#&I call Indicates the processing a program is allowed to do on the database The name of the segment is stored by D#&I in this field after each D#&I call. The field D#&I uses to report the length of the concatenated $ey of the lowest level segment processed during the previous call (sed with the $ey feedbac$ area !ontains the number of S4<S4; macros subordinate to the '!B macro for this database
Segment *e-e*
N N
Status code
N N
(rocessing options
N
N N
=aries in length from one '!B to another %s long as the longest possible concatenated $ey that can be used with the programs view of the database %fter a database operation, D#&I returns the concatenated $ey of he lowest level segment processed in this field, and it returns the $eys length in the $ey length feedbac$ area
I I I I I I
Types of SS%s Basic (n9ualified SS% Basic Iualified SS% !ommand !odes The <ull !ommand !ode Multiple Iualifications
'%/es of SS!s
I I
An SSA identi5ies t)e segment occurrence you +ant to access t can be eit)er
N N
I I
An un/ua*i5ied SSA simp*y names t)e type o5 segment you +ant to use A /ua*i5ied SSA< on t)e ot)er )and< speci5ies not on*y t)e segment type< but a*so a database speci5ic occurrence o5 it6
N N
Includes a field value D#&I uses to search for the segment you re9uest %ny field to which the program is sensitive to can be used in an SS%
I I I
,ecause o5 t)e )ierarc)ica* structure D"4 uses< you o5ten )a-e to speci5y se-era* *e-e*s o5 SSAs to access a segment at a *o+ *e-e* in a database 9ou can code as many SSAs on a sing*e ca** as you need 9ou can combine /ua*i5ied and un/ua*i5ied SSAs on a sing*e ca**
A basic un/ua*i5ied SSA is C bytes *ong T)e 5irst eig)t bytes contain t)e name o5 t)e segment you +ant to process 5 t)e segment name is *ess t)an eig)t c)aracters *ong< you must pad it on t)e rig)t +it) b*an!s T)e nint) position o5 a basic un/ua*i5ied SSA a*+ays contains a b*an!
N
The D#&I uses the value in position J to decide what $ind of SS% you are providing
To access a particular segment type, you must modify the segment name during program e*ecution, by moving an appropriate eight2character segment name to the field (<I(%#2SS%2S4;M4<T2 <%M4
+or e*ample,
MOVE ,INVENSE!- TO UN"UAL-SSA-SE!MENT-NAME MOVE ,INITMSE!- TO UN"UAL-SSA-SE!MENT-NAME
A*ternati-e*y< you can code t)e segment name as a *itera* +)en you de5ine a /ua*i5ied SSA
N
7or e8amp*e<
01 UN"UAL-VENDOR-SSA PIC X(9) VALUE ,INVENSE! -. ) 01 UN"UAL-ITEM-SSA PIC X(9) VALUE ,INITMSE! -. ) 01 UN"UAL-STOCK-LOC-SSA PIC X(9) VALUE ,INVENSE! -.
01 VENDOR-SSA. ) 05 +ILLER PIC X(9) VALUE ,INVENSE!(-. 05 +ILLER PIC X(10) VALUE ,INVENCOD %-. 05 VENDOR-SSA-CODE PIC X(3). 05 +ILLER PIC X VALUE ,)-. )
*ig 2+, 0 basic 7-a$ified SS0
I I I I I
A /ua*i5ied SSA *ets you speci5y a particu*ar segment occurrence based on a condition t)at a 5ie*d +it)in t)e segment must meet T)e 5irst eig)t c)aracters o5 a basic /ua*i5ied SSA is t)e eig)t c)aracter segment name T)e nint) byte is a *e5t parent)esis: 0 mmediate*y 5o**o+ing t)e *e5t parent)esis in positions #B t)roug) #D is an eig)t c)aracter 5ie*d name A5ter t)e 5ie*d name< in positions #E and #C< you code a t+o-c)aracter re*ationa* operator to indicate t)e !ind o5 c)ec!ing D"4 s)ou*d do on t)e 5ie*d in t)e segment
N
E?5/@ 79 E" % % N97 1?5/@ 79 NE A% %A !=1/71= T>/. !T B B !=1/71= 7>/. 9= E?5/@ 79 !E B% %B L1:: T>/. LT C C
LE
C%
%C
A5ter t)e re*ationa* operator< you code a -ariab*e 5ie*d into +)ic) you mo-e t)e searc) -a*ue you +ant to use 5or t)e ca** T)e *engt) o5 t)e searc) -a*ue 5ie*d can -ary depending on t)e si?e o5 t)e 5ie*d in t)e segmentF it is t)e on*y part o5 a basic /ua*i5ied SSA t)at doesn@t )a-e a 5i8ed *engt) T)e *ast c)aracter in t)e /ua*i5ied SSA is a rig)t parent)esis: 1
Command Codes
To e*tend D#&I functionality To simplify programs by reducing the number of D#&I calls +or performance improvement resulting from the reduced number of D#&I calls
I I I I I I
To use command codes< code an asteris! in position C o5 t)e SSA T)en code your command codes starting 5rom position #B6 G)en D"4 5inds an asteris! in position C< it !no+s command codes +i** 5o**o+ 7rom position #B on+ards< D"4 considers a** c)aracters to be command codes unti* it encounters a space 05or an un/ua*i5ied SSA1 or a *e5t parent)esis 05or a /ua*i5ied SSA1 t is unusua* to use more t)an one command code in a sing*e SSA A basic un/ua*i5ied SSA +it) a sing*e -ariab*e command code is s)o+n be*o+
01 UN"UALI+IED-SSA. ) 05 UN"UAL-SSA-SE!MENT-NAME PIC X('). 05 +ILLER PIC X VALUE G)H. 05 UN"UAL-SSA-COMMAND-CODE PIC X. 05 +ILLER PIC X VALUE SPACE. )
3eaning Concatenated 2ey (at) Ca** 7irst Occurrence "ast Occurrence (at) Ca** gnore Set (arentage En/ueue Segment 3aintain position at t)is *e-e* 3aintain position at t)is and a** superior *e-e*s Nu** command codes
I I I I
Va*ue is a )yp)en 0F1 A*t)oug) command code position is present< D"4 ignores it (articu*ar*y use5u* i5 you +ou*d *i!e to use t)e same SSA +it) and +it)out command codes An SSA +it) t)e nu** command code is s)o+n be*o+
01 UN"UALI+IED-SSA. ) 05 UN"UAL-SSA-SE!MENT-NAME PIC X('). 05 +ILLER PIC X VALUE G)H. 05 UN"UAL-SSA-COMMAND-CODE PIC X VALUE G-H. 05 +ILLER PIC X VALUE SPACE. )
Multi/le 7ualifications
I
T)ere are t+o cases in +)ic) you +ou*d use mu*tip*e /ua*i5ication
N N
-hen you want to process a segment based on the contents of two or more fields within it -hen you want to process a segment based on a range of possible values for a single field
I I I I
To use mu*tip*e /ua*i5ication< you connect t+o or more /ua*i5ication statements 0a 5ie*d name< a re*ationa* operator< and a comparison -a*ue1 +it)in t)e parent)eses o5 t)e SSA6 To connect t)em< you use t)e ,oo*ean operators AND and OR Eit)er o5 t)e t+o symbo*s s)o+n in t)e tab*e be*o+ may be used 5or AND or OR T)e independent AND operator is used 5or specia* operations +it) secondary inde8es and +i** be discussed *ater
01 VENDOR-SSA. ) 05 +ILLER PIC X(9) VALUE ,INVENSE!(-. 05 +ILLER PIC X(10) VALUE ,INVENCODB%-. 05 VENDOR-SSA-LOI-CODE PIC X(3). 05 +ILLER PIC X VALUE ,J-. 05 +ILLER PIC X(10) VALUE ,INVENCODC%-. 05 VENDOR-SSA-HI!H-CODE PIC X(3). 05 +ILLER PIC X VALUE ,)-.
I
T)e abo-e SSA< +)ic) uses mu*tip*e /ua*i5ications can be used to retrie-e -endor segments +)ose -endor codes 5a** +it)in a certain range
N
The first 9ualification statement specifies that the vendor code field must be greater than or e9ual to a particular valueG that is the low end of the range The second 9ualification statement specifies that the vendor code field must be less than or e9ual to a particular valueG 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- LOI-CODE and VENDOR-SSA- HI!H-CODE Then you would e*ecute ;< calls that include VENDOR-SSA
I I I I I I
The ;( !all The ;< !all The ;<' !all Status !odes 4*pected during Se9uential 'rocessing (sing !ommand !odes with )etrieval !alls Multiple 'rocessing
I I
'he 06 Call
-hen a relatively small number of updates are posted to a large database To establish position in a database for subse9uent se9uential retrieval
I I
9ou !no+ +)at data you +ant to retrie-e and you +ant to get to it direct*y ndependent o5 t)e position estab*is)ed by t)e pre-ious ca**s
I I
A typica* HA ca** *i!e t)e one abo-e< +)erein a comp*ete set o5 /ua*i5ied SSAs to retrie-e a segment< inc*udes one 5or eac) *e-e* in t)e )ierarc)ica* pat) to t)e segment you +ant to retrie-e is ca**ed a >5u**y /ua*i5ied ca**@ Asua**y< HA processing is based on se/uence 0!ey1 5ie*ds +it) uni/ue -a*ues Ho+e-er< 5or some app*ications you may 5ind it necessary to eit)er
N N N
%ccess a segment whose se9uence field allows non2uni9ue values, or, %ccess a segment based on a field that is not the segments $ey field In the above cases, D#&I returns the first segment occurrence with the specified search value -hen you use an un9ualified SS% in a ;( call, D#&I accesses the first segment occurrence in the database that meets the criteria you specify If you issue a ;( call without any SS%s, D#&I returns the first occurrence of the root segment in the database If you omit some SS%s for intermediate levels in a hierarchical path, the action D#&I ta$es depends on your current position and on the SS%s that are missing
 D#&I either uses the established position or defaults to an un9ualified SS% for the segment Recommended sty*e o5 coding
N
!ode a 9ualified or un9ualified SS% for each level in the path from the root segment to the segment you want to retrieve "nly two status code values need to be considered@ spaces and ;4 Spaces means the call was successful and the re9uested segment was returned in your programs segment I&" area % ;4 status code indicates that D#&I couldnt find a segment that met the criteria you specified in the call
Status codes you can e8pect during random processing +it) HA ca**s
N N
'he 01 Call
Ased 5or basic se/uentia* processing A5ter any success5u* database ca**< your database position is immediate*y be5ore t)e ne8t segment occurrence in t)e norma* )ierarc)ica* se/uence ,e5ore your program issues any ca**s< position is be5ore t)e root segment o5 t)e 5irst database record T)e HN ca** mo-es 5or+ard t)roug) t)e database 5rom t)e position estab*is)ed by t)e pre-ious ca** 5 a HN ca** is un/ua*i5ied 0t)at is< i5 it does not emp*oy an SSA1< it returns t)e ne8t segment occurrence in t)e database regard*ess o5 type< in )ierarc)ica* se/uence 5 a HN ca** inc*udes SSAsF /ua*i5ied or un/ua*i5iedF D"4 retrie-es on*y segments t)at meet re/uirements o5 a** SSAs you speci5y 5 you inc*ude an un/ua*i5ied SSA or omit an SSA a*toget)er 5or a segment type< D"4 a**o+s any occurrence o5 t)at segment type to satis5y t)e ca** ,ut +)en you speci5y a /ua*i5ied SSA< D"4 se*ects on*y t)ose segment occurrences t)at meet t)e criteria you speci5y
I I I
Ased 5or se/uentia* processing +it)in parentage Gor!s *i!e t)e HN ca**< e8cept it retrie-es on*y segments t)at are subordinate to t)e current*y estab*is)ed parent To estab*is) parentage< your program 3AST issue eit)er a HA ca** or a HN ca**< and t)e ca** must be success5u*
N
'arentage is never automatically established, in spite of the hierarchical structure of the database
I I I
T)e segment returned by t)e ca** becomes t)e estab*is)ed parent Subse/uent HN( ca**s return on*y segment occurrences t)at are dependent on t)at parent G)en t)ere are no more segments +it)in t)e estab*is)ed parentage D"4 returns HE as t)e status code
Vendor #
(arent
tem $
"oc $ "oc #
-hen you issue a call with an SS% that includes the + command code, the call processes the first occurrence of the segment named by the SS%, sub8ect to the calls other 9ualifications !an be used when you are doing se9uential processing and you need to bac$ up in the database, or in other words, the + command code can be used for se9uential retrieval using ;< and ;<' calls Meaningless with ;( calls, because ;( normally retrieves the first segment occurrence that meets the criteria you specify
-hen you issue a call with an SS% that includes the # command code, the call processes the last occurrence of the segment named by the SS%, sub8ect to the calls other 9ualifications (sed to retrieve more than one segment occurrence using 8ust one call <ormally D#&I operates on the lowest level segment you specify in an SS%, but in many cases, you want data not 8ust from the lowest level in the call, but from other levels as well Ma$es it easy to retrieve an entire path of segments
The usage of the D command code is illustrated below
01 VENDOR-SSA. 05 +ILLER PIC X(11) VALUE GINVENSE!)D(H. 05 +ILLER PIC X(10) VALUE GINVENCOD %H. 05 VENDOR-SSA-CODE PIC X(3). 05 +ILLER PIC X VALUE G)H. ) 01 ITEM-SSA. 05 +ILLER PIC X(11) VALUE GINITMSE!)D(H. 05 +ILLER PIC X(10) VALUE GINITMNUM %H. 05 ITEM-SSA-NUM ER PIC X(5). 05 +ILLER PIC X VALUE G)H. ) 01 LOCATION-SSA. 05 +ILLER PIC X(11) VALUE GINLOCSE!)D(H. 05 +ILLER PIC X(10) VALUE GINLOCLOC %H. 05 LOCATION-SSA-CODE PIC X(3). 05 +ILLER PIC X VALUE G)H. ) 01 PATH-CALL-I-O-AREA. 05 INVENTORY-VENDOR-SE!MENT PIC X(131). 05 INVENTORY-ITEM-SE!MENT PIC X(('). 05 INVENTORY-STOCK-LOC-SE!MENT PIC X(#1). ) ... ) CALL GC LTDLIH USIN! DLI-!U INVENTORY-PC -MASK PATH-CALL-I-O-AREA VENDOR-SSA ITEM-SSA LOCATION-SSA.
I
N N
If you are developing a program that retrieves 8ust lower2level segment occurrences from a database, you dont have to code separate SS%s for each level in the hierarchical path Instead you can use a single SS% with the ! command code Then, rather than coding a field name, relational operator, and search value, you specify the concatenated $ey for the segment you are interested in %n illustration of the use of the ! command code is shown below
) 01 LOCATION-SSA. ) 05 +ILLER PIC X(11) VALUE ,INLOCSE!)C(,. 05 LOCATION-SSA-VENDOR PIC X(3). 05 LOCATION-SSA-ITEM PIC X(5). 05 LOCATION-SSA-LOCATION PIC X(3). 05 +ILLER PIC X VALUE ,)-.
-hen you issue a ;( or ;< call, D#&I normally establishes parentage at the lowest level segment that is retrieved ,owever, if you want to override that and cause parentage to be established at a higher2level segment in the hierarchical path, you can use the ' command code in its SS% -hen you use an un9ualified SS% that specifies the ( command code in a ;< call, D#&I restricts the search for the segment you re9uest to dependents of the segments with the ( command code ,as the same effect as a call which contains a 9ualified SS% for the current position Is ignored if used with a 9ualified SS% 4ffect is same as coding the ( command code at that level and all levels above it in the hierarchy Is ignored if used with a 9ualified SS% This command code is used to en9ueue, or reserve for e*clusive use, a segment or path of segments Fou only need to use the I command code in an interactive environment where there is a chance that another program might ma$e a change to a segment between the time you first access it and the time you are finished with it
N N
Multi/le Processing
I
3u*tip*e processing is a genera* term t)at means a program can )a-e more t)an one position in a sing*e p)ysica* database at t)e same time D"4 *ets t)e programmer imp*ement mu*tip*e processing in t+o +ays
N N
Through multiple '!Bs Through multiple positioning The DB% can define multiple '!Bs for a single database Then, the program has two 5or more6 views of the database %s with '!Bs for different databases, each has its own mas$ in the #in$age Section and is specified in the 4<T)F statement It is up to the programs logic to decide when to use a particular '!B to access the database This method for implementing multiple processing, though fle*ible, is inefficient because of the overhead imposed by the e*tra '!Bs #ets a program maintain more than one position within a database using a single '!B To do that, D#&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 se9uentially at the same time
3u*tip*e (C,s
N N N
N N
3u*tip*e positioning
N N N
A1 #atabase Record 1
$1! $1" 1! 1" 11 $"" "" $11 A" #atabase Record "
$"1
"1 *ig 3+, /wo database records to i$$-strate m-$tip$e positioning MOVE ,SE! - TO UN"UAL-SSA-SE!MENT-NAME. CALL ,C LTDLI- USIN! DLI-!N SAMPLE-D -PC SE!MENT- -I-O-AREA UN"UALI+IED-SSA. MOVE ,SE!C - TO UN"UAL-SSA-SE!MENT-NAME. CALL ,C LTDLI- USIN! DLI-!N SAMPLE-D -PC SE!MENT-C-I-O-AREA UN"UALI+IED-SSA.
N N
N N
N N
-hen you use multiple positioning, D#&I maintains its separate positions based on segment type %s a result you include an un9ualified SS% in the call that names the segment type whose position you want to use It is the DB% who decides whether single or multiple positioning will be in effect in the programs 'SB %s a result multiple positioning is not the characteristic of the database but instead, its how D#&I allows a program to view a database The same program can be processed with either single or multiple positioning by different programs The techni9ue a program uses is determined by the programs 'SB
I I I I
T)e SRT Ca** T)e Het Ho*d Ca**s T)e RE(" Ca** T)e D"ET Ca**
I I I I
T)e SRT ca** is used to add a segment occurrence to a database< eit)er during update processing o5 an e8isting database or during *oad processing o5 a ne+ database ,e5ore an SRT ca** is issued< you s)ou*d 5irst bui*d t)e segment occurrence by mo-ing data to t)e 5ie*ds o5 t)e segment description A5ter 5ormatting t)e segment< you issue t)e SRT ca** +it) at *east one SSA: an un/ua*i5ied SSA 5or t)e segment type you +ant to add Consider t)e e8amp*e be*o+
I I I I
Here AN;AA" 7 ED-SSA speci5ies t)e segment name ,ecause t)e SSA is un/ua*i5ied< D"4 tries to satis5y t)e ca** based on t)e current position in t)e database As a resu*t< you need to be care5u* about position +)en you issue an SRT ca** t)at speci5ies on*y a sing*e un/ua*i5ied SSA A sa5er tec)ni/ue is to speci5y a /ua*i5ied SSA 5or eac) )ierarc)ica* *e-e* abo-e t)e one +)ere you +ant to insert t)e segment< as i**ustrated be*o+
5 SSAs 5or -endor and item are initia*i?ed +it) t)e proper !ey -a*ues< D"4 inserts t)e ne+ segment occurrence in t)e correct position in t)e database G)en you issue a 5u**y /ua*i5ied SRT ca** *i!e t)is< D"4 returns a status code o5 HE i5 any segment occurrence you speci5y in an SSA isn@t present in t)e database As a resu*t< you can issue an SRT ca** +it) /ua*i5ied SSAs instead o5 5irst issuing HA ca**s to 5ind out i5 )ig)er-*e-e* segments in t)e pat) are present ,y issuing one ca** instead o5 t+o 0or more1< you can sa-e system resources G)ere inserted segments are stored
N
I I
If the new segment has a uni9ue se9uence field, as most segment types do, it is added in its proper se9uential position ,owever, some lower2level segment types in some databases have non2uni9ue se9uence fields or dont have se9uence fields at all -hen thats the case, where the segment occurrence is added depends on the rules the DB% specifies for the database +or a segment without a se9uence field, the insert rule determines how the new segment is positioned relative to e*isting twin segments
  
If the rule is >first?, the new segment is added before any e*isting twins If the rule is >last?, the new segment is added after all e*isting twins If the rule is >here?, it is added at the current position relative to e*isting twins, which may be first, last, or anywhere in the middle
+or a segment with non2uni9ue se9uence fields, the rules are similar, but they determine where the new segment is positioned relative to e*isting twin segments that have the same $ey value ;4 -hen you use multiple SS%s and D#&I cannot satisfy the call with the specified path -hen you try to add a segment occurrence that is already present in the database +or load processing you might get status codes #B, #!, #D or #4.
N
N
II
In most cases they indicate that you are not inserting segments in e*act hierarchical se9uence That means there is an error in your program or the files from which you are loading the database contain incorrect data
T)ere are t)ree get )o*d 5unctions you can speci5y in a D"4 ca**:
N N N
;,( 5;et hold uni9ue6 ;,< 5;et hold ne*t6, and, ;,<' 5;et hold ne*t within parent6
I I I
T)ese ca**s para**e* t)e t)ree retrie-a* ca**s ear*ier discussed ,e5ore you can rep*ace or de*ete a segment< you must dec*are your intent to do so< by retrie-ing t)e segment +it) one o5 t)ese t)ree ca**s T)en you must issue t)e rep*ace or de*ete ca** be5ore you do anot)er D"4 processing in your program A5ter you )a-e retrie-ed a segment +it) one o5 t)e get )o*d ca**s< you can ma!e c)anges to t)e data in t)at segment< t)en issue an RE(" ca** to rep*ace t)e origina* segment +it) t)e ne+ data T)ere are t+o restrictions on t)e c)anges you can ma!e:
N N
I I
9ou can@t c)ange t)e *engt) o5 t)e segment 9ou can@t c)ange t)e -a*ue o5 t)e se/uence 5ie*d 0i5 t)e segment )as one1
I I
Ne-er code a /ua*i5ied SSA on an RE(" ca**: i5 you do< t)e ca** +i** 5ai* An e8amp*e o5 a typica* rep*ace operation is s)o+n be*o+
ADD TRANS-RECEIPT-"TY TO ISLS-"UANTITY-ON-HAND. SU TRACT TRANS-RECEIPT-"TY +ROM ISLS-"UANTITY-ON-ORDER. CALL ,C LTDLI- USIN! DLI-REPL INVENTORY-PC -MASK INVENTORY-STOCK-LOC-SE!MENT.
If you try to use a 9ualified SS% on an )4'# call, you will get an %E status code If your program issues a replace call without an immediately preceding get hold call, D#&I returns a DE status code If your program ma$es a change to the segments $ey field before issuing the )4'# call, D#&I returns a D% status code
I I I I
T)e D"ET ca** +or!s muc) *i!e RE(" 9ou must 5irst issue a get )o*d ca** to indicate t)at you intend to ma!e a c)ange to t)e segment you are retrie-ing T)en you issue a D"ET ca** to de*ete t)e segment occurrence 5rom t)e database 7or e8amp*e< to de*ete a stoc! *ocation t)at is no *onger acti-e< you@d code a series o5 statements *i!e t)e ones be*o+
DLI-!HU
INVENTORY-PC -MASK INVENTORY-STOCK-LOC-SE!MENT VENDOR-SSA ITEM-SSA LOCATION-SSA. CALL ,C LTDLI- USIN! DLI-DLET INVENTORY-PC -MASK INVENTORY-STOCK-LOC-SE!MENT.
I I I
Notice t)at t)e D"ET ca** does not inc*ude any SSAs T)ere is one important point you must !eep in mind +)ene-er you use t)e D"ET ca**F +)en you de*ete a segment< you automatica**y de*ete a** segment occurrences subordinate to it T)e status codes you mig)t get a5ter a D"ET ca** are t)e same as t)ose you can get a5ter an RE(" ca**
I I I I I I I I I I I I
The <eed for Secondary Inde*ing % !ustomer Database Secondary Inde*es Secondary eys Secondary Data Structures DBD;4< )e9uirements for Secondary Inde*es 'SB;4< )e9uirements for Secondary Inde*ing Inde*ing a Segment based on a Dependent Segment The Independent %<D "perator Sparse Se9uencing Duplicate Data +ields
I I I
O5ten you need to be ab*e to access a database in an order ot)er t)an its primary )ierarc)ica* se/uence Or< you may need to access a segment in a database direct*y< +it)out supp*ying its comp*ete concatenated !ey Git) secondary inde8ing bot) are possib*e
01 LINE-ITEM-SEGMENT. 05 LIS-ITEM-$EY. 10 LIS-ITEM-$EY-%ENDOR PIC X(3). 10 LIS-ITEM-$EY-NUMBER PIC X(3). 05 LIS-UNIT-PRICE PIC S!(5)%!! COMP-3. 05 LIS-#UANTITY PIC S!(() COMP-3.
01 05 05 05 05
01 S"IP-TOSEGMENT. 05 STS-S"IPTO-SE#UENCE PIC XX. 05 STS-S"IPTO-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- IPCODE PIC X(!).
'ayment
01 CUSTOMER-SE!MENT.
PIC PIC PIC PIC X(16). X(25). X(6). S!(5)%!! COMP-3. 01 BUYER-SEGMENT. 05 BS-BUYER-NAME 05 BS-TITLE 05 BS-TELEP"ONE
!ustomer
Ship2to
! Customer Database
01 RECEI%ABLE-SEGMENT. 05 RS-IN%OICE-NUMBER 05 RS-IN%OICE-DATE 05 RS-PO-NUMBER 05 RS-PRODUCT-TOTAL 05 RS-CAS"-DISCOUNT 05 RS-SALES-TAX 05 RS-'REIG"T 05 RS-BALANCE-DUE 3. PIC X(6). PIC X(6). PIC X(25). PIC S!(5)%!! COMP-3. PIC S!(5)%!! COMP-3. PIC S!(5)%!! COMP-3. PIC S!(5)%!! COMP-3. PIC S!(5)%!! COMP-
Buyer
%d8ustment )eceivable
#ine Item
05 05 05 05 05 05 05
PIC PIC PIC PIC PIC X(1'). PIC XX. PIC PIC XX. PIC PIC PIC PIC X(1'). PIC PIC
) 01 SHIP-TO-SE!MENT. 05 STS-SHIP-TO-SE"UENCE 05 STS-SHIP-TO-NAME 05 STS-ADDRESS-LINE-1 05 STS-ADDRESS-LINE-# 05 STS-CITY 05 STS-STATE 05 STS-ZIP-CODE ) 01 UYER-SE!MENT. 05 S- UYER-NAME 05 S-TITLE 05 S-TELEPHONE ) 01 RECEIVA LE-SE!MENT. 05 RS-INVOICE-NUM ER 05 RS-INVOICE-DATE 05 RS-PO-NUM ER 05 RS-PRODUCT-TOTAL 05 RS-CASH-DISCOUNT 05 RS-SALES-TAX 05 RS-+REI!HT 05 RS- ALANCE-DUE )
PIC X(31). PIC X(31). PIC X(10). PIC PIC X($). PIC PIC PIC PIC PIC PIC X($). X(#5). 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.
*ig 5+, Segment La o-ts for the C-stomer Database =Part 1 of ,> 01 PAYMENT-SE!MENT. 05 PS-CHECK-NUM ER 05 PS- ANK-NUM ER 05 PS-PAYMENT-DATE 05 PS-PAYMENT-AMOUNT ) 01 ADKUSTMENT-SE!MENT. 05 AS-RE+ERENCE-NUM ER 05 AS-ADKUSTMENT-DATE 05 AS-ADKUSTMENT-TYPE 05 AS-ADKUSTMENT-AMOUNT ) 01 LINE-ITEM-SE!MENT. 05 LIS-ITEM-KEY. 10 LIS-ITEM-KEY-VENDOR 10 LIS-ITEM-KEY-NUM ER 05 LIS-UNIT-PRICE 05 LIS-"UANTITY ) PIC X(1$). PIC X(#5). PIC X($). PIC S9(5)V99 COMP-3. PIC PIC PIC PIC X(1$). X($). X. S9(5)V99
COMP-3.
COMP-3. COMP-3.
*ig 5+, Segment La o-ts for the C-stomer Database =Part , of ,>
Secondar% Inde9es
Secondary &nde' #atabase $(stomer #atabase !ustomer &nvoice n(mber inde' database (re5i8 Data Rec% Seg% Addr% &nvoice No% &nde' Pointer Segment
Ship2to
Buyer
)eceivable
'ayment
%d8ustment
#ine Item
&nde'ed #atabase
*ig 5+. Secondar Inde1ing "1amp$e in which the Inde1 So-rce Segment and the Inde1 /arget Segment are the same
D"4 maintains t)e a*ternate se/uence by storing pointers to segments o5 t)e inde8ed database in a separate inde8 database A secondary inde8 database )as .ust one segment type< ca**ed t)e inde8 pointer segment T)e inde8 pointer segment contains t+o main e*ementsF a pre5i8 e*ement and a data e*ement T)e data e*ement contains t)e !ey -a*ue 5rom t)e segment in t)e inde8ed database o-er +)ic) t)e inde8 is bui*t< ca**ed t)e inde8 source segment T)e pre5i8 part o5 t)e inde8 pointer segment contains a pointer to t)e inde8 target segmentF t)e segment t)at is accessib*e -ia t)e secondary inde8 T)e inde8 source and target segments need not be t)e same A5ter a secondary inde8 )as been set up< D"4 maintains it automatica**y as c)anges are made to t)e inde8ed databaseF t)oug) t)e inde8 is transparent to app*ication programs t)at use it
N
So, even if a program that is not sensitive to a secondary inde* updates a database record in a way that would affect the inde*, D#&I automatically updates the inde* That can also result in performance degradation In practice, the number of secondary inde*es for a given database is $ept low because each imposes additional processing overhead on D#&I
5 mu*tip*e access pat)s are re/uired into t)e same database< t)e D,A can de5ine as many di55erent secondary inde8es as necessaryF eac) stored in a separate inde8 database
N
Secondar% 4e%s
I I I
T)e 5ie*d in t)e inde8 source segment o-er +)ic) t)e secondary inde8 is bui*t is ca**ed t)e secondary !ey T)e secondary !ey need not be t)e segment@s se/uence 5ie*dF any 5ie*d can be used as a secondary !ey T)oug) usua**y< a sing*e 5ie*d +it)in t)e inde8 source segment is designated as t)e secondary !ey 5or a secondary inde8< t)e D,A can combine as many as 5i-e 5ie*ds in t)e source segment to 5orm t)e comp*ete secondary !ey
N
A secondary inde8 c)anges t)e apparent )ierarc)ica* structure o5 t)e database T)e inde8 target segment is presented to your program as i5 it +ere a root segment< e-en i5 it isn@t actua**y t)e root segment As a resu*t< t)e )ierarc)ica* se/uence o5 t)e segments in t)e pat) 5rom t)e inde8 target segment to t)e root segment is in-erted: t)ose segments appear to be subordinate to t)e inde8 target segment< e-en t)oug) t)ey are actua**y superior to it T)e resu*ting rearrangement o5 t)e database structure is ca**ed a secondary data structure
)eceivable
Ship2to
'ayment
%d8ustment
#ine Item
!ustomer
Buyer
I I
Secondary data structures don@t c)ange t)e +ay t)e database segments are stored on dis!
N
T)ey .ust a*ter t)e +ay D"4 presents t)ose segments to app*ication programs
G)en you code an app*ication program t)at processes a database -ia a secondary inde8< you must consider )o+ t)e secondary data structure a55ects your program@s *ogic
,ecause a secondary inde8 re*ations)ip in-o*-es t+o databases< t+o D,DHENs are re/uiredF one 5or t)e inde8ed database and t)e ot)er 5or t)e secondary inde8 database
In the DBD;4< for the inde*ed database, an #!,I#D macro relates an inde* target segment to its associated secondary inde* database In the DBD;4< for the secondary inde* database, an #!,I#D macro relates the inde* pointer segment to the inde* target segment
ACCESSI NDE: in t)e D,D macro in 7ig D6J te**s D"4 t)at an inde8 database is being de5ined T)e NDE: parameter o5 t)e "CH "D macro in 7ig D6J speci5ies t)e name o5 t)e secondary !ey 5ie*dF CRREC:NO T)e :D7"D macro in 7ig D6% supp*ies a 5ie*d name 0CRREC:NO1 t)at is used to access t)e database -ia t)e secondary !ey
N N
This $ey field does not become a part of the segment Instead, its value is derived from up to five fields defined within the segment with +I4#D macros
T)e SRCH parameter de5ines t)e 5ie*d0s1 t)at constitute t)e secondary inde8
=ust because a secondary inde8 e8ists 5or a database doesn@t mean D"4 +i** automatica**y use it +)en one o5 your programs issues ca**s 5or t)at database 9ou need to be sure t)at t)e (S,HEN 5or t)e program speci5ies t)e proper processing se/uence 5or t)e database on t)e (ROCSE; parameter o5 t)e (S, macro 5 it doesn@t< processing is done using t)e norma* )ierarc)ica* se/uence 5or t)e database 7or t)e (ROCSE; parameter< t)e D,A codes t)e D,D name 5or t)e secondary inde8 database t)at +i** be used
T)e SENSEH macros in 7ig D6D re5*ect t)e secondary data structure imposed by t)e secondary inde8 G)en t)e (ROCSE; parameter is present< processing is done based on t)e secondary inde8 se/uence 5 a program needs to access t)e same inde8ed database using di55erent processing se/uences< t)e program@s (S,HEN +i** contain more t)an one (C, macro< eac) speci5ying a di55erent -a*ue 5or t)e (ROCSE; parameter
Ship)to
(yer
Receivable
&nde'ed #atabase
*ig 5+6 Secondar Inde1ing "1amp$e in which the Inde1 So-rce Segment and the Inde1 /arget Segment are different
I I
T)e nde8 Source Segment and t)e nde8 Target Segment need not be t)e same Some app*ications re/uire t)at a particu*ar segment be inde8ed by a -a*ue t)at is deri-ed 5rom a dependent segment
N N N
In such a case, the Inde* Target Segment and the Inde* Source Segment are different +or e*ample, in +ig 7.C, you can retrieve customers based on items they have purchased In other words, the SS% for a get call would specify an item number, but the call would retrieve a customer segment Thus, in the e*ample shown in +ig 7.C, it wouldnt be possible to inde* 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 inde* the line item segment based in the customer segment, because the customer segment is superior to the line item segment
T)e on*y restriction you need to be a+are o5 )ere is t)at t)e nde8 Source Segment must be a dependent o5 t)e nde8 Target Segment
N
I I I I I I
-hen used with secondary inde*es, %<D 5 ) or K 6 is called the dependent %<D operator The independent %<D 5L6 lets you specify 9ualifications that would be impossible with the dependent %<D This operator can be used only for secondary inde*es where the inde* source segment is a dependent of the inde* target segment Then, you can code an SS% with the independent %<D 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 %<D re9uires that all fields you specify in the SS% be in the same segment occurrence %n SS% that uses the independent %<D operator is shown below
01 ITEM-SELECTION-SSA. ) 05 +ILLER PIC 05 +ILLER PIC 05 SSA-ITEM-KEY-1 PIC X('). 05 +ILLER PIC 05 +ILLER PIC 05 SSA-ITEM-KEY-# PIC 05 +ILLER PIC
X(9) X(10)
S/arse Sequencing
I I I I I I I
G)en t)e D,A imp*ements a secondary inde8 database +it) sparse se/uencing 0a*so ca**ed sparse inde8ing1< it is possib*e to omit some inde8 source segments 5rom t)e inde8 Sparse se/uencing can impro-e per5ormance +)en some occurrences o5 t)e inde8 source segment must be inde8ed but ot)ers need not be D"4 uses a suppression -a*ue< a suppression routine< or bot) to determine +)et)er a segment s)ou*d be inde8ed 0eit)er +)en inserting a ne+ segment or processing an e8isting one1 5 t)e -a*ue o5 t)e se/uence 5ie*d0s1 in t)e inde8 source segment matc)es a suppression -a*ue speci5ied by t)e D,A< no inde8 re*ations)ip is estab*is)ed 05or an insert1 or e8pected 05or any ot)er ca**1 T)e D,A can a*so speci5y a suppression routine t)at D"4 in-o!es to determine t)e inde8 status 5or t)e segment T)e suppression routine is a user-+ritten program t)at e-a*uates t)e segment and determines +)et)er or not it s)ou*d be inde8ed Note:
N N
-hen sparse inde*ing is used, its functions are handled by D#&I Fou dont need to ma$e special provisions for it in your application program
7or some app*ications< it mig)t be desirab*e to store user data 5rom t)e inde8 source segment in t)e inde8 pointer segment G)en t)e D,A speci5ies t)at some 5ie*ds are dup*icate data 5ie*ds< t)is is possib*e Ap to 5i-e data 5ie*ds can be stored in t)e inde8 database< and D"4 maintains t)em automatica**y Dup*icate data 5ie*ds are use5u* on*y +)en t)e inde8 database is processed as a separate database Note:
N N
Duplicate data fields impose e*tra D#&I overhead and re9uire e*tra D%SD storage It is the DB%s responsibility to decide whether the advantages of using duplicate data fields outweigh the e*tra D#&I overhead and D%SD storage re9uirements mentioned above
I I
Types DBD;4<s 'rogramming !onsiderations !oncatenated Segments and Inverted ,ierarchies DBD;4<s 'rogramming !onsiderations
"ogica* Databases
N N N
T)e basic ru*e t)at eac) segment type can )a-e on*y one parent< *imits t)e comp*e8ity o5 a p)ysica* database 3any D"4 app*ications re/uire a more comp*e8 structure t)at a**o+s a segment to )a-e t+o parent segment types As a resu*t D"4 a**o+s t)e D,A to imp*ement *ogica* re*ations)ips in +)ic) a segment can )a-e bot) a p)ysica* parent and a *ogica* parent T)en< ne+ data structures ca**ed *ogica* databases can be bui*t around t)ose *ogica* re*ations)ips
Logical Relationshi/s
I
%lways between two segments (sually in separate databases, but could also be between two segments in the same database
(yer
Payment
Ad*(stment
Line &tem
*ig-re 6+1 /he C-stomer and In!entor Databases witho-t $ogica$ re$ationships DBD(") code for the Line Item segment in the C-stomer Database SE!M +IELD +IELD +IELD NAME%CRLINSE!&PARENT%CRRECSE!& YTES%1$ NAME%CRLININO& YTES%'&START%1&TYPE%C NAME%CRLINPRC& YTES%(&START%9&TYPE%P NAME%CRLIN"TY& YTES%(&START%13&TYPE%P
DBD(") code for the Item segment in the In!entor Database SE!M +IELD +IELD +IELD +IELD NAME%INITMSE!&PARENT%INVENSE!& YTES%(' NAME%(INITMNUM&SE")& YTES%5&START%1&TYPE%C NAME%INITMDES& YTES%35&START%$&TYPE%C NAME%INITMPRC& YTES%(&START%(1&TYPE%P NAME%INITMCST& YTES%(&START%(5&TYPE%P
*ig-re 6+, Partia$ DBD(") for the C-stomer and In!entor databases witho-t a $ogica$ re$ationship
"ogica* Re*ations)ip +endor $(stomer "ogica* (arent Ship)to ()ysica* (arent (yer Receivable Stoc, Location Line &tem &tem
Virtua* "ogica* C)i*d Payment Ad*(stment Line &tem Rea* "ogica* C)i*d *ig-re 6+. /he C-stomer and In!entor Databases with a $ogica$ re$ationship
I
Is the basis of a logical relationship Is a physical data segment, but D#&I loo$s at it as if it had two parent segments
 
I I
The physical parent, and The logical parent One *ogica* c)i*d segment occurrence )as on*y one *ogica* parent segment occurrence One *ogica* parent segment occurrence can )a-e many *ogica* c)i*d segment occurrences
N
Such logical child segment occurrences are called logical twins "ccurrences of a logical child segment type that are all subordinate to a single occurrence of the logical parent segment type This segment, called the =irtual #ogical !hild segment, does not e*ist physically The $ind of relationship the DB% specifies determines the e*istence of a virtual logical child segment
"ogica* t+ins
N
D"4 ma!es t)e *ogica* c)i*d segment appear to be *i!e an actua* p)ysica* c)i*d segment
N
Ho+e-er< a** *ogica* c)i*d segments need not be imp*emented as -irtua* *ogica* c)i*d segments
N
T)ere are t)ree !inds o5 *ogica* re*ations)ips t)e D,A can speci5y
N N N
(nidirectional Bidirectional =irtual Bidirectional 'hysical #ogical connection goes from the logical child to the logical parent and not the other way around %llows access in both directions ,owever, the segment actually e*ists only in its physical database The logical child in its physical structure and the corresponding virtual logical child are said to be paired #ogical 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 DBD0.1s for Ph%sical Databases -ith Logical Relationshi/s
Anidirectiona*
N
,idirectiona* Virtua*
N N N
,idirectiona* ()ysica*
N N N
Deciding +)at !ind o5 *ogica* database to use 5or a particu*ar situation is t)e responsibi*ity o5 t)e D,A
DBD;4< code for the real logical child segment 5the #ine Item segment !)#I<S4;6 in the !ustomer database 5!)DBD6
SE!M NAME%CRLINSE!& PARENT%((CRRECSE!&D LE)&(INITMSE!&V&IND D))& POINTER%(TIIN<IIN)&RULES%(LLV&LAST) & YTES%1$ +IELD NAME%CRLININO& YTES%'&START%1&TYPE%C +IELD NAME%CRLINPRC& YTES%(&START%9&TYPE%P +IELD NAME%CRLIN"TY& YTES%(&START%13&TYPE%P
DBD;4< code for the logical parent segment 5the Item segment I<ITMS4;6 and the virtual logical child segment 5the #ine Item segment I<#I<S4;6 in the Inventory database 5I<DBD6
SE!M NAME%INITMSE!&PARENT%INVENSE!& YTES%(' LCHILD NAME%(CRLINSE!&CRD D)&POINTER%D LE&PAIR%INLINSE!& RULES%LAST +IELD NAME%(INITMNUM&SE")& YTES%5&START%1&TYPE%C +IELD NAME%INITMDES& YTES%35&START%$&TYPE%C +IELD NAME%INITMPRC& YTES%(&START%(1&TYPE%P +IELD NAME%INITMCST& YTES%(&START%(5&TYPE%P SE!M NAME%INLINSE!&PARENT%INITMSE!&POINTER%PAIRED& SOURCE%(CRLINSE!&D&CRD D)
Figure 8.4 Partial DBDGEN code for the Customer and Inventory data ases !ith a logical relationshi"
I
To imp*ement a *ogica* re*ations)ip< t)e D,A )as to speci5y it in t)e D,DHENs 5or t)e in-o*-ed p)ysica* databases
n t)e D,DHEN code 5or t)e Customer database< t+o parent segments )a-e been speci5ied 5or t)e "ine tem segment
N N
The first is its physical parent !))4!S4; The second is its logical parent I<ITMS4;
n t)e D,DHEN code 5or t)e n-entory database< N T3SEH is speci5ied as t)e *ogica* parent o5 t)e CR" NSEH segment in t)e Customer database< CRD,D
N N N
The #!,I#D macro is used for this purpose The '%I) parameter indicates that the virtual logical child segment is I<#I<S4; +or a unidirectional relationship, the DB% would have omitted the '%I) parameter
T)e D,DHEN 5or t)e database t)at contains a *ogica* parent in a bidirectiona* -irtua* *ogica* re*ations)ip a*so must contain an SEH3 5or t)e -irtua* *ogica* c)i*d segment
N
The S"()!4 parameter in this S4;M macro specifies that the data that will appear to be in the virtual logical child will actually be stored in the #ine Item segment in the !ustomer database
To process segments in-o*-ed in a *ogica* re*ations)ip< you issue ca**s .ust as you +ou*d i5 t)e segments +eren@t in-o*-ed in t)e *ogica* re*ations)ip (rogram speci5ications +i** indicate t)e structure o5 t)e database you +i** be using
N
In some cases, you may not even $now that you are processing a segment that is involved in a logical relationship
I I I
Ho+e-er< *ogica* re*ations)ips add a ne+ dimension to database programming n cases +)ere t+o databases are integrated t)roug) a *ogica* re*ations)ip< c)anges to one database can a55ect t)e ot)er T)e D,A )as to anticipate t)e resu*ts o5 possib*e database processing on segments in-o*-ed in a *ogica* re*ations)ip
N
The DB% can control processing by specifying appropriate processing options for involved databases and segments %t a finer level, the DB% 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 non2blan$ status code %s an application programmer, you dont have to worry about all their ramifications
T)e potentia* prob*ems o5 updating databases in-o*-ed in *ogica* re*ations)ips are e8tensi-e
N
) 01 LINE-ITEM-LO!-CHILD-SE!MENT. ) 05 LILCS-DEST-PARENT-CONCAT-KEY. 10 LILCS-DPCK-CUSTOMER-NUM ER PIC X($). 10 LILCS-DPCK-SHIP-TO-SE"UENCE PIC XX. 10 LILCS-DPCK-INVOICE-NUM ER PIC X($). 05 LILCS-LINE-ITEM-SE!MENT. 10 LILCS-LIS-ITEM-KEY. 15 LILCS-LIS-ITEM-KEY-VENDOR PIC X(3). 15 LILCS-LIS-ITEM-KEY-NUM ER PIC X(5). 10 LILCS-LIS-UNIT-PRICE PIC S9(5)V99 COMP-3. 10 LILCS-LIS-"UANTITY PIC S9(7) COMP-3.
Figure 8.# $ayout of the $ine Item segment !hen accessed from its logical "ath
) 01 LINE-ITEM-SE!MENT. ) 05 LIS-DEST-PARENT-CONCAT-KEY. 10 LIS-ITEM-KEY-VENDOR PIC X(3). 10 LIS-ITEM-KEY-NUM ER PIC X(5). 05 LIS-UNIT-PRICE PIC S9(5)V99 COMP-3. 05 LIS-"UANTITY PIC S9(7) COMP-3.
Figure 8.% $ayout of the $ine Item &egment !hen accessed from its "hysical "ath
G)at you do need to !no+ is t)at t)e Segment 4O area you use 5or a *ogica* c)i*d segment a*+ays begins +it) t)e comp*ete concatenated !ey o5 t)e destination parent
N N
This is called the Destination 'arent !oncatenated ey 5D'! 6 The destination parent is the parent other than the one from which the logical child was accessed
A*t)oug) you must a*+ays code t)e D(C2 at t)e start o5 your Segment 4O area 5or a *ogica* c)i*d< t)e data t)at is actua**y stored in t)e database doesn@t necessari*y inc*ude t)e D(C2
N
-hether it does or not depends on how the DB% defined the segment
I I I I I
Asing *ogica* re*ations)ips +)en you process p)ysica* databases is use5u*< but *imiting n many app*ication programs< t)e D,A de5ines *ogica* databases< +)ic) is a sing*e structure based on *ogica* re*ations)ips speci5ied in t)e p)ysica* databases T)e *ogica* database is not a separate entity< t)oug) it appears to t)e app*ication programmer to be so T)e *ogica* database is instead< an a*ternati-e -ie+ o5 one or more p)ysica* databases To create a *ogica* database< t)e D,A )as to per5orm t)e D,DHEN process
N
Logical Databases
+or each physical database that will be involved in the logical structure, with all segments involved in the logical relationship so indicated +or the logical database itself
I I
T)en< (S,s 5or programs t)at +i** use t)e *ogica* database )a-e to be created =ust as +it) (S,s t)at speci5y p)ysica* databases< a (S, t)at speci5ies a *ogica* database can se*ecti-e*y present parts o5 it6
% concatenated segment is a single segment type in the logical database, but D#&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
N N
4ven segment types from the destination parents database that dont participate directly in the logical relationship are still part of the logical database ,owever, the structure may be changed
n a *ogica* database< t)e concatenated segment ma!es t)e connection bet+een segments t)at are de5ined in di55erent p)ysica* databases
N
%s 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
Payment
Ad*(stment
Line &tem
*ig-re 6+6 0 possib$e $ogica$ database -sing the C-stomer and In!entor ph sica$ databases
22 301 302
Figure 8.' DBDGEN out"ut for the customer inventory logical data ase
I
n t)e D,DHEN 5or a *ogica* database< a** o5 t)e segment types t)e D,A names must )a-e a*ready been de5ined in a p)ysica* database D,DHEN
N
%s a result, the DB% doesnt have to describe their si.es or the fields they contain in a logical database DBD;4< Instead, the S4;M macro in a logical database DBD;4< specifies the S"()!4 parameter to identify the related physical database segment and the database that it is a part of Its S"()!4 parameter specifies that it is actually stored in the physical database !)DBD as the segment !)!STS4; %lthough the segment names in this logical database and the associated physical databases are the same, they dont have to be %n e*ample of how the DB% specifies a concatenated segment In this case, the segment !)#I<S4; will be a concatenation of the physical segment !)#I<S4; from !)DBD and the physical segment I<ITMS4; from I<DBD
n 7igure E6C< t)e segment at t)e top o5 t)e *ogica* data structure is CRCSTSEH
N
Notice t)e SOARCE parameter in t)e SEH3 macro 5or CR" NSEH
N N
Notice t)at subordinate to t)is concatenated segment are t+o segment types 5rom t)e in-entory database: NVENSEH and N"OCSEH
N N
Both specify the '%)4<TA!#I<S4; This name refers to !)#I<S4; defined as a segment in the logical database, not to !)#I<S4; in the customer physical database
Note: Destination parent concatenated !ey and t)e se/uence 5ie*d in t)e *ogica* c)i*d user data may o-er*ap *ig-re 6+1? *ormat of a concatenated segment
I I I I
T)ere is no mystery to coding programs t)at process *ogica* databases 9ou issue D"4 ca**s against t)e (C, mas! 5or t)e database< and you e-a*uate t)e (C, status code to determine +)et)er or not t)e ca**s +ere success5u* G)en you process a concatenated segment< you need to !eep in mind t)at D"4 presents it to your program as a sing*e segment< a*t)oug) it actua**y contains data 5rom t+o segments 9ou process t)e concatenated segment +it) a sing*e ca**< and t)e 4O area you speci5y must be proper*y de5ined to contain t)e concatenated segment
01 *
CONCATENATED-SEGMENT. 05 CS-DEST-PARENT-CONCAT-$EY. 10 CS-DPC$-CUSTOMER-NUMBER 10 CS-DPC$-S"IP-TO-SE#UENCE 10 CS-DPC$-IN%OICE-NUMBER CS-LINE-ITEM-SEGMENT. 10 CS-LIS-ITEM-$EY. 15 CS-LIS-ITEM-$EY-%ENDOR 15 CS-LIS-ITEM-$EY-NUMBER 10 CS-LIS-UNIT-PRICE 10 CS-LIS-#UANTITY CS-RECEI%ABLE-SEGMENT. 10 CS-RS-IN%OICE-NUMBER 10 CS-RS-IN%OICE-DATE 10 CS-RS-PO-NUMBER 10 CS-RS-PRODUCT-TOTAL 10 CS-RS-CAS"-DISCOUNT 10 CS-RS-SALES-TAX 10 CS-RS-'REIG"T 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). S!(5)%!! S!(() X(6). X(6). X(25). S!(5)%!! S!(5)%!! S!(5)%!! S!(5)%!! S!(5)%!!
05
COMP-3. COMP-3.
05
* *ormat 6+11 *ormat of the concatenated segment that combines the $ine item and in!entor item segments
I
The logical child segment The destination parent segment The full D'! , followed by, The logical child user data
I I
T)e Segment 4O areas mentioned in D"4 ca**s must re5*ect t)is structure G)en you +or! +it) concatenated segments during update processing< it may be possib*e to add or c)ange data in bot) *ogica* c)i*d and t)e destination parent +it) a sing*e ca**
N
This also depends on the rules the DB% specified for the database
I I
7or an insert< be sure to pro-ide t)e D(C2 in t)e rig)t position 7or a rep*ace or de*ete< don@t c)ange t)e D(C2 or se/uence 5ie*d data in eit)er part o5 t)e concatenated segment
I I I I
C)ec!pointing
N N
D,As )a-e to ma!e sure t)at prob*ems +it) t)e system )a-e as *itt*e impact on t)e integrity o5 t)e database and t)e e55iciency o5 operations as possib*e
N
%s a result, the DB% has to devote a lot of attention to planning for database recovery and program restart in the even of failure +ailures can be of many $inds, including application abends, system software errors, hardware errors, and power failures
'eriodically ma$e bac$up copies of important datasets +rom the time the bac$up 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 re2posted to the bac$up copy to bring it up to date 4ven in a simple file2based application, this approach can be inappropriate, because it can ta$e a long time to re2post all accumulated transactions "ther applications have to wait until the file is restored and wor$ bac$log grows Database recovery ta$es much more time than file recovery, particularly if logical and secondary inde* relationships are involved
N N
A D"4 program cras)es in a +ay t)at is di55erent 5rom t)e +ay a standard program cras)es
N
This is because standard programs are e*ecuted directly by the operating system, while D#&I programs are not This is done by employing the abnormal termination routine Ma$es sure that database datasets are properly closed !ancels the 8obs Based on whether you had re9uested 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
G)en a D"4 program cras)es< t)e system inter-enes so t)at t)e damage to t)e database is contained
N
t is usua**y necessary to bac! out t)e c)anges made by t)e abending program< correct t)e error< and rerun t)e program
N
Logging
I I I I I I I
D"4 records a** t)e c)anges a program ma!es to its databases in a specia* 5i*e ca**ed a *og G)en a program c)anges a segment< D"4 *ogs bot) a >be5ore@ image and an >a5ter@ image o5 it T)ese segment images can be used to restore a database to its proper condition in t)e e-en o5 a program or system 5ai*ure D"4 uses a tec)ni/ue ca**ed >+rite-a)ead *ogging@ to record database c)anges Git) +rite-a)ead *ogging< a database c)ange is +ritten to t)e *og dataset be5ore it is +ritten to t)e actua* database dataset ,ecause t)e *og is a*+ays a)ead o5 t)e database< t)e reco-ery uti*ities can determine t)e status o5 any database c)ange ,asic *ogging operations are transparent to t)e app*ication programmer
N
-hen a program e*ecutes a call to change a database segment, D#&I ta$es care of the logging +or e*ample, a change made in a segment can cause changes in that segments parent, twins and dependents
!hanges to segments involved in logical relationships or secondary inde*es can cause even more log activity In a comple* data structure, even the simplest call to change a segment can cause e*tensive logging
So< +)en a D,A p*ans a database< )e )as to consider not on*y t)e database structure itse*5< but a*so t)e e55ects t)at structure +i** )a-e on *ogging per5ormance
G)en a batc) D"4 program abends< t+o approac)es are a-ai*ab*e 5or reco-ering t)e damaged databases: 5or+ard reco-ery and bac!+ard reco-ery 7or+ard Reco-ery
N
!hange data over a period of time is accumulated, then applied to a copy of the database as it e*isted before the changes began D#&I uses D#&I logs to store the change data
N N
D#&I uses the database at the time of an application programs failure and reverses all changes made to it since the program began 5or since the program issued the last chec$point6 #og records for the program are read bac$wards and their effects are reversed in the database -hen the bac$out is complete, the databases are in the same state they were in before the failure 5assuming another application program hasnt altered the database in the meantime6
<or-ard Recover%
4*ample: If a device error ma$es the current version of a database inaccessible, forward recovery is the techni9ue the operations staff will use to restore it %n old copy of the database has to be available %ll the changes posted to the database since the copy was made must be available
To meet t)e 5irst re/uirement< t)e operations sta55 can periodica**y run t)e Database mage Copy Ati*ity 0Section # o5 t)e 7ig6 C6# i**ustrates t)is1 A5ter t)e image copy o5 t)e database )as been made< many app*ication programs can be run t)at c)ange t)e database 0Section $ o5 7igure C6# i**ustrates t)is1
N N
%s the figure indicates, each program writes its own log That meets the second re9uirement of forward recovery: that all changes made since the previous image copy was ta$en are saved
,ecause e-ery e8ecution o5 a batc) D"4 app*ication program produces its o+n *og 5i*e< it is e55icient to periodica**y combine t)em< in case t)ey )a-e to be used to reco-er t)e database
N N
The Database !hange %ccumulation (tility is used for this It consolidates multiple logs and organi.es 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 5or change accumulation log6 which may be stored either on dis$ or on tape 5Section B of +igure J.1 shows this process6
I I
A5ter t)e Database C)ange Accumu*ation Ati*ity )as been run< app*ication programs t)at c)ange t)e database are sti** e8ecuted and eac) one o5 t)em +rites its o+n *og 0Section & o5 7igure C6# i**ustrates t)is1 5 somet)ing )appens to ma!e t)e database unusab*e 0*i!e a )ead cras) on t)e DASD t)at contains t)e database dataset1< it )as to be 5or+ard reco-ered T)e Dataset Reco-ery Ati*ity is used to restore t)e database
N
This utility wor$s 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 D#&I or accumulated change logs +orward )ecovery can be an aw$ward and time consuming process %pplication is limited to hardware crashes Bac$ward recovery, a simpler process is more appropriate for most situations
Disad-antages
N N N
Bac,out
+or e*ample, if a program encounters an invalid situation it cant handle, such as an une*pected status code, it can end in such a way as to cause an abend
 
It can do this by invo$ing an installation2standard termination routine that records and reports the problem, then abends This is called a pseudo2abend
I I I I I
T)en bac!out can be per5ormed to restore t)e databases to t)eir pre-ious condition A5ter t)e app*ication program or input data is corrected< t)e .ob can be run again T)e bac!out process is carried out by t)e ,atc) ,ac!out Ati*ity 0named D7S,,OBB1 Ander 3S< a database in use by a batc) program t)at abends can be bac!+ard-reco-ered t)roug) dynamic bac!out 5 t)e =C" t)at in-o!es t)e program speci5ies dynamic bac!out and t)e program 5ai*s< 3S automatica**y bac!s out a** database c)anges made since t)e program began< or since it issued its *ast c)ec!point - - - - - - - - - - - EXEC PGM)SORT - - - - - - - - - - - EXEC PGM)D'SRRC00* PARM)-DLI*GNC230*GNC230***********Y-* COND)(0*NE*GNC23005) - - - - - - - - - - - EXEC PGM)D'SRRC00* PARM)-DLI*D'SBBO00*GNC230-* COND)((0*E#*GNC23010)*E%EN) - - - - - - - - - - - EXEC PGM)SORT* COND)(0*NE) - - - - - - - - - - - EXEC PGM)GNCA&ERR* COND)(0*NE) - - - - - - - - - - - -
,,GNC23025 ,, - - - ,,ABENDC"$ ,, - - - -
n addition< an app*ication program under 3S can in-o!e dynamic bac!out by issuing a ro**bac! ca** 0RO",1 T)ere is se*dom cause to use RO", in a typica* batc) program and on*y in rare cases +i** an app*ication programmer be ca**ed upon to code suc) a ca**
Chec,/ointing
I
A c)ec!point is a point in t)e e8ecution o5 a program +)ere t)e database c)anges t)e program )as made are considered comp*ete and accurate
N N
Database changes made before the most recent chec$point are not reversed by bac$ward recovery Database changes logged after the most recent chec$point are not applied to an image copy of the database during forward recovery
I I I I I I
So< +)et)er bac!+ard or 5or+ard reco-ery is used< t)e database is restored to its condition at t)e most recent c)ec!point +)en t)e reco-ery process comp*etes T)e de5au*t 5or batc) programs is t)at t)e c)ec!point is t)e beginning o5 t)e program Ho+e-er< in a program t)at +i** process many update transactions< it is use5u* to be ab*e to te** D"4 at inter-a*s< t)at +)at )as been done so 5ar is o!ay T)en< is t)e program *ater abends< t)ere is no need to bac!out t)e database c)anges t)at )a-e been made upto t)at point A c)ec!point can be estab*is)ed using a c)ec!point ca** 0CH2(1 T)e c)ec!point ca** causes a c)ec!point record to be +ritten on t)e D"4 *og
N
It is the presence of a chec$point record in a log that tells the D#&I recovery utilities to stop their recovery processing Basic !hec$pointing
Depending on your program@s re/uirements< you can use t+o di55erent types o5 c)ec!pointing< name*y
N
#ets the programmer issue chec$point calls that the D#&I recovery utilities use during recovery processing %n advanced form of chec$pointing that is used in combination with the e*tended restart facility Together, symbolic chec$pointing and e*tended restart let the application programmer code programs so they can resume processing at the point following a chec$point
Symbolic !hec$pointing
 
Basic Chec,/ointing
I I
To use basic c)ec!pointing< a program is coded so t)at it periodica**y issues c)ec!point ca**s 7re/uency o5 issuing c)ec!points
N
N N
In a simple implementation, one chec$point is issued for every transaction performed, but this method is uncommon Most programs issue chec$points at intervals li$e every 1DD or 1DDD transactions Some applications also issue chec$points based on elapsed time, perhaps every 1D or 10 minutes
CALL
.CBLTDLI/
USING
The !%## function The '!B <ame %n eight2character wor$ing storage field that contains a chec$point ID
I I I
7or t)e CH2( ca** under 3S< t)e programmer supp*ies t)e name o5 a specia* (C, ca**ed t)e 4O (C, T)e 4O (C,< norma**y used 5or data communication programs< )as a 5ormat t)at is di55erent 5rom a database (C, T)e structure o5 t)e 4O (C, mas! is *i!e t)is: 01 * 05 05 'ILLER I-O-PCB-STATUS-CODE PIC X(10). PIC XX. I-O-PCB-MAS$.
I I I I I I I
T)e 4O (C, mas! must be *isted as t)e 5irst (C, mas! on t)e ENTR9 statement in t)e (ROCEDARE D V S ON nstead o5 t)e Segment 4O Area< an eig)t byte c)ec!point D 5ie*d is used n it< t)e program p*aces a -a*ue t)at identi5ies t)e c)ec!point record T)en< during reco-ery< t)e operations sta55 can use t)e c)ec!point D to restart t)e program< assuming t)e program is coded to +or! t)at +ay Git) basic c)ec!pointing< it is easy to !eep trac! o5 +)ere a program 5ai*s and to restore t)e database bac! to t)at point Ho+e-er< pic!ing up t)e e8ecution o5 t)e program at t)e intermediate point is di55icu*t T)e program )as to pro-ide a 5aci*ity to accept t)e c)ec!point D< and t)en must decide +)at to do +it) it
N
Typically this involves reading through any transaction files to s$ip transactions that were posted before the last chec$point It may also involve resetting wor$ing storage fields 5such as total fields6 to the values they had when the chec$point was ta$en In a database update program that prepares reports and updates non2D#&I datasets, recovery will be very comple* ,owever, if a program simply changes a database according to input transactions, recovery will be much simpler %s a result, it is practical to limit the function of a database update program that uses chec$pointing to database operationsG then restart is simpler
Henera**y< t)e more 5unctions t)e program per5orms< t)e more comp*e8 t)e considerations are 5or restart
N
S%mbolic Chec,/ointing
. . . 01 * 05 05 05 * 01 * 05 05 05 05 * 01 * 01 * 01 * 05 05 05 LENGT"-COUNT-'IELDS LENGT"-PRINT-'IELDS LENGT"-LONGEST-SEGMENT PIC S!(5) PIC S!(5) PIC S!(5) COMP COMP COMP %ALUE 011. %ALUE 0!. %ALUE 0128. LENGT"-'IELDS. RETSTART-1OR$-AREA PIC X(12) %ALUE SPACE. C"EC$POINT-ID PIC S!(8) %ALUE ERO. PAGE-NUMBER SPACE-CONTROL LINE-COUNT LINES-ON-PAGE PIC PIC PIC PIC S!(5) S!(3) S!(3) S!(3) COMP-3 COMP-3 COMP-3 COMP-3 %ALUE %ALUE %ALUE %ALUE 01. 01. 0!!. 050. PRINT-'IELDS. CAS"-RECEI%ED %ALID-TRANSACTION-COUNT IN%ALID-TRANSACTION-COUNT PIC S!(()%!! COMP-3 %ALUE PIC S!(5) COMP-3 %ALUE PIC S!(5) COMP-3 %ALUE ERO. ERO. ERO.
COUNT-'IELDS.
. . . * LIN$AGE SECTION. * 01 * 05 05 . . . * PROCEDURE DI%ISION. * ENTRY -DLITCBLUSING I-O-PCB . . . 'ILLER I-O-PCB-STATUS-CODE PIC X(10). PIC XX. I-O-PCB.
* 000-POST-CAS"-RECEIPTS. * CALL USING DLI-XRST I-O-PCB LENGT"-LONGEST-SEGMENT RESTART-1OR$-AREA LENGT"-COUNT-'IELDS COUNT-'IELDS LENGT"-PRINT-'IELDS PRINT-'IELDS. I' I-O-PCB-STATUS-CODE NOT ) SPACE DISPLAY -CR1000 I 1 RESTART 'AILED -- STATUS CODE I-O-PCB-STATUS-CODE ELSE I' RESTART-1OR$-AREA NOT ) SPACE PER'ORM 100-REPOSITION-DATA-BASE. . . . * 230-ISSUE-C"EC$POINT-CALL. * ADD 1 TO C"EC$POINT-ID. CALL -CBLTDLI- USING DLI-C"$P I-O-PCB LENGT"-LONGEST-SEGMENT C"EC$POINT-ID LENGT"-COUNT-'IELDS COUNT-'IELDS LENGT"-PRINT-'IELDS PRINT-'IELDS. I' I-O-PCB-STATUS-CODE NOT ) SPACE DISPLAY -CR1000 I 2 C"EC$POINT 'AILED -- STATUS CODE I-O-PCB-STATUS-CODE . . . Symbo*ic c)ec!pointing is simi*ar to basic c)ec!pointing in t)at a CH2( ca** is used to +rite c)ec!point records to a D"4 *og -CBLTDLI-
Ho+e-er< symbo*ic c)ec!pointing< a*ong +it) e8tended restart< pro-ide an ad-antage: t)ey *et t)e program store program data a*ong +it) t)e c)ec!point records and retrie-e t)at data +)en it is necessary to restart t)e program a5ter a 5ai*ure G)i*e using symbo*ic c)ec!pointing< t)e c)ec!point ca** begins +it) t)e same t)ree parameters as t)e basic c)ec!point ca**:
N N N
The !, ' function code The '!B Mas$, and, The eight byte chec$point ID field
I I
A5ter t)ese< t)e programmer can code upto se-en pairs o5 5ie*d names to speci5y t)e GOR2 NH-STORAHE areas )e +ants to )a-e sa-ed a*ong +it) t)e c)ec!point record n eac) pair<
N
The first item is the name of a full word binary field, 'I! SJ5D06 !"M', that contains the length of the data area to be saved The second is the name of the data area itself
I I I
A program t)at uses e8tended restart s)ou*d a*+ays issue an :RST ca** be5ore it issues any ot)er D"4 ca**s On t)e :RST ca**< t)e same +or!ing storage 5ie*ds t)at are *isted in t)e CH2( ca** are used During norma* e8ecution< t)e :RST ca** does not)ing
N
,ut +)en t)e program is being restarted< D"4 retrie-es t)e -a*ues stored in t)e c)ec!point record and restores t)e speci5ied 5ie*ds
**ustrati-e (rogram
N
,as two data areas 5!"(<T2+I4#DS and ')I<T2+I4#DS6 that are to be saved by the chec$point calls and restored during restart processing The first two length fields 5#4<;T,2!"(<T2+I4#DS and #4<;T,2')I<T2+I4#DS6 correspond to the two data areas that need to be saved and are initiali.ed with the si.es of those areas The third length field, #4<;T,2#"<;4ST2S4;M4<T is a 'I! SJ506 binary field that contains the length of the longest I&" area the program uses 5in other words, the length of the longest segment or path of segments the program processes6 D#&I uses this value to ac9uire a buffer area
%s the program e*ecutes, it periodically increments the !,4! '"I<T2ID field and issues the chec$point call This call uses the specified areas to be saved on the log along with the chec$point record If the program fails, the problem that caused the failure is corrected and the affected databases are restored using forward or bac$ward recovery The program is then restarted The operator supplies the last chec$point ID on the '%)M for the 4H4! that invo$es the program
N N N N N
,,GNC8!0BD PROC ,,* ,,****************************************** ,,GNC8!0BD EXEC PGM)D'SRRC00* ,, PARM)(BMP*GNC!030*GNC!030***110028***2C"$PTID* ,, ****2EN%1*AGNALL*****5) ,,******************************************
N
Then the H)ST call, which is the first call in the program, $nows the program should restart rather than begin a normal e*ecution Instead of specifying the !,4! '"I<T2ID field, the H)ST call specifies a 1/2byte wor$ area This field named, )4ST%)T2-") 2%)4% must be initiali.ed with spaces If the program is being restarted, D#&I places the chec$point ID value in this fieldG otherwise D#&I leaves this field blan$ %fter these items, the H)ST call specifies the length and data fields for any saved data in the same se9uence as they appeared in the !, ' call
In the illustrative program, there is one difference between the H)ST call and the !, ' call
N N N N
N N
If the program is being restarted, D#&I retrieves the values for those fields from the chec$point record If not, D#&I doesnt change the values of those fields +irst, it chec$s to see if the restart call was successful
A5ter t)e :RST ca**< t)e program c)ec!s 5or t+o conditions
N
If the status code field in the I&" '!B mas$ is not spaces, the restart call failed2 so an appropriate message is displayed
If the call didnt fail, the program then tests to see if this is a normal e*ecution or a restart e*ecution by chec$ing the restart wor$ area
If that field isnt spaces, the program is being restarted, so a module is invo$ed to reestablish position in the database
'han, 3ou