IBM Support

PI57812: SUPPORT DYNAMIC STORAGE IN COBOL (PIC X(1) LINKAGE SECTION ITEMS WITH REFERENCE MODIFICATION AND TABLE ODO OVERLAYS)

A fix is available

Subscribe

You can track all active APARs for this component.

 

APAR status

  • Closed as program error.

Error description

  • 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.
    

Local fix

Problem summary

  • ****************************************************************
    * USERS AFFECTED: Users of Enterprise COBOL 5.1 compiling and  *
    *                 running programs that are compiled with the  *
    *                 OPT(1) or OPT(2) compiler options and are    *
    *                 using a variable length reference            *
    *                 modification to deliberately move data into  *
    *                 a linkage section data item beyond its       *
    *                 defined length.                              *
    *                                                              *
    *                                                              *
    ****************************************************************
    * PROBLEM DESCRIPTION: Incorrect output. The number of bytes   *
    *                      that are moved into the receiver is     *
    *                      capped at the defined length of the     *
    *                      receiver data item, which may be        *
    *                      shorter than the runtime length of the  *
    *                      reference modification in the move      *
    *                      operation. This behavior differs from   *
    *                      pre-V5 releases of the Enterprise       *
    *                      COBOLcompiler, which did not attempt    *
    *                      to cap the length of such move          *
    *                      operations.                             *
    *                                                              *
    ****************************************************************
    * RECOMMENDATION: Apply the provided PTF.                      *
    *                                                              *
    ****************************************************************
    Consider two COBOL programs, PROGA and PROGB:
    
    PROGA:
    
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 DATA1 PIC X(100).
    PROCEDURE DIVISION.
    CALL PROGB USING BY REFERENCE DATA1
    
    PROGB:
    
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 LEN PIC 9(5) BINARY.
    LINKAGE SECTION.
    01 DATA1 PIC X(1).
    01 DATA2 PIC X(500).
    PROCEDURE DIVISION USING BY REFERENCE DATA1.
    :
    MOVE 100 to LEN
    MOVE DATA2(1:LEN) TO DATA1(1:LEN)                      col 64->|
    
    When optimizing PROGB, the compiler was capping the length of
    the move in statement 'MOVE DATA2(1:LEN) TO DATA1(1:LEN)' to 1
    byte, which technically is the maximum length of the move based
    on the definition of DATA1 in PROGB, but this behavior is
    different from pre-V5 releases of the compiler which allowed
    users to simulate unbounded parameters using this pattern.
    

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.
    

Temporary fix

Comments

APAR Information

  • APAR number

    PI57812

  • Reported component name

    ENT COBOL FOR Z

  • Reported component ID

    5655W3200

  • Reported release

    510

  • Status

    CLOSED PER

  • PE

    NoPE

  • HIPER

    NoHIPER

  • Special Attention

    NoSpecatt / Xsystem

  • Submitted date

    2016-02-22

  • Closed date

    2016-04-27

  • Last modified date

    2016-05-30

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

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

    PI59330 PI59354 PI63286

Modules/Macros

  •    IGYECNTL
    

Fix information

  • Fixed component name

    ENT COBOL FOR Z

  • Fixed component ID

    5655W3200

Applicable component levels

  • R510 PSY UI37372

       UP16/04/29 P F604

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"},"Component":"","ARM Category":[],"Platform":[{"code":"PF025","label":"Platform Independent"}],"Version":"5.1","Edition":"","Line of Business":{"code":"LOB17","label":"Mainframe TPS"}},{"Business Unit":{"code":"BU054","label":"Systems w\/TPS"},"Product":{"code":"SG19M","label":"APARs - z\/OS environment"},"Component":"","ARM Category":[],"Platform":[{"code":"PF025","label":"Platform Independent"}],"Version":"5.1","Edition":"","Line of Business":{"code":"","label":""}}]

Document Information

Modified date:
30 May 2016