Previous Topic: Minor DC Status CodesNext Topic: Data Manipulation Language Statements


Precompiler-Directive Statements

Compiler-directive statements instruct the precompiler to copy source code from the data dictionary into the COBOL application program. These statements do not produce any executable commands. Compiler-directive statements are coded beginning in columns 8-11 of the IDENTIFICATION and ENVIRONMENT DIVISIONs, and in columns 8-72 of the DATA and PROCEDURE DIVISIONs, as follows:

All compiler-directive statements are optional except the SCHEMA SECTION and DB statement. If a program accesses the database, it must include a SCHEMA SECTION that contains a DB statement identifying the subschema. All other compiler-directive statements can be omitted; the precompiler will generate the required source code components automatically.

If the program does not access the database (that is, does not invoke a subschema and does not issue any DML statements), the SCHEMA SECTION and DB statement can be omitted as well.

The COPY IDMS and other compiler-directive statements are explained separately for each of the following divisions. References to the IDMS communications block apply equally to the IDMS-DC communications block.

This section contains the following topics:

IDENTIFICATION DIVISION

ENVIRONMENT DIVISION

DATA DIVISION

PROCEDURE DIVISION

IDENTIFICATION DIVISION

The PROGRAM-ID statement in the IDENTIFICATION DIVISION identifies your program to the precompiler.

Syntax
►►─── IDENTIFICATION DIVISION. ───────────────────────────────────────────────►

 ►─── PROGRAM-ID.program-name ─┬──────────────────────────┬───────────────────►◄
                               └─ VERSION version-number ─┘
Parameters
PROGRAM ID

Specifies the program.

program-name

The name of the program. If the program has been previously defined in the data dictionary through IDD facilities, program-name must match the name assigned to the program when it was defined in order for the precompiler to recognize it as the same program.

VERSION

Qualifies program-name with a version number (for example, for purposes of testing or development).

version-number

An integer in the range 1 through 9999. By default, if you do not specify a number, the default is either the highest number defined in the data dictionary for the named program or 1 if the program does not already exist in the data dictionary.

ENVIRONMENT DIVISION

An IDMS-CONTROL SECTION is required in the ENVIRONMENT DIVISION to establish the following:

Syntax
►►─── ENVIRONMENT DIVISION. ──────────────────────────────────────────────────►◄

 ►─┬──────────────────────────────────────────────────────────────────────────►─
   └─ IDMS-CONTROL SECTION. ──────────────────────────────────────────────────

─►──────────────────────────────────────────────────────────────┬─────────────►
  ─── PROTOCOL. ─┬────────────────────────────────────────────┬─┘
                 └─ MODE is ─┬─ BATCH ◄ ────────┬─┬─────────┬─┘
                             ├─ IDMS-DC ────────┤ └─ DEBUG ─┘
                             ├─ DC-BATCH ───────┤
                             └─ user-mode-name ─┘
 ►─┬──────────────────────────────────────┬───────────────────────────────────►
   └─ SUBSCHEMA-NAMES LENGTH IS ─┬─ 16 ◄─┬┘
                                 └─ 18 ──┘

 ►─┬──────────────────────────────────────────────────────────────────────────►─
   └─ IDMS-RECORDS ───────────────────────────────────────────────────────────

─►──────────────────────────────────────────────────────────────────────────┬─►◄
 ┬─ WITHIN WORKING-STORAGE section ◄─┬┬───────────────────────────────┬── . ┘
 ├─ WITHIN LINKAGE section ──────────┘└─ levels INCREMENTED by count ─┤
 └─ MANUAL ───────────────────────────────────────────────────────────┘
Parameters
PROTOCOL

Specifies how CA IDMS CALL statements are generated and whether the debugging sequence option is included.

MODE IS

Identifies the operating mode used by the precompiler to generate call statements for the program's PROCEDURE DIVISION DML statements.

BATCH

Specifies to execute the program in batch mode.

This is the default.

The IDMS communications block is copied into variable storage; standard CALL statements (CALL 'IDMS') are generated in the PROCEDURE DIVISION.

IDMS DC

Specifies to execute the program in IDMS-DC mode.

The IDMS DC communications block is copied into variable storage; CA IDMS CALL statements (CALL 'IDMSCOBI') are generated in the PROCEDURE DIVISION for DC requests.

DC-BATCH

Specifies to execute the program in DC-BATCH mode. The IDMS-DC communications block is copied into variable storage; DC-BATCH CALL statements (CALL 'IDMSDCCI') are generated in the PROCEDURE DIVISION for DC requests.

Specify MODE IS DC-BATCH to access DC queues and printers from batch applications running under the central version.

user-mode-name

Specifies to execute the program in a special environment (for example, under a teleprocessing monitor or in a user-defined operating mode) as determined by the DBA. The appropriate communications block is copied into variable storage; mode-specific CALL statements (for example, in CICS: CALL 'IDMSINC1' USING DFHCADS) are generated in the PROCEDURE DIVISION. The following list provides the standard operating modes (protocols) available for COBOL programs.

