MainframeMaster

COBOL Tutorial

Data Types and Representation in COBOL

Progress0 of 0 lessons

Numeric Data Representation and Formats

COBOL provides several ways to represent numeric data, each with its own characteristics and uses.

External Decimal (DISPLAY)

cobol
1
01 EXT-DEC-FIELD PIC 9(5) USAGE DISPLAY.
  • Default if USAGE is not specified
  • Each digit uses one byte of storage
  • Stored as character data (e.g., "12345")
  • Human-readable in memory dumps
  • Less efficient for calculations

Binary (COMP, COMP-4, BINARY)

cobol
1
01 BINARY-FIELD PIC 9(5) USAGE COMP.
  • Stored in binary format
  • More efficient for calculations
  • Uses less storage than DISPLAY
  • PIC 9(1) to 9(4): 2 bytes
  • PIC 9(5) to 9(9): 4 bytes
  • PIC 9(10) to 9(18): 8 bytes

Packed Decimal (COMP-3)

cobol
1
01 PACKED-FIELD PIC 9(5) USAGE COMP-3.
  • Stores 2 digits per byte plus sign
  • PIC 9(5) uses 3 bytes of storage
  • Efficient storage and calculation
  • Common on mainframe systems
  • Each byte contains two 4-bit nibbles

Floating Point (COMP-1, COMP-2)

cobol
1
2
01 FLOAT-SINGLE PIC 9(9) USAGE COMP-1. 01 FLOAT-DOUBLE PIC 9(18) USAGE COMP-2.
  • COMP-1: Single precision (4 bytes)
  • COMP-2: Double precision (8 bytes)
  • For scientific calculations
  • PICTURE clause is ignored
  • Can handle very large or small values

Alphanumeric Data Handling

Alphanumeric data in COBOL can contain any character in the character set, including letters, numbers, and special characters.

Alphanumeric Data Types

cobol
1
2
3
4
01 ALPHA-X PIC X(10). *> Any character 01 ALPHA-A PIC A(10). *> Alphabetic only 01 ALPHA-MIXED PIC X(5)A(5). *> Mixed format 01 ALPHA-EDIT PIC X(5)/X(5). *> With editing
  • PIC X: Can contain any character
  • PIC A: Can contain only letters and spaces
  • PIC 9: Can contain only numeric digits (when used for display)
  • Editing characters can be included for formatting

Common Operations

cobol
1
2
3
4
5
6
7
MOVE "HELLO" TO ALPHA-X. *> Simple assignment MOVE SPACES TO ALPHA-X. *> Initialize with spaces MOVE "12345" TO ALPHA-X. *> Numbers as text IF ALPHA-A IS ALPHABETIC *> Conditional test DISPLAY "Contains only letters and spaces". STRING "Hello " "World" DELIMITED BY SIZE INTO ALPHA-X. *> String concatenation

Signed Numbers Handling

COBOL provides mechanisms for representing signed numbers through the PICTURE clause and specific USAGE options.

Defining Signed Numbers

cobol
1
2
3
4
01 SIGNED-DISP PIC S9(5) USAGE DISPLAY. 01 SIGNED-COMP PIC S9(5) USAGE COMP. 01 SIGNED-COMP3 PIC S9(5) USAGE COMP-3. 01 UNSIGNED-NUM PIC 9(5). *> No sign

The 'S' in the PICTURE clause indicates that the field can hold a sign (positive or negative).

Sign Representation

  • DISPLAY: Sign is typically stored in the rightmost byte (overpunch)
  • COMP: Sign is part of the binary representation
  • COMP-3: Sign is stored in the rightmost nibble (C=positive, D=negative)
  • The SIGN clause can control sign position: SIGN IS LEADING or SIGN IS TRAILING
  • The SIGN clause can also control sign representation: SIGN IS SEPARATE

Examples with Different Sign Representations

cobol
1
2
3
4
5
6
7
8
9
10
01 TRAIL-SEPARATE PIC S9(5) SIGN TRAILING SEPARATE. 01 LEAD-SEPARATE PIC S9(5) SIGN LEADING SEPARATE. 01 TRAIL-COMBINED PIC S9(5) SIGN TRAILING. 01 LEAD-COMBINED PIC S9(5) SIGN LEADING. *> For value -12345: *> TRAIL-SEPARATE would be stored as: "12345-" *> LEAD-SEPARATE would be stored as: "-12345" *> TRAIL-COMBINED would have the sign combined with the last digit *> LEAD-COMBINED would have the sign combined with the first digit

Decimal Point Alignment

In COBOL, the decimal point is not physically stored in the data but is defined by the PICTURE clause.

Using the V Symbol

cobol
1
2
3
01 AMOUNT-1 PIC 9(5)V99. *> 5 digits before, 2 after decimal 01 AMOUNT-2 PIC 9(3)V9(3). *> Alternative notation 01 DISPLAY-AMOUNT PIC Z(4)9.99. *> For display with actual decimal point
  • The V indicates the position of an assumed decimal point
  • No actual decimal point is stored in memory
  • For display, you need a separate field with an actual decimal point

Decimal Alignment in Operations

cobol
1
2
3
4
5
6
01 PRICE PIC 9(3)V99 VALUE 012.50. 01 QUANTITY PIC 9(3) VALUE 003. 01 TOTAL PIC 9(5)V99. MULTIPLY PRICE BY QUANTITY GIVING TOTAL. *> TOTAL will contain 0037.50 (internally stored as 003750)

COBOL automatically handles decimal alignment during arithmetic operations.

P Symbol for Assumed Decimal Scaling

