Previous Topic: Precompiler OptionsNext Topic: Major DB Status Codes


Communications Blocks and Error Detection

This chapter describes the 16-byte communications block available under CA IDMS. These blocks return status information about requested database and data communications services to the application program. This chapter also describes the ERROR-STATUS field in the IDMS and IDMS-DC communications blocks, status codes, and error detection routines.

Note: For more information about 18-byte communications blocks, see 18-Byte Communications Blocks.

This section contains the following topics:

Communications Blocks

ERROR-STATUS Field and Codes

DB Status Codes

DC Status Codes

ERROR-STATUS Condition Names

Error Detection

Communications Blocks

Communications blocks return status information about requested database and data communications services to the application program. Depending on the usage mode (LR, DML, or MIXED) defined in the subschema, your program will use one or two of the following blocks:

The LRC block is copied in with either the IDMS communications block (operating mode of BATCH or BATCH-AUTOSTATUS) or the IDMS-DC communications block (operating mode of IDMS-DC or DC-BATCH).

Each of these blocks is discussed in detail below.

Note: For more information about operating modes and protocols, see Precompiler-Directive Statements.

IDMS Communications Block

The IDMS communications block is used when the operating mode is either BATCH or BATCH-AUTOSTATUS; it serves as an interface between the database management system (DBMS) and the application program. Whenever a run unit issues a call to the DBMS for a database operation, the DBMS returns information about the outcome of the requested service to the application program's IDMS communications block.

The data description (identified as SUBSCHEMA-CTRL) of the IDMS communications block is copied from the data dictionary into the WORKING-STORAGE SECTION or LINKAGE SECTION of the program. When you submit the program to the precompiler, the IDMS communications block is copied automatically unless an IDMS-RECORDS MANUAL statement is included in the ENVIRONMENT DIVISION. In that case, the program can explicitly call in the data description by using a COPY IDMS SUBSCHEMA-CTRL statement.

Note: For more information about the IDMS-RECORDS MANUAL and the COPY IDMS statements, see Precompiler-Directive Statements.

You should examine the ERROR-STATUS field of the IDMS communications block after every call to the DBMS. Depending on the value contained in this field, you should perform the IDMS-STATUS routine (see IDMS-STATUS Routine later in this chapter). For example, if the ERROR-STATUS field contains the value 0307 (DB-END-OF-SET) while walking a set, you should perform end-of-set processing; otherwise, IDMS-STATUS should be performed.

The following figure show the layout of the 16-byte IDMS communications block. Each field is described separately following the figure.

                  ┌────────────────────────────────────────┐
                  │ 16-CHARACTER IDMS COMMUNICATIONS BLOCK │
                  └────────────────────────────────────────┘

                                              Length      
                 Field           Data Type   (bytes)      Initial Value
  ┌──────────┐
 *│ 1      8 │   PROGRAM-NAME    Alphanumeric  8           Program Name
  ├────────┬─┘
  │ 9  12  │     ERROR-STATUS    Alphanumeric  4          '1400'
  ├────────┤
  │ 13  16 │     DBKEY           Binary        4(Fullword) 0000
  ├────────┴───┐
  │ 17      32 │ RECORD-NAME     Alphanumeric  16          Spaces
  ├────────────┤
  │ 33      48 │ AREA-NAME       Alphanumeric  16          Spaces
  ├────────────┤
  │ 49      64 │ ERROR-SET       Alphanumeric  16          Spaces
  ├────────────┤
  │ 65      80 │ ERROR-RECORD    Alphanumeric  16          Spaces
  ├────────────┤
  │ 81      96 │ ERROR-AREA      Alphanumeric  16          Spaces
  ├─────────┬──┘
**│ 97  100 │    PAGE-INFO       Binary        4(Fullword) 0000
  └─────────┘
  ┌──────────┐
  │ 97   196 │   IDBMSCOM-AREA   Alphanumeric  100         Low Values
  ├──────────┤
  │ 197  200 │   DIRECT-DBKEY    Binary        4(Fullword) 0000
  └──────────┘
  ┌─────────┐
  │ 201 207 │    DATABASE-STATUS Alphanumeric  7           Spaces
  ├─────┬───┘
  │ 208 │        FILLER          ...           1           ...
  ├─────┴───┐
  │ 209 212 │    RECORD-OCCUR    Binary        4(Fullword) 0000
  ├─────────┤
  │ 213 216 │    DML-SEQUENCE    Binary        4(Fullword) 0000
  └─────────┘
    * word aligned
   ** PAGE-INFO-GROUP overlays bytes 97 and 98 and PAGE-INFO-DBK-FORMAT
     overlays bytes 99 and 100. Both of these fields are binary datatype,
     each with a length of two bytes. Suggested initial values for
     both are 00. Together these two fields represent PAGE-INFO.

