Sei sulla pagina 1di 52

IDMS BATCH COBOL PROGRAMMING

by Neal Walters
Amerisoft Inc. 1998 Last Updated: November 17, 1998

This document is licensed for use by customers of the IDMS Tutorial program from Amerisoft Inc.

Intended Audiences: 1) Batch COBOL Programmers 2) Or CICS/PL1 programmers who need an overview of Batch IDMS Programming Major Topics: 1) Details on how to code and maintain Batch COBOL IDMS programs 2) Brief overview of IDMS and DBMSs 3) How to compile programs 4) Testing and debugging techniques 5) Error Handling 6) DML Verbs

To be used in conjunction with IDMS FUNDAMENTALS course book by Amerisoft Inc.

email: nwalters@sprynet.com web site: http://www.amerisoftinc.com/mainframe.htm

Table of Contents
Overview of Network Databases ......................................................................................... 1 DBMS Overview ............................................................................................................. 1 Why a DBMS? ................................................................................................................ 1 IDMS and SQL ............................................................................................................... 2 IDMS Overview .............................................................................................................. 3 IDMS Schema or Bachman Diagram................................................................................ 4 DML - Data Manipulation Language ............................................................................... 5 Two useful Tools............................................................................................................. 6 CA/IDMS Manuals Relating to DML and COBOL: ......................................................... 6 The DML Precompiler......................................................................................................... 6 Precompiler Options ........................................................................................................ 7 Precompiler Directives..................................................................................................... 9 ENVIRONMENT DIVISION ..................................................................................... 9 DATA DIVISION: SCHEMA SECTION AND WORKING-STORAGE .................. 11 Figure 8 shows where the SCHEMA SECTION is added to the program, and how to copy IDMS records into the program......................................................................... 11 PROCEDURE DIVISION DECLARATIVES........................................................... 12 ERROR HANDLING........................................................................................................ 14 Autostatus vs Non-Autostatus ....................................................................................... 14 IDMS-STATUS Routine ............................................................................................... 17 MVS JOB LOG............................................................................................................. 19 The Programs SYSOUT............................................................................................... 20 IDMS Error Status ........................................................................................................ 20 IDMS RETRIEVAL COMMANDS .................................................................................. 21 1) FIND/OBTAIN CALC/DUPLICATE........................................................................ 22 2) FIND/OBTAIN CURRENT and 6) FIND/OBTAIN NEXT WITHIN SET/AREA .... 24 3) FIND/OBTAIN DBKEY........................................................................................... 26 4) FIND/OBTAIN OWNER WITHIN set-name ............................................................ 27 5) FIND/OBTAIN WITHIN SET USING SORT KEY.................................................. 28 IDMS UPDATE COMMANDS ........................................................................................ 29 MODIFY EXAMPLE: .................................................................................................. 30 STORE EXAMPLE: ..................................................................................................... 31 ERASE COMMAND: ................................................................................................... 32 ERASE EXAMPLE ...................................................................................................... 33 CONNECT AND DISCONNECT................................................................................. 34 CONNECT EXAMPLE:............................................................................................ 35 DISCONNECT EXAMPLE: ..................................................................................... 35 OTHER REQUIRED COMMANDS:................................................................................ 36 The READY Command................................................................................................. 37 IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998 page ii Use by license agreement only.

The COMMIT Command .............................................................................................. 38 The TWO BIND Commands.......................................................................................... 41 The FINISH and ROLLBACK Commands .................................................................... 42 IDMS Online Programming ............................................................................................... 43 IDMS Online Programming Overview ........................................................................... 43 Sample IDMS/DC Commands ....................................................................................... 44 Overview of ADS .......................................................................................................... 45 Overview of CICS ......................................................................................................... 46 Overview of IDMS/DC.................................................................................................. 46 Overview of Native VSAM............................................................................................ 46 Maintaining IDMS Programs ............................................................................................. 47 Files on CD/ROM.............................................................................................................. 49

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page iii Use by license agreement only.

Overview of Network Databases DBMS Overview A DBMS (Database Management System) is an advanced method of maintaining data. Many sites have left sequential and random files behind and develop all new systems under a DBMS. There are three types of DBMS: 1) relational (such as DB2/SQL or Oracle) 2) hierarchical (such as IMS) 3) network (such as IDMS) Relational database deal with tables where the COBOL program can issue SQL commands to select and join from various tables. Each table is similar to a flat file, and each row in the table is the same as a record in the flat file. A hierarchical database establishes a parent child relationship between records. A netwhork database is similar to a hierarchical database, but is more flexible in that the relationships can be more complex. For example, a child record can have more than one parent. Many companies adopted IDMS as the Database of choice in the 80s. Although in the late 90s, most companies are using relational databases, IDMS still has a strong foothold in major corporations around the world. If often costs millions of dollars to convert a system from one DBMS technology to another, so many companies continue to run older systems until they are obsolete or can be re-written. Other companies still believe that IDMS is a better choice than todays relational alternatives. IDMS was originally marketed by a company called Cullinet, but is now sold and supported by Computer Associates. Why a DBMS? A DBMS typically has the following benefits over sequential and VSAM files: 1) centralized control often with a data dictionary or repository for the meta-data (i.e. the data about the data) and controlled by the database administration group 2) concurrent batch and online update and retrieval 3) improved recovery (backout or rollback procedures) 4) improved record locking to prevent simultaneous update of same record(s) and to allow programs to wait for a lock to be released - then continue execution. IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998 page 1 Use by license agreement only.

IDMS and SQL With release 12.0 of IDMS, an SQL option became available as an extra-cost product. Since SQL is covered in another chapter of this book, IDMS/SQL will not be discussed in this chapter. One of the unique aspects of the IDMS/SQL option is that SQL can be used against either an IDMS/Relational database or an IDMS/Network database. Another advantage of the SQL option is the ODBC capability to download data to PCs or to access IDMS mainframe data on client server platforms.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 2 Use by license agreement only.

IDMS Overview In IDMS terminology, a parent record is called an OWNER, and a child record is called a MEMBER. Records are connected to each other via SETs. All database relationships are predefined in a schema. A subschema is a smaller view of the schema that a COBOL program uses to access the database. Some sites have one large global subschema, while other sites have many small subschemas. When dealing with IDMS, there is usually a Database Administration (DBA) group that is responsible for defining the databases (and for keeping the production databases well organized). IDMS records are stored in IDMS areas, each of which has a physical page range. The page range and page size of each area determines how much space is available in any given area. Usually, each area is mapped to one physical file (data set), but in the cases of large areas, one area may be mapped to a series of data set names. It is also possible for one physical data set to contain several areas. In IDMS 12.0 and after, several related areas are grouped together to form a SEGMENT. Segments, buffering, and journalling all defined in a DMCL (Device Media Control Language) created by the DBA. Each IDMS record occurrence, when stored, is assigned a DBKEY, which consists of the pagenumber and line-index (usually between 1 and 256). DBKEYs are referenced as an S9(8) COMP field in COBOL. To convert this number to a page and line number, usually the dbkey is divided by 256 to get the page number, and the remainder is the line number (see the sample IDMS programs on the CD/ROM for a program that converts DBKEYs from one format to another and gives full details.) An IDMS system is called a Central Version, or CV for short. It is common to say that the test CV will come down at 9 pm and back up at 6 am. When the IDMS CV is down, IDMS programmer testing may be limited. Some sites have different CVs for different applications, for instance a development CV, a maintenance CV, a Y2K Conversion CV, and a production CV. IDMS programs can run in local-mode or under the CV. When running under the CV, all database I/O is done by by the Central Version (one task running on the computer). Usually, for the sake of speed, retrieval only jobs run in local-mode, and update jobs run under the CV to allow for concurrent update and record locking. While update jobs can be run in local mode, this feature is seldom used because the areas must be varied out of update mode - thus preventing online and other batch jobs from concurrent update. This is sometimes done on weekends to speed up long running batch jobs. Running under the CV incurs typical DBMS overhead such as journalling, buffering, and record-locking. All online programs always run under the CV. Most sites use the presence of a //SYSCTL JCL statement to indicate that the job is running under the CV.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 3 Use by license agreement only.

IDMS Schema or Bachman Diagram Most IDMS sites publish a book or chart of schema diagrams, also called Bachman diagrams (after Charles Bachman, one of the pioneers in database technology). Each IDMS record-type is illustrated by a box. A set relationship is shown by connecting two recordstogether. All sets represent a one-to-many relationship (where the point of the arrow indicates the child relationship). IDMS records can be stored in three location modes: 1) CALC - a randomly assigned hash key, based on any logical key(s) in the record 2) VIA - records are physically stored near their owner record (this allows for extremely rapid access) 3) DIRECT - this storage mode is most commonly used for audit trails (the record can be stored with the highest dbkey in the area, or a specific dbkey can be provided and the record is stored at that location) ???Editor: I have asked Computer Associates for permission to reprint this schema diagram - but have not yet received anything from them in writing. They should be in contact with Tracy Dunkelberger. Figure 23.1. IDMS Schema Diagram (Employee Demo Database) **Insert figure here - I am sending a photocopy of a diagram from a Computer Associates Manual. I do not have this diagram in computer format. (This is the only figure in this document - all other examples are listings.) **

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 4 Use by license agreement only.

