Your Browser is not longer supported

Please use Google Chrome, Mozilla Firefox or Microsoft Edge to view the page correctly
Loading...

{{viewport.spaceProperty.prod}}

BLANK WHEN ZERO clause

Function

The BLANK WHEN ZERO clause specifies that an item is to be set to blanks when its value is zero.

Format


BLANK WHEN ZERO


Syntax rules

  1. The BLANK WHEN ZERO clause may be specified only at the elementary level for numeric-edited or numeric items.

  2. The numeric or numeric edited data description entry to which the BLANK WHEN ZERO clause applies must be described, either implicitly or explicitly, as USAGE IS DISPLAY.

General rules

  1. When the BLANK WHEN ZERO clause is used, the item will contain only blanks if the value of the item is zero.

  2. When the BLANK WHEN ZERO clause is used for numeric data items, the category of the item is considered to be “numeric-edited”.

  3. If the BLANK WHEN ZERO clause and the PICTURE clause with asterisk (*) (for zero suppression) are used simultaneously in a data description entry, the zero suppression editing function overrides the function of the BLANK WHEN ZERO clause (see section "PICTURE clause").

Example 7-5

IDENTIFICATION DIVISION.
PROGRAM-ID. BWHENZ.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SPECIAL-NAMES.
    TERMINAL IS T.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 PURCHASE-EXAMPLE.
   02 PURCHASE PICTURE $Z.99 BLANK WHEN ZERO.
PROCEDURE DIVISION.
MAIN SECTION.
P1.
    MOVE ZERO TO PURCHASE.
    DISPLAY PURCHASE UPON T.
    STOP RUN.

Value of PURCHASE after the MOVE statement:

'BLANK' 'BLANK' 'BLANK' 'BLANK' 'BLANK' (5 spaces)