INSPECT TALLYING REPLACING Statement


INSPECT TALLYING REPLACING counts the occurrences of the specific character and replaces them with new characters. It is used to count and replace the occurrence of character(s). It performs the TALLYING operation first and REPLACING next.

Syntax -

* Tallying and Replacing all characters
INSPECT   ws-input-string
TALLYING  ws-tally-count 
          FOR CHARACTERS
REPLACING CHARACTERS 
          BY ws-replacing-char|replacing-literal

* Tallying and Replacing all characters
* with BEFORE|AFTER|INITIAL
INSPECT   ws-input-string
TALLYING  ws-tally-count 
          FOR CHARACTERS
          [[BEFORE|AFTER] [INITIAL] 
		  ws-tally-delimeter1|delimeter-literal1]
REPLACING CHARACTERS 
          BY ws-replacing-char|replacing-literal
	      [[BEFORE/AFTER] [INITIAL] 
		  ws-replace-delimeter2|delimeter-literal2]

* Tallying and Replacing specific occurrences of characters
INSPECT   ws-input-string
TALLYING  ws-tally-count  
          FOR [ALL|LEADING] {ws-tally-chars|tally-literal}
REPLACING [ALL|LEADING|FIRST] ws-replaced-char|replaced-literal  
          BY ws-replacing-char|replacing-literal

* Tallying and Replacing specific occurrences of characters
* with BEFORE|AFTER|INITIAL
INSPECT   ws-input-string
TALLYING  ws-tally-count 
          FOR [ALL|LEADING] {ws-tally-chars|tally-literal}
          [[BEFORE|AFTER] [INITIAL] 
		  ws-tally-delimeter1|delimeter-literal1]
REPLACING [ALL|LEADING|FIRST] ws-replaced-char|replaced-literal  
          BY ws-replacing-char|replacing-literal
	      [[BEFORE/AFTER] [INITIAL] 
		  ws-replace-delimeter2|delimeter-literal2]
Note! All statements coded in [ ] are optional.

Parameters -

  • ws-input-string - The data item that will be inspected for replacements. It should be an alphanumeric variable declared with usage DISPLAY.
  • INITIAL - Specifies the first occurrence of a delimeter.
  • ws-tally-delimeter1|delimeter-literal1,
    ws-replace-delimeter2|delimeter-literal2
    - Specifies the delimeter alphanumeric variable or literal.

TALLYING Parameters -

  • ws-tally-char|tally-literal - The character(s) we're searching for in ws-input-string to count.
  • BEFORE ws-tally-delimeter1|delimeter-literal1 - Specifies tallying begins at the leftmost character position and continues till the first occurrence of the delimiter. If no delimiter is found, tallying continues to count until the last character of the string.
  • AFTER ws-tally-delimeter1|delimeter-literal1 - Specifies tallying begins at the first character to the right of delimiter and continues until the last character of the string. If no delimiter is found, no counting takes place.
  • FOR CHARACTERS -
    • Each character is counted when CHARACTERS BY alone coded (without BEFORE or AFTER phrases).
    • If the BEFORE or AFTER is coded, the counting happens depending on BEFORE or AFTER ws-delimeter.
  • ALL -
    • Each occurrence of ws-tally-char is counted when ALL alone coded (without BEFORE or AFTER phrases).
    • If the BEFORE or AFTER is coded along with ALL, the counting happens depending on BEFORE or AFTER ws-delimeter.
  • LEADING -
    • The leftmost occurrence of ws-replaced-char is counted when LEADING alone coded (without BEFORE or AFTER phrases).
    • If the BEFORE or AFTER is coded along with LEADING, the counting happens depending on BEFORE or AFTER ws-delimeter.

