MainframeMaster

COBOL Tutorial

Internal Data Manipulation in COBOL

Progress0 of 0 lessons

Moving Data Between Fields

The cornerstone of data manipulation in COBOL is the ability to move data between different storage locations (fields or variables). The primary verb for this is MOVE, but INITIALIZE also plays a key role in setting up data fields.

The MOVE Statement

The MOVE statement copies data from a sending field to one or more receiving fields. COBOL has specific rules for how data is moved based on the data types of the sending and receiving fields.

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
IDENTIFICATION DIVISION. PROGRAM-ID. MOVE-EXAMPLE. DATA DIVISION. WORKING-STORAGE SECTION. 01 SOURCE-NUMERIC PIC 9(5)V99 VALUE 123.45. 01 TARGET-NUMERIC PIC 9(7)V99. 01 SOURCE-ALPHA PIC X(10) VALUE "HELLO COBOL". 01 TARGET-ALPHA-SMALL PIC X(5). 01 TARGET-ALPHA-LARGE PIC X(15). PROCEDURE DIVISION. MOVE SOURCE-NUMERIC TO TARGET-NUMERIC. * TARGET-NUMERIC will be 00123.45 (right-justified, zero-filled) MOVE SOURCE-ALPHA TO TARGET-ALPHA-SMALL. * TARGET-ALPHA-SMALL will be "HELLO" (truncated from right) MOVE SOURCE-ALPHA TO TARGET-ALPHA-LARGE. * TARGET-ALPHA-LARGE will be "HELLO COBOL " (left-justified, space-filled) DISPLAY "TARGET-NUMERIC: " TARGET-NUMERIC. DISPLAY "TARGET-ALPHA-SMALL: " TARGET-ALPHA-SMALL. DISPLAY "TARGET-ALPHA-LARGE: " TARGET-ALPHA-LARGE. STOP RUN.

Numeric Moves: Data is aligned by decimal point. If the receiving field is larger, it's zero-padded. If smaller, truncation can occur (digits lost from left or right, potentially causing a size error).
Alphanumeric Moves: Data is left-justified. If the receiving field is larger, it's space-padded on the right. If smaller, it's truncated on the right.

MOVE CORRESPONDING

The MOVE CORRESPONDING (or MOVE CORR) statement is used to move data between group items. It transfers data from elementary items in the sending group to elementary items with the exact same name in the receiving group.

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
IDENTIFICATION DIVISION. PROGRAM-ID. MOVE-CORR-EXAMPLE. DATA DIVISION. WORKING-STORAGE SECTION. 01 SOURCE-RECORD. 05 ITEM-ID PIC 9(5) VALUE 12345. 05 ITEM-DESC PIC X(20) VALUE "SAMPLE DESCRIPTION". 05 ITEM-QTY PIC 9(3) VALUE 100. 05 FILLER PIC X(5) VALUE "EXTRA". 01 TARGET-RECORD. 05 ITEM-ID PIC 9(5). 05 ITEM-DESC PIC X(10). * Shorter description field 05 ITEM-PRICE PIC 9(5)V99. * Different field 05 ITEM-QTY PIC 9(3). PROCEDURE DIVISION. MOVE CORRESPONDING SOURCE-RECORD TO TARGET-RECORD. DISPLAY "TARGET ITEM-ID: " ITEM-ID OF TARGET-RECORD. * Output: TARGET ITEM-ID: 12345 DISPLAY "TARGET ITEM-DESC: " ITEM-DESC OF TARGET-RECORD. * Output: TARGET ITEM-DESC: SAMPLE DES (truncated) DISPLAY "TARGET ITEM-QTY: " ITEM-QTY OF TARGET-RECORD. * Output: TARGET ITEM-QTY: 100 * ITEM-PRICE in TARGET-RECORD remains unchanged as there's no matching field. * FILLER in SOURCE-RECORD is ignored. STOP RUN.

