MainframeMaster

COBOL Tutorial

COBOL Debugging Techniques

Progress0 of 0 lessons

Introduction to COBOL Debugging

Debugging is an essential skill for COBOL programmers. Due to COBOL's widespread use in critical business applications, effective debugging techniques are vital to maintain system reliability and minimize downtime. This guide covers systematic approaches to identify, isolate, and fix problems in COBOL programs.

The Debugging Process

  1. Reproducing the problem in a controlled environment
  2. Gathering information about the error and its context
  3. Formulating hypotheses about possible causes
  4. Testing hypotheses through strategic instrumentation
  5. Isolating the root cause of the problem
  6. Implementing and verifying a solution
  7. Preventing similar issues in the future

Types of Errors in COBOL Programs

Error TypeDescriptionDetection Point
Syntax ErrorsViolations of COBOL language rulesDuring compilation
Logic ErrorsIncorrect program algorithms or business logicTesting/execution
Data ErrorsIssues with data handling, conversion, or validationExecution
Boundary ErrorsArray subscript out of bounds, buffer overflowsExecution (with proper options)
I/O ErrorsProblems with file access or record processingExecution
Performance IssuesPrograms that work correctly but inefficientlyPerformance testing

Common COBOL Bugs and Solutions

Certain types of bugs appear frequently in COBOL programs. Recognizing these common patterns can help you diagnose problems more quickly and develop effective solutions.

S0C7 - Data Exception

One of the most common abends in COBOL programs, S0C7 occurs when the program attempts to perform arithmetic operations on non-numeric data.

Common Causes:

  • Moving alphanumeric data to numeric fields without validation
  • Uninitialized numeric fields used in calculations
  • Numeric overflow conditions
  • Misaligned data in record structures

Solutions:

  • Add data validation before performing arithmetic
  • Initialize all numeric fields with valid values
  • Use the NUMVAL or NUMVAL-C function to convert external data
  • Check record layouts and file descriptions for alignment issues
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
* Bad: No validation before using numeric data READ CUSTOMER-FILE AT END SET END-OF-FILE TO TRUE END-READ COMPUTE TOTAL-BALANCE = TOTAL-BALANCE + CUSTOMER-BALANCE * Good: Validate numeric data before using READ CUSTOMER-FILE AT END SET END-OF-FILE TO TRUE END-READ IF CUSTOMER-BALANCE IS NUMERIC COMPUTE TOTAL-BALANCE = TOTAL-BALANCE + CUSTOMER-BALANCE ELSE DISPLAY "Invalid numeric data in CUSTOMER-BALANCE: " CUSTOMER-BALANCE ADD 1 TO ERROR-COUNT END-IF

S0C4 - Protection Exception

A S0C4 abend typically indicates an attempt to access memory that the program is not authorized to use.

Common Causes:

  • Uninitialized or invalid pointer references
  • Array subscripts out of bounds
  • Reference modification outside field boundaries
  • Calling a subprogram that doesn't exist or isn't accessible

Solutions:

  • Initialize all pointers and addresses
  • Validate array subscripts before use
  • Check reference modification bounds
  • Verify subprogram existence and accessibility
  • Compile with SSRANGE option to detect boundary violations
cobol
1
2
3
4
5
6
7
8
9
10
* Bad: No validation of array subscript MOVE CUSTOMER-NAME(CUSTOMER-INDEX) TO OUTPUT-NAME * Good: Validate subscript before using IF CUSTOMER-INDEX > 0 AND CUSTOMER-INDEX <= 100 MOVE CUSTOMER-NAME(CUSTOMER-INDEX) TO OUTPUT-NAME ELSE DISPLAY "Invalid index: " CUSTOMER-INDEX MOVE SPACES TO OUTPUT-NAME END-IF

Endless Loops

Programs that never terminate due to logic errors in loop control structures.

Common Causes:

  • Missing or incorrect loop termination conditions
  • Failing to update the loop control variable
  • Conditions that can never be satisfied
  • Infinite PERFORM...THROUGH structures with GO TO statements

Solutions:

  • Add counter limits to all loops
  • Ensure loop control variables are properly updated
  • Verify termination conditions are achievable
  • Avoid complex control flow with GO TO statements