Each bachman record box consist of four lines: line 1 contains the record-name line 2 contains the record-id, F,FC,V,VC for Fixed, Fixed Compressed, Variable, Variable Compressed the record length (in bytes) the location mode (CALC, VIA, or DIRECT) line 3 contains the CALC key or VIA SET-NAME, followed by the duplicates option (DN=Duplicates Not Allowed, DF=Duplicates First, DL=Duplicates Last) line 4 contains the physical AREA-NAME Some sites add the approximate record occurrence count on the fourth line. This sometimes helps the programmer to create a faster navigation path. Usually, a copy of the IDMSRPTS utility is used with the schema diagram. This report contain the same information that is on the diagram, along with a full listing of all the elements in each record. A triangle symbol on a schema diagram represents an indexed set. This is a set that has a pre-defined sort key assigned. Indexes are used 1) as a rapid access entry point into the database based on a logical key value and 2) as a means of quickly displaying sorted data on an online retrieval transaction. DML - Data Manipulation Language IDMS databases are maintained by executing DML (Data Manipulation Language) commands. The same commands can be used from COBOL, Assembler, PL/1 or even FORTRAN. The DML commands allow the programmer to navigate the database (using OBTAIN commmnds) and to make changes by issuing simple commands like MODIFY, STORE and ERASE. The differences between DML and SQL show that there are two primary differences between an IDMS network database and a relational database: 1) With IDMS, all the set relationships are pre-defined, i.e. a program cannot issue a JOIN between two record types. There must be a pre-defined set relationship between the two record types (and this set relationship is drawn on the schema diagram). 2) With IDMS, the programmer chooses the his preferred database navigation strategy (which hopefully is the fastest). With relational databases, the programmer just queries for the desired data, and the DBMS chooses the access logic. Thus, as the metrics of an IDMS database change, a programs DML navigation may become slower. Sometimes, the programs runtime can be improved by changing the DML navigation path. For example, it might be better to walk an index set when there are only 100 records in the database, but when there are one million records, it might be faster to do an area sweep for the same records. IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998 page 5 Use by license agreement only.

Two useful Tools Computer Associates (CA) has an additional-cost product called DMLO which stands for Data Manipulation Language Online. A competitor product called DBOL (Database Online) is sold by Allen Systems Group. These two products allow programmers to issue and practice DML commands online and interactively. A programmer often uses these products for the following purposes: 1) to test a DML navigation path before writing a COBOL program 2) to help debug a COBOL program by verifying DML navigation or values of fields in a database CA/IDMS Manuals Relating to DML and COBOL: Bookname in IBM/READER CAIDDMLC CAIDNDML CAIDMSG Order Number R005/&F0CBE R005/&F0NPE R005/&F0M1E R005/&F0M2E R005/&F0M3E R005/&F0M4E RC05/&F0PQE Manual Name CA-IDMS DML Reference COBOL CA-IDMS DML Navigational DML Programming CA-IDMS Messages and Codes (Volumes 1 through 4)

CAIDQPRG

CA-IDMS Programming Quick Reference Figure 1 -Recommended IDMS Manuals for COBOL Programmers The DML Precompiler The DML Precompiler, also called the DML pre-processor, converts high-level DML (Data Manipulation Language) statements to standard COBOL calls to the appropriate IDMS subroutine. A sample JCL (Job Control Language) to execute the preprocessor, the COBOL compiler, and the linkage editor can be found in file COMPJCL on the CD/ROM that accompanies this book. Figure 2 and Figure 3 show the DML code before and after expansion by the DML precompiler. Since OBTAIN CALC is not recognized by COBOL, the DML Precompiler converts this statement to a CALL IDMS statement with the appropriate using parameters. Most programmers to do not need to understand the format of the CALL IDMS, because the code is maintained in the high-level DML language. Note two things about this example: IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998 page 6 Use by license agreement only.

1) The OBTAIN CALC statement remains in the program, but is commented out 2) A unique DML-SEQUENCE number is assigned to each CALL to IDMS. This DML-SEQUENCE number is displayed in the IDMS ERRORSTATUS routine; thus, if the program fails with a bad IDMS STATUS, the DML-SEQUENCE number is used to identify which IDMS DML VERB caused the problem.
028400 028500 028600 028800 028900 029000 029010 029100 029200 029300 029400 1000-OBTAIN-EMPLOYEE. MOVE '123456789' TO EMPLOYEE-NUM OBTAIN CALC EMPLOYEE-REC IF DB-REC-NOT-FOUND PERFORM 1100-EMP-NOT-FOUND THRU 1100-EXIT ELSE PERFORM IDMS-STATUS PERFORM 1200-EMP-FOUND THRU 1200-EXIT END-IF . 1000-EXIT. EXIT.

Figure 2 - Code Submitted to DML Preprocessor


000332 000333 000334 000335 000336 000337 000338 000339 000340 000341 000342 000343 000344 000345 000346 000347 1000-OBTAIN-EMPLOYEE. MOVE '123456789' TO EMPLOYEE-NUM * OBTAIN CALC EMPLOYEE-REC MOVE 4 TO DML-SEQUENCE CALL 'IDMS' USING SUBSCHEMA-CTRL IDBMSCOM (32) SR2001 IDBMSCOM (43); IF DB-REC-NOT-FOUND PERFORM 1100-EMP-NOT-FOUND THRU 1100-EXIT ELSE PERFORM IDMS-STATUS PERFORM 1200-EMP-FOUND THRU 1200-EXIT END-IF . 1000-EXIT. EXIT.

Figure 3 - Code as Output from the DML Preprocessor Precompiler Options PRECOMPILER OPTIONS tell the precompiler how to do its work.
*RETRIEVAL *DMLIST *NODMLIST

NOTE: These three lines are standard COBOL comments (the asterisk should begin in column 7).

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 7 Use by license agreement only.

A feature of the DML PRECOMPILER is that it can update the IDMS Integrated Data Dictionary (IDD) each time the program is compiled. This can be both a blessing and curse. The advantage is that detailed information about the program will be automatically documented in the dictionary. The disadvantage is that large programs can create a large number of record locks on the dictionary, causing other IDD users and other program precompiles to slow down or to ABEND with deadlocks. Figure 4 shows a sample of program information that is automatically stored in IDD by the precompiler. This information is available within the online task IDD or by running a batch IDD job.
DIS PROG DBATDEMO AS SYN. ADD PROGRAM NAME IS DBATDEMO VERSION IS 1 *+ DATE CREATED IS 04/14/98 *+ DATE LAST COMPILED IS 04/14/98 *+ NUMBER OF TIMES COMPILED IS 1 PUBLIC ACCESS IS ALLOWED FOR ALL ESTIMATED LINES ARE 339 PROGRAM CALLED IS IDMS VERSION IS 1 PROGRAM CALLED IS IDMSERR1 VERSION IS 1 PROGRAM CALLED IS ABORT VERSION IS 1 MODULE USED IDMS-STATUS VERSION IS 11 LANGUAGE IS COBOL RECORD COPIED SUBSCHEMA-CTRL VERSION IS 2 RECORD COPIED EMPLOYEE-REC VERSION IS 1 RECORD COPIED DB-STATISTICS VERSION IS 1 SUBSCHEMA IS DBATSS01 OF SCHEMA DBATSC01 VERSION IS 1 AREA DBATEST1-AREA READIED FOR UPDATE RECORD EMPLOYEE-REC BIND RECORD EMPLOYEE-REC OBTAIN MODE IS BATCH LANGUAGE IS COBOL .

Figure 4 - IDD Display Program Figure 5 shows how the IDD can also cross-references records back to programs:
DIS REC EMPLOYEE-REC WITH PROGRAMS AS SYN. ADD RECORD NAME IS EMPLOYEE-REC VERSION IS 1 RECORD NAME SYNONYM IS EMPLOYEE-REC VERSION 1 *+ COPIED INTO PROGRAM DBATDEMO VERSION 1 .

Figure 5 - IDD Display Record Most cross reference information can be also be obtained by scanning the source code (using TSO/ISPF 3.14, PANSCAN for Panvalet, or a Librarian Scan for Librarian). Therefore, many sites disable the auto-update of the dictionary by including the *RETRIEVAL command at the top of each program. This is often done by your compile PROC which concatenates a one line member IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998 page 8 Use by license agreement only.

that contains just the line *RETRIEVAL. An advantage of running in RETRIEVAL mode is that the program can run in local mode rather than CV mode. NOTE: The precompiler runs vary fast for small subschemas, but when a subschema contains 50 or 100 or 150 records, the precompiler can run for several minutes. The *DMLIST or *NODMLIST option specifies that the source listing it to be displayed as output from the preprocessor. The default is *NODMLIST. A listing of error messages is always produced. However, the errors typically point to the line number of the error, and with *NODMLIST is can be difficult to find the error. Precompiler Directives PRECOMPILER DIRECTIVES also affect the way the DML PRECOMPILER works.
ENVIRONMENT DIVISION

The first required directive is the IDMS-CONTROL SECTION in the ENVIRONMENT DIVISION and is shown in Figure 6.
008700 008800 009000 009100 009200 009300 009400 009500 ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT INPUT1-FILE ASSIGN TO INPUT1. IDMS-CONTROL SECTION. PROTOCOL. MODE IS BATCH DEBUG IDMS-RECORDS MANUAL.