MOVE CORR is useful for moving subsets of data between record structures without listing each field individually.

The INITIALIZE Statement

The INITIALIZE statement sets one or more data items to predetermined values based on their data type: numeric fields to zeros, alphanumeric fields to spaces. It can initialize group items or elementary items.

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
IDENTIFICATION DIVISION. PROGRAM-ID. INITIALIZE-EXAMPLE. DATA DIVISION. WORKING-STORAGE SECTION. 01 MY-RECORD. 05 FIELD-A PIC X(5) VALUE "OLD-A". 05 FIELD-B PIC 9(3) VALUE 123. 05 FIELD-C PIC X(3) VALUE "OLD". 05 GROUP-ITEM. 10 SUB-FIELD-X PIC X(2) VALUE "XX". 10 SUB-FIELD-N PIC 9(1) VALUE 9. 01 ANOTHER-FIELD PIC X(10) VALUE "INITIAL". PROCEDURE DIVISION. INITIALIZE MY-RECORD. * FIELD-A will be " " (spaces) * FIELD-B will be 000 (zeros) * FIELD-C will be " " (spaces) * SUB-FIELD-X will be " " (spaces) * SUB-FIELD-N will be 0 (zero) DISPLAY "MY-RECORD AFTER INITIALIZE: " MY-RECORD. INITIALIZE ANOTHER-FIELD REPLACING ALPHANUMERIC BY "NEWVAL". * ANOTHER-FIELD would be "NEWVAL " (if "NEWVAL" is shorter than field) * Or "NEWVALNEWS" (if "NEWVALNEWS" is longer, it will be "NEWVALNEWS") * Actually, if "NEWVAL" is shorter, it will be padded by spaces. * If longer, "NEWVALNEWS" is moved, and if the field is X(10), it will be "NEWVALNEWS" (no truncation specified) * Corrected: If "NEWVAL" is X(6), and ANOTHER-FIELD is X(10), result is "NEWVAL " * If REPLACING value "TOO LONG" is X(8) for a PIC X(5) field, it's a compile error for literals. * For variables, it follows MOVE rules. Let's simplify example for clarity. INITIALIZE ANOTHER-FIELD REPLACING ALPHANUMERIC DATA BY "DEFAULT". * ANOTHER-FIELD will be "DEFAULT " (assuming ANOTHER-FIELD is PIC X(10)) DISPLAY "ANOTHER-FIELD AFTER INITIALIZE REPLACING: " ANOTHER-FIELD. STOP RUN.

The REPLACING phrase allows specifying different values for specific data types (NUMERIC, ALPHANUMERIC, ALPHABETIC, etc.).

Data Type Conversion

COBOL often requires converting data from one type to another, for example, when reading input (typically character-based) into numeric fields for calculations, or formatting numeric data for display or reports. The MOVE statement is also the primary mechanism for implicit data type conversion.

Numeric to Alphanumeric Conversion

