Space announcement This documentation space provides the same content as before, but the organization of the content has changed. The content is now organized based on logical branches instead of legacy book titles. We hope that the new structure will help you quickly find the content that you need.

Review the Analysis of Error section to identify the error.


First review the Analysis of Error section on the Diagnostic Summary (DIAG) screen for the analysis of the problem. Find the name of the program in error.

Analysis of Error Section

 A data exception occurred during execution of program TESTPGM.  The    
 expected completion code is S0C7.                                      
                                                                       
   *******************************************                             
   *            Analysis of Error            *                             
   *******************************************                             
                                                                           
                                                                           
    A Data Exception was caused by data referenced at displacement 0000C1   
   from the start of W31 cell 00 (X'0000').  The field contains            
    X'025F5B'.  Refer to the data division map in the program listing to    
    locate the field name.                                                  
                                                                           
    A Data Exception is caused when a computational-3 field has             
    an invalid digit (not 0-9), or its last byte contains an invalid        
    sign (not A, B, C, D, E, or F).

Task 1: Find the name of the program in error

The Error Location section on the DIAG screen identifies the program name and the displacement of the next sequential instruction to be executed.

The Error Location section also provides the following information:

  • Program’s compile date and length
  • Program’s link date and load module length

The name of the load module or program object and the name of the library it was loaded from.

Error Location Section

*******************************************                                  
*             Error Location              *                                  
*******************************************                                  
                                                                                
The next sequential instruction to be executed in program TESTPGM was at     
displacement 0000030C.                                                       
                                                                                
The program was compiled on 02 MAY 2022 and is 00000C38 bytes long.          
                                                                                
It is part of PDSE object module TESTPGM.                                    
                                                                                
The module was loaded from STEPLIB library                                   
SYS22122.T052454.RA000.PINAX130.LOAD.H01.                                    
                                                                                
The module was bound at 05:24:54 on 02 MAY 2022 and is 000019C0 bytes        
long.                                                                        
                                                                                
The last known I/O request or call in the program above was issued with      
a return address at displacement 00000162.

Task 2: Use the Program Summary to locate the abending program

In the Supporting information section, select the Program Summary or enter the PROG command from any screen.

Program Summary screen

COMMAND ===>                                                                             
                                                                                        
To display the current Data Locator search criteria, select FINDDATA                     
                                                                                        
 D Program Detail         L Program Listing         S Program Storage                   
 C Compiler Options       R Data Locator            X Extended Search                   
 I Impact Analysis        W COBOL PERFORM Flow                                          
                                                                                        
                                  Load                               Compile            
 Program / Procedure Name         Module    Length  Language         Date       Time    
 *******************************  ********  ******  ***************  *********  ********
_ CWAACOB1                         CWAACOB1  0032E0  COBOL for z/OS   29SEP2020  15:15:02
_ CWAAHOUR                         CWAAHOUR  000C80  COBOL for z/OS   29SEP2020  15:15:05
_ CWAADATE                         CWAAHOUR  000AE8  COBOL for z/OS   29SEP2020  15:15:04
 *********************************************************** BOTTOM OF DATA ********

Find the abending program on the Program Summary screen and enter C in front of the name of the abending program to see the Compile Options screen. will be displayed. The header for the Compile Options screen contains the version of the Cobol compiler.

Compile options screen header

COMMAND ===>                                                                
                                                                           
Compile Options for CSECT.. CWAAHOUR                                       
                                                                           
Compile date............... 29SEP2020    Language COBOL for z/OS     V6R1M0
Compile time............... 15:15:05     LVLINFO  P190404                  

In this example, we see that it is Cobol for z/.OS V6R1M0.

Task 3: Obtain a copy of the correct compiler listing

Make sure that the date of your compiler listing exactly matches the date and time provided by Abend-AID. The date and time of the compile is shown on the first line of every page of the listing. An example for Cobol 6.3.0 is shown below.

Compiler Listing – Date