Figure 6 - Precompiler/Environment Division In place of the word BATCH (in the above figure), specify IDMSDC for online programs (programs that will use IDMS services such as MAPIN/MAPOUT), or DC-BATCH for programs that run in batch but require DC services such as GET QUEUE, or CICS-AUTOSTATUS.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 9 Use by license agreement only.

There are several common modes listed below. Check with the DBA or reference manual for a complete listing. Some sites may also have defined their own customized modes. BATCH BATCH-AUTOSTATUS CICS CICS-AUTOSTATUS DC-BATCH IDMS-DC Typical batch program Typical batch program with AUTOSTATUS on Typical CICS program Typical CICS program with AUTOSTATUS on For batch programs that need some typically online services such as GET QUEUE or PUT QUEUE. For online IDMS programs that will use IDMS services such as MAP IN, MAP OUT, READ TERMINAL, or GET QUEUE Figure 7 - Common Modes The word DEBUG is optional (but almost always used), and causes the DML-SEQUENCE numbers to be generated for each DML VERB. The AUTOSTATUS protocols are discussed in the next section on ERRORHANDLING. The IDMS RECORDS MANUAL clause specifies that the program will manually include the required COPY IDMS statements in the WORKING-STORAGE or LINKAGE SECTION. Instead, if IDMS RECORDS WITHIN WORKING-STORAGE is specified, then all records in the entire subschema will automatically be copied into the program. This works fine for small subschemas, but may be inappropriate for larger subschemas.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 10 Use by license agreement only.

DATA DIVISION: SCHEMA SECTION AND WORKING-STORAGE Figure 8 shows where the SCHEMA SECTION is added to the program, and how to copy IDMS records into the program.
010000 010100 010200 010300 010400 010500 010600 010700 011000 011100 011200 011300 011400 011500 011600 DATA DIVISION FILE SECTION. FD INPUT1-FILE LABEL RECORDS ARE STANDARD BLOCK CONTAINS 0 RECORDS. 01 INPUT1-REC PIC X(80). SCHEMA SECTION. DB DBATSS01 WITHIN DBATSC01. WORKING-STORAGE SECTION. COPY IDMS SUBSCHEMA-CONTROL. COPY IDMS RECORD EMPLOYEE-REC. COPY IDMS DB-STATISTICS.

Figure 8 - Precompiler/Data Division The SCHEMA SECTION simply identifies the name of the schema and subschema. Each source program can only access one schema (a called subroutine can be used to access data from a different schema). In the WORKING-STORAGE section, COPY IDMS statements are used to build the required record layouts from the data dictionary (IDD). (If the IDMS RECORDS WITHIN WORKING-TORAGE clause was used, then all subschema records are automatically copied, and COPY IDMS record statements do not need to be coded. The SUBSCHEMA-CONTROL is actually a special code word for four record-names: SUBSCHEMA-CTRL, SUBSCHEMA-RECNAMES, SUBSCHEMASETNAMES, and SUBSCHEMA-AREANAMES. Every program must include these, as they are used in the CALL IDMS statements. DB-STATISTICS is a optional record used with the ACCEPT STATISTICS command. Many programs ACCEPT and display the IDMS statistics at the end of the program. This information is extremely useful for debugging and/or improving performance of a program.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 11 Use by license agreement only.

PROCEDURE DIVISION DECLARATIVES

Figure 9 and Figure 10 show how and where the COPY IDMS SUBSCHEMA-BINDS (the first listing is before the DML precompiler, the second listing is after the expansion by the precompiler).
025800 025900 026000 026100 026200 026300 026400 026700 026710 028000 028100 0500-INITIALIZE. ACCEPT TODAYS-DATE FROM DATE. ACCEPT TODAYS-TIME FROM TIME. DISPLAY 'START: DBATDEMO - RELOAD AUDHST-RECS ' DISPLAY 'DATE = ' TODAYS-DATE ' TIME = ' TODAYS-TIME. COPY IDMS SUBSCHEMA-BINDS. 0500-EXIT. EXIT.

Figure 9 - Precompiler Directives in the Procedure Division

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 12 Use by license agreement only.

0500-INITIALIZE. ACCEPT TODAYS-DATE FROM DATE. ACCEPT TODAYS-TIME FROM TIME. DISPLAY 'START: DBATDEMO - RELOAD AUDHST-RECS ' DISPLAY 'DATE = ' TODAYS-DATE ' TIME = ' TODAYS-TIME. * * COPY IDMS SUBSCHEMA-BINDS. MOVE 'DBATDEMO' TO PROGRAM-NAME BIND RUN-UNIT MOVE 1 TO DML-SEQUENCE CALL 'IDMS' USING SUBSCHEMA-CTRL IDBMSCOM (59) SUBSCHEMA-CTRL SUBSCHEMA-SSNAME; BIND JOB-REC MOVE 2 TO DML-SEQUENCE CALL 'IDMS' USING SUBSCHEMA-CTRL IDBMSCOM (48) SR2003 JOB-REC; BIND EMPLOYEE-REC. MOVE 3 TO DML-SEQUENCE CALL 'IDMS' USING SUBSCHEMA-CTRL IDBMSCOM (48) SR2001 EMPLOYEE-REC. 0500-EXIT. EXIT.

Figure 10 - Same after Precompiler Expansion The COPY IDMS SUBSCHEMA-BINDS accomplishes three things: 1) The program-name from the PROGRAM-ID statement is moved to a field called PROGRAM-NAME. This is useful to the DBA when monitoring the system. 2) The BIND RUN UNIT statement is generated 3) A BIND RECORD statement is generated for each database record (either each record in the subschema or each record included into the program with COPY IDMS statements). This COPY statement does NOT generate a READY statement for each database area. NOTE: Some sites make use of Logical Record Facility (LRF) which results in several changes to this information in this section. LRF allows the DBA or programmers to create logical records in the subschema - where a logical record consists of one or more physical records. Special processing logic is actually coded in the subschema, special return-codes can be set, and much of the database navigation is done by the subschema instead of the COBOL IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998 page 13 Use by license agreement only.

program. Any site using LRF should have special instructions available for its unique implementation. ERROR HANDLING Autostatus vs Non-Autostatus Note that some modes (see Figure 7) contain the word AUTOSTATUS. This causes the precompiler to automatically generate a PERFORM IDMS-STATUS statement after each DML command. It is a matter of a sites coding standards or a programmers own personal preference as to whether autostatus is used. Some people prefer AUTOSTATUS, because if a programmer forgets to check the ERROR-STATUS and the program keeps running, then logic errors occur which can be difficult to debug. Some people prefer not using AUTOSTATUS because the code looks cleaner. Use of AUTOSTATUS requires coding an ON statement for any allowable errors. For instance, an ERROR-STATUS of 0326 or DB-REC-NOTFOUND is common when doing an OBTAIN CALC DML command. Thus, when using AUTOSTATUS, the programmer must code one ON error statement for each anticipated status. Figure 11 shows a program coded to use AUTOSTATUS, and Figure 12 shows the same code after it is expanded by the DML precompiler. There are several COBOL 88-level working-storage variables defined for the most common IDMS error codes. The definition of these 88-levels is available in Figure 15.
028400 028500 028600 028700 028800 028900 029000 029100 029200 1000-OBTAIN-EMPLOYEE. MOVE '123456789' TO EMPLOYEE-NUM OBTAIN CALC EMPLOYEE-REC ON DB-REC-NOT-FOUND PERFORM 1100-EMP-NOT-FOUND THRU 1100-EXIT . PERFORM 1200-EMP-FOUND THRU 1200-EXIT . 1000-EXIT. EXIT.

Figure 11 - Sample OBTAIN with AUTOSTATUS

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 14 Use by license agreement only.

The above code gets translated to the following


000336 000337 000338 000339 000340 000341 000342 000343 000344 000345 000346 000347 000348 000349 000350 000351 1000-OBTAIN-EMPLOYEE. MOVE '123456789' TO EMPLOYEE-NUM * OBTAIN CALC EMPLOYEE-REC * ON DB-REC-NOT-FOUND MOVE 4 TO DML-SEQUENCE CALL 'IDMS' USING SUBSCHEMA-CTRL IDBMSCOM (32) SR2001 IDBMSCOM (43) IF NOT DB-REC-NOT-FOUND PERFORM IDMS-STATUS; ELSE PERFORM 1100-EMP-NOT-FOUND THRU 1100-EXIT . PERFORM 1200-EMP-FOUND THRU 1200-EXIT . 1000-EXIT. EXIT.

Figure 12 - Same after precompiler expansion Figure 13 shows the same code as Figure 12 when not using AUTOSTATUS. The programmer should code the appropriate PERFORM IDMS-STATUS after each DML verb (after checking for any normally expected errors - such as the DB-REC-NOT-FOUND condition). Note the addition of line 28950.
028400 028500 028600 028700 028800 028900 028950 029000 029100 029200 1000-OBTAIN-EMPLOYEE. MOVE '123456789' TO EMPLOYEE-NUM OBTAIN CALC EMPLOYEE-REC IF DB-REC-NOT-FOUND PERFORM 1100-EMP-NOT-FOUND THRU 1100-EXIT . PERFORM IDMS-STATUS PERFORM 1200-EMP-FOUND THRU 1200-EXIT . 1000-EXIT. EXIT.

