Function
The INSPECT statement enables single characters or groups of characters within a data item to be tallied, replaced, or tallied and replaced.
Format 1 (tallying)
INSPECT identifier-1 TALLYING
{identifier-2 FOR { { {ALL | LEADING} {identifier-3 | literal-1} | CHARACTERS}
[{BEFORE | AFTER} INITIAL {identifier-4 | literal-2}]... }... }...
Format 2 (replacing)
INSPECT identifier-1 REPLACING
{ CHARACTERS BY {identifier-5 | literal-3} [{BEFORE | AFTER} INITIAL {identifier-4 | literal-2}]...
|{ALL | LEADING | FIRST} { {identifier-3 | literal-1}
BY {identifier-5 | literal-3} [{BEFORE | AFTER} INITIAL { identifier-4 | literal-2} ]... }...
}...
Format 3 (tallying and replacing)
INSPECT identifier-1 TALLYING
{identifier-2 FOR {{ {ALL | LEADING} {identifier-3 | literal-1} | CHARACTERS}
[{BEFORE | AFTER} INITIAL {identifier-4 | literal-2}]... }... }...
REPLACING
{ CHARACTERS BY {identifier-5 | literal-3}
[{BEFORE | AFTER} INITIAL {identifier-4 | literal-2 }]...
|{ALL | LEADING | FIRST} { {identifier-3 | literal-1}
BY {identifier-5 | literal-3}
[{BEFORE | AFTER} INITIAL {identifier-4 | literal-2}]... }... }...
Format 4 (converting)
INSPECT identifier-1 CONVERTING {identifier-6 | literal-4}
TO {identifier-7 | literal-5}
[{BEFORE | AFTER} INITIAL {identifier-4 | literal-2}]...
Syntax rules for all formats
identifier-1 may reference either an alphanumeric or national group item or an elementary item, which is described (implicitly or explicitly) with USAGE DISPLAY or USAGE NATIONAL.
identifier-3, ..., identifier-n may reference either an alphanumeric or national group item or an elementary item, which is described (implicitly or explicitly) with USAGE DISPLAY or USAGE NATIONAL.
literal-1, ..., literal-5 must be non-numeric literals. They may not be figurative constants which begin with ALL.
If literal-1, literal-2 or literal-4 is a figurative constant, it stand for an implicitly singlecharacter item. If the class of identifier-1 is national, the class of the figurative constant is also national. Otherwise the class of the figurative constant is alphanumeric.
If the class of any literal-1, ..., literal-5, identifier-1, ..., identifier-7 is national, the class of all must be national.
Only one BEFORE and/or AFTER entry may be assigned to each individual ALL, LEADING, CHARACTERS, FIRST, or CONVERTING phrases.
Syntax rule for formats 1 and 3
identifier-2 must be an elementary numeric data item.
Syntax rules for formats 2 and 3
literal-3 or identifier-5 must be equal in size to literal-1 or identifier-3. When a figurative constant is used as literal-3, it is implicitly equal in size to literal-1 or identifier-3.
When CHARACTERS is used, literal-3 and identifier-5 must each be one character in length.
Syntax rules for format 4
literal-5 or identifier-7 must be equal in size to literal-4 or identifier-6.
When a figurative constant is used as literal-5, it is implicitly equal in size to literal-4 or identifier-6.
No character may appear more than once in literal-4 or identifier-6.
General rules for all formats
The length of identifier-1 is calculated in the same way as for sending items (see section "OCCURS clause"). If identifier-1 is a zero-length item:
identifier-1 and identifier-2 remain unchanged.
The runtime control passes to the end of the INSPECT statement.
identifier-1 is processed from left to right regardless of its data class.
The contents of the data items indicated by identifier-1, identifier-3, identifier-4, identifier-5, identifier-6, identifier-7 are treated as follows:
If any of these identifiers is described as alphabetic, alphanumeric or national its contents will be treated as a character-string of the according category.
If any of these identifiers is described as alphanumeric-edited, numeric-edited, or unsigned numeric, it will be treated as though it had been redefined as alphanumeric.
If any of these identifiers is described as signed numeric, it will be treated as though it had been moved to an unsigned numeric data item of the same length (not counting sign position) and this item had then been redefined as alphanumeric (see section "MOVE statement").
If identifier-1 is described as a signed numeric data item, its original sign will be retained until the INSPECT statement has executed.
If any of these identifiers is indexed, the index value for these items will be calculated once only, namely immediately following execution of the INSPECT statement.
In general rules 5 to 15, everything that applies to literal-1, literal-2, literal-3, literal-4, or literal-5 applies equally to identifier-3, identifier-4, identifier-5, identifier-6 or identifier-7.
General rules for formats 1, 2 and 3
- While the contents of identifier-1 are being checked, each occurrence of literal-1 will be tallied (format 1) or all characters matching literal-1 will be replaced by literal-3 (format 2). If CHARACTERS is used, the characters in identifier-1 are tallied or replaced by literal-3 one at a time, depending on where the comparison operation is currently positioned.
The TALLYING or REPLACING operands are processed from left to right in the order in which they were specified in the INSPECT statement (comparison cycle). The first comparison cycle starts at the leftmost character in identifier-1.
If BEFORE or AFTER are omitted, the comparison operation to determine the occurrences of literal-1 in identifier-1 takes place as follows:
The first literal-1 is compared to a series of contiguous characters within identifier1 starting with the leftmost character, where the length of this series is equal to the length of literal-1. Only if literal-1 and this portion of identifier-1 are identical, character-for-character, does a match occur.
If no match between literal-1 and identifier-1 occurs, the comparison is repeated with each successive literal-1 until either a match is found or there is no next successive literal-1.
If no match whatsoever occurs between literal-1 and identifier-1, the character position within identifier-1 is shifted one position to the right and the comparison cycle starts again with the first literal-1.
Whenever a match occurs, the comparison cycle is terminated. Identifier-2 is incremented by 1 and/or the characters in identifier-1 which match literal-1 are replaced by literal-3. The character position within identifier-1 is then shifted to the right by the number of characters in literal-1 and the comparison cycle starts again with the first literal-1.
The comparison operation continues until the rightmost character in identifier-1 has either participated successfully in a match or is the character at which a comparison cycle begins.
If ALL is used, points a) to e) apply without restrictions.
If LEADING is used, the corresponding literal-1 is always involved in the first runthrough of the comparison cycle. It only takes part is subsequent comparison cycles if the preceding cycle has produced a match with literal-1.
If CHARACTERS is used, an implicit single-character operand takes part in the comparison cycle as though it were entered as literal-1. However, no comparison with the contents of identifier-1 takes place; instead, this operand is always considered to match the character in identifier-1 at which the comparison cycle is currently positioned.
If BEFORE or AFTER is used, the following restrictions apply to point 7 above:
If BEFORE is used, the operation proceeds as follows: literal-1 or (if CHARACTERS has been specified) the implicit operand participates only in those comparison cycles which would have been performed if identifier-1 had ended with the character located immediately in front of the first occurrence of literal-2 within identifier-1.
If literal-2 does not occur at all within identifier-1 or identifier-4 is a zero-length item, the comparison proceeds as if BEFORE had never been entered.
If AFTER is used, the same considerations apply as in a). That is, a search is made in identifier-1 for literal-2. If literal-2 is located, the record pointer is positioned to the character within identifier-1 which is located immediately to the right of literal-2. From this point on, literal-1 or (if CHARACTERS has been specified) the implicit operand participates in the subsequent comparison cycles.
If literal-2 does not occur at all within identifier-1 or identifier-4 is a zero-length item, literal-1 or (if CHARACTERS has been specified) the implicit operand is not involved in a comparison cycle.
General rules for formats 1 and 3
- The contents of identifier-2 are not initialized when the INSPECT statement is executed.
- If identifier-1, identifier-3 or identifier-4 occupies the same memory area as identifier-2, the results of the INSPECT statement will be unpredictable, even when these identifiers are defined in the same data description entry (see section "Overlapping operands").
General rules for formats 2 and 3
- The mandatory words ALL, LEADING and FIRST are adjectives which apply to all subsequent BY phrases until the next adjective is entered.
- If FIRST is used, literal-1 will be replaced by literal-3 within identifier-1 only at the position where it occurs for the first time. This rule applies to all successive FIRST phrases, regardless of the value of literal-1.
If identifier-3, identifier-4 or identifier-5 occupies the same memory area as identifier-1, the results of the INSPECT statement will be unpredictable, even when these identifiers are described in the same data description entry (see section "Overlapping operands" ).
General rule for format 3
A format 3 INSPECT statement is executed as though it were two successive INSPECT statements referring to the same identifier-1, namely one format 1 INSPECT statement (with TALLYING phrase) and a format 2 INSPECT statement (with REPLACING phrase). The rules given for formats 1 and 2 apply accordingly. Subscripting associated with any identifier in the format 2 statement is evaluated only once before executing the format 1 statement.
General rules for format 4
A format-4 INSPECT statement is interpreted and executed as though it were a format-2 INSPECT statement containing a series of ALL phrases (one for each character in literal-4 or identifier-6) which refer to the same identifier-1.
Thus, each character in literal-4 or identifier-6 and the corresponding character in literal-5 or identifier-7 is interpreted as though it were a self-contained literal-1 (or identifier-3) or literal-3 (identifier-5) in format 2.
The unique assignment of characters from literal-4 (identifier-6) and literal-5 (identifier-7) results from their position within the data item.
If identifier-4, identifier-6 or identifier-7 occupies the same memory area as identifier-1, the results of the INSPECT statement will be unpredictable, even when the identifiers are defined in the same data description entry (see section "Overlapping operands").
Example 8-52
for all formats:
IDENTIFICATION DIVISION. PROGRAM-ID. INSP. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. TERMINAL IS T. DATA DIVISION. WORKING-STORAGE SECTION. 01 COUNTER1 PIC 99 VALUE ZEROES. 01 COUNTER2 PIC 99 VALUE 0. 01 COUNTER3 PIC 99 VALUE 0. 01 FIELD PIC X(20) VALUE SPACES. ... PROCEDURE DIVISION. PROC SECTION. COUNT-PAR. MOVE "BBYZYZBBYZAXBXBBX" TO FIELD. INSPECT FIELD TALLYING COUNTER1 FOR ALL "X" AFTER INITIAL "A" COUNTER2 FOR LEADING "YZ" AFTER INITIAL "BB" (1) COUNTER3 FOR CHARACTERS BEFORE INITIAL "A". DISPLAY "After INSPECT" UPON T. DISPLAY "Counter1 = *" COUNTER1 "*" UPON T. DISPLAY "Counter2 = *" COUNTER2 "*" UPON T. DISPLAY "Counter3 = *" COUNTER3 "*" UPON T. REPLACE-1. MOVE "MR. COBOLUSER" TO FIELD. DISPLAY "Before INSPECT" UPON T DISPLAY "Field = *" FIELD "*" UPON T. INSPECT FIELD REPLACING CHARACTERS BY "X" AFTER INITIAL "MR. " BEFORE INITIAL "U". DISPLAY "After INSPECT" UPON T. DISPLAY "Field = *" FIELD "*" UPON T. REPLACE-2. MOVE "ALGOL-PROGRAM" TO FIELD. DISPLAY "Before INSPECT" UPON T. DISPLAY "Field = *" FIELD "*" UPON T. INSPECT FIELD REPLACING ALL "A" BY "C" BEFORE INITIAL "P" ALL "L" BY "O" BEFORE INITIAL "G" ALL "G" BY "B" BEFORE INITIAL "P". DISPLAY "After INSPECT" UPON T. DISPLAY "Field = *" FIELD "*" UPON T. REPLACE-3. MOVE "XXYZYZXXYZ-XYZXYZ" TO FIELD. DISPLAY "Before INSPECT" UPON T. DISPLAY "Field = *" FIELD "*". INSPECT FIELD REPLACING LEADING "YZ" BY "AB" BEFORE INITIAL "-" AFTER INITIAL "XX" (2) FIRST "YZ" BY "CD" AFTER INITIAL "-". DISPLAY "After INSPECT" UPON T. DISPLAY "Field = *" FIELD "*" UPON T. CONVERT. MOVE "CE#CGDHDEF-CD#F" TO FIELD. DISPLAY "Before INSPECT" UPON T. DISPLAY "Field = *" FIELD "*" UPON T. INSPECT FIELD CONVERTING (3) "CDEF" TO "UVWU" AFTER "#" BEFORE "-". DISPLAY "After INSPECT" UPON T. DISPLAY "Field = *" FIELD "*" UPON T. ENDE. STOP RUN.
Result:
After INSPECT (1)
COUNTER1 = *03* COUNTER2 = *02* COUNTER3 = *06*
Before INSPECT | After INSPECT |
|
|
|
|
Explanation
(1) | In the case of COUNTER2, the instances of YZ underlined in the following string were tallied in FIELD: BBYZYZBBYZAXBXBBX In other words, with each of the underlined YZ pairs there was a match in the sense of general rule 7f. Hence, on both occasions the compare cycle resumed with the first literal-1, i.e. with COUNTER1. The result is as follows: COUNTER3 is not incremented for the underlined YZ pairs. Hence, only the following underlined characters are tallied: BBYZYZBBYZAXBXBBX Thus, COUNTER3 is equal to 6. |
(2) | The replacement of leading YZ pairs by AB is caused by entering AFTER INITIAL "XX". BEFORE INITIAL "-" has no effect, because on account of the LEADING phrase each string that is not equal to YZ prevents further replacements. |
(3) | This INSPECT statement has the same effect as the following statement: INSPECT FIELD REPLACING ALL "C" BY "U" AFTER "#" BEFORE "-" ALL "D" BY "V" AFTER "#" BEFORE "-" ALL "E" BY "W" AFTER "#" BEFORE "-" ALL "F" BY "U" AFTER "#" BEFORE "-". |