MainframeMaster

COBOL Tutorial

COBOL SYMBOLIC Clause - Quick Reference

The SYMBOLIC clause in COBOL is used within the SPECIAL-NAMES clause to define symbolic characters for custom character sets. It allows you to create custom character definitions that can be used in alphabet definitions and character set operations.

Primary Use

Define symbolic characters for custom character sets

Division

ENVIRONMENT DIVISION

Section

CONFIGURATION SECTION

Status

Optional clause

Overview

The SYMBOLIC clause is part of the SPECIAL-NAMES clause in the CONFIGURATION SECTION of the ENVIRONMENT DIVISION. It allows you to define custom symbolic characters that can be used in alphabet definitions and character set operations. This is particularly useful for international applications, specialized business requirements, or when you need custom character definitions that are not part of the standard character set.

Syntax

cobol
1
2
3
4
5
6
7
8
9
10
ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. SYMBOLIC CHARACTERS {symbolic-character-1 | symbolic-character-2} IN alphabet-name. * Examples: SPECIAL-NAMES. SYMBOLIC CHARACTERS SYMBOL-1 SYMBOL-2 IN CUSTOM-ALPHABET. SYMBOLIC CHARACTERS EURO-SIGN IN CURRENCY-ALPHABET. SYMBOLIC CHARACTERS MATH-PLUS MATH-MINUS IN MATH-ALPHABET.

Practical Examples

Basic SYMBOLIC Usage

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
* Basic SYMBOLIC clause example IDENTIFICATION DIVISION. PROGRAM-ID. SYMBOLIC-EXAMPLE. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. SYMBOLIC CHARACTERS CUSTOM-SYMBOL-1 CUSTOM-SYMBOL-2 IN CUSTOM-ALPHABET. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-TEXT-FIELD PIC X(20). 01 WS-SYMBOL-COUNT PIC 9(2). PROCEDURE DIVISION. MAIN-LOGIC. * Initialize text with custom symbols MOVE "Hello CUSTOM-SYMBOL-1 World" TO WS-TEXT-FIELD * Count custom symbols in text INSPECT WS-TEXT-FIELD TALLYING WS-SYMBOL-COUNT FOR ALL CUSTOM-SYMBOL-1 DISPLAY "Text: " WS-TEXT-FIELD DISPLAY "Custom symbols found: " WS-SYMBOL-COUNT * Check if text uses custom alphabet IF WS-TEXT-FIELD IS CUSTOM-ALPHABET DISPLAY "Text uses custom alphabet" ELSE DISPLAY "Text does not use custom alphabet" END-IF STOP RUN.

Explanation: This example demonstrates basic usage of the SYMBOLIC clause. The program defines custom symbolic characters (CUSTOM-SYMBOL-1, CUSTOM-SYMBOL-2) in a custom alphabet. These symbols can then be used in text processing, character counting, and alphabet validation. The INSPECT statement can count occurrences of these custom symbols, and the alphabet can be used for character set validation.

International Character Support

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
* SYMBOLIC clause for international characters IDENTIFICATION DIVISION. PROGRAM-ID. INTERNATIONAL-SYMBOLIC-EXAMPLE. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. SYMBOLIC CHARACTERS EURO-SIGN POUND-SIGN YEN-SIGN CENT-SIGN IN CURRENCY-ALPHABET. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-CURRENCY-TEXT PIC X(50). 01 WS-AMOUNT PIC 9(7)V99. 01 WS-CURRENCY-SYMBOL PIC X. PROCEDURE DIVISION. MAIN-LOGIC. * Process different currency symbols MOVE "€" TO WS-CURRENCY-SYMBOL PERFORM PROCESS-CURRENCY MOVE "£" TO WS-CURRENCY-SYMBOL PERFORM PROCESS-CURRENCY MOVE "¥" TO WS-CURRENCY-SYMBOL PERFORM PROCESS-CURRENCY STOP RUN. PROCESS-CURRENCY. MOVE 1234.56 TO WS-AMOUNT * Create currency display text STRING WS-CURRENCY-SYMBOL DELIMITED BY SIZE " " DELIMITED BY SIZE WS-AMOUNT DELIMITED BY SIZE INTO WS-CURRENCY-TEXT END-STRING * Check if currency symbol is valid IF WS-CURRENCY-SYMBOL IS CURRENCY-ALPHABET DISPLAY "Valid currency symbol: " WS-CURRENCY-TEXT ELSE DISPLAY "Invalid currency symbol: " WS-CURRENCY-SYMBOL END-IF.

Explanation: This example shows how to use the SYMBOLIC clause for international currency support. The program defines various currency symbols (Euro, Pound, Yen, Cent) as symbolic characters in a currency alphabet. This allows the program to validate currency symbols and process international monetary amounts. The alphabet validation ensures that only valid currency symbols are used in the application.