1PP 5655-EC6 IBM Enterprise COBOL for z/OS  6.3.0 P201119       TESTPGM   Date 05/02/2022  Time 05:24:54   Page     4       
 LineID  PL SL  ----+-*A-1-B--+----2----+----3----+----4----+----5----+----6----+----7-|--+----8 Map and Cross Reference  

 000001                IDENTIFICATION DIVISION

Task 4: Find the source code of the statement in error

Review the Assembler listing section of the compiler listing. The assembler listing includes the Cobol line number, the Cobol source statement, and the generated assembler code for that instruction. The first column of each generated assembler statement is the displacement of the instruction.

Find the instruction at the displacement shown in the Error Location section. The previous assembler statement is the cause of the error. For information about the assembler instructions, see the IBM z/Architecture Principles of Operation.

Assembler listing

0002D2  96F0 90D1          000092            OI      209(,R9),X'F0'        #                                     
 000093:                 COMPUTE H-OT-AMOUNT = H-OT-HOURS * (H-EMP-RATE * 1.5)                                       
    0002D6  F852 D192 90C1     000093            ZAP     402(6,R13),193(3,R9)  #                          H-EMP-RATE
    0002DC  960F D197          000093            OI      407(,R13),X'0F'       #                                     
    0002E0  FC41 D193 31B8     000093            MP      403(5,R13),440(2,R3)  #                           +440      
    0002E6  E901 D198 90D0     000093            PKA     408(R13),208(2,R9)    #                          H-OT-HOURS
    0002EC  FC51 D192 D1A6     000093            MP      402(6,R13),422(2,R13) #                                     
    0002F2  920F D197          000093            MVI     407(,R13),X'0F'       #                                     
    0002F6  F133 D194 D193     000093            MVO     404(4,R13),403(4,R13) #                                     
    0002FC  D203 90D8 D194     000093            MVC     216(4,R9),404(R13)    #                                     
    000302  A7F4 0012          000093            J       L0014                                                       
    000306                     000095  L0013:    EQU     *                                                           
000095:                 COMPUTE H-EMP-WAGES = H-EMP-HOURS * H-EMP-RATE.                                             
    000306  F842 D1A3 90C1     000095            ZAP     419(5,R13),193(3,R9)  #                          H-EMP-RATE
    00030C  960F D1A7          000095            OI      423(,R13),X'0F'       #                                     
    000310  E901 D188 90C8     000095            PKA     392(R13),200(2,R9)    #                          H-EMP-HOURS
    000316  FC41 D1A3 D196     000095            MP      419(5,R13),406(2,R13) #                                     
    00031C  960F D1A7          000095            OI      423(,R13),X'0F'       #                                     
    000320  D203 90B0 D1A4     000095            MVC     176(4,R9),420(R13)    #                                     
    000326                     000096  L0014:    EQU     *                                                           

The displacement given in the Error Location section above is 30C. Match that displacement to the Assembler listing. In this example, the error is in statement 95. Look at the compile listing and find the statement number to see the logic flow around the abending instruction.

Compiler Listing – Statement in Error

000089                1000-PROCESS-HOURLY.                                                                        
  000090                    IF H-EMP-HOURS GREATER THAN 40                                        34                
  000091      1                 COMPUTE H-EMP-WAGES = H-EMP-RATE * 40                             21 33             
  000092      1                 COMPUTE H-OT-HOURS  = H-EMP-HOURS - 40                            35 34             
  000093      1                 COMPUTE H-OT-AMOUNT = H-OT-HOURS * (H-EMP-RATE * 1.5)             36 35 33          
  000094                    ELSE                                                                                    
  000095      1                 COMPUTE H-EMP-WAGES = H-EMP-HOURS * H-EMP-RATE.                   21 34 33          
  000096                    COMPUTE H-EMP-COMPENSATION = H-EMP-WAGES + H-OT-AMOUNT.               37 21 36             

Task 5: Determine the field in error

The abending statement is COMPUTE H-EMP-WAGES = H-EMP-HOURS * W-EMP-RATE.  So the invalid field is either H-EMP-HOURS or H-EMP-RATE. Use the Data Division Map to determine where the variables are located.

Cobol version 5.1 and above

Data Division Map for Cobol version 5.1 and higher

