Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

LOWER-CASE - Lowercase letters

The LOWER-CASE function returns a character string that is the same length as argument-1 with each uppercase letter replaced by a corresponding lowercase letter.
The type of this function depends upon the argument types as follows:

Argument type

Function type

alphabetic
alphanumeric
national

alphanumeric
alphanumeric
national

Format


FUNCTION LOWER-CASE (argument-1)


Arguments

  1. argument-1 must be class alphabetic, alphanumeric or national and must be at least one character in length.

  2. argument-1 must not be defined in the ANY LENGTH clause.

Returned values

  1. The returned value is the same character string as argument-1, except that each uppercase letter is replaced by the corresponding lowercase letter.

  2. The character string returned has the same length as argument-1.

  3. Umlauts are not converted.

  4. The error default value is a space.

See also:        UPPER-CASE

Example 9-23

...
DATA DIVISION.
WORKING-STORAGE SECTION.
01  RES PIC X(20).
PROCEDURE DIVISION.
P1 SECTION.
MAIN.
    MOVE FUNCTION LOWER-CASE ("UPPER lower") TO RES.
    DISPLAY RES UPON T.
    STOP RUN.

Result: upper lower