This document describes how COBOL data items and related syntax are mapped to Software AG IDL by the IDL Extractor for COBOL using the Extractor Wizard and Mapping Editor. It document covers the following topics:
See also IDL Extraction per Interface Type under COBOL Mapping Editor for guidelines on IDL extraction per interface type.
The IDL Extractor for COBOL maps the following subset of COBOL data types to Software AG IDL data types.
In the table below, the following metasymbols and informal terms are used for the IDL.
The metasymbols "[" and "]" enclose optional lexical entities.
The informal term number
(or in some cases number1
.number2
) is a sequence of numeric characters, for example 123.
COBOL Data Type | Software AG IDL Data Type | Notes | |||
---|---|---|---|---|---|
Alphabetic | PIC A(n) |
An , AVn |
Alphanumeric | 1,2 | |
DBCS | PIC G(n) |
Kn*2 , KVn*2 |
Kanji | 1,2,3 | |
DBCS | PIC N(n) [USAGE] [IS] DISPLAY-1 |
Kn*2 , KVn*2 |
Kanji | 1,2,3 | |
Unicode or DBCS | PIC N(n) |
Un , UVn or Kn*2 , KVn*2 |
Unicode or Kanji | 1,2,3,9 | |
Unicode | PIC N(n) [USAGE] [IS] NATIONAL |
Un , UVn |
Unicode | 1,2 | |
Alphanumeric | PIC X(n) |
An , AVn |
Alphanumeric | 1,2 | |
Numeric | Zoned decimal | PIC 9(n)[V9(m)] |
NUn[,m] |
Unpacked decimal unsigned | 2,4 |
Zoned decimal | PIC S9(n)[V9(m)] |
Nn[,m] |
Unpacked decimal | 2,4 | |
Packed decimal | PIC 9(n) [V9(m)] COMP[UTATIONAL]-3 |
PUn[,m] |
Packed decimal unsigned | 2,4 | |
Packed decimal | PIC S9(n) [V9(m)] COMP[UTATIONAL]-3 |
Pn[,m] |
Packed decimal | 2,4 | |
Packed decimal | PIC 9(n) [V9(m)] PACKED-DECIMAL |
PUn[,m] |
Packed decimal unsigned | 2,4 | |
Packed decimal | PIC S9(n) [V9(m)] PACKED-DECIMAL |
Pn[,m] |
Packed decimal | 2,4 | |
Binary | PIC [S]9(n) BINARY (1<=n<=4) |
I2 |
Integer (medium) | 2,4,5,6 | |
Binary | PIC [S]9(n) BINARY (5<=n<=9) |
I4 |
Integer (large) | 2,4,5,6,7 | |
Computational | PIC 9(n) COMP[UTATIONAL] |
PUn |
Packed decimal unsigned | 2,4,11 | |
Computational | PIC 9(n) COMP[UTATIONAL] (1<=n=4) |
I2 |
Integer (medium) | 2,4,5,6,12 | |
Computational | PIC 9(n) COMP[UTATIONAL] (5<=n=9) |
I4 |
Integer (large) | 2,4,5,6,7,12 | |
Computational | PIC S9(n) COMP[UTATIONAL] |
Pn |
Packed decimal | 2,4,11 | |
Computational | PIC S9(n) COMP[UTATIONAL] (1<=n=4) |
I2 |
Integer (medium) | 2,4,5,6,12 | |
Computational | PIC S9(n) COMP[UTATIONAL] (5<=n=9) |
I4 |
Integer (large) | 2,4,5,6,7,12 | |
Binary | PIC [S]9(n) COMP[UTATIONAL][-4] (1<=n<=4) |
I2 |
Integer (medium) | 2,4,5,6 | |
Binary | PIC [S]9(n) COMP[UTATIONAL][-4] (5<=n<=9) |
I4 |
Integer (large) | 2,4,5,6,7 | |
Binary | PIC [S]9(n) COMP-5 (1<=n<=4) |
I2 |
Integer (medium) | 2,4,6 | |
Binary | PIC [S]9(n) COMP-5 (5<=n<=9) |
I4 |
Integer (medium) | 2,4,6,7 | |
Floating point | COMP[UTATIONAL]-1 |
F4 |
Floating point (small) | 8 | |
Floating point | COMP[UTATIONAL]-2 |
F8 |
Floating point (large) | 8 | |
Alphanumeric-edited | Alphanumeric item containing "0 " or "/ "
|
A(length of PIC) |
Alphanumeric | 10 | |
Numeric-edited | Numeric item containing "DB ", "CR ", "Z ", "$ ",
". ", ", ", "+ ", "- ", "* ", "B ", "O " or "/ "
|
A(length of PIC) |
Alphanumeric | 10 |
Mapping to fixed-length or variable-length Software AG IDL data type is controlled in the extraction settings of the extraction wizard, see Step 4: Define the Extraction Settings and Start Extraction.
Equivalent alternative forms of the PICTURE
clause, e.g. XXX
,
AAA,NNN
, GGG
or 999
may also be used.
The length for IDL data type is given in bytes. For COBOL the length is in DBCS characters (2 bytes).
The character "P[(n)]
" stands for a decimal scaling position, this
character has no effect on the length of the generated data type. Only the data
fraction will be mapped to the Software AG IDL:
01 GROUP1. 10 FIELD1 PIC PPP9999.
will be mapped to IDL:
1 GROUP1 2 FIELD1 NU4
Behavior depends on the COBOL compiler settings:
With COBOL 85 standard, the value range depends on the number of
digits in the PICTURE
clause. This differs from the value range of the IDL data
type using the binary field size instead. If the parameter is of direction "In"
your RPC client application has to ensure the integer value sent is within the
allowed range. See Software AG IDL Grammar.
With no COBOL 85 standard, the value range of the COBOL data type reflects the binary field size, thus matches the IDL data type exactly. In this case, there are no restrictions regarding value ranges. For example:
with operating system z/OS and IBM compiler, see option
TRUNC(BIN)
in your COBOL compiler documentation
with operating systems UNIX and Windows and a Micro Focus
compiler, see option NOTRUNC
in your Micro Focus COBOL
documentation.
For unsigned COBOL data types (without "S
" in the PICTURE
clause) the
value range of the IDL data type differs:
IDL allows negative values, COBOL does not.
For I2, the maximum is 32767 for IDL instead of 65535 for COBOL.
For I4, the maximum is 2147483647 for IDL instead of 4294967294 for COBOL.
COBOL binary or computational items with more than 9 digits in the PICTURE
clause
cannot be mapped to IDL type I. See the following table:
S9(10) thru S9(18) |
Binary doubleword (8 bytes) | -9,223,372,036,854,775 thru +9.223,372,036,854,775 |
9(10) thru 9(18) |
Binary doubleword (8 bytes) | 0 thru 18,446,744,073,709,551 |
COMPUTATIONAL-1
(4-byte, single precision) and COMPUTATIONAL-2
items
(8-byte, double precision) items are an IBM-specific extension. When
floating-point data types are used, rounding errors can occur, so the values of
senders and receivers might differ slightly.
If this form is extracted from a COBOL program originally written for
Micro Focus COBOL and operating system UNIX or Windows, the mapping to the IDL
data type depends on the setting in the IDL Extractor for COBOL Preferences.
See Meaning of PIC N without USAGE clause within pane
Compiler Directives under
Creating a New Local Extractor Environment for Micro Focus (UNIX and Windows). For all other COBOL
program extractions, the mapping is always to IDL data type
Un/Uvn
.
COBOL alphanumeric/numeric edited items will force the generation of
IDL data type A
with an inline comment containing the original COBOL
PICTURE
clause. The CURRENCY SIGN
clause in the
SPECIAL-NAMES
and the CURRENCY
compiler option is not considered.
On platform IBM i, COBOL computational items are mapped by default to packed decimal.
On all platform except IBM i, COBOL computational items are mapped by default to IDL type I.
Depending on the COBOL syntax and the COBOL server implementation, user interaction may be required to get correct extraction results. User interaction can also simplify or modernize the extracted IDL. As a result, the user-defined mapping is contained in a Designer file with extension .cvm that contains COBOL-specific mapping information. See Server Mapping Files for COBOL in the Designer documentation. The following is covered:
See the following COBOL syntax:
88condition_name
VALUE [IS] 'literal_1
' 88condition_name
VALUE [IS] 'literal_1
' [THRU | THROUGH] 'literal_2
' 88condition_name
VALUES [ARE] 'literal_1
' [THRU | THROUGH] 'literal_2
'
Semantically, level-88 condition names can be
Enumeration Type Values
If your COBOL server requires the level-88 value to be provided on a
call-by-call basis, that is, the value may change with every call, map the level-88
base variable to a simple IDL parameter with the desired direction In or InOut.
RPC clients have to pass correct values, the same as defined by the level-88
condition names.
Single Constant Values
If your COBOL server interface expects for your purpose always a
constant value, map the level-88 condition names to a constant.
For more information and COBOL examples, see Mapping Editor IDL Interface mapping function Set COBOL Data Items to Constants for interface type DFHCOMMAREA (In same as Out, In different to Out) | Large Buffer (In same as Out, In different to Out) | Channel Container | Batch | IMS BMP | Micro Focus | IMS Connect | COBOL Converter (In same as Out, In different to Out).
Function or Operation Codes
If your COBOL server implements verious functions or operations and the level-88 values are function or operation codes, map
the
COBOL interface to multiple IDL interfaces. For more information and COBOL examples see the
Mapping Editor IDL Interface mapping function Map to Multiple IDL Interfaces for interface type DFHCOMMAREA (In same as Out, In different to Out) | Large Buffer (In same as Out, In different to Out) | Channel Container | Batch | IMS BMP | Micro Focus | IMS Connect | COBOL Converter (In same as Out, In different to Out).
If the mapping functions Server Mapping Files for COBOL.
or are used, a server mapping file is required to provide additional information. SeeThis section covers the following topics:
COBOL server programs do not contain parameter direction information (input, output).
Therefore IDL directions (see attribute-list
under Software AG IDL Grammar in the IDL Editor documentation) need to be added manually in the COBOL Mapping Editor.
See Map to In, Out, InOut for interface type DFHCOMMAREA (In same as Out) | Large Buffer (In same as Out) | Batch | IMS BMP | Micro Focus | COBOL Converter (In same as Out).
Numbers in the first position of the parameter name are not allowed in Software AG IDL syntax (see Software AG IDL Grammar). Thus COBOL names starting with a number are prefixed with the character "#" by default. For example:
01 1BSP PIC XXX.
by default will be mapped to Software AG IDL:
01 #1BSP A(3).
If a parameter name is not specified, e.g.
01 GROUP1. 10 FIELD1 PIC XX. 10 PIC XX. 10 FIELD2 PIC S99. 10 FILLER PIC XX. 10 . 20 FIELD3 PIC S9(4) BINARY. 20 FIELD4 PIC S9(4) BINARY.
see FILLER
Pseudo-Parameter above.
You can rename all IDL parameters in the COBOL Mapping Editor. See IDL Interface for interface type DFHCOMMAREA (In same as Out, In different to Out) | Large Buffer (In same as Out, In different to Out) | Channel Container | Batch | IMS BMP | Micro Focus | IMS Connect | COBOL Converter (In same as Out, In different to Out).
If your COBOL server interface expects for your purpose always a constant value, use Set COBOL Data Items to Constants for interface type DFHCOMMAREA (In same as Out, In different to Out) | Large Buffer (In same as Out, In different to Out) | Channel Container | Batch | IMS BMP | Micro Focus | IMS Connect | COBOL Converter (In same as Out, In different to Out).
If your COBOL server implements various functions or operations and the data items represent function or operation codes, map the COBOL interface to multiple IDL interfaces. For more information and COBOL examples see the Mapping Editor IDL Interface mapping function Map to Multiple IDL Interfaces for interface type DFHCOMMAREA (In same as Out, In different to Out) | Large Buffer (In same as Out, In different to Out) | Channel Container | Batch | IMS BMP | Micro Focus | IMS Connect | COBOL Converter (In same as Out, In different to Out).
If your COBOL server interface produces dissimilar shapes of optional output, COBOL group data items can be mapped to multiple possible output (MPO). Criteria can be added under which circumstances COBOL groups are part of the returned data or not. This is done with Mapping Editor IDL Interface mapping function Set Multiple Possible Output (MPO) Structures for interface type DFHCOMMAREA (In same as Out, In different to Out) | Large Buffer (In same as Out, In different to Out) | Channel Container | IMS Connect | COBOL Converter (In same as Out, In different to Out).
COBOL data items that are not needed in the IDL Interface but are required by the COBOL server can be suppressed. See Suppress Unneeded COBOL Data Items for interface type DFHCOMMAREA (In same as Out, In different to Out) | Large Buffer (In same as Out, In different to Out) | Channel Container | Batch | IMS BMP | Micro Focus | IMS Connect | COBOL Converter (In same as Out, In different to Out)
In the check box Map FILLER fields to IDL of the
COBOL to IDL in the extraction settings of the wizard (see Step 4: Define the Extraction Settings and Start Extraction) you can define whether COBOL
FILLER
pseudo-parameters should be part of the RPC client interface by default
or not. By default they are not mapped to IDL. In the
COBOL Mapping Editor you can change the
mapping for a FILLER
field individually, e.g. mapping required ones to IDL. If
FILLER
fields are mapped to IDL, they are made unique by appending a sequence
number. You can set the prefix to be used in the COBOL Preferences.
If the resulting names are not suitable, you can rename IDL field names in the Mapping Editor with the
function of the context menu. See the following example:01 GROUP1. 10 FIELD1 PIC XX. 10 FILLER PIC XX. 10 FIELD2 PIC S99. 10 FILLER PIC XX.
This will be mapped to Software AG IDL:
1 GROUP1 2 FIELD1 (A2) 2 FILLER_1 (A2) 2 FIELD2 (N2.0) 2 FILLER_2 (A2)
If a group is named FILLER
and the group has scalar fields, the group
is always mapped to IDL, independent of the check box Map FILLER
fields to IDL. For example:
01 GROUP1. 10 FIELD1 PIC XX. 10 PIC XX. 10 FIELD2 PIC S99. 10 FILLER PIC XX. 10 . 20 FIELD3 PIC S9(4) BINARY. 20 FIELD4 PIC S9(4) BINARY.
This will be mapped to Software AG IDL:
1 GROUP1 2 FIELD1 (A2) 2 FILLER_1 (A2) 2 FIELD2 (N2.0) 2 FILLER_2 (A2) 2 FILLER_3 3 FIELD3 (I2) 3 FIELD4 (I2)
A redefinition is a second parameter layout of the same memory
portion. In most modern programming languages, and also the Software AG IDL,
this is not directly supported.
The following possibilities are available to map COBOL REDEFINE
s:
You can select a single redefine path for IDL usage. In this case, the COBOL server requires predictable input and output structures. The redefine path can be determined at design time (extraction time). This is supported for all IDL directions that is, In, Out and InOut. For more information and COBOL examples, see Mapping Editor IDL Interface mapping function Select REDEFINE Paths for interface type DFHCOMMAREA (In same as Out, In different to Out) | Large Buffer (In same as Out, In different to Out) | Channel Container | Batch | IMS BMP | Micro Focus | IMS Connect | COBOL Converter (In same as Out, In different to Out).
If a REDEFINE
path is selected, the mapping is as follows:
COBOL Syntax | Software AG IDL Syntax |
---|---|
1 |
1 |
1 REDEFINES |
1 FILLER_ |
1 FILLER REDEFINES |
1 FILLER_ |
If the COBOL server supports more than one type of input (redefine paths) but uses predictable output structures, you can map the COBOL interface to multiple IDL interfaces. This is supported for IDL direction In only. In this case, the redefine path used is selected as described under 1 above. For more information and COBOL examples, see Mapping Editor IDL Interface mapping function Map to Multiple IDL Interfaces for interface type DFHCOMMAREA (In same as Out, In different to Out) | Large Buffer (In same as Out, In different to Out) | Channel Container | Batch | IMS BMP | Micro Focus | IMS Connect | COBOL Converter (In same as Out, In different to Out).
If the COBOL server produces more than one type of output (redefine paths) and implements the multiple possible output (MPO) concept, you can map the redefine to MPO. In this case the redefine path used is determined at runtime from a set of predefined redefine paths. The set of alternate redefine paths is determined during design time (extraction time). This is supported for IDL direction Out only. For more information and COBOL examples of the MPO concept, see Mapping Editor IDL Interface mapping function Set Multiple Possible Output (MPO) Structures for interface type DFHCOMMAREA (In same as Out, In different to Out) | Large Buffer (In same as Out, In different to Out) | Channel Container | IMS Connect.
If a REDEFINE
is mapped to multiple possible output (MPO), the mapping is as follows:
COBOL Syntax | Software AG IDL Syntax |
---|---|
1 name_1 2 name_1_1 . . . . . |
1 name_1 (/V1) 2 name_1_1 . . . . . |
1 name_2 REDEFINES name_1 2 name_2_1 . . . . . |
1 name_2 (/V1) 2 name_2_1. . . . . |
1 name_3 REDEFINES name_1 2 name_3_1 . . . . . |
1 name_3 (/V1) 2 name_3_1 . . . . . |
If the COBOL server supports more than one type of input (redefine paths) and implements the multiple possible output (MPO) concept as well, you can combine extraction as described under 2 and 3 above.
In all cases the, COBOL REDEFINE
requires a server mapping file to provide additional information. See Server Mapping Files for COBOL.
The following possibilities are available to map COBOL tables with fixed size:
By default, fixed-size COBOL tables are converted automatically to fixed-size IDL groups
(see group-parameter-definition
) with fixed-bound-array (see array-definition
).
This is the usual way and is suitable for most situations. See the following syntax:
COBOL Syntax | Software AG IDL Syntax |
---|---|
1 name OCCURS n [TIMES] 2 name_1 . . . . . |
1 name (/n) 2 name_1 . . . . . |
1 name OCCURS n [TIMES] [ ASCENDING | DESCENDING [KEY] [IS] key_name ] 2 name_1 . . . . . |
1 name (/n) 2 name_1 . . . . . |
1 name OCCURS n [TIMES] [ [ INDEXED [BY] index_name] 2 name_1 . . . . . |
1 name (/n) 2 name_1 . . . . . |
In very rare situations, the COBOL server uses a fixed-size COBOL table in a variable-size manner. In contrast - as the syntax implies - a variable number of elements is transferred in this fixed-size array (input only, output only or both directions are possible). Array elements at the end of the array are unused. The current number of elements can be calculated using different approaches by the receiver of such an array. This is possible for message-oriented interface types: DFHCOMMAREA, Large Buffer, Channel Container, IMS Connect. The fixed-sized COBOL table must be the last parameter in the interface. For more information and COBOL examples see the Mapping Editor IDL Interface mapping function Set Array Mapping (fixed <-> unbounded) for interface type DFHCOMMAREA (In same as Out, In different to Out) | Large Buffer (In same as Out, In different to Out) | Channel Container | IMS Connect | COBOL Converter (In same as Out, In different to Out).
The following rules apply:
The combination of phrases ASCENDING
and INDEXED BY
and phrases DESCENDING
and INDEXED BY
is meaningless for EntireX and therefore ignored by the IDL Extractor for COBOL.
If the mapping function Set Arrays (Fixed <-> Unbounded) is used, a server mapping file is required to provide additional information. See Server Mapping Files for COBOL.
The VALUE
clause specifies the initial contents of a data item or the
value(s) associated with a condition name. For condition names, see Condition Names - Level-88 Data Items above.
COBOL Syntax |
---|
1 |
Initial values can be specified on data items in the Working-Storage
Section. As an IBM extension, in the File and Linkage Sections, the VALUE
clause is treated as a comment.
The IDL Extractor for COBOL ignores initial values of data items. The
DATA DIVISION
is parsed as without the VALUE
clause.
If you require the value on input to the COBOL server you specify to be a constant, see Set COBOL Data Items to Constants for interface type DFHCOMMAREA (In same as Out, In different to Out) | Large Buffer (In same as Out, In different to Out) | Channel Container | Batch | IMS BMP | Micro Focus | IMS Connect | COBOL Converter (In same as Out, In different to Out).
This section describes the COBOL syntax relevant for extracting the
DATA DIVISION
. No user decisions in the COBOL Mapping Editor are required or possible here.
The BLANK WHEN ZERO
clause specifies that an item
contains nothing but spaces when its value is zero. The BLANK WHEN
ZERO
clause is not considered by the IDL Extractor for COBOL. The
DATA DIVISION
is parsed as without the BLANK WHEN
ZERO
clause. Because the BLANK WHEN ZERO
clause only has an
impact if the item is displayed, such a program can be mapped to IDL. The
workaround for RPC clients is to imitate the BLANK WHEN ZERO
clause.
Continuation lines, starting with a hyphen in the indicator area, are supported.
The DATE FORMAT
clause is an IBM-specific extension. The
DATE FORMAT
clause specifies that a data item is a windowed or
expanded date field.
The DATE FORMAT
clause is not considered by the
IDL Extractor for COBOL. The DATA DIVISION
is parsed as without
the DATE FORMAT
clause. The semantic given by the DATE
FORMAT
clause has to be considered by RPC clients.
The GLOBAL
clause
specifies that a data-name is available to every program contained within the program that declares it, as long as the contained program does not itself have a declaration for that name.
is not considered by the IDL Extractor for COBOL. The DATA
DIVISION
is parsed as without the GLOBAL
clause.
However, program parameters containing the GLOBAL
clause
can be mapped to IDL, which can make sense as long as the EXTERNAL
DATA
clause is used to pass parameters from the called COBOL server to
further subprograms called.
The EXTERNAL
clause
can only be specified on data description entries that are in the Working-Storage section of a program.
is not considered by the IDL Extractor for COBOL. The DATA
DIVISION
is parsed as without the EXTERNAL
clause.
Note:
EntireX RPC technology cannot pass data using
EXTERNAL
linkage from the RPC server to the COBOL server. However,
program parameters containing the EXTERNAL
clause can be mapped to
IDL, which can make sense as long as the EXTERNAL DATA
clause is
used to pass parameters from the called COBOL server to further subprograms
called.
The IDL Extractor for COBOL ignores the JUSTIFIED
clause.
The DATA DIVISION
is parsed as without the JUSTIFIED
clause. The workaround for RPC clients is to imitate the JUSTIFIED
clause.
The OBJECT REFERENCE
phrase is an IBM-specific extension.
A program containing an OBJECT REFERENCE
phrase cannot be mapped
to IDL.
The POINTER
phrase is an IBM-specific extension.
COBOL Syntax | Software AG IDL Syntax |
---|---|
1 |
none |
1 |
none |
The following rules apply:
All pointers are mapped to "suppressed" in the Mapping Editor because the Software AG IDL does not support pointers.
Offsets to following parameters are maintained by a server mapping file. See Server Mapping Files for COBOL. At runtime, the RPC server passes a null pointer to the COBOL server.
The PROCEDURE-POINTER
phrase is an IBM-specific
extension. A program containing a procedure-reference phrase cannot be mapped
to IDL.
Level-66 entries are ignored and cannot be used for mapping to IDL.
The DATA DIVISION
is parsed as without the level-66 entry.
The SIGN LEADING
and TRAILING SEPARATE
clauses are supported. Both require a server mapping file. See Server Mapping Files for COBOL.
The synchronized clause aligns COBOL data items at word boundaries. The clause does not have any relevance for RPC clients and is not written into the IDL file but into the server mapping file. See Server Mapping Files for COBOL. At runtime, the RPC server aligns the data items accordingly.
Variable size COBOL tables are converted to IDL unbounded groups (see group-parameter-definition
)
with an unbounded array (see array-definition
) and maximum upper bound set.
The lower-bound is always set to 1 in the IDL. See the following example:
01 COUNTER-1 PIC 99. 01 TABLE OCCURS 1 TO 10 DEPENDING ON COUNTER-1 02 FIELD1 PIC XX. 02 FIELD2 PIC 99.
The ODO subject (data item TABLE
) will be mapped in the IDL to an unbounded group (with maximum).
The ODO object (data item COUNTER-1
) is not part of the IDL because the number of elements is implicitly available with the IDL unbounded group.
See Map OCCURS DEPENDING ON
for interface type DFHCOMMAREA (In same as Out, In different to Out) | Large Buffer (In same as Out, In different to Out) | Channel Container | Batch | IMS BMP | Micro Focus | IMS Connect | COBOL Converter (In same as Out, In different to Out).
01 TABLES (/V10) 02 FIELD1 (A2) 02 FIELD2 (NU2.0)
COBOL Syntax | Software AG IDL Syntax |
---|---|
1 name OCCURS n TO m [TIMES] DEPENDING [ON] index 2 name_1 . . . . . |
1 name (/Vm) 2 name_1 . . . . . |
1 name OCCURS n TO m [TIMES] DEPENDING [ON] index [ ASCENDING | DESCENDING [KEY] [IS] key_name ] 2 name_1 . . . . . |
1 name (/Vm) 2 name_1 . . . . . |
1 name OCCURS n TO m [TIMES] DEPENDING [ON] index [ INDEXED [BY] index_name] 2 name_1 . . . . . |
1 name (/Vm) 2 name_1 . . . . . |
The following rules apply:
The COBOL from value, n
above, is semantically different
from the IDL lower bound and means a lower-bound of elements which must not be
crossed. It is the duty of the calling RPC client to take care of this and set
the corresponding number of elements correctly. Do not send less than the COBOL
lower bound.
The combination of the phrases ASCENDING
and INDEXED
BY
and phrases DESCENDING
and INDEXED BY
is meaningless for EntireX and therefore ignored by the IDL Extractor for COBOL.
The COBOL clause OCCURS DEPENDING ON
requires a server mapping file to provide additional information. See Server Mapping Files for COBOL.
COBOL level-77 data items are handled as COBOL data items on level 1. They are always mapped to IDL level 1.
A USAGE
clause can be specified on group level, which
defines the data type of subsequent groups or parameters. The
USAGE
clause on subsequent groups or parameters may not contradict
a higher level definition. Therefore IDL data types may depend on
USAGE
clauses of parent groups if the COBOL data structure is
defined as explained.
COBOL data items defined with USAGE IS INDEX
are parsed
as without USAGE IS INDEX
. The USAGE IS INDEX
clause
is ignored.
This section discusses the syntax relevant for extraction of the
PROCEDURE DIVISION
:
For Batch, IMS BMP and Micro Focus programs, the PROCEDURE DIVISION
header
is relevant for the COBOL InOut parameters. The parameters of the header are
suggested as default COBOL InOut parameters.
For CICS DFHCOMMAREA programs, the PROCEDURE DIVISION
header is of no
interest, because the DFHCOMMAREA
is the relevant information to get the COBOL
InOut parameters from. If the DFHCOMMAREA
is defined in the linkage section all
parameters of the DFHCOMMAREA
are suggested as default COBOL InOut parameters. If there is no DFHCOMMAREA
, no suggestion is made.
For CICS Large Buffer, Channel Container and IMS MPP (IMS Connect) programs, parameters are not suggested; you select the parameters in the Mapping Editor manually.
However, you can always add, change and correct the suggested parameters if they are not the correct ones in the extraction wizard. See Step 5: Select the COBOL Interface and Map to IDL Interface in Using the IDL Extractor for COBOL.
The BY VALUE
clause is an IBM-specific extension for
COBOL batch programs. It is ignored by the IDL Extractor for COBOL. Directions
are added in the Mapping Editor manually.
The RETURNING
phrase is an IBM-specific extension for
COBOL batch programs. It is ignored by the IDL Extractor for COBOL. Handling is
as without the phrase. No return value is transferred during execution time. If
the RETURNING
phrase is relevant for the interface, the COBOL
program cannot be mapped to IDL.
COPY statements are supported if nested copy statements do not recursively call the same source file.
If copybooks cannot be located, the following rules apply:
In the case of a remote extraction, the copybook location (data set) is unknown.
In the case of a local extraction, either the copybook location (directory) or the copybook extension is unknown.
In both cases, the extraction wizard will appear with a dialog to browse for the copybook location (local directory or remote data set) and allows you to append your copybook extensions. Both will be saved in the preferences.
You can also predefine the following in the preferences:
the copybook locations, see Define the remote copybook locations or Define the local copybook locations in COBOL Preferences.
the copybook extensions for local extractions, see Define the local copybook locations in COBOL Preferences.
COPY statements with the REPLACE
option are supported. Beneath the
REPLACE
option, those copybooks are worked off like all other copybooks above.
Example:
a copybook ACPYBK with REPLACE
option
01 WS-ZEUGNIS. :F: WS-AKTIONEN PIC 9(01). :L: :C:-NEU VALUE 'N'. :L: :C:-MOD VALUE 'M'. :L: :C:-INS VALUE 'I'. :L: :C:-WEG VALUE 'W'. :L: :C:-SIG VALUE 'S'. :F: WS-NOTEN PIC X(03). :L: SEHR-GUT VALUE 100. :L: GUT VALUE 95 THROUGH 99. :L: BEFRIEDIGEND VALUE 80 THROUGH 94. :L: AUSREICHEND VALUE 50 THROUGH 79. :L: MANGELHAFT VALUE 01 THROUGH 49. :L: UNGENUEGEND VALUE 0.
referencing the copybook above
COPY ACPYBK REPLACING ==:F:== BY ==10==, ==:L:== BY ==88==, ==:C:== BY ==CMD==, 95 BY 90, 94 BY 89, WS-NOTEN BY WS-PROZENT, ==X(03)== BY ==9(03)==, ==9(01)== BY ==X(01)==.