MainframeMaster

COBOL Tutorial

Testing COBOL Programs

Progress0 of 0 lessons

Introduction to Testing COBOL Programs

Testing is a critical aspect of COBOL application development and maintenance. Thorough testing ensures that programs function correctly, meet business requirements, and maintain reliability even after modifications. For COBOL applications that often support mission-critical business functions, effective testing is particularly important.

Why Testing COBOL Programs Is Crucial

  • COBOL applications often process critical financial and business transactions
  • Many COBOL systems have been in production for decades and contain complex business logic
  • The cost of errors in production can be substantial, both financially and reputationally
  • Legacy systems may lack documentation, making testing essential for understanding behavior
  • Regulatory compliance often requires demonstrable testing practices

Testing Challenges in COBOL Environments

ChallengeImpactMitigation Strategies
Complex Legacy CodebasesDifficult to isolate components for testingIncremental refactoring, modularization
Limited Testing ToolsFewer automated testing optionsSpecialized mainframe testing tools, custom frameworks
Environment ConstraintsLimited MIPS, batch windows, resource contentionTest environment optimization, scheduling
Knowledge GapsRetiring workforce, undocumented logicKnowledge transfer, code analysis tools
Integration ComplexityInterdependencies with other systemsService virtualization, stubs/mocks

Types of Testing for COBOL Applications

  1. Unit Testing: Testing individual components or modules in isolation
  2. Integration Testing: Testing interactions between components
  3. Functional Testing: Verifying functionality against business requirements
  4. Regression Testing: Ensuring changes don't break existing functionality
  5. Performance Testing: Evaluating system performance under various conditions
  6. System Testing: Testing the complete application in an environment that mimics production
  7. User Acceptance Testing (UAT): Validation by business users

A comprehensive testing strategy for COBOL applications should include all these types of testing, adapted to the specific requirements and constraints of the mainframe environment.

Unit Testing Approaches

Unit testing involves testing individual components of a program in isolation to verify that each part functions correctly on its own. While unit testing can be challenging for legacy COBOL applications, several approaches have proven effective.

Creating Test Drivers

Test drivers are small COBOL programs written specifically to test a component by providing controlled inputs and verifying outputs.

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
32
33
34
35
36
37
38
39
40
41
42
43
IDENTIFICATION DIVISION. PROGRAM-ID. TEST-DRIVER. DATA DIVISION. WORKING-STORAGE SECTION. 01 TEST-INPUTS. 05 INPUT-VALUE-1 PIC 9(5)V99 VALUE 1234.56. 05 INPUT-VALUE-2 PIC 9(5)V99 VALUE 7890.12. 05 EXPECTED-RESULT PIC 9(6)V99 VALUE 9124.68. 01 TEST-OUTPUTS. 05 ACTUAL-RESULT PIC 9(6)V99. 05 TEST-PASSED-FLAG PIC X. 88 TEST-PASSED VALUE 'Y'. 88 TEST-FAILED VALUE 'N'. PROCEDURE DIVISION. MAIN-PARAGRAPH. DISPLAY "BEGINNING TEST OF CALC-SUM PARAGRAPH" * Set up test inputs MOVE 1234.56 TO INPUT-VALUE-1 MOVE 7890.12 TO INPUT-VALUE-2 * Call the paragraph being tested PERFORM CALC-SUM * Verify results IF ACTUAL-RESULT = EXPECTED-RESULT SET TEST-PASSED TO TRUE DISPLAY "TEST PASSED: Result = " ACTUAL-RESULT ELSE SET TEST-FAILED TO TRUE DISPLAY "TEST FAILED:" DISPLAY " Expected: " EXPECTED-RESULT DISPLAY " Actual: " ACTUAL-RESULT END-IF STOP RUN. * This is the paragraph being tested CALC-SUM. COMPUTE ACTUAL-RESULT = INPUT-VALUE-1 + INPUT-VALUE-2 .

Test drivers can be used to test individual paragraphs, sections, or entire subprograms. They are particularly useful for testing complex business logic.