Data Division Map                                                                                                               

Data Definition Attribute codes (rightmost column) have the following meanings:                                                 
   D = Object of OCCURS DEPENDING    G = GLOBAL                             S = Spanned file                                   
   E = EXTERNAL                      O = Has OCCURS clause                  U = Undefined format file                          
   F = Fixed-length file             OG= Group has own length definition    V = Variable-length file                           
   FB= Fixed-length blocked file     R = REDEFINES                          VB= Variable-length blocked file                   
   X = Unallocated                                                                                                             

Source   Hierarchy and                                    Base      Displacement  Asmblr Data                      Data Def     
LineID   Data Name                                        Locator     Structure   Definition        Data Type      Attributes   
    2  PROGRAM-ID TESTPGM-----------------------------------------------------------------------------------------------------*
   11   1  HOURLY-RECORDS-PROCESSED. . . . . . . . . . .             000000000   DS 2C             Disp-Num                    
   12   1  RATE-DETERMINATION-FIELDS . . . . . . . . . .             000000000   DS 0CL6           Group                       
   13     2  HOURLY-EMP-RATE . . . . . . . . . . . . . .             000000000   DS 3C             Disp-Num                    
   14     2  HOURLY-OVERTIME-RATE. . . . . . . . . . . .             000000003   DS 2C             Display                     
   15     2  HOURLY-EVALUATOR. . . . . . . . . . . . . .             000000005   DS 1C             Display                     
   16   1  WS-HOURLY-SWITCHES. . . . . . . . . . . . . .             000000000   DS 0CL3           Group                       
   17     2  WS-SENIOR-RATE-IND-SW . . . . . . . . . . .             000000000   DS 1C             Display                     
   18     2  WS-OVERTIME-INDICATOR-SW. . . . . . . . . .             000000001   DS 1C             Display                     
   19     2  WS-HOURLY-RAISE-REVIEW-SW . . . . . . . . .             000000002   DS 1C             Display                     
   21   1  H-EMP-WAGES . . . . . . . . . . . . . . . . .             000000000   DS 4P             Packed-Dec                  
   22   1  H-EMP-RATE-INFO . . . . . . . . . . . . . . .             000000000   DS 0CL14          Group                       
   23     2  FILLER. . . . . . . . . . . . . . . . . . .             000000000   DS 2C             Display                 
   24     2  FILLER. . . . . . . . . . . . . . . . . . .             000000002   DS 3C             Display                 
   25     2  FILLER. . . . . . . . . . . . . . . . . . .             000000005   DS 4C             Display                 
   26     2  HOURLY-RATE . . . . . . . . . . . . . . . .             000000009   DS 2P             Packed-Dec              
   27     2  HOURLY-INDICATOR. . . . . . . . . . . . . .             00000000B   DS 1C             Display                 
   28     2  HOURLY-OT-RATE. . . . . . . . . . . . . . .             00000000C   DS 2C             Display                 
   29   1  FILLER. . . . . . . . . . . . . . . . . . . .             000000000   DS 0CL12          Group          R        
   30     2  FILLER. . . . . . . . . . . . . . . . . . .             000000000   DS 2C             Display                 
   31     2  FILLER. . . . . . . . . . . . . . . . . . .             000000002   DS 0CL10          Group                   
   32       3  FILLER. . . . . . . . . . . . . . . . . .             000000002   DS 7C             Display                 
   33       3  H-EMP-RATE. . . . . . . . . . . . . . . .             000000009   DS 3P             Packed-Dec              
   34   1  H-EMP-HOURS . . . . . . . . . . . . . . . . .             000000000   DS 2C             Disp-Num                
   35   1  H-OT-HOURS. . . . . . . . . . . . . . . . . .             000000000   DS 2C             Disp-Num                
   36   1  H-OT-AMOUNT . . . . . . . . . . . . . . . . .             000000000   DS 4P             Packed-Dec              
   37   1  H-EMP-COMPENSATION. . . . . . . . . . . . . .             000000000   DS 4P             Packed-Dec              
   38   1  H-END-OF-MONTH-SW . . . . . . . . . . . . . .             000000000   DS 1C             Display                 
   39   1  H-ANNIVERSARY-IND . . . . . . . . . . . . . .             000000000   DS 1C             Display                 
   40   1  H-TODAYS-DATE . . . . . . . . . . . . . . . .             000000000   DS 6C             Display                 