When a numeric field is moved to an alphanumeric field, it is typically de-edited: signs and decimal points are stripped, and the number is right-justified and space-padded if the target is larger, or truncated from the left if the target is smaller. Using a numeric-edited field as the source allows for formatting (like leading zeros, signs, decimal points) to be included in the alphanumeric target.

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
IDENTIFICATION DIVISION. PROGRAM-ID. NUM-TO-ALPHA. DATA DIVISION. WORKING-STORAGE SECTION. 01 AMOUNT-NUMERIC PIC S9(5)V99 VALUE -123.45. 01 AMOUNT-EDITED PIC -ZZZ,ZZ9.99. 01 DISPLAY-FIELD-RAW PIC X(10). 01 DISPLAY-FIELD-EDIT PIC X(12). PROCEDURE DIVISION. MOVE AMOUNT-NUMERIC TO DISPLAY-FIELD-RAW. * DISPLAY-FIELD-RAW would effectively be "0012345 " (implementation dependent on how sign is handled internally without edit) * More accurately, it is de-edited. Sign is lost. Standard COBOL: right-justified, zero-padded on left. * For S9(5)V99 -> X(10): the value "12345" (7 digits) moved to X(10) results in "12345 ". * Some compilers might store it as "0012345 " when PIC has S, but typical de-edit means sign stripped. * Let's clarify with a standard de-editing example. * If AMOUNT-NUMERIC is +123.45 (PIC S9(5)V99), then MOVE AMOUNT-NUMERIC TO DISPLAY-FIELD-RAW (PIC X(7)) makes it "12345 " * If DISPLAY-FIELD-RAW is PIC X(10), it will be "0012345 " or "12345 " depending on compiler interpretation of numeric to alpha move. * For simplicity, let's assume simple digit transfer, right justified. * Corrected: Standard de-editing. Numeric value 12345 (sign and decimal are conceptual for numeric type) to X(10). * It would be "0012345 " assuming standard de-editing (internal to external). MOVE 123.45 TO DISPLAY-FIELD-RAW. *> PIC 9(5)V99 to X(10) * DISPLAY-FIELD-RAW becomes "0012345 " (typical behavior, right-justified, zero-filled, then treated as alpha for padding) * This is often not what is desired for display. MOVE AMOUNT-NUMERIC TO AMOUNT-EDITED. * AMOUNT-EDITED becomes " -123.45 " (if PIC is ---,---9.99) * If PIC is -ZZZ,ZZ9.99, and value is -123.45, it becomes " -123.45" MOVE AMOUNT-EDITED TO DISPLAY-FIELD-EDIT. * DISPLAY-FIELD-EDIT becomes " -123.45 " DISPLAY "DISPLAY-FIELD-RAW : " DISPLAY-FIELD-RAW. DISPLAY "DISPLAY-FIELD-EDIT: " DISPLAY-FIELD-EDIT. STOP RUN.

Alphanumeric to Numeric Conversion

When an alphanumeric field is moved to a numeric field, the alphanumeric data must represent a valid number. The data is typically right-justified, and leading spaces are treated as zeros. Non-numeric characters (except for a leading/trailing sign or decimal point, if allowed by PIC) will cause a data exception at runtime.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
IDENTIFICATION DIVISION. PROGRAM-ID. ALPHA-TO-NUM. DATA DIVISION. WORKING-STORAGE SECTION. 01 INPUT-STRING PIC X(8) VALUE " 12345". 01 OUTPUT-NUMERIC PIC 9(5)V99. 01 INPUT-STRING-BAD PIC X(8) VALUE "AB123". PROCEDURE DIVISION. MOVE INPUT-STRING TO OUTPUT-NUMERIC. * OUTPUT-NUMERIC will be 12345.00 (leading spaces treated as zeros, right-justified) DISPLAY "OUTPUT-NUMERIC: " OUTPUT-NUMERIC. * The following MOVE would likely cause a data exception (runtime error) * MOVE INPUT-STRING-BAD TO OUTPUT-NUMERIC. * DISPLAY "This won't be reached if error occurs.". STOP RUN.

It's crucial to validate alphanumeric input using IF NUMERIC class condition before moving it to a numeric field to prevent runtime errors.

Padding and Truncation Handling

Understanding how COBOL handles padding and truncation is essential for accurate data manipulation and preventing unintended data loss or corruption.

Alphanumeric Fields (PIC X, PIC A)

  • Padding: When moving a shorter alphanumeric value to a longer field, the receiving field is padded with spaces on the right (left-justification).
  • Truncation: When moving a longer alphanumeric value to a shorter field, the data is truncated from the right.
cobol
1
2
3
4
5
6
01 SOURCE-STR PIC X(5) VALUE "ABC". 01 TARGET-STR-LONG PIC X(8). 01 TARGET-STR-SHORT PIC X(2). ... MOVE SOURCE-STR TO TARGET-STR-LONG. * Becomes "ABC " MOVE "XYZ123" TO TARGET-STR-SHORT. * Becomes "XY"