Using Stubs and Mocks

Stubs and mocks replace external dependencies with simplified versions that return predefined data, allowing you to isolate the component being tested.

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
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
* Original code with external dependency CUSTOMER-LOOKUP. MOVE CUST-ID-IN TO DB-CUSTOMER-ID CALL 'DB-PROGRAM' USING DB-REQUEST-AREA IF DB-STATUS-OK MOVE DB-CUSTOMER-NAME TO CUST-NAME-OUT MOVE DB-CUSTOMER-ADDR TO CUST-ADDR-OUT ELSE MOVE SPACES TO CUST-NAME-OUT MOVE SPACES TO CUST-ADDR-OUT END-IF. * Test stub replacing the database call IDENTIFICATION DIVISION. PROGRAM-ID. DB-PROGRAM. DATA DIVISION. LINKAGE SECTION. 01 DB-REQUEST-AREA. 05 DB-FUNCTION PIC X(8). 05 DB-CUSTOMER-ID PIC X(10). 05 DB-STATUS PIC XX. 88 DB-STATUS-OK VALUE "00". 05 DB-CUSTOMER-DATA. 10 DB-CUSTOMER-NAME PIC X(30). 10 DB-CUSTOMER-ADDR PIC X(50). PROCEDURE DIVISION USING DB-REQUEST-AREA. MAIN-PARAGRAPH. * Simulate database lookup with test data EVALUATE DB-CUSTOMER-ID WHEN "1234567890" MOVE "00" TO DB-STATUS MOVE "JOHN DOE" TO DB-CUSTOMER-NAME MOVE "123 MAIN ST" TO DB-CUSTOMER-ADDR WHEN "9876543210" MOVE "00" TO DB-STATUS MOVE "JANE SMITH" TO DB-CUSTOMER-NAME MOVE "456 OAK AVE" TO DB-CUSTOMER-ADDR WHEN OTHER MOVE "01" TO DB-STATUS MOVE SPACES TO DB-CUSTOMER-NAME MOVE SPACES TO DB-CUSTOMER-ADDR END-EVALUATE GOBACK.

Batch Testing with JCL

JCL (Job Control Language) can be used to set up automated unit tests for batch COBOL programs.

jcl
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
//UNITTEST JOB (ACCT),'UNIT TEST',CLASS=A,MSGCLASS=X //* //* JCL TO EXECUTE UNIT TESTS FOR THE CUSTOMER PROCESSING PROGRAM //* //STEP01 EXEC PGM=CUSTPROC //STEPLIB DD DSN=TEST.LOADLIB,DISP=SHR //* //* TEST INPUT DATA //CUSTINP DD DSN=TEST.DATA.CUSTTEST,DISP=SHR //* //* OUTPUT WILL BE COMPARED TO EXPECTED RESULTS //CUSTOUT DD DSN=TEST.DATA.ACTUAL,DISP=(NEW,CATLG), // SPACE=(CYL,(1,1)), // DCB=(RECFM=FB,LRECL=100,BLKSIZE=0) //* //SYSOUT DD SYSOUT=* //SYSUDUMP DD SYSOUT=* //* //* COMPARE ACTUAL OUTPUT TO EXPECTED OUTPUT //STEP02 EXEC PGM=IDCAMS //SYSPRINT DD SYSOUT=* //SYSIN DD * COMPARE - DATA(TEST.DATA.ACTUAL) - WITH(TEST.DATA.EXPECTED) /*

This approach uses standard mainframe utilities like IDCAMS COMPARE to verify that the program produces the expected output files given known input data.

Unit Testing Frameworks for COBOL

