Let's understand Mainframe
Home Tutorials Interview Q&A Quiz Mainframe Memes Contact us About us

MODULE 8: String handling


INSPECT

  • Used to count characters in a string
  • Used to replaces a group of characters in a sting with another group of characters
  • Permits several tallies (counts) and replacements with a single statement (instead of writing multiple statements)
  • Allows group of characters to be counted and replaced
  • Converts each of a set of character to its corresponding character in another set of characters
  • INSPECT can be used in one of the following format as per requirement:-
    • Syntax 1: (Counting characters in a string : INSPECT TALLYING)
    • Syntax 2: (Counting characters in a string: INSPECT REPLACING)
    • Syntax 3: (Counting & replacing together)
    • Syntax 4: (INSPECT with CONVERTING option)

Syntax 1: (Counting characters in a string : INSPECT TALLYING)

INSPECT identifier-1 TALLYING identifier-2 FOR [{{{ALL/LEADING} {identifier-3/literal-1}}/CHARACTERS}] [{BEFORE/AFTER} INITIAL {identifier-4/literal-2}]

  • Where,
    • identifier-1 must be alphanumeric data item and it is main string
    • identifier-3, identifier-4 should be an elementary data item with usage DISPLAY. identifier-3 or literal-1 is a character or group of characters which you are searching in the main string
    • identifier-2 is the count field and must be an elementary integer item. This field is used to store count.
    • CHARACTERS phrase when coded, identifier-2 is incremented by 1 for each character in identifier-1
    • ALL phrase when coded, identifier-2 is incremented by 1 for each occurrences of identifier-3 or literal-2 in identifier-1
    • LEADING phrase when code, identifier-2 is incremented by 1 for each initial contiguous occurrence of identifier-3/literal-1 from starting position of identifier-1
    • INSPECT further qualifies the search with BEFORE and AFTER of the initial occurrence of identifier-4 OR literal-2
  • Suppose there is below data declaration in DATA DIVISION,

    01 WS-STRING PIC X(30) VALUE ‘TT-THIS IS TEST. THIS IS, TOO.’. 01 WS-COUNT PIC 99.

  • Considering above data declaration, let’s see multiple uses of INSPECT TALLYING in below examples:-
    In PROCEDURE DIVISION we can code INSPECT statement.
    Example 1:

    INSPECT WS-STRING TALLYING WS-COUNT FOR ALL ‘T’.

    Results:- WS-COUNT contains ‘7’
    Example 2:

    MOVE 0 TO WS-COUNT. INSPECT WS-STRING TALLYING WS-COUNT FOR LEADING ‘T’

    Result: WS-COUNT contains ‘2’
    Example 3:

    MOVE 0 TO WS-COUNT INSPECT WS-STIRNG TALLYING WS-COUNT FOR ALL ‘I’ BEFORE INITIAL ‘.’

    Result: WS-COUNT contains ‘2’
    Example 4:

    MOVE 0 TO WS-COUNT. INSPECT WS-STRING TALYYING WS-COUNT FOR CHARACTERS

    Result: WS-COUNT contains ‘30’
    Reason: Because whole string contains 30 characters
    Example 5:

    MOVE 0 TO WS-COUNT INSPECT WS-STRING TALLYING WS-COUNT FOR CHARACTERS BEFORE INITIAL ‘TOO’ AFTER INITIAL ‘TEST’

    Result: WS-COUNT contains ‘11’
    Reason: There are 11 characters between ‘TEST’ and ‘TOO’
    Example 6:

    MOVE 0 TO WS-COUNT INSPECT WS-STRING TALLYING WS-COUNT FOR ALL ‘I’ BEFORE INITIAL ‘TOO’ AFTER INITIAL ‘TEST’

    Result: WS-COUNT contains ‘2’
    Reason: In WS-STRING, there are only 2 ‘I’ exist between TEST and TOO.

Syntax 2: (Counting characters in a string: INSPECT REPLACING)