Numeric Fields (PIC 9)

  • Padding (Integer Part): When moving a numeric value to a field with a larger integer part, the receiving field is padded with zeros on the left (right-justification).
  • Padding (Fractional Part): When moving a numeric value to a field with a larger fractional part, the receiving field is padded with zeros on the right.
  • Truncation (Integer Part): When moving a numeric value to a field with a smaller integer part, high-order digits (most significant, from the left) are truncated. This can lead to an ON SIZE ERROR condition if not handled.
  • Truncation (Fractional Part): When moving a numeric value to a field with a smaller fractional part, low-order digits (least significant, from the right of the decimal) are truncated (not rounded by default).
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
01 SOURCE-NUM PIC 9(3)V99 VALUE 123.45. 01 TARGET-NUM-LIP PIC 9(5)V99. * Larger Integer Part 01 TARGET-NUM-LFP PIC 9(3)V999. * Larger Fractional Part 01 TARGET-NUM-SIP PIC 9(2)V99. * Smaller Integer Part 01 TARGET-NUM-SFP PIC 9(3)V9. * Smaller Fractional Part ... MOVE SOURCE-NUM TO TARGET-NUM-LIP. * Becomes 00123.45 MOVE SOURCE-NUM TO TARGET-NUM-LFP. * Becomes 123.450 MOVE SOURCE-NUM TO TARGET-NUM-SIP. * Becomes 23.45 (1 is truncated). Potential ON SIZE ERROR. * To demonstrate: ADD SOURCE-NUM TO SOME-OTHER-FIELD GIVING TARGET-NUM-SIP ON SIZE ERROR DISPLAY "SIZE ERROR SIP". MOVE SOURCE-NUM TO TARGET-NUM-SFP. * Becomes 123.4 (5 is truncated). MOVE 789 TO TARGET-NUM-SIP. * 789 -> 9(2)V99. Becomes 89.00. (7 truncated) DISPLAY "TARGET-NUM-SIP after 789: " TARGET-NUM-SIP.

Strategies for Handling Truncation

  • Define Adequate Field Sizes: Ensure receiving fields are large enough to hold the maximum expected data size.
  • Validate Input: Check lengths or numeric ranges before moving data.
  • ON SIZE ERROR Clause: For arithmetic statements (ADD, SUBTRACT, MULTIPLY, DIVIDE, COMPUTE), use the ON SIZE ERROR phrase to detect and handle potential overflow/truncation in the result field. Note that MOVE does not directly support ON SIZE ERROR for simple moves, but the principle applies to results of calculations being moved.
  • STRING/UNSTRING with POINTER and OVERFLOW: For alphanumeric data, these verbs offer more control over concatenation and parsing, allowing detection of overflow conditions.
  • Inspect and Trim: Use INSPECT to check for significant non-space characters before moving to a smaller field or use FUNCTION TRIM.

Rounding Techniques

In financial and scientific calculations, precise rounding is crucial. COBOL provides several ways to control how numeric values are rounded when decimal places are dropped, or when results of calculations exceed the precision of the receiving field.

Default Behavior (Truncation)

By default, when a COBOL arithmetic operation results in more decimal places than the receiving field can store, the extra digits are simply truncated (dropped) without rounding.

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
IDENTIFICATION DIVISION. PROGRAM-ID. ROUNDING-DEFAULT. DATA DIVISION. WORKING-STORAGE SECTION. 01 NUM-1 PIC 9V999 VALUE 1.237. 01 NUM-2 PIC 9V999 VALUE 2.346. 01 RESULT-FIELD PIC 9V99. * Stores only 2 decimal places PROCEDURE DIVISION. COMPUTE RESULT-FIELD = NUM-1 + NUM-2. * NUM-1 + NUM-2 = 1.237 + 2.346 = 3.583 * Without ROUNDED, RESULT-FIELD becomes 3.58 (3 is truncated) DISPLAY "Default (Truncated) Result: " RESULT-FIELD. MOVE 4.567 TO RESULT-FIELD. * RESULT-FIELD becomes 4.56 (7 is truncated) DISPLAY "Move (Truncated) Result: " RESULT-FIELD. STOP RUN.