Modern COBOL unit testing can leverage specialized frameworks:

  • Micro Focus Topaz for Total Test: Provides automated unit testing capabilities for mainframe applications
  • IBM Rational Developer for z: Offers integrated unit testing features
  • COBOL-Check: An open-source unit testing framework for COBOL
  • Custom frameworks: Many organizations develop in-house testing frameworks
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
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
* Example using a hypothetical unit testing framework IDENTIFICATION DIVISION. PROGRAM-ID. CALC-INTEREST-TEST. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. TEST-FRAMEWORK IS UNITTEST. DATA DIVISION. WORKING-STORAGE SECTION. 01 UNITTEST-FRAMEWORK. 05 TEST-CASE-NAME PIC X(30). 05 TEST-RESULT PIC X. 88 TEST-PASSED VALUE 'P'. 88 TEST-FAILED VALUE 'F'. 05 TEST-MESSAGE PIC X(100). 01 TEST-DATA. 05 PRINCIPAL PIC 9(7)V99. 05 RATE PIC 9(2)V9(6). 05 TERM PIC 9(2). 05 EXPECTED-INTEREST PIC 9(7)V99. 05 ACTUAL-INTEREST PIC 9(7)V99. PROCEDURE DIVISION. TEST-MAIN. PERFORM SETUP-TEST-CASE PERFORM RUN-TEST-CASES UNITTEST FINISH-TESTS. STOP RUN. SETUP-TEST-CASE. UNITTEST INITIALIZE. RUN-TEST-CASES. * Test case 1: Simple interest calculation MOVE "CALC-SIMPLE-INTEREST-TEST-1" TO TEST-CASE-NAME UNITTEST START-TEST USING TEST-CASE-NAME MOVE 1000.00 TO PRINCIPAL MOVE 0.05 TO RATE MOVE 1 TO TERM MOVE 50.00 TO EXPECTED-INTEREST CALL 'CALC-INTEREST' USING PRINCIPAL, RATE, TERM, ACTUAL-INTEREST UNITTEST ASSERT-EQUALS EXPECTED-INTEREST ACTUAL-INTEREST UNITTEST END-TEST. * Test case 2: Zero principal MOVE "CALC-SIMPLE-INTEREST-TEST-2" TO TEST-CASE-NAME UNITTEST START-TEST USING TEST-CASE-NAME MOVE 0 TO PRINCIPAL MOVE 0.05 TO RATE MOVE 1 TO TERM MOVE 0 TO EXPECTED-INTEREST CALL 'CALC-INTEREST' USING PRINCIPAL, RATE, TERM, ACTUAL-INTEREST UNITTEST ASSERT-EQUALS EXPECTED-INTEREST ACTUAL-INTEREST UNITTEST END-TEST.

Best Practices for COBOL Unit Testing

  • Design for Testability: Structure code with clear interfaces and minimal dependencies
  • Test Data Independence: Don't rely on production data for unit tests
  • Isolate Logic: Separate business logic from I/O operations where possible
  • Boundary Conditions: Test edge cases and boundary values thoroughly
  • Negative Testing: Verify correct handling of invalid inputs and error conditions
  • Automation: Automate unit tests to run as part of the build process
  • Coverage Metrics: Track which parts of the code are being tested

Test Data Generation

Effective testing requires appropriate test data that covers various scenarios, boundary conditions, and error cases. Creating comprehensive test data is particularly important for COBOL applications that often process large volumes of records with complex business rules.

Test Data Requirements

Well-designed test data should meet these criteria:

  • Representative: Resembles real-world data in structure and content
  • Comprehensive: Covers all possible input combinations and paths
  • Controlled: Produces predictable and verifiable results
  • Maintainable: Can be updated as the application evolves
  • Secure: Does not contain sensitive production information
  • Reusable: Can be used across multiple test cycles

Manual Test Data Creation

