Top
NetCOBOL V11.0 Syntax Samples
FUJITSU Software

1.48 LOWER-CASE and UPPER-CASE Functions

The LOWER-CASE function is used to convert upper-case letters in a character string specified as an argument to lower-case letters.

The LOWER-CASE function is useful for uniformly managing alphabetic data using lower-case letters.

The UPPER-CASE function is used to convert lower-case letters in a character string specified in an argument to upper-case letters.

The UPPER-CASE function is useful for uniformly managing alphabetic data using upper-case letters.

000010 @OPTIONS MAIN
000020*----------------------------------------------------------------------
000030* The LOWER-CASE function is used to uniformly manage alphabetic data 
000040* using lower-case letters.
000050* The UPPER-CASE function is used to uniformly manage alphabetic data 
000055* using upper-case letters.
000060*----------------------------------------------------------------------
000070 IDENTIFICATION  DIVISION.
000080 PROGRAM-ID.     SAMPLE.
000090*
000100 DATA            DIVISION.
000110 WORKING-STORAGE SECTION.
000120 01 IN-STR       PIC X(40).
000130 01 LOWER-STR    PIC X(40).
000140 01 UPPER-STR    PIC X(40).
000150*
000160 PROCEDURE       DIVISION.
000170     DISPLAY "Please input a name using alphabetic characters. >>"
000175             WITH NO ADVANCING.
000180     ACCEPT IN-STR FROM CONSOLE.
000190*----------------------------------------------------------------------
000200* The upper-case letters are converted to lower-case letters.
000210*----------------------------------------------------------------------
000220     MOVE FUNCTION LOWER-CASE (IN-STR) TO LOWER-STR.
000223*----------------------------------------------------------------------
000225* The lower-case letters are converted to upper-case letters.
000227*----------------------------------------------------------------------
000230     MOVE FUNCTION UPPER-CASE (IN-STR) TO UPPER-STR.
000240*----------------------------------------------------------------------
000250     DISPLAY " ".
000260     DISPLAY "Lower-case letter notation: " LOWER-STR.
000270     DISPLAY "Upper-case letter notation: " UPPER-STR.
000280 END PROGRAM SAMPLE.