The ROUNDED Phrase

The ROUNDED phrase can be used with arithmetic verbs (ADD, SUBTRACT, MULTIPLY, DIVIDE, COMPUTE) to specify that if the result has more fractional digits than the receiving field can hold, the least significant digit of the result should be rounded. Standard COBOL rounding typically rounds half to the nearest even digit or away from zero (compiler/standard dependent, but commonly away from zero for .5).

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
IDENTIFICATION DIVISION. PROGRAM-ID. ROUNDED-PHRASE. DATA DIVISION. WORKING-STORAGE SECTION. 01 PRICE PIC 9(5)V999 VALUE 10.125. 01 QUANTITY PIC 9(3) VALUE 3. 01 TOTAL-COST PIC 9(7)V99. 01 AVERAGE-VALUE PIC 9(5)V99. PROCEDURE DIVISION. COMPUTE TOTAL-COST ROUNDED = PRICE * QUANTITY. * PRICE * QUANTITY = 10.125 * 3 = 30.375 * TOTAL-COST (PIC 9(7)V99) becomes 30.38 (0.005 rounds up) DISPLAY "Total Cost (Rounded): " TOTAL-COST. DIVIDE TOTAL-COST BY QUANTITY GIVING AVERAGE-VALUE ROUNDED. * 30.38 / 3 = 10.12666... * AVERAGE-VALUE (PIC 9(5)V99) becomes 10.13 DISPLAY "Average Value (Rounded): " AVERAGE-VALUE. COMPUTE RESULT-FIELD ROUNDED = 1.235. *> to PIC 9V99 * RESULT-FIELD becomes 1.24 DISPLAY "1.235 Rounded: " RESULT-FIELD. COMPUTE RESULT-FIELD ROUNDED = 1.234. * RESULT-FIELD becomes 1.23 DISPLAY "1.234 Rounded: " RESULT-FIELD. STOP RUN. WORKING-STORAGE SECTION. 01 RESULT-FIELD PIC 9V99.

The ROUNDED phrase applies only to the final result being stored in the receiving field of that specific arithmetic statement.

Intrinsic Functions for Rounding (Modern COBOL)

Modern COBOL standards (COBOL 2002 and later) provide intrinsic functions for more explicit control over rounding:

  • FUNCTION ROUND (argument mode): Not a standard COBOL function for rounding to a number of decimal places. Instead, COBOL has ROUNDED phrase. Some compilers might offer ROUND as an extension, but standard rounding is via ROUNDED or other functions.
  • Actually, the standard numeric intrinsic functions are more about mathematical operations. Standard COBOL intrinsic functions related to rounding are:
  • FUNCTION INTEGER(numeric-argument): Returns the greatest integer less than or equal to the argument if positive, or least integer greater than or equal if negative (truncates towards zero).
  • FUNCTION INTEGER-PART(numeric-argument): Returns the integer part of the argument (truncates fractional part).
  • To achieve specific rounding like round-half-up, round-to-nearest, developers often implement custom logic or use the ROUNDED phrase. For explicit rounding control beyond the ROUNDED phrase, you might need to perform arithmetic manipulations. For example, to round to 2 decimal places: COMPUTE Y = X + 0.005, then move Y to a field with 2 decimal places (truncating).

