MainframeMaster

COBOL Tutorial

COBOL REDEFINES Clause - Quick Reference

Progress0 of 0 lessons

Overview

The REDEFINES clause allows multiple data layouts to share the same storage area, creating union-like structures in COBOL. This enables different interpretations of the same memory location and is commonly used for multiple record layouts and data type conversions.

Purpose and Usage

  • Multiple data layouts - Different structures for same storage
  • Union-like behavior - Share memory between different fields
  • Record type handling - Different record layouts in single file
  • Data interpretation - View same data in different formats
  • Memory efficiency - Reduce storage requirements

Storage Sharing Concept

Original Field: [Field1][Field2][Field3][Field4]
REDEFINES A: [Alt1][Alt2][Alt3][Alt4]
REDEFINES B: [Diff1][Diff2][Diff3][Diff4]
All share the same memory location

Multiple REDEFINES fields occupy the same storage area as the original field.

Syntax

The REDEFINES clause follows specific syntax patterns and can be used at various levels in data definitions.

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
* Basic REDEFINES clause syntax level-number data-name REDEFINES original-field-name * Examples 05 ALTERNATE-LAYOUT REDEFINES ORIGINAL-FIELD. 05 NUMERIC-VALUE REDEFINES CHARACTER-FIELD. 05 DATE-FIELD REDEFINES TIMESTAMP-FIELD. * Complete example 01 CUSTOMER-RECORD. 05 RECORD-TYPE PIC X. 05 CUSTOMER-DATA PIC X(99). 01 CUSTOMER-HEADER REDEFINES CUSTOMER-RECORD. 05 HR-RECORD-TYPE PIC X. 05 HR-FILE-DATE PIC 9(8). 05 HR-RECORD-COUNT PIC 9(5). 05 HR-FILLER PIC X(86). 01 CUSTOMER-DETAIL REDEFINES CUSTOMER-RECORD. 05 DR-RECORD-TYPE PIC X. 05 DR-CUSTOMER-ID PIC 9(5). 05 DR-CUSTOMER-NAME PIC X(30). 05 DR-CUSTOMER-ADDR PIC X(50). 05 DR-STATUS PIC X. 05 DR-FILLER PIC X(13).

REDEFINES can be used at any level except 01 (record level).

Level Restrictions

LevelCan Use REDEFINESCommon Usage
01NoRecord level - cannot redefine
02-49YesField and group levels
66NoRENAMES level - different purpose
77NoIndependent item level
88NoCondition name level

Multiple REDEFINES

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
* Multiple REDEFINES of the same field 01 SHARED-STORAGE. 05 ORIGINAL-FIELD PIC X(10). 05 ALTERNATE-1 REDEFINES ORIGINAL-FIELD. 10 ALT1-PART1 PIC X(5). 10 ALT1-PART2 PIC X(5). 05 ALTERNATE-2 REDEFINES ORIGINAL-FIELD. 10 ALT2-NUMERIC PIC 9(10). 05 ALTERNATE-3 REDEFINES ORIGINAL-FIELD. 10 ALT3-DATE PIC 9(8). 10 ALT3-TIME PIC 9(2). * All three REDEFINES share the same 10-byte storage area

Multiple REDEFINES can share the same original field storage.

Common Use Cases

REDEFINES is commonly used in specific scenarios where different data layouts need to share storage or where data interpretation varies.

Multiple Record Types in File

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
* File with different record types 01 INVENTORY-RECORD. 05 RECORD-TYPE PIC X. 88 HEADER-RECORD VALUE 'H'. 88 DETAIL-RECORD VALUE 'D'. 88 TRAILER-RECORD VALUE 'T'. 05 RECORD-DATA PIC X(99). 01 HEADER-RECORD REDEFINES INVENTORY-RECORD. 05 HR-TYPE PIC X. 05 HR-FILE-DATE PIC 9(8). 05 HR-COMPANY-NAME PIC X(50). 05 HR-VERSION PIC 9(2). 05 HR-FILLER PIC X(39). 01 DETAIL-RECORD REDEFINES INVENTORY-RECORD. 05 DR-TYPE PIC X. 05 DR-ITEM-NUMBER PIC 9(10). 05 DR-ITEM-NAME PIC X(30). 05 DR-QUANTITY PIC 9(5). 05 DR-UNIT-PRICE PIC 9(5)V99. 05 DR-LOCATION PIC X(10). 05 DR-STATUS PIC X. 05 DR-FILLER PIC X(36). 01 TRAILER-RECORD REDEFINES INVENTORY-RECORD. 05 TR-TYPE PIC X. 05 TR-RECORD-COUNT PIC 9(10). 05 TR-TOTAL-ITEMS PIC 9(10). 05 TR-TOTAL-VALUE PIC 9(10)V99. 05 TR-FILLER PIC X(66).

Different record layouts share the same storage area based on record type.

