MainframeMaster

COBOL Tutorial

USAGE Clause in COBOL

Progress0 of 0 lessons

DISPLAY Usage (Default)

DISPLAY is the default USAGE in COBOL when no explicit USAGE is specified. It stores data in a human-readable character format, with each character or digit occupying one byte of storage.

DISPLAY Usage Examples

cobol
1
2
3
4
5
6
7
8
9
10
11
12
01 EMPLOYEE-RECORD. 05 EMPLOYEE-ID PIC 9(5) USAGE DISPLAY. 05 EMPLOYEE-NAME PIC X(30) USAGE DISPLAY. 05 DEPARTMENT-CODE PIC 99 USAGE IS DISPLAY. 05 SALARY PIC 9(7)V99 USAGE DISPLAY. *> Since DISPLAY is the default, these are equivalent to the above: 01 EMPLOYEE-RECORD-EQUIV. 05 EMPLOYEE-ID PIC 9(5). 05 EMPLOYEE-NAME PIC X(30). 05 DEPARTMENT-CODE PIC 99. 05 SALARY PIC 9(7)V99.

These examples show explicit and implicit DISPLAY usage for different data types.

Key characteristics of DISPLAY usage:

  • Each digit or character occupies one byte of storage
  • Numeric data is stored in character format (EBCDIC on mainframes, ASCII or Unicode on other platforms)
  • Human-readable without conversion
  • Sign information for numeric data is typically stored in the rightmost byte (overpunched)
  • Less efficient for arithmetic operations compared to binary formats
  • Works well for data that is primarily used for input/output and display purposes
  • Compatible with most external data formats

Note: For numeric fields with DISPLAY usage, sign information (for PIC S9...) is typically stored as an "overpunch" character in the rightmost digit position. This means that the last digit and the sign are combined into a single character, which can be confusing when examining raw data.

COMPUTATIONAL and COMP Variants

COMPUTATIONAL (or COMP for short) usage types store numeric data in binary format, which is more efficient for arithmetic operations. COBOL provides several variants of the COMPUTATIONAL usage with different characteristics.

COMPUTATIONAL Usage Examples

cobol
1
2
3
4
5
6
7
01 CALCULATION-FIELDS. 05 TOTAL-AMOUNT PIC 9(9)V99 USAGE COMPUTATIONAL. 05 COUNTER PIC 9(5) USAGE COMP. 05 RATE-PERCENT PIC 9(3)V9(2) USAGE IS COMP. 05 FLOAT-VALUE PIC 9(5)V9(2) USAGE COMP-1. 05 DOUBLE-VALUE PIC 9(10)V9(5) USAGE COMP-2. 05 SMALL-INTEGER PIC S9(4) USAGE COMP-5.

These examples show different COMPUTATIONAL usage variants for numeric data.

Common COMPUTATIONAL variants:

  • COMP or COMPUTATIONAL - Binary format, usually equivalent to COMP-4
  • COMP-1 - Single-precision floating-point (typically 4 bytes)
  • COMP-2 - Double-precision floating-point (typically 8 bytes)
  • COMP-3 - Packed-decimal format (see next section)
  • COMP-4 - Usually the same as COMP (binary)
  • COMP-5 - Binary format with native byte order (useful for interoperability with other languages)

Important: The exact implementation of COMP variants can vary between COBOL compilers. Always check your compiler's documentation for specific details about size, alignment, and behavior.

Storage Allocation for COMP/COMPUTATIONAL

Basic COMP (or COMP-4) allocates binary storage based on the number of digits in the PICTURE clause:

  • 1-4 digits: 2 bytes (halfword)
  • 5-9 digits: 4 bytes (fullword)
  • 10-18 digits: 8 bytes (doubleword)

Advantages of COMPUTATIONAL usage:

  • More efficient arithmetic operations
  • Can use less storage than DISPLAY for larger numbers
  • Better performance for intensive calculations
  • Direct compatibility with binary arithmetic hardware

Disadvantages of COMPUTATIONAL usage:

  • Not human-readable without conversion
  • May require conversion for external data exchange
  • Potential for platform-dependent behavior
  • Potential precision issues for very large numbers

PACKED-DECIMAL

PACKED-DECIMAL (often equivalent to COMP-3) is a hybrid storage format that balances storage efficiency and computational performance. It's especially popular on mainframe systems with hardware support for packed decimal operations.