Let's demonstrate a common rounding technique by adding 0.5 (or 0.05, 0.005 etc. depending on decimal places) and then truncating.

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
IDENTIFICATION DIVISION. PROGRAM-ID. CUSTOM-ROUNDING. DATA DIVISION. WORKING-STORAGE SECTION. 01 ORIGINAL-VALUE PIC 9(5)V999 VALUE 76.543. 01 VALUE-TO-ROUND PIC 9(5)V999 VALUE 76.547. 01 ROUNDED-2DP PIC 9(5)V99. 01 TEMP-CALC PIC 9(5)V999. PROCEDURE DIVISION. * Round ORIGINAL-VALUE (76.543) to 2 decimal places (should be 76.54) ADD 0.0005 TO ORIGINAL-VALUE GIVING TEMP-CALC. MOVE TEMP-CALC TO ROUNDED-2DP. *> Truncates to 2dp DISPLAY "Original (76.543) Rounded to 2dp: " ROUNDED-2DP. *> Should be 76.54 * Round VALUE-TO-ROUND (76.547) to 2 decimal places (should be 76.55) ADD 0.005 TO VALUE-TO-ROUND GIVING TEMP-CALC. MOVE TEMP-CALC TO ROUNDED-2DP. *> Truncates to 2dp DISPLAY "Value (76.547) Rounded to 2dp: " ROUNDED-2DP. *> Should be 76.55 * Using a more direct approach for 2 decimal places COMPUTE ROUNDED-2DP = ORIGINAL-VALUE + 0.005. DISPLAY "Alternative Original (76.543) Rounded to 2dp: " ROUNDED-2DP. *> 76.54 COMPUTE ROUNDED-2DP = VALUE-TO-ROUND + 0.005. DISPLAY "Alternative Value (76.547) Rounded to 2dp: " ROUNDED-2DP. *> 76.55 STOP RUN.

Note: The ROUNDED phrase is generally preferred for its clarity and directness when applicable with arithmetic verbs. Custom logic is for scenarios where ROUNDED isn't available or specific non-standard rounding is needed.

Considerations for Rounding

  • Precision: Ensure intermediate fields used in COMPUTE statements have enough precision to hold values before rounding to prevent premature truncation.
  • Rounding Method: Be aware of the specific rounding method your COBOL compiler implements for the ROUNDED phrase (e.g., round half up, round half to even). This can vary. Typically, it rounds .5 away from zero.
  • Cumulative Effects: Repeated rounding in sequential calculations can sometimes lead to accumulated rounding errors. Analyze critical calculations for such potential impacts.
  • Business Rules: Always conform to the specific rounding rules required by the business application (e.g., financial regulations might dictate specific rounding methods).

Data Transformation Patterns

COBOL programs frequently need to transform data from one format or structure to another. This can involve simple repackaging of data, complex parsing, or conditional logic to derive new values.

STRING and UNSTRING for Complex Manipulations