cobol
1
2
3
4
5
6
7
8
9
10
11
12
* Bad: Potential infinite loop with no safety counter PERFORM PROCESS-RECORD UNTIL END-OF-FILE * Good: Safety counter to prevent infinite loops INITIALIZE LOOP-COUNTER PERFORM PROCESS-RECORD UNTIL END-OF-FILE OR LOOP-COUNTER > 1000000 IF NOT END-OF-FILE AND LOOP-COUNTER > 1000000 DISPLAY "Possible infinite loop detected" DISPLAY "Processing terminated after " LOOP-COUNTER " iterations" END-IF

File Status Errors

Problems related to file operations, often indicated by non-zero file status codes.

Common Causes:

  • Missing or incorrect file definitions
  • Attempting to access a file that's not open
  • File not found or access permission issues
  • Record length or key violations
  • Trying to read beyond the end of a file

Solutions:

  • Always check file status after each I/O operation
  • Implement proper error handling for file operations
  • Verify file attributes match program definitions
  • Check for end-of-file conditions before reading
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
* Bad: No file status checking OPEN INPUT CUSTOMER-FILE READ CUSTOMER-FILE AT END SET END-OF-FILE TO TRUE END-READ * Good: Check file status after each operation OPEN INPUT CUSTOMER-FILE IF FILE-STATUS NOT = "00" DISPLAY "Error opening CUSTOMER-FILE. Status: " FILE-STATUS PERFORM ERROR-ROUTINE EXIT PROGRAM END-IF READ CUSTOMER-FILE AT END SET END-OF-FILE TO TRUE END-READ IF NOT END-OF-FILE AND FILE-STATUS NOT = "00" DISPLAY "Error reading CUSTOMER-FILE. Status: " FILE-STATUS DISPLAY "Status " FILE-STATUS " = " FILE-STATUS-MESSAGE(FILE-STATUS) PERFORM ERROR-ROUTINE END-IF

Data Truncation Issues

Problems that occur when moving data between fields of different sizes.

Common Causes:

  • Moving data to a smaller field without checking length
  • Numeric field overflow during calculations
  • Incorrect PICTURE clause definitions
  • Failing to account for sign or decimal positions

Solutions:

  • Validate data length before moving to smaller fields
  • Use appropriate PICTURE clauses with sufficient size
  • Check for numeric overflow during calculations
  • Be aware of implicit decimal point alignment
cobol
1
2
3
4
5
6
7
8
9
10
11
12
* Bad: Potential truncation without warning MOVE LONG-CUSTOMER-NAME TO SHORT-CUSTOMER-NAME * Good: Check length before moving IF FUNCTION LENGTH(FUNCTION TRIM(LONG-CUSTOMER-NAME)) > FUNCTION LENGTH(SHORT-CUSTOMER-NAME) DISPLAY "Warning: Name truncated: " LONG-CUSTOMER-NAME MOVE LONG-CUSTOMER-NAME TO SHORT-CUSTOMER-NAME MOVE "Y" TO TRUNCATION-OCCURRED ELSE MOVE LONG-CUSTOMER-NAME TO SHORT-CUSTOMER-NAME END-IF

DISPLAY Statements for Debugging

The DISPLAY statement is one of the most fundamental and effective debugging tools in COBOL. It allows programmers to output the values of variables, status information, and progress messages during program execution, making it invaluable for tracking down bugs.

Basic DISPLAY Usage

The DISPLAY statement can output literals, variables, or a combination of both:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
* Display a literal message DISPLAY "Processing customer records". * Display a variable value DISPLAY CUSTOMER-NAME. * Display combination of literals and variables DISPLAY "Customer ID: " CUSTOMER-ID " Name: " CUSTOMER-NAME. * Display multiple items with formatting DISPLAY "Balance: $" CUSTOMER-BALANCE " Status: " CUSTOMER-STATUS.

In batch programs, DISPLAY output typically goes to the system output (SYSOUT). In online environments, the destination depends on the specific runtime environment.

Strategic DISPLAY Placement