For smaller tests or specialized cases, manually created test data can be effective:

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
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
* Example of a COBOL program to generate test data IDENTIFICATION DIVISION. PROGRAM-ID. TESTGEN. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT TEST-FILE ASSIGN TO TESTOUT ORGANIZATION IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD TEST-FILE RECORDING MODE IS F RECORD CONTAINS 100 CHARACTERS. 01 TEST-RECORD. 05 CUSTOMER-ID PIC X(10). 05 CUSTOMER-NAME PIC X(30). 05 TRANSACTION-AMT PIC 9(9)V99. 05 TRANSACTION-DATE PIC X(8). 05 TRANSACTION-TYPE PIC X. 05 FILLER PIC X(40). WORKING-STORAGE SECTION. 01 COUNTERS. 05 RECORD-COUNT PIC 9(5) VALUE ZERO. 05 IDX PIC 9(5) VALUE ZERO. 01 TEST-DATA-VALUES. 05 TRANS-TYPES PIC X(5) VALUE "CDPRA". 05 TRANS-TYPE-COUNT PIC 9 VALUE 5. PROCEDURE DIVISION. MAIN-PARAGRAPH. OPEN OUTPUT TEST-FILE * Generate standard test cases PERFORM GENERATE-NORMAL-CASES * Generate boundary condition test cases PERFORM GENERATE-BOUNDARY-CASES * Generate error condition test cases PERFORM GENERATE-ERROR-CASES CLOSE TEST-FILE DISPLAY "Generated " RECORD-COUNT " test records" STOP RUN. GENERATE-NORMAL-CASES. * Regular transaction with positive amount MOVE "0000000001" TO CUSTOMER-ID MOVE "JOHN SMITH" TO CUSTOMER-NAME MOVE 1250.95 TO TRANSACTION-AMT MOVE "20230615" TO TRANSACTION-DATE MOVE "C" TO TRANSACTION-TYPE PERFORM WRITE-TEST-RECORD * Regular transaction with zero amount MOVE "0000000002" TO CUSTOMER-ID MOVE "JANE DOE" TO CUSTOMER-NAME MOVE ZERO TO TRANSACTION-AMT MOVE "20230616" TO TRANSACTION-DATE MOVE "P" TO TRANSACTION-TYPE PERFORM WRITE-TEST-RECORD. GENERATE-BOUNDARY-CASES. * Maximum transaction amount MOVE "0000000003" TO CUSTOMER-ID MOVE "BOUNDARY TEST MAX" TO CUSTOMER-NAME MOVE 999999999.99 TO TRANSACTION-AMT MOVE "20230617" TO TRANSACTION-DATE MOVE "D" TO TRANSACTION-TYPE PERFORM WRITE-TEST-RECORD * Minimum valid date MOVE "0000000004" TO CUSTOMER-ID MOVE "BOUNDARY TEST MIN DATE" TO CUSTOMER-NAME MOVE 100.00 TO TRANSACTION-AMT MOVE "19000101" TO TRANSACTION-DATE MOVE "R" TO TRANSACTION-TYPE PERFORM WRITE-TEST-RECORD. GENERATE-ERROR-CASES. * Invalid transaction type MOVE "0000000005" TO CUSTOMER-ID MOVE "ERROR TEST INVALID TYPE" TO CUSTOMER-NAME MOVE 100.00 TO TRANSACTION-AMT MOVE "20230618" TO TRANSACTION-DATE MOVE "X" TO TRANSACTION-TYPE PERFORM WRITE-TEST-RECORD * Invalid date format MOVE "0000000006" TO CUSTOMER-ID MOVE "ERROR TEST INVALID DATE" TO CUSTOMER-NAME MOVE 100.00 TO TRANSACTION-AMT MOVE "20231350" TO TRANSACTION-DATE MOVE "C" TO TRANSACTION-TYPE PERFORM WRITE-TEST-RECORD. WRITE-TEST-RECORD. WRITE TEST-RECORD ADD 1 TO RECORD-COUNT.

Generating Test Data with Utilities

Mainframe utilities can be used to generate or manipulate test data efficiently:

  • DFSORT/ICETOOL: For sorting, merging, copying, and transforming data
  • IDCAMS: For creating and manipulating VSAM files
  • File-AID: Commercial tool for file manipulation and test data creation
  • DB2 Utilities: For database-related test data
