MainframeMaster

COBOL Tutorial

COBOL STRING and UNSTRING Operations

Progress0 of 0 lessons

STRING Statement Syntax and Usage

The STRING statement in COBOL provides a powerful way to concatenate multiple strings into a single string with precise control over the process. This ability to combine strings is essential for building formatted messages, report lines, data for display, or any situation requiring text assembly from various sources.

Basic STRING Syntax

cobol
1
2
3
4
5
6
7
STRING {identifier-1|literal-1} [DELIMITED BY {identifier-2|literal-2|SIZE}] [{identifier-3|literal-3} [DELIMITED BY {identifier-4|literal-4|SIZE}]] ... INTO identifier-5 [WITH POINTER identifier-6] [ON OVERFLOW imperative-statement-1] [NOT ON OVERFLOW imperative-statement-2] [END-STRING]

  • identifier-1, literal-1, etc. - Source fields to be concatenated
  • DELIMITED BY - Controls how much of each source field is used
  • SIZE - Special keyword indicating the entire field should be used
  • INTO identifier-5 - Destination field that will receive the concatenated result
  • WITH POINTER - Controls starting position in the receiving field
  • ON OVERFLOW - Actions to take if the receiving field is too small
  • END-STRING - Explicit scope terminator (required in some contexts)

Simple STRING Example

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. STRINGSAMPLE. DATA DIVISION. WORKING-STORAGE SECTION. 01 FIRST-NAME PIC X(10) VALUE "John". 01 LAST-NAME PIC X(15) VALUE "Smith". 01 FULL-NAME PIC X(30) VALUE SPACES. 01 GREETING-MSG PIC X(50) VALUE SPACES. PROCEDURE DIVISION. MAIN-PARA. * Basic concatenation of first and last name with a space between STRING FIRST-NAME DELIMITED BY SIZE " " DELIMITED BY SIZE LAST-NAME DELIMITED BY SIZE INTO FULL-NAME END-STRING DISPLAY "Full name: " FULL-NAME * Using the result in another STRING operation STRING "Hello, " DELIMITED BY SIZE FULL-NAME DELIMITED BY SIZE "! How are you today?" DELIMITED BY SIZE INTO GREETING-MSG END-STRING DISPLAY GREETING-MSG STOP RUN.

This example demonstrates basic string concatenation. First, it combines a first and last name with a space between them, and then uses that result to build a greeting message. The DELIMITED BY SIZE clause ensures each field is used in its entirety.

The DELIMITED BY Clause

The DELIMITED BY clause provides fine-grained control over how much of each source field is included in the concatenation. It can use specific delimiters or the special keyword SIZE.

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
* Example of different DELIMITED BY options 01 PRODUCT-CODE PIC X(10) VALUE "ABC123****". 01 CUSTOMER-INFO PIC X(20) VALUE "SMITH,JOHN,ACTIVE". 01 RESULT-FIELD PIC X(50) VALUE SPACES. 01 TEMP-FIELD PIC X(50) VALUE SPACES. * Using SIZE - takes the entire field STRING PRODUCT-CODE DELIMITED BY SIZE INTO RESULT-FIELD END-STRING * Result: "ABC123****" * Using a specific delimiter - stops at the first occurrence STRING PRODUCT-CODE DELIMITED BY "*" INTO RESULT-FIELD END-STRING * Result: "ABC123" * Using a space delimiter 01 TEXT-WITH-SPACES PIC X(20) VALUE "Hello world example". STRING TEXT-WITH-SPACES DELIMITED BY SPACE INTO TEMP-FIELD END-STRING * Result: "Hello" * Using multiple fields with different delimiters STRING PRODUCT-CODE DELIMITED BY "*" " - " DELIMITED BY SIZE CUSTOMER-INFO DELIMITED BY "," INTO RESULT-FIELD END-STRING * Result: "ABC123 - SMITH"

  • DELIMITED BY SIZE - Uses the entire field (up to any trailing spaces for alphanumeric fields)
  • DELIMITED BY literal - Stops at the first occurrence of the specified delimiter
  • DELIMITED BY identifier - Uses the contents of the identifier as the delimiter
  • The delimiter itself is not included in the result
  • If the delimiter is not found, the entire field is used (same as SIZE)

Using the POINTER Clause