The IDMS DB communications block contains the following fields that describe program status information:

Field name

Description

PROGRAM-NAME

The name of the program being executed, as defined in the program's IDENTIFICATION DIVISION.

This field is initialized automatically at the beginning of program execution if the program contains a COPY IDMS SUBSCHEMA-BINDS statement in its PROCEDURE DIVISION. Otherwise, it must be initialized by the programmer.

ERROR-STATUS

An alphanumeric value indicating the outcome of the last DML statement executed.

The ERROR-STATUS field must be initialized to 1400 by the program. The ERROR-STATUS field is updated by the DBMS after (attempted) performance of a requested database service and before control is returned to the program.

A program that consists of more than one run unit must reinitialize the ERROR-STATUS field to 1400 after finishing one run unit and before binding the next.

DBKEY

The database key of the last record accessed by the run unit. For example, after successful execution of a FIND command, DBKEY is updated with the database key of the located record.

DBKEY is not changed if the call to the DBMS results in a nonzero status condition.

RECORD-NAME

The name of the last record accessed successfully by the run unit.

This field is left-justified and padded with spaces on the right.

AREA-NAME

The name of the last area accessed successfully by the run unit.

This field is left-justified and padded with spaces on the right.

ERROR-SET

The name of the set involved in the last operation to produce a nonzero status code.

This field is left-justified and padded with spaces on the right.

ERROR-RECORD

The name of the record involved in the last operation to produce a nonzero status code.

This field is left-justified and padded with spaces on the right.

ERROR-AREA

The name of the area involved in the last operation to produce a nonzero status code.

This field is left-justified and padded with spaces on the right.

PAGE-INFO

Two binary halfwords that represent the page information associated with the last record accessed by the run unit. PAGE-INFO is not changed if the call to the DBMS results in a non-zero status. The first halfword (PAGE-INFO-GROUP) represents the page group number. The second halfword (PAGE-INFO-DBK-FORMAT) represents the db-key radix.

The db-key radix portion of the page information can be used in interpreting a db-key for display purposes and in formatting a db-key from page and line numbers. The db-key radix represents the number of bits within a db-key value that are reserved for the line number of a record. By default, this value is 8, meaning that up to 255 records can be stored on a single page of the area. Given a db-key, you can separate its associated page number by dividing the db-key by 2 raised to the power of the db-key radix. For example, if the db-key radix is 4, you would divide the db-key value by 2**4. The resulting value is the page number of the db-key. To separate the line number, you would multiply the page number by 2 raised to the power of the db-key radix and subtract this value from the db-key value. The result would be the line number of the db-key. The following two formulas can be used to calculate the page and line numbers from a db-key value:

Page-number = db-key value /

(2 ** db-key radix)

Line-number = db-key value -

(page-number *

( 2 ** db-key radix))

IDBMSCOM-AREA

Used internally by the DBMS for specification of runtime function information.

DIRECT-DBKEY

Either a user-specified db-key value or a null db-key value of -1.

This field is used for storing a record with a location mode of DIRECT. It must be initialized by the user; it is not updated by the DBMS.

DATABASE-STATUS

Reserved for use by the DBMS.

FILLER

Used to ensure fullword alignment.

RECORD-OCCUR

A record occurrence sequence identifier used internally by the DBMS.

DML-SEQUENCE

The source level sequence number generated by the precompiler. This field is updated before each call to the DBMS if DEBUG is specified in the program's ENVIRONMENT DIVISION; it is not used by the runtime system.

Native VSAM users: The DIRECT-DBKEY field can be used only when storing a record in a native VSAM relative record data set (RRDS) or when storing records with DIRECT location mode. You must initialize DIRECT-DBKEY to the relative record number of the record being stored.