Figure 13 - Obtain with NON-AUTOSTATUS Some programmers will CODE a variation of the Figure 13 as shown in Figure 14(note the addition of line 28910). This avoids performing the IDMS-STATUS paragraph unless needed but results in two lines of code error-checking code instead of one.
028400 028500 028600 028700 028800 028900 028910 028950 029000 029100 029200 1000-OBTAIN-EMPLOYEE. MOVE '123456789' TO EMPLOYEE-NUM OBTAIN CALC EMPLOYEE-REC IF DB-REC-NOT-FOUND PERFORM 1100-EMP-NOT-FOUND THRU 1100-EXIT . IF DB-ANY-ERROR PERFORM IDMS-STATUS. PERFORM 1200-EMP-FOUND THRU 1200-EXIT . 1000-EXIT. EXIT.

Figure 14 - Alternative Coding

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 15 Use by license agreement only.

*COPY IDMS SUBSCHEMA-CONTROL. 01 SUBSCHEMA-CTRL. 03 PROGRAM-NAME 03 ERROR-STATUS 88 88 88 88 88 03 DBKEY

PIC X(8) VALUE SPACES. PIC X(4) VALUE '1400'. DB-STATUS-OK VALUE '0000'. ANY-STATUS VALUE ' ' THRU '9999'. ANY-ERROR-STATUS VALUE '0001' THRU '9999'. DB-END-OF-SET VALUE '0307'. DB-REC-NOT-FOUND VALUE '0326'. PIC S9(8) COMP SYNC.

Figure 15 - Error-Status and 88-levels

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 16 Use by license agreement only.

IDMS-STATUS Routine Figure 16 shows the common code that is copied into all batch IDMS programs. Your site may have made minor modifications to this code. The code itself is stored on the data dictionary (IDD) as a module with source code. The CALL ABORT statement results in the U2222 Abend as shown in Figure 16.
*COPY IDMS IDMS-STATUS. ****************************************************************** IDMS-STATUS. ************************ V 33 BATCH-AUTOSTATUS ******************* *IDMS-STATUS-PARAGRAPH. IF NOT DB-STATUS-OK PERFORM IDMS-ABORT DISPLAY '**************************' ' ABORTING - ' PROGRAM-NAME ', ' ERROR-STATUS ', ' ERROR-RECORD ' **** RECOVER IDMS ****' UPON CONSOLE DISPLAY 'PROGRAM NAME ------ ' PROGRAM-NAME DISPLAY 'ERROR STATUS ------ ' ERROR-STATUS DISPLAY 'ERROR RECORD ------ ' ERROR-RECORD DISPLAY 'ERROR SET --------- ' ERROR-SET DISPLAY 'ERROR AREA -------- ' ERROR-AREA DISPLAY 'LAST GOOD RECORD -- ' RRECORD-NAME DISPLAY 'LAST GOOD AREA ---- ' AREA-NAME DISPLAY 'DML SEQUENCE--------' DML-SEQUENCE * IN-HOUSE CUSTOMIZATION - CHANGED "ROLLBACK" * TO A HARD-CODED CALL - TO AVOID "AUTOSTATUS" * ADDING A "PERFORM IDMS-STATUS" AFTER THE ROLLBACK COMMAND * AND THUS CREATING AN ENDLESS LOOP IN THIS PARAGRAPH * (WHICH WOULD NOW FLOOD THE CONSOLE WITH THE IDMSERR1 MESSAGES. * ROLLBACK CALL 'IDMS' USING SUBSCHEMA-CTRL IDBMSCOM (67) IF ANY-ERROR-STATUS DISPLAY 'ROLLBACK FAILED WITH STATUS=' ERROR-STATUS DISPLAY 'ROLLBACK FAILED WITH STATUS=' ERROR-STATUS UPON CONSOLE END-IF CALL 'ABORT' . IDMS-ABORT SECTION. IDMS-ABORT-EXIT. EXIT.

Figure 16 - IDMS-STATUS Paragraph There are several versions of the IDMS-STATUS routine, and the appropriate one is copied from the IDD based on the MODE IS clause of the PROTOCOL statement. A site may have custom tailored this routine to provide additional functionality. The IDMS-STATUS routine should be performed after each DML Verb after checking for anticipated errors. An example of an anticipated error is 0326 or DB-REC-NOT-FOUND. This occurs IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998 page 17 Use by license agreement only.

frequently and the program should handle such an error. If there is an unexpected error, the program will ABORT with a U2222 (also called a USER 2222 ABEND). An example of an unexpected error might be an 0069 or 1469 - which means that the IDMS/Central Version went down - and thus the program cannot continue. In the case of an U2222 ABEND, the programmer must look at the DISPLAY statements found in the //SYSOUT and the job log.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 18 Use by license agreement only.

MVS JOB LOG Figure 17 shows the MVS output of a batch job with a U2222 ABEND. The key error messages are highlighted in bold.
The job log on MVS would look something like this: J E S 2 J O B L O G -- S Y S T E M G S L P 10.15.37 10.15.38 10.15.38 10.15.38 10.16.45 10.16.46 10.16.46 10.16.46 JOB05801 JOB05801 JOB05801 JOB05801 JOB05801 JOB05801 JOB05801 JOB05801 -N O D

IRR010I USERID USERID1 IS ASSIGNED TO THIS JOB. ICH70001I USERID1 LAST ACCESS AT 10:13:47 ON WEDNESDAY, JULY $HASP373 NRWDTSTE STARTED - INIT 12 - CLASS N - SYS ABCD IEF403I NRWDTSTE - STARTED - TIME=10.15.38 +IDMS DB347011 dbname XXXXXXXX invalid - binding subschema is +************************** ABORTING - TESTERR1, 1477, +IDMS RUN-UNIT CANCELLED DUE TO PROGRAM REQUEST IEA995I SYMPTOM DUMP OUTPUT USER COMPLETION CODE=2222 TIME=10.16.45 SEQ=04261 CPU=0000 ASID=0031 PSW AT TIME OF ERROR 078D1000 851000DE ILC 2 INTC 0D ACTIVE LOAD MODULE ADDRESS=05100080 OFFSET=0000 NAME=IDMSCANC DATA AT PSW 051000D8 - 00181610 0A0D1814 0A0D0700 GPR 0-3 80000000 800008AE 0000CB08 00006D60 GPR 4-7 000008AE 0004B298 051000B4 851000A4 GPR 8-11 80012BE0 0000A6A0 0004ACC0 851000A4 GPR 12-15 80012662 0004AFE8 80012BDE 00000000 END OF SYMPTOM DUMP 10.16.46 JOB05801 IEC130I SYSABOUT DD STATEMENT MISSING 10.16.46 JOB05801 +IGZ043I A 'SYSABOUT' error occurred. The ABEND information 10.16.46 JOB05801 + incomplete. 10.16.46 JOB05801 +IGZ057I An ABEND was intercepted by the COBOL run-time ABEN 10.16.46 JOB05801 + It is described by a corresponding IEA995I message. 10.16.46 JOB05801 IEF450I NRWDTSTE STEP01 - ABEND=S000 U2222 REASON=00000000 TIME=10.16.46 10.16.46 JOB05801 *END STEP STEP01 OF NRWDTSTE TIME 10:16 **** ABEND U2222 10.16.46 JOB05801 IEF404I NRWDTSTE - ENDED - TIME=10.16.46 10.16.46 JOB05801 JOB NRWDTSTE END DATE 96.213 CPU 0.002 75085AA 8000XXXA TIM 10.16.46 JOB05801 $HASP395 NRWDTSTE ENDED ------ JES2 JOB STATISTICS -----31 JUL 1996 JOB EXECUTION DATE 379 CARDS READ

Figure 17 - Errors in MVS Job Log

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 19 Use by license agreement only.

The Programs SYSOUT A sample listing of the //SYSOUT appears in Figure 18.
PROGRAM NAME ------ TESTERR1 ERROR STATUS ------ 0301 ERROR RECORD ------ EMPLOYEE-REC ERROR SET --------ERROR AREA -------- USER-AREA-NAME LAST GOOD RECORD -LAST GOOD AREA ---DML SEQUENCE--------0000000008

. .

Figure 18 - Errors in Programs //SYSOUT IDMS Error Status The IDMS Error-Status is a four byte code. The first two bytes are the major code and the last two bytes are the minor code. The major code always indicates the verb number (for example 03=OBTAIN, 09=READY). The minor code indicates the problem, such as 26=RECORD NOT FOUND, 66=AREA NOT AVAILABLE). The IDMS manuals (seeFigure 1) should be consulted for a full explanation of each error code.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 20 Use by license agreement only.

IDMS RETRIEVAL COMMANDS There are three retrieval commands: FIND, GET, and OBTAIN. 95% of programmers use only the OBTAIN command, because an OBTAIN does a FIND plus a GET. A FIND command sets database currency and retrieves the data, but does not put the data into the COBOLs working-storage records. A GET presumes that a FIND command has already been done, and simply moves the data from the IDMS buffer space to the designated record-name in the COBOLs workingstorage. Occasionally, a programmer will just do a FIND in order to save small amount of computer time. A completed sample IDMS retrieval program can be found in file EMPDEMO1 on the CD/ROM that accompanies this book. There are six formats of the FIND/OBTAIN command: 1) 2) 3) 4) 5) 6) FIND/OBTAIN FIND/OBTAIN FIND/OBTAIN FIND/OBTAIN FIND/OBTAIN FIND/OBTAIN CALC/DUPLICATE CURRENT DBKEY OWNER WITHIN set-name WITHIN SET USING SORT KEY WITHIN SET/AREA