jcl
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
32
33
34
35
36
//GENSORT JOB (ACCT),'TEST DATA GEN',CLASS=A,MSGCLASS=X //STEP1 EXEC PGM=SORT //SORTIN DD DUMMY //SORTOUT DD DSN=TEST.CUSTOMER.DATA, // DISP=(NEW,CATLG), // SPACE=(CYL,(1,1)), // DCB=(RECFM=FB,LRECL=100,BLKSIZE=0) //SYSIN DD * OPTION COPY OUTFIL REMOVECC, BLKCCH=100, IFTHEN=(WHEN=INIT, BUILD=(1:C'0000000001', 11:C'JOHN SMITH ', 41:C'123 MAIN ST ', 71:C'19760523', 79:C'A', 80:C'0000100000', 90:C' ')), IFTHEN=(WHEN=INIT, BUILD=(1:C'0000000002', 11:C'JANE DOE ', 41:C'456 OAK AVE ', 71:C'19820617', 79:C'B', 80:C'0000250000', 90:C' ')), IFTHEN=(WHEN=INIT, BUILD=(1:C'0000000003', 11:C'ALICE JOHNSON ', 41:C'789 PINE BLVD ', 71:C'19900712', 79:C'C', 80:C'0000075000', 90:C' ')) /*

This JCL example uses DFSORT to generate test customer records with different values.

Production Data Subsetting and Masking

Using production data for testing can provide realistic scenarios but requires careful handling:

  • Data Subsetting: Extract a representative sample from production
  • Data Masking: Replace sensitive information while preserving data characteristics
  • Anonymization: Modify data to prevent identification of individuals
  • Synthetic Data Generation: Create artificial data that resembles production patterns
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
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
* Example of a simple data masking program IDENTIFICATION DIVISION. PROGRAM-ID. DATAMASK. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT PROD-FILE ASSIGN TO PRODIN ORGANIZATION IS SEQUENTIAL. SELECT MASKED-FILE ASSIGN TO MASKOUT ORGANIZATION IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD PROD-FILE RECORDING MODE IS F RECORD CONTAINS 100 CHARACTERS. 01 PROD-RECORD. 05 PR-CUSTOMER-ID PIC X(10). 05 PR-CUSTOMER-NAME PIC X(30). 05 PR-SSN PIC X(9). 05 PR-BIRTH-DATE PIC X(8). 05 PR-ACCOUNT-NUM PIC X(16). 05 PR-BALANCE PIC 9(9)V99. 05 PR-FILLER PIC X(14). FD MASKED-FILE RECORDING MODE IS F RECORD CONTAINS 100 CHARACTERS. 01 MASKED-RECORD. 05 MR-CUSTOMER-ID PIC X(10). 05 MR-CUSTOMER-NAME PIC X(30). 05 MR-SSN PIC X(9). 05 MR-BIRTH-DATE PIC X(8). 05 MR-ACCOUNT-NUM PIC X(16). 05 MR-BALANCE PIC 9(9)V99. 05 MR-FILLER PIC X(14). WORKING-STORAGE SECTION. 01 FILE-STATUS. 05 PROD-EOF PIC X VALUE 'N'. 88 END-OF-PROD-FILE VALUE 'Y'. PROCEDURE DIVISION. MAIN-PARAGRAPH. OPEN INPUT PROD-FILE OPEN OUTPUT MASKED-FILE PERFORM UNTIL END-OF-PROD-FILE READ PROD-FILE AT END SET END-OF-PROD-FILE TO TRUE NOT AT END PERFORM PROCESS-RECORD END-READ END-PERFORM CLOSE PROD-FILE CLOSE MASKED-FILE STOP RUN. PROCESS-RECORD. * Copy the record structure MOVE PROD-RECORD TO MASKED-RECORD * Mask sensitive data PERFORM MASK-SSN PERFORM MASK-NAME PERFORM MASK-ACCOUNT-NUMBER PERFORM ADJUST-BALANCE WRITE MASKED-RECORD. MASK-SSN. * Replace all but last 4 digits with X's STRING "XXXXX" DELIMITED BY SIZE PR-SSN(6:4) DELIMITED BY SIZE INTO MR-SSN. MASK-NAME. * Replace real names with generic names EVALUATE PR-CUSTOMER-ID(10:1) WHEN "0" MOVE "TEST USER ZERO " TO MR-CUSTOMER-NAME WHEN "1" MOVE "TEST USER ONE " TO MR-CUSTOMER-NAME WHEN "2" MOVE "TEST USER TWO " TO MR-CUSTOMER-NAME WHEN "3" MOVE "TEST USER THREE " TO MR-CUSTOMER-NAME WHEN "4" MOVE "TEST USER FOUR " TO MR-CUSTOMER-NAME WHEN "5" MOVE "TEST USER FIVE " TO MR-CUSTOMER-NAME WHEN "6" MOVE "TEST USER SIX " TO MR-CUSTOMER-NAME WHEN "7" MOVE "TEST USER SEVEN " TO MR-CUSTOMER-NAME WHEN "8" MOVE "TEST USER EIGHT " TO MR-CUSTOMER-NAME WHEN "9" MOVE "TEST USER NINE " TO MR-CUSTOMER-NAME END-EVALUATE. MASK-ACCOUNT-NUMBER. * Replace with fixed test account numbers + last 4 of original STRING "TESTACCT" DELIMITED BY SIZE PR-ACCOUNT-NUM(9:8) DELIMITED BY SIZE INTO MR-ACCOUNT-NUM. ADJUST-BALANCE. * Round balances to nearest 100 to help mask exact values COMPUTE MR-BALANCE = (PR-BALANCE / 100) * 100.

