MainframeMaster

COBOL Tutorial

PICTURE Clause in COBOL

Progress0 of 0 lessons

PICTURE Clause Syntax and Purpose

The PICTURE clause (often abbreviated as PIC) is one of the most fundamental elements in COBOL data definition. It defines the format and size of a data item, specifying its data type, length, and how it should be displayed or interpreted.

Basic PICTURE Clause Syntax

cobol
1
2
3
4
5
6
05 EMPLOYEE-ID PIC 9(5). 05 EMPLOYEE-NAME PIC X(30). 05 HOURLY-RATE PIC 9(3)V99. 05 HIRE-DATE PIC 9(8). 05 DEPARTMENT-CODE PIC AA9. 05 TAX-AMOUNT PIC $Z,ZZ9.99.

These examples show various PICTURE clause formats used to define different types of data.

The PICTURE clause serves several important purposes:

  • Defines the data type (numeric, alphabetic, or alphanumeric)
  • Specifies the size of the field in memory
  • Determines how data is represented internally
  • Controls how data will be formatted for display or output
  • Provides implicit data validation for input

The PICTURE clause consists of the keyword PIC or PICTURE followed by a character string that defines the data characteristics. The character string can contain:

  • Data characters: 9, A, X, etc.
  • Operational symbols: S, V, P
  • Editing symbols: Z, $, ., B, etc.
  • Repetition factors: 9(5) = 99999

Note: The PICTURE clause only applies to elementary items, not group items. A group item inherits its characteristics from its constituent elementary items.

Numeric PIC Specifications (9, V, S, P)

Numeric PICTURE specifications are used to define fields that contain numeric data and can be used in arithmetic operations. Several special characters are used to define various aspects of numeric data.

Numeric PICTURE Examples

cobol
1
2
3
4
5
6
7
05 WHOLE-NUMBER PIC 9(5). *> 5-digit whole number 05 DECIMAL-NUMBER PIC 9(3)V99. *> 3 digits before and 2 after decimal 05 SIGNED-NUMBER PIC S9(7). *> 7-digit signed number 05 NEGATIVE-NUMBER PIC S9(5)V99. *> Signed with 2 decimal places 05 SCALED-NUMBER PIC 9(5)P(2). *> Multiplied by 100 05 P-SCALED-NUMBER PIC P(2)9(5). *> Divided by 100 05 LARGE-AMOUNT PIC 9(10)V99. *> 10 digits with 2 decimal places

These examples show different numeric PICTURE clauses using various numeric symbols.

Key numeric PICTURE symbols:

  • 9 - Represents a numeric digit position (0-9)
  • V - Indicates an implied decimal point (no storage allocated)
  • S - Indicates a sign for the number (+ or -)
  • P - Scaling position (implied decimal scaling, no storage allocated)
How V and P differ:
  • The V indicates where a decimal point is conceptually located but does not occupy storage or appear in the data.
  • The P indicates an implied decimal scaling—multiplication or division by a power of 10—and does not occupy storage.
  • For example, PIC 999V99 means 3 digits, decimal point, 2 digits (like 123.45).
  • PIC 999P means 3 digits multiplied by 10 (like 1230 stored as 123).
  • PIC P999 means 3 digits divided by 10 (like 12.3 stored as 123).

Behavior of numeric fields:

  • Can be used in arithmetic operations
  • Default initialization is zero
  • Alignment is based on the decimal point (V) when moving between numeric fields
  • The S symbol impacts both storage and operations, allowing representation of negative values
  • The actual storage format depends on the USAGE clause (DISPLAY, COMP, etc.)

Alphanumeric PIC Specifications (X, A, 9)

Alphanumeric PICTURE specifications define fields that can contain letters, digits, and special characters. These fields are used for text data that isn't used in arithmetic operations.

Alphanumeric PICTURE Examples

cobol
1
2
3
4
5
6
7
05 CUSTOMER-NAME PIC X(30). *> Any 30 characters 05 PRODUCT-CODE PIC X(10). *> 10-character code 05 ADDRESS-LINE PIC X(50). *> 50-character address 05 LAST-NAME PIC A(20). *> 20 alphabetic characters 05 STATE-CODE PIC AA. *> 2-letter state code 05 ALPHANUMERIC-CODE PIC AAA99. *> 3 letters followed by 2 digits 05 MIXED-CODE PIC A(3)X(5). *> 3 letters followed by 5 any chars