Database currency refers to the where the program is positioned in the database. There are four types of currency: 1) 2) 3) 4) Database Currency (one only) Area Currency (one for each area) Record Currency (one for each record) Set Currency (one for each set)

When a command like OBTAIN NEXT WITHIN ABC-AREA is issued, the area currency for area ABC-AREA is used to obtain the next record in the area. Likewise, when a command like OBTAIN NEXT WITHIN XYZ-SET is issued, the set currency for the XYZ-SET is used to obtain the next record in the set. Beginning programmers can easily get lost when navigating a database if they lack a good understanding of database currency. Unfortunately, this topic deserves an entire chapter to itself.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 21 Use by license agreement only.

1) FIND/OBTAIN CALC/DUPLICATE If a record is stored with location-mode of CALC, the fastest way to retrieve that record is to OBTAIN it by using its CALC key. A typical scenario would be an EMPLOYEE-RECORD where the CALC KEY might be EMPLOYEE-NUM or EMP-SOCIAL-SECURITY-NUM. A record can have only one CALC KEY - but it might consists of several noncontiguous field-names. Figure 19 shows a code fragment that demonstrates this command.

MOVE 123456789 TO EMPLOYEE-NUM OBTAIN CALC EMPLOYEE-REC IF DB-REC-NOT-FOUND DISPLAY EMPLOYEE-NUM= EMPLOYEE-NUM WAS NOT FOUND ELSE PERFORM IDMS-STATUS DISPLAY EMPLOYEE-NUM= EMPLOYEE-NUM EMPLOYEE-NAME= EMPLOYEE-NAME END-IF

Figure 19 - OBTAIN CALC Example Duplicates are rare on CALC KEYS, but if the CALC record was defined as DUPLICATES FIRST or DUPLICATES LAST the program can continue to get the remaining records with the same CALC KEY by performing a loop. Figure 20 shows a code fragment that demonstrates this command.
1000-GET-EMPLOYEE. MOVE '123456789' TO EMPLOYEE-NUM OBTAIN CALC EMPLOYEE-REC PERFORM IDMS-STATUS PERFORM 2100-DISPLAY-RESULT THRU 2100-EXIT PERFORM 2000-GET-DUP-EMPLOYEES THRU 2000-EXIT UNTIL DB-REC-NOT-FOUND. 1000-EXIT. EXIT. 2000-GET-DUP-EMPLOYEES. OBTAIN CALC EMPLOYEE-REC DUPLICATE. IF NOT DB-REC-NOT-FOUND PERFORM IDMS-STATUS PERFORM 2100-DISPLAY-RESULT THRU 2100-EXIT . 2000-EXIT. EXIT. 2100-DISPLAY-NAME. IF DB-REC-NOT-FOUND DISPLAY EMPLOYEE-NUM= EMPLOYEE-NUM WAS NOT FOUND ELSE DISPLAY EMPLOYEE-NUM= EMPLOYEE-NUM EMPLOYEE-NAME= EMPLOYEE-NAME END-IF. 2100-EXIT. EXIT.

Figure 20 - OBTAIN CALC DUPLICATE Example IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998 page 22 Use by license agreement only.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 23 Use by license agreement only.

2) FIND/OBTAIN CURRENT and 6) FIND/OBTAIN NEXT WITHIN SET/AREA The FIND/OBTAIN NEXT command is used to get the first or next record in the area or set. If the database area is over 50% full, the fastest way to retrieve all of a certain record type from the database is to do an AREA SWEEP. This process might also be called an extract job. This involves getting the FIRST record in the area, and then performing the OBTAIN NEXT command until the DB-END-OF-SET condition is reached. The FIND/OBTAIN NEXT WITHIN SET is used to walk a set. Usually, the program is obtains the owner record and then processes each member of the set. The FIND/OBTAIN CURRENT is used to reposition database currency back to a prior location. This is very common when sweeping a database for record-1 while then walking a set for record-2. If the program is not careful, it can lose currency. For example, the OBTAIN NEXT EMPLOYEE-REC WITHIN AREA statement will start from the currency of area, and go forward in the area, looking for the next EMPLOYEE-REC. If the current database position is not on the last EMPLOYEE-REC, this could cause the program to omit records in an extract, or to go into a loop re-reading the same series of records over-and-over. The following code fragment demonstrates the following: 2) FIND/OBTAIN CURRENT 6) FIND/OBTAIN NEXT WITHIN SET and AREA

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 24 Use by license agreement only.

Figure 21 shows a code fragment that demonstrates these commands.


1000-GET-EMPLOYEE. MOVE ZERO TO RECORD-COUNT PERFORM 2000-GET-NEXT-EMPLOYEE THRU 2000-EXIT UNTIL DB-END-OF-SET. 1000-EXIT. EXIT. 2000-GET-NEXT-EMPLOYEE. IF RECORD-COUNT = 0 OBTAIN FIRST EMPLOYEE-REC WITHIN EMPLOYEE-AREA ELSE OBTAIN NEXT EMPLOYEE-REC WITHIN EMPLOYEE-AREA END-IF IF DB-END-OF-SET GO TO 2000-EXIT END-IF PERFORM IDMS-STATUS PERFORM 3000-GET-NEXT-JOBHIST THRU 3000-EXIT UNTIL DB-ANY-ERROR. *SET CURRENCY BACK TO LAST EMPLOYEE-REC *THE FIND IS USED INSTEAD OF THE OBTAIN BECAUSE THE PROGRAM *IS NO LONGER INTERESTED IN THE DATA FROM THAT RECORD. FIND CURRENT EMPLOYEE-REC PERFORM IDMS-STATUS . 2000-EXIT. EXIT. 3000-GET-NEXT-JOBHIST. OBTAIN NEXT JOBHIST WITHIN EMP-JOBHIST IF NOT DB-END-OF-SET PERFORM 4000-WRITE-OUT-DATA THRU 4000-EXIT END-IF . 3000-EXIT. EXIT.

Notes: options: 1) 2) 3) 4) 5) desired

Figure 21 - OBTAIN CURRENT & OBTAIN NEXT Example With the OBTAIN WITHIN SET/AREA command, there are five

OBTAIN FIRST OBTAIN NEXT OBTAIN LAST OBTAIN PRIOR OBTAIN ws-number where ws-number is the Nth record (this option is rarely used)

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 25 Use by license agreement only.

3) FIND/OBTAIN DBKEY The FIND/OBTAIN DBKEY command is used to retrieve a record based on a dbkey that was saved from a prior retrieval of that record. This is the fastest possible way to retrieve a record, because IDMS will only have to do one I/O. WARNING: If the database administrator reorgs or re-sizes the physical database, then all the dbkeys will change. Therefore it is unwise to save dbkeys in sequential files for processing that will occur more than a few hours later in the same day. TIP: A DBKEY consists of a page-number and a line-number. COBOL it is defined as an S9(8) COMP field. DBKEYs can be displayed three different ways: 1) page:line-number - for example: 50,123:49 2) cobol number 50,123 * 256 + 49) for example: 12831537 (which equals In

3) hex - for example: 00C3CB31 (where X00C3CB converts to 50,123 and X31 converts to 49).

ADVANCED NOTES on DBKEYs: 1) large dbkeys over 8,388,608 will appear as negative numbers in an S9(8) COMP field, and require special processing to convert to page/line number 2) 99% of all databases are defined to allow 255 records per page, and thus the number 256 is used in converting dbkeys to page-line numbers. The database administrator has the power to change the radix of the dbkey, and occasionally a different computation must be used. 3) There is a field called DBKEY in the SUBSCHEMA-CTRL record. This field always contains the value of the dbkey of the last database record accessed, and thus can be used in a MOVE statement in lieu of an ACCEPT command.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 26 Use by license agreement only.

The FIND/OBTAIN DBKEY is almost useless without the ACCEPT DBKEY statement, which saves the current DBKEY into a working-storage variable. NOTE: The dbkey can also be saved by doing a move of the field DBKEY in the SUBSCHEMA-CTRL to a working-storage variable. Figure 22 shows a code fragment that demonstrates this command.
77 WS-SAVE-DBKEY PIC S9(8) COMP.

* * *

ACCEPT WS-SAVE-DBKEY FROM CURRENCY. PERFORM IDMS-STATUS (or ACCEPT WS-SAVE-DBKEY FROM EMPLOYEE-REC CURRENCY.) (or MOVE DBKEY TO WS-SAVE-DBKEY) . . . misc other processing here . . . OBTAIN EMPLOYEE-REC DBKEY IS WS-SAVE-DBKEY. PERFORM IDMS-STATUS.

