Top
NetCOBOL V11.0 Syntax Samples
FUJITSU Software

1.31 Boolean Expression

When coding a program, there will be several situations where you might want to perform logical operations using Boolean items. COBOL enables this using Boolean expressions.

000010 @OPTIONS MAIN
000020*----------------------------------------------------------------------
000030* Boolean expressions are used for operations using Boolean data items.
000040*----------------------------------------------------------------------
000050 IDENTIFICATION   DIVISION.
000060 PROGRAM-ID.      SAMPLE.
000070 DATA             DIVISION.
000080 WORKING-STORAGE  SECTION.
000090 01 IN-DATA       PIC S9(4) COMP-5.
000100 01 CNT           PIC S9(4) COMP-5.
000110 01 .
000120    02 RESULT     PIC 1(12) BIT VALUE ALL B"0".
000130    02 RES-BIT    REDEFINES RESULT OCCURS 12 PIC 1(1) BIT.
000140 CONSTANT         SECTION.
000150 01 ELM-TBL.
000160    02              PIC X(10) VALUE "USA".
000170    02              PIC X(10) VALUE "Korea".
000180    02              PIC X(10) VALUE "Germany".
000190    02              PIC X(10) VALUE "Russia".
000200    02              PIC X(10) VALUE "England".
000210    02              PIC X(10) VALUE "Japan".
000220    02              PIC X(10) VALUE "Spain".
000230    02              PIC X(10) VALUE "France".
000240    02              PIC X(10) VALUE "Kenya".
000250    02              PIC X(10) VALUE "China".
000260    02              PIC X(10) VALUE "Brazil".
000270    02              PIC X(10) VALUE "Italy".
000280 01              REDEFINES ELM-TBL.
000290    02 ELM-NAME     PIC X(10)  OCCURS 12.
000300*----------------------------------------------------------------------
000310* The category information of each country is defined using Boolean 
000315* expressions.
000320* UNSC:  The resident country of the United Nations is set to 1.
000330* NATO:  The member nations of NATO are set to 1.
000340*----------------------------------------------------------------------
000350  01 SUBSET-TBL.
000360    02 UNSC         PIC 1(12) BIT VALUE B"100110010100".
000370    02 NATO         PIC 1(12) BIT VALUE B"101010110001".
000380*----------------------------------------------------------------------
000390 PROCEDURE        DIVISION.
000400     DISPLAY "The following countries are categorized.".
000410     PERFORM TEST BEFORE
000420             VARYING CNT FROM 1 BY 1 UNTIL CNT > 12
000430       IF CNT = 6 OR 12 THEN
000440         DISPLAY ELM-NAME(CNT)
000450       ELSE
000460         DISPLAY ELM-NAME(CNT) WITH NO ADVANCING
000470       END-IF
000480     END-PERFORM.
000490     DISPLAY " ".
000500     DISPLAY "<Category>".
000510     DISPLAY "Resident country of the United Nations :1".
000520     DISPLAY "Member nations of NATO                 :2".
000530     DISPLAY "Countries of 1 and 2                   :3".
000540     DISPLAY "Countries of neither                   :4".
000550     DISPLAY " ".
000560     DISPLAY "Please select the category. >>" WITH NO ADVANCING.
000570     ACCEPT  IN-DATA.
000580*----------------------------------------------------------------------
000590* Boolean operators such as AND and OR can be used to obtain the 
000600* countries that match the conditions.  Expressions that use these 
000605* Boolean operators are referred to as Boolean expressions.
000610*----------------------------------------------------------------------
000620     EVALUATE IN-DATA
000630      WHEN 1  COMPUTE RESULT = UNSC
000640      WHEN 2  COMPUTE RESULT = NATO
000650      WHEN 3  COMPUTE RESULT = UNSC AND NATO
000660      WHEN 4  COMPUTE RESULT = NOT (UNSC OR NATO)
000670     END-EVALUATE.
000680*----------------------------------------------------------------------
000690     PERFORM TEST BEFORE
000700             VARYING CNT FROM 1 BY 1 UNTIL CNT > 12
000710       IF RES-BIT(CNT) = B"1" THEN
000720         DISPLAY ELM-NAME(CNT)
000730       END-IF
000740     END-PERFORM.
000750 END PROGRAM SAMPLE.