These powerful verbs are essential for advanced data transformation.

  • STRING: Concatenates (joins) multiple data items into a single string. It offers fine-grained control with DELIMITED BY clauses to specify delimiters or stop concatenation based on specific characters or field sizes. The POINTER phrase allows tracking the current position in the receiving field, and ON OVERFLOW handles cases where the receiving field is too small.
  • UNSTRING: Parses a single string into multiple fields based on delimiters (e.g., comma, space). It can count the number of fields found (TALLYING) and track the position in the source string (POINTER). ON OVERFLOW handles situations where there are more delimited fields than receiving fields.
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
IDENTIFICATION DIVISION. PROGRAM-ID. STRING-UNSTRING-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 FIRST-NAME PIC X(10) VALUE "John". 01 LAST-NAME PIC X(10) VALUE "Doe". 01 MIDDLE-INITIAL PIC X(1) VALUE "M". 01 FULL-NAME PIC X(30). 01 NAME-POINTER PIC 99. 01 CSV-DATA PIC X(50) VALUE "Smith,Jane,F,123 Main St,Anytown". 01 REC-LAST-NAME PIC X(15). 01 REC-FIRST-NAME PIC X(15). 01 REC-GENDER PIC X(1). 01 REC-ADDRESS PIC X(20). 01 REC-CITY PIC X(10). 01 FIELD-COUNT PIC 99. PROCEDURE DIVISION. DISPLAY "STRING Example:". INITIALIZE FULL-NAME NAME-POINTER. SET NAME-POINTER TO 1. STRING FIRST-NAME DELIMITED BY SPACE " " DELIMITED BY SIZE MIDDLE-INITIAL DELIMITED BY SIZE ". " DELIMITED BY SIZE LAST-NAME DELIMITED BY SPACE INTO FULL-NAME POINTER NAME-POINTER ON OVERFLOW DISPLAY "String overflow occurred!" END-STRING. DISPLAY "Full Name: " FULL-NAME. DISPLAY "Pointer: " NAME-POINTER. DISPLAY " ". DISPLAY "UNSTRING Example:". INITIALIZE REC-LAST-NAME REC-FIRST-NAME REC-GENDER REC-ADDRESS REC-CITY FIELD-COUNT. UNSTRING CSV-DATA DELIMITED BY "," INTO REC-LAST-NAME REC-FIRST-NAME REC-GENDER REC-ADDRESS REC-CITY TALLYING IN FIELD-COUNT ON OVERFLOW DISPLAY "Unstring overflow!" END-UNSTRING. DISPLAY "Last Name: " REC-LAST-NAME. DISPLAY "First Name: " REC-FIRST-NAME. DISPLAY "Gender: " REC-GENDER. DISPLAY "Address: " REC-ADDRESS. DISPLAY "City: " REC-CITY. DISPLAY "Fields Unstrung: " FIELD-COUNT. STOP RUN.

INSPECT for Character-Level Transformation

The INSPECT statement is used to examine a data item and perform operations like counting occurrences of specific characters, replacing characters, or converting characters (e.g., lowercase to uppercase).

  • TALLYING: Counts occurrences of characters or substrings.
  • REPLACING: Replaces characters or substrings with others.
  • CONVERTING: Translates characters from one set to another (e.g., CONVERTING "abc" TO "XYZ").
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
IDENTIFICATION DIVISION. PROGRAM-ID. INSPECT-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 SAMPLE-TEXT PIC X(30) VALUE "COBOL is cool! COBOL is fun!". 01 CHAR-COUNT PIC 99 VALUE ZERO. 01 LOWER-CASE-TEXT PIC X(20) VALUE "example text". PROCEDURE DIVISION. INSPECT SAMPLE-TEXT TALLYING CHAR-COUNT FOR ALL "COBOL". DISPLAY "Occurrences of 'COBOL': " CHAR-COUNT. *> Output: 2 INSPECT SAMPLE-TEXT REPLACING ALL "cool" BY "great". DISPLAY "After REPLACING: " SAMPLE-TEXT. * Output: COBOL is great! COBOL is fun! INSPECT LOWER-CASE-TEXT CONVERTING "abcdefghijklmnopqrstuvwxyz" TO "ABCDEFGHIJKLMNOPQRSTUVWXYZ". DISPLAY "Uppercase Text: " LOWER-CASE-TEXT. * Output: EXAMPLE TEXT STOP RUN.

Using REDEFINES for Different Views of Data

