Back to first page...

THE DATA DIVISION

This is the most important and most crowded division of COBOL programs. All variables, arrays and structures are declared here. The programmer is NOT FREE to declare his/her variables, arrays and structures ( collectrively called DATA NAMES in COBOL jargon) in any order he/she wants. Structure declarations that define the layout of file records go into a special section called the FILE SECTION. Other data names go into another section; namely the WORKING-STORAGE SECTION.

The File Section

The general syntax of FILE SECTION entries is :

       FD    file-name
             LABEL RECORDS ARE {STANDARD or OMITTED}
             RECORD CONTAINS nnnn CHARACTERS
             DATA RECORD IS structure-name.
       01    structure-name.
             02 xxxx    PIC  {XX...X or 99...9}.
             02 yyyy    PIC  {XX...X or 99...9}.
             02 xxxx.
                03 zzz  PIC  {XX...X or 99...9}.
                   etc.

An example would look like :

       FD    STUDENT-FILE
             LABEL RECORDS ARE STANDARD
             RECORD CONTAINS 56 CHARACTERS
             DATA RECORD IS STUDENT-REC.
       01    STUDENT-REC.
             02 STU-NAME.
                03 SURNAME          PIC X(16).
                03 MID_INITIAL      PIC X.
                03 NAME             PIC X(16).
             02 REGISTRATION-DATE.
                03 REG-DD           PIC 99.
                03 REG-MM           PIC 99.
                03 REG-YYYY         PIC 9999.
             02 DEPT-CODE           PIC XXXXX.
             02 STUDENT-NUMBER      PIC 9(10).
Now, lets have a closer look at these statements :
       FD    STUDENT-FILE
             LABEL RECORDS ARE STANDARD
             RECORD CONTAINS 56 CHARACTERS
             DATA RECORD IS STUDENT-REC.
These statements declare that a file called STUDENT-FILE is going to be used in this program. It is not shown here, but we are sure that this symbolic file name STUDENT-FILE is already associated to a physical (or actual) file name in a SELECT statement in the ENVIRONMENT DIVISION.

The LABEL RECORDS ARE STANDARD statement is an almost standard statement used for disk files. Usually label records and this declarative statements make sense for tape files; that is, files that are kept on magnetic tapes rather than disks. For disk files, you should declare STANDARD LABEL RECORDS.

The RECORD CONTAINS 56 CHARACTERS statement declares the record length for the file to fixed and 56 bytes. If you are going to use a file with variable length records, you should re-phrase the statement into something like :

        RECORD CONTAINS 50 TO 80 CHARACTERS
or
        RECORD IS VARYING IN SIZE FROM 50 TO 80 CHARACTERS
or even
        RECORD IS VARYING IN SIZE FROM 50 TO 80 CHARACTERS
               DEPENDING UPON REC-LEN
Advice : Try to avoid using variable length record data files in COBOL like in ANY other language. They are usually a head ache.

The DATA RECORD IS STUDENT-REC phrase indicates that the layout of the data records will be declared under the structure "STUDENT-REC". If your file contains different records laid out in different formats, you can declare multiple DATA RECORDS. For example, DATA RECORDS ARE STU-REC1 STU-REC2 is such a declarative, but this technique is seldom used.

Finally,
       01    STUDENT-REC.
             02 STU-NAME.
                03 SURNAME          PIC X(16).
                03 MID_INITIAL      PIC X.
                03 NAME             PIC X(16).
             02 REGISTRATION-DATE.
                03 REG-DD           PIC 99.
                03 REG-MM           PIC 99.
                03 REG-YYYY         PIC 9999.
             02 DEPT-CODE           PIC XXXXX.
             02 STUDENT-NUMBER      PIC 9(10).
describes the format of the data records that the file STUDENT-FILE will contain.

In this example, we see that each record consists of 4 major fields; the name of the student, registration date, department code and the student's number.

The field student name, further consists of 3 subfields, namely the first name, middle initial and the surname. Similarly the registration date is broken into subfields, tha day, month and year parts.

Just like in any language which has the "structure" construct, COBOL will let you refer to the "whole" name of students using the data name "STU-NAME" or just to the SURNAME if need to.

With the above structure, you can find out students with the same surname and move their "whole" names to a printer line with one assignment statement :

       IF SURNAME = OLD-SURNAME THEN
          MOVE STU-NAME TO PRTLINE.STU-NAME.