After a call has been made to the DBMS, one or more of the fields described above may have been updated, depending on the DML statement issued and if the statement was executed successfully. The following figure illustrates the IDMS communications block fields updated by successful and unsuccessful calls to the DBMS; only those fields accessed by the runtime system are shown. Fields used internally by the DBMS are not shown. Blank fields are not updated by DML statements.

                           ┌───────────────────┐┌───────────────────────┐
                           │     SUCCESSFUL    ││        UNSUCCESSFUL   │
                           ├─┬─┬─┬─┬─┬─┬─┬─┬─┬─┤├─┬─────┬─┬─┬─┬─┬─┬─┬─┬─┤
                           │ │ │ │ │ │ │ │ │ │ ││ │     │ │ │ │ │ │ │ │ │
                           │P│E│D│R│A│E│E│E│P│D││P│  E  │D│R│A│E│E│E│P│D│
                           │R│R│B│E│R│R│R│R│A│I││R│  R  │B│E│R│R│R│R│A│I│
                           │O│R│K│C│E│R│R│R│G│R││O│  R  │K│C│E│R│R│R│G│R│
                           │G│O│E│O│A│O│O│O│E│E││G│  O  │E│O│A│O│O│O│E│E│
                           │R│R│Y│R│-│R│R│R│-│C││R│  R  │Y│R│-│R│R│R│-│C│
                           │A│-│ │D│N│-│R│-│I│T││A│  -  │ │D│N│-│-│-│I│T│
                           │M│S│ │-│A│S│-│A│N│-││M│  S  │ │-│A│S│R│A│N│-│
                           │-│T│ │N│M│E│R│R│F│D││-│  T  │ │N│M│E│E│R│F│D│
                           │N│A│ │A│E│T│E│E│O│B││N│  A  │ │A│E│T│C│E│O│B│
                           │A│T│ │M│ │ │C│A│ │K││A│  T  │ │M│ │ │O│A│ │K│
                           │M│U│ │E│ │ │O│ │ │E││M│  U  │ │E│ │ │R│ │ │E│
                           │E│S│ │ │ │ │R│ │ │Y││E│  S  │ │ │ │ │D│ │ │Y│
                           │ │ │ │ │ │ │D│ │ │ ││ │     │ │ │ │ │ │ │ │ │
                           │ │ │ │ │ │ │ │ │ │ ││ │     │ │ │ │ │ │ │ │ │
                           │ │ │ │ │ │ │ │ │ │ ││ │     │ │ │ │ │ │ │ │ │
