IBM Support

PI31403: PROBLEM MIGRATING PROGRAMS WITH INVALID ZONE BITS TO COBOL V5.x FROM COBOL V4.2.

A fix is available

Subscribe

You can track all active APARs for this component.

 

APAR status

  • Closed as program error.

Error description

  • Customer found that they had blanks inside of USAGE DISPLAY
    numeric data (zoned decimal data) so that comparing to ZERO was
    true (4 is not a valid zone code):
        77  VALUE0    PIC X(4) VALUE '00 0'.     <*  x'F0F040F0'
        77  VALUE1    REDEFINES VALUE0 PIC 9(4).           ^
        IF VALUE1 = ZERO
          DISPLAY ?COBOL V4 (or earlier) with NUMPROC(MIG) and V5
                 with OPT(0)'
        ELSE
          DISPLAY ?COBOL V4 with NUMPROC(NOPFD or PFD) and also
                  ? COBOL V5 with OPT(1) or OPT(2) in effect
        END-IF
    If users have such invalid zone codes in their zoned decimal
    data and do numeric compariosons with such data items, they
    could get different results with COBOL V5.x.
    Best approach for the users is to fix their invalid data. The
    more practical approach to accommodate migration to Enterprise
    COBOL V5.x is to use a new compiler option ZONEDATA.
    

Local fix

  • N/A
    

Problem summary

  • ****************************************************************
    * USERS AFFECTED: Users of Enterprise COBOL V5 migrating from  *
    *                 earlier COBOL compilers when there are       *
    *                 invalid zone bits in USAGE DISPLAY numeric   *
    *                 (zoned decimal) data items that are also     *
    *                 used in numeric comparisons                  *
    *                                                              *
    ****************************************************************
    * PROBLEM DESCRIPTION: Numeric comparisons get different       *
    *                      results in COBOL V5 with OPT(1 or 2).   *
    *                      If users recompile programs that have:  *
    *                       - USAGE DISPLAY numeric data items     *
    *                         that contain bad zone bits and have  *
    *                       - numeric comparisons using such data  *
    *                         items                                *
    *                                                              *
    ****************************************************************
    * RECOMMENDATION: Apply the provided PTF.                      *
    *                                                              *
    ****************************************************************
    The compiler was assuming that the zone bits were valid so
    that comparisons could be done with instructions that were
    optimized to string compares rather than instructions to convert
    to numeric and do numeric compares in relation conditions.
    

