Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

NUMVAL - Numeric value of string

The NUMVAL function returns the numeric value represented by the character string specified by argument-1. Leading and trailing spaces are ignored.
The type of this function is numeric.

Format


FUNCTION NUMVAL (argument-1)


Arguments

  1. argument-1 must be from the category alphanumeric or national and must have one of the following two formats:

    ['BLANK'] [+ | -] ['BLANK'] {digit[.[digit]] | .digit} ['BLANK']
    or
    ['BLANK'] {digit[.[digit]] | .digit} ['BLANK'] [+ | - | CR | DB]

    'BLANK'String of one or more spaces
    digitOne or more digits of the set {0, 1, 2, 3, 4, 5, 6, 7, 8, 9}
  2. The letter string "CR" or "DB" in upper case must be specified for CR and DB.

  3. The total number of digits in argument-1 must not exceed 31.

  4. If the DECIMAL-POINT IS COMMA clause is specified in the SPECIAL-NAMES paragraph, a comma must be used in argument-1 rather than a decimal point.

Returned values

  1. The returned value is the numeric value represented by argument-1.

  2.  If argument-1 has a variable length or a length with more than 16 characters (or more than 14 characters if the error return value is required), the result can deviate from the exact value, since a floating point representation is required for the return value.
  3. If argument-1 has a fixed length of up to 14 characters then the error default value is -999’999’999’999’999’999.
    If argument-1 has a variable length or a length of more than 14 characters then the error default value is -9’999’999’999’999’999’999’999’999’999’999.

See also:        NUMVAL-C

Example 9-31

...
DATA DIVISION.
WORKING-STORAGE SECTION.
01  V PIC X(8) VALUE "+ 15.00".
01  R PIC 99V99.
01  RES PIC 99.99.
PROCEDURE DIVISION.
P1 SECTION.
MAIN.
    COMPUTE R = FUNCTION NUMVAL (V).
    MOVE R TO RES.
    DISPLAY RES UPON T.
    STOP RUN.

Result:              15.00