┌──────────────────────────┴─┴─┴─┴─┴─┴─┴─┴─┴─┴─┤├─┴─────┴─┴─┴─┴─┴─┴─┴─┴─┤
│Controlstatements                             ││                       │
├──────────────────────────┬─┬─┬─┬─┬─┬─┬─┬─┬─┬─┤├─┬─────┬─┬─┬─┬─┬─┬─┬─┬─┤
│BINDRUN-UNIT              │ │O│ │ │ │ │ │ │ │ ││ │14nn │ │ │ │ │ │ │ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│BINDRECORD                │ │O│ │ │ │ │ │ │ │ ││ │14nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│BINDPROCEDURE             │ │O│ │ │ │ │ │ │ │ ││ │14nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│READY                     │ │O│ │ │ │ │ │ │ │ ││ │09nn │ │ │ │C│C│C│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│FINISH                    │ │O│N│C│ │C│C│C│ │ ││ │01nn │ │ │ │C│C│C│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│COMMIT(ALL)               │ │O│N│C│ │C│C│C│ │ ││ │18nn │ │ │ │C│C│C│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│ROLLBAK(CONTINUE)         │ │O│N│C│ │C│C│C│ │ ││ │19nn │ │ │ │C│C│C│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│KEEP(EXCLUSIVE)           │ │O│Y│Y│Y│C│C│C│Y│ ││ │06nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│IFSET                     │ │*│Y│Y│Y│C│C│C│Y│ ││ │16nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│IFNOTSET                  │ │*│Y│Y│Y│C│C│C│Y│ ││ │16nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┴─┴─┴─┴─┴─┴─┴─┴─┴─┴─┤├─┴─────┴─┴─┴─┴─┴─┴─┴─┴─┤
│Retrievalstatements                           ││                       │
├──────────────────────────┬─┬─┬─┬─┬─┬─┬─┬─┬─┬─┤├─┬─────┬─┬─┬─┬─┬─┬─┬─┬─┤
│FIND/OBTAINRECORD         │ │O│Y│Y│Y│C│C│C│Y│ ││ │03nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│GETRECORD                 │ │O│Y│Y│Y│C│C│C│Y│ ││ │05nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│RETURNRECORD              │ │O│Y│Y│Y│C│C│C│Y│ ││ │17nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┴─┴─┴─┴─┴─┴─┴─┴─┴─┴─┤├─┴─────┴─┴─┴─┴─┴─┴─┴─┴─┤
│Modificationstatements                        ││                       │
├──────────────────────────┬─┬─┬─┬─┬─┬─┬─┬─┬─┬─┤├─┬─────┬─┬─┬─┬─┬─┬─┬─┬─┤
│STORERECORD               │ │O│Y│Y│Y│C│C│C│Y│ ││ │12nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│CONNECTRECORD             │ │O│Y│Y│Y│C│C│C│Y│ ││ │07nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│MODIFYRECORD              │ │O│Y│Y│Y│C│C│C│Y│ ││ │08nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│DISCONNECTRECORD          │ │O│Y│Y│Y│C│C│C│Y│ ││ │11nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│ERASERECORD               │ │O│N│Y│Y│C│C│C│ │ ││ │02nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┴─┴─┴─┴─┴─┴─┴─┴─┴─┴─┤├─┴─────┴─┴─┴─┴─┴─┴─┴─┴─┤
│Acceptstatements                              ││                       │
├──────────────────────────┬─┬─┬─┬─┬─┬─┬─┬─┬─┬─┤├─┬─────┬─┬─┬─┬─┬─┬─┬─┬─┤
│ACCEPTDBKEYOFCURRENCY     │ │O│ │ │ │C│C│C│ │ ││ │15nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│ACCEPTDBKEYOFN/P/O        │ │O│ │ │ │C│C│C│ │ ││ │15nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│ACCEPTIDMSSTATISTICS      │ │O│ │ │ │C│C│C│ │ ││ │15nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│ACCEPTBINDRECORD          │ │O│ │ │ │C│C│C│ │ ││ │15nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│ACCEPTPROCEDURE           │ │O│ │ │ │C│C│C│ │ ││ │82nn │ │ │ │Y│Y│Y│ │ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┼─┤
│ACCEPTpage-info-location  │ │O│ │ │ │C│C│C│ │ ││ │15nn │ │ │ │Y│Y│Y│ │ │
└──────────────────────────┴─┴─┴─┴─┴─┴─┴─┴─┴─┴─┴┴─┴─────┴─┴─┴─┴─┴─┴─┴─┴─┘
┌────────────────────────────────────────────┐┌─────────────────────┐
│Acceptstatements                            ││                     │
├──────────────────────────┬─┬─┬─┬─┬─┬─┬─┬─┬─┤├─┬─────┬─┬─┬─┬─┬─┬─┬─┤
│ACCEPTFROMCURRENCY        │ │O│ │ │ │C│C│C│ ││ │15nn │ │ │ │Y│Y│Y│ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┤
│ACCEPTFROMN/P/OCURRENCY   │ │O│ │ │ │C│C│C│ ││ │15nn │ │ │ │Y│Y│Y│ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┤
│ACCEPTFROMIDMS-STATISTICS │ │O│ │ │ │C│C│C│ ││ │15nn │ │ │ │Y│Y│Y│ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┤
│ACCEPTFROMBIND            │ │O│ │ │ │C│C│C│ ││ │15nn │ │ │ │Y│Y│Y│ │
├──────────────────────────┼─┼─┼─┼─┼─┼─┼─┼─┼─┤├─┼─────┼─┼─┼─┼─┼─┼─┼─┤
│ACCEPTFROMPROCEDURE       │ │O│ │ │ │C│C│C│ ││ │15nn │ │ │ │Y│Y│Y│ │
└──────────────────────────┴─┴─┴─┴─┴─┴─┴─┴─┴─┴┴─┴─────┴─┴─┴─┴─┴─┴─┴─┘
┌────────────────────────────────────────────────────────┐
│┌──────────────────────────────────────────────────────┐│
││                                                      ││
││*Iftrue,fieldissettozonedecimalzeroes(0000)           ││
││Iffalse,fieldissetto1601                              ││
││                                                      ││
││OFieldissettozonedecimalzeroes                        ││
││                                                      ││
││YFieldisupdated                                       ││
││                                                      ││
││CFieldisclearedtospaces                               ││
││                                                      ││
││NFieldissettonulldb-keyvalue(-1)                      ││
││                                                      ││
││nnSpecificminorerrorcode                              ││
││                                                      ││
│└──────────────────────────────────────────────────────┘│
└────────────────────────────────────────────────────────┘