Effective debugging requires placing DISPLAY statements at strategic locations:

  • Entry/Exit Points: Add DISPLAY at the beginning and end of important procedures
  • Before Critical Operations: Display values before they're used in calculations or conditions
  • After Data Modifications: Display values after they've been changed
  • Decision Points: Show which branch of logic is being taken
  • Loop Controls: Display iteration counters and condition values
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
PROCESS-CUSTOMER-RECORD. DISPLAY "Entering PROCESS-CUSTOMER-RECORD". DISPLAY " Customer ID: " CUSTOMER-ID. DISPLAY " Customer Balance: " CUSTOMER-BALANCE. EVALUATE TRUE WHEN CUSTOMER-BALANCE < 0 DISPLAY " Processing overdue account" PERFORM PROCESS-OVERDUE-ACCOUNT WHEN CUSTOMER-BALANCE = 0 DISPLAY " Processing zero balance account" PERFORM PROCESS-ZERO-BALANCE WHEN OTHER DISPLAY " Processing active account" PERFORM PROCESS-ACTIVE-ACCOUNT END-EVALUATE DISPLAY "Exiting PROCESS-CUSTOMER-RECORD".

Advanced DISPLAY Techniques

TechniqueDescriptionExample
Conditional DebuggingOnly display output when in debug modeIF DEBUG-MODE DISPLAY "Debug: " WS-COUNTER END-IF
Value FormattingUse reference modification to format outputDISPLAY "Date: " WS-DATE(1:4) "-" WS-DATE(5:2) "-" WS-DATE(7:2)
Binary/Hex DisplayConvert binary data to displayable formatDISPLAY "Hex value: " FUNCTION HEX-OF(WS-BINARY-DATA)
Milestone MarkersAdd visible markers in outputDISPLAY "===== BEGINNING PROCESSING PHASE 2 ====="
Execution TracingCreate breadcrumb trail through codeDISPLAY "TRACE: " PROGRAM-ID " - Line " LINE-NUMBER

Binary Search Debugging Technique

The binary search method is a powerful technique for isolating bugs in large programs:

  1. Insert a DISPLAY statement at the beginning and end of the program to confirm execution
  2. Add a DISPLAY at the midpoint of the suspected problem area
  3. Based on which DISPLAY statements appear in the output, narrow down where the problem occurs
  4. Continue dividing the problem area in half until the exact location is found
  5. Once isolated, add more detailed DISPLAY statements to inspect data values

This method is particularly effective for locating the point where a program abends or where data values begin to deviate from expected results.

Managing DISPLAY Statements

Effective management of debugging DISPLAY statements is important for maintaining code quality:

  • Temporary vs. Permanent: Consider which DISPLAY statements should be removed after debugging and which provide ongoing value
  • Comment Out vs. Delete: Comment out useful debugging statements rather than deleting them when moving to production
  • Debug Indicators: Use a debug flag that can enable/disable all debugging output
  • WITH DEBUGGING MODE: Use special debugging lines (D in column 7) that can be enabled/disabled via compilation
  • Standardized Format: Adopt consistent formatting for debug output to make it easier to scan
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
WORKING-STORAGE SECTION. 01 DEBUG-FLAGS. 05 DEBUG-MODE PIC X VALUE 'N'. 88 DEBUGGING-ON VALUE 'Y'. 88 DEBUGGING-OFF VALUE 'N'. 05 DEBUG-LEVEL PIC 9 VALUE 0. 88 DEBUG-CRITICAL VALUE 1. 88 DEBUG-IMPORTANT VALUE 1 THRU 2. 88 DEBUG-DETAILED VALUE 1 THRU 3. 88 DEBUG-TRACE VALUE 1 THRU 4. *> Elsewhere in the program: IF DEBUGGING-ON AND DEBUG-IMPORTANT DISPLAY "DEBUG: Processing record " RECORD-COUNT DISPLAY "DEBUG: Customer: " CUSTOMER-NAME END-IF

Compiler Options for Debugging

COBOL compilers provide various options that can help detect errors earlier and provide additional information for debugging. Understanding and using these options can significantly improve the debugging process.

Key Debugging Compiler Options