The POINTER clause lets you control where in the receiving field the concatenation begins, and it's automatically updated as the operation progresses.

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
* Example using the POINTER clause 01 OUTPUT-AREA PIC X(100) VALUE SPACES. 01 START-POS PIC 9(3) VALUE 1. 01 HEADER-TEXT PIC X(20) VALUE "Customer Report - ". 01 CURRENT-DATE PIC X(10) VALUE "2023/05/15". * Basic pointer usage STRING HEADER-TEXT DELIMITED BY SIZE CURRENT-DATE DELIMITED BY SIZE INTO OUTPUT-AREA WITH POINTER START-POS END-STRING DISPLAY "Result: " OUTPUT-AREA DISPLAY "New pointer position: " START-POS * Using the updated pointer for further concatenation STRING ": Page 1" DELIMITED BY SIZE INTO OUTPUT-AREA WITH POINTER START-POS END-STRING DISPLAY "Final result: " OUTPUT-AREA DISPLAY "Final pointer position: " START-POS * Using pointer to position within the field MOVE 10 TO START-POS STRING "**INSERTED**" DELIMITED BY SIZE INTO OUTPUT-AREA WITH POINTER START-POS END-STRING DISPLAY "After insertion: " OUTPUT-AREA

Key points about the POINTER clause:

  • The pointer must be initialized before the STRING operation
  • It controls where in the receiving field the concatenation starts
  • After the operation, it contains the position following the last character moved
  • You can use the updated pointer value in subsequent STRING operations
  • If the pointer is outside the receiving field's bounds, an overflow condition occurs

Handling Overflow Conditions

The ON OVERFLOW clause allows you to handle situations where the receiving field is not large enough to hold the entire concatenated result.

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
* Example of overflow handling 01 SMALL-FIELD PIC X(15) VALUE SPACES. 01 LONG-TEXT PIC X(50) VALUE "This is a very long text that will not fit in the small field". 01 OVERFLOW-FLAG PIC X VALUE "N". 88 OVERFLOW-OCCURRED VALUE "Y". * Without overflow handling - truncation occurs silently STRING LONG-TEXT DELIMITED BY SIZE INTO SMALL-FIELD END-STRING DISPLAY "Without overflow handling: " SMALL-FIELD * With overflow handling STRING LONG-TEXT DELIMITED BY SIZE INTO SMALL-FIELD ON OVERFLOW MOVE "Y" TO OVERFLOW-FLAG DISPLAY "Overflow occurred!" END-STRING DISPLAY "With overflow handling: " SMALL-FIELD DISPLAY "Overflow flag: " OVERFLOW-FLAG * Using NOT ON OVERFLOW MOVE SPACES TO SMALL-FIELD STRING "Short text" DELIMITED BY SIZE INTO SMALL-FIELD ON OVERFLOW DISPLAY "Overflow occurred (not expected)" NOT ON OVERFLOW DISPLAY "Operation completed without overflow" END-STRING

  • Without ON OVERFLOW, the STRING operation will silently truncate when the receiving field is full
  • The ON OVERFLOW condition is triggered when the receiving field is filled before all source data is processed
  • It's also triggered if the POINTER value is less than 1 or greater than the receiving field size
  • The NOT ON OVERFLOW clause executes when the operation completes without an overflow
  • Always include ON OVERFLOW handling for robust error detection

Practical Applications of STRING

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
* Building formatted report lines 01 REPORT-LINE PIC X(80) VALUE SPACES. 01 LINE-POS PIC 9(2) VALUE 1. 01 PRODUCT-INFO. 05 PROD-ID PIC X(5) VALUE "P1234". 05 PROD-NAME PIC X(20) VALUE "Deluxe Widget". 05 PROD-PRICE PIC 9(4)V99 VALUE 24.99. 05 PROD-PRICE-DISPLAY PIC Z,ZZ9.99. * Format the numeric price for display MOVE PROD-PRICE TO PROD-PRICE-DISPLAY * Build the report line with proper alignment MOVE 1 TO LINE-POS STRING PROD-ID DELIMITED BY SIZE INTO REPORT-LINE WITH POINTER LINE-POS END-STRING MOVE 10 TO LINE-POS STRING PROD-NAME DELIMITED BY SIZE INTO REPORT-LINE WITH POINTER LINE-POS END-STRING MOVE 35 TO LINE-POS STRING "$" DELIMITED BY SIZE PROD-PRICE-DISPLAY DELIMITED BY SIZE INTO REPORT-LINE WITH POINTER LINE-POS END-STRING DISPLAY REPORT-LINE * Building formatted addresses 01 CUSTOMER-ADDRESS. 05 STREET PIC X(25) VALUE "123 Main Street". 05 CITY PIC X(15) VALUE "Springfield". 05 STATE PIC XX VALUE "IL". 05 ZIP PIC X(10) VALUE "62701". 01 FORMATTED-ADDRESS PIC X(80) VALUE SPACES. STRING STREET DELIMITED BY SIZE ", " DELIMITED BY SIZE CITY DELIMITED BY SIZE ", " DELIMITED BY SIZE STATE DELIMITED BY SIZE " " DELIMITED BY SIZE ZIP DELIMITED BY SIZE INTO FORMATTED-ADDRESS END-STRING DISPLAY FORMATTED-ADDRESS * "123 Main Street, Springfield, IL 62701"

