Created On:  04 March 2011

Problem:

An issue arose when a client was migrating an application from an older version of COBOL to Server Express. They wanted to know why the behaviour changed in Server Express for numeric fields that had not been initialized. Take the following program as an example, where no initialization is applied:

WORKING-STORAGE SECTION.

*SET HOSTNUMCOMPARE
 01 num-fld pic 9(01).
 Procedure Division.
 If num-fld = 0
    Then
         Display "THEN num-fld-->["num-fld"]"
    Else
         Display "ELSE num-fld-->["num-fld"]"
End-if.

When they compiled the program to object code (i.e. .gnt, .so or executable) in Server Express, with the default compiler directives, the 'THEN' logical path was taken. This meant that the non-initialized numeric field was treated as equal to zero.

But when they recompiled with the HOSTNUMCOMPARE compiler directive set (i.e. replace the asterisk with $) the 'ELSE' path was taken.

In their older versions of COBOL (where HOSTNUMCOMPARE was not an option) the 'ELSE' path was also taken.

When interrogated via the animator the value of the field was hex(20) – spaces - in both instances, as expected.

Their conclusion was that HOSTNUMCOMPARE causes the rts to behave the same as it did in their older version of COBOL, which emulated mainframe COBOL. But they were concerned of the consequences and if that would impact behaviour elsewhere.

The other question that arose was why in Server Express the 'IF THEN' condition was passed if HOSTNUMCOMPARE was not set – when the value of num-fld was hex(20)?

This seemed to be behaving as if SPZERO was set.

Resolution:

The underlying issue is that their numeric variable contained invalid data - i.e. a space character in a numeric display field. The behaviour of this is undefined. It was undefined in OCDS, it is undefined in Server Express, and it is undefined in Visual COBOL. Expecting and relying on a particular behaviour is a bad idea.

Micro Focus makes no apology for emphasizing this point - do not use uninitialized/invalid data in numeric items.

The best fix is either to initialize the value, or to use "if numeric" tests.

HOSTNUMCOMPARE is a directive to aid migrating from the mainframe to Micro Focus. It emulates certain mainframe behaviour, but this comes at a performance cost. It will not guarantee that undefined cases behave the same in Server Express as they did in OCDS - after all they are undefined.

Note: when we tested running .int code compiled without HOSTNUMCOMPARE set, it took the 'ELSE' path, meaning it deems num-fld is not = 0. Of course to do this COBSW=-F has to be set to switch off reporting of error code 163. Setting COBSW=-F adds another component the rts has to deal with, and it’s these various combinations of directives and switches that makes it difficult to predict the behaviour and why we can’t give definitive answers on all settings.