In this example, compiled with Cobol 6.3, the fields are all in the Working-Storage section, as evidenced by the fact that the “Base Locator” column is blank. Base Locators are no longer used for Working-Storage.

H-EMP-HOURS, on line 34, is an 01 level, 2 bytes long and is defined as display numeric. Because it is an 01 level, the offset is zero

H-EMP-RATE, on line 33 is at level 3. It is a 3 byte packed decimal field at displacement 9 from the 01 level FILLER on line 29, which redefines 01 level H-EMP-RATE-INFO.

Next, we look in the Below the Bar Heap Map. This maps the start of all the 77 level and 01 level data names, as well as some special data names

Heap Storage Map

                     * * * * *   I N I T I A L   H E A P     S T O R A G E     M A P   * * * * *   
                                                                                                     
OFFSET (HEX)   LENGTH (HEX)   NAME                                                                       
                                                                                                          
          0              4       MGMT-IX                                                                  
          4              C       BLT_Ptrs                                                                       
         10              8       VNI_cells                                                                      
         18             74       GPCB                                                                           
         8C              4       WS-BASE-ADDRESS                                                                
                                                                                                                
                                                                                                                
                   * * * * *   E N D     O F    I N I T I A L   H E A P     S T O R A G E     M A P   * * * * *
                                                                                                                
                   * * * * *   B E L O W    T H E    B A R    H E A P    M A P   * * * * *                      
                                                                                                                
OFFSET (HEX)   LENGTH (HEX)   NAME                                                                              
                                                                                                                
          0              4       JNIENVPTR                                                                      
          8              2       RETURN-CODE                                                                    
         10              2       SORT-RETURN                                                                    
         18              8       SORT-CONTROL                                                                   
         20              4       SORT-CORE-SIZE             
         28              4       SORT-FILE-SIZE             
         30              4       SORT-MODE-SIZE             
         38              8       SORT-MESSAGE               
         40              4       TALLY                      
         48              1       SHIFT-OUT                  
         50              1       SHIFT-IN                   
         58              4       XML-CODE                   
         60             1E       XML-EVENT                  
         80              4       XML-INFORMATION            
         88              4       JSON-CODE                  
         90              4       JSON-STATUS                
         98              2       HOURLY-RECORDS-PROCESSED   
         A0              6       RATE-DETERMINATION-FIELDS  
         A8              3       WS-HOURLY-SWITCHES         
         B0              4       H-EMP-WAGES                
         B8              E       H-EMP-RATE-INFO            
         C8              2       H-EMP-HOURS                
         D0              2       H-OT-HOURS                 
         D8              4       H-OT-AMOUNT                
         E0              4       H-EMP-COMPENSATION         
         E8              1       H-END-OF-MONTH-SW          
         F0              1       H-ANNIVERSARY-IND          
         F8              6       H-TODAYS-DATE              
        100              6       H-EMP-HIRE-DATE            
        108              8       MGMT-RANGE                 
        110              F       MGMT-RATE-TABLE            
                                                                                                              
                   * * * * *   E N D     O F     B E L O W    T H E    B A R    H E A P    M A P   * * * * * *

From this, we see that the offset into the Working-Storage area for H-EMP-HOURS is X’C8’. 01 level H-EMP-RATE-INFO is at offset X’B8’, so H-EMP-RATE, at displacement 9, is at offset X’B8’ + X’09’ = X’C1’.

If the fields that we were looking for were in the Linkage Section, we might see a data division map like this:

Data Division Map with Linkage Section

PP 5655-EC6 IBM Enterprise COBOL for z/OS  6.3.0 P200901       CWAAHOUR  Date 04/20/2022  Time 08:42:14   Page     8            

Data Division Map                                                                                                               

