IBM Support

PH23770: (IBM DEVELOPER FOR Z) IDZ COBOL SCAN FAILS TO RESPOND UNDER CERTAIN CIRCUMSTANCES

Subscribe to this APAR

By subscribing, you receive periodic emails alerting you to the status of the APAR, along with a link to the fix after it becomes available. You can track this item individually or track all items by product.

Notify me when this APAR changes.

Notify me when an APAR for this component changes.

 

APAR status

  • Closed as program error.

Error description

  • "Scan for Compatibility" in IDz -- right click a module in
    remote systems view and then click the menu option to scan for
    compatibility; we get no response in a few different scenarios:
    
    A) nested calls (pgm0 calls pgm1 which then calls pgm2) give no
    results (no error, no msg, no abend) if only pgm0 is selected
    for scan (and the "Search libraries" box is set correctly).
    
    B) a program whose member-name is not the same as the program-id
    also causes "no response" (see pgm4 below).
    
    C) a program with an ENTRY statement causes "no response" (see
    pgm5 below).  Note that the USING keyword is on the ENTRY
    statement rather than the PROCEDURE DIVISION.  The customer has
    thousands of programs coded that way.
    
    D) non-existent pgm6 is treated as okay, without any warning
    message.
    
    In all cases it should either respond that no issues were found,
    or provide the Remote Error List with issues that were found.
    
    Here are six sample programs for recreating the issues.  The
    symptoms vary depending on which modules are selected for
    scanning, e.g. selecting PGM0 alone will give no response, but
    selecting (PGM0, PGM1, PGM2) gives the expected results, i.e.
    msg CRRZI0791E.
    
    pgm0.cbl -
    
           ID DIVISION.
           PROGRAM-ID. PGM0.
           DATA DIVISION.
           WORKING-STORAGE SECTION.
           01 PARM-OUT  PIC X(14).
           PROCEDURE DIVISION.
          * OMITTED causes NPE in the scanner (before v14.1.7)
          * CRRZI0791E Missing element for PGM1: 'OMITTED' (after
    v14.1.6)
               CALL 'pgm1' USING OMITTED.
          *
          * pgm0 --> pgm1 --> pgm2 but the scanner gives
          * no response, no msg unless pgm0 also calls pgm2
          *    CALL 'pgm2' USING PARM-OUT.
               EXIT PROGRAM.
    
    pgm1.cbl -
    
           ID DIVISION.
           PROGRAM-ID. PGM1.
           DATA DIVISION.
           WORKING-STORAGE SECTION.
           01 PARM-OUT  PIC X(4).
           LINKAGE SECTION.
           01 PARM-IN   PIC X(8).
           PROCEDURE DIVISION USING PARM-IN.
          * CRRZI0791E PGM1 is incompatible with PGM2;
          * Parameter 1 has a size of 4 but PGM2 is expecting a size
    of 8
               CALL 'pgm2' USING PARM-OUT.
               EXIT PROGRAM.
    
    pgm2.cbl -
    
           ID DIVISION.
           PROGRAM-ID. PGM2.
           DATA DIVISION.
           WORKING-STORAGE SECTION.
           LINKAGE SECTION.
           01 PARM-IN  PIC X(8).
           PROCEDURE DIVISION USING PARM-IN.
               DISPLAY 'hello'.
               EXIT PROGRAM.
    
    pgm3.cbl -
    
           ID DIVISION.
           PROGRAM-ID. PGM3.
           DATA DIVISION.
           WORKING-STORAGE SECTION.
           01 PARM-OUT  PIC X(4).
           LINKAGE SECTION.
           01 PARM-IN   PIC X(8).
           PROCEDURE DIVISION USING PARM-IN.
          * CRRZI0791E PGM3 is incompatible with PGM2;
          * Parameter 1 has a size of 4 but PGM2 is expecting a size
    of 8
               CALL 'pgm2' USING PARM-OUT.
    
          * pgm4 - program-id (pgmd) is not equal to member-name
    (pgm4)
          * but the scanner gives no message, no response, no abend
               CALL 'pgm4' USING PARM-OUT.
    
          * CRRZI0789E PGM3 is using 1 parameter but PGM5 expects 0
    parms
               CALL 'pgm5' USING PARM-OUT.
    
          * pgm6 does not exist (but no incompatibilities found!)
               CALL 'pgm6' USING PARM-OUT.
               EXIT PROGRAM.
    
    pgm4.cbl -
    
           ID DIVISION.
          * program-id is not equal to member-name
          * the scanner gives no message, no response, no abend
           PROGRAM-ID. PGMD.
           DATA DIVISION.
           WORKING-STORAGE SECTION.
           LINKAGE SECTION.
           01 PARM-IN  PIC X(8).
           PROCEDURE DIVISION USING PARM-IN.
               DISPLAY 'hello'.
               EXIT PROGRAM.
    
    pgm5.cbl -
    
    (Note that the member name, program-id, and entry-name are all
    equal to PGM5 ... the only "problem" is the USING clause on the
    ENTRY statement rather than the PROCEDURE DIVISION.  This is not
    a problem for the COBOL compiler, but it is a problem for the
    IDz Scanner.)
    
           ID DIVISION.
           PROGRAM-ID. PGM5.
           DATA DIVISION.
           WORKING-STORAGE SECTION.
           LINKAGE SECTION.
           01 PARM-IN  PIC X(8).
           PROCEDURE DIVISION.
               ENTRY 'pgm5' USING PARM-IN.
          *  expect CRRZI0789E (using 1 parm, but pgm5 expects 0
    parms)
               DISPLAY 'hello world'.
               EXIT PROGRAM.
    
    pgm6.cbl - does not exist (deliberately)
    

Local fix

Problem summary

  • In certain cases, such as when the called program could not be
    found, the Scan for Compatibility action failed to provide a
    response.
    

Problem conclusion

  • A correction has been made so that when a program cannot be
    found a new message with the id CRRZI0792W will be added to the
    Remote Error List.
    

Temporary fix

Comments

APAR Information

  • APAR number

    PH23770

  • Reported component name

    DEV FOR Z/OS

  • Reported component ID

    5724T0700

  • Reported release

    E20

  • Status

    CLOSED PER

  • PE

    NoPE

  • HIPER

    NoHIPER

  • Special Attention

    NoSpecatt / Xsystem

  • Submitted date

    2020-03-26

  • Closed date

    2020-06-15

  • Last modified date

    2020-06-15

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

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

Fix information

  • Fixed component name

    DEV FOR Z/OS

  • Fixed component ID

    5724T0700

Applicable component levels

[{"Business Unit":{"code":"BU058","label":"IBM Infrastructure w\/TPS"},"Product":{"code":"SSJK49","label":"IBM Developer for z Systems"},"Platform":[{"code":"PF025","label":"Platform Independent"}],"Version":"E20","Line of Business":{"code":"LOB35","label":"Mainframe SW"}}]

Document Information

Modified date:
27 October 2020