Top
NetCOBOL V11.0 Syntax Samples
FUJITSU Software

1.36 INSPECT Statement

The INSPECT statement (format 1) is used to count the occurrence of characters or character strings in a data item.

000010 @OPTIONS MAIN
000020*----------------------------------------------------------------------
000030* The INSPECT statement (format 1) is used to count the occurrence of
000035* characters or character strings.
000040*----------------------------------------------------------------------
000050 IDENTIFICATION        DIVISION.
000060 PROGRAM-ID.           SAMPLE.
000070 DATA                  DIVISION.
000080 WORKING-STORAGE SECTION.
000090 01 NUMBER-OF-MALES    PIC 9(4) VALUE ZERO.
000100 01 NUMBER-OF-FEMALES  PIC 9(4) VALUE ZERO.
000110 CONSTANT              SECTION.
000120 01 PARTICIPANT-NAMES  PIC X(50)
000130     VALUE "Mr.Brown Mrs.Brown Mr.Jones Mrs.Margaret Mr.Smith".
000140 PROCEDURE             DIVISION.
000150     DISPLAY "Name of travelers: " PARTICIPANT-NAMES.
000160     DISPLAY " ".
000170*----------------------------------------------------------------------
000180* The INSPECT statement is used to find character strings.
000190*----------------------------------------------------------------------
000200     INSPECT PARTICIPANT-NAMES TALLYING NUMBER-OF-MALES FOR ALL "Mr.".
000210     DISPLAY "For males, there are " NUMBER-OF-MALES " participants.".
000220     INSPECT PARTICIPANT-NAMES TALLYING NUMBER-OF-FEMALES FOR ALL
000335             "Mrs.".
000230     DISPLAY "For females, there are " NUMBER-OF-FEMALES "
000235-            " participants.".
000240*----------------------------------------------------------------------
000250 END PROGRAM SAMPLE.

In addition, the inspected character or character string can be replaced with another character or character string (format 2).

000010 @OPTIONS MAIN
000020*----------------------------------------------------------------------
000030* The INSPECT statement (format 2) is used to replace the character 
000035* string.
000040*----------------------------------------------------------------------
000050 IDENTIFICATION   DIVISION.
000060 PROGRAM-ID.      SAMPLE.
000070 DATA             DIVISION.
000080 WORKING-STORAGE SECTION.
000090 01 CR-DATE.
000100    02 CR-YEAR      PIC 9(4).
000110    02 CR-MON       PIC 9(2).
000120    02 CR-DAY       PIC 9(2).
000130 01 COPYRIGHT    PIC X(60)
000140     VALUE "Copyright yyyy FUJITSU LIMITED".
000150 PROCEDURE        DIVISION.
000160     MOVE FUNCTION CURRENT-DATE TO CR-DATE.
000170*----------------------------------------------------------------------
000180* The desired word is found in the character string, and replaced with  
000185* the specified word.
000190*----------------------------------------------------------------------
000200     INSPECT COPYRIGHT REPLACING ALL "yyyy" BY CR-YEAR.
000210*----------------------------------------------------------------------
000220     DISPLAY COPYRIGHT.
000230 END PROGRAM SAMPLE.