Data Criteria for Comprehensive Testing

Ensure your test data covers these critical areas:

Test CriteriaExamples for COBOL Programs
Boundary ValuesMaximum/minimum field values, zero values, one below/above limits
Data TypesNumeric, alphanumeric, packed decimal, binary, floating-point
Special CasesEmpty fields, non-printable characters, foreign languages, special symbols
Business ScenariosCommon transactions, historical cases, seasonal processing
Error ConditionsInvalid dates, out-of-range values, incorrect codes
Volume TestingEmpty files, single record, few records, maximum expected volume

Regression Testing Strategies

Regression testing ensures that modifications to a program don't break existing functionality. This is particularly important for COBOL systems that have evolved over decades and contain critical business logic.

Regression Testing Fundamentals

  • Baseline Establishment: Document existing functionality before changes
  • Test Case Repository: Maintain a comprehensive set of test cases
  • Automated Execution: Run tests consistently and efficiently
  • Results Comparison: Verify outputs match expected results
  • Impact Analysis: Identify which components need testing after a change

Regression Testing Approaches

ApproachWhen to UseImplementation in COBOL Environment
Full RegressionMajor releases, critical systemsRun all test cases with complete input data sets
Partial RegressionMinor changes, time constraintsTest modified modules and those impacted by changes
Risk-Based RegressionMixed criticality componentsFocus on high-risk areas, critical business functions
Smoke TestingRapid verification after buildsRun critical path tests to verify basic functionality
Delta TestingSpecific feature changesTest only what's changed using change impact analysis

Automating Regression Tests

Automated regression testing for COBOL can be implemented in several ways:

  • JCL Batch Streams: Create standardized job streams to run test cases
  • Comparison Utilities: Use utilities to compare output files with baselines
  • Test Harnesses: Develop or use specialized frameworks to execute tests
  • Commercial Tools: Leverage tools like Micro Focus Enterprise Test Server
  • CI/CD Integration: Include regression tests in automated build pipelines