Mathematical Symbols

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
* SYMBOLIC clause for mathematical symbols IDENTIFICATION DIVISION. PROGRAM-ID. MATH-SYMBOLIC-EXAMPLE. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. SYMBOLIC CHARACTERS MATH-PLUS MATH-MINUS MATH-MULTIPLY MATH-DIVIDE MATH-EQUALS MATH-LESS-THAN MATH-GREATER-THAN IN MATH-ALPHABET. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-MATH-EXPRESSION PIC X(30). 01 WS-OPERATOR PIC X. 01 WS-VALID-OPERATOR PIC X VALUE 'N'. 88 VALID-OP VALUE 'Y'. PROCEDURE DIVISION. MAIN-LOGIC. * Test mathematical expressions MOVE "5 + 3 = 8" TO WS-MATH-EXPRESSION PERFORM VALIDATE-MATH-EXPRESSION MOVE "10 - 4 = 6" TO WS-MATH-EXPRESSION PERFORM VALIDATE-MATH-EXPRESSION MOVE "2 * 6 = 12" TO WS-MATH-EXPRESSION PERFORM VALIDATE-MATH-EXPRESSION STOP RUN. VALIDATE-MATH-EXPRESSION. DISPLAY "Expression: " WS-MATH-EXPRESSION * Check if expression uses valid math symbols IF WS-MATH-EXPRESSION IS MATH-ALPHABET DISPLAY "Valid mathematical expression" ELSE DISPLAY "Invalid mathematical expression" END-IF * Extract and validate operator PERFORM EXTRACT-OPERATOR IF VALID-OP DISPLAY "Valid operator: " WS-OPERATOR ELSE DISPLAY "Invalid operator: " WS-OPERATOR END-IF. EXTRACT-OPERATOR. * Extract operator from expression (simplified) MOVE WS-MATH-EXPRESSION(7:1) TO WS-OPERATOR * Check if operator is in math alphabet IF WS-OPERATOR IS MATH-ALPHABET SET VALID-OP TO TRUE ELSE SET VALID-OP TO FALSE END-IF.

Explanation: This example demonstrates using the SYMBOLIC clause for mathematical symbols. The program defines common mathematical operators (+, -, *, /, =, <, >) as symbolic characters in a math alphabet. This allows the program to validate mathematical expressions and ensure that only valid mathematical operators are used. The alphabet validation provides a way to check if expressions contain valid mathematical symbols.

Business Application Symbols

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
* SYMBOLIC clause for business application symbols IDENTIFICATION DIVISION. PROGRAM-ID. BUSINESS-SYMBOLIC-EXAMPLE. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. SYMBOLIC CHARACTERS CHECK-MARK X-MARK STAR-RATING ARROW-UP ARROW-DOWN BULLET-POINT IN BUSINESS-ALPHABET. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-STATUS-FIELD PIC X(20). 01 WS-RATING-FIELD PIC X(10). 01 WS-NOTE-FIELD PIC X(50). PROCEDURE DIVISION. MAIN-LOGIC. * Process status indicators MOVE "Task CHECK-MARK Complete" TO WS-STATUS-FIELD PERFORM PROCESS-STATUS MOVE "Task X-MARK Failed" TO WS-STATUS-FIELD PERFORM PROCESS-STATUS * Process ratings MOVE "STAR-RATING STAR-RATING STAR-RATING" TO WS-RATING-FIELD PERFORM PROCESS-RATING * Process notes with bullets MOVE "BULLET-POINT First item BULLET-POINT Second item" TO WS-NOTE-FIELD PERFORM PROCESS-NOTES STOP RUN. PROCESS-STATUS. DISPLAY "Status: " WS-STATUS-FIELD * Validate status symbols IF WS-STATUS-FIELD IS BUSINESS-ALPHABET DISPLAY "Valid status format" ELSE DISPLAY "Invalid status format" END-IF. PROCESS-RATING. DISPLAY "Rating: " WS-RATING-FIELD * Count stars in rating INSPECT WS-RATING-FIELD TALLYING WS-STAR-COUNT FOR ALL STAR-RATING DISPLAY "Star count: " WS-STAR-COUNT. PROCESS-NOTES. DISPLAY "Notes: " WS-NOTE-FIELD * Count bullet points INSPECT WS-NOTE-FIELD TALLYING WS-BULLET-COUNT FOR ALL BULLET-POINT DISPLAY "Bullet points: " WS-BULLET-COUNT.

Explanation: This example shows how to use the SYMBOLIC clause for business application symbols. The program defines common business symbols (check marks, X marks, stars, arrows, bullet points) as symbolic characters in a business alphabet. This allows the program to process status indicators, ratings, and formatted notes. The symbols can be counted, validated, and used in business logic to represent different states or formatting requirements.

Best Practices and Considerations

Important Considerations

  • SYMBOLIC is optional and can be omitted if not needed
  • Use descriptive names for symbolic characters
  • Consider portability when defining custom symbols
  • Test symbolic character definitions thoroughly
  • Document custom symbol meanings and usage

Advantages

  • Enables custom character definitions
  • Supports international applications
  • Provides character set validation
  • Allows specialized business symbols
  • Enhances character processing flexibility

Limitations

  • Implementation-dependent availability
  • May not be supported in all COBOL versions
  • Requires careful testing and validation
  • Can add complexity to program maintenance
  • May not be portable across different systems

Best Practices

  • • Use descriptive names for symbolic characters
  • • Document all custom symbol definitions
  • • Test symbolic character usage thoroughly
  • • Consider portability when defining symbols
  • • Use consistent naming conventions

Test Your Knowledge

1. What is the primary purpose of the SYMBOLIC clause in COBOL?

  • To define mathematical symbols
  • To define symbolic characters for custom character sets
  • To create symbolic links
  • To define symbolic constants

2. In which COBOL division is the SYMBOLIC clause typically used?

  • IDENTIFICATION DIVISION
  • ENVIRONMENT DIVISION
  • DATA DIVISION
  • PROCEDURE DIVISION

3. What is the relationship between SYMBOLIC and SPECIAL-NAMES?

  • They are the same thing
  • SYMBOLIC is a clause within SPECIAL-NAMES
  • SPECIAL-NAMES is a clause within SYMBOLIC
  • They are completely unrelated

4. What can be defined using the SYMBOLIC clause?

  • Only numeric characters
  • Only alphabetic characters
  • Custom symbolic characters for character sets
  • Only special punctuation marks

5. How are symbolic characters typically used in COBOL programs?

  • Only for display purposes
  • In alphabet definitions and character set operations
  • Only for mathematical operations
  • Only for file operations