These examples demonstrate practical applications of the STRING statement, including:

  • Building formatted report lines with precise column positioning
  • Formatting addresses for display or printing
  • Combining data from various fields with appropriate separators
  • Controlling the exact layout of text data

Best Practices for STRING Operations

  • Always initialize the receiving field (typically to SPACES) before using STRING
  • Always include the ON OVERFLOW clause to detect when the receiving field is too small
  • Consider the trailing space behavior in alphanumeric fields when using DELIMITED BY SIZE
  • Initialize POINTER values before using them in STRING operations
  • Use reference modification or DELIMITED BY to control exactly which portions of fields are used
  • For complex formatting, break down the operation into multiple STRING statements
  • When building report lines, use the POINTER clause for precise column positioning
  • Include the END-STRING scope terminator for better readability and to avoid scope confusion
  • Test STRING operations with edge cases, especially for boundary conditions
  • Consider the performance impact of complex STRING operations in high-volume processing

UNSTRING Statement for String Parsing

The UNSTRING statement is the counterpart to STRING, designed to break down a single string into multiple substrings. It's an essential tool for parsing input data, extracting specific parts of a string, or breaking down complex formatted text into its component parts.

Basic UNSTRING Syntax

cobol
1
2
3
4
5
6
7
8
UNSTRING identifier-1 [DELIMITED BY [ALL] {identifier-2|literal-1} [OR [ALL] {identifier-3|literal-2}]...] INTO {identifier-4 [DELIMITER IN identifier-5] [COUNT IN identifier-6]}... [WITH POINTER identifier-7] [TALLYING IN identifier-8] [ON OVERFLOW imperative-statement-1] [NOT ON OVERFLOW imperative-statement-2] [END-UNSTRING]

  • identifier-1 - The source string to be parsed
  • DELIMITED BY - Specifies the delimiters that separate the substrings
  • ALL - Treats consecutive occurrences of the delimiter as a single delimiter
  • INTO - Specifies the receiving fields for the substrings
  • DELIMITER IN - Stores the delimiter that ended a substring
  • COUNT IN - Stores the length of a substring
  • WITH POINTER - Controls the starting position in the source string
  • TALLYING IN - Counts the number of fields parsed
  • ON OVERFLOW - Actions when more data exists than receiving fields can handle
  • END-UNSTRING - Explicit scope terminator

Simple UNSTRING Example

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
IDENTIFICATION DIVISION. PROGRAM-ID. UNSTRINGSAMPLE. DATA DIVISION. WORKING-STORAGE SECTION. 01 FULL-NAME PIC X(30) VALUE "Smith,John,Robert". 01 NAME-PARTS. 05 LAST-NAME PIC X(15) VALUE SPACES. 05 FIRST-NAME PIC X(10) VALUE SPACES. 05 MIDDLE-NAME PIC X(10) VALUE SPACES. 01 DELIMITER-USED PIC X VALUE SPACE. PROCEDURE DIVISION. MAIN-PARA. * Basic parsing of a comma-separated name UNSTRING FULL-NAME DELIMITED BY "," INTO LAST-NAME FIRST-NAME MIDDLE-NAME END-UNSTRING DISPLAY "Last name: " LAST-NAME DISPLAY "First name: " FIRST-NAME DISPLAY "Middle name: " MIDDLE-NAME * Parsing with additional options UNSTRING FULL-NAME DELIMITED BY "," INTO LAST-NAME DELIMITER IN DELIMITER-USED FIRST-NAME MIDDLE-NAME END-UNSTRING DISPLAY "Delimiter used: '" DELIMITER-USED "'" STOP RUN.