Data Definition Attribute codes (rightmost column) have the following meanings:                                                 
   D = Object of OCCURS DEPENDING    G = GLOBAL                             S = Spanned file                                   
   E = EXTERNAL                      O = Has OCCURS clause                  U = Undefined format file                          
   F = Fixed-length file             OG= Group has own length definition    V = Variable-length file                           
   FB= Fixed-length blocked file     R = REDEFINES                          VB= Variable-length blocked file                   
   X = Unallocated                                                                                                             

Source   Hierarchy and                                    Base      Displacement  Asmblr Data                      Data Def     
LineID   Data Name                                        Locator     Structure   Definition        Data Type      Attributes   
    2  PROGRAM-ID CWAAHOUR----------------------------------------------------------------------------------------------------*
   14   1  HOURLY-RECORDS-PROCESSED. . . . . . . . . . .             000000000   DS 2C             Disp-Num                    
   15   1  RATE-DETERMINATION-FIELDS . . . . . . . . . .             000000000   DS 0CL6           Group                       
   16     2  HOURLY-EMP-RATE . . . . . . . . . . . . . .             000000000   DS 3C             Disp-Num                    
   17     2  HOURLY-OVERTIME-RATE. . . . . . . . . . . .             000000003   DS 2C             Display                     
   18     2  HOURLY-EVALUATOR. . . . . . . . . . . . . .             000000005   DS 1C             Display                     
   19   1  WS-HOURLY-SWITCHES. . . . . . . . . . . . . .             000000000   DS 0CL3           Group                       
   20     2  WS-SENIOR-RATE-IND-SW . . . . . . . . . . .             000000000   DS 1C             Display                     
   21     2  WS-OVERTIME-INDICATOR-SW. . . . . . . . . .             000000001   DS 1C             Display                     
   22     2  WS-HOURLY-RAISE-REVIEW-SW . . . . . . . . .             000000002   DS 1C             Display                     
   24   1  H-EMP-WAGES . . . . . . . . . . . . . . . . . BLL=00001   000000000   DS 4P             Packed-Dec                  
   25   1  H-EMP-RATE-INFO . . . . . . . . . . . . . . . BLL=00002   000000000   DS 0CL5           Group                
   26     2  HOURLY-RATE . . . . . . . . . . . . . . . . BLL=00002   000000000   DS 2P             Packed-Dec           
   27     2  HOURLY-INDICATOR. . . . . . . . . . . . . . BLL=00002   000000002   DS 1C             Display              
   28     2  HOURLY-OT-RATE. . . . . . . . . . . . . . . BLL=00002   000000003   DS 2C             Display              
   29   1  FILLER. . . . . . . . . . . . . . . . . . . . BLL=00002   000000000   DS 0CL3           Group          R     
   30     2  H-EMP-RATE. . . . . . . . . . . . . . . . . BLL=00002   000000000   DS 3P             Packed-Dec           
   31   1  H-EMP-HOURS . . . . . . . . . . . . . . . . . BLL=00003   000000000   DS 2C             Disp-Num             
   32   1  H-OT-HOURS. . . . . . . . . . . . . . . . . . BLL=00004   000000000   DS 2C             Disp-Num   

In this illustration, on line 28, HOURLY-OT-RATE is a 2 character display field. It is at offset 3 from the 01 level pointed to by BLL 2.

Cobol version 4.2 and below

Prior to Cobol version 5, Cobol used BLW cells to keep track of Working Storage. BLL cells are for Linkage section, and BLF cells are for records defined in the File Section.

MAP/DMAP for Cobol 4.2

Source  Hierarchy and                        Base       Hex-Displacement    Asmblr Data                      Data Def
LineID  Data Name                            Locator    Blk   Structure     Definition      Data Type        Attributes
     2 PROGRAM-ID PAYROLLX -------------------------------------------------------------------------------------------*
