MainframeMaster

COBOL DISPLAY-1 Format

Master the DISPLAY-1 numeric format for character-based representation of signed numeric data with separate sign storage in COBOL applications.

Overview

DISPLAY-1 is a specialized numeric data format in COBOL that stores signed numeric values as character strings with the sign stored in a separate character position. This format provides excellent readability and portability, making it ideal for data interchange between different systems and for applications where human-readable numeric data is required.

Unlike the standard DISPLAY format, which embeds the sign information in the zone bits of the last digit, DISPLAY-1 uses a dedicated character position for the sign. This approach eliminates potential compatibility issues between different systems and character sets, making DISPLAY-1 data truly portable across various platforms.

DISPLAY-1 format is particularly valuable in mainframe environments where data exchange with external systems is common, and in applications that require clear, unambiguous representation of signed numeric values. Understanding DISPLAY-1 is essential for developing robust COBOL applications that handle numeric data efficiently and reliably.

Basic Syntax and Declaration

DISPLAY-1 format is specified using the USAGE clause in data declarations:

cobol
1
2
3
4
5
6
DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-NUMERIC-FIELDS. 05 WS-AMOUNT PIC S9(7)V99 USAGE DISPLAY-1. 05 WS-QUANTITY PIC S9(5) USAGE DISPLAY-1. 05 WS-PERCENTAGE PIC S9(3)V99 USAGE DISPLAY-1.

The 'S' in the PICTURE clause indicates that the field is signed, and USAGE DISPLAY-1 specifies the storage format with separate sign representation.

Sign Position Control

You can control the position of the sign character using the SIGN clause:

cobol
1
2
3
4
5
01 WS-SIGNED-FIELDS. 05 WS-LEADING-SIGN PIC S9(5) USAGE DISPLAY-1 SIGN IS LEADING SEPARATE. 05 WS-TRAILING-SIGN PIC S9(5) USAGE DISPLAY-1 SIGN IS TRAILING SEPARATE.

LEADING SEPARATE places the sign before the digits, while TRAILING SEPARATE places it after the digits.

Storage and Memory Layout

Memory Allocation

DISPLAY-1 format requires specific memory allocation based on the field definition:

cobol
1
2
3
4
5
6
7
8
9
01 WS-STORAGE-EXAMPLES. * 5 digits + 1 sign = 6 bytes total 05 WS-FIELD-1 PIC S9(5) USAGE DISPLAY-1. * 7 digits + 2 decimal + 1 sign = 10 bytes total 05 WS-FIELD-2 PIC S9(7)V99 USAGE DISPLAY-1. * 3 digits + 1 sign = 4 bytes total 05 WS-FIELD-3 PIC S999 USAGE DISPLAY-1.

Each digit requires one byte, and the sign requires an additional byte, regardless of its position.

Character Representation

Understanding how values are stored in DISPLAY-1 format:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
WORKING-STORAGE SECTION. 01 WS-DEMO-VALUES. 05 WS-POSITIVE PIC S9(3) USAGE DISPLAY-1 VALUE +123. 05 WS-NEGATIVE PIC S9(3) USAGE DISPLAY-1 VALUE -456. 05 WS-ZERO PIC S9(3) USAGE DISPLAY-1 VALUE ZERO. PROCEDURE DIVISION. DISPLAY-STORAGE-FORMAT. * WS-POSITIVE stored as "+123" (4 bytes) * WS-NEGATIVE stored as "-456" (4 bytes) * WS-ZERO stored as "+000" (4 bytes) DISPLAY "Positive: " WS-POSITIVE DISPLAY "Negative: " WS-NEGATIVE DISPLAY "Zero: " WS-ZERO.

The sign character is explicitly visible and takes up a separate storage position.

Arithmetic Operations

Basic Calculations

DISPLAY-1 fields can be used directly in arithmetic operations:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
WORKING-STORAGE SECTION. 01 WS-CALC-FIELDS. 05 WS-NUM1 PIC S9(5)V99 USAGE DISPLAY-1. 05 WS-NUM2 PIC S9(5)V99 USAGE DISPLAY-1. 05 WS-RESULT PIC S9(7)V99 USAGE DISPLAY-1. PROCEDURE DIVISION. PERFORM-CALCULATIONS. MOVE 1234.56 TO WS-NUM1 MOVE -567.89 TO WS-NUM2 ADD WS-NUM1 TO WS-NUM2 GIVING WS-RESULT DISPLAY "Addition: " WS-RESULT MULTIPLY WS-NUM1 BY WS-NUM2 GIVING WS-RESULT DISPLAY "Multiplication: " WS-RESULT.