This example demonstrates basic string parsing using UNSTRING. It breaks down a full name with comma separators into last, first, and middle names. The second example also captures the delimiter that was used.

DELIMITED BY Options

The DELIMITED BY clause in UNSTRING determines how the source string should be broken down. You can specify multiple delimiters and control how consecutive delimiters are handled.

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
* Examples of different DELIMITED BY options 01 CSV-RECORD PIC X(50) VALUE "Smith,42,Active,12/15/2022". 01 DATA-ITEMS. 05 NAME-FIELD PIC X(15) VALUE SPACES. 05 AGE-FIELD PIC X(5) VALUE SPACES. 05 STATUS-FIELD PIC X(10) VALUE SPACES. 05 DATE-FIELD PIC X(15) VALUE SPACES. 01 PHONE-NUMBER PIC X(20) VALUE "(555) 123-4567". 01 PHONE-PARTS. 05 AREA-CODE PIC X(5) VALUE SPACES. 05 PREFIX PIC X(5) VALUE SPACES. 05 LINE-NUMBER PIC X(5) VALUE SPACES. * Basic delimiter UNSTRING CSV-RECORD DELIMITED BY "," INTO NAME-FIELD AGE-FIELD STATUS-FIELD DATE-FIELD END-UNSTRING * Multiple delimiters with OR UNSTRING PHONE-NUMBER DELIMITED BY "(" OR ")" OR " " OR "-" INTO AREA-CODE PREFIX LINE-NUMBER END-UNSTRING * Using the ALL option 01 TEXT-WITH-SPACES PIC X(30) VALUE "This has multiple spaces". 01 WORD-ARRAY OCCURS 5 TIMES PIC X(10). UNSTRING TEXT-WITH-SPACES DELIMITED BY ALL SPACE INTO WORD-ARRAY(1) WORD-ARRAY(2) WORD-ARRAY(3) WORD-ARRAY(4) END-UNSTRING * Results: * WORD-ARRAY(1): "This" * WORD-ARRAY(2): "has" * WORD-ARRAY(3): "multiple" * WORD-ARRAY(4): "spaces"

  • DELIMITED BY literal - Uses the specified character(s) as a delimiter
  • DELIMITED BY identifier - Uses the contents of the identifier as a delimiter
  • DELIMITED BY OR - Allows multiple delimiter options (any will be recognized)
  • DELIMITED BY ALL - Treats consecutive occurrences of the delimiter as one
  • Without ALL, each delimiter creates a separate field (potentially empty)
  • Without a DELIMITED BY clause, the entire source field is moved to the first INTO field

Additional UNSTRING Options

UNSTRING provides several additional options for capturing more information about the parsing process.

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
* Example with COUNT IN, DELIMITER IN, and TALLYING 01 RECORD-TEXT PIC X(50) VALUE "Smith:42:Active:12/15/2022". 01 FIELD-COUNTS. 05 NAME-COUNT PIC 99 VALUE ZERO. 05 AGE-COUNT PIC 99 VALUE ZERO. 05 STATUS-COUNT PIC 99 VALUE ZERO. 05 DATE-COUNT PIC 99 VALUE ZERO. 01 FIELD-DELIMITERS. 05 NAME-DELIM PIC X VALUE SPACE. 05 AGE-DELIM PIC X VALUE SPACE. 05 STATUS-DELIM PIC X VALUE SPACE. 01 TOTAL-FIELDS PIC 99 VALUE ZERO. 01 DATA-FIELDS. 05 NAME-FIELD PIC X(15) VALUE SPACES. 05 AGE-FIELD PIC X(5) VALUE SPACES. 05 STATUS-FIELD PIC X(10) VALUE SPACES. 05 DATE-FIELD PIC X(15) VALUE SPACES. UNSTRING RECORD-TEXT DELIMITED BY ":" INTO NAME-FIELD DELIMITER IN NAME-DELIM COUNT IN NAME-COUNT AGE-FIELD DELIMITER IN AGE-DELIM COUNT IN AGE-COUNT STATUS-FIELD DELIMITER IN STATUS-DELIM COUNT IN STATUS-COUNT DATE-FIELD COUNT IN DATE-COUNT TALLYING IN TOTAL-FIELDS END-UNSTRING DISPLAY "Fields processed: " TOTAL-FIELDS DISPLAY "Name: " NAME-FIELD " (Length: " NAME-COUNT ")" DISPLAY "Age: " AGE-FIELD " (Length: " AGE-COUNT ")" DISPLAY "Status: " STATUS-FIELD " (Length: " STATUS-COUNT ")" DISPLAY "Date: " DATE-FIELD " (Length: " DATE-COUNT ")" DISPLAY "Delimiters: '" NAME-DELIM "', '" AGE-DELIM "', '" STATUS-DELIM "'"