jcl
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
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
//REGTEST JOB (ACCT),'REGRESSION TEST',CLASS=A,MSGCLASS=X //* //* AUTOMATED REGRESSION TEST FOR CUSTOMER BILLING SYSTEM //* //STEP01 EXEC PGM=CBILLMN //STEPLIB DD DSN=TEST.LOADLIB,DISP=SHR //CUSTMAST DD DSN=TEST.REGRESSION.CUSTMAST,DISP=SHR //BILLHIST DD DSN=TEST.REGRESSION.BILLHIST,DISP=SHR //NEWTRANS DD DSN=TEST.REGRESSION.NEWTRANS,DISP=SHR //BILLOUT DD DSN=TEST.REGRESSION.ACTUAL.BILLOUT, // DISP=(NEW,CATLG,DELETE), // SPACE=(CYL,(1,1)), // DCB=(RECFM=FB,LRECL=100,BLKSIZE=0) //ERRLOG DD DSN=TEST.REGRESSION.ACTUAL.ERRLOG, // DISP=(NEW,CATLG,DELETE), // SPACE=(CYL,(1,1)), // DCB=(RECFM=FB,LRECL=80,BLKSIZE=0) //SYSOUT DD SYSOUT=* //* //STEP02 EXEC PGM=IDCAMS //SYSPRINT DD SYSOUT=* //SYSIN DD * COMPARE - DATA(TEST.REGRESSION.ACTUAL.BILLOUT) - WITH(TEST.REGRESSION.BASELINE.BILLOUT) - EXITCK(10) IF LASTCC > 0 THEN - DO SET MAXCC = 8 WRITE 'REGRESSION TEST FAILED: BILLOUT FILE MISMATCH' END COMPARE - DATA(TEST.REGRESSION.ACTUAL.ERRLOG) - WITH(TEST.REGRESSION.BASELINE.ERRLOG) - EXITCK(10) IF LASTCC > 0 THEN - DO SET MAXCC = 8 WRITE 'REGRESSION TEST FAILED: ERRLOG FILE MISMATCH' END /* //* //STEP03 EXEC PGM=TESTRPT,COND=(8,LT) //STEPLIB DD DSN=TEST.LOADLIB,DISP=SHR //DIFFILE DD DSN=TEST.REGRESSION.DIFFS,DISP=SHR //RESULTS DD SYSOUT=* //*

This JCL example runs a program with regression test data, compares outputs to baselines, and generates a report of differences if any are found.

Managing Baseline Expectations