COBOL automatically handles the conversion between DISPLAY-1 format and internal arithmetic representation.

Mixed Format Operations

DISPLAY-1 fields can be used with other numeric formats:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
WORKING-STORAGE SECTION. 01 WS-MIXED-FORMATS. 05 WS-DISPLAY1 PIC S9(5)V99 USAGE DISPLAY-1. 05 WS-COMP3 PIC S9(5)V99 USAGE COMP-3. 05 WS-BINARY PIC S9(5)V99 USAGE BINARY. 05 WS-RESULT PIC S9(7)V99 USAGE DISPLAY-1. PROCEDURE DIVISION. MIXED-ARITHMETIC. MOVE 1000.50 TO WS-DISPLAY1 MOVE 2000.75 TO WS-COMP3 MOVE 500.25 TO WS-BINARY COMPUTE WS-RESULT = WS-DISPLAY1 + WS-COMP3 - WS-BINARY DISPLAY "Mixed calculation result: " WS-RESULT.

COBOL handles automatic conversion between different numeric formats during arithmetic operations.

Data Validation and Editing

Numeric Validation

Implementing validation for DISPLAY-1 numeric data:

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
WORKING-STORAGE SECTION. 01 WS-INPUT-FIELD PIC X(10). 01 WS-NUMERIC-FIELD PIC S9(7)V99 USAGE DISPLAY-1. 01 WS-VALIDATION-FLAGS. 05 WS-IS-NUMERIC PIC X(1). 05 WS-IS-VALID PIC X(1). PROCEDURE DIVISION. VALIDATE-INPUT. ACCEPT WS-INPUT-FIELD IF WS-INPUT-FIELD IS NUMERIC MOVE "Y" TO WS-IS-NUMERIC MOVE WS-INPUT-FIELD TO WS-NUMERIC-FIELD PERFORM RANGE-CHECK ELSE MOVE "N" TO WS-IS-NUMERIC DISPLAY "Invalid numeric input" END-IF. RANGE-CHECK. IF WS-NUMERIC-FIELD >= -9999999.99 AND WS-NUMERIC-FIELD <= 9999999.99 MOVE "Y" TO WS-IS-VALID DISPLAY "Valid number: " WS-NUMERIC-FIELD ELSE MOVE "N" TO WS-IS-VALID DISPLAY "Number out of range" END-IF.

Proper validation ensures data integrity when working with DISPLAY-1 fields.

Output Formatting

Formatting DISPLAY-1 data for output presentation:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
WORKING-STORAGE SECTION. 01 WS-SOURCE-AMOUNT PIC S9(7)V99 USAGE DISPLAY-1. 01 WS-FORMATTED-OUTPUT. 05 WS-SIGN-CHAR PIC X(1). 05 WS-DOLLAR-SIGN PIC X(1) VALUE "$". 05 WS-AMOUNT-EDIT PIC ZZ,ZZZ,ZZ9.99. PROCEDURE DIVISION. FORMAT-FOR-DISPLAY. MOVE 1234567.89 TO WS-SOURCE-AMOUNT IF WS-SOURCE-AMOUNT < ZERO MOVE "-" TO WS-SIGN-CHAR COMPUTE WS-SOURCE-AMOUNT = WS-SOURCE-AMOUNT * -1 ELSE MOVE "+" TO WS-SIGN-CHAR END-IF MOVE WS-SOURCE-AMOUNT TO WS-AMOUNT-EDIT DISPLAY WS-SIGN-CHAR WS-DOLLAR-SIGN WS-AMOUNT-EDIT.

This formatting approach provides professional output presentation while preserving the original DISPLAY-1 data.

File I/O and Data Exchange

File Processing