OptionPurposeWhen to Use
TESTIncludes information necessary for interactive debugging toolsDuring development and test phases, when detailed interactive debugging is needed
SSRANGEChecks subscript and reference modification boundaries at runtimeWhen using arrays/tables or reference modification extensively
NUMCHECKValidates numeric data at runtime to prevent S0C7 abendsWhen processing external data or when experiencing data exceptions
NOOPTIMIZEDisables compiler optimizations for more predictable debuggingDuring debugging sessions when you need exact correlation with source
OFFSETProvides a listing of offsets for each statement in the programWhen analyzing dumps to correlate addresses with source statements
XREFGenerates cross-reference of all variablesWhen tracking variable usage across a large program
LISTCreates a listing file with generated code and sourceWhen detailed analysis of program compilation is needed
MAPProvides memory map of data division itemsWhen analyzing storage layout and data structure organization

The TEST Compiler Option

The TEST option is particularly important for interactive debugging. It generates additional information that allows debugging tools to correlate the executing program with the source code.

Common suboptions for TEST include:

  • STMT: Enables setting breakpoints at COBOL statement boundaries
  • PATH: Enables setting breakpoints at all path points
  • BLOCK: Enables setting breakpoints at entry and exit of program blocks
  • NOSYMBOL/SYMBOL: Controls inclusion of symbolic information (variable names)
  • SEPARATE: Stores debugging information in a separate file to reduce program size
jcl
1
2
3
// JCL example with TEST compiler option //COBOL EXEC PGM=IGYCRCTL,REGION=0M, // PARM='NOOPT,TEST(STMT,SYM,SEPARATE),SSRANGE,NUMCHECK'

Compile-Time vs. Runtime Checking

Different compiler options enable checks at different stages:

StageOptionsTypes of Errors Caught
Compile-TimeFLAGSAA, FLAGSTD, DBCS, WORDSyntax errors, standards violations, obsolete features
Link-TimeDYNAM, NODYNAMUnresolved references, missing modules
RuntimeSSRANGE, NUMCHECK, TESTBoundary violations, data errors, logic errors

Runtime checking options have a performance impact, so they are typically used during development and testing but may be disabled in production for performance-critical applications.

WITH DEBUGGING MODE

COBOL provides a special debugging mode that can be enabled via the SOURCE-COMPUTER paragraph. When debugging mode is active, any lines with 'D' in column 7 (the indicator area) are compiled and executed. When debugging mode is not active, these lines are treated as comments.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
IDENTIFICATION DIVISION. PROGRAM-ID. DEBUGEX. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SOURCE-COMPUTER. IBM-370 WITH DEBUGGING MODE. OBJECT-COMPUTER. IBM-370. DATA DIVISION. WORKING-STORAGE SECTION. 01 COUNTER PIC 9(3) VALUE ZERO. 01 TOTAL PIC 9(5) VALUE ZERO. PROCEDURE DIVISION. MAIN-LOGIC. D DISPLAY "Debug: Entering MAIN-LOGIC". PERFORM VARYING COUNTER FROM 1 BY 1 UNTIL COUNTER > 100 D DISPLAY "Debug: Counter = " COUNTER ADD COUNTER TO TOTAL END-PERFORM. D DISPLAY "Debug: Total = " TOTAL. DISPLAY "Processing complete. Total: " TOTAL. STOP RUN.

This approach allows you to include debugging statements directly in the source code but easily disable them when compiling for production by changing just one line.

Debugging Tools and Techniques

Beyond basic DISPLAY statements and compiler options, various specialized tools and techniques can help debug COBOL applications more efficiently, especially in complex environments.

Interactive Debuggers

Interactive debuggers provide a powerful environment for examining and controlling program execution.

ToolEnvironmentKey Features
IBM Debug Tool / z/OS Debuggerz/OS MainframeSource-level debugging, breakpoints, variable monitoring, step execution
CEDF (CICS Execution Diagnostic Facility)CICSIntercepts CICS commands, displays parameters and results
Xpediter (Compuware)z/OSAdvanced debugging features, memory inspection, batch/CICS support
InterTest (Broadcom)z/OSInteractive debugging, automated error detection, data monitoring
GnuCOBOL DebuggerOpen Source/LinuxBasic debugging for GnuCOBOL programs
Visual COBOL DebuggerWindows/.NETIntegrated debugging in Visual Studio, modern interface

Interactive debuggers typically require programs to be compiled with special options (such as TEST) to enable all features.

Dump Analysis

When a program abends, system dumps provide valuable information for diagnosing the cause.