Maintaining regression test baselines requires careful management:

  • Baseline Versioning: Keep historical versions of baseline output files
  • Expected Changes: Document when program changes are intended to modify outputs
  • Baseline Updates: Establish a process for reviewing and approving baseline changes
  • Partial Comparisons: For date/time fields or other volatile data, exclude from comparisons
  • Documentation: Maintain clear records of what each test verifies
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
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
* Example of a COBOL program to selectively compare files IDENTIFICATION DIVISION. PROGRAM-ID. SELCOMP. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT BASELINE-FILE ASSIGN TO BASELIN ORGANIZATION IS SEQUENTIAL. SELECT ACTUAL-FILE ASSIGN TO ACTUALIN ORGANIZATION IS SEQUENTIAL. SELECT DIFF-FILE ASSIGN TO DIFFOUT ORGANIZATION IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD BASELINE-FILE RECORDING MODE IS F RECORD CONTAINS 100 CHARACTERS. 01 BASELINE-RECORD. 05 BR-CUSTOMER-ID PIC X(10). 05 BR-TRANSACTION-TYPE PIC X. 05 BR-AMOUNT PIC 9(9)V99. 05 BR-DATE PIC X(8). 05 BR-TIME PIC X(8). 05 BR-RESULT-CODE PIC X(2). 05 BR-RESULT-DESC PIC X(50). 05 BR-FILLER PIC X(10). FD ACTUAL-FILE RECORDING MODE IS F RECORD CONTAINS 100 CHARACTERS. 01 ACTUAL-RECORD. 05 AR-CUSTOMER-ID PIC X(10). 05 AR-TRANSACTION-TYPE PIC X. 05 AR-AMOUNT PIC 9(9)V99. 05 AR-DATE PIC X(8). 05 AR-TIME PIC X(8). 05 AR-RESULT-CODE PIC X(2). 05 AR-RESULT-DESC PIC X(50). 05 AR-FILLER PIC X(10). FD DIFF-FILE RECORDING MODE IS F RECORD CONTAINS 200 CHARACTERS. 01 DIFF-RECORD PIC X(200). WORKING-STORAGE SECTION. 01 FILE-STATUS. 05 BASELINE-EOF PIC X VALUE 'N'. 88 END-OF-BASELINE VALUE 'Y'. 05 ACTUAL-EOF PIC X VALUE 'N'. 88 END-OF-ACTUAL VALUE 'Y'. 01 COUNTERS. 05 RECORDS-COMPARED PIC 9(7) VALUE ZERO. 05 RECORDS-DIFFERENT PIC 9(7) VALUE ZERO. 01 COMPARISON-RESULT PIC X. 88 RECORDS-MATCH VALUE 'Y'. 88 RECORDS-DIFFER VALUE 'N'. 01 DIFF-LINE. 05 DL-HEADER PIC X(30). 05 DL-BASELINE PIC X(80). 05 FILLER PIC X(10) VALUE SPACES. 05 DL-ACTUAL PIC X(80). PROCEDURE DIVISION. MAIN-PARAGRAPH. OPEN INPUT BASELINE-FILE OPEN INPUT ACTUAL-FILE OPEN OUTPUT DIFF-FILE PERFORM UNTIL END-OF-BASELINE OR END-OF-ACTUAL READ BASELINE-FILE AT END SET END-OF-BASELINE TO TRUE END-READ IF NOT END-OF-BASELINE READ ACTUAL-FILE AT END SET END-OF-ACTUAL TO TRUE END-READ IF NOT END-OF-ACTUAL ADD 1 TO RECORDS-COMPARED PERFORM COMPARE-RECORDS IF NOT RECORDS-MATCH ADD 1 TO RECORDS-DIFFERENT PERFORM WRITE-DIFF-RECORD END-IF END-IF END-IF END-PERFORM CLOSE BASELINE-FILE CLOSE ACTUAL-FILE CLOSE DIFF-FILE DISPLAY "Records compared: " RECORDS-COMPARED DISPLAY "Differences found: " RECORDS-DIFFERENT STOP RUN. COMPARE-RECORDS. * Compare records, ignoring date and time fields SET RECORDS-MATCH TO TRUE IF BR-CUSTOMER-ID NOT = AR-CUSTOMER-ID OR BR-TRANSACTION-TYPE NOT = AR-TRANSACTION-TYPE OR BR-AMOUNT NOT = AR-AMOUNT OR BR-RESULT-CODE NOT = AR-RESULT-CODE OR BR-RESULT-DESC NOT = AR-RESULT-DESC SET RECORDS-DIFFER TO TRUE END-IF. WRITE-DIFF-RECORD. MOVE "RECORD #:" TO DL-HEADER MOVE BASELINE-RECORD TO DL-BASELINE MOVE ACTUAL-RECORD TO DL-ACTUAL MOVE DIFF-LINE TO DIFF-RECORD WRITE DIFF-RECORD IF BR-CUSTOMER-ID NOT = AR-CUSTOMER-ID MOVE "CUSTOMER ID DIFFERS:" TO DL-HEADER MOVE BR-CUSTOMER-ID TO DL-BASELINE MOVE AR-CUSTOMER-ID TO DL-ACTUAL MOVE DIFF-LINE TO DIFF-RECORD WRITE DIFF-RECORD END-IF * Similar comparisons for other fields .

Impact Analysis for Targeted Regression

For large systems, identifying which components need regression testing is crucial:

  • Call Trees: Analyze program call hierarchies to identify affected modules
  • Data Dependency: Map data flows to determine impacted components
  • Analysis Tools: Use tools like IBM Application Discovery to identify dependencies
  • Traceability Matrix: Maintain mapping between requirements, code, and test cases
  • Change Classification: Categorize changes by impact level to guide testing scope