Data Item (Variable) Declaration
Variable declaration syntax is an important aspect of COBOL programming to produce reliable and efficient code. Declaring variables is important and is required to process the data within the program.
The variable declaration is as follows -
level-number data-item|variable-name
PIC data-type-character(length)
[VALUE literal-value] [additional-clauses].
For example -
Level Number
The level number specifies the hierarchy of data items or variables in the declaration. It is a one- or two-digit numeric value. The valid level numbers are 01 to 49, 66, 77, and 88.
Level numbers are of two types based on their usage -
- General purpose level numbers (01 to 49) - General purpose level numbers declare regular variables that simply process the data.
The hierarchy of level numbers should be in ascending order.
For example, 01 is the highest level number, and 49 is the lowest level number.
Declaring a employee record having employee id under it representing the level numbers hierarchy.
01 EMPLOYEE-RECORD. 05 EMP-ID PIC 9(5).
- Special purpose level numbers (66, 77 and 88) - These level numbers are used to declare the variables for special purposes.
- 66 level number - It is used to create another logical group by regrouping the elementary variables of a group.
The RENAMES clause is used along with it to rename the group.
Renaming EMPLOYEE-RECORD as EMPLOYEE-REC01.01 EMPLOYEE-RECORD. 05 EMP-ID PIC 9(5). 05 EMP-NAME PIC X(45). 66 EMPLOYEE-REC01 RENAMES EMPLOYEE-RECORD.
- 77 level number - It is used to declare the individual variables.
It's not part of any hierarchical structure and doesn't subordinate other variables.
Declaring EMP-CTR as individual variable.
77 EMP-CTR PIC 9(03).
- 88 level number - It defines a condition name for a specific value or a set of values under the variable.
It can't declare a variable, but it is used to provide a descriptive name for a condition.
INVALID-EMP-ID is the condition name that is declared with 88 level number. INVALID-EMP-ID is equal to IF EMP-ID EQUAL LOW-VALUES OR SPACES.01 EMPLOYEE-RECORD. 05 EMP-ID PIC 9(5). 88 INVALID-EMP-ID VALUE LOW-VALUES SPACES.
- 66 level number - It is used to create another logical group by regrouping the elementary variables of a group.
The RENAMES clause is used along with it to rename the group.
Data item | Variable
A variable is a name used to hold the value for processing in the program. It is also called as a data item. It should be declared in the DATA DIVISION of the program. The variables are divided into three types and those are -
- Individual variable - An individual variable is declared individually but not under a group variable or as a group variable.
It always has the picture clause during its declaration.
* Individual variable 77 LEVEL-1 PIC 9(03) VALUE 256.
- Group variable - A Group variable is declared without the picture clause and has elementary variables declared under it.
It does not have a picture clause.
LEVEL-GROUP is a group variable.* Group variable 01 LEVEL-GROUP. * Elementary variables 05 LEVEL-21 PIC 9(03) VALUE 256. 05 LEVEL-22 PIC 9(03) VALUE 128.
- Elementary variable - The elementary variable is a variable that is declared under the group variable.
It should always have a PIC clause.
LEVEL-21, LEVEL-22 are the elementary variables.* Group variable 01 LEVEL-GROUP. * Elementary variables 05 LEVEL-21 PIC 9(03) VALUE 256. 05 LEVEL-22 PIC 9(03) VALUE 128.
PICTURE Clause
The PICTURE clause is used to specify the characteristics of the variable while declaring it. i.e., variable type, length, etc. PICTURE clause always codes with the symbol which is a letter used to specify the type of the variable. For example - A, B, E, G, N, P, S, V, X, Z, CR, DB.
Data Types
A data type defines the kind of data a variable can hold, such as numeric values, alphabetic characters, or alphanumeric strings. There are five data types in COBOL and those are -
Data Type | Description |
---|---|
Numeric | Numeric data type allows to declare the variables to store the numeric decimal values.
Numeric values are the combination of 0 to 9 numbers. Declaration Symbol - 9 Allowed Characters - 0 to 9. For Example -
|
Alphabet | Alphabetic data type allows to declare the variables to store the alphabetic strings.
Alphabetic strings are the combination of A to Z or a to z characters. Declaration Symbol - A Allowed Characters - Space + - * / = $ Comma(,) ; Decimal point(.) " ' ( ) > < : _ A-Z, a-z. For Example -
|
Alpha-numeric | Alphanumeric data type allows to declare the variables to store the strings that are combination of alphabets and numbers.
Alphanumeric strings are the combination of A to Z or a to z characters or 0 to 9 numbers. Declaration Symbol - X Allowed Characters - Space + - * / = $ Comma(,) ; Decimal point(.) " ' ( ) > < : _ A-Z, a-z 0-9. For Example -
|
Sign | Sign data type allows to declare the numeric variable with sign to capture the negative values.
Sign can specify for numeric values. i.e. sign data types can come up with numeric data type. Declaration Symbol - S Allowed Characters - - (minus) or + (plus) For Example -
|
Decimal point | When a data comes as a decimal to the program, a variable should declare with decimal point to handle the decimal value. Declaration Symbol - P/V Allowed Characters - . (Dot) For Example -
|
We will discuss more about this topic in the next chapter.
VALUE Clause
The VALUE clause is used to assign an initial value to a variable at the time of declaration. This initialization happens when the program starts executing and before any other operation occurs.
Examples -
Scenario1 - Alphanumeric Initialization.
WORKING-STORAGE SECTION.
01 WS-NAME PIC X(15) VALUE 'Mainframes'.
Here, the alphanumeric variable WS-NAME is initialized with the value 'Mainframes'.
Scenario2 - Numeric Initialization.
WORKING-STORAGE SECTION.
01 WS-AGE PIC 9(02) VALUE 25.
Additional Clauses -
Additional clauses may use on a need basis -
- BLANK WHEN ZERO Clause
is used to define a variable display spaces when its value is zero.
It is applicable to numeric, or numeric-edited variables.
Output -WORKING-STORAGE SECTION. 01 WS-VAR. * Declaring a variable with BLANK WHEN ZERO 05 WS-BWZ-VAR PIC ZZ,ZZ9.9(2) BLANK WHEN ZEROES. PROCEDURE DIVISION. MOVE ZEROES TO WS-BWZ-VAR. DISPLAY "WS-BWZ-VAR: " WS-BWZ-VAR. DISPLAY " ". MOVE 20000 TO WS-BWZ-VAR. DISPLAY "WS-BWZ-VAR: " WS-BWZ-VAR.
WS-BWZ-VAR: WS-BWZ-VAR: 20,000.00
- JUSTIFIED | JUST Clause
By default, alphabetic or alphanumeric data in COBOL variables is left aligned.
JUSTIFIED clause overrides the default data alignment and aligns it to the right while displaying it.
It applies only to alphabetic and alphanumeric variables.
Output -WORKING-STORAGE SECTION. 01 WS-VAR PIC X(15). 01 WS-RJE-VAR PIC X(15) JUSTIFIED RIGHT. PROCEDURE DIVISION. MOVE "MAINFRAMES" TO WS-VAR WS-RJE-VAR. DISPLAY "WS-VAR :" WS-VAR ":". DISPLAY "WS-RJE-VAR :" WS-RJE-VAR ":".
WS-VAR :MAINFRAMES : WS-RJE-VAR : MAINFRAMES:
- SYNCHRONIZED Clause
System allocates the variables at their respective natural memory boundaries and introduces the slack bytes (unused bytes between the boundary start and the previous allocation ending). For Example -
01 STUDENT. 05 STUDENT-NO PIC 9(02). 05 STUDENT-NAME PIC X(12). 05 STUDENT-GRADE PIC 9(02). 05 STUDENT-CLASS PIC X(03).
After the compiler inserts the slack bytes, the declaration is modified. For instance, after STUDENT-NO, the next item STUDENT-NAME starts from the boundary. Similarly, for STUDENT-GRADER, the STUDENT-CLASS starts from the boundary after the insertion of slack bytes. The declaration after slack bytes is -01 STUDENT. 05 STUDENT-NO PIC 9(02). [05 SLACK-BYTES PIC XX. INSERTED BY COMPILER] 05 STUDENT-NAME PIC X(12). 05 STUDENT-GRADE PIC 9(02). [05 SLACK-BYTES PIC XX. INSERTED BY COMPILER] 05 STUDENT-CLASS PIC X(03).
Four slack bytes are inserted if we do not use the SYNC clause. SYNC clause removes the slack bytes and allocates the variables continuously. The variables (followed by slack bytes) with SYNC clause to avoid the slack bytes as shown below -01 STUDENT. 05 STUDENT-NO PIC 9(02). 05 STUDENT-NAME PIC X(12) SYNC. 05 STUDENT-GRADE PIC 9(02). 05 STUDENT-CLASS PIC X(03) SYNC.