Using DISPLAY-1 fields in file processing operations:

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
DATA DIVISION. FILE SECTION. FD TRANSACTION-FILE. 01 TRANSACTION-RECORD. 05 TRANS-ID PIC X(10). 05 TRANS-AMOUNT PIC S9(9)V99 USAGE DISPLAY-1. 05 TRANS-DATE PIC X(8). 05 TRANS-TYPE PIC X(1). WORKING-STORAGE SECTION. 01 WS-TOTAL-AMOUNT PIC S9(11)V99 USAGE DISPLAY-1. 01 WS-RECORD-COUNT PIC 9(6) VALUE ZERO. PROCEDURE DIVISION. PROCESS-TRANSACTIONS. OPEN INPUT TRANSACTION-FILE PERFORM UNTIL WS-EOF = "Y" READ TRANSACTION-FILE AT END MOVE "Y" TO WS-EOF NOT AT END ADD 1 TO WS-RECORD-COUNT ADD TRANS-AMOUNT TO WS-TOTAL-AMOUNT PERFORM VALIDATE-TRANSACTION END-READ END-PERFORM CLOSE TRANSACTION-FILE DISPLAY "Total records: " WS-RECORD-COUNT DISPLAY "Total amount: " WS-TOTAL-AMOUNT.

DISPLAY-1 format ensures consistent numeric representation across different file processing operations.

Data Export and Import

Handling DISPLAY-1 data in export/import scenarios:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
WORKING-STORAGE SECTION. 01 WS-EXPORT-RECORD. 05 WS-FIELD1 PIC S9(7)V99 USAGE DISPLAY-1. 05 WS-FIELD2 PIC S9(5) USAGE DISPLAY-1. 05 WS-FIELD3 PIC S9(3)V999 USAGE DISPLAY-1. 01 WS-CSV-OUTPUT PIC X(100). PROCEDURE DIVISION. EXPORT-TO-CSV. MOVE 12345.67 TO WS-FIELD1 MOVE -999 TO WS-FIELD2 MOVE 123.456 TO WS-FIELD3 STRING WS-FIELD1 DELIMITED BY SIZE "," DELIMITED BY SIZE WS-FIELD2 DELIMITED BY SIZE "," DELIMITED BY SIZE WS-FIELD3 DELIMITED BY SIZE INTO WS-CSV-OUTPUT DISPLAY "CSV Output: " WS-CSV-OUTPUT.

DISPLAY-1 format provides excellent compatibility for data exchange with external systems.

Performance Considerations

Storage Efficiency

Comparing storage requirements across different numeric formats:

cobol
1
2
3
4
5
6
7
8
9
10
* Storage comparison for PIC S9(7)V99: 01 WS-STORAGE-COMPARISON. * DISPLAY-1: 10 bytes (7+2 digits + 1 sign) 05 WS-DISPLAY1 PIC S9(7)V99 USAGE DISPLAY-1. * COMP-3: 5 bytes (packed decimal) 05 WS-COMP3 PIC S9(7)V99 USAGE COMP-3. * BINARY: 8 bytes (binary representation) 05 WS-BINARY PIC S9(7)V99 USAGE BINARY.

DISPLAY-1 uses more storage than packed formats but provides superior readability and portability.

Processing Speed

Optimizing performance when using DISPLAY-1 fields:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
WORKING-STORAGE SECTION. 01 WS-PERFORMANCE-TEST. 05 WS-LOOP-COUNTER PIC 9(6) VALUE ZERO. 05 WS-START-TIME PIC 9(8). 05 WS-END-TIME PIC 9(8). 05 WS-DISPLAY1-SUM PIC S9(9)V99 USAGE DISPLAY-1. PROCEDURE DIVISION. PERFORMANCE-TEST. ACCEPT WS-START-TIME FROM TIME PERFORM VARYING WS-LOOP-COUNTER FROM 1 BY 1 UNTIL WS-LOOP-COUNTER > 100000 ADD 1.23 TO WS-DISPLAY1-SUM END-PERFORM ACCEPT WS-END-TIME FROM TIME COMPUTE WS-ELAPSED = WS-END-TIME - WS-START-TIME DISPLAY "Processing time: " WS-ELAPSED " centiseconds".

While DISPLAY-1 may be slower than binary formats, the performance difference is often negligible for most applications.

Best Practices and Guidelines

When to Use DISPLAY-1

Choose DISPLAY-1 format in these scenarios:

  • Data exchange with external systems requiring character-based numeric data
  • Applications where human readability of numeric data is important
  • Cross-platform data compatibility requirements
  • Debugging and testing scenarios where data inspection is needed
  • Legacy system integration where DISPLAY-1 format is established
  • Report generation with embedded numeric values

Implementation Guidelines

