MainframeMaster

COBOL Tutorial

COBOL REWIND Statement - Quick Reference

Progress0 of 0 lessons

Overview

The REWIND statement is used to reposition a file to its beginning, allowing you to read the file from the start again without closing and reopening it. It is primarily used with sequential files for efficient file repositioning.

Purpose and Usage

  • File repositioning - Move file pointer to beginning
  • Efficient processing - Avoid close/open overhead
  • Multiple passes - Process same file multiple times
  • Error recovery - Restart processing after errors
  • Sequential access - Optimize sequential file operations

File Positioning Concept

File: [Record1] [Record2] [Record3] [Record4] [Record5]
After READ: [Record1] [Record2] [Record3] [Record4] [Record5]
↑ (current position)
After REWIND: [Record1] [Record2] [Record3] [Record4] [Record5]
↑ (back to beginning)

REWIND moves the file pointer back to the first record.

Syntax

The REWIND statement has a simple syntax and can be used with various file types.

Basic Syntax

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
* Basic REWIND syntax REWIND file-name * With error handling REWIND file-name ON EXCEPTION PERFORM ERROR-HANDLING END-REWIND * Complete example IDENTIFICATION DIVISION. PROGRAM-ID. REWIND-EXAMPLE. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT INPUT-FILE ASSIGN TO "DATA.TXT" ORGANIZATION IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD INPUT-FILE. 01 INPUT-RECORD PIC X(80). WORKING-STORAGE SECTION. 01 FILE-STATUS PIC XX. PROCEDURE DIVISION. MAIN-LOGIC. OPEN INPUT INPUT-FILE * Process file first time PERFORM PROCESS-FILE * Rewind to beginning REWIND INPUT-FILE * Process file second time PERFORM PROCESS-FILE CLOSE INPUT-FILE STOP RUN. PROCESS-FILE. READ INPUT-FILE AT END EXIT PARAGRAPH END-READ DISPLAY INPUT-RECORD GO TO PROCESS-FILE.

REWIND requires the file to be open and available for reading.

REWIND vs CLOSE/OPEN Comparison

MethodPerformanceUse Case
REWINDFastReposition to beginning
CLOSE/OPENSlowerChange file attributes
STARTMediumPosition to specific record

Practical Examples

These examples demonstrate how to use the REWIND statement effectively in different file processing scenarios.

Multiple Pass 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
IDENTIFICATION DIVISION. PROGRAM-ID. MULTI-PASS-PROCESSING. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT DATA-FILE ASSIGN TO "CUSTOMERS.DAT" ORGANIZATION IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD DATA-FILE. 01 CUSTOMER-RECORD. 05 CUST-ID PIC 9(6). 05 CUST-NAME PIC X(30). 05 CUST-BALANCE PIC 9(8)V99. WORKING-STORAGE SECTION. 01 RECORD-COUNT PIC 9(6) VALUE ZERO. 01 TOTAL-BALANCE PIC 9(10)V99 VALUE ZERO. 01 AVERAGE-BALANCE PIC 9(8)V99. PROCEDURE DIVISION. MAIN-LOGIC. OPEN INPUT DATA-FILE * First pass: Count records and sum balances PERFORM COUNT-AND-SUM * Calculate average IF RECORD-COUNT > 0 DIVIDE TOTAL-BALANCE BY RECORD-COUNT GIVING AVERAGE-BALANCE END-IF * Rewind for second pass REWIND DATA-FILE * Second pass: Display records above average PERFORM DISPLAY-ABOVE-AVERAGE CLOSE DATA-FILE STOP RUN. COUNT-AND-SUM. READ DATA-FILE AT END EXIT PARAGRAPH END-READ ADD 1 TO RECORD-COUNT ADD CUST-BALANCE TO TOTAL-BALANCE GO TO COUNT-AND-SUM. DISPLAY-ABOVE-AVERAGE. READ DATA-FILE AT END EXIT PARAGRAPH END-READ IF CUST-BALANCE > AVERAGE-BALANCE DISPLAY "High Balance: " CUST-NAME " - " CUST-BALANCE END-IF GO TO DISPLAY-ABOVE-AVERAGE.

REWIND allows efficient multiple passes over the same file.

Error Recovery

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
* Error recovery with REWIND PROCEDURE DIVISION. PROCESS-WITH-RETRY. OPEN INPUT DATA-FILE PERFORM PROCESS-FILE CLOSE DATA-FILE. PROCESS-FILE. READ DATA-FILE AT END EXIT PARAGRAPH END-READ * Simulate processing error IF CUST-BALANCE < 0 DISPLAY "Error: Negative balance found" * Rewind and retry processing REWIND DATA-FILE PERFORM PROCESS-FILE EXIT PARAGRAPH END-IF * Normal processing DISPLAY "Processing: " CUST-NAME GO TO PROCESS-FILE. * Alternative: Retry with different logic PROCEDURE DIVISION. RETRY-PROCESSING. OPEN INPUT DATA-FILE PERFORM FIRST-ATTEMPT * If first attempt fails, rewind and try different approach REWIND DATA-FILE PERFORM SECOND-ATTEMPT CLOSE DATA-FILE. FIRST-ATTEMPT. READ DATA-FILE AT END EXIT PARAGRAPH END-READ * First processing logic GO TO FIRST-ATTEMPT. SECOND-ATTEMPT. READ DATA-FILE AT END EXIT PARAGRAPH END-READ * Different processing logic GO TO SECOND-ATTEMPT.

REWIND enables error recovery by restarting file processing.