cobol
1
2
01 LARGE-VALUE PIC 9(3)P(2). *> Multiplies value by 100 (adds 2 zeros) 01 SMALL-VALUE PIC VP(2)9(3). *> Divides value by 100 (0.01234)
  • The P symbol represents an assumed zero digit
  • Used for scaling factors when no storage is needed for those positions
  • Trailing P: Multiplies the value (shifts decimal right)
  • Leading P: Divides the value (shifts decimal left)

Handling Special Characters

COBOL provides several techniques for handling special characters in data.

Special Characters in Literals

cobol
1
2
3
4
5
6
7
8
9
10
01 TEXT-FIELD PIC X(20). *> Single quote in a double-quoted literal MOVE "John's Book" TO TEXT-FIELD. *> Double quote in a single-quoted literal MOVE 'Say "Hello"' TO TEXT-FIELD. *> Quotation mark figurative constant MOVE QUOTE TO TEXT-FIELD(1:1).

Currency and Other Symbols

cobol
1
2
3
4
5
6
7
8
01 AMOUNT PIC $$,$$9.99. 01 CUSTOM-CURR PIC X(10). *> Currency symbol from SPECIAL-NAMES MOVE 123.45 TO AMOUNT. *> Shows as $ 123.45 *> Custom currency character MOVE '€123.45' TO CUSTOM-CURR.

SPECIAL-NAMES for Character Customization

cobol
1
2
3
4
5
6
7
8
9
10
11
ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. CURRENCY SIGN IS "€" DECIMAL-POINT IS COMMA. DATA DIVISION. WORKING-STORAGE SECTION. 01 EURO-AMOUNT PIC €€€.€€9,99. *> With these settings, €123,45 will be displayed instead of $123.45

The SPECIAL-NAMES paragraph allows customization of currency symbols and decimal point characters.

Inspecting and Manipulating Special Characters

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
01 INPUT-TEXT PIC X(50). 01 OUTPUT-TEXT PIC X(50). 01 TALLY-COUNT PIC 9(3). *> Replace all special characters with spaces INSPECT INPUT-TEXT REPLACING ALL "!" BY SPACE ALL "@" BY SPACE ALL "#" BY SPACE ALL "$" BY SPACE. *> Count occurrences of a special character INSPECT INPUT-TEXT TALLYING TALLY-COUNT FOR ALL "@". *> Convert special characters to a string STRING INPUT-TEXT DELIMITED BY "@" INTO OUTPUT-TEXT.

Exercise: Working with Data Types

Complete the following COBOL program to properly handle different data types:

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
IDENTIFICATION DIVISION. PROGRAM-ID. DATATYPES. DATA DIVISION. WORKING-STORAGE SECTION. 01 SALES-DATA. 05 PRODUCT-ID PIC X(5). 05 QUANTITY PIC 9(3). 05 UNIT-PRICE PIC 9(3)V99. 05 DISCOUNT-PERCENT PIC 9(2)V9. 05 TAX-RATE PIC V999. 01 CALCULATION-FIELDS. 05 SUBTOTAL PIC 9(5)V99. 05 DISCOUNT-AMOUNT PIC 9(4)V99. 05 TAX-AMOUNT PIC 9(4)V99. 05 TOTAL-PRICE PIC 9(5)V99. 01 DISPLAY-FIELDS. 05 DISPLAY-SUBTOTAL PIC $Z,ZZ9.99. 05 DISPLAY-DISCOUNT PIC $Z,ZZ9.99. 05 DISPLAY-TAX PIC $Z,ZZ9.99. 05 DISPLAY-TOTAL PIC $Z,ZZ9.99. PROCEDURE DIVISION. MOVE "AB123" TO PRODUCT-ID. MOVE 10 TO QUANTITY. MOVE 24.95 TO UNIT-PRICE. MOVE 15.0 TO DISCOUNT-PERCENT. MOVE .075 TO TAX-RATE. *> Calculate subtotal (quantity * unit price) *> Calculate discount amount (subtotal * discount percentage / 100) *> Calculate tax amount (subtotal - discount) * tax rate *> Calculate total price (subtotal - discount + tax) *> Move numeric values to display fields *> Display the results DISPLAY "Product: " PRODUCT-ID. DISPLAY "Quantity: " QUANTITY. DISPLAY "Unit Price: $" UNIT-PRICE. DISPLAY "Subtotal: " DISPLAY-SUBTOTAL. DISPLAY "Discount: " DISPLAY-DISCOUNT. DISPLAY "Tax: " DISPLAY-TAX. DISPLAY "Total: " DISPLAY-TOTAL. STOP RUN.

Complete the calculation logic and ensure proper numeric handling.

Knowledge Check

Test Your Knowledge

1. How are signed numbers represented in COBOL?

  • Using the S in the PICTURE clause
  • Using the SIGNED clause
  • Using negative values in the VALUE clause
  • All numbers are signed by default

2. Which of the following PICTURE clauses correctly represents a field that can store dollar amounts up to $9,999.99?

  • PIC 9(4)V99
  • PIC $9,999.99
  • PIC $9(4).9(2)
  • PIC Z,ZZZ.99

3. In COBOL, where is the decimal point actually stored in numeric data?

  • As a physical decimal point character in the data
  • It is not stored; its position is defined by the PICTURE clause
  • In a separate metadata field
  • As a special byte marker

4. How would you define a numeric field to store a signed value with 5 digits to the left of the decimal and 2 to the right?

  • PIC S9(5)V99
  • PIC S9(5).9(2)
  • PIC S9(5)-9(2)
  • PIC S99999V99

5. Which of the following statements about alphanumeric data in COBOL is true?

  • Alphanumeric fields can only store letters and numbers
  • Alphanumeric fields automatically convert lowercase to uppercase
  • Alphanumeric fields can store any character in the character set
  • Alphanumeric fields require a specific encoding directive

Frequently Asked Questions