MainframeMaster

COBOL Tutorial

COBOL START and END-START Statements - Quick Reference

The START and END-START statements in COBOL are used to position the file pointer within indexed and relative files. START establishes a position based on key values, while END-START marks the end of the START statement scope. These statements enable efficient file positioning and retrieval operations.

Primary Use

Position within indexed and relative files

Division

PROCEDURE DIVISION

File Types

Indexed and Relative

Status

Required for positioning

Overview

The START statement is used to position the file pointer at a specific record within indexed and relative files based on key values. It does not retrieve data but establishes a position from which subsequent READ statements can retrieve records. The END-START statement marks the end of the START statement scope and is used in structured programming to clearly define the statement boundaries.

Syntax

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
START file-name [KEY IS {EQUAL TO | GREATER THAN | NOT LESS THAN} data-name] [INVALID KEY imperative-statement] [NOT INVALID KEY imperative-statement] END-START * Examples: START CUSTOMER-FILE KEY IS EQUAL TO WS-CUSTOMER-KEY INVALID KEY DISPLAY "Customer not found" END-START START PRODUCT-FILE KEY IS GREATER THAN WS-PRODUCT-KEY INVALID KEY PERFORM ERROR-HANDLING NOT INVALID KEY PERFORM PROCESS-RECORDS END-START

Practical Examples

Basic START Statement Usage

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
* Basic START statement example IDENTIFICATION DIVISION. PROGRAM-ID. START-EXAMPLE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT CUSTOMER-FILE ASSIGN TO "CUSTOMER.DAT" ORGANIZATION IS INDEXED ACCESS MODE IS SEQUENTIAL RECORD KEY IS CUSTOMER-ID FILE STATUS IS WS-FILE-STATUS. DATA DIVISION. FILE SECTION. FD CUSTOMER-FILE. 01 CUSTOMER-RECORD. 05 CUSTOMER-ID PIC 9(5). 05 CUSTOMER-NAME PIC X(30). 05 CUSTOMER-ADDRESS PIC X(50). WORKING-STORAGE SECTION. 01 WS-FILE-STATUS PIC XX. 01 WS-CUSTOMER-KEY PIC 9(5) VALUE 10001. 01 WS-RECORD-FOUND PIC X(1) VALUE 'N'. PROCEDURE DIVISION. MAIN-LOGIC. DISPLAY "START Statement Example" * Open the file OPEN INPUT CUSTOMER-FILE * Check file status IF WS-FILE-STATUS NOT = "00" DISPLAY "Error opening file: " WS-FILE-STATUS STOP RUN END-IF * Use START to position at specific customer START CUSTOMER-FILE KEY IS EQUAL TO WS-CUSTOMER-KEY INVALID KEY DISPLAY "Customer " WS-CUSTOMER-KEY " not found" MOVE 'N' TO WS-RECORD-FOUND NOT INVALID KEY MOVE 'Y' TO WS-RECORD-FOUND END-START * If record found, read and display it IF WS-RECORD-FOUND = 'Y' READ CUSTOMER-FILE AT END DISPLAY "End of file reached" NOT AT END DISPLAY "Customer ID: " CUSTOMER-ID DISPLAY "Customer Name: " CUSTOMER-NAME DISPLAY "Customer Address: " CUSTOMER-ADDRESS END-READ END-IF * Close the file CLOSE CUSTOMER-FILE STOP RUN.

Explanation: This example demonstrates basic usage of the START statement. The program opens an indexed customer file, uses START to position at a specific customer ID, and then reads the record if found. The START statement positions the file pointer at the record with the specified key, and the subsequent READ retrieves that record. Error handling is included for cases where the key is not found.