Problem conclusion

  • The compiler was changed to add a new compiler option to address
    this challenge.  This APAR adds the ZONEDATA(PFD|MIG) compiler
    option.  With ZONEDATA(MIG), COBOL V5 will behave like
    COBOL V4 for the above narrow case.  This will be true
    regardless of OPT setting.  Here are changes to the Programming
    Guide and Customization Guide for this new compiler option:
    +--------------------------------------------------------------+
    | Start of changes for:                                        |
    | Enterprise COBOL for z/OS Programming Guide, SC14-7382-01    |
      Chapter 17:  Compiler options
       Add the ZONEDATA compiler option between XREF and ZWB:
      ZONEDATA(PFD|MIG)
      This compiler option tells the compiler whether USAGE DISPLAY
      numeric data items(zoned decimal) will contain data with
      valid zone bits (PFD) or may contain data with invalid zone
      bits (MIG) for numeric comparisons.
                         +--PFD--+
                         |       |
        >>---ZONEDATA--(-+--MIG--+-)--->>
     Default: ZONEDATA(PFD)
     Abbreviations:  ZD
     Each digit of a valid zoned decimal number is represented by a
     single byte X'F0' through X'F9'. The 4 high-order bits of each
     byte are zone bits . The 4 low-order bits of each byte contain
     the value of the digit. The 4 high-order bits of the low-order
     byte (for SIGN TRAILING) represent the sign of the item.
     The sign is in the high-order byte with SIGN LEADING, or in a
     separate byte for SIGN IS SEPARATE.
     When ZONEDATA(MIG) is in effect, the compiler will generate
     instructions to do numeric compares that will ignore the zone
     bits of each digit in zoned decimal data items. For example,
     if the zoned decimal value is converted to packed-decimal
     with a PACK instruction prior to the compare.
     Note1: The sign zone must still be a valid sign according to
            the NUMPROC zompiler option setting.
     Note2: For unsigned and for sign is separate, the last zone
            must also have correct zone bits
     When ZONEDATA(PFD) is in effect, the compiler will assume that
     the zone bits in zoned decimal data items are valid, and
     generate the most efficient code possible to make the
     comparison.  For example, it might generate a string compare
     to avoid numeric conversion.
     Example:
    ***************************************************************
    *  In this example we use a data item with a bad zone code
    *  '4' in the zone bits in the middle of data item VALUE1,
    *  forced in via REDEFINES
    ***************************************************************
     77  VALUE0    PIC X(4) VALUE '00 0'.     <*  x'F0F040F0''
     77  VALUE1    REDEFINES VALUE0 PIC 9(4).           ¼
     PROCEDURE DIVISION..
    ***************************************************************
    *  In this example the test is true in COBOL V4 and earlier
    *  if the NUMPROC(MIG) option was used, and FALSE for other
    *  NUMPROC settings.
    *  In COBOL V5.1 before the ZONEDATA option was added, the
    *  test was true at OPT(0) and false at OPT(1|2).  With
    *  ZONEDATA(MIG) the test will be TRUE at any OPT setting.
    ***************************************************************
         IF VALUE1 = ZERO
            DISPLAY 'ZONEDATA(MIG) is in effect ' VALUE1
         ELSE
            DISPLAY 'ZONEDATA(PFD) is in effect '  VALUE1
         END-IF
     ZONEDATA(MIG) can help migration to COBOL V5 for customers
     who have:
      - USAGE DISPLAY numeric data items that contain bad zone
        bits at run time and
      - numeric comparisons using such data items and
      - been compiling with the NUMPROC(MIG) compiler option.
     In such cases, ZONEDATA(PFD) can give different results for
     comparisons using USAGE DISPLAY numeric data items than the
     previous compiler.  Customers can either correct their data
     or use ZONEDATA(MIG).
     ZONEDATA(MIG) will have worse runtime performance than
     ZONEDATA(PFD).
     ZONEDATA(MIG) will disable some of the optimizations that
     NUMPROC(PFD) could give.
    | End of changes for:                                          |
    | Enterprise COBOL for z/OS Programming Guide, SC14-7382-01    |
    +--------------------------------------------------------------+
    +--------------------------------------------------------------+
    | Start of changes for:                                        |
    | Enterprise COBOL for z/OS Customization Guide, SC14-7380-01  |
      Chapter 2:  Enterprise COBOL compiler options
       Add the ZONEDATA compiler option between XREF and ZWB.  Use
      the same descriptions as the Programming Guide except for
      different syntax:
                               +--PFD--+
                               |       |
        >>---ZONEDATA=--+---+--+--MIG--+---->>
                        |   |
                        +-*-+
       Default: ZONEDATA=PFD
       Abbreviations:  None
    | End of changes for:                                          |
    | Enterprise COBOL for z/OS Customization Guide, SC14-7380-01  |
    +--------------------------------------------------------------+
    

Temporary fix

Comments

APAR Information

  • APAR number

    PI31403

  • Reported component name

    ENT COBOL FOR Z

  • Reported component ID

    5655W3200

  • Reported release

    510

  • Status

    CLOSED PER

  • PE

    NoPE

  • HIPER

    NoHIPER

  • Special Attention

    YesSpecatt / New Function / Xsystem

  • Submitted date

    2014-12-11

  • Closed date

    2015-01-08

  • Last modified date

    2015-03-12

  • APAR is sysrouted FROM one or more of the following:

  • APAR is sysrouted TO one or more of the following:

Modules/Macros

  •    IGYCDOPT IGYCOPI  IGYCOPT  IGYKCNTL IGYKSTAT
    IGYWINIT
    

Publications Referenced
SC14738001SC14738201   

Fix information

  • Fixed component name

    ENT COBOL FOR Z

  • Fixed component ID

    5655W3200

Applicable component levels

  • R510 PSY UI24300

       UP15/01/15 P F501

Fix is available

  • Select the PTF appropriate for your component level. You will be required to sign in. Distribution on physical media is not available in all countries.

[{"Business Unit":{"code":"BU058","label":"IBM Infrastructure w\/TPS"},"Product":{"code":"SS6SG3","label":"Enterprise COBOL for z\/OS"},"Platform":[{"code":"PF025","label":"Platform Independent"}],"Line of Business":{"code":"LOB17","label":"Mainframe TPS"}}]

Document Information

Modified date:
01 May 2020