PACKED-DECIMAL Usage Examples

cobol
1
2
3
4
5
01 FINANCE-FIELDS. 05 ACCOUNT-BALANCE PIC S9(13)V99 USAGE PACKED-DECIMAL. 05 TRANSACTION-AMOUNT PIC S9(7)V99 USAGE COMP-3. 05 INTEREST-RATE PIC 9(3)V9(5) USAGE IS PACKED-DECIMAL. 05 CUSTOMER-BALANCE PIC S9(11)V99 COMP-3.

These examples show PACKED-DECIMAL and equivalent COMP-3 usage for financial data.

Key characteristics of PACKED-DECIMAL:

  • Each byte stores two decimal digits (except the rightmost byte)
  • The rightmost byte contains the last digit and the sign
  • Requires approximately (n/2) + 1 bytes for n digits
  • More storage-efficient than DISPLAY for numeric data
  • Often preferred for financial calculations on mainframes
  • Provides exact decimal precision (no binary conversion issues)
  • Typically offers good performance on mainframe systems

Storage Format Example

For a field defined as PIC S9(5) USAGE PACKED-DECIMAL with a value of +12345:

  • Requires 3 bytes of storage
  • First byte: 0x01 (contains digits 0 and 1)
  • Second byte: 0x23 (contains digits 2 and 3)
  • Third byte: 0x45 (contains digit 4 and sign code C for positive)

For a negative value -12345:

  • Same as above except the last byte would be 0x4D (digit 4 and sign code D for negative)

Note: PACKED-DECIMAL is particularly well-suited for financial applications on mainframes. IBM mainframes have specialized hardware instructions for packed decimal arithmetic, making this format very efficient for financial calculations where exact decimal precision is required.

BINARY, BINARY-LONG, BINARY-SHORT

The BINARY usage and its variants store numeric data in native binary format. These usage types are often used for efficient arithmetic operations and interfacing with other programming languages.

BINARY Usage Examples

cobol
1
2
3
4
5
01 BINARY-DATA-ITEMS. 05 ITEM-COUNT PIC 9(4) USAGE BINARY. 05 RECORD-SIZE PIC 9(8) USAGE BINARY-LONG. 05 FLAG-VALUE PIC 9(2) USAGE BINARY-SHORT. 05 LARGE-COUNTER PIC 9(16) USAGE BINARY SYNC.

These examples show different BINARY usage variants for numeric data.

BINARY usage variants:

  • BINARY - Standard binary format (often equivalent to COMP)
  • BINARY-SHORT - Binary in short (halfword) format, typically 2 bytes
  • BINARY-LONG - Binary in long (fullword) format, typically 4 bytes
  • BINARY-DOUBLE - Binary in double (doubleword) format, typically 8 bytes

Key characteristics of BINARY usage:

  • Stores data in the computer's native binary format
  • Most efficient for arithmetic operations and loops
  • Often used for index values, counters, and array subscripts
  • Fixed storage size based on the variant used (not dependent on PICTURE digit count)
  • Can be used with the SYNCHRONIZED clause for aligned memory access
  • Directly compatible with system APIs and calls to other languages

Important: When using BINARY usage, be aware of the maximum values that can be stored. For example, BINARY-SHORT can only store values up to 32,767 (for signed) or 65,535 (for unsigned). Attempting to store larger values may result in truncation or unexpected behavior.

POINTER and Other Special USAGEs

Modern COBOL provides several specialized USAGE types for specific purposes, such as memory addressing, function references, and object-oriented programming.

Special USAGE Examples

cobol
1
2
3
4
5
6
7
01 SPECIAL-USAGES. 05 MEMORY-ADDRESS USAGE POINTER. 05 PROCEDURE-ADDRESS USAGE PROCEDURE-POINTER. 05 FUNCTION-ADDRESS USAGE FUNCTION-POINTER. 05 OBJECT-REFERENCE USAGE OBJECT REFERENCE. 05 STRING-HANDLE USAGE DISPLAY-1. 05 NATIONAL-STRING USAGE NATIONAL.

These examples show special USAGE types for various advanced purposes.

