Skip to content

Commit 2a663b6

Browse files
committed
Add S0C7 ABEND Lab: Handling Data Exception Due to Invalid Numeric Operations
Signed-off-by: Athar Ramzan <[email protected]>
1 parent d660d52 commit 2a663b6

File tree

5 files changed

+102
-0
lines changed

5 files changed

+102
-0
lines changed

COBOL Programming Course #2 - Learning COBOL/COBOL Programming Course #2 - Learning COBOL.md

Lines changed: 71 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3590,6 +3590,77 @@ With S0C7, the program is expecting numeric data, however, it found other invali
35903590
- Incorrect MOVE CORRESPONDING
35913591
- Incorrect assignment statements when MOVE from one field to another
35923592

3593+
## Lab
3594+
3595+
**Handling ABEND S0C7 - Data Exception**
3596+
3597+
**Objective:** Learn how to recognize and debug a common ABEND error, S0C7, caused by performing arithmetic on invalid numeric data in a COBOL program.
3598+
3599+
### What is S0C7?
3600+
3601+
S0C7 is a **runtime error** (called an **ABEND**, short for *abnormal end*) that happens when your COBOL program tries to perform arithmetic on invalid numeric data.
3602+
3603+
You will typically see an error message like:
3604+
3605+
`CEE3207S The system detected a data exception (System Completion Code=0C7)`
3606+
3607+
### Why does this error happen?
3608+
3609+
COBOL uses **PIC 9** or **COMP-3** for numeric fields. If these fields contain **non-numeric data** (like letters or symbols), and you try to perform arithmetic on them, the program crashes with a **S0C7 ABEND**.
3610+
3611+
### Here's a simple example:
3612+
3613+
```
3614+
01 JUNK-FIELD PIC X(05) VALUE "ABCDE".
3615+
01 NUM-FIELD-BAD REDEFINES JUNK-FIELD PIC S9(05) COMP-3.
3616+
...
3617+
ADD 100 TO NUM-FIELD-BAD.
3618+
3619+
```
3620+
3621+
- `"ABCDE"` is not a number.
3622+
- But `NUM-FIELD-BAD` is defined as a packed decimal (`COMP-3`).
3623+
- This mismatch causes the crash.
3624+
3625+
### Instructions
3626+
3627+
1. Open the COBOL file `CBL0014.cobol`. Analyze the code carefully. Notice that it uses `REDEFINES` to treat text as a numeric field.
3628+
2. Look at the value assigned to `JUNK-FIELD`. It is initialized with `"ABCDE"`, which is not a valid numeric value.
3629+
3. Observe how `NUM-FIELD-BAD`, a numeric `COMP-3` field, reuses the same memory space as `JUNK-FIELD`.
3630+
4. Submit the JCL program: `CBL0014J.jcl`.
3631+
3632+
*You should observe the job fails with a S0C7 ABEND.*
3633+
3634+
![](Images/image014.png)
3635+
3636+
### How to Fix It
3637+
3638+
To avoid getting this ABEND:
3639+
1. We need to modify the CBL0014.cobol
3640+
3641+
For example:
3642+
3643+
```
3644+
IDENTIFICATION DIVISION.
3645+
PROGRAM-ID. CBL0014.
3646+
DATA DIVISION.
3647+
WORKING-STORAGE SECTION.
3648+
01 TEXT-FIELD PIC X(05) VALUE "00012".
3649+
01 NUM-FIELD PIC 9(05).
3650+
01 RESULT PIC 9(06).
3651+
PROCEDURE DIVISION.
3652+
DISPLAY "Moving text to numeric field...".
3653+
MOVE TEXT-FIELD TO NUM-FIELD.
3654+
DISPLAY "Performing calculation...".
3655+
ADD 100 TO NUM-FIELD GIVING RESULT.
3656+
DISPLAY "Result: " RESULT.
3657+
STOP RUN.
3658+
```
3659+
3660+
2. Save the `CBL0014.cobol`file and resubmit the `CBL0014J.jcl`. The program should now run successfully and display the result of the arithmetic.
3661+
3662+
![](Images/image014j.png)
3663+
35933664
### S0CB - Division by Zero
35943665

35953666
Just like mathematics, attempting to divide a number with 0 in Enterprise COBOL is an undefined operation.
65.2 KB
Loading
30.4 KB
Loading
Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
IDENTIFICATION DIVISION.
2+
PROGRAM-ID. CBL0014.
3+
AUTHOR. Athar Ramzan.
4+
5+
DATA DIVISION.
6+
WORKING-STORAGE SECTION.
7+
01 JUNK-FIELD PIC X(05) VALUE "ABCDE".
8+
01 NUM-FIELD-BAD REDEFINES JUNK-FIELD PIC S9(05) COMP-3.
9+
01 RESULT PIC S9(06) COMP-3.
10+
11+
PROCEDURE DIVISION.
12+
DISPLAY "Triggering S0C7...".
13+
ADD 100 TO NUM-FIELD-BAD GIVING RESULT.
14+
DISPLAY "Result: " RESULT.
15+
STOP RUN.
Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,16 @@
1+
//CBL0014J JOB 1,NOTIFY=&SYSUID
2+
//***************************************************/
3+
//COBRUN EXEC IGYWCL
4+
//COBOL.SYSIN DD DSN=&SYSUID..CBL(CBL0014),DISP=SHR
5+
//LKED.SYSLMOD DD DSN=&SYSUID..LOAD(CBL0014),DISP=SHR
6+
//***************************************************/
7+
// IF RC = 0 THEN
8+
//***************************************************/
9+
//RUN EXEC PGM=CBL0014
10+
//STEPLIB DD DSN=&SYSUID..LOAD,DISP=SHR
11+
//SYSOUT DD SYSOUT=*,OUTLIM=15000
12+
//CEEDUMP DD SYSOUT=*
13+
//SYSUDUMP DD SYSOUT=*
14+
//***************************************************/
15+
// ELSE
16+
// ENDIF

0 commit comments

Comments
 (0)