If user-mode-name specifies an AUTOSTATUS protocol (for example, CICS-AUTOSTATUS), the precompiler automatically generates an IDMS-STATUS statement after every DML command except IF. When using an AUTOSTATUS protocol, be sure to include the COPY IDMS IDMS-STATUS statement in the PROCEDURE DIVISION. For details on programming under an AUTOSTATUS protocol, see Communications Blocks and Error Detection.

DEBUG

Specifies that a unique DML sequence number is placed in the IDMS communications block for each DML statement. These numbers appear in columns 81-88 of the COBOL compiler output listing in the form DMLCnnnn. The precompiler generates numbers to identify the sequence in which DML statements appear in the program. Depending on the error routine defined by the DBA, you can use the DML sequence number to help debug your program.

If DEBUG is not specified, the precompiler does not associate sequence numbers with source statements.

SUBSCHEMA-NAMES LENGTH IS

Specifies whether to use a 16-byte or 18-byte communications block.

For information about 16-byte communications blocks, see Communications Blocks and Error Detection.

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

IDMS-RECORDS

Specifies whether source CA IDMS data description code is inserted into the DATA DIVISION automatically.

WITHIN WORKING-STORAGE section

Instructs the processor to insert automatically the copied DATA DIVISION components as the last entries in the WORKING-STORAGE SECTION of the source program.

This is the default.

WITHIN LINKAGE section

Instructs the processor to automatically insert the copied DATA DIVISION components as the last entries in the LINKAGE SECTION of the source program. Any VALUE clauses present in source code will be dropped automatically.

levels INCREMENTED by

Varies the level numbers for inserted descriptions from those stored in the data dictionary. If you specify a level number, the first level of code will be inserted to the level specified by count; all other levels will be adjusted accordingly. If you do not specify a level, the descriptions inserted will begin at 01 and have the same level numbers as originally specified in the data dictionary.

count

An integer in the range 1 through 48.

Specifies the value by which the DATA DIVISION level numbers (including the 01 level number) of all stored elements are to be incremented.

Note: Using the LEVELS INCREMENTED BY clause may cause unpredictable results if record fields have been defined with a SYNCHRONIZED clause. Such fields may contain extra bytes (slack bytes) inserted to ensure correct alignment. Because CA IDMS does not recognize slack bytes as functional, it may misinterpret data fields that contain them. Therefore, you should ensure that all fields and records are properly structured.

MANUAL

Indicates that CA IDMS-related source data description code (for example, SUBSCHEMA-CTRL or SUBSCHEMA-NAMES) will be inserted explicitly into the source program by means of DATA DIVISION COPY IDMS statements. If MANUAL is not specified, the required DATA DIVISION code is inserted automatically by the precompiler.

Standard Modes Available for COBOL Programs

BATCH

DC-BATCH

TASKMASTER

BATCH-AUTOSTATUS

IDMS-DC

TASKMASTER-AUTO

CICS

INTERCOMM

UTM

CICS-AUTOSTATUS

INTERCOMM-AUTO

UTM-AUTOSTATUS

CICS-EXEC

INTERCOMM-REENT

WESTI

CICS-EXEC-AUTO

ICOMM-REENT-AUTO

WESTI-AUTOSTATUS

CICS-STANDARD

SHADOW

WESTI-REENT

CICS-STD-AUTO

SHAD-AUTOSTATUS

WESTI-REENT-AUTO

The following example illustrates the statements used to code the IDMS-CONTROL SECTION of a program running under DC with DEBUG sequencing and automatic insertion of IDMS-RECORDS in WORKING-STORAGE SECTION:

ENVIRONMENT DIVISION.
 IDMS-CONTROL SECTION.
 PROTOCOL.
 MODE IS IDMS-DC
  DEBUG
  IDMS-RECORDS WITHIN WORKING-STORAGE SECTION.

DATA DIVISION

Compiler-directive statements can be in the following sections of the DATA DIVISION:

FILE SECTION

The FILE SECTION can include one or more COPY IDMS statements to copy non-IDMS file descriptions from the data dictionary into the program. Each COPY IDMS statement generates the file definition that includes record size, block size, and recording mode from the data dictionary. Additionally, any records defined within the file through the IDD facilities are also copied.

Syntax
►►─── FILE SECTION. ──────────────────────────────────────────────────────────►

 ►─┬─────────────────────────────────────────────────────────────────┬────────►◄
   │ ┌─────────────────────────────────────────────────────────────┐ │
   └─▼─ COPY IDMS FILE file-name ─┬──────────────────────────┬─ . ─┴─┘
                                  └─ VERSION version-number ─┘
Parameters
COPY IDMS FILE

Copies the description of a non-IDMS file into the DATA DIVISION.

file-name

Either the primary name or a synonym for a file defined in the data dictionary.

VERSION

Qualifies file-name with a version number.

If you do not specify a version number, the default is the highest version number defined in the data dictionary for file-name.

version-number

An integer in the range 1 through 9999.