Data Type Conversion

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
* Converting between data types 01 FLEXIBLE-DATA. 05 CHARACTER-VALUE PIC X(8). 05 NUMERIC-VALUE REDEFINES CHARACTER-VALUE. 10 NUM-PART PIC 9(8). 05 DATE-VALUE REDEFINES CHARACTER-VALUE. 10 YEAR PIC 9(4). 10 MONTH PIC 9(2). 10 DAY PIC 9(2). 05 TIME-VALUE REDEFINES CHARACTER-VALUE. 10 HOUR PIC 9(2). 10 MINUTE PIC 9(2). 10 SECOND PIC 9(2). 10 HUNDREDTH PIC 9(2). * Usage example PROCEDURE DIVISION. * Store as character MOVE "20231225" TO CHARACTER-VALUE * Access as date components DISPLAY "Year: " YEAR DISPLAY "Month: " MONTH DISPLAY "Day: " DAY * Access as numeric DISPLAY "Numeric: " NUMERIC-VALUE

Same data can be interpreted as different types using REDEFINES.

Bit-Level Manipulation

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
* Bit-level access using REDEFINES 01 FLAG-WORD. 05 FLAG-BYTE PIC X. 05 FLAG-BITS REDEFINES FLAG-BYTE. 10 BIT-0 PIC 1. 10 BIT-1 PIC 1. 10 BIT-2 PIC 1. 10 BIT-3 PIC 1. 10 BIT-4 PIC 1. 10 BIT-5 PIC 1. 10 BIT-6 PIC 1. 10 BIT-7 PIC 1. * Usage example PROCEDURE DIVISION. * Set individual bits MOVE 1 TO BIT-0 MOVE 1 TO BIT-3 MOVE 1 TO BIT-7 * Check bit values IF BIT-0 = 1 DISPLAY "Bit 0 is set" END-IF * Access as byte DISPLAY "Flag byte value: " FLAG-BYTE

REDEFINES enables bit-level access to byte data.

Best Practices and Tips

Following these best practices ensures effective and safe use of the REDEFINES clause in COBOL applications.

REDEFINES Design Principles

  • Ensure size compatibility - Total REDEFINES size should not exceed original
  • Use condition names - 88-level items to determine which layout to use
  • Document relationships - Clearly document which fields share storage
  • Validate data integrity - Ensure data makes sense in all layouts
  • Consider data alignment - Be aware of potential alignment issues
  • Test thoroughly - Verify all REDEFINES layouts work correctly

Common Pitfalls to Avoid

PitfallProblemSolution
Size mismatchData corruption, program errorsEnsure total size doesn\'t exceed original
Incorrect field accessWrong data interpretationUse condition names to determine layout
Data corruptionChanges affect all REDEFINES fieldsBe careful when modifying shared data
Complex structuresHard to maintain and debugKeep REDEFINES structures simple
No documentationConfusion about data relationshipsDocument all REDEFINES relationships

Performance Considerations

  • Memory efficiency - REDEFINES reduces memory usage
  • No runtime overhead - REDEFINES is compile-time only
  • Data access patterns - Consider how data will be accessed
  • Alignment issues - Some platforms may have alignment requirements
  • Debugging complexity - REDEFINES can make debugging harder
  • Maintenance considerations - Changes affect multiple layouts

When to Use REDEFINES

Use CaseREDEFINES SuitabilityReasoning
Multiple record typesExcellentNatural fit for different layouts
Data type conversionGoodEfficient for type reinterpretation
Bit manipulationGoodProvides bit-level access
Simple field aliasesPoorUse RENAMES instead
Independent dataPoorUse separate fields

REDEFINES Clause Quick Reference

UsageSyntaxExample
Basic redefinitionlevel data-name REDEFINES original-field05 ALT-LAYOUT REDEFINES ORIG-FIELD
Multiple redefinitionsMultiple REDEFINES of same field05 ALT1 REDEFINES FIELD
05 ALT2 REDEFINES FIELD
Record layouts01 record-name REDEFINES original-record01 HEADER-REC REDEFINES DATA-REC
Data type conversion05 numeric-field REDEFINES char-field05 NUM-VAL REDEFINES CHAR-VAL
Bit manipulation05 bit-fields REDEFINES byte-field05 BITS REDEFINES FLAG-BYTE

Test Your Knowledge

1. What is the primary purpose of the REDEFINES clause in COBOL?

  • To define data types
  • To allow multiple data layouts to share the same storage area
  • To control file operations
  • To perform calculations

2. At what level can the REDEFINES clause be used?

  • Only at the 01 level
  • Only at the 05 level
  • At any level except 01
  • At any level including 01

3. What happens when you modify data in a REDEFINES field?

  • Only that field is changed
  • All REDEFINES fields sharing the same storage are affected
  • The program terminates with an error
  • Nothing happens

4. Which of the following is a common use case for REDEFINES?

  • Simple arithmetic operations
  • Multiple record layouts in a single file
  • File I/O operations
  • Screen display

5. What is the relationship between the original field and REDEFINES fields?

  • They are completely independent
  • They share the same storage location
  • They are automatically synchronized
  • They have different data types

Frequently Asked Questions