File Validation

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
* File validation with multiple passes WORKING-STORAGE SECTION. 01 VALIDATION-STATS. 05 TOTAL-RECORDS PIC 9(6) VALUE ZERO. 05 VALID-RECORDS PIC 9(6) VALUE ZERO. 05 INVALID-RECORDS PIC 9(6) VALUE ZERO. 05 ERROR-MESSAGES PIC X(100) OCCURS 10 TIMES. PROCEDURE DIVISION. VALIDATE-FILE. OPEN INPUT DATA-FILE * First pass: Count and validate PERFORM COUNT-AND-VALIDATE * Display validation results DISPLAY "Total Records: " TOTAL-RECORDS DISPLAY "Valid Records: " VALID-RECORDS DISPLAY "Invalid Records: " INVALID-RECORDS * Rewind for second pass: Process only valid records REWIND DATA-FILE * Second pass: Process valid records PERFORM PROCESS-VALID-RECORDS CLOSE DATA-FILE. COUNT-AND-VALIDATE. READ DATA-FILE AT END EXIT PARAGRAPH END-READ ADD 1 TO TOTAL-RECORDS * Validation logic IF CUST-ID > 0 AND CUST-NAME NOT = SPACES ADD 1 TO VALID-RECORDS ELSE ADD 1 TO INVALID-RECORDS MOVE "Invalid record found" TO ERROR-MESSAGES(INVALID-RECORDS) END-IF GO TO COUNT-AND-VALIDATE. PROCESS-VALID-RECORDS. READ DATA-FILE AT END EXIT PARAGRAPH END-READ * Only process if valid IF CUST-ID > 0 AND CUST-NAME NOT = SPACES DISPLAY "Processing valid record: " CUST-NAME END-IF GO TO PROCESS-VALID-RECORDS.

REWIND enables validation followed by processing of valid records.

Data Analysis

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
* Data analysis with multiple passes WORKING-STORAGE SECTION. 01 ANALYSIS-STATS. 05 MIN-BALANCE PIC 9(8)V99 VALUE 999999.99. 05 MAX-BALANCE PIC 9(8)V99 VALUE ZERO. 05 MIN-CUSTOMER PIC X(30). 05 MAX-CUSTOMER PIC X(30). PROCEDURE DIVISION. ANALYZE-DATA. OPEN INPUT DATA-FILE * First pass: Find min and max PERFORM FIND-MIN-MAX * Display analysis results DISPLAY "Minimum Balance: " MIN-BALANCE " - " MIN-CUSTOMER DISPLAY "Maximum Balance: " MAX-BALANCE " - " MAX-CUSTOMER * Rewind for second pass: Find records near min/max REWIND DATA-FILE * Second pass: Find similar records PERFORM FIND-SIMILAR-RECORDS CLOSE DATA-FILE. FIND-MIN-MAX. READ DATA-FILE AT END EXIT PARAGRAPH END-READ IF CUST-BALANCE < MIN-BALANCE MOVE CUST-BALANCE TO MIN-BALANCE MOVE CUST-NAME TO MIN-CUSTOMER END-IF IF CUST-BALANCE > MAX-BALANCE MOVE CUST-BALANCE TO MAX-BALANCE MOVE CUST-NAME TO MAX-CUSTOMER END-IF GO TO FIND-MIN-MAX. FIND-SIMILAR-RECORDS. READ DATA-FILE AT END EXIT PARAGRAPH END-READ * Find records within 10% of min or max IF CUST-BALANCE <= MIN-BALANCE * 1.10 OR CUST-BALANCE >= MAX-BALANCE * 0.90 DISPLAY "Similar record: " CUST-NAME " - " CUST-BALANCE END-IF GO TO FIND-SIMILAR-RECORDS.

REWIND enables complex data analysis requiring multiple passes.

Best Practices and Considerations

Understanding best practices ensures efficient and reliable use of the REWIND statement.

Best Practices

  • Check file status - Always verify REWIND operations complete successfully
  • Ensure file is open - REWIND requires the file to be open
  • Use appropriate file mode - REWIND works with INPUT and I-O modes
  • Handle errors gracefully - Provide error recovery for REWIND failures
  • Consider performance - REWIND is more efficient than CLOSE/OPEN
  • Document usage - Clearly document when and why REWIND is used

File Organization Compatibility

File OrganizationREWIND SupportNotes
SequentialYesPrimary use case
RelativeYesRepositions to record 1
IndexedNoUse START instead
Line SequentialYesTreats as sequential

Error Handling

  • File not open - Check file status before REWIND
  • Invalid file mode - Ensure file is opened for reading
  • File system errors - Handle system-level errors
  • Permission issues - Verify file access permissions
  • File corruption - Detect and handle file integrity issues

REWIND Statement Quick Reference

UsageSyntaxExample
Basic REWINDREWIND file-nameREWIND INPUT-FILE
With error handlingREWIND file-name ON EXCEPTION...REWIND DATA-FILE ON EXCEPTION PERFORM ERROR-HANDLING
Multiple filesREWIND file1, file2REWIND FILE1, FILE2
After processingREAD... REWIND... READ...READ FILE AT END... REWIND FILE READ FILE...
Error recoveryIF error REWIND fileIF ERROR-FLAG = "Y" REWIND DATA-FILE

Test Your Knowledge

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

  • To delete a file
  • To reposition a file to its beginning
  • To create a new file
  • To close a file

2. Which file organization types support the REWIND statement?

  • Only indexed files
  • Only sequential files
  • Sequential and relative files
  • All file organization types

3. What happens when you REWIND a file that is not open?

  • The file is automatically opened
  • An error occurs
  • Nothing happens
  • The file is created

4. Can REWIND be used with files opened for OUTPUT?

  • Yes, always
  • No, never
  • Only if the file is empty
  • Only with certain file organizations

5. What is the relationship between REWIND and START statements?

  • They are the same thing
  • REWIND goes to beginning, START goes to specific position
  • REWIND is faster than START
  • They cannot be used together

Frequently Asked Questions