These examples show different alphanumeric PICTURE clauses for text and code data.

Key alphanumeric PICTURE symbols:

  • X - Represents any character (letters, digits, special characters)
  • A - Represents alphabetic characters only (A-Z, a-z, space)
  • 9 - When used in alphanumeric context, represents numeric digits

Important: When '9' is used in a field with 'A' or 'X', it loses its numeric properties—the field becomes alphanumeric and cannot be used in arithmetic operations. For example, PIC A9 defines a 2-character alphanumeric field where the first position must be alphabetic and the second must be a digit.

Behavior of alphanumeric fields:

  • Cannot be used in arithmetic operations
  • Default initialization is spaces
  • Alignment is left-justified when moving between alphanumeric fields
  • Truncation or padding occurs on the right when moving between fields of different sizes
  • PIC X fields accept any characters; PIC A fields will cause validation errors if non-alphabetic data is moved to them

Editing Characters (Z, $, ., B, etc.)

Editing characters allow you to format numeric data for display or reporting. They define how numbers will appear when used in output operations, controlling aspects like leading zero suppression, insertion of separators, and currency symbols.

Editing Characters Examples

cobol
1
2
3
4
5
6
7
05 AMOUNT-Z PIC Z,ZZ9.99. *> Leading zero suppression 05 AMOUNT-DOLLAR PIC $,$$9.99. *> Currency symbol 05 PHONE-NUMBER PIC 999B999B9999. *> Space insertion 05 DASH-NUMBER PIC 999-999-9999. *> Dash insertion 05 CR-DR-AMOUNT PIC 9(6).99CR. *> Credit notation 05 PLUS-MINUS-AMT PIC +9(6).99. *> Explicit sign 05 STARRED-CHECK-AMT PIC $**,***,**9.99. *> Check protection

These examples show different editing characters used for formatted display of numeric data.

Common editing characters:

  • Z - Replace leading zeros with spaces
  • $ - Insert a currency symbol
  • . - Insert a decimal point at this position
  • , - Insert a comma (typically as a thousands separator)
  • B - Insert a blank space
  • - - Insert a minus sign or display a minus for negative values
  • + - Insert a plus sign or display appropriate sign
  • CR/DB - Display CR for negative values, spaces for positive
  • * - Replace leading zeros with asterisks (check protection)
  • 0 - Insert a zero at this position
  • / - Insert a slash character

Note: Fields with editing characters are treated as alphanumeric fields and cannot be used in arithmetic operations. They are typically used for displaying results rather than for computation.

Key points about edited numeric fields:

  • Editing characters only affect how data is displayed, not how it's stored
  • To perform calculations on an edited field, you must first move the data to a non-edited numeric field
  • Moving data to an edited field automatically applies the formatting
  • The Z character and $ character can float (appear immediately to the left of the first significant digit)
  • Multiple editing symbols can be combined to create complex formats

PIC Clause Examples and Usage

Let's see some practical examples of how PICTURE clauses are used in real COBOL programs for different scenarios.

Employee Record Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
01 EMPLOYEE-RECORD. 05 EMP-ID PIC 9(5). 05 EMP-NAME. 10 LAST-NAME PIC X(20). 10 FIRST-NAME PIC X(15). 10 MIDDLE-INIT PIC X. 05 EMP-ADDRESS. 10 STREET PIC X(30). 10 CITY PIC X(20). 10 STATE PIC XX. 10 ZIP-CODE PIC 9(5)X(4). 05 EMP-DOB. 10 DOB-YEAR PIC 9(4). 10 DOB-MONTH PIC 99. 10 DOB-DAY PIC 99. 05 EMP-HIRE-DATE PIC 9(8). 05 EMP-SALARY PIC 9(7)V99. 05 EMP-DEPARTMENT PIC 9(3). 05 EMP-STATUS PIC X. 88 EMP-ACTIVE VALUE 'A'. 88 EMP-TERMINATED VALUE 'T'. 88 EMP-LEAVE VALUE 'L'.

This example shows various PICTURE clauses used in an employee record structure.

Financial Report Line Example