23 FD MASTER. . . . . . . . . . . . . . . . .                                                QSAM             FB
29 01 MASTER-RECORD . . . . . . . . . . . . . BLF=0000  000                 DS 80C           Display
30 FD OUTLIST . . . . . . . . . . . . . . . .                                                QSAM             FB
36 01 DATA-LINE . . . . . . . . . . . . . . . BLF=0001  000                 DS 133C          Display
37 FD TIMECARD. . . . . . . . . . . . . . . . QSAM                                                            FB
43 01 TIMECARD-RECORD . . . . . . . . . . . . BLF=0002  000                 DS 80C           Display
45 77 WS-LINE-CTR . . . . . . . . . . . . . . BLW=0000  000                 DS 2P            Packed-Dec
46 77 WS-PAGE-CTR . . . . . . . . . . . . . . BLW=0000  008                 DS 2P            Packed-Dec
47 77 WS-RECORD-CTR . . . . . . . . . . . . . BLW=0000  010                 DS2P             Packed-Dec
48 77 WS-TOTAL-NET-PAY. . . . . . . . . . . . BLW=0000  018                 DS 5P            Packed-Dec
49 77 WS-NET-PAY. . . . . . . . . . . . . . . BLW=0000  020                 DS 4P            Packed-Dec
50 77 WS-EMP-NO . . . . . . . . . . . . . . . BLW=0000  028                 DS 8C            Disp-Num
51 01 WS-TIMECARD-REC . . . . . . . . . . . . BLW=0000  030                 DS 0CL80         Group
52 02 TCR-EMP-NO. . . . . . . . . . . . . .   BLW=0000  030   0 000 000     DS 8C            Disp-Num
53 02 TCR-MONTH-CODE. . . . . . . . . . . .   BLW=0000  038   0 000 008     DS 2C            Disp-Num
54 02 TCR-EMP-NAME. . . . . . . . . . . . .   BLW=0000  03A   0 000 00A     DS 32C           Display
55 02 TCR-GROSS-PAY . . . . . . . . . . . .   BLW=0000  05A   0 000 02A     DS 7C            Disp-Num
56 02 TCR-TOTAL-TAXES . . . . . . . . . . .   BLW=0000  061   0 000 031     DS 6C            Disp-Num
57 02 TCR-FILLER. . . . . . . . . . . . . .   BLW=0000  067   0 000 037     DS 25C           Display

To find the contents of the fields listed in the Data Division map, locate this information from the listing:

  • The Base Locator type, BLF, BLW, or BLL and number
  • The displacement of the field.

Task 6: Find the correct cell for the fields of interest

From the Program Summary screen, select Program Storage for the abending program. The display looks like this:

Abend-AID ---------------- COBOL Storage Areas ----------------------
COMMAND ===>                                                         
                                                                     
 Program........... TESTPGM                                           
                                                                     
                                                                     
                        1  FILE    File Section                      
                                                                     
                        2  WORK    Working Storage                   
                                                                     
                        3  LINK    Linkage Section                   
                                                                     
                        4  SUPPORT Supporting Data                   
                                                                     
                        5  TGT     Task Global Table                 
                                                                     
                        6  DSA     Dynamic 31 Bit Save Area          

Select the correct section for the variables. In our example, there are two fields that could be in error, and both are in Working-Storage, so we go to the Working-Storage section for the abending program.

Cobol 5.1 and above

The Working Storage screen for Cobol version 5 and higher program looks like this:

Abend-AID ----------------- COBOL Storage Area -------- Row 000001 of 000002
COMMAND ===>                                                SCROLL ===> CSR
                                                                        ==>
Working Storage Section for program: CWAACOB                                
                                                                            
Name                   Address   Length                                     
*********************  ********  ********  *********************************
C_WSA WRITABLE STATIC  176CB058  00000738  Total Bytes=0001848              
WSA31-BASE-ADDRESS     176CB938  00001528  Total Bytes=0005416              
***************************** BOTTOM OF DATA *******************************

WSA31-BASE-ADDRESS is the start of Working-Storage for the program. Some programs might have WSA24-BASE-ADDRESS instead.

Cobol 4.2 and below

For releases of Cobol before version 5, Working-Storage would look like the following figure. The number of BLW cells depends upon the size of Working Storage.

Abend-AID ----------------- COBOL Storage Area -------- Row 000001 of 000001
COMMAND ===>                                                SCROLL ===> PAGE
                                                                        ==>  