Key components of dump analysis:

  • PSW (Program Status Word): Indicates the address where the program failed
  • Registers: Show the values in CPU registers at the time of failure
  • Call Stack: Displays the sequence of program calls leading to the error
  • Storage Areas: Shows the contents of memory, including variables
  • System Information: Provides environmental context for the failure
text
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
----------------------------- STORAGE AREAS ------------------------------- MODULE EP=CUSTMAIN OFFSET=00003A76 REGISTER VALUES R0 00000000 R1 16B57240 R2 16B57240 R3 00000008 R4 169FA5D0 R5 169FA610 R6 16AD08C8 R7 16B55238 R8 169FA258 R9 00000000 RA 00000000 RB 16AFFDE4 RC 00000000 RD 16B00F28 RE 16AD9ED4 RF 00003BDC STORAGE FOR ABEND DATA ADDRESS 16B572C0 TO 16B572DF 16B572C0 C3E4E2E3 D6D4C5D9 40404040 40404040 *CUSTOMER * 16B572D0 40404040 40C9C440 F2F54040 40404040 * ID 25 * CALL CHAIN: PROGRAM=CUSTMAIN OFFSET=+00003A76 EP=CUSTMAIN CALLED BY PROGRAM=MAINPROG OFFSET=+00002E48 EP=MAINPROG

Tools like IPCS (Interactive Problem Control System) on z/OS provide interfaces for navigating and analyzing dumps. Dump analysis skills are essential for debugging complex problems, especially in production environments where interactive debugging may not be possible.

Trace Facilities

Trace facilities record the execution path and key events during program execution:

  • Language Environment Trace: Records entry/exit from procedures and runtime events
  • CICS Trace: Tracks CICS commands and system interactions
  • DB2 Trace: Monitors database interactions and SQL execution
  • Custom Trace Routines: User-developed logging mechanisms for specific needs
cobol
1
2
3
4
5
6
7
8
9
10
11
12
//STEP1 EXEC PGM=CUSTMAIN, // PARM='TRACE(ALL),TRAP(ON)' * In the program: WORKING-STORAGE SECTION. 01 TRACE-FLAG PIC X VALUE 'Y'. 88 TRACE-ON VALUE 'Y'. ... IF TRACE-ON DISPLAY "TRACE: Entering PROCESS-CUSTOMER with ID " CUSTOMER-ID DISPLAY "TRACE: Balance = " CUSTOMER-BALANCE END-IF

Log Analysis

Analyzing application and system logs can provide insights into program behavior:

  • Application Logs: Custom logs created by the application via DISPLAY or other means
  • System Logs: Operating system records of program execution and errors
  • Transaction Logs: Records of online transactions in systems like CICS or IMS
  • Database Logs: Records of database activity and changes

Log analysis often requires tools to filter, search, and correlate large volumes of log data. Many mainframe environments have specialized tools for this purpose.

Data Analysis Techniques

Analyzing data files and database content can help identify data-related issues:

  • File Browsing: Examine file contents using tools like ISPF browser on mainframes
  • Data Comparison: Compare expected vs. actual results using comparison utilities
  • Database Queries: Directly query databases to verify data state
  • Data Mapping: Verify that file descriptions match actual data layouts
  • Test Data Generation: Create specific test cases to isolate data handling issues
jcl
1
2
3
4
5
6
7
8
//STEP1 EXEC PGM=IDCAMS //SYSPRINT DD SYSOUT=* //SYSIN DD * PRINT INFILE(CUSTFILE) - CHAR - COUNT(100) /* //CUSTFILE DD DSN=PROD.CUSTOMER.MASTER,DISP=SHR

Memory Inspection Tools

Specialized tools can examine program memory during execution:

  • Viewing raw memory contents at specific addresses
  • Monitoring changes to variables during execution
  • Setting watchpoints that trigger when memory changes
  • Detecting memory leaks and storage overlays

Most interactive debuggers include memory inspection capabilities. In mainframe environments, tools like Debug Tool's STORAGE command can examine memory directly.

Remote Debugging

Modern COBOL development environments often support remote debugging:

  • IBM Debug Tool for Eclipse: Connect to mainframe programs from Eclipse IDE
  • Visual COBOL: Debug applications from Visual Studio across platforms
  • Web-based Interfaces: Browser-based debugging interfaces for mainframe programs