SCHEMA SECTION

For any program that accesses the database, a SCHEMA SECTION is included in the DATA DIVISION to identify a subschema view to the precompiler. The subschema named in the DB statement of the SCHEMA SECTION determines which record descriptions can be copied into the program from the data dictionary. Every DML command issued by the program is checked against the record, set, and area access restrictions specified in this subschema.

Syntax
►►─── SCHEMA SECTION. ────────────────────────────────────────────────────────►

 ►─── DB subschema-name WITHIN schema-name ─┬──────────────────────────┬─ . ──►◄
                                            └─ VERSION version-number ─┘
Parameters
DB subschema-name

Specifies a subschema defined in the data dictionary. If the DBA has chosen to preregister valid program names for this subschema in the data dictionary, the program named in the IDENTIFICATION DIVISION must be associated with subschema-name in the data dictionary.

WITHIN schema-name

Specifies the schema under which subschema-name is compiled.

VERSION

Qualifies schema-name with a version number.

If you do not specify a version number, the default is the highest version number defined in the data dictionary for file-name.

version-number

An integer in the range 1 through 9999.

MAP SECTION

The MAP SECTION notifies the precompiler that mapping mode terminal I/O is being used, defines the program's maps, and specifies the size of map field lists.

Syntax
►►─── MAP SECTION. ───────────────────────────────────────────────────────────►

 ►─┬─────────────────────────────────────┬────────────────────────────────────►
   └─ MAX FIELD LIST is field-list-size ─┘

  ┌──────────────────────────────────────────────────────────────────────────
 ►─▼─ MAP map-name ─┬──────────────────────────┬──────────────────────────────►─
                    └─ VERSION version-number ─┘

───────────────────────────────────────────────────┐
─►─┬─────────────────────────────────────────┬─ . ─┴──────────────────────────►◄
   └─ TYPE is ─┬─ STANDARD ◄ ─┬─┬──────────┬─┘
               └─ EXTENDED ───┘ └─ PAGING ─┘
Parameters
MAX FIELD LIST is

Specifies the size of field lists used in MODIFY MAP and INQUIRE MAP statements.

field-list-size

The field list size or the size is expressed as a numeric constant.

The specified size must be at least one greater than the size of the largest field list used by the program. For example, if the largest map field list contains 5 fields, the value of field-list-size must be at least 6.

The MAX FIELD LIST statement must be specified if the program uses a field list in a MODIFY MAP or INQUIRE MAP request.

MAP

Defines the map used by the program. This parameter can be repeated as necessary to define each map to be used.

map-name

The name of a map used by the program.

VERSION

Qualifies the named map with a version number.

version-number

An integer in the range 1 through 9999.

There is no default for version-number. If your site uses multiple versions, you must specify a version number.

TYPE Is

Specifies whether the map request block (MRB) built for the map is to be standard or extended.

STANDARD

Specifies that the map has standard 3270-type terminal attributes.

This is the default.

EXTENDED

Specifies that the map has extended 3279-type terminal attributes (for example, color, blinking fields, reverse video).

PAGING

Specifies that the named map is a pageable map.

Note: For more information about pageable maps, see "MAP OUT" and MAP IN, or see the CA IDMS Mapping Facility Guide.

The following example shows the DATA DIVISION statements required to access the EMPSS09 subschema and the EMPMAPLR map; the largest map field list allowed is 4.

DATA DIVISION.
SCHEMA SECTION.
DB EMPSS09 WITHIN EMPSCHM.
MAP SECTION.
MAX FIELD LIST IS 5.
MAP EMPMAPLR VERSION 1 TYPE IS STANDARD.

WORKING-STORAGE and LINKAGE SECTIONS

COPY IDMS statements can be coded in the WORKING-STORAGE and LINKAGE SECTIONs, allowing you to explicitly copy source code from the data dictionary into the program. No COPY IDMS statements are required in the DATA DIVISION unless the IDMS-RECORDS MANUAL clause has been specified in the IDMS-CONTROL SECTION of the ENVIRONMENT DIVISION.

If the source code to be copied into the LINKAGE SECTION includes VALUE clauses, these clauses are not copied.

