Your Browser is not longer supported

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

{{viewport.spaceProperty.prod}}

SYMBOLIC CHARACTERS clause

Syntax rules

  1. No symbolic name for a character may be used more than once in the SYMBOLIC CHARACTERS clause.

  2. The relationship between each separate symbolic name and its corresponding integer results from the sequence within the SYMBOLIC CHARACTERS clause: symbolic-character-1 is paired with integer-1, symbolic-character-2 with integer-2, and so on.

  3. An integer must be specified for each symbolic name which is specified.

  4. The position specified by integer-1 must exist in the alphanumeric native character set. If IN is specified, the position must exist in the character set named by alphabet-name-2.

General rules

  1. symbolic-character is a figurative constant.

  2. If the IN phrase is omitted, symbolic-character-1 represents the character whose position is identified by integer-1 in the collating sequence of the native character set.

  3. If the IN specification exists, character position integer-1 selects a character from the character set specified by alphabet-name-2. The internal representation of symboliccharacter-1 is the same as that of the corresponding character in the native character set.

Example 6-12

IDENTIFICATION DIVISION.
PROGRAM-ID. SYMCHAR.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SPECIAL-NAMES.
    TERMINAL IS T
    SYMBOLIC CHARACTERS HEX-0A IS 11.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 PRINT-RECD.
   02 CNTRLBYTE        PIC X.
   02 PRINT-LINE       PIC X(132).
PROCEDURE DIVISION.
MAIN SECTION.
P1.
    MOVE HEX-0A TO CNTRLBYTE.
    DISPLAY CNTRLBYTE UPON T.
STOP RUN.


The symbolic name HEX-0A is assigned to the eleventh character of the EBCDIC character set (this character corresponds to the hexadecimal value 0A).
The MOVE statement uses this symbolic name in order to move the hexadecimal value 0A into the control byte.