The REDEFINES clause allows a single area of memory to be described by multiple data definitions. This is useful for interpreting the same data in different ways (e.g., as a single string or as a group of subfields) without moving it.

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
IDENTIFICATION DIVISION. PROGRAM-ID. REDEFINES-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 RAW-DATE-FIELD PIC X(8) VALUE "20231225". 01 FORMATTED-DATE REDEFINES RAW-DATE-FIELD. 05 FD-YEAR PIC 9(4). 05 FD-MONTH PIC 9(2). 05 FD-DAY PIC 9(2). 01 NUMERIC-GROUP. 05 PART-A PIC 9(3) VALUE 123. 05 PART-B PIC 9(2) VALUE 45. 01 COMBINED-NUM REDEFINES NUMERIC-GROUP PIC 9(5). PROCEDURE DIVISION. DISPLAY "Raw Date: " RAW-DATE-FIELD. DISPLAY "Year: " FD-YEAR " Month: " FD-MONTH " Day: " FD-DAY. * Output: Year: 2023 Month: 12 Day: 25 DISPLAY "Numeric Group: " PART-A PART-B. DISPLAY "Combined Numeric: " COMBINED-NUM. * Output: Combined Numeric: 12345 MOVE "10203" TO COMBINED-NUM. DISPLAY "After MOVE to COMBINED-NUM:". DISPLAY "PART-A: " PART-A " PART-B: " PART-B. * Output: PART-A: 102 PART-B: 03 STOP RUN.

Care must be taken with REDEFINES, especially with differing data types or USAGE clauses, as it can lead to alignment issues or misinterpretation if not handled correctly.

Conditional Logic (IF, EVALUATE) for Transformation

Often, data transformation depends on certain conditions. IF and EVALUATE statements are used to apply different transformation rules based on data values or other criteria.

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
IDENTIFICATION DIVISION. PROGRAM-ID. CONDITIONAL-TRANSFORM. DATA DIVISION. WORKING-STORAGE SECTION. 01 INPUT-CODE PIC X(1). 01 OUTPUT-DESCRIPTION PIC X(20). PROCEDURE DIVISION. MOVE "A" TO INPUT-CODE. PERFORM TRANSFORM-CODE. DISPLAY "Input: A, Output: " OUTPUT-DESCRIPTION. MOVE "B" TO INPUT-CODE. PERFORM TRANSFORM-CODE. DISPLAY "Input: B, Output: " OUTPUT-DESCRIPTION. MOVE "X" TO INPUT-CODE. PERFORM TRANSFORM-CODE. DISPLAY "Input: X, Output: " OUTPUT-DESCRIPTION. STOP RUN. TRANSFORM-CODE SECTION. EVALUATE INPUT-CODE WHEN "A" MOVE "Account Active" TO OUTPUT-DESCRIPTION WHEN "I" MOVE "Account Inactive" TO OUTPUT-DESCRIPTION WHEN "S" MOVE "Account Suspended" TO OUTPUT-DESCRIPTION WHEN OTHER MOVE "Unknown Code" TO OUTPUT-DESCRIPTION END-EVALUATE. EXIT.

Test Your Knowledge

1. What happens when a numeric value is moved to a larger numeric field in COBOL?

  • The value is right-justified and zero-filled
  • The value is left-justified and space-filled
  • The value is left-justified and zero-filled
  • The compiler reports an error

2. Which COBOL statement can be used to convert data from one type to another?

  • TRANSFORM
  • CONVERT
  • MOVE
  • CHANGE

3. What happens when you move a larger alphanumeric field to a smaller one?

  • The data is truncated from the right
  • The data is truncated from the left
  • An error occurs
  • The data is compressed to fit

4. Which of the following rounding methods is native to COBOL?

  • ROUNDED option with arithmetic operations
  • ROUND function
  • CEILING and FLOOR functions
  • All of the above

5. What is the primary purpose of the STRING statement in COBOL?

  • To convert numeric data to character strings
  • To compare string values
  • To combine multiple fields into one
  • To check if a field contains a specific string

Related Concepts

Data Types and Representation

Understanding how different data types are stored and handled in COBOL.

Learn more →

PICTURE Clause

Detailed guide on using the PIC clause to define data item characteristics.

Learn more →

Related Pages

Data Validation Techniques

Ensuring data integrity before manipulation.

Explore →

STRING and UNSTRING Operations

Advanced string handling in COBOL.

Explore →

Exercises