LRC Block

The logical-record request control (LRC) block is used when the subschema usage mode is LR or MIXED. The LRC block, which is used in conjunction with the IDMS or IDMS-DC communications block, provides an interface between LRF and the application program. It passes information about a logical-record request to LRF and returns path status information about the processing of the request to the program.

The data description (identified as SUBSCHEMA-LR-CTRL) of the LRC block is copied from the data dictionary into the WORKING-STORAGE SECTION or LINKAGE SECTION of the program. When the program is submitted to the precompiler, the LRC block and the IDMS or IDMS-DC communications block are copied automatically, unless the IDMS-RECORDS MANUAL statement is included in the ENVIRONMENT DIVISION. In that case, both descriptions can be called in explicitly by the program by using a COPY IDMS SUBSCHEMA-LR-CTRL statement

For more information about the IDMS-RECORDS MANUAL and the COPY IDMS statements, see Precompiler-Directive Statements.

You should examine the LR-STATUS field of the LRC block for all possible statuses after every call to LRF. If the value returned is LR-ERROR, you should then examine the ERROR-STATUS field of the IDMS or IDMS-DC communications block.

The following figure shows the layout of the LRC block. Each field is described separately, following the figure.

Logical-Record Request Control Block

                      ┌───────────┐
                      │ LRC BLOCK │
                      └───────────┘
                                                    Length     Suggested
                         Field        Data Type    (bytes)     Initial Value
    ┌─────┐
    │1  2 │              LRC-LRPXELNG Binary        2 (Halfword)  00
    ├─────┤
    │3  4 │              LRC-MAXVXP   Binary        2 (Halfword)  00
    ├─────┴┐
    │5   8 │             LRIDENT      Alphanumeric  4       'LRC'
    ├──────┴──┐
    │9     16 │          LRVERB       Alphanumeric  8       Spaces
    ├─────────┴──┐
    │17       32 │       LRNAME       Alphanumeric  16       Spaces
    ├────────────┤
    │33       48 │       LR-STATUS    Alphanumeric  16       Spaces
    ├────────────┤
    │49       64 │       FILLER       ...           16       ...
    ├──┬───┬─────┴──────┐
    │65(variable-length)│PXE          Mixed         ...      ...
    └──┴───┴────────────┘
    * word aligned

The LRC block contains the following fields:

Field name

Position

Description

LRC-LRPXELNG

1-2

 

Specifies the length of the LRC block.

LRC-MAXVXP

3-4

Specifies the length of the work area required to evaluate the WHERE clause.

LRIDENT

5-8

The constant 'LRC' followed by a space.

LRVERB

9-16

The verb passed to LRF.

LRNAME

17-32

The name of the logical record being accessed.

LR-STATUS

33-48

The path status of a logical-record request.

Path statuses are 1- to 16-character strings; they can be either standard or defined in the subschema by the DBA. LRF provides three standard path statuses: LR-FOUND, LR-NOT-FOUND, and LR-ERROR.

Note: For more information about path statuses, see the Logical-Record Clauses.

FILLER

49-64

Used internally by LRF.

PXE

65-end

The variable-length expansion of the WHERE clause. From 0 to 512 1-byte elements.

The 512-byte limit can be raised or lowered by using the SIZE IS parameter of the COPY IDMS SUBSCHEMA-LR-CTRL statement.

Note: For more information about the SIZE IS parameter and the COPY IDMS statement, see Precompiler-Directive Statements.

IDMS-DC Communications Block

The IDMS DC communications block replaces the IDMS communications block when the operating mode is either IDMS-DC or DC-BATCH. At run time, the IDMS-DC communications block is used to pass information about the outcome of requested data communications and database services to an application program.