START with Different Key Conditions

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
* START with different key conditions example IDENTIFICATION DIVISION. PROGRAM-ID. START-CONDITIONS-EXAMPLE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT PRODUCT-FILE ASSIGN TO "PRODUCT.DAT" ORGANIZATION IS INDEXED ACCESS MODE IS SEQUENTIAL RECORD KEY IS PRODUCT-CODE FILE STATUS IS WS-FILE-STATUS. DATA DIVISION. FILE SECTION. FD PRODUCT-FILE. 01 PRODUCT-RECORD. 05 PRODUCT-CODE PIC X(10). 05 PRODUCT-NAME PIC X(30). 05 PRODUCT-PRICE PIC 9(5)V99. WORKING-STORAGE SECTION. 01 WS-FILE-STATUS PIC XX. 01 WS-SEARCH-KEY PIC X(10). 01 WS-RECORD-COUNT PIC 9(3) VALUE ZERO. PROCEDURE DIVISION. MAIN-LOGIC. DISPLAY "START with Different Key Conditions" * Open the file OPEN INPUT PRODUCT-FILE * Example 1: START with EQUAL TO MOVE "PROD001" TO WS-SEARCH-KEY DISPLAY "Searching for exact match: " WS-SEARCH-KEY START PRODUCT-FILE KEY IS EQUAL TO WS-SEARCH-KEY INVALID KEY DISPLAY "Exact match not found" NOT INVALID KEY DISPLAY "Exact match found" PERFORM READ-AND-DISPLAY END-START * Example 2: START with GREATER THAN MOVE "PROD005" TO WS-SEARCH-KEY DISPLAY "Searching for records greater than: " WS-SEARCH-KEY START PRODUCT-FILE KEY IS GREATER THAN WS-SEARCH-KEY INVALID KEY DISPLAY "No records greater than key" NOT INVALID KEY DISPLAY "Records greater than key found" PERFORM READ-MULTIPLE-RECORDS END-START * Example 3: START with NOT LESS THAN MOVE "PROD010" TO WS-SEARCH-KEY DISPLAY "Searching for records not less than: " WS-SEARCH-KEY START PRODUCT-FILE KEY IS NOT LESS THAN WS-SEARCH-KEY INVALID KEY DISPLAY "No records found" NOT INVALID KEY DISPLAY "Records found starting from key" PERFORM READ-MULTIPLE-RECORDS END-START CLOSE PRODUCT-FILE STOP RUN. READ-AND-DISPLAY. READ PRODUCT-FILE AT END DISPLAY "End of file" NOT AT END DISPLAY "Product Code: " PRODUCT-CODE DISPLAY "Product Name: " PRODUCT-NAME DISPLAY "Product Price: " PRODUCT-PRICE END-READ. READ-MULTIPLE-RECORDS. MOVE 0 TO WS-RECORD-COUNT PERFORM UNTIL WS-RECORD-COUNT >= 5 READ PRODUCT-FILE AT END DISPLAY "End of file reached" EXIT PERFORM NOT AT END ADD 1 TO WS-RECORD-COUNT DISPLAY "Record " WS-RECORD-COUNT ": " PRODUCT-CODE " - " PRODUCT-NAME END-READ END-PERFORM.

Explanation: This example shows different key conditions that can be used with the START statement. EQUAL TO finds an exact match, GREATER THAN positions at the first record with a key greater than the specified value, and NOT LESS THAN positions at the first record with a key greater than or equal to the specified value. Each condition provides different positioning behavior for efficient file access patterns.

START with Error Handling

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
* START with comprehensive error handling example IDENTIFICATION DIVISION. PROGRAM-ID. START-ERROR-HANDLING. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT EMPLOYEE-FILE ASSIGN TO "EMPLOYEE.DAT" ORGANIZATION IS INDEXED ACCESS MODE IS SEQUENTIAL RECORD KEY IS EMPLOYEE-ID FILE STATUS IS WS-FILE-STATUS. DATA DIVISION. FILE SECTION. FD EMPLOYEE-FILE. 01 EMPLOYEE-RECORD. 05 EMPLOYEE-ID PIC 9(6). 05 EMPLOYEE-NAME PIC X(30). 05 EMPLOYEE-DEPT PIC X(20). WORKING-STORAGE SECTION. 01 WS-FILE-STATUS PIC XX. 01 WS-SEARCH-KEY PIC 9(6). 01 WS-ERROR-MESSAGE PIC X(50). 01 WS-PROCESSING-STATUS PIC X(1) VALUE 'C'. * C = Continue, S = Stop, R = Retry PROCEDURE DIVISION. MAIN-LOGIC. DISPLAY "START with Error Handling Example" * Open the file OPEN INPUT EMPLOYEE-FILE * Check file status IF WS-FILE-STATUS NOT = "00" PERFORM HANDLE-FILE-ERROR STOP RUN END-IF * Get search key from user DISPLAY "Enter Employee ID to search: " ACCEPT WS-SEARCH-KEY * Use START with error handling PERFORM SEARCH-EMPLOYEE CLOSE EMPLOYEE-FILE STOP RUN. SEARCH-EMPLOYEE. START EMPLOYEE-FILE KEY IS EQUAL TO WS-SEARCH-KEY INVALID KEY PERFORM HANDLE-INVALID-KEY NOT INVALID KEY PERFORM PROCESS-EMPLOYEE-RECORD END-START. HANDLE-INVALID-KEY. * Check specific file status for different error conditions EVALUATE WS-FILE-STATUS WHEN "23" MOVE "Employee not found" TO WS-ERROR-MESSAGE DISPLAY "Error: " WS-ERROR-MESSAGE WHEN "24" MOVE "Key out of range" TO WS-ERROR-MESSAGE DISPLAY "Error: " WS-ERROR-MESSAGE WHEN "30" MOVE "File not found" TO WS-ERROR-MESSAGE DISPLAY "Error: " WS-ERROR-MESSAGE WHEN "35" MOVE "File not open" TO WS-ERROR-MESSAGE DISPLAY "Error: " WS-ERROR-MESSAGE WHEN OTHER MOVE "Unknown file error" TO WS-ERROR-MESSAGE DISPLAY "Error: " WS-ERROR-MESSAGE " Status: " WS-FILE-STATUS END-EVALUATE. PROCESS-EMPLOYEE-RECORD. READ EMPLOYEE-FILE AT END DISPLAY "Unexpected end of file" NOT AT END DISPLAY "Employee found:" DISPLAY "ID: " EMPLOYEE-ID DISPLAY "Name: " EMPLOYEE-NAME DISPLAY "Department: " EMPLOYEE-DEPT END-READ. HANDLE-FILE-ERROR. DISPLAY "File error occurred: " WS-FILE-STATUS DISPLAY "Cannot continue processing".