INSPECT identifier-1 REPLACING {CHARACTERS/ [{ALL/LEADING/FIRST} {identifier-2/literal-1}]} BY {identifier-3/literal-2} [{BEFORE/AFTER} INITIAL {identifier-4/literal-3}]

  • Where,
    • identifier-1 must be alphanumeric data item and it is main string on which operations will be done
    • identifier-2, literal-1 should be an elementary data item. It is a subject field, which identifies the characters to be replaced
    • identifier-3, literal-2 must be elementary data items. It is substitution field (the item that replaces the subject field). The subject field & substitution field must be of same length
    • CHARACTERS phrase when coded, identifier-3 or literal-2 must refer to a single character
    • ALL and LEADING have the same meaning as in syntax 1 except that replacement will be done instead of counting
    • FIRST when coded, leftmost occurrences of identifier-2/literal-1 matched within content of identifier-1 and once match is found, it gets replaced by identifier-3/literal-2
    • BEFORE and AFTER have same meaning as explained in Syntax 1
    • Size of identifier-2/literal-1 must be equal to the size of identifier-3/literal-2.
  • Suppose there is below data declaration in DATA DIVISION,

    01 WS-STRING PIC X(30) VALUE 'TT-THIS IS TEST. THIS IS, TOO.'.

  • Considering above data declaration, let’s see multiple uses of INSPECT REPLACING in below examples:-
    In PROCEDURE DIVISION we can code INSPECT statement.
    Example 1:

    INSPECT WS-STRING REPLACING CHARACTERS BY ‘*’ AFTER INITIAL ‘TEST’.

    Results:- WS-STRING contains ‘TT-THIS IS TEST***************’
    Example 2:

    INSPECT WS-STRING REPLACING CHARACTERS BY ‘$’ BEFORE INITIAL ‘THIS’

    Result: WS-STRING contains ‘$$$THIS IS TEST. THIS IS, TOO.’
    Example 3:

    INSPECT WS-STIRNG REPLACING ALL ‘THIS’ BY ‘HERE’

    Result: WS-STRING contains ‘TT-HERE IS TEST. HERE IS, TOO.’
    Example 4:-

    INSPECT WS-STIRNG REPLACING ALL ‘THIS’ BY ‘HERE’, ‘IS’ BY ‘$$’

    Result: WS-STRING contains ‘TT-HERE $$ TEST. HERE $$, TOO.’
    Example 5:-

    INSPECT WS-STIRNG REPLACING FIRST ‘THIS’ BY ‘HERE’

    Result: WS-STRING contains ‘TT-HERE IS TEST. THIS IS, TOO.’

Syntax 3: (Counting & replacing together)

This is combination of syntax 1 an syntax 2 and this can be used to count and replace character(s) in string together

INSPECT identifier-1 TALLYING      <tallying part as in syntax-1> REPLACING      <replacing part as in syntax-2>

  • Example:-
    Suppose there is below data declaration in DATA DIVISION,

    01 WS-STRING PIC X(30) VALUE ‘TT-THIS IS TEST. THIS IS, TOO.’. 01 WS-COUNT PIC 99.

    Example 1:

    INSPECT WS-STRING TALLYING WS-COUNT REPLACING ALL ‘H’ BY ‘$’

    Results:- WS-STRING contains ‘TT-T$IS IS TEST. T$IS IS, TOO.’ and WS-COUNT contains ‘2’
    Reason: WS-COUNT contains two because there are only 2 occurrences of ‘H’ are there in WS-STRING which are replaced by ‘$’.

Syntax 4: (INSPECT with CONVERTING option)

INSPECT identifier-1 CONVERTING {identifier-2/literal-1} TO {identifier-3/literal-2} [{BEFORE/AFTER} INITIAL {identifier-4/literal-3}]…

  • Where,
    • identifier-1 is alphanumeric data item and it is main string on which operation will be done
    • CONVERTING looks up identifier-1 for each character in identifier-2 or literal-1 and if found then replaces that character with corresponding character supplied in identifier-2 or literal-2.
    • identifier-2 must be elementary data item. identifier-2/literal-1 specifies the character string to be replaced. The same character must not appear more than once in identifier-2 or literal-1.
    • identifier-3 must be elementary data item. identifier-3/literal-2 specifies replacing character string
    • Replacing character string(identifier-3/literal-2) must be of the same size as replaced character string(identifier-2/literal-1)
    • BEFORE and AFTER INITIAL holds same meaning as in syntax 1
  • Example:-
    Suppose there is below data declaration in DATA DIVISION,

    01 WS-STRING PIC X(15) VALUE ‘MAINFRAMEISBEST’.

    In PROCEDURE DIVISION:

    INSPECT WS-STRING CONVERTING ‘MEI’ TO ‘$*#’

    Results:- WS-STRING contains ‘$A#NFRA$*#SB*ST’
    In above example, INSPECT replaced characters ‘M’, ’E’, ‘I’ in WS-STRING with ‘$’, ‘*’, ‘#’ respectively.
    We could have achieved same result using below format of INSPCET.

    INSPECT WS-STRING REPLACING ALL ‘M’ BY ‘$’ ’E’ BY ‘*’ ‘I’ BY ‘#’

    Results:- WS-STRING contains ‘$A#NFRA$*#SB*ST’ (There is no change in result when compared to result of INSPECT CONVERTING example)
  • Difference between CONVERTING and REPLACING
    • On WS-STRING, if we perform below operation using REPLACING, then the result will be different.
      COBOL statement:-

      INSPECT WS-STRING REPLACING ALL ‘MEI’ BY ‘$*#’

      Result:-  WS-STRING: ‘MAINFRA$*#SBEST’
    • If you observe results of CONVERTING and REPLACING then you will be able to conclude that REPLACING look up for whole string passed to it and CONVERTING look up for single character of STRING passed to it and does replacement accordingly
    • In CONVERTING, all occurrences of character ‘M’, ’E’, ‘I’ are replaced by ‘$’, ‘*’, ‘#’ respectively.
    • In REPLACING, all occurrences of string ‘MEI’ is replaced by ‘$*#’






© copyright mainframebug.com
Privacy Policy