The data description (identified as SUBSCHEMA-CTRL) of the IDMS-DC communications block is copied from the data dictionary into the WORKING-STORAGE SECTION or LINKAGE SECTION of the program. When the program is submitted to the precompiler, the IDMS-DC communications block is copied automatically unless the IDMS-RECORDS MANUAL statement is included in the ENVIRONMENT DIVISION. In that case, the program can explicitly call in the data description by using a COPY IDMS SUBSCHEMA-CTRL statement (for more information on the IDMS-RECORDS MANUAL and the COPY IDMS statements, see Precompiler-Directive Statements).

The following figure shows the layout of the IDMS-DC communications block. Each field is described separately below.

                   ┌──────────────────────────────┐
                   │ IDMS-DC COMMUNICATIONS BLOCK │
                   └──────────────────────────────┘

                   Field               Data Type        (bytes)     Initial Value
  ┌────────┐
 *│1     8 │       PROGRAM-NAME        Alphanumeric     8           Program Name
  ├──────┬─┘
  │9  12 │         ERROR-STATUS        Alphanumeric     4          '1400'
  ├──────┤
  │13  16│         DBKEY               Binary           4(Fullword) 0000
  ├──────┴───┐
  │17     32 │     RECORD-NAME         Alphanumeric     16          Spaces
  ├──────────┤
  │33     48 │     AREA-NAME           Alphanumeric     16          Spaces
  ├──────────┤
  │49     64 │     ERROR-SET           Alphanumeric     16          Spaces
  ├──────────┤
  │65     80 │     ERROR-RECORD        Alphanumeric     16          Spaces
  ├──────────┤
  │81     96 │     ERROR-AREA          Alphanumeric     16          Spaces
  ├──────────┘
**│ 97  100 │      PAGE-INFO           Binary           4(Fullword) 0000
  └─────────┘
  ┌────┬────┬────┐
  │ 97   ... 196 │ IDBMSCOM-AREA       Alphanumeric     100         Low Values
  ├────┴───┬┴────┘
  │197 200 │       DIRECT-DBKEY        Binary           4(Fullword) 0000
  ┌────┬────┬────┐
  │ 201  ... 300 │ DCBMSCOM-AREA       Alphanumeric     100         Low Values
  ├────┴───┬┴────┘
  │301 304 │       SSC-ERRSTAT-SAVE    Alphanumeric     4           Spaces
  ├────────┤
  │305 308 │       SSC-DMLSEQ-SAVE     Binary           4(Fullword) 0000
  ├────────┤
  │309 312 │       DML-SEQUENCE        Binary           4(Fullword) 0000
  ├────────┤
  │313 316 │       RECORD-OCCUR        Binary           4(Fullword) 0000
  ├────────┤
  │317 320 │       SUBSCHEMA-CTRL-END  Alphanumeric     4           Spaces
  └────────┘
 * word aligned
 ** PAGE-INFO-GROUP overlays bytes 97 and 98 and PAGE-INFO-DBK-FORMAT
  overlays bytes 99 and 100. Both of these fields are binary datatype each
  having a length of two bytes. Suggested initial values for
  both are 00. Together these two fields represent PAGE-INFO. 
Field Descriptions

The IDMS-DC communications block contains the following fields that describe program status information:

Field name

Position

Description

PROGRAM-NAME

1-8

The name of the program being executed, as defined in the program's IDENTIFICATION DIVISION.

This field is initialized automatically at the beginning of program execution if the program contains a COPY IDMS SUBSCHEMA-BINDS statement in its PROCEDURE DIVISION. Otherwise, it must be initialized by the programmer.

ERROR-STATUS

9-12

A value indicating the outcome of the last DML statement executed. The ERROR-STATUS field must be initialized to 1400 by the program.

This field is updated by CA IDMS after (attempted) performance of a requested database or data communications service and before control is returned to the program.

The ERROR-STATUS field and its use are described in greater detail under ERROR-STATUS Field and Codes.

A program that consists of more than one run unit must reinitialize the ERROR-STATUS field to 1400 after finishing one run unit and before binding the next.

DBKEY

13-16

The database key of the last record accessed by the run unit. For example, after successful execution of a FIND command, DBKEY is updated with the database key of the located record. DBKEY is not changed if the database call results in a nonzero status condition.

RECORD-NAME

17-32

The name of the last record accessed successfully by the run unit.

This field is left-justified and padded with spaces on the right.

AREA-NAME

33-48

