Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

MIN - Value of minimum argument

The MIN function returns the content of the argument that contains the minimum value.The type of this function depends upon the argument types as follows:

Argument type

Function type

alphabetic
alphanumeric
all arguments integer
index
national
numeric
numeric/integer

alphanumeric
alphanumeric
integer
index
national
numeric
numeric

Format


FUNCTION MIN ({argument-1}...)


Arguments

  1. If more than one argument is specified, all arguments must be of the same class.

  2. The individual values must not be defined with the ANY LENGTH clause.

Returned values

  1. The returned value is the content of the argument having the least value. The comparisons used to determine the least value are made according to the rules for simple conditions.

  2. If more than one argument has the same least value, the content of the argument returned is the leftmost argument having that value.

  3. If the type of the function is alphanumeric or national, the size of the returned value is the same as the size of the selected argument.

  4. The error default value is 0.


See also:
        MAX, RANGE, MEAN, MEDIAN, MIDRANGE, SUM

 

Example 9-28

...
DATA DIVISION.
WORKING-STORAGE SECTION.
01  RES PIC 9(3).
PROCEDURE DIVISION.
P1 SECTION.
MAIN.
    COMPUTE RES = FUNCTION MIN (12 32 5 8 17 9).
    DISPLAY RES UPON T.
    STOP RUN.

Result:              005