Working Storage Section for program: TESTPGM                                 
                                                                             
Name                   Address   Length                                      
*********************  ********  ********  *********************************
TGT BLW   0(X'0000')   2B4C80C0  00001000
TGT BLW   1(X'0001')   2B4C90C0  00001000
TGT BLW   2(X'0002')   2B4CA0C0  00001000
TGT BLW   3(X'0003')   2B4CB0C0  00001000
***************************** BOTTOM OF DATA ******************************* 

Task 7: Find the data in the report

Select the address of the WSA-31-BASE-ADDRESS or the appropriate BLx cell. The screen will be formatted like this.

Abend-AID ------------------- Memory Display -------------------------------
COMMAND ===>                                                SCROLL ===> CSR
                                                                            
                                                        Clip Prev Next Lock
 Start Addr: 3DFD57F0          Comment:                                     
                                                                            
 Address    Offset    Word 1   Word 2   Word 3   Word 4    Storage          
 3DFD57F0 +00000000  00000000 00000000 00000000 00000000  *................*
 3DFD5800 +00000010  00000000 00000000 C9C7E9E2 D9E3C3C4  *........IGZSRTCD*
 3DFD5810 +00000020  00000000 00000000 00000000 00000000  *................*
  3DFD5820 +00000030  00000000 00000000 E2E8E2D6 E4E34040  *........SYSOUT  *
 3DFD5830 +00000040  00000000 00000000 0E000000 00000000  *........ .......*
 3DFD5840 +00000050  0F000000 00000000 00000000 00000000  * ...............*
 3DFD5850 +00000060  40404040 40404040 40404040 40404040  *                *
 3DFD5860 +00000070  40404040 40404040 40404040 40400000  *              ..*
 3DFD5870 +00000080  00000000 00000000 00000000 00000000  *................*
 3DFD5880 +00000090  F0F00000 00000000 D5D5D5D5 D5D5D500  *00......NNNNNNN.*
 3DFD5890 +000000A0  F0F0F1F5 C6F5C6F0 F0F3F0F0 F8F0F1F0  *0015F5F003008010*
 3DFD58A0 +000000B0  F0F0F0F0 F1000000 F5000000 00000000  *00001...5.......*
 3DFD58B0 +000000C0  F2F0F0F9 F2F90000 FF000000 00000000  *200929.. .......*

For Working Storage fields in Cobol 5.1 and above, use the Below the Bar Heap Map to find the displacement past the WSA31-BASE ADDRESS (or WSA24-BASE-ADDRESS) of the 01 level field containing the field that you want to find. On the memory display screen, use the “+” command to position to the beginning of the 01 level. For example, if the 01-level for the field that you want has a displacement of B8, issue

COMMAND ===> +B8

This will position the display to the start of the 01 level area. From there, the procedure is the same as for BLL cells, BLF cells and BLW cells for releases 4.2 and below.

Use the displacement for the field that you want to find and use the “+” command as above to position to the start of the field that you want to see. Use the length of the field from the Data Division Map and verify whether the data is a valid packed decimal number. Packed decimal numbers have two decimal digits, from 0 to 9 in each byte except the last. The last byte has the low order digit and a sign. The value of the sign must be A through F.

Task 8: Find the contents of other data fields in your program

Use Abend-AID in conjunction with the Data Division map to investigate the contents of other data fields in your program. Study the program listing to determine the source of the bad data.

To find the contents of an indexed field, for more information, see Determining Index and Indexed Field Values.

Review record information. The File section shows information about all files that are open at the time of the error. This information includes identification of the current record and previous records, when available. DCB and other control block information is also given. Abend-AID displays records using decimal locations, making fields easier to find when using record layouts. File information is provided for all file types, including VSAM and IAM.

If you are viewing the report by using ISPF to access the Viewing Server, you can directly access these files through File-AID from the online File Summary Selection List, which lists multiple open files. Inside a file you have full File-AID edit and browse capabilities.


 

Tip: For faster searching, add an asterisk to the end of your partial query. Example: cert*