Explanation: This example demonstrates comprehensive error handling with the START statement. The program checks file status after each operation and handles different error conditions appropriately. File status "23" indicates no record found, "24" indicates key out of range, and other status codes indicate different file-related errors. This ensures robust error handling and provides meaningful feedback to users when operations fail.

START for Range Processing

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
* START for range processing example IDENTIFICATION DIVISION. PROGRAM-ID. START-RANGE-PROCESSING. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT ORDER-FILE ASSIGN TO "ORDER.DAT" ORGANIZATION IS INDEXED ACCESS MODE IS SEQUENTIAL RECORD KEY IS ORDER-NUMBER FILE STATUS IS WS-FILE-STATUS. DATA DIVISION. FILE SECTION. FD ORDER-FILE. 01 ORDER-RECORD. 05 ORDER-NUMBER PIC 9(8). 05 CUSTOMER-ID PIC 9(5). 05 ORDER-DATE PIC 9(8). 05 ORDER-AMOUNT PIC 9(7)V99. WORKING-STORAGE SECTION. 01 WS-FILE-STATUS PIC XX. 01 WS-START-RANGE PIC 9(8) VALUE 10000000. 01 WS-END-RANGE PIC 9(8) VALUE 10000999. 01 WS-CURRENT-KEY PIC 9(8). 01 WS-RECORD-COUNT PIC 9(5) VALUE ZERO. 01 WS-TOTAL-AMOUNT PIC 9(9)V99 VALUE ZERO. PROCEDURE DIVISION. MAIN-LOGIC. DISPLAY "START for Range Processing Example" DISPLAY "Processing orders from " WS-START-RANGE " to " WS-END-RANGE * Open the file OPEN INPUT ORDER-FILE * Position at start of range MOVE WS-START-RANGE TO WS-CURRENT-KEY START ORDER-FILE KEY IS GREATER THAN OR EQUAL TO WS-CURRENT-KEY INVALID KEY DISPLAY "No orders found in range" GO TO END-PROCESSING NOT INVALID KEY DISPLAY "Starting range processing" END-START * Process records in range PERFORM PROCESS-RANGE-RECORDS END-PROCESSING. CLOSE ORDER-FILE DISPLAY "Range processing completed" DISPLAY "Total records processed: " WS-RECORD-COUNT DISPLAY "Total amount: " WS-TOTAL-AMOUNT STOP RUN. PROCESS-RANGE-RECORDS. PERFORM UNTIL WS-CURRENT-KEY > WS-END-RANGE READ ORDER-FILE AT END DISPLAY "End of file reached" EXIT PERFORM NOT AT END * Check if record is within range IF ORDER-NUMBER <= WS-END-RANGE ADD 1 TO WS-RECORD-COUNT ADD ORDER-AMOUNT TO WS-TOTAL-AMOUNT DISPLAY "Order: " ORDER-NUMBER " Amount: " ORDER-AMOUNT MOVE ORDER-NUMBER TO WS-CURRENT-KEY ELSE EXIT PERFORM END-IF END-READ END-PERFORM.

Explanation: This example shows how to use START for range processing. The program positions at the beginning of a range of order numbers and then processes all records within that range. This is useful for batch processing, reporting, and data analysis where you need to process records within specific key ranges. The START statement efficiently positions the file pointer, and subsequent READ statements retrieve records in sequence.

Best Practices and Considerations

Important Considerations

  • START only works with indexed and relative files
  • Always check file status after START operations
  • Use appropriate key conditions for positioning
  • Handle INVALID KEY conditions properly
  • Ensure file is open before using START

Advantages

  • Efficient file positioning
  • Supports range processing
  • Enables selective record access
  • Improves file access performance
  • Provides flexible key-based positioning

Limitations

  • Only works with indexed and relative files
  • Requires proper error handling
  • May not find records if key doesn't exist
  • Performance depends on index structure
  • Requires understanding of file organization

Best Practices

  • • Always check file status after START operations
  • • Use appropriate key conditions for your needs
  • • Handle INVALID KEY conditions properly
  • • Ensure files are properly opened before START
  • • Use START for efficient range processing

Test Your Knowledge

1. What is the primary purpose of the START statement in COBOL?

  • To begin program execution
  • To position within indexed and relative files
  • To start a new file
  • To initialize variables

2. Which file organizations support the START statement?

  • Sequential files only
  • Indexed and relative files
  • All file types
  • VSAM files only

3. What is the relationship between START and READ statements?

  • They are the same thing
  • START positions the file, READ retrieves the record
  • START reads the record, READ positions the file
  • They cannot be used together

4. What happens if a START statement fails to find a matching record?

  • The program crashes
  • The file status is set to indicate the condition
  • The program continues normally
  • The file is automatically closed

5. Can the START statement be used with sequential files?

  • Yes, always
  • No, only with indexed and relative files
  • Only in some implementations
  • Only with VSAM files