Key features demonstrated:

  • COUNT IN - Records the length of each extracted substring
  • DELIMITER IN - Captures the delimiter that terminated each substring
  • TALLYING IN - Counts the total number of receiving fields that received data
  • These options provide valuable metadata about the parsing operation
  • The COUNT IN value does not include trailing spaces for alphanumeric fields

Using the WITH POINTER Option

The WITH POINTER clause in UNSTRING allows you to control where parsing begins in the source string and tracks the position after parsing is complete.

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
* Example using the WITH POINTER clause 01 COMPLEX-DATA PIC X(50) VALUE "Header:Smith,Jones,Brown:Footer". 01 POSITION-PTR PIC 99 VALUE 1. 01 NAME-LIST. 05 NAME1 PIC X(10) VALUE SPACES. 05 NAME2 PIC X(10) VALUE SPACES. 05 NAME3 PIC X(10) VALUE SPACES. 01 HEADER-FIELD PIC X(10) VALUE SPACES. 01 FOOTER-FIELD PIC X(10) VALUE SPACES. * Extract the header UNSTRING COMPLEX-DATA DELIMITED BY ":" INTO HEADER-FIELD WITH POINTER POSITION-PTR END-UNSTRING DISPLAY "Header: " HEADER-FIELD DISPLAY "Current position: " POSITION-PTR * Extract the name list UNSTRING COMPLEX-DATA DELIMITED BY "," OR ":" INTO NAME1 NAME2 NAME3 WITH POINTER POSITION-PTR END-UNSTRING DISPLAY "Names: " NAME1 ", " NAME2 ", " NAME3 DISPLAY "Current position: " POSITION-PTR * Extract the footer UNSTRING COMPLEX-DATA DELIMITED BY SIZE INTO FOOTER-FIELD WITH POINTER POSITION-PTR END-UNSTRING DISPLAY "Footer: " FOOTER-FIELD DISPLAY "Final position: " POSITION-PTR

  • The POINTER must be initialized before the UNSTRING operation (typically to 1)
  • It specifies the character position in the source field where parsing begins
  • After UNSTRING completes, it contains the position after the last character processed
  • Multiple UNSTRING operations can use the same POINTER to continue parsing from where the previous operation left off
  • If the POINTER value is invalid (less than 1 or greater than the source length), an overflow condition occurs

Handling Overflow Conditions

Overflow handling is crucial in UNSTRING operations to manage situations where there are more substrings in the source field than there are receiving fields to hold them.

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
* Example of overflow handling in UNSTRING 01 COMMA-LIST PIC X(50) VALUE "Apple,Orange,Banana,Grape,Peach". 01 FRUIT-ARRAY. 05 FRUIT1 PIC X(10) VALUE SPACES. 05 FRUIT2 PIC X(10) VALUE SPACES. 05 FRUIT3 PIC X(10) VALUE SPACES. 01 OVERFLOW-FLAG PIC X VALUE "N". * Without overflow handling UNSTRING COMMA-LIST DELIMITED BY "," INTO FRUIT1 FRUIT2 FRUIT3 END-UNSTRING DISPLAY "Without overflow handling:" DISPLAY "Fruit1: " FRUIT1 DISPLAY "Fruit2: " FRUIT2 DISPLAY "Fruit3: " FRUIT3 * Note: Grape and Peach are lost without warning * With overflow handling MOVE "N" TO OVERFLOW-FLAG MOVE SPACES TO FRUIT1, FRUIT2, FRUIT3 UNSTRING COMMA-LIST DELIMITED BY "," INTO FRUIT1 FRUIT2 FRUIT3 ON OVERFLOW MOVE "Y" TO OVERFLOW-FLAG DISPLAY "Warning: Not all data was processed" END-UNSTRING DISPLAY "With overflow handling:" DISPLAY "Fruit1: " FRUIT1 DISPLAY "Fruit2: " FRUIT2 DISPLAY "Fruit3: " FRUIT3 DISPLAY "Overflow occurred: " OVERFLOW-FLAG * Using NOT ON OVERFLOW UNSTRING "A,B" DELIMITED BY "," INTO FRUIT1 FRUIT2 FRUIT3 ON OVERFLOW DISPLAY "Overflow occurred (not expected)" NOT ON OVERFLOW DISPLAY "All data was processed without overflow" END-UNSTRING

  • Without ON OVERFLOW, the UNSTRING operation silently discards extra data after filling all receiving fields
  • The ON OVERFLOW condition is triggered when there are more substrings than receiving fields
  • It's also triggered if the POINTER value is less than 1 or greater than the source field size
  • The NOT ON OVERFLOW clause executes when all substrings are successfully processed
  • Always include ON OVERFLOW handling for data integrity

