String Handling Statements
String handling statements are used to handle and manipulate strings. These statements are essential for processing textual data, allowing for modifications, evaluations, and extractions of character data within a COBOL program. They are -
- STRING
- UNSTRING
- INSPECT
STRING Statement
STRING statement concatenates two or more strings or literals into a single string and places them into a result variable. It enables the creation of a single string from multiple stings separated by delimiter. Concatenation requires a minimum of two variables or literals.
STRING source-item-1 [DELIMITED BY delimiter-1]
[source-item-2 DELIMITED BY delimiter-2] [...]
INTO destination-item
[ON OVERFLOW statements-block-1]
[NOT ON OVERFLOW statement-block-2]
[END-STRING].
- source-item - Specifies the variables that we want to concatenate.
- DELIMITED BY - Specifies the character to place at the end of the source item. If SIZE is used, it'll consider the entire variable.
- destination-item - Specifies the data item where the result will be placed after concatenation.
- ON OVERFLOW statements-block-1 - Specifies the statements block executed when ON OVERFLOW occurs.
- NOT ON OVERFLOW statement-block-2 - Specifies the statements block executed when the STRING operation is successful.
- END-STRING - Explicit scope terminator for the STRING statement.
Example - Concatenate two strings separated by space.
----+----1----+----2----+----3----+----4----+----5----
...
WORKING-STORAGE SECTION.
01 WS-OUTPUT PIC X(70).
...
PROCEDURE DIVISION.
STRING "Mainframestechhelp" DELIMITED BY SIZE,
SPACE,
"is a Mainframe Community" DELIMITED BY SIZE
INTO WS-OUTPUT
ON OVERFLOW DISPLAY "Error occured"
NOT ON OVERFLOW DISPLAY "Result: " WS-OUTPUT
END-STRING.
...
Output -
Result: Mainframestechhelp is a Mainframe Community
UNSTRING Statement
UNSTRING statement takes a single string, breaks it down into several separate strings, and places them into the variables. It breaks the strings into multiple stings based on the delimiter. It requires a minimum two receiving variables.
UNSTRING source-item
[DELIMITED BY delimiter1]
INTO target-item-1 [target-item-2 ...]
[TALLYING IN counter-name]
[ON OVERFLOW statements-block-1]
[NOT ON OVERFLOW statements-block-2]
[END-UNSTRING].
- source-string - Specifies the input string that we want to break down.
- DELIMITED BY delimiter1 - The delimiter1 is used to specify where to split the string. If it's not coded, then each character is considered separately.
- INTO target-item-1 [target-item-2 ...] - Specifies the target variables where the divided strings should be placed.
- TALLYING IN - Count the number of characters transferred to the target items.
- ON OVERFLOW statements-block-1 - Specifies the statements block executed when ON OVERFLOW occurs.
- NOT ON OVERFLOW statement-block-2 - Specifies the statements block executed when the STRING operation is successful.
- END-UNSTRING - Explicit scope terminator for the UNSTRING statement.
Example - Split the string into two strings.
----+----1----+----2----+----3----+----4----+----5----
...
WORKING-STORAGE SECTION.
01 WS-VAR.
05 WS-INPUT PIC X(70) VALUE
"Mainframestechhelp, is a Mainframe Community".
05 WS-OUTPUT1 PIC X(30).
05 WS-OUTPUT2 PIC X(40).
...
PROCEDURE DIVISION.
UNSTRING WS-INPUT DELIMITED BY ","
INTO WS-OUTPUT1, WS-OUTPUT2
ON OVERFLOW DISPLAY "ERROR OCCURED"
NOT ON OVERFLOW
DISPLAY "WS-OUTPUT1: ", WS-OUTPUT1
DISPLAY "WS-OUTPUT2: ", WS-OUTPUT2
END-UNSTRING.
...
Output -
WS-OUTPUT1: MAINFRAMESTECHHELP WS-OUTPUT2: IS A MAINFRAME COMMUNITY
INSPECT Statement
INSPECT statement analyzes, counts, or replaces specific character(s) within a string. It is flexible and provides a range of functions to help with string manipulations. It has four formats -
- INSPECT...TALLYING
- INSPECT...REPLACING
- INSPECT...TALLYING...REPLACING
- INSPECT CONVERTING
INSPECT...TALLYING -
INSPECT TALLYING counts the occurrences of the specific characters in the input string. It is an efficient way to decide how many times a particular character appears within a string.
INSPECT ws-input-string
TALLYING ws-tally-count
FOR [ALL|LEADING] {CHARACTERS|ws-tally-chars}
- ws-input-string - Specifies the input string or variable.
- ws-tally-count - A numeric variable where the count is stored.
- FOR CHARACTERS - Each character is counted.
- ws-tally-char - Specifies the characters that should find the number of occurrences in the count ws-input-string.
- ALL - Each occurrence of ws-tally-char is counted.
- LEADING - leftmost occurrence of ws-tally-chars is counted.
Examples -
Scenario - Counting for ALL character "A".
Input- WS-DATA = "MAINFRAMES" Declaration- 05 WS-DATA PIC X(10) VALUE "MAINFRAMES". 05 WS-CNT PIC 9(02). Code- INSPECT WS-DATA TALLYING WS-CNT FOR ALL "A". Result- WS-CNT = 2
INSPECT...REPLACING -
INSPECT...REPLACING replaces the replacing characters with the replaced characters in the input string. It's a way to replace all instances of certain characters with target characters.
INSPECT ws-input-string
REPLACING [ALL|LEADING|FIRST] {CHARACTERS|ws-replaced-char}
BY ws-replacing-char
- ws-replaced-char - Specifies the characters in string to replace.
- ws-replacing-char - Specifies the characters that replaces ws-replaced-char.
- ALL CHARACTERS - Replace each occurrence of character with a ws-replacing-char.
- LEADING - Replaces leftmost occurrence of ws-replaced-char by ws-replacing-char.
- FIRST - Replaces the leftmost first occurrence of ws-replaced-char by ws-replacing-char.
Examples -
Scenario - Replace all "-" with "/".
Input- WS-DATA = "DD-MM-YYYY" Declaration- 05 WS-DATA PIC X(10) VALUE "DD-MM-YYYY". Code- INSPECT WS-DATA REPLACING ALL "-" BY "/". Result- WS-DATA = "DD/MM/YYYY"
INSPECT...TALLYING...REPLACING -
INSPECT TALLYING REPLACING counts the occurrences of the specific characters and replaces them with new characters. It performs the TALLYING operation first and REPLACING next.
INSPECT ws-input-string
TALLYING ws-tally-count
FOR [ALL|LEADING] {CHARACTERS|ws-tally-chars}
REPLACING [ALL|LEADING|FIRST] {CHARACTERS|ws-replaced-char}
BY ws-replacing-char
Examples -
Scenario - Count for no of characters and Replace them with "&".
Input- WS-DATA = "DD-MM-YYYY" Declaration- 05 WS-DATA PIC X(10) VALUE "DD-MM-YYYY". 05 WS-CNT PIC 9(02) VALUE ZEROES. Code- INSPECT WS-DATA TALLYING WS-CNT FOR CHARACTERS REPLACING CHARACTERS BY "&". Result- WS-CNT = 10 WS-DATA = "&&&&&&&&&&"
In the above case, WS-DATA has 10 characters. So the count result is 10 and replaces all characters with "&". The result is "&&&&&&&&&&".
INSPECT...CONVERTING -
INSPECT...CONVERTING performs character conversion in a variable. It's a way to convert all instances of certain characters with other characters.
INSPECT ws-input-string
CONVERTING ws-char-1 .... char-n
TO char-a ... char-z
[[BEFORE | AFTER] [INITIAL] ws-delimeter].
- char-1 ... char-n - Specifies the character(s) we're searching for.
- char-a ... char-z - specifies the character(s) that will replace the characters char-1 ... char-n during the conversion.
Examples -
Scenario - Conveting all uppercase characters to lowercase.
Input- WS-DATA = "MAINFRAMES" Declaration- 05 WS-DATA PIC X(10) VALUE "MAINFRAMES". Code- INSPECT WS-DATA CONVERTING "ABCDEFGHIJKLMNOPQRSTUVWXYZ" TO "abcdefghijklmnopqrstuvwxyz". Result- WS-DATA = "mainframes"
The first character, 'M', converts to its equal character, 'm'. In the second iteration, the second character, 'A', converts to its equal character, 'a'. Similarly, every character is converted with its equal characters. The result is 'mainframes'.