Firstly, evidence of IBM's plans to make V5 (and onwards) more compatible with 
how V4 works.

http://www-01.ibm.com/support/docview.wss?uid=swg1PI59330

"In earlier versions of COBOL, customer source frequently
handled dynamically sized pieces of storage by using a PIC X(1)
linkage section data-item and then reading or writing beyond
the bounds of that array.  This APAR will add this type of
support to COBOL V5 to make the behavior consistent with COBOL
V4.

LINKAGE Example:

WORKING-STORAGE SECTION.
01  wrk-len                 PIC s9(08) binary.
LINKAGE SECTION.
01  L-String1               PIC X(1).
01  L-String2               PIC X(1).
PROCEDURE DIVISION.
0000-MAIN.
    MOVE 1000 TO wrk-len
    MOVE L-String1(1:wrk-len) TO L-String2(1:wrk-len)

Behavior difference:  COBOL V4 moves 1000 bytes.  COBOL V5
moves 232 bytes due to differing instructions.

TABLE ODO Example:
WORKING-STORAGE SECTION.
01  CONTROLVAR PIC 9(5) BINARY.
01  MYCONTAINER.
    02  MYTABLE.
        03 TBL OCCURS 0 TO 1 TIMES DEPENDING ON CONTROLVAR.
           05 MYFIELD PIC X(1).
    02 DUMMY PIC X(300).
PROCEDURE DIVISION.
    MOVE 1 TO CONTROLVAR
    MOVE ALL 'Z' TO DUMMY
    DISPLAY DUMMY          <= Contains all Z's
    MOVE 300 TO CONTROLVAR
    MOVE ALL 'M' TO MYTABLE <= MYTABLE has 1 byte of M's in V4
    DISPLAY MYTABLE
    MOVE 1 TO CONTROLVAR
    DISPLAY DUMMY   <= DUMMY HAS 299 BYTES OF M's in V4.

Behavior difference:  COBOL V4 overlays storage following
MYTABLE exactly as expected byte for byte.  COBOL V5 handles
the overlay differently such that the storage results differ
from COBOL V4."

And:

"Problem conclusion

    The compiler was updated to ensure that in the above move
    scenario the runtime length of the move, as implied by the
    variable length reference modification, is always used
    regardless of the defined length of the receiving data item in
    the linkage section."

Note, it won't work if compiled with SSRANGE.

No "Local Fix" was outlined. The idea is that you no longer have to fix the 
code :-)

Where such techniques are used, it will make migration easier.

Secondly, some movement on the NUMPROC(MIG) issue which has previously been 
discussed here.

http://www-01.ibm.com/support/docview.wss?uid=swg1PI56073

"    ****************************************************************
    * USERS AFFECTED: Users of Enterprise COBOL V5.2 migrating     *
    *                 from a pre-V5 compiler, compiling and        *
    *                 running programs that were using the         *
    *                 NUMPROC(MIG) compiler option in pre-V5.      *
    *                                                              *
    ****************************************************************
    * PROBLEM DESCRIPTION: Performance: Programs compiled with     *
    *                      NUMPROC(NOPFD) using Enterprise COBOL   *
    *                      V5 is slower than programs compiled     *
    *                      with NUMPROC(MIG) using a pre           *
    *                      Enterprise COBOL V5 compiler.           *
    *                                                              *
    ****************************************************************
    * RECOMMENDATION: Apply the provided PTF.                      *
    ****************************************************************
    NUMPROC(MIG) does not require sign codes to be cleaned before
    comparing two zoned decimal data items. NUMPROC(NOPFD) requires
    sign codes to be cleaned.

Problem conclusion

    A more efficient code sequence for cleaning sign codes during
    comparisons was developed."

So, NUMPROC(MIG) has not returned (and is less likely to), but NUMPROC(NOPFD) 
has been made faster.

This is an amusing one:

http://www-01.ibm.com/support/docview.wss?uid=swg1PI59344

ADD 0 TO a-zoned-decimal-field was "optimized out" under the new 
ZONEDATA(NOPFD)/ZONEDATA(MIG). Since this was sefl-defeating (the ADD 0 would 
cause zones, and signs, to be fixed), the ADD 0 will remain.

It is still optimized-out for ZONEDATA(PFD) because "the zone bits are assumed 
to be correct with ZONEDATA(PFD)".

I'm not so sure that last is a good idea, because the ADD 0 also affects the 
sign.  Research needed.

----------------------------------------------------------------------
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

Reply via email to