cobol
1
2
3
4
5
6
7
8
9
10
11
01 FINANCIAL-REPORT-LINE. 05 FILLER PIC X(5) VALUE SPACES. 05 ACCOUNT-NUMBER-OUT PIC X(10). 05 FILLER PIC X(2) VALUE SPACES. 05 ACCOUNT-NAME-OUT PIC X(20). 05 FILLER PIC X(2) VALUE SPACES. 05 PREVIOUS-BALANCE-OUT PIC $$$,$$$,$$9.99-. 05 FILLER PIC X(2) VALUE SPACES. 05 CURRENT-BALANCE-OUT PIC $$$,$$$,$$9.99-. 05 FILLER PIC X(2) VALUE SPACES. 05 PERCENT-CHANGE-OUT PIC ---9.99%.

This example shows how PICTURE clauses with editing characters are used in a report line.

Data Validation Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
01 CUSTOMER-INPUT-RECORD. 05 CUST-ID-IN PIC X(8). 05 CUST-NAME-IN PIC X(30). 05 CUST-PHONE-IN PIC X(12). 05 CUST-BALANCE-IN PIC X(10). 01 VALIDATED-CUSTOMER-DATA. 05 CUST-ID PIC X(8). 05 CUST-NAME PIC X(30). 05 CUST-PHONE. 10 AREA-CODE PIC 9(3). 10 PHONE-PREFIX PIC 9(3). 10 PHONE-SUFFIX PIC 9(4). 05 CUST-BALANCE PIC S9(8)V99. 01 ERROR-FLAGS. 05 ID-ERROR-FLAG PIC X VALUE 'N'. 88 ID-ERROR VALUE 'Y'. 05 PHONE-ERROR-FLAG PIC X VALUE 'N'. 88 PHONE-ERROR VALUE 'Y'. 05 BALANCE-ERROR-FLAG PIC X VALUE 'N'. 88 BALANCE-ERROR VALUE 'Y'.

This example shows how PICTURE clauses are used in data validation scenarios.

Best practices for using PICTURE clauses:

  • Choose the appropriate data type (numeric vs. alphanumeric) based on how the data will be used
  • Define fields with sufficient length to accommodate the maximum expected data size
  • Use the S symbol for numeric fields that might contain negative values
  • Use editing characters only for display fields, not for fields used in calculations
  • Consider the USAGE clause in conjunction with the PICTURE clause for optimal storage and performance
  • Use level 88 items with numeric and alphanumeric fields to create meaningful condition names
  • Document unusual or complex PICTURE clauses with comments

Exercises

  1. Define PICTURE clauses for a customer record

    Create appropriate PICTURE clauses for a customer record that includes customer ID, name, address, phone number, email, account balance, and credit limit.

  2. Design a financial report line

    Create a report line structure with appropriate edited numeric fields to display account numbers, descriptions, and monetary values with proper formatting.

  3. Work with decimal point alignment

    Write a program that demonstrates decimal point alignment when moving values between numeric fields with different PICTURE clauses (different numbers of decimal positions).

  4. Experiment with editing characters

    Create a series of PICTURE clauses using different editing characters to format the same numeric value (e.g., 12345.67) in various ways.

  5. Use the P symbol for scaling

    Demonstrate the use of the P symbol for scaling by creating fields that automatically multiply or divide values by powers of 10.

FAQ Section

Test Your Knowledge

1. Which PICTURE symbol is used for decimal point alignment in numeric fields?

  • V
  • P
  • .
  • S

2. What does PIC X(10) specify?

  • A 10-digit numeric field
  • A 10-character alphanumeric field
  • A 10-position alphabetic field
  • A 10-decimal place numeric field

3. Which PICTURE character is used to represent a sign position in a numeric field?

  • S
  • +
  • -
  • Z

4. What does the editing character Z do in a PICTURE clause?

  • Zeros are displayed as zeros
  • Leading zeros are displayed as spaces
  • Trailing zeros are displayed as spaces
  • Zeros are displayed as Z characters

5. Which PICTURE specification would correctly define a field for a monetary amount like $1,234.56?

  • PIC $9,999.99
  • PIC $9(4).99
  • PIC $Z,ZZ9.99
  • PIC $,$$$,$$9.99