Practical Applications of UNSTRING

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
* Parsing CSV data 01 CSV-RECORD PIC X(100) VALUE "1234,Smith,John,42,Sales,65000". 01 CSV-FIELDS. 05 ID-FIELD PIC X(10) VALUE SPACES. 05 LAST-NAME PIC X(15) VALUE SPACES. 05 FIRST-NAME PIC X(15) VALUE SPACES. 05 AGE PIC X(5) VALUE SPACES. 05 DEPT PIC X(15) VALUE SPACES. 05 SALARY PIC X(10) VALUE SPACES. UNSTRING CSV-RECORD DELIMITED BY "," INTO ID-FIELD LAST-NAME FIRST-NAME AGE DEPT SALARY END-UNSTRING * Parsing a date/time string 01 DATE-TIME-STAMP PIC X(20) VALUE "2023-05-15 14:30:45". 01 DATE-PARTS. 05 YEAR-PART PIC X(4) VALUE SPACES. 05 MONTH-PART PIC X(2) VALUE SPACES. 05 DAY-PART PIC X(2) VALUE SPACES. 01 TIME-PARTS. 05 HOUR-PART PIC X(2) VALUE SPACES. 05 MINUTE-PART PIC X(2) VALUE SPACES. 05 SECOND-PART PIC X(2) VALUE SPACES. 01 WORK-PTR PIC 99 VALUE 1. * First parse the date portion UNSTRING DATE-TIME-STAMP DELIMITED BY "-" OR " " INTO YEAR-PART MONTH-PART DAY-PART WITH POINTER WORK-PTR END-UNSTRING * Then parse the time portion UNSTRING DATE-TIME-STAMP DELIMITED BY ":" INTO HOUR-PART MINUTE-PART SECOND-PART WITH POINTER WORK-PTR END-UNSTRING * Parsing a fixed-position report line 01 REPORT-LINE PIC X(50) VALUE "P1234 Deluxe Widget 24.99 10 249.90". 01 PRODUCT-DETAILS. 05 PROD-ID PIC X(8) VALUE SPACES. 05 PROD-NAME PIC X(20) VALUE SPACES. 05 UNIT-PRICE PIC X(8) VALUE SPACES. 05 QUANTITY PIC X(4) VALUE SPACES. 05 TOTAL-PRICE PIC X(8) VALUE SPACES. UNSTRING REPORT-LINE INTO PROD-ID PROD-NAME UNIT-PRICE QUANTITY TOTAL-PRICE END-UNSTRING

These examples demonstrate practical applications of the UNSTRING statement, including:

  • Parsing comma-separated values (CSV) data
  • Breaking down complex date and time strings
  • Extracting fields from fixed-width report lines
  • Processing multiple parts of a string in sequence with the POINTER option
  • Parsing mixed format data with different delimiters

Best Practices for UNSTRING Operations

  • Initialize receiving fields (typically to SPACES) before using UNSTRING
  • Always include the ON OVERFLOW clause to detect when there are more substrings than receiving fields
  • Use the TALLYING IN option to verify how many fields were actually processed
  • When parsing complex strings, consider using multiple UNSTRING operations with the WITH POINTER option
  • Use the ALL keyword when dealing with data that might have consecutive delimiters
  • Use DELIMITER IN when you need to know which delimiter terminated each field
  • Use COUNT IN when you need to know the exact length of each extracted substring
  • For complex parsing, break down the operation into multiple UNSTRING statements
  • Include the END-UNSTRING scope terminator for better readability
  • Test UNSTRING operations with edge cases, including empty fields and missing delimiters