Common special USAGE types:

  • POINTER - Holds memory addresses, typically for dynamic memory allocation
  • PROCEDURE-POINTER - References a procedure or paragraph
  • FUNCTION-POINTER - References a function entry point
  • OBJECT REFERENCE - References an object in object-oriented COBOL
  • DISPLAY-1 - For DBCS (Double-Byte Character Set) data
  • NATIONAL - For Unicode data, typically using UTF-16

POINTER Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
WORKING-STORAGE SECTION. 01 BLOCK-SIZE PIC 9(8) COMP. 01 MEMORY-BLOCK USAGE POINTER. PROCEDURE DIVISION. SET BLOCK-SIZE TO 1024 CALL "GETMAIN" USING BLOCK-SIZE MEMORY-BLOCK *> Use the allocated memory *> Free the memory when done CALL "FREEMAIN" USING MEMORY-BLOCK

This example shows how POINTER usage might be used with dynamic memory allocation on a mainframe system.

Key points about special USAGE types:

  • Do not require a PICTURE clause (except for specific implementations)
  • Size is determined by the implementation and architecture
  • Provide advanced capabilities for modern programming techniques
  • Support for these types varies significantly between COBOL compilers
  • Typically used with specific statements like SET, CALL, or INVOKE
  • Essential for certain system programming tasks and interface with other languages

Note: Special USAGE types are primarily used in modern COBOL applications, especially those that interface with other systems or use object-oriented features. These USAGE types are less common in traditional legacy COBOL programs.

Choosing the Right USAGE

Selecting the appropriate USAGE clause for your data items is an important design decision that affects performance, storage requirements, and compatibility. Here are some guidelines for choosing the right USAGE.

USAGE Selection Guidelines

Data TypeRecommended USAGEReason
Input/Output fieldsDISPLAYCompatible with external data formats, human-readable
Calculation-intensive numericsCOMP, BINARYBest performance for arithmetic operations
Financial dataPACKED-DECIMAL, COMP-3Exact decimal precision, efficient storage, good mainframe performance
Index values, countersBINARY, COMP-5Efficient for loop processing
Floating-point calculationsCOMP-1, COMP-2Required for floating-point operations
Memory addressingPOINTERRequired for dynamic memory handling
Unicode textNATIONALProper handling of international character sets

Considerations for USAGE selection:

  • Performance - Choose COMP or BINARY for calculation-intensive fields
  • Storage efficiency - PACKED-DECIMAL (COMP-3) often provides the best balance
  • Precision requirements - PACKED-DECIMAL for exact decimal precision
  • Compatibility - DISPLAY for external interfaces and human-readable data
  • Platform considerations - Use PACKED-DECIMAL on mainframes with hardware support
  • Data size - For large numbers, PACKED-DECIMAL or COMP may be more efficient
  • Compiler support - Check which USAGE types are supported by your compiler

Exercises

  1. Compare storage requirements

    Create a program that defines the same numeric value (e.g., 9999999999) using different USAGE clauses and determine how much storage each requires.

  2. Performance comparison

    Write a program that performs the same calculation (e.g., a loop with many additions) using fields with different USAGE clauses and compare the execution time.

  3. Design a financial record

    Create a complete financial transaction record structure, choosing appropriate USAGE clauses for each field based on its purpose and requirements.

  4. POINTER usage experiment

    Write a simple program that uses POINTER usage to allocate and work with dynamic memory.

  5. Mixed USAGE operations

    Experiment with arithmetic operations involving fields with different USAGE clauses to observe how COBOL handles the conversions.

FAQ Section

Test Your Knowledge

1. What is the default USAGE for data items in COBOL?

  • COMPUTATIONAL
  • DISPLAY
  • BINARY
  • PACKED-DECIMAL

2. Which USAGE type stores numeric data in the form that humans can read directly?

  • COMP
  • BINARY
  • DISPLAY
  • PACKED-DECIMAL

3. What is the main advantage of using COMP or COMPUTATIONAL usage?

  • It uses less storage space
  • It makes data easier to read
  • It improves arithmetic processing speed
  • It makes data portable across systems

4. Which USAGE is generally synonymous with COMPUTATIONAL-3 in most COBOL implementations?

  • BINARY
  • DISPLAY
  • PACKED-DECIMAL
  • POINTER

5. What type of data would you typically store with USAGE POINTER?

  • Numeric values for calculations
  • Character data
  • Memory addresses
  • Dates and times