WORKING-STORAGE SECTION and LINKAGE SECTION source code requirements differ according to the usage mode defined in the program's subschema: DML, LR, or MIXED. These usage modes determine whether the program can access database records only, logical records only, or both database records and logical records. The program should not copy components that conflict with its subschema's usage mode (for example, do not copy SUBSCHEMA-LR-CTRL if the subschema's usage mode is DML).

An explanation of each usage mode and the required source code components in the program is shown below:

The use of MIXED mode is not recommended for the following reasons:

The precompiler inserts the required data descriptions into the program automatically unless IDMS RECORDS MANUAL is specified in the IDMS-CONTROL SECTION of the ENVIRONMENT DIVISION. If IDMS RECORDS MANUAL is specified, you must explicitly copy the required components, as outlined above, by coding COPY IDMS statements in the DATA DIVISION.

UTM modes only: You must include SUBSCHEMA-CTRL and all subschema records in the LINKAGE SECTION. You must include SUBSCHEMA-NAMES in the WORKING-STORAGE SECTION.

Syntax
►►─┬─ WORKING STORAGE SECTION. ─┬─────────────────────────────────────────────►
   └─ LINKAGE SECTION. ─────────┘

 ►───┬────────────────────────────────────────────────────────────────────────►─
     │ ┌──────────────────────────────────────────────────────────────────────
     └─▼─┬────────────────┬─ COPY-IDMS ───────────────────────────────────────
         └─ level-number ─┘
─►──────────────────────────────────────────────────────────────────────────┬─►◄
 ─────────────────────────────────────────────────────────────────────────┐ │
 ─┬─ SUBSCHEMA-DML-LR-DESCRIPTION ──────────────────────────────────┬─ . ─┴─┘
  ├─ SUBSCHEMA-DESCRIPTION ─────────────────────────────────────────┤
  ├─ SUBSCHEMA-CONTROL ─────────────────────────────────────────────┤
  ├─ SUBSCHEMA-CTRL ────────────────────────────────────────────────┤
  ├─ SUBSCHEMA-NAMES ───────────────────────────────────────────────┤
  ├─ SUBSCHEMA-SSNAME ──────────────────────────────────────────────┤
  ├─ SUBSCHEMA-RECNAMES ────────────────────────────────────────────┤
  ├─ SUBSCHEMA-SETNAMES ────────────────────────────────────────────┤
  ├─ SUBSCHEMA-AREANAMES ───────────────────────────────────────────┤
  ├─ SUBSCHEMA-RECORDS ─────────────────────────────────────────────┤
  ├─ RECORD rec-name ─┬────────────────────┬┬──────────────────────┬┤
  │                   └─ VERSION vers-num ─┘└─ REDEFINES rec-name ─┘│
  ├─ TRANSACTION-STATISTICS ────────────────────────────────────────┤
  ├─ SUBSCHEMA-LR-DESCRIPTION ──────────────────────────────────────┤
  ├─ SUBSCHEMA-LR-CONTROL ──────────────────────────────────────────┤
  ├─ SUBSCHEMA-LR-CTRL ─┬──────────────────────────┬────────────────┤
  │                     ├─ SIZE IS lrc-block-size ─┤                │
  │                     └─ 512 ◄ ──────────────────┘                │
  ├─ SUBSCHEMA-LR-NAMES ────────────────────────────────────────────┤
  ├─ SUBSCHEMA-LR-RECORDS ──────────────────────────────────────────┤
  ├─ LR logical-record-name ─┬─────────────────────────┬────────────┤
  │                          └─ REDEFINES record-name ─┘            │
  ├─ MAPS ──────────────────────────────────────────────────────────┤
  ├─ MAP map-name ──────────────────────────────────────────────────┤
  ├─ MAP CONTROLS ──────────────────────────────────────────────────┤
  ├─ MAP CONTROL map-name ──────────────────────────────────────────┤
  └─ MAP RECORDS ───────────────────────────────────────────────────┘
Parameters
level-number

An integer in the range 01 through 48.

Instructs the precompiler to copy the descriptions into the program at a level other than that originally specified for the description in the data dictionary. If you specify a level number, the first level of code will be copied to the specified level; all other levels will be adjusted accordingly. If you do not specify a level, the descriptions copied will begin at 01 and have the same level numbers as originally specified in the data dictionary.

Note: Using the level-number clause can cause unpredictable results if record fields have been defined with a SYNCHRONIZED clause. Such fields may contain slack bytes, inserted to ensure correct alignment. Because CA IDMS does not regard slack bytes as functional, it may misrepresent fields that contain such bytes. Therefore, you should ensure that all fields and records are properly structured.

COPY IDMS

Requests that the specified source data description code be copied into the DATA DIVISION at the location of the COPY IDMS statement.

SUBSCHEMA-DML-LR-DESCRIPTION

Copies all components required to access both database and logical records (SUBSCHEMA-CTRL, SUBSCHEMA-NAMES, SUBSCHEMA-RECORDS, SUBSCHEMA-LR-CTRL, SUBSCHEMA-LR-RECORDS). SUBSCHEMA-DML-LR-DESCRIPTION should be specified only when the subschema's usage mode is MIXED; do not specify SUBSCHEMA-DML-LR-DESCRIPTION if the usage mode is DML or LR.

SUBSCHEMA-DESCRIPTION

Copies all components required to access database records (SUBSCHEMA-CTRL, SUBSCHEMA-NAMES, and SUBSCHEMA-RECORDS). Do not specify SUBSCHEMA-DESCRIPTION if the subschema's usage mode is LR.

SUBSCHEMA-CONTROL

Copies both the SUBSCHEMA-CTRL and SUBSCHEMA-NAMES components. Do not specify SUBSCHEMA-CONTROL if the subschema's usage mode is LR.

SUBSCHEMA-CTRL

Copies the IDMS communications block data description; if the operating mode is IDMS-DC or DC-BATCH, SUBSCHEMA-CTRL copies the IDMS-DC communications block.

SUBSCHEMA-NAMES

Copies the eight-character literal name of the subschema and the literal names of all database records, sets, and areas contained in the subschema. SUBSCHEMA-NAMES includes SUBSCHEMA-SSNAME, SUBSCHEMA-RECNAMES, SUBSCHEMA-SETNAMES, and SUBSCHEMA-AREANAMES. Do not specify SUBSCHEMA-NAMES if the subschema's usage mode is LR.

SUBSCHEMA-SSNAME

Copies the eight-character literal name of the program's subschema. Do not specify SUBSCHEMA-SSNAME if the subschema's usage mode is LR.

SUBSCHEMA-RECNAMES

Copies the literal names of all database records contained in the subschema. Do not specify SUBSCHEMA-RECNAMES if the subschema's usage mode is LR.

SUBSCHEMA-SETNAMES

Copies the literal names of all sets contained in the subschema. Do not specify SUBSCHEMA-SETNAMES if the subschema's usage mode is LR.

SUBSCHEMA-AREANAMES

Copies the literal names of all database areas that can be accessed through the subschema. Do not specify SUBSCHEMA-AREANAMES if the subschema's usage mode is LR.

SUBSCHEMA-RECORDS

Copies the descriptions of all records contained in the subschema. COBOL synonyms defined for the subschema records in the data dictionary may be copied into the program, according to the rules of synonym usage. Do not specify SUBSCHEMA-RECORDS if the subschema's usage mode is LR.

Note: The OCCURS DEPENDING ON clause will be commented out for all schema-owned records. Therefore, although the maximum length of variable storage will be reserved, only the correct amount of data will be transferred to variable storage at run time.

Since COBOL will doubleword align an 01 level record, the precompiler adds up to seven bytes, if necessary, to make the record length divisible by eight when copying in a schema-owned record to an 01 level.

RECORD

Copies the description of a record defined in the data dictionary. If the subschema's usage mode is LR, only copy in IDD work records.

rec-name

The name of the record to be copied. Either the primary name or a synonym for a record stored in the data dictionary.

Schema-owned records cannot be copied into non-IDMS programs (that is, programs that do not use a subschema and that do not access the database). However, a synonym defined for a schema-owned record can be copied into a non-IDMS program (use the VERSION clause to identify the synonym).

IDD records: If an operating mode is associated with record-name in the data dictionary, it must agree with the mode in effect for the program (see "ENVIRONMENT DIVISION" earlier in this chapter).

VERSION

Optionally qualifies IDD records (but not schema-owned records) with a version number.

If you do not specify a version number, the default is the highest version number defined in the data dictionary for the language and operating mode under which the program is being compiled.

When copying a record that is schema owned using a synonym name, a version clause is needed, even if the synonym is not schema owned. The only time the version clause may be left off when copying a record using a synonym name is when the record is IDD owned. Once a record becomes schema owned, version clauses are needed.

vers-num

An integer in the range 1 through 9999.

You cannot specify a version number for a rec-name specified in the subschema named in the DB subschema-name statement. The precompiler will automatically copy the correct version into the program.

REDEFINES

Copies a record description to an area previously defined by another record description. Two record descriptions can thus provide alternative definitions of the same storage location.

rec-name

The name of the record to be redefined.

TRANSACTION-STATISTICS

Copies the definition of the transaction statistics block (TSB) with a length of 560 bytes. This block can be used in the ACCEPT TRANSACTION STATISTICS or END TRANSACTION STATISTICS DML statements.

SUBSCHEMA-LR-DESCRIPTION

Copies all components required to access logical records (SUBSCHEMA-CTRL, SUBSCHEMA-LR-CTRL, SUBSCHEMA-LR-NAMES, and SUBSCHEMA-LR-RECORDS). Do not include SUBSCHEMA-LR-DESCRIPTION if the subschema's usage mode is DML.

SUBSCHEMA-LR-CONTROL

Copies the SUBSCHEMA-CTRL, SUBSCHEMA-LR-CTRL, and SUBSCHEMA-LR-NAMES components. Do not include SUBSCHEMA-LR-CONTROL if the subschema's usage mode is DML.

SUBSCHEMA-LR-CTRL

Copies the LRC block data description.

SIZE IS

Specifies the size of that portion of the LRC block that contains information about the logical-request request WHERE clause (PXE).

If included, this parameter should specify a size large enough to accommodate the most complex WHERE clause in the program. The default, 512, is large enough to include approximately 32 operators, operands, and literals.

Do not include SUBSCHEMA-LR-CTRL if the subschema's usage mode is DML.

lrc-block-size

A positive integer in the range 0 through 9999.

Calculate the size as follows:

SUBSCHEMA-LR-NAMES

Copies the literal name of the program's subschema and the literal names of all database areas that can be accessed through the subschema. Logical-record names are not copied into the program. Do not include SUBSCHEMA-LR-NAMES if the subschema's usage mode is DML.

SUBSCHEMA-LR-RECORDS

Copies the descriptions of all logical records defined in the subschema. All participating database records become 02-level group fields, permitting the program to reference as a group field that portion of a logical record that corresponds to a database record. Do not include SUBSCHEMA-LR-RECORDS if the subschema's usage mode is DML.

Note: The OCCURS DEPENDING ON clause will be commented out for all schema-owned records. Therefore, although the maximum length of variable storage will be reserved, only the correct amount of data will be transferred to variable storage at runtime.

When copying a schema-owned record to a level other than 01, the precompiler adds up to seven bytes, if necessary, to make the record length divisible by eight for doubleword alignment.

LR

Copies the description of an individual logical record contained in the subschema.

logical-record-name

The name of the logical record to copy.

REDEFINES

Copies a redefinition of the data contained in another logical record, a database record, or a non-IDMS record, while maintaining the same location in variable storage.

Do not include this statement if the subschema's usage mode is DML.

record-name

The name of the record to be redefined.

MAPS

Copies the map request block (MRB) and map records associated with all maps defined in the MAP SECTION.

MAP map-name

Copies the MRB and map records associated with the named map. The map version number defaults to the version specified for the map in the MAP SECTION.

MAP-CONTROLS

Copies the MRBs associated with all maps specified in the MAP SECTION.

MAP-CONTROL map-name

Copies the MRB for the named map. The map version number defaults to the version specified for the map in the MAP SECTION.

MAP-RECORDS

Copies the map records associated with all maps specified in the MAP SECTION.

Results of COPY IDMS Specifications

The following figure shows the code copied into the DATA DIVISION as a result of COPY IDMS specifications.

                         ┌──────────────────────────────────────────────┐
                         │    Source code components brought in from    │
                         │   the data dictionary by the DML Cprocessor  │
                         ├──┬──┬──┬──┬──┬──┬──┐┌──┬──┬──┬──┐┌──┬──┬──┬──┤
                         │ S│ S│ S│ S│ S│ S│ r││ S│ S│ S│ l││ A│ N│ A│ m│
                         │ U│ U│ U│ U│ U│ U│ e││ U│ U│ U│ o││ l│ a│ l│ a│
                         │ B│ B│ B│ B│ B│ B│ c││ B│ B│ B│ g││ l│ m│ l│ p│
                         │ S│ S│ S│ S│ S│ S│ o││ S│ S│ S│ i││  │ e│  │  │
                         │ C│ C│ C│ C│ C│ C│ r││ C│ C│ C│ c││ M│ d│ M│ ││
                         │ H│ H│ H│ H│ H│ H│ d││ H│ H│ H│ a││ a│  │ a│  │
                         │ E│ E│ E│ E│ E│ E│  ││ E│ E│ E│ l││ p│ M│ p│ n│
                         │ M│ M│ M│ M│ M│ M│  ││ M│ M│ M│  ││  │ a│  │ a│
                         │ A│ A│ A│ A│ A│ A│  ││ A│ A│ A│ │││ R│ p│ R│ m│
                         │  │  │  │  │  │  │ n││  │  │  │  ││ e│  │ e│ e│
                         │ ││ ││ ││ ││ ││ ││ a││ ││ ││ ││ r││ q│ R│ c│  │
                         │  │  │  │  │  │  │ m││  │  │  │ e││ u│ e│ o│ M│
                         │ C│ S│ R│ S│ A│ R│ e││ L│ L│ L│ c││ e│ q│ r│ a│
                         │ T│ S│ E│ E│ R│ E│  ││ R│ R│ R│ o││ s│ u│ d│ p│
                         │ R│ N│ C│ T│ E│ C│  ││  │  │  │ r││ t│ e│ s│  │
                         │ L│ A│ N│ N│ A│ O│  ││ ││ ││ ││ d││  │ s│  │ R│
                         │  │ M│ A│ A│ N│ R│  ││  │  │  │  ││ B│ t│  │ e│
                         │  │ E│ M│ M│ A│ D│  ││ C│ N│ R│ │││ l│  │  │ c│
                         │  │  │ E│ E│ M│ S│  ││ T│ A│ E│  ││ o│ B│  │ o│
                         │  │  │ S│ S│ E│  │  ││ R│ M│ C│ n││ c│ l│  │ r│
                         │  │  │  │  │ S│  │  ││ L│ E│ O│ a││ k│ o│  │ d│
   ┌───────────────────┐ │  │  │  │  │  │  │  ││  │ S│ R│ m││ s│ c│  │ s│
   │COPYIDMSstatements │ │  │  │  │  │  │  │  ││  │ D│ e│ e││ k│  │  │  │
   │codedinthe         │ │  │  │  │  │  │  │  ││  │  │ S│  ││  │  │  │  │
   │DATADIVISION       │ │  │  │  │  │  │  │  ││  │  │  │  ││  │  │  │  │
┌──┴───────────────────┴─┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│SUBSCHEMA-DML-LR-       │ X│ X│ X│ X│ X│ X│  ││  │  │  │  ││  │  │  │  │
│DESCRIPTION             │  │  │  │  │  │  │  ││  │  │  │  ││  │  │  │  │
├────────────────────────┴──┴──┴──┴──┴──┴──┴──┘└──┴──┴──┴──┘└──┴──┴──┴──┤
├────────────────────────┬──┬──┬──┬──┬──┬──┬──┐┌──┬──┬──┬──┐┌──┬──┬──┬──┤
│SUBSCHEMA-DESCRIPTION   │ X│ X│ X│ X│ X│ X│  ││ X│  │ X│  ││  │  │  │  │
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│SUBSCHEMA-CONTROL       │ X│ X│ X│ X│ X│  │  ││  │  │  │  ││  │  │  │  │
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│SUBSCHEMA-CTRL          │ X│  │  │  │  │  │  ││  │  │  │  ││  │  │  │  │
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│SUBSCHEMA-NAMES         │  │ X│ X│ X│ X│  │  ││  │  │  │  ││  │  │  │  │
├────────────────────────┴──┴──┴──┴──┴──┴──┴──┴┴──┴──┴──┴──┴┴──┴──┴──┴──┤
├────────────────────────┬──┬──┬──┬──┬──┬──┬──┬┬──┬──┬──┬──┬┬──┬──┬──┬──┤
│SUBSCHEMA-SSNAME        │  │ X│  │  │  │  │  ││  │  │  │  ││  │  │  │  │
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│SUBSCHEMA-RECNAMES      │  │  │ X│  │  │  │  ││  │  │  │  ││  │  │  │  │
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│SUBSCHEMA-SETNAMES      │  │  │  │ X│  │  │  ││  │  │  │  ││  │  │  │  │
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│SUBSCHEMA-AREANAMES     │  │  │  │  │ X│  │  ││  │  │  │  ││  │  │  │  │
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│SUBSCHEMA-RECORDS       │  │  │  │  │  │ X│  ││  │  │  │  ││  │  │  │  │
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│RECORDrecord-name       │  │  │  │  │  │  │ X││  │  │  │  ││  │  │  │  │
├────────────────────────┴──┴──┴──┴──┴──┴──┴──┘└──┴──┴──┴──┘└──┴──┴──┴──┤
├────────────────────────┬──┬──┬──┬──┬──┬──┬──┐┌──┬──┬──┬──┐┌──┬──┬──┬──┤
│SUBSCHEMA-LR-DESCRIPTION│ X│  │  │  │  │  │  ││ X│ X│ X│  ││  │  │  │  │
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│SUBSCHEMA-LR-CONTROL    │ X│  │  │  │  │  │  ││ X│ X│  │  ││  │  │  │  │
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│SUBSCHEMA-LR-CTRL       │  │  │  │  │  │  │  ││ X│  │  │  ││  │  │  │  │
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│SUBSCHEMA-LR-NAMES      │  │  │  │  │  │  │  ││  │ X│  │  ││  │  │  │  │
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│SUBSCHEMA-LR-RECORDS    │  │  │  │  │  │  │  ││  │  │ X│  ││  │  │  │  │
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│LRlogical-record-name   │  │  │  │  │  │  │  ││  │  │  │ X││  │  │  │  │
├────────────────────────┴──┴──┴──┴──┴──┴──┴──┘└──┴──┴──┴──┘└──┴──┴──┴──┤
├────────────────────────┬──┬──┬──┬──┬──┬──┬──┐┌──┬──┬──┬──┐┌──┬──┬──┬──┤
│MAPS                    │  │  │  │  │  │  │  ││  │  │  │  ││ X│  │ X│  │
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│MAP-CONTROLS            │  │  │  │  │  │  │  ││  │  │  │  ││ X│  │  │  │
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│MAPCONTROLmap-name      │  │  │  │  │  │  │  ││  │  │  │  ││  │ X│  │  │
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│MAPmap-name             │  │  │  │  │  │  │  ││  │  │  │  ││  │ X│  │ X│
├────────────────────────┼──┼──┼──┼──┼──┼──┼──┤├──┼──┼──┼──┤├──┼──┼──┼──┤
│MAP-RECORDS             │  │  │  │  │  │  │  ││  │  │  │  ││  │  │ X│  │
└────────────────────────┴──┴──┴──┴──┴──┴──┴──┴┴──┴──┴──┴──┴┴──┴──┴──┴──┘

PROCEDURE DIVISION

The COPY IDMS statements in the PROCEDURE DIVISION allow inclusion into the source program of BIND statements for CA IDMS records and for procedure source statements defined as modules in the data dictionary by the DBA.

Syntax
►►─── PROCEDURE DIVISION. ────────────────────────────────────────────────────►

 ►─┬──────────────────────────────┬───────────────────────────────────────────►
   └─ COPY IDMS SUBSCHEMA-BINDS. ─┘

 ►─┬─────────────────────────────────────┬────────────────────────────────────►
   └─ COPY IDMS SUBSCHEMA-RECORD-BINDS. ─┘

 ►─┬────────────────────────┬─────────────────────────────────────────────────►
   └─ COPY IDMS MAP-BINDS. ─┘

 ►─┬─────────────────────────────────────────────────────────────────────┬────►◄
   │                                                                     │
   │ ┌─────────────────────────────────────────────────────────────────┐ │
   └─▼─ COPY IDMS module module-name ─┬──────────────────────────┬─ . ─┴─┘
                                      └─ VERSION version-number ─┘
Parameters
COPY IDMS SUBSCHEMA-BINDS

Initializes the PROGRAM-NAME field in the IDMS communications block and copies a standard BIND RUN-UNIT statement and appropriate standard BIND record-name commands for each CA IDMS record in the program's DATA DIVISION. COPY IDMS SUBSCHEMA-BINDS does not generate BIND RECORD statements for logical records, nor are any needed.

In cases where more than one copy of a given database record description (including synonyms) is present in the program, COPY IDMS SUBSCHEMA-BINDS will not automatically generate bind record statements. Individual bind record statements must be issued to bind the record to the correct location.

If IDMS-RECORDS MANUAL has been specified in the ENVIRONMENT DIVISION, the COPY IDMS SUBSCHEMA-BINDS statement generates BINDS only for subschema records explicitly copied into the DATA DIVISION by means of COPY IDMS statements; it does not automatically generate BINDS for all subschema records.

Do not use the COPY IDMS SUBSCHEMA-BINDS statement when binding several records to the same location. Instead, code DML BIND statements in the PROCEDURE DIVISION for each record (for more informails, see BIND RECORD).

Note: If AUTOSTATUS is in use, a PERFORM IDMS-STATUS occurs automatically after each BIND generated by a COPY IDMS SUBSCHEMA-BINDS statement. If AUTOSTATUS is not in use, you should explicitly code the BIND RUN-UNIT and BIND RECORD statements so that a PERFORM IDMS-STATUS can be coded after each BIND.

For more information about AUTOSTATUS, see Chapter 4:.

COPY IDMS SUBSCHEMA-RECORD-BINDS

Copies appropriate standard BIND record-name commands for each CA IDMS record in the program's DATA DIVISION.

In cases where more than one copy of a given database record description (including synonyms) is present in the program, COPY IDMS SUBSCHEMA-RECORD-BINDS will not automatically generate bind record statements. Individual bind record statements must be issued to bind the record to the correct location.

If IDMS-RECORDS MANUAL has been specified in the ENVIRONMENT DIVISION, the COPY IDMS SUBSCHEMA-RECORD-BINDS statement generates BINDS only for subschema records explicitly copied into the DATA DIVISION by means of COPY IDMS statements; it does not automatically generate BINDS for all subschema records.

Do not use the COPY IDMS SUBSCHEMA-RECORD-BINDS statement when binding several records to the same location. Instead, code DML BIND statements in the PROCEDURE DIVISION for each record (for more information, see BIND RECORD).

Note: If AUTOSTATUS is in use, a PERFORM IDMS-STATUS occurs automatically after each BIND generated by a COPY IDMS SUBSCHEMA-BINDS statement. If AUTOSTATUS is not in use, you should explicitly code the BIND RUN-UNIT and BIND RECORD statements so that a PERFORM IDMS-STATUS can be coded after each BIND.

For more information about AUTOSTATUS, see Chapter 4:.

COPY IDMS MAP-BINDS

Copies map- and map-record-specific BIND MAP statements for all maps in the program's MAP SECTION. For more information, see BIND MAP.

COPY IDMS module

Copies source statements from a module stored in the data dictionary into the source program.

The unmodified module is placed into the program by the precompiler at the location of the request. The module can, but need not, contain DML statements. Any DML statements will be examined and expanded within the context of the program's subschema view and compile mode as if they were coded directly.

COPY IDMS MODULE statements can be nested (that is, code invoked by a COPY IDMS MODULE entry can itself contain a COPY IDMS MODULE statement). However, you must ensure that a copied module does not, in turn, copy itself.

module-name

The name of a module previously defined by the DBA by means of the IDD DDDL compiler.

The following standard modules are available for COBOL programs:

Note: The IDMS-STATUS module must be copied into the program if an AUTOSTATUS protocol is in effect, as specified in the IDMS-CONTROL SECTION of the ENVIRONMENT DIVISION.

VERSION

Optionally qualifies module-name with a version number.

If you do not specify a version number, the default is the highest version number defined in the data dictionary for the language mode under which the program is being compiled (for example, BATCH or IDMS-DC).

If no mode-specific version exists for module-name, the non-mode-specific version (if present) is copied. If neither a mode-specific entry nor a non-mode-specific entry for module-name has been established, an error results. The same rules apply to the module's language (that is, version-number defaults to the highest value defined in the data dictionary for the language in which the program is written).

version-number

An integer in the range 1 through 9999.

By default, if you do not specify a version number, the highest value defined in the data dictionary will be used.