Figure 22 - OBTAIN DBKEY Example 4) FIND/OBTAIN OWNER WITHIN set-name The FIND/OBTAIN OWNER command allows the programmer to navigate up a hierarchy by moving from a member (child) record to its owner (or parent). Although an OBTAIN OWNER statement may be coded with checking for ownership first, this can cause bad program logic and make debugging difficult. Thus, it should be a standard procedure to always use the IF MEMBER statement first. Technically, this is only needed for OPTIONAL sets, but by always coding the IF MEMBER, this gives a site the flexibility to change the set options without having to worry about having to re-code programs. For the following example, the program has already obtained a JOBHIST record and needs to OBTAIN the owner EMPLOYEE-REC within the EMPLOYEE-JOBHIST set. Figure 23 shows a code fragment that demonstrates this command.
IF EMPLOYEE-JOBHIST MEMBER OBTAIN OWNER WITHIN EMPLOYEE-JOBHIST DISPLAY OWNER-EMPLOYEE-NUM= EMPLOYEE-NUM ELSE DISPLAY WARNING: JOBHIST IS NOT A MEMBER OF EMPLOYEE-JOBHIST END-IF

Figure 23 - IF setname MEMBER Example

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 27 Use by license agreement only.

5) FIND/OBTAIN WITHIN SET USING SORT KEY The FIND/OBTAIN WITHIN SET USING SORT KEY is used when a sortedset is available, and the program is aware of the value of the sort-key of a desired member-record. For example, suppose EMPLOYEE-JOBHIST set is sorted by START-DATE. In other words, the START-DATE is the day that the employee began working on a certain job. Suppose the query is: What job did employee 123456789 start on the date of 19970501? Figure 24 shows a code fragment that demonstrates this command.
MOVE 123456789 TO WS-SEARCH-EMP-NUM * NOTE: THE EMPLOYEE DEMO-DATABASE IS NOT Y2K COMPLIANT MOVE 970501 TO WS-SEARCH-DATE MOVE WS-SEARCH-EMP-NUM TO EMPLOYEE-NUM OBTAIN CALC EMPLOYEE-REC IF DB-REC-NOT-FOUND DISPLAY EMPLOYEE-NUM= EMPLOYEE-NUM WAS NOT FOUND ELSE PERFORM IDMS-STATUS DISPLAY EMPLOYEE-NUM= EMPLOYEE-NUM EMPLOYEE-NAME= EMPLOYEE-NAME MOVE WS-SEARCH-DATE TO START-DATE OBTAIN JOBHIST WITHIN EMPLOYEE-JOBHIST USING START-DATE IF DB-REC-NOT-FOUND DISPLAY NO JOBHIST FOUND FOR DATE= START-DATE ELSE DISPLAY START DATE= START-DATE JOB-TITLE= JOB-TITLE END-IF END-IF

Figure 24 - OBTAIN USING sortkey Example

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 28 Use by license agreement only.

IDMS UPDATE COMMANDS Figure 25 shows the five simple commands used to update an IDMS database. MODIFY After OBTAINING a record, the program can change the values of the fields in the record, and then use this command to MODIFY (replace) the record in the database After setting the working-storage values for a record, the program can use this command to STORE (add) a new record to the database After OBTAINING a record, the program can use this command to ERASE (delete) the record from the database Used to connect a database record to an optional set Used to disconnect a database record from an optional set Figure 25 - IDMS Update Commands

STORE

ERASE

CONNECT DISCONNECT

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 29 Use by license agreement only.

MODIFY EXAMPLE: Figure 26 shows a code fragment that demonstrates the MODIFY command.
MOVE 123456789 TO WS-SEARCH-EMP-NUM MOVE JONES TO WS-NEW-LAST-NAME MOVE WS-SEARCH-EMP-NUM TO EMPLOYEE-NUM OBTAIN CALC EMPLOYEE-REC IF DB-REC-NOT-FOUND DISPLAY EMPLOYEE-NUM= EMPLOYEE-NUM WAS NOT FOUND ELSE PERFORM IDMS-STATUS MOVE EMPLOYEE-LAST-NAME TO WS-OLD-LAST-NAME MOVE WS-NEW-LAST-NAME TO EMPLOYEE-LAST-NAME MODIFY EMPLOYEE-REC PERFORM IDMS-STATUS DISPLAY EMPLOYEE-NUM= EMPLOYEE-NUM LAST-NAME CHANGED FROM: TO: EMPLOYEE-LAST-NAME END-IF

Figure 26 - MODIFY Example

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 30 Use by license agreement only.

STORE EXAMPLE: Figure 27 shows a code fragment that demonstrates the STORE command.
INITIALIZE EMPLOYEE-REC MOVE 1231231234 TO EMPLOYEE-NUM MOVE JONES TO EMPLOYEE-LAST-NAME MOVE JOHN TO EMPLOYEE-FIRST-NAME STORE EMPLOYEE-REC PERFORM IDMS-STATUS

Figure 27 - STORE Example Note: If you attempt to store a child record (into a Mandatory Automatic set, see Figure 30 and Figure 31), then you must be current on the owner record in that set. IDMS will automatically connect the member record to the current owner record. If no record is current, you will get error-status 1225.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 31 Use by license agreement only.

ERASE COMMAND: The ERASE command has four options (shown in Figure 28). These options provide flexibility and safety for deleting OWNER records. When dealing with a record that is not the owner of any set, the simplest option (#1 below) may be used. 1) ERASE record-name Erases only the specified record (but if record has children, ERASE will fail). Erases the specified record and all mandatory member records Erases the specified record and all optional member records Erases the specified record and all mandatory and optional member records

2) ERASE record-name PERMANENT MEMBERS 3) ERASE record-name SELECTIVE MEMBERS 4) ERASE record-name ALL MEMBERS

Figure 28 - Erase Sub-Options NOTE: When dealing with a database that has a hierarchical structure (Record A owns B owns C owns D), when the top record in the hierarchy is erased, all members records below (including C and D) might also be erased, depending on the ERASE options specified. If the ERASE EMPLOYEE-REC command is used, and the EMPLOYEEJOBHIST set is not empty, the program get an IDMS ERRORSTATUS=0230 (an attempt has been made to erase the owner record of a non-empty set). It is often practical to check for members, before attempting an ERASE. This can be done with the IF MEMBER command. The IF MEMBER statement and the ERASE command are illustrated in Figure 29.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 32 Use by license agreement only.

ERASE EXAMPLE
MOVE WS-SEARCH-EMP-NUM TO EMPLOYEE-NUM OBTAIN CALC EMPLOYEE-REC IF DB-REC-NOT-FOUND DISPLAY EMPLOYEE-NUM= EMPLOYEE-NUM WAS NOT FOUND ELSE PERFORM IDMS-STATUS DISPLAY EMPLOYEE-NUM= EMPLOYEE-NUM IF EMPLOYEE-JOBHIST NOT EMPTY DISPLAY CANNOT ERASE UNTIL MEMBERS ARE DELETED ELSE ERASE EMPLOYEE-REC PERFORM IDMS-STATUS END-IF END-IF

Figure 29 - ERASE Example

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 33 Use by license agreement only.

CONNECT AND DISCONNECT The CONNECT and DISCONNECT commands are used less frequently than the other IDMS update commands. The majority of IDMS sets are MANDATORY AUTOMATIC. It is important to understand the meaning of these set options. These options always come in a pair, where there are two possible values for the first of the pair, and two possible values for the second part of the pair. The four combinations of set options are usually abbreviated by their initials (MA, MM, OM, OA). These sets option are explained in the following in figures (Figure 30 and Figure 31). MANDATORY The member record cannot be disconnect from the set and therefore the DISCONNECT command NOT allowed. The member record can be disconnected from the set.

OPTIONAL

Figure 30 - First Set Option AUTOMATIC The member record will automatically be connected to the set when the member record is stored. The member record will not be connected to the set when the member record is stored.

MANUAL

Figure 31 - Second Set Option The CONNECT command can be executed on any record that is not connected to its owner by the set relationship. This can either be a record that was STORED and never connected (OM or MM set options), or a record that had been disconnected by the DISCONNECT command (OA or OM) set options. A program may never do a CONNECT or DISCONNECT on when the set options are MandatoryAutomatic (MA). An example of the CONNECT verb is shown in Figure 32.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 34 Use by license agreement only.

CONNECT EXAMPLE:
IF NOT EMPLOYEE-JOBHIST MEMBER CONNECT JOBHIST TO EMPLOYEE-JOBHIST PERFORM IDMS-STATUS END-IF

Figure 32 - CONNECT Example It is common for a member record to be disconnect from one owner and then reconnected immediately to another owner. A record that is disconnected from one owner but not reconnected to another owner is sometimes called an ORPHAN record. An example of the DISCONNECT verb is shown in Figure 33.
DISCONNECT EXAMPLE:
DISCONNECT JOBHIST FROM EMPLOYEE-JOBHIST PERFORM IDMS-STATUS

Figure 33 - DISCONNECT Example

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 35 Use by license agreement only.

OTHER REQUIRED COMMANDS: A few other commands are important to COBOL programmers, although they neither retrieve data or store data. They are the READY, BIND, FINISH, ROLLBACK and COMMIT commands. A brief summary of each command is shown in Figure 34. READY BIND Used to READY IDMS-AREAs in retrieval or update mode. Two formats: 1) BIND RUN-UNIT - establishes a run-unit with IDMS 2) BIND RECORD - specifies an area of working storage to be used for retrieving and updating each database record FINISH ROLLBACK Indicates that all database updates are final and ends the run-unit Indicates that all database updates since the start of the program or the last commit (which ever is most recent) should be reversed or rolled-out and the rununit is ended. Indicates that all database updates are final and releases all update (exclusive) locks, but does NOT end the run-unit.

