MainframeMaster

COBOL Tutorial

COBOL GO Statement

The GO statement represents a fundamental but controversial program control transfer mechanism within COBOL programming environments, serving as an unconditional branching instruction that immediately transfers execution control to a specified paragraph or section without providing return capability. This statement embodies the principles of direct program flow manipulation by enabling immediate control transfer operations, supporting legacy programming patterns, and facilitating specific control flow requirements while presenting significant challenges to structured programming practices and code maintainability in modern enterprise applications that prioritize readable, maintainable, and debuggable code architectures with predictable execution patterns and clear program logic flow.

Syntax and Usage

GO Statement Syntax
cobol
1
2
3
4
5
6
7
GO TO paragraph-name GO TO section-name *> Examples: GO TO ERROR-HANDLING GO TO CLEANUP-SECTION GO TO END-PROCESSING
Control Transfer
Unconditional
Legacy Pattern

Basic GO Examples (Legacy 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
IDENTIFICATION DIVISION. PROGRAM-ID. GO-STATEMENT-EXAMPLES. DATA DIVISION. WORKING-STORAGE SECTION. 01 PROCESS-CODE PIC X. 88 NORMAL-PROCESSING VALUE 'N'. 88 ERROR-PROCESSING VALUE 'E'. 88 SPECIAL-PROCESSING VALUE 'S'. 01 ERROR-FLAG PIC X VALUE 'N'. 01 RECORD-COUNT PIC 9(5) VALUE 0. PROCEDURE DIVISION. MAIN-PROCESSING. DISPLAY 'Starting application...' *> Legacy pattern using GO TO (NOT RECOMMENDED) ACCEPT PROCESS-CODE IF NORMAL-PROCESSING GO TO NORMAL-PROCESS ELSE IF ERROR-PROCESSING GO TO ERROR-PROCESS ELSE IF SPECIAL-PROCESSING GO TO SPECIAL-PROCESS ELSE GO TO INVALID-INPUT END-IF END-IF END-IF. NORMAL-PROCESS. DISPLAY 'Processing normal operations...' ADD 1 TO RECORD-COUNT IF RECORD-COUNT > 1000 GO TO CAPACITY-WARNING END-IF DISPLAY 'Normal processing completed' GO TO END-PROCESSING. ERROR-PROCESS. DISPLAY 'Processing error conditions...' MOVE 'Y' TO ERROR-FLAG GO TO ERROR-CLEANUP. SPECIAL-PROCESS. DISPLAY 'Processing special operations...' PERFORM SPECIAL-VALIDATION IF ERROR-FLAG = 'Y' GO TO ERROR-CLEANUP END-IF GO TO END-PROCESSING. CAPACITY-WARNING. DISPLAY 'Warning: Approaching capacity limit' GO TO END-PROCESSING. INVALID-INPUT. DISPLAY 'Error: Invalid process code entered' MOVE 'Y' TO ERROR-FLAG GO TO ERROR-CLEANUP. ERROR-CLEANUP. DISPLAY 'Performing error cleanup...' DISPLAY 'Error flag status: ' ERROR-FLAG GO TO END-PROCESSING. SPECIAL-VALIDATION. *> Simulate validation that might set error flag IF RECORD-COUNT < 0 MOVE 'Y' TO ERROR-FLAG END-IF. END-PROCESSING. DISPLAY 'Application ending...' DISPLAY 'Final record count: ' RECORD-COUNT STOP RUN.

Problems with GO TO

Maintainability Issues
  • • Difficult to follow program logic
  • • Hard to debug and trace execution
  • • Creates "spaghetti code" patterns
  • • Complicates code modifications
Structural Problems
  • • Breaks structured programming rules
  • • No automatic return mechanism
  • • Unpredictable control flow
  • • Difficult testing and validation

Interactive Tutorial

Hands-On Exercise: Refactoring GO TO
Learn to replace GO TO with structured programming constructs

Exercise 1: Before - Using GO TO (Poor Practice)

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
PROCEDURE DIVISION. MAIN-LOGIC. ACCEPT USER-INPUT IF USER-INPUT = 'A' GO TO PROCESS-A ELSE IF USER-INPUT = 'B' GO TO PROCESS-B ELSE GO TO ERROR-HANDLER END-IF END-IF. PROCESS-A. DISPLAY 'Processing option A' GO TO END-PROGRAM. PROCESS-B. DISPLAY 'Processing option B' GO TO END-PROGRAM. ERROR-HANDLER. DISPLAY 'Invalid input' GO TO END-PROGRAM. END-PROGRAM. STOP RUN.

Exercise 2: After - Structured Approach (Best Practice)

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
PROCEDURE DIVISION. MAIN-LOGIC. ACCEPT USER-INPUT EVALUATE USER-INPUT WHEN 'A' PERFORM PROCESS-A WHEN 'B' PERFORM PROCESS-B WHEN OTHER PERFORM ERROR-HANDLER END-EVALUATE STOP RUN. PROCESS-A. DISPLAY 'Processing option A'. PROCESS-B. DISPLAY 'Processing option B'. ERROR-HANDLER. DISPLAY 'Invalid input'.

Modern Alternatives to GO TO

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
IDENTIFICATION DIVISION. PROGRAM-ID. STRUCTURED-ALTERNATIVES. DATA DIVISION. WORKING-STORAGE SECTION. 01 OPERATION-CODE PIC X. 01 PROCESSING-COMPLETE PIC X VALUE 'N'. 01 ERROR-OCCURRED PIC X VALUE 'N'. PROCEDURE DIVISION. MAIN-PROCESSING. *> Modern structured approach instead of GO TO PERFORM INITIALIZATION PERFORM MAIN-LOOP UNTIL PROCESSING-COMPLETE = 'Y' PERFORM CLEANUP STOP RUN. INITIALIZATION. DISPLAY 'System initialization...' MOVE 'N' TO PROCESSING-COMPLETE MOVE 'N' TO ERROR-OCCURRED. MAIN-LOOP. ACCEPT OPERATION-CODE *> Using EVALUATE instead of multiple GO TO statements EVALUATE OPERATION-CODE WHEN '1' PERFORM DATA-ENTRY WHEN '2' PERFORM REPORT-GENERATION WHEN '3' PERFORM MAINTENANCE WHEN 'Q' MOVE 'Y' TO PROCESSING-COMPLETE WHEN OTHER PERFORM INVALID-OPTION END-EVALUATE *> Structured error handling instead of GO TO IF ERROR-OCCURRED = 'Y' PERFORM ERROR-RECOVERY MOVE 'N' TO ERROR-OCCURRED END-IF. DATA-ENTRY. DISPLAY 'Performing data entry operations...' *> Structured validation PERFORM VALIDATE-INPUT IF ERROR-OCCURRED = 'N' PERFORM SAVE-DATA END-IF. REPORT-GENERATION. DISPLAY 'Generating reports...' PERFORM CHECK-PREREQUISITES IF ERROR-OCCURRED = 'N' PERFORM CREATE-REPORT END-IF. MAINTENANCE. DISPLAY 'Performing maintenance...' PERFORM BACKUP-DATA PERFORM CLEANUP-TEMP-FILES. INVALID-OPTION. DISPLAY 'Invalid option selected' MOVE 'Y' TO ERROR-OCCURRED. VALIDATE-INPUT. *> Input validation logic CONTINUE. SAVE-DATA. *> Data saving logic CONTINUE. CHECK-PREREQUISITES. *> Prerequisite checking logic CONTINUE. CREATE-REPORT. *> Report creation logic CONTINUE. BACKUP-DATA. *> Backup logic CONTINUE. CLEANUP-TEMP-FILES. *> Cleanup logic CONTINUE. ERROR-RECOVERY. DISPLAY 'Performing error recovery...' *> Error recovery logic CONTINUE. CLEANUP. DISPLAY 'System cleanup completed'.

Best Practices

Knowledge Check

Test Your Understanding

Question 1: Basic Syntax

What's the syntax for an unconditional jump to a paragraph?

Answer: GO TO paragraph-name

Question 2: Modern Alternative

What structured construct should replace GO TO for conditional logic?

Answer: Use IF-THEN-ELSE for two-way conditions, EVALUATE for multi-way selection, and PERFORM for subroutine calls.

Question 3: Problems

Why is GO TO considered poor programming practice?

Answer: GO TO creates unstructured, hard-to-follow code that's difficult to debug, maintain, and understand. It breaks structured programming principles and can lead to "spaghetti code."

Refactoring Patterns

Legacy Pattern (Avoid)
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
MAIN-LOGIC. IF CONDITION-A GO TO PROCESS-A ELSE GO TO PROCESS-B END-IF. PROCESS-A. *> Processing A GO TO END-PROCESSING. PROCESS-B. *> Processing B GO TO END-PROCESSING. END-PROCESSING. STOP RUN.
Modern Pattern (Preferred)
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
MAIN-LOGIC. IF CONDITION-A PERFORM PROCESS-A ELSE PERFORM PROCESS-B END-IF STOP RUN. PROCESS-A. *> Processing A CONTINUE. PROCESS-B. *> Processing B CONTINUE.

Frequently Asked Questions