Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

ORD - Ordinal position in collating sequence

The ORD function returns an integer value that is the ordinal position of argument-1 in the collating sequence for the program. The lowest ordinal position is 1.
The type of this function is integer.

Format


FUNCTION ORD (argument-1)


Argument

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

Returned value

  1. If argument-1 is class alphabetic or alpanumeric, the returned value is the ordinal position of argument-1 in the alphanumeric collating sequence.

  2. If argument-1 is class national, the returned value is the ordinal position of argument-1 in the national collating sequence.


See also:
        CHAR

Example 9-33

...
DATA DIVISION.
WORKING-STORAGE SECTION.
01  L PIC X VALUE "Z".
01  R PIC X(3).
PROCEDURE DIVISION.
P1 SECTION.
MAIN.
    COMPUTE R = FUNCTION ORD (L).
    DISPLAY R UPON T.
    STOP RUN. 

Result:               234
                          The ordinal position of the letter Z in EBCDIC is 234.