COMMIT

Figure 34 - Other Required Commands

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 36 Use by license agreement only.

The READY Command The READY command deals with the programs intentions as to how an IDMS AREA is to be used. If area is readied in RETRIEVAL mode, any updates against that area will fail. It is wise to READY each area in the lowest possible READY mode. This reduces locking and contention. The READY AREA statement is extremely useful in production job scheduling. Typically, the job schedulers needs to know if two programs can run at the same time, or if the Database Administrator can run a re-org job against AREA-X while program B is running on a weekend. Thus, a SCAN utility is often run against the COBOL source code to identify the how each program readies each IDMS-AREA. The format of the READY statement is:
READY area-name USAGE-MODE IS PROTECTED/EXCLUSIVE RETRIEVAL/UPDATE.

Usually the PROTECTED and EXCLUSIVE options are omitted, because they limit the ability of other programs to run concurrently against the same IDMS AREAs. PROTECTED UPDATE indicates that this program will be the only program allowed to update the AREA. Once the program starts, any other program that attempts to READY the same AREA in UPDATE mode will fail with an IDMS ERROR-STATUS = 0966. PROTECTED UPDATE has one main advantage; it avoids deadlocks. To understand deadlocks, IDMS locking must be understood. When an IDMS program readies an area in update mode, every record retrieved has a SELECT lock (also called INQUIRE lock)turned on. This lock is released when another record of the same record-name is retrieved. Any record that is updated has an UPDATE lock (also called EXCLUSIVE lock) turned on. This lock is released when the program does a COMMIT or when the run unit terminates (via either a ROLLBACK or FINISH). When program-B requests a record that program-A has locked, program-B will go into a DBKEY WAIT. If two programs access different data in the same area there is no problem. But, when two programs tend to use the same data records, performance usually decreases because one program will go into WAIT until the lock is freed by the other program. When the condition arises that program-A needs a record locked by program-B, and program-B needs a record that is locked by program-A a DEADLOCK occurs. IDMS will return the xx29 errorstatus causing one of the two programs to ABEND.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 37 Use by license agreement only.

The COMMIT Command Deadlocks can often be avoided by increasing the COMMIT frequency. A program typically has a record-update counter, and when that counter reaches a certain point, the program performs a commit. Figure 35 shows how to code COMMIT frequency logic in an update program:
*THIS PROGRAM READS A SEQUENTIAL FILE CONTAINING *AN EMPLOYEE-ID AND A CHANGE TO THE EMPLOYEES LAST-NAME. 03 03 03 WS-UPDATE-COUNTER WS-COMMIT-COUNTER WS-COMMIT-FREQ PIC S9(4) COMP. VALUE ZERO. PIC S9(4) COMP VALUE ZERO. PIC S9(4) COMP VALUE +100.

PERFORM 1000-UPDATE-LOOP THRU 1000-EXIT UNTIL WS-YN-INPUT1-EOF = Y DISPLAY NUMBER OF UPDATES= WS-UPDATE-COUNTER. 1000-UPDATE-LOOP. READ INPUT1-FILE AT END MOVE Y TO WS-YN-INPUT1-EOF GO TO 1000-EXIT END-READ MOVE INPUT1-EMP-ID TO EMPLOYEE-EMP-ID OBTAIN CALC EMPLOYEE-REC IF DB-REC-NOT-FOUND DISPLAY RECORD NOT FOUND EMP-ID= INPUT1-EMP-ID GO TO 1000-EXIT END-IF PERFORM IDMS-STATUS MOVE INPUT1-LAST-NAME TO EMPLOYEE-LAST-NAME MODIFY EMPLOYEE-REC PERFORM IDMS-STATUS ADD 1 TO WS-UPDATE-COUNTER ADD 1 TO WS-COMMIT-COUNTER IF WS-COMMIT-COUNTER NOT < WS-COMMIT-FREQ PERFORM 8000-COMMIT THRU 8000-EXIT END-IF . 1000-EXIT. EXIT. 8000-COMMIT. COMMIT. PERFORM IDMS-STATUS. MOVE ZERO TO WS-COMMIT-COUNTER. 8000-EXIT. EXIT.

Figure 35 - COMMIT Frequency Example However, the above program is incomplete because it does not handle the case of an ABEND and restart logic. Suppose there are 500 records on the input file and that the program ABENDs when processing record #325. What happens? Since the commit counter is set for every 100 records, then 300 records have been written to the database. In the case of a simple MODIFY-only program as shown above, the program could be restarted and could simply IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998 page 38 Use by license agreement only.

reprocess all 500 records. However, if the program was storing records instead of modifying them, then the restart logic becomes more difficult. The program could be changed in two ways: 1) The program could check to see if each record existed and only STORE new records 2) The program could spin past the first 300 records, and begin its STORE logic right where it left off, at record #301 (realizing that records #301 thru #325 were rolled-out when the program ABENDed). The second approach is more elegant - but also is more difficult to code. This means that the program must save the current record counter each time it does a commit. This could be done by adding logic as shown in Figure 36. A complete sample IDMS update program with commit and restart logic can be found in file EMPDEMO2 on the CD/ROM that accompanies this book.
*THIS TECHNIQUE ASSUMES THAT THE COMMIT1-FILE EXISTS *AND THAT DISP=SHR IS SPECIFIED IN THE MAINFRAME MVS *JCL (JOB CONTROL LANGUAGE). 8000-COMMIT. COMMIT. PERFORM IDMS-STATUS. MOVE ZERO TO WS-COMMIT-COUNTER. OPEN OUTPUT COMMIT1-FILE. MOVE WS-UPDATE-COUNTER TO COMMIT1-UPDATE-COUNTER. WRITE COMMIT1-REC CLOSE COMMIT1-FILE. 8000-EXIT. EXIT.

Figure 36 - COMMIT Example (UPDATE-COUNTER is saved)

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 39 Use by license agreement only.

The program now writes the update-counter to a sequential file. By opening and closing the file each time, the last record written is overlaid. Now that the program saves this counter, it also needs restart logic, which is shown in Figure 37.
0000-INIT. OPEN INPUT INPUT1-FILE PERFORM 8500-CHECK-RESTART THRU 8500-EXIT. PERFORM 1000-UPDATE-LOOP THRU 1000-EXIT UNTIL WS-YN-INPUT1-EOF = Y DISPLAY NUMBER OF UPDATES= WS-UPDATE-COUNTER. 8500-CHECK-RESTART. OPEN INPUT COMMIT1-FILE. READ COMMIT1-FILE AT END MOVE Y TO WS-YN-COMMIT1-EOF END-READ IF WS-YN-COMMIT1-EOF = Y DISPLAY 8500 NO RESTART REQUIRED ELSE DISPLAY 8500 RESTARTING AT UPDATE-COUNTER= COMMIT1-UPDATE-COUNTER PERFORM 8510-SKIP-INPUT1-REC THRU 8510-EXIT COMMIT1-UPDATE-COUNTER TIMES MOVE COMMIT1-UPDATE-COUNTER TO WS-UPDATE-COUNTER END-IF. CLOSE COMMIT1-FILE. 8500-EXIT. EXIT. 8510-SKIP-INPUT1-REC. READ INPUT1-FILE AT END MOVE Y TO WS-YN-INPUT1-EOF DISPLAY 8510: ERROR //INPUT1 EOF ON RESTART MOVE 16 TO RETURN-CODE STOP RUN END-READ. 8510-EXIT. EXIT.

Figure 37 - COMMIT/Restart Example

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 40 Use by license agreement only.

The TWO BIND Commands The BIND RUN-UNIT statement is used to establish a run-unit. A run-unit is an IDMS term that describes a program that has issued a BIND but has not yet issued a FINISH or ROLLBACK. A run-unit establishes communication with the IDMS database server and creates all necessary control blocks to communicate with IDMS. The following precompiler directive builds the BIND RUN-UNIT statement and a BIND for each record-type.
COPY IDMS SUBSCHEMA-BINDS.

This statement was previously discussed in the precompiler directives section (seeFigure 9). Prior to release 12.0 of IDMS, sites using multiple DBNAMEs would code the DBNAME on the BIND RUN-UNIT statement. But with 12.0, the DBNAME is usually specified external to the program in the //SYSIDMS file. (DBNAMEs allow the same program to run against different copies of the same database. For example, a USA Payroll database and a CANADA Payroll database could be maintained by the same programs, although the data in each database would be entirely different. This is often called segmentation or segmented databases.) There must be one BIND record statement issued for each record that the program will access. Each BIND record statement provides addressability to the COBOL working-storage section for each record-layout. If the precompiler directive COPY SUBSCHEMA BINDS (Figure 8) is not used, your BINDs AND READYs could be coded as shown in Figure 38.
BIND RUN-UNIT PERFORM IDMS-STATUS BIND JOB PERFORM IDMS-STATUS BIND EMPOSITION PERFORM IDMS-STATUS BIND EMPLOYEE PERFORM IDMS-STATUS READY EMP-DEMO-REGION USAGE-MODE RETRIEVAL. PERFORM IDMS-STATUS. READY ORG-DEMO-REGION USAGE-MODE RETRIEVAL. PERFORM IDMS-STATUS.