The name of the last area accessed successfully by the run unit.

This field is left-justified and padded with spaces on the right.

ERROR-SET

49-64

The name of the set involved in the last operation to produce a nonzero status code.

This field is left-justified and padded with spaces on the right.

ERROR-RECORD

65-80

The name of the record involved in the last operation to produce a nonzero status code.

This field is left-justified and padded with spaces on the right.

ERROR-AREA

81-96

The name of the area involved in the last operation to produce a nonzero status code.

This field is left-justified and padded with spaces on the right.

PAGE-INFO

97-100

Two binary halfwords that represent the page information associated with the last record accessed by the run unit. PAGE-INFO is not changed if the call to the DBMS results in a non-zero status. The first halfword (PAGE-INFO-GROUP) represents the page group number. The second halfword (PAGE-INFO-DBK-FORMAT) represents the db-key radix.

The db-key radix portion of the page information can be used in interpreting a db-key for display purposes and in formatting a db-key from page and line numbers. The db-key radix represents the number of bits within a db-key value that are reserved for the line number of a record. By default, this value is 8, meaning that up to 255 records can be stored on a single page of the area. Given a db-key, you can separate its associated page number by dividing the db-key by 2 raised to the power of the db-key radix. For example, if the db-key radix is 4, you would divide the db-key value by 2**4. The resulting value is the page number of the db-key. To separate the line number, you would multiply the page number by 2 raised to the power of the db-key radix and subtract this value from the db-key value. The result would be the line number of the db-key. The following two formulas can be used to calculate the page and line numbers from a db-key value:

Page-number = db-key value /

(2 ** db-key radix)

Line-number = db-key value -

(page-number *

( 2 ** db-key radix))

IDBMSCOM-AREA

97-196

Used internally by CA IDMS for specification of DBMS runtime function information.

DIRECT-DBKEY

197-200

Either a user-specified db-key value or a null db-key value of -1.

This field is used for storing a record with a location mode of DIRECT. It must be initialized by the user; it is not updated by CA IDMS.

Native VSAM users: The DIRECT-DBKEY field can be used when storing a record in a native VSAM relative record data set (RRDS). You must initialize DIRECT-DBKEY to the relative record number of the record being stored.

DCBMSCOM-AREA

201-300

Used internally by CA IDMS for specification of runtime function information.

SSC-ERRSTAT-SAVE

301-304

Used by the IDMS-STATUS routine to save a nonzero ERROR-STATUS in the event of an abend.

SSC-DMLSEQ-SAVE

305-308

Used by the IDMS-STATUS routine to save the value of DML-SEQUENCE in the event of an abend.

DML-SEQUENCE

309-312

The source level sequence number generated by the precompiler.

This field is updated before each call to CA IDMS if DEBUG is specified in the program's ENVIRONMENT DIVISION; it is not used by the runtime system.

RECORD-OCCUR

313-316

A record occurrence sequence identifier used internally by CA IDMS.

SUBSCHEMA-CTRL-END

317-320

Marks the end of the IDMS-DC communications block.

ERROR-STATUS Field and Codes

You can use the ERROR-STATUS field of the IDMS or IDMS-DC communications block to determine if a DML request was processed successfully. The DBMS or the DC system returns a value to the ERROR-STATUS field indicating the result of each DML request. For more information on using the ERROR-STATUS field, see Error Detection.

LRF users: You should check the LR-STATUS field of the LRC block before checking the ERROR-STATUS field.

Major and Minor Codes

The ERROR-STATUS field is a four-byte zoned decimal field. The first two bytes represent a major code; the second two bytes represent a minor code. Major codes identify the function performed; minor codes describe the status of that function.

Value of Codes

A value of 0000 indicates successful completion of the requested function. A value other than 0000 indicates completion of the function in a manner that may or may not be in error, depending on your expectations. For example, 0326 (DB-REC-NOT-FOUND) should be anticipated after FIND CALC retrieval; this allows you to trap the condition and continue processing.

DB status codes have a major code in the range 01 to 20. They occur during database access in batch or online processing. DC status codes have a major code in the range 30 to 51. They occur in online or DC-BATCH processing. Status codes with a major code of 00 apply to all DML functions. DB status codes and DC status codes are discussed separately below.

DB Status Codes

The following tables list DB major and minor codes and their meanings.