2 COBOL Interface for Micro Focus Visual COBOL

Availability

IDM for Microsoft Windows from IDM version A.06.01.d.

2.1 Unicode Support

The COBOL Interface for Micro Focus Visual COBOL supports Unicode as character encoding. A Unicode string is represented by Micro Focus Visual COBOL as National Character, where the encoding complies with the IDM code page CP-utf16. Within Micro Focus Visual COBOL this is represented as PIC N NATIONAL.

2.1.1 Activating Unicode

The use of Unicode is activated by setting the application code page. This can be accomplished through a command line option or within the application using the DMcob_Control function:

...
WORKING-STORAGE SECTION.

01  ACTION  PIC 9(4) BINARY VALUE 0.
...

PROCEDURE DIVISION
...
    MOVE DMF-SetCodePage TO ACTION.
    MOVE CP-utf16 TO DM-options.
    CALL "DMcob_Control" USING DM-STDARGS NULL-OBJECT ACTION.
...

Notes

2.1.2 Enhancement of CopyFiles

The copy files are defined in a way that texts can be stored either as Character or as National Character. The name of the Character entry remains. To access the National Character entry, a ‑u has to be appended to the name.

Character National Character (UTF-16)
DM-setsep          pic X.
DM-setsep-u          pic N national.
DM-getsep          pic X.
DM-getsep-u          pic N national.
DM-usercodepage    pic X(32).
DM-usercodepage-u    pic N(32) national.
DM-value-string    pic X(80).
DM-value-string-u    pic N(80) national.
DM-va-value-string pic X(80).
DM-va-value-string-u pic N(80) national.

For the following structure elements of the ValueRecord, the length or size is defined as the number of characters, not of bytes:

The same applies to all other structures based on the ValueRecord.

Note

The IDM reads or writes the respective values based on the currently valid application code page.

2.1.3 Call Parameters of COBOL Functions

For all texts either Character or National Character can be used. The IDM interprets the text according to the currently valid application code page. The length specification refers to the number of characters, not of bytes. This applies both to the IDM interface functions as well as to the COBOL functions called by the IDM. It is important that the currently used application code page complies with the text definition.

2.1.4 Functions with Records as Parameters

For functions with record objects as parameters, the pidm application creates a copy file by means of the command line option +writetrampolin. In order not to interfere with existing applications, these copy files are created without support for National Character by default. Support for it has to be explicitly specified by using the -mfviscob-u option instead of the COBOL compiler option -mfviscob:

pidm mydlg.dlg –mfviscob-u +writetrampolin myappl_tr

The generated copy file may then contain either character or national character. Again, the IDM will access based on the current application code page.

2.2 Data Type DT-anyvalue

The data type DT-anyvalue is supported through the POINTER data type of Micro Focus Visual COBOL.

See also

Chapter “Using the anyvalue Data Type”

2.3 Support of Collections

The colection data types of the IDM and the related functions for (managed) IDM values (Managed DM-Values) are supported through the pointer data type (POINTER) of Micro Focus Visual COBOL.

DM Data Type

Visual COBOL Data Type

hash

POINTER

list

POINTER

matrix

POINTER

refvec

POINTER

vector

POINTER

A Managed DM-Value is passed as pointer to Micro Focus Visual COBOL:

01 ManagedValue pointer.
ENTRY "GetAnyValue" using DM-COMMON-DATA ManagedValue.

To use such a value within the DM-Value structure, the value is copied to DM-value-pointer and DM-datatype is set to DT-anyvalue.

MOVE DT-anyvalue TO DM-datatype.
MOVE ManagedValue To DM-value-pointer.

2.3.1 Data Function in COBOL

With the support of the collection data types, it is also possible to implement data functions in COBOL.

See also

Chapter “Data Functions”

Chapter “Data Function Structure DM-Datafunc-Data”

Function DMcob_DataChanged

2.3.2 Structure DM-ValueIndex

This structure allows for a full-fledged index argument. It is used by the DMcob_Value* functions of the COBOL Interface for Micro Focus Visual COBOL to process the collection data types. However, the structure is available for all supported COBOL variants and is not restricted to these application areas. It is identical to the DM-Value structure.

2.3.3 Functions for Working with Collections