Remote debugging allows developers to use modern, graphical interfaces to debug programs running on traditional mainframe systems, combining the power of mainframe processing with the convenience of desktop development tools.

Defensive Programming Practices

Defensive programming focuses on preventing bugs before they occur by anticipating potential issues and building safeguards into the code. These practices can significantly reduce debugging time by catching problems early or preventing them entirely.

Input Validation

Always validate data before processing it, especially data from external sources:

  • Check numeric fields for valid numeric content
  • Verify dates for valid formats and logical values
  • Ensure codes or identifiers match expected patterns
  • Validate that values fall within acceptable ranges
  • Verify required fields are not empty
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
VALIDATE-CUSTOMER-DATA. MOVE 'Y' TO DATA-VALID-FLAG. * Validate customer ID format (must be numeric) IF CUSTOMER-ID IS NOT NUMERIC DISPLAY "Error: Customer ID must be numeric: " CUSTOMER-ID MOVE 'N' TO DATA-VALID-FLAG END-IF * Validate customer name (must not be spaces) IF CUSTOMER-NAME = SPACES DISPLAY "Error: Customer name is required" MOVE 'N' TO DATA-VALID-FLAG END-IF * Validate date format (YYYYMMDD) IF TRANSACTION-DATE IS NOT NUMERIC OR TRANSACTION-DATE(5:2) < '01' OR TRANSACTION-DATE(5:2) > '12' OR TRANSACTION-DATE(7:2) < '01' OR TRANSACTION-DATE(7:2) > '31' DISPLAY "Error: Invalid date format: " TRANSACTION-DATE MOVE 'N' TO DATA-VALID-FLAG END-IF * Validate amount range IF TRANSACTION-AMOUNT < ZERO OR TRANSACTION-AMOUNT > 1000000 DISPLAY "Error: Amount out of acceptable range: " TRANSACTION-AMOUNT MOVE 'N' TO DATA-VALID-FLAG END-IF

Explicit Initialization

Always initialize variables before use to prevent unpredictable behavior:

  • Use VALUE clauses for static initialization
  • Add explicit initialization paragraphs
  • Consider using INITIALIZE statement for group items
  • Be careful with reused variables in loops
  • Pay special attention to counters and accumulators
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
WORKING-STORAGE SECTION. * Explicit initialization with VALUE clauses 01 COUNTERS-AND-ACCUMULATORS. 05 RECORD-COUNT PIC 9(6) VALUE ZERO. 05 ERROR-COUNT PIC 9(4) VALUE ZERO. 05 TRANSACTION-TOTAL PIC S9(9)V99 VALUE ZERO. * Group initialization in the procedure division INITIALIZE-VARIABLES. INITIALIZE CUSTOMER-RECORD INITIALIZE TRANSACTION-RECORD MOVE SPACES TO ERROR-MESSAGE MOVE ZEROS TO CALCULATION-RESULT MOVE 'N' TO EOF-FLAG

Boundary Checking

Always validate array indices and buffer operations to prevent overflows:

  • Check table subscripts before accessing array elements
  • Validate sizes when moving data between fields
  • Use reference modification carefully
  • Consider compiler options like SSRANGE for additional checking
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
* Validate subscript before using IF PRODUCT-INDEX > 0 AND PRODUCT-INDEX <= PRODUCT-TABLE-SIZE MOVE PRODUCT-PRICE(PRODUCT-INDEX) TO OUTPUT-PRICE ELSE DISPLAY "Error: Invalid product index: " PRODUCT-INDEX MOVE ZERO TO OUTPUT-PRICE END-IF * Check string length before reference modification COMPUTE STRING-LENGTH = FUNCTION LENGTH(INPUT-STRING) IF EXTRACT-START > 0 AND EXTRACT-START <= STRING-LENGTH AND EXTRACT-LENGTH > 0 AND EXTRACT-START + EXTRACT-LENGTH - 1 <= STRING-LENGTH MOVE INPUT-STRING(EXTRACT-START:EXTRACT-LENGTH) TO OUTPUT-STRING ELSE DISPLAY "Error: Invalid string extraction parameters" DISPLAY "String length: " STRING-LENGTH DISPLAY "Start: " EXTRACT-START DISPLAY "Length: " EXTRACT-LENGTH MOVE SPACES TO OUTPUT-STRING END-IF