REPLACING Parameters -

  • ws-replaced-char|replaced-literal - The character(s) we're searching for in ws-input-string to replace.
  • ws-replacing-char|replacing-literal - The character(s) that will replace the ws-replaced-char.
  • BEFORE ws-replace-delimeter2|delimeter-literal2 - Specifies replacing begins at the leftmost character position and continues till the first occurrence of the delimiter. If no delimiter is found, replacing continues until the last character of the string.
  • AFTER ws-replace-delimeter2|delimeter-literal2 - Specifies replacing begins at the first character to the right of delimiter and continues until the last character of the string. If no delimiter is found, no replacement takes place.
  • CHARACTERS BY -
    • Each occurrence of character is replaced by a replacing character (includes space) when CHARACTERS BY alone coded (without BEFORE or AFTER phrases).
    • If the BEFORE or AFTER is coded, the replacement happens depending on BEFORE or AFTER ws-delimeter.
  • ALL -
    • Each occurrence of ws-replaced-char is replaced by a replacing character (includes space) when ALL alone coded (without BEFORE or AFTER phrases).
    • If the BEFORE or AFTER is coded along with ALL, the replacement happens depending on BEFORE or AFTER ws-delimeter.
  • LEADING -
    • Replaces leftmost occurrence of ws-replaced-char is replaced by a replacing character (includes space) when LEADING alone coded (without BEFORE or AFTER phrases).
    • If the BEFORE or AFTER is coded along with LEADING, the replacement happens depending on BEFORE or AFTER ws-delimeter.
  • FIRST -
    • Replaces leftmost first occurrence of ws-replaced-char is replaced by a replacing character (includes space) when FIRST alone coded (without BEFORE or AFTER phrases).
    • If the BEFORE or AFTER is coded along with FIRST, the replacement happens depending on BEFORE or AFTER ws-delimeter.

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 "&&&&&&&&&&".

Scenario3 - Count for no of characters before "Y" 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 BEFORE "Y"
              REPLACING CHARACTERS BY "&". 
			  
Result-       WS-CNT = 6
              WS-DATA = "&&&&&&&&&&"

In the above case, WS-DATA has 6 characters before "Y". So the count result is 6 and replaces all characters with "&". The result is "&&&&&&&&&&".

Scenario4 - Count leading "-" before "M" and Replace all "-" with "/" before "M".

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 LEADING "-" BEFORE "M"
              REPLACING ALL "-" BY "/". 
Result-       WS-CNT = 0
              WS-DATA = "DD/MM/YYYY"

In the above case, WS-DATA has no leading "-" before "M". The count result is 0 and replace all "-" with "/". The result is "DD/MM/YYYY".

Practical Example -


Scenario - INSPECT TALLYING REPLACING statement used for multiple conditions in COBOL programming.

Code -

----+----1----+----2----+----3----+----4----+----5----+
       IDENTIFICATION DIVISION.
       PROGRAM-ID. INSPCTTR.
       AUTHOR. MTH.

       DATA DIVISION.
       WORKING-STORAGE SECTION.

       01 WS-VAR.
          05 WS-DATA    PIC X(40) VALUE 
             "COBOL LANGUAGE IS A HIGH LEVEL LANGUAGE".
          05 WS-CNT1    PIC 9(02).
          05 WS-CNT2    PIC 9(02).  
          05 WS-CNT3    PIC 9(02).

       PROCEDURE DIVISION.

           INSPECT   WS-DATA 
		   TALLYING  WS-CNT1 FOR ALL SPACES BEFORE "HIGH"
                     WS-CNT2 FOR ALL "A" AFTER "IS"
                     WS-CNT3 FOR LEADING "C"
           REPLACING ALL SPACES BY "#" AFTER "LEVEL"
                     "LANGUAGE" BY "&&&&&&&&" BEFORE "HIGH"
                     "IS" BY "**".

           DISPLAY "WS-CNT1:     " WS-CNT1.
           DISPLAY "WS-CNT2:     " WS-CNT2.
           DISPLAY "WS-CNT3:     " WS-CNT3.

           DISPLAY "AFTER REPLACING:   " WS-DATA. 

           STOP RUN.

Output -

INSPECT TALLYING REPLACING program Output

Explaining Example -

In the above counting case,

  • SPACES before "HIGH" has 4 occurrences.
  • "A" has 3 occurrences before "IS".
  • "C" has only one occurrence of leading.

After counting, the results are WS-CNT1 = 04, WS-CNT2 = 03 and WS-CNT3 = 01.

In the above replacing case,

  • SPACES AFTER "LEVEL" replaced by "#".
  • "LANGUAGE" before "HIGH" replaced by "&&&&&&&&".
  • "IS" replaced by "**".

After replacements, the result is "COBOL &&&&&&&& ** A HIGH LEVEL#LANGUAGE###########".