The two digit numbers (LEVEL NUMBERS) at the beginning of each structure declaration line is QUITE IMPORTANT.

The PICTURE (PIC) Clause in DATA DIVISION

PIC clause is the type declarative for scalar variables or elementary items in structures. The variable types are quite straightforward in the COBOL language. Due to the nature of COBOL programs, variables are either numeric, alphanumeric or logical. No long integers no double precision floats... If you want to make mathematical iterations to solve a set of nonlinear differential equations, don't use COBOL. Go and get a Pascal compiler!

If a variable holds numerical values you must declare the number of digits that you expect the value of the variable reach. Please note that this is not the ONLY way declaring numerical variables in COBOL; but this is the most popular and easy way... You specify the number of digits that a variable can have by using a number of 9's in the PICTURE clause.

        06  TEMP-VAR1      PIC 999999.
means that the variable TEMP-VAR1 can not have a value of 1,000,000. It also cannot be negative! (We'll come back to negative numbers later!). Another attribute for this variable that it is an INTEGER. If your program might yield higer values just add some more 9's. If you do not want to type many 9's and then have to count them, you can parenthesize the 9's.
        06  TEMP-VAR1      PIC 999999.
is identical to
        06  TEMP-VAR1      PIC 9(6).
If you will need to store floating point numbers (numbers which have some digits after the decimal point) in a variable, you should specify the number of decimal places. For example the declaration
        06  TEMP-VAR2      PIC 999999V99.
or
        06  TEMP-VAR2      PIC 9(6)V99.
specifies that the value of TEMP-VAR2 can have two decimal places after the IMPLIED DECIMAL POSITION indicated by the V symbol. In this example, computed values which yield three or more decimal places will be automatically rounded to 2 decimal places. Some numbers that fit into this picture are 2.23, 123456.78, 234.50, 234.00. If you try to store the value 234.456 into a variable declared with a 9(6)V99 picture, the value stored in the variable will be 234.46. That is, the decimal digits will be adjusted to the picture clause specification with ROUNDING.

If a variable holds alphanumeric values you must declare the variable with X pictures. You should use one X for each byte that your variable can hold.
        06  STR-VAR1      PIC XXX.
        06  STR-VAR2      PIC X(16).
Note : You cannot combine X and 9 picture items to represent variables which have a fixed alpha-alpha-numeric-numeric pattern. Suppose that you want to declare a variable for course codes in Bilkent University. One way could be to declare a 6 character long character string variable
        02  COURSE-CODE      PIC X(6).
If your application requires that the sub fields (department code and numerical course id) should be separately maintained, you might declare a structure (grouped item) to hold the course codes :
        02  COURSE-CODE.
            03 DEPT-CODE      PIC XXX.
            03 COURSE-NO      PIC 999.
If a variable holds signed numerical values you must prepend "S" to the PICTURE of the variable reach.
        02  TEMPERATURE      PIC S999.

The COBOL language provide many options to the programmer with rich variations of the PICTURE clause. We shall these options later during our lab sessions and classwork.

The Working-Storage Section

Variables that are local to the application program are declared in this section. All temporary variables, arrays and structures must be mentioned in this section. The declaration rules are very similar to those in the FILE SECTION.

Scalar Variables (variables that are not structures or arrays) should declared after all the structure definitions are finished. Scalar variables must always have a level number of 77. The special level number 88 is reserved for SWITCH variables. Switch variables can only hold a TRUE or FALSE value ( a logical variable in C sense).

Arrays are represented in structure format, therefore array declarations require 01 level group items, hence arrays are declared among regular structures. ( We'll come back to this issue later in the course).

A typical working-storage section would look like .
        WORKING-STORAGE SECTION.
        01  TEMP-CODE.
            02 DEPT-CODE         PIC XXX.
            02 COURSE-NO         PIC 999.
        01  TEMP-STU
            02 FULL-NAME         PIC X(33).
            02 REG-DATE          PIC 9(8).
            02 OTHERS            PIC X(15).
        77  I                    PIC 9999.
        77  J                    PIC 9999.
        77  ROW-INDEX            PIC 999999.
        77  COL-INDEX            PIC 9.
        77  TOTAL-PRICE          PIC 9999999999V99.
        77  E-MAIL-ADDR          PIC X(40).

Back to first page...