String Handling Statements
The string handling statements that manage and manipulate strings or character sequences. The main statements for string handling in COBOL are -
- STRING
- UNSTRING
- INSPECT
These statements are essential for processing textual data, allowing for modifications, evaluations, and extractions of character data within a COBOL program.
STRING -
The STRING statement is used to concatenate the contents of two or more data item or literals into a single data item. It enables the construction of strings by combining separate pieces of data together. STRING requires a minimum of two variables or literals to concatenate.
STRING source-item-1 [DELIMITED BY delimiter-1]
[source-item-2 DELIMITED BY delimiter-2] [...]
INTO destination-item
[WITH POINTER pointer-name]
[ON OVERFLOW statements-block-1]
[NOT ON OVERFLOW statement-block-2]
[END-STRING].
- source-item - These are the variables that we want to concatenate. We can string together multiple source items.
- DELIMITED BY - This clause specifies the delimiter that specifies the end of each source item. If we use SIZE, it'll consider the whole variable.
- destination-item - This is the result of the concatenation. It's where the stringed data will be stored.
- WITH POINTER pointer-name - Optional. Sets before the stringing process and can be checked afterward.
- ON OVERFLOW statements-block-1 - Specifies the set of statements that are executed when ON OVERFLOW occurs.
- NOT ON OVERFLOW statement-block-2 - Specifies the set of statements that are executed when the STRING operation is successful.
- END-STRING - This is the explicit scope terminator for the STRING statement.
Example - Concatenate two strings separated by space.
IDENTIFICATION DIVISION.
PROGRAM-ID. STRINGE.
DATA DIVISION.
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.
STOP RUN.
Output -
Result: MAINFRAMESTECHHELP IS A MAINFRAME COMMUNITY
Explaining Example -
In the above example, two strings are concatenated by separating a space between them and storing them in the WS-OUTPUT variable.
UNSTRING -
The UNSTRING statement takes a single string, breaks it down into several separate strings, and places them into the variables. It requires a minimum of two receiving variables.
UNSTRING source-string
[DELIMITED BY delimiter1]
INTO target-string-1 [target-string-2 ...]
[WITH POINTER pointer-name]
[TALLYING IN counter-name]
[ON OVERFLOW statements-block-1]
[NOT ON OVERFLOW statements-block-2]
[END-UNSTRING].
- source-string - This is the string that we want to break down.
- DELIMITED BY delimiter1 - Specifies the delimiter1 used to specify where to split the string. If it's not coded, then each character is considered separately.
- INTO - Specifies the variables where the divided strings of the source string should be placed.
- WITH POINTER - It will hold the position of next delimiter in the source string immediately after the last character that was processed.
- TALLYING IN - Used to count the number of characters that have been transferred to the target fields.
- ON OVERFLOW statements-block-1 - Specifies the set of statements that are executed when ON OVERFLOW occurs.
- NOT ON OVERFLOW statement-block-2 - Specifies the set of statements that are executed when the STRING operation is successful.
- END-UNSTRING - This is the explicit scope terminator for the UNSTRING statement.
Example - Split the string into two strings.
IDENTIFICATION DIVISION.
PROGRAM-ID. UNSTREXP.
AUTHOR. MTH.
DATA DIVISION.
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.
STOP RUN.
Output -
WS-OUTPUT1: MAINFRAMESTECHHELP WS-OUTPUT2: IS A MAINFRAME COMMUNITY
INSPECT -
The INSPECT statement analyzes, counts, or replaces certain character(s) within a variable. It's quite flexible and provides a range of functions to help with string manipulations. INSPECT statement used to do the following tasks by using its 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's 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 - The data item that will be inspected for replacements.
- ws-tally-count - A numeric variable where the count is stored.
- FOR CHARACTERS - Each character is counted.
- ws-tally-char - The characters we're searching for in ws-input-string to count.
- ALL - Each occurrence of ws-tally-char is counted.
- LEADING - The leftmost occurrence of ws-tally-chars is counted.
Examples -
Scenario1 - 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
Scenario2 - Counting for characters.
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 CHARACTERS. Result- WS-CNT = 10
In the above case, WS-DATA has 10 characters. So the result is 10.
INSPECT...REPLACING -
INSPECT...REPLACING performs character replacement in a variable. It's a way to replace all instances of certain characters with other characters.
INSPECT ws-input-string
REPLACING [ALL|LEADING|FIRST] {CHARACTERS|ws-replaced-char}
BY ws-replacing-char
- ws-replaced-char - The characters we're searching for in input string to replace.
- ws-replacing-char - The characters that will replace the ws-replaced-char.
- CHARACTERS BY - Each occurrence of character is replaced by a replacing character).
- ALL - Each occurrence of ws-replaced-char is replaced by a replacing character.
- LEADING - Replaces leftmost occurrence of ws-replaced-char is replaced by ws-replacing-char.
- FIRST - Replaces leftmost first occurrence of ws-replaced-char is replaced by ws-replacing-char.
Examples -
Scenario1 - 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"
Scenario2 - Replace characters with '$'.
Input- WS-DATA = "MAINFRAMES" Declaration- 05 WS-DATA PIC X(10) VALUE "MAINFRAMES". Code- INSPECT WS-DATA REPLACING CHARACTERS BY "$". Result- WS-DATA = "$$$$$$$$$$"
In the above case, every character is replaced by '$'. So the result is "$$$$$$$$$$".
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 -
Scenario1 - Count for all "-" and Replace all "-" 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 ALL "-" REPLACING ALL "-" BY "/". Result - WS-CNT = 2 WS-DATA = "DD/MM/YYYY"
Scenario2 - 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].
- ws-input-string - The data item that will be inspected for replacements. It should be alphanumeric variable declared with usage DISPLAY.
- char-1 ... char-n - The character(s) we're searching for in ws-variable.
- char-a ... char-z - The character(s) that will convert the characters char-1 ... char-n.
Examples -
Scenario1 - 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 converted with its equal characters. The result is 'mainframes'.
Scenario2 - Conveting all uppercase characters to lowercase before "R".
Input- WS-DATA = "MAINFRAMES" Declaration- 05 WS-DATA PIC X(10) VALUE "MAINFRAMES". Code- INSPECT WS-DATA CONVERTING "ABCDEFGHIJKLMNOPQRSTUVWXYZ" TO "abcdefghijklmnopqrstuvwxyz" BEFORE "R". Result- WS-DATA = "mainfRAMES"
In the above case, it converts all uppercase characters to lowercase characters before "R".