Error Handling

Implement robust error handling to gracefully manage unexpected conditions:

  • Check file status codes after every I/O operation
  • Handle unexpected values in EVALUATE statements with WHEN OTHER
  • Implement error recovery procedures where appropriate
  • Log detailed error information for debugging
  • Provide meaningful error messages to users
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
READ CUSTOMER-FILE INVALID KEY MOVE "Y" TO RECORD-NOT-FOUND-FLAG STRING "Customer not found: " DELIMITED BY SIZE CUSTOMER-ID DELIMITED BY SIZE INTO ERROR-MESSAGE PERFORM LOG-ERROR END-READ IF FILE-STATUS NOT = "00" AND FILE-STATUS NOT = "23" STRING "File I/O error: " DELIMITED BY SIZE FILE-STATUS DELIMITED BY SIZE " on CUSTOMER-FILE" DELIMITED BY SIZE INTO ERROR-MESSAGE PERFORM LOG-ERROR MOVE FILE-STATUS TO RETURN-CODE EXIT PROGRAM END-IF LOG-ERROR. DISPLAY "ERROR: " FUNCTION CURRENT-DATE " - " ERROR-MESSAGE WRITE ERROR-RECORD FROM ERROR-MESSAGE ADD 1 TO ERROR-COUNT

Safe Copy Books

Design copy books with defensive programming in mind:

  • Include length fields for variable data
  • Add version identifiers to detect mismatches
  • Use FILLER fields as buffers between critical data
  • Standardize error handling code in copy books
  • Include validation routines for complex data structures
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
* Example of a defensive copybook: * CUSTDEF.CPY - Customer Record Definition * Version: 1.2 * Last Updated: 2023-03-15 01 CUSTOMER-RECORD. 05 CR-HEADER. 10 CR-VERSION PIC 9(2)V9(2). 10 CR-RECORD-LENGTH PIC 9(4) COMP. 10 FILLER PIC X(10). 05 CR-DATA. 10 CR-CUSTOMER-ID PIC X(10). 10 CR-CUSTOMER-NAME PIC X(30). 10 CR-ADDRESS PIC X(50). 10 CR-PHONE PIC X(15). 10 FILLER PIC X(20). 05 CR-FINANCIAL. 10 CR-CREDIT-LIMIT PIC 9(7)V99. 10 CR-CURRENT-BALANCE PIC S9(7)V99. 10 CR-LAST-PAYMENT PIC 9(8). 10 FILLER PIC X(20). 05 CR-TRAILER PIC X(8) VALUE "CUSTEND".

Code Reviews

Regular code reviews are a crucial defensive programming practice:

  • Have peers review code for potential issues
  • Use checklists focused on common error patterns
  • Review error handling logic specifically
  • Ensure all boundary conditions are handled
  • Verify consistent use of defensive techniques

Code reviews catch many issues before they reach testing, let alone production. They're also an effective way to share defensive programming knowledge across the team.

Assertions and Self-Checks

Build self-checking mechanisms into the code:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
* Balance check to verify processing integrity COMPUTE EXPECTED-TOTAL = OPENING-BALANCE + TOTAL-CREDITS - TOTAL-DEBITS IF EXPECTED-TOTAL NOT = CLOSING-BALANCE DISPLAY "Balance check failed!" DISPLAY "Opening balance: " OPENING-BALANCE DISPLAY "Total credits: " TOTAL-CREDITS DISPLAY "Total debits: " TOTAL-DEBITS DISPLAY "Expected total: " EXPECTED-TOTAL DISPLAY "Closing balance: " CLOSING-BALANCE MOVE "Y" TO PROCESSING-ERROR END-IF * Data consistency check IF DETAIL-RECORD-COUNT NOT = HEADER-RECORD-COUNT DISPLAY "Record count mismatch!" DISPLAY "Header count: " HEADER-RECORD-COUNT DISPLAY "Detail count: " DETAIL-RECORD-COUNT MOVE "Y" TO PROCESSING-ERROR END-IF