Follow these guidelines for effective DISPLAY-1 usage:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
* Good practice: Consistent sign positioning 01 WS-FINANCIAL-DATA. 05 WS-AMOUNT PIC S9(9)V99 USAGE DISPLAY-1 SIGN IS LEADING SEPARATE. 05 WS-BALANCE PIC S9(9)V99 USAGE DISPLAY-1 SIGN IS LEADING SEPARATE. 05 WS-INTEREST PIC S9(7)V99 USAGE DISPLAY-1 SIGN IS LEADING SEPARATE. * Good practice: Appropriate field sizing 01 WS-COUNTERS. 05 WS-SMALL-COUNT PIC S9(3) USAGE DISPLAY-1. 05 WS-MEDIUM-COUNT PIC S9(5) USAGE DISPLAY-1. 05 WS-LARGE-COUNT PIC S9(9) USAGE DISPLAY-1.

Consistent formatting and appropriate field sizing improve code maintainability and data integrity.

Hands-on Exercise

Exercise: Financial Calculator with DISPLAY-1

Create a COBOL program that implements a financial calculator using DISPLAY-1 format for all numeric operations.

Requirements:

  • Use DISPLAY-1 format for all monetary amounts
  • Implement basic arithmetic operations (add, subtract, multiply, divide)
  • Include input validation and error handling
  • Format output for professional presentation
  • Handle both positive and negative amounts
View Solution
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
69
70
71
72
73
74
75
IDENTIFICATION DIVISION. PROGRAM-ID. FINANCIAL-CALC. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-CALCULATOR-DATA. 05 WS-AMOUNT1 PIC S9(9)V99 USAGE DISPLAY-1 SIGN IS LEADING SEPARATE. 05 WS-AMOUNT2 PIC S9(9)V99 USAGE DISPLAY-1 SIGN IS LEADING SEPARATE. 05 WS-RESULT PIC S9(11)V99 USAGE DISPLAY-1 SIGN IS LEADING SEPARATE. 05 WS-OPERATION PIC X(1). 01 WS-INPUT-FIELDS. 05 WS-INPUT1 PIC X(15). 05 WS-INPUT2 PIC X(15). 01 WS-FORMATTED-OUTPUT. 05 WS-RESULT-EDIT PIC +Z,ZZZ,ZZZ,ZZ9.99. PROCEDURE DIVISION. MAIN-LOGIC. PERFORM GET-INPUTS PERFORM VALIDATE-INPUTS PERFORM CALCULATE-RESULT PERFORM DISPLAY-RESULT GOBACK. GET-INPUTS. DISPLAY "Enter first amount: " WITH NO ADVANCING ACCEPT WS-INPUT1 DISPLAY "Enter operation (+, -, *, /): " WITH NO ADVANCING ACCEPT WS-OPERATION DISPLAY "Enter second amount: " WITH NO ADVANCING ACCEPT WS-INPUT2. VALIDATE-INPUTS. IF WS-INPUT1 IS NUMERIC MOVE WS-INPUT1 TO WS-AMOUNT1 ELSE DISPLAY "Invalid first amount" GOBACK END-IF IF WS-INPUT2 IS NUMERIC MOVE WS-INPUT2 TO WS-AMOUNT2 ELSE DISPLAY "Invalid second amount" GOBACK END-IF. CALCULATE-RESULT. EVALUATE WS-OPERATION WHEN "+" ADD WS-AMOUNT1 TO WS-AMOUNT2 GIVING WS-RESULT WHEN "-" SUBTRACT WS-AMOUNT2 FROM WS-AMOUNT1 GIVING WS-RESULT WHEN "*" MULTIPLY WS-AMOUNT1 BY WS-AMOUNT2 GIVING WS-RESULT WHEN "/" IF WS-AMOUNT2 NOT = ZERO DIVIDE WS-AMOUNT1 BY WS-AMOUNT2 GIVING WS-RESULT ELSE DISPLAY "Division by zero error" GOBACK END-IF WHEN OTHER DISPLAY "Invalid operation" GOBACK END-EVALUATE. DISPLAY-RESULT. MOVE WS-RESULT TO WS-RESULT-EDIT DISPLAY "Result: " WS-RESULT-EDIT.

Quiz

Test Your Knowledge

1. How is the sign stored in DISPLAY-1 format?

2. What is the storage requirement for PIC S9(5) USAGE DISPLAY-1?

3. What is the main advantage of DISPLAY-1 over regular DISPLAY format?

View Answers

1. In a separate character position - DISPLAY-1 stores the sign in a dedicated character position, separate from the numeric digits.

2. 6 bytes - 5 bytes for the digits plus 1 byte for the separate sign character.

3. Better portability and readability - DISPLAY-1 provides superior cross-platform compatibility and human readability compared to regular DISPLAY format.

Frequently Asked Questions