Comparing STRING and UNSTRING

STRING and UNSTRING are complementary operations for string manipulation in COBOL. Understanding their similarities and differences helps in choosing the right tool for the job.

Feature Comparison

FeatureSTRINGUNSTRING
Primary PurposeConcatenate multiple fields into oneSplit one field into multiple fields
DirectionMany-to-oneOne-to-many
Delimiter HandlingDELIMITED BY controls how much of each sending field is usedDELIMITED BY specifies separators between substrings
Position ControlWITH POINTERWITH POINTER
Overflow ConditionReceiving field too smallMore substrings than receiving fields
CountingNo direct counting optionTALLYING IN counts fields processed
Delimiter CaptureNot availableDELIMITER IN captures delimiters
Length CaptureNot availableCOUNT IN captures substring lengths
Special FeaturesSIZE option for full field usageALL option for consecutive delimiters

Common Workflows: STRING to UNSTRING and Back

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
* Example of using STRING and UNSTRING together IDENTIFICATION DIVISION. PROGRAM-ID. STRINGUNSTRING. DATA DIVISION. WORKING-STORAGE SECTION. 01 EMPLOYEE-DETAILS. 05 EMP-ID PIC X(5) VALUE "12345". 05 EMP-NAME PIC X(20) VALUE "Smith, John". 05 EMP-DEPT PIC X(10) VALUE "IT". 05 EMP-SALARY PIC 9(6) VALUE 65000. 01 SALARY-DISPLAY PIC $ZZ,ZZ9. 01 COMBINED-RECORD PIC X(50) VALUE SPACES. 01 DELIMITER PIC X VALUE "|". 01 PARSED-FIELDS. 05 ID-FIELD PIC X(5) VALUE SPACES. 05 NAME-FIELD PIC X(20) VALUE SPACES. 05 DEPT-FIELD PIC X(10) VALUE SPACES. 05 SALARY-FIELD PIC X(10) VALUE SPACES. PROCEDURE DIVISION. MAIN-PARA. * Format the salary for display MOVE EMP-SALARY TO SALARY-DISPLAY * STRING - Combine fields into a delimited record STRING EMP-ID DELIMITED BY SIZE DELIMITER DELIMITED BY SIZE EMP-NAME DELIMITED BY SIZE DELIMITER DELIMITED BY SIZE EMP-DEPT DELIMITED BY SIZE DELIMITER DELIMITED BY SIZE SALARY-DISPLAY DELIMITED BY SIZE INTO COMBINED-RECORD END-STRING DISPLAY "Combined record: " COMBINED-RECORD * UNSTRING - Parse the record back into individual fields UNSTRING COMBINED-RECORD DELIMITED BY "|" INTO ID-FIELD NAME-FIELD DEPT-FIELD SALARY-FIELD END-UNSTRING DISPLAY "Parsed ID: " ID-FIELD DISPLAY "Parsed Name: " NAME-FIELD DISPLAY "Parsed Dept: " DEPT-FIELD DISPLAY "Parsed Salary: " SALARY-FIELD STOP RUN.

This example demonstrates a common workflow:

  • Using STRING to create a delimited record (similar to CSV creation)
  • Using UNSTRING to parse the delimited record back into its components
  • This pattern is common in file processing, data interchange, and message handling
  • The same delimiter ("|") is used in both operations for consistency

Test Your Knowledge

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

  • To search for strings in a data item
  • To concatenate multiple strings into a single data item
  • To create arrays of strings
  • To compare two strings for equality

2. What is the function of the DELIMITED BY phrase in the STRING statement?

  • It specifies where to begin storing the result
  • It defines how much of each sending field should be moved
  • It determines the maximum size of the receiving field
  • It sets the number of iterations for string processing

3. What happens when you include the POINTER phrase in the STRING statement?

  • It returns the memory address of the receiving field
  • It tracks the position where the next sending value will be placed
  • It points to the size of the resulting field
  • It counts the number of fields processed

4. What is the primary purpose of the UNSTRING statement?

  • To initialize string fields to spaces
  • To compare two strings character by character
  • To split a single string into multiple substrings
  • To remove specified characters from a string

5. How is the TALLYING phrase used in the UNSTRING statement?

  • To count the total length of the sending field
  • To limit the number of characters processed
  • To count the number of times the delimiter appears
  • To count the number of receiving fields that receive data

Frequently Asked Questions