Figure 38 - BIND Example NOTE: It is always wise to do the PERFORM IDMS-STATUS after each statement. This ensures that you get the proper error as soon as possible, rather than getting a misleading error later.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 41 Use by license agreement only.

The FINISH and ROLLBACK Commands The FINISH command is used to complete the IDMS RUN-UNIT and to make permanent all the changes to the database (since the last COMMIT). As IDMS updates are written to the actual database files, before and after images are also written to the IDMS journal files. If the program ABENDs or issues the ROLLBACK command, these journal images are used to reverse the changes made to the actual database. If the program fails to include either a FINISH or ROLLBACK, a ROLLBACK is assumed (however, the DML Precompiler will issue a warning). Thus if a programmer runs a test program and then discovers that the updates did not happen, it is likely that the program did not include the FINISH statement. After the program does a FINISH or ROLLBACK, the run-unit is terminated, and it cannot do any further DML commands (resulting in a bad error-status such as nn77).

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 42 Use by license agreement only.

IDMS Online Programming IDMS Online Programming Overview Online programming involves creating screens (called maps) that allow COBOL programs to communicate with mainframe 3270 terminals (or PC programs that emulate 3270 terminals). Literals and database variables are presented on the terminal and the application end-users use function keys, transaction codes, and/or menus to access the desired programs and data. Online programming involves skills above and beyond batch COBOL programming. The four most common means of writing online programs for IDMS databases are: 1) ADS - IDMS Application Development System 2) CICS - IBMs Customer Information System 3) IDMS/DC - IDMS TP Commands 4) TSO/ISPF Panels IDMS also includes DC (Data Communications) or Teleprocessing capabilities (sometimes called a TP/Monitor). This allows IDMS online programs using interactive screens to access or update an IDMS database. Online programming is usually done in full-screen (mapping) mode, but also can be done in line mode. IDMS full-screen maps are created in an IDMS task called MAPC (Mapping Compiler for IDMS 12.0 and after) or OLM (Online Mapping - for IDMS pre 12.0 releases). CICS Maps are created with a language called BMS Basic Mapping Support.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 43 Use by license agreement only.

Sample IDMS/DC Commands Sample IDMS DC commands include: FULL-SCREEN: MAP IN MAP OUT MAP OUTIN INQUIRE MAP LINE-MODE: WRITE LINE TO TERMINAL, READ LINE FROM TERMINAL READ TERMINAL OTHER DC Commands: SET TIMER SEND MESSAGE SNAP STARTPAGE WAIT ENQUEUE/DEQUEUE POST GET QUEUE/PUT QUEUE GET SCRATCH/PUT SCRATCH These DC commands allows IDMS/DC programs to do most anything that CICS programs can do. IDMS software called Universal Communication Facility (UCF) allows IDMS/DC programs to run under CICS, or a site might run IDMS/DC and not use CICS at all.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 44 Use by license agreement only.

Overview of ADS ADS is a separate product and an entire programming language but one that is totally integrated with IDMS. Many sites have adopted it as their primary online development system. ADS is often referred to as ADSO (ADS/Online), but ADS also has batch capabilities (ADS/Batch). ADS is rarely used for batch reporting; most sites choose COBOL, Online Query (OLQ/BATCH), CULPRIT, or fourth generation language (4GL) report-writers such as FOCUS, SAS, Data-Analyzer, or Easytrieve-Plus. ADS programs are written as module text and stored on the IDMS Integrated Data Dictionary (IDD). ADSO programmers usually have access to create work records and elements on the IDD. ADSO programs are typically built online using the Application Generation and Application Compiler. An ADSO program is called a dialog, which usually consists of a map, a subschema, one premap process, and several response processes.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 45 Use by license agreement only.

Overview of CICS CICS programs using CICS command level language and go through a CICS precompiler in addition to the DML precompiler. A CICS/IDMS program is designed by specifying a proper mode statement in the ENVIRONMENT DIVISION, as shown in Figure 39.
009200 009300 009400 009500 ENVIRONMENT DIVISION. IDMS-CONTROL SECTION. PROTOCOL. MODE IS CICS-AUTOSTATUS IDMS-RECORDS MANUAL.

Figure 39 - CICS MODE IS Example Some sites use only CICS to create online programs (instead of IDMS/DC or ADS) for the following reasons: 1) CICS programmers might be easier to find and/or the company has a larger base of CICS experience 2) Other in-house programs use CICS/VSAM or sophisticated CICS menuing systems, and the end-users want a consistent method of accessing data. Overview of IDMS/DC IDMS/DC programs use the same DML precompiler as batch programs. An online IDMS/DC program is designated by specifying a proper mode statement in the ENVIRONMENT DIVISION as shown in Figure 40.
009200 009300 009400 009500 ENVIRONMENT DIVISION. IDMS-CONTROL SECTION. PROTOCOL. MODE IS IDMS-DC IDMS-RECORDS MANUAL.

Figure 40 - IDMS/DC MODE IS Example Overview of Native VSAM Native VSAM files can be defined to IDMS schemas so that an IDMS/DC or IDMS/Batch program can read or update a VSAM file using DML commands.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 46 Use by license agreement only.

Maintaining IDMS Programs Once an IDMS system is implemented, IDMS has some unique aspects for maintaining the programs. 1) Management Issues Management usually works with the customer to determine what changes must be made. Often there is a large list of changes which the customer must prioritize. It is not unusual to have a one to three year backlog of changes. 2) Program migration Usually each site has a unique set of procedures for migrating programs from the test environment to the production environment (often using an intermediate staging or quality assurance environment). Most sites recompile the program at some point in this process. Some sites require change control paperwork or the approval of a Quality Control group. In some cases, getting the paperwork signed-off can be more challenging than the COBOL program changes. 3) Coordinating Record Structure Changes and Schema Changes with the DBA Typically, when a database record must be changed, it is the job of the DBA (database administrator) to run the appropriate restructure utilities. Usually senior programmers work with the DBA to migrate programs from a test system to the production system immediately after these changes are made. Usually, months before such a change is made, the programmer/analysts do research to identify the amount of effort and the number of programs that must be changed. Suppose the change is to add a PIC X(2) STATUS-CODE to the EMPLOYEE-REC. Someone must create a list of all the effected programs and determine if they need a simple recompile, or if the program code must be changed.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 47 Use by license agreement only.

4) Program Documentation If a report or an online screen is changed, is there a manual that must be changed? Are there any changes to the customer procedures that will be required before the program is migrated? Is it appropriate to hold a training class before implementing the change? 5) Performance and Tuning Many program changes are made in an effort to make programs run faster. Perhaps a batch program ran in one hour the first six months in the life of the system, but now it runs in four hours, which no longer satisfactory for the nightly batch window. Perhaps an index can be added to the database to make the program run faster. Perhaps the DML navigation path of program can be changed to make the program run faster. 6) Preventative Maintenance Frequently, the DBA will reorganize database for the sake of efficiency. This is commonly done when database areas approach 70% full, or upon areas where there are abnormally high number of changes. Index sets also need to be reorganized frequently. Since the DBA must take the databases offline when making his changes, he usually performs them late nights or weekends, with the coordination of the production job schedulers. The DBA will also install maintenance and new releases of IDMS software and coordinate the implementation with the programming staff.

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 48 Use by license agreement only.

Files on CD/ROM 1) EMPDEMO1 - COBOL SOURCE - Sample report program that reads sequential file and creates detailed employee/job-history report for each employee-id specified 2) EMPDEMO2 - COBOL SOURCE - Sample update program, reads sequential file containing OFFICE-CODE, DEPT-ID, EMP-ID, EMPLAST-NAME, and EMP-FIRST-NAME and stores on database. This program has complete COMMIT and restart logic. 3) EMPDEMO3 - COBOL SOURCE - Sample update program that deletes all employees with EMP-ID between 1000 and 2000 (i.e. those employees added by program EMPDEMO2). This is used to clean up the database so that EMPDEMO2 can be run again without getting duplicates. This program also write a zero counter to the COMMIT file. 4) XMPDEMO1 - EXECUTION JCL - Job Control Language (JCL) and INPUT data to demonstrate report program EMPDEMO1 5) XMPDEMO2 - EXECUTION JCL - JCL and INPUT data to demonstrate EMPDEMO2. JCL comments explain what each step does. JCL is set up to cause an ABEND after x records are processed, so the restart logic can be demonstrated in the next step. 6) XMPDEMO3 - EXECUTION JCL - JCL demonstrate delete program EMPDEMO3 7) COMPJCL - EXECUTION JCL - Sample JCL for DML Preprocessor and COBOL Compile and link. Check with your site for actual COBOL JCL or compile PROC to be used. 8) PMPDEMO1 - PRINTOUT OF EXECUTION - from EMPDEMO1 9) PMPDEMO2 - PRINTOUT OF EXECUTION - from EMPDEMO2

IDMS COBOL Programming by Neal Walters, Amerisoft Inc. 1998

page 49 Use by license agreement only.

Potrebbero piacerti anche