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 |
Format
FUNCTION LOWER-CASE (argument-1)
Arguments
argument-1 must be class alphabetic, alphanumeric or national and must be at least one character in length.
argument-1 must not be defined in the ANY LENGTH clause.
Returned values
The returned value is the same character string as argument-1, except that each uppercase letter is replaced by the corresponding lowercase letter.
The character string returned has the same length as argument-1.
Umlauts are not converted.
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