COBOL

Under Construction

DATA DIVISION


Overview

The third division in a COBOL (sub)program is the DATA DIVISION, in which the data used by the (sub)program is declared/described. The DATA DIVISION of a subprogram contains three sections --FILE, WORKING-STORAGE, and LINKAGE-- while that of a (main) program contains only the first two.

The FILE SECTION describes the record structures of files used by the (sub)program. In effect, for each file, it sets up a one-record buffer (in RAM) that is used for holding the record most recently read in (if the file is an input file) or for holding the data that is "waiting" to be written out (if the file is an output file).

Remark: COBOL is best-suited for dealing with files whose structure conforms to the classic file-record-field-character hierarchy, in which a file is a sequence of uniformly-formatted records, each of which is a sequence of fields, each of which is a character string. (To be fair, COBOL does a good job of handling files containing records of different formats, as long as the number of formats is fairly small.)

The WORKING-STORAGE SECTION describes temporary (i.e., non-persistent) data, which exists only during program execution.

Remark: When a file has records of a number of different formats (such as a "generic" output file through which all output is written), it is often convenient to use the WORKING-STORAGE section to describe the various record formats. End of remark.

The data division of a subprogram also includes a LINKAGE SECTION, which is where the formal parameters (called "arguments" in COBOL) are described.


Data Names

A data-name in COBOL is analogous to what is called a variable in most programming languages. A data-name may be up to 31 characters in length and may include alphabetic characters, numeric characters (i.e., digits such as '4'), and hyphens. (Some compilers allow underscores and, in fact, do not distinguish them from hyphens.) At least one character in a data-name must be alphabetic, and a hyphen may not appear as the first or last character. None of COBOL's approximately 300 reserved words may be used as a data-name.

In contrast to most programming languages, a data-name in COBOL may begin with a numeric character, so that, e.g., 4-Dead-In-Ohio is a legal data-name. In the COBOL culture, it is common for data-names to be lengthy.

For more on data-names, see pages 19-20 of Comprehensive COBOL.


Structure of Data in COBOL

Each data item in COBOL is either a group item or an elementary item. A group data item is one that is composed of one or more (subordinate) data items. An elementary data item is one having no subordinates. Hence, an elementary data item in COBOL is somewhat analogous to a value of a primitive type (e.g., int or char) in Java, whereas a group data item is more like an object, which typically contains several pieces of data (i.e., instance variables) within it. (An even closer similarity can be drawn with a struct in C or a record in Pascal or Ada.)

A group data item may itself be subordinate to a higher-level group item. Thus, in COBOL we are able to describe data having a multi-level hierarchical (i.e., tree) structure.

As an example, suppose that a client is described by her name, address, date of birth, and the state of her account. Refining this further, suppose that a name is composed of a last name and a first name, an address is composed of a street address, city, and zip code, the last of which is composed of a regular 5-digit part and a 4-digit extension. A date of birth is given by a month, day, and year. Finally, the state of an account is given by a string serving as its ID and by a numeric balance. Presenting this in familiar outline form, we get

Client-Record
   I. Name
      A. Last-Name 
      B. First-Name
   II. Home-Address
      A. Street-Addr 
      B. City       
      C. Zip-Code
         1. Zip-Regular 
         2. Zip-Extension 
   III. Date-of-Birth
      A. Month 
      B. Day
      C. Year
   IV. Account-Info
      A. Account-ID
      B. Account-Balance

In COBOL, a declaration of a client record would look much like the outline above. Not surprisingly, however, COBOL does not recognize the numbering scheme typically used in outlines, nor does it pay attention to code indentation. Rather, to indicate a record's hierarchical structure (i.e., which fields are nested within which fields), one uses (two-digit) level numbers. Although the programmer is given some freedom in choosing level numbers, we recommend that each data item be assigned a level number that is one greater than that of its parent. Data items that are siblings of one another must have the same level number, and a data item not nested within another one must have a level number of either 01 or 77, the latter of which may be used only for data items that are elementary. In order to provide visual cues to aid human comprehension, we continue to employ indentation. The above becomes

01 Client-Record
   02 Name
      03 Last-Name 
      03 First-Name
   02 Home-Address
      03 Street-Addr 
      03 City       
      03 Zip-Code
         04 Zip-Regular 
         04 Zip-Extension 
   02 Date-of-Birth
      02 Month 
      02 Day
      02 Year
   02 Account-Info
      03 Account-ID
      03 Account-Balance

What remains is to declare, for each elementary item, its data type. Well, sort of. In COBOL, elementary data items are declared to be in one of two major varieties, called modes: display and computational. The former, which stipulates that the data item is to be represented by a character string (and hence is suitable for displaying in a human-readable form), is the default, even for numeric data items. The latter applies only to numeric data and is used in order to improve efficiency in the storage and manipulation of such data. A numeric item declared to be in computational mode is stored not as a string of digit characters but rather in a format (e.g., binary or binary-coded decimal) that requires less space and allows arithmetic operations to be performed more efficiently (and hence is more suitable for computation). Unfortunately, computational data in COBOL tends not to be very portable, as the representation schemes offered by different compilers tend to be suited specifically to the respective underlying machine architectures.

In this discussion, all data items will be declared (implicitly, as it is the default) to be in display mode.

Returning to our client record example (and keeping in mind that all data items will be in display mode, meaning that we can think of them as character strings), it remains to give precise descriptions of the elementary data items. Such a description is provided by a picture clause, which indicates the length (# of characters) of the string and which type(s) of characters are intended to occur within it. The choices are alphanumeric, alphabetic, and numeric, which are denoted, respectively, by the picture characters X, A, and 9. An alphanumeric field is intended to contain characters of any kind. An alphabetic field is intended to contain only letters and spaces. A numeric field is intended to represent a number and hence should contain only numeric characters (i.e., '0', '1', ..., '9'). (There are some exceptions, however, as will be discussed below.)

Remark: There seems to be little advantage in declaring a field to be alphabetic rather than alphanumeric: few, if any, COBOL compilers will produce code that generates a run-time error when non-alphabetic data is placed into an alphabetic field. For similar reasons, there is little reason to use a "mixed" picture clause (e.g., PIC 999X99X9999 for a social security number) specifying that some characters must be numeric whereas others are unrestricted. Indeed, it would seem that the only circumstance in which COBOL balks at the contents of a data field is when (at run time) there is an attempt to perform an arithmetic operation involving a field containing non-numeric data. An attempt to perform an arithmetic operation upon anything but an elementary field declared to be "purely" numeric will be flagged at compile time. End of remark.

To complete our client record declaration, we insert picture clauses (and periods, which COBOL requires at the end of each field's declaration). The notes in italics to the right are not part of the program; they are simply to aid the reader. The example uses picture characters V and S that will be discussed afterwards.

01 Client-Record.
   02 Name.
      03 Last-Name   PIC A(20).        alphabetic field of length 20
      03 First-Name  PIC A(12).
   02 Home-Address.
      03 Street-Addr  PIC X(25).       alphanumeric field of length 25
      03 City         PIC X(18).
      03 Zip-Code.
         04 Zip-Regular    PIC 9(5).   (unsigned) numeric field of length 5
         04 Zip-Extension  PIC 9(4).
   02 Date-of-Birth.
      03 Month  PIC 99.                (unsigned) numeric field of length 2
      03 Day    PIC 99.                equivalent to PIC 9(2)
      03 Year   PIC 9999.              equivalent to PIC 9(4)
   02 Account-Info
      03 Account-ID      PIC X(10).
      03 Account-Balance PIC S9(5)V99. (signed) numeric field of length 7
                                       with two digits after the decimal
                                       point and five before

Picture Characters for Numeric Data

The V Picture Character

A (display mode) numeric data item can be viewed as a sequence of digit characters. In order to specify where the decimal point lies, one uses the V picture character. Here are some examples:
01 Cntr  PIC 9(6).               six digits to left, none to right
01 Cntr-2 PIC 9(6)V.             equivalent to above
01 Gross-Pay  PIC 9(4)V99 .      four digits to left, two to right
01 PI  PIC 9V9(5) VALUE 3.14159. one digit to left, five to right
01 Tax-Rate  PIC V99 VALUE 0.06. no digits to left, two to right 
The decimal point is "invisible" in the sense that, if such a data item is displayed (via the DISPLAY verb) or written to an output file as part of a record, only its digits will appear, absent any indication of where the decimal point lies. Similarly, if such a data item is part of an input record, the characters read into it should not include a decimal point.

The S Picture Character

To declare a numeric data item to be signed (meaning capable of assuming negative values), one begins its picture clause with the character S.

Edited Numeric Data

When numbers are to be displayed or printed as output intended for human consumption, rarely does one want minus signs or decimal points to be omitted or leading zeroes to appear. Yet that's what will happen if one outputs a "plain" numeric data item. In order to get numeric data into a format fit for human consumption, one uses edited numeric data items, whose picture clauses determine how numeric data will be "edited" when placed into them.

The . (decimal point) Picture Character

The Z (leading zero suppression) Picture Character

The - (minus sign) Picture Character

The + (plus sign) Picture Character

The $ (dollar sign) Picture Character


Initializing an Elementary Data Item via a VALUE Clause

An elementary data item can be initialized using a VALUE clause, as in the following examples:

01 Counter PIC 9(3) VALUE 0.
01 My-Name PIC X(16) VALUE 'Rumpelstiltzkin'.

Be warned that data items declared in subprograms are, by default, static (to use C's terminology), meaning that their values are preserved between calls. In effect, then, the initialization specified in a VALUE clause occurs only once, before the first call to the subprogram, and not before each time it executes as a result of being invoked.

In order to override the default and force the initializations specified by VALUE clauses to take effect upon each invocation of a subprogram, the subprogram should be declared to be INITIAL. This is done in the PROGRAM-ID paragraph, by inserting the phrase IS INITIAL (in which the word IS is optional) immediately after the subprogram's name, as illustrated here:

PROGRAM-ID. Some-Subprogram IS INITIAL.

For more examples of the use of the VALUE clause, see the next two sections.


Constants

There are three kinds of constants in COBOL: numeric literals, nonnumeric literals, and figurative constants.

Numeric literals in COBOL are like those in other programming languages. Examples include -542 and 3.14159.

Nonnumeric literals are what in other languages are called string literals. Examples are 'Telephone #' and '3.14159'. Here we have used single quotes as delimiters. Some compilers may require the use of double quotes instead, as in "Telehpone #". Other compilers may recognize both kinds of quotes.

Figurative constants are reserved words that represent commonly-used numeric or string values. These include ZERO (or its equivalent ZEROES), SPACE (or its equivalent SPACES), and HIGH-VALUES. As an example of usage, below we declare an alphanumeric data-item Junk and use a VALUE clause and a figurative constant to initialize it with spaces:

01 Junk PIC X(13) VALUE SPACES.

Figurative constants may be referred to in the PROCEDURE DIVISION as well, as in

MOVE ZERO TO Counter

which gives the value zero to Counter (which we are assuming is a numeric data item).

In COBOL (unlike many languages), there is no way to indicate that a data-name is to act as a symbolic constant, i.e., that the value associated with it cannot be changed. Thus, for example, we might include the declaration

01 PI PIC 9V9(5) VALUE 3.14159.

but there is no way to say that PI's value cannot be changed during execution. Nevertheless, it is a good practice to use such "symbolic constants" rather than using the corresponding literal value each time it occcurs

For more, see pages 65-66 of Comprehensive COBOL.


Anonymous Data

In COBOL, it is not uncommon to declare data items to which no direct references are ever made. To relieve the programmer of the nuisance of devising data-names for such data items, COBOL provides a way of declaring anonymous data items. The reserved word FILLER is used, in place of a data-name, for this purpose. Here is an example:

01 Out-Rec.
   02 Out-Name     PIC X(20).
   02 FILLER       PIC X(5) VALUE SPACES.
   02 Out-Birthdate.
      03 Out-Month    PIC 9(2).
      03 FILLER       PIC X VALUE '/'.
      03 Out-Day      PIC 9(2).
      03 FILLER       PIC X VALUE '/'.
      03 Out-Year     PIC 9(4).

Note that the term FILLER is optional, so that either of the two anonymous data items at the 03 level above could have been described by the line

      03              PIC X VALUE '/'.

REDEFINES Clause

This feature makes it possible to interpret the same chunk of storage in two or more ways. This is useful if, for example, the records in a file are not of a uniform structure. It is similar to the variant record construct in Pascal, or the union type construct in C. (In Ada, a somewhat more general capability is offered by using a discriminated record type.)

Suppose, for example, that a particular file contains data regarding a particular collection of published works, among them being books, articles (from journals and magazines), and PhD theses. Each record in the file describes one such work. The difficulty here is that for different kinds of works we wish to maintain different sets of attributes. For books, we want the attributes author, title, publisher, year published, and edition. For articles, we want author, title, journal, month published, starting page, and ending page. For PhD theses, we want author, title, school, and year published. Hence, records representing two different kinds of works (e.g., one representing a book and the other representing an article) should have different formats. To accommodate this, COBOL includes the REDEFINES feature. Here is an illustration:

01 Published-Work.
   02 Author          PIC X(16).     --these fields are
   02 Title           PIC X(20).     --common to all three
   03 FILLER          PIC X.         --types of published works
      88 Is-Book     VALUE 'B'.
      88 Is-Article  VALUE 'A'.
      88 Is-Thesis   VALUE 'T'.
   02 Rest-of-Fields  PIC X(34).
   02 Rest-of-Book  REDEFINES Rest-of-Fields.   --remaining fields for books
      03 Publisher   PIC X(18).
      03 B-Year      PIC 9(4).
      03 Edition     PIC 9.
      03 FILLER      PIC X(11).
   02 Rest-of-Article REDEFINES Rest-of-Fields. --remaining fields for articles
      03 Journal     PIC X(20).
      03 Date.
         04 Month    PIC 9(2).
         04 A-Year   PIC 9(4).
      03 Pages.
         04 Start-Page  PIC 9(4).
         04 End-Page    PIC 9(4).
   02 Rest-of-Thesis REDEFINES Rest-of-Fields.   --remaining fields for theses
      03 School     PIC X(20).
      03 T-Year     PIC 9(4).
      03 FILLER     PIC X(10).  

The data declaration above for Published-Work indicates that its first 16 bytes hold an Author field, its next 20 bytes hold a Title field, and the next byte holds a character indicating whether the data occupying it describes a book, article, or thesis. Following that are 34 bytes allocated to something called Rest-of-Fields. Notice that the declarations for Rest-of-Book, Rest-of-Article, and Rest-of-Thesis specify that each of them REDEFINES Rest-of-Fields, which is to say that each of them occupies the same 34 bytes as the Rest-of-Fields field! In other words, each of these four fields describes a different way of interpreting those same 34 bytes. (Note that all four fields occur at the same level (namely, 02) of the hierarchy; this was necessary: if one field REDEFINES another, the two must be at the same hierarchical level and be declared "consecutively".)

Suppose that the data currently occupying Published-Work describes an article. Then the data declarations subordinate to Rest-of-Article tell us that the 34 bytes comprising it are (assumed to be) organized as follows: the first 20 contain the name of the journal in which the article appears, the next six contain the date (month and year) of publication, and the next eight bytes hold the starting and ending page numbers (4 bytes each).

Notice that the "meaningful" fields within Rest-of-Book occupy only 23 bytes. As Rest-of-Book must be 34 bytes in length (because the lengths of a field and another one that REDEFINES it must be the same), we "correct" this by padding it with an 11-byte anonymous data item. For similar reasons, Rest-of-Thesis is padded with a 10-byte anonymous field.

A sketch of a paragraph that processes a Published-Work record could be as follows. Note that it examines the byte indicating which kind of published work is described in order to determine in what manner to treat the record. For example, if the byte says that the data describes a book, it makes sense to access the Edition field but it does not make sense to access the Journal or School fields. Indeed, conceptually, neither the Journal nor the School field even exists if the record's contents describes a book. (COBOL does not disallow access to these "non-existent" fields, however. In contrast, Pascal's variant record construct and Ada's discriminated record construct are such that access to logically non-existent fields within the record results in a run-time error.)

Process-Rec.
   IF Is-Book
      [code referring to fields Author, Title,  ]
      [and ones nested in Rest-of-Book, but not ]
      [to ones nested in Rest-of-Article/Thesis ]

   ELSE IF Is-Article
      [code referring to fields Author, Title,   ]
      [and ones nested in Rest-of-Article, but   ]
      [not to ones nested in Rest-of-Book/Thesis ]
 
   ELSE IF Is-Thesis
      [code referring to fields Author, Title,    ]
      [and ones nested in Rest-of-Thesis, but not ]
      [to ones nested in Rest-of-Book/Article     ]

   END-IF END-IF END-IF 

As another illustration of the REDEFINES clause, here is a clever use of it for the purpose of constructing a table (i.e., array) containing the names of the months of the year.

01 Month-Values.
   02 FILLER  PIC X(9) VALUE 'January  '.
   02 FILLER  PIC X(9) VALUE 'February '.
   02 FILLER  PIC X(9) VALUE 'March    '.
   02 FILLER  PIC X(9) VALUE 'April    '.
   02 FILLER  PIC X(9) VALUE 'May      '.
   02 FILLER  PIC X(9) VALUE 'June     '.
   02 FILLER  PIC X(9) VALUE 'July     '.
   02 FILLER  PIC X(9) VALUE 'August   '.
   02 FILLER  PIC X(9) VALUE 'September'.
   02 FILLER  PIC X(9) VALUE 'October  '.
   02 FILLER  PIC X(9) VALUE 'November '.
   02 FILLER  PIC X(9) VALUE 'December '.

01 Month-Table  REDEFINES Month-Values.
   02 Month  PIC X(9) OCCURS 12 TIMES.

As a result of these declarations, we have Month(1) = 'January ', Month(2) = 'February ', etc., which makes it easy to translate from a numeric representation of a month (e.g., 1 stands for January) to its string representation.

For more information about REDEFINES, see pages 468-469 of Comprehensive COBOL.


Reference Modification

This feature makes it possible to refer to any desired segment of any data field (other than numeric data in COMPUTATIONAL mode). In effect, it allows any such data field to be viewed as an array of characters.

For example, if Junk has been declared by the picture clause PIC X(12), then the expression Junk(4:6) refers to the segment of Junk of length 6 beginning at position 4. Such an expression can be used as the source or destination of the MOVE verb, for example.

See pages 471-474 of Comprehensive COBOL.


Qualification (Or, What to do when two data items have the same name)

See pages 201-203 of Comprehensive COBOL.


Tables (i.e., Arrays)

In COBOL terminology, we use the term table to refer to what in most other programming languages are called arrays. A table is declared using an OCCURS clause. For example, the declaration

01 A-Table.
   02 Junk  PIC X(4)  OCCURS 10 TIMES.
corresponds to the following storage structure (in which Junk has been abbreviated to J), in which sample (Star Trek-related) data is shown:
         J(1) J(2) J(3) J(4) J(5) J(6) J(7) J(8) J(9) J(10)
        +----+----+----+----+----+----+----+----+----+----+
A-Table |kirk|sulu|gorn|beam| me | up |worf|data|star|trek|
        +----+----+----+----+----+----+----+----+----+----+
That is, the declaration above describes a field called A-Table that contains a table called Junk, which has ten elements, each of which is an alphanumeric string of length four. (Note: The PICture and OCCURS clauses can be placed in either order.) To refer to, for example, the 5-th element of Junk ---which can be treated just as any other 4-byte alphanumeric field--- we could write Junk(5). Assuming that Cntr, say, is a numeric data item, we could use it as a subscript by writing Junk(Cntr). We could even use expressions such as Cntr + 1 as subscripts, but COBOL does not allow general arithmetic expressions to be used. (Note: I do not know the exact limitations/restrictions.)

Warning: Depending upon the compiler you use and the options you have set in that compiler, subscript-out-of-bounds errors may or may not be detected at run-time. For example, if subscript-out-of-bounds errors are not being detected and Cntr has value 15, the expression Junk(Cntr) refers to the 4-byte block that begins 16 bytes after the end of the last element of Junk (i.e., in the space that would have been occupied by Junk(15) had the table been at least 15 elements in length).

In COBOL, one cannot use the name of a table without including a subscript. That is, anywhere that Junk appears, it must be followed by a parenthesized subscript. In most other languages, an array name without a subscript refers to the entire array (as one unit of data), as opposed to a particular element of it. In COBOL, to refer to a table as a single unit of data we must use the enclosing data-name; in our example this would be A-Table. That is, A-Table is, in some sense, the name of the table; the data-name Junk is used only for accessing individual elements of it.

In our example, Junk is a table of elementary data items. Suppose that we wanted to form a table of group-level items (or, what in Ada or C we might refer to as an array of records or structs, respectively). Here is an example, set in a relevant context:

01 Course.
   02 Name-of-Course PIC X(12).
   02 Student-Table.
      03 Student  OCCURS 25 TIMES.
         04 Name.
            05 Last-Name  PIC X(15).
            05 First-Name PIC X(9).
         04 Major  PIC X(4).
   02 Name-of-Instructor PIC X(20).
Embedded inside a larger record is a table, called Student, each 28-byte element of which contains a Name field (which itself contains two subordinate fields) and a Major field. To refer to, for example, the Name field within the 13th element of Student, we would say Name(13). (If you are familiar with Ada, C, or Java, you might have expected the answer to be Student(13).Name.) A similar syntax is used for fields nested arbitrarily deeply; for example, the Last-Name field within the 13th element of Student is referred to by the expression Last-Name(13).

A different way of organizing the data in a Course record is as follows:

01 Course.
   02 Name-of-Course PIC X(12).
   02 Student-Name-Table.
      03 Student-Name  OCCURS 25 TIMES.
         04 Name.
            05 Last-Name  PIC X(15).
            05 First-Name PIC X(9).
   02 Student-Major-Table.
      03 Student-Major OCCURS 25 TIMES.
         04 Major  PIC X(4).
   02 Name-of-Instructor PIC X(20).
Here, instead of a single table in which each element contains both a name and a major, we have described two "parallel" tables, one holding names and the other holding majors. (The intent here is that, for all i, the student whose name is stored in Student-Name(i) is the same one whose major is stored in Student-Major(i).)

Warning: Strangely, COBOL does not allow a table to be declared at the 01 level. Thus, the following is illegal:

01 Junk  PIC X(4)  OCCURS 10 TIMES.   <--- ILLEGAL 

Note: Here should include a discussion of variable-length tables.

For more information on tables, see Chapter 12 of Comprehensive COBOL.


Conditional (i.e., boolean) Data

In COBOL, the term boolean is not used; instead, we refer to any expression that evaluates to either true or false (e.g., Num < 10) as a condition. Conditions are used in IF statements (to determine which of two alternative code segments to execute) and in loops (to determine when termination occurs).

As in other programming languages, one way to generate a true/false value is via an expression involving one or more operators by which data items are compared against one another. In COBOL, we refer to such expressions as a relation condition (which is consistent with the fact that, with respect to some other languages, such operators are called relational operators).

The syntax of a relation condition is

     <item-1> <relational-op> <item-2>
where each of item-1 and item-2 is either an identifier (i.e., name of a data item), a literal (e.g., 40, 'stupid'), an arithmetic expression (e.g., Cntr + 1, or an index name. (An index is a special kind of numeric data item.)

The relational operators (some of which are words, some of which are comprised of symbols) are as follows: GREATER, >, LESS, <, EQUAL, >, =, GREATER OR EQUAL, >=, LESS OR EQUAL, <=. In addition, any of these may be preceded by the optional word IS, and any except for the last four may be preceded by the negation operator NOT (which goes after IS if that word is present). Also, the word THAN may be included immediately following any occurrence of GREATER or LESS and the word TO may be placed after any occurrence of EQUAL. To illustrate, all the following are equivalent:

>=
GREATER OR EQUAL
GREATER THAN OR EQUAL
GREATER OR EQUAL TO
GREATER THAN OR EQUAL TO
IS GREATER THAN OR EQUAL TO
NOT <
NOT LESS
NOT LESS THAN
IS NOT LESS THAN

As all data in COBOL is either numeric, alphanumeric, or alphabetic, there is no way to use a picture clause to "directly" declare a data item as being a condition (i.e., what in Ada or Pascal we would refer to as being of type boolean). However, using what are called condition-name conditions (which are declared using the special level number 88), we can achieve the desired effect.

For example, suppose we make the following declaration:

    01 End-of-File  PIC X.
       88 Eof  VALUE 'T'.  
Then, at any moment during execution, the value of Eof is either true or false, according to the following rule: If End-of-File has value 'T', then Eof has value true; otherwise, Eof is false.

Here is how you might write a loop to process a file without using the condition name Eof:

          PERFORM UNTIL End-of-File = 'T'
             READ In-File
                AT END     MOVE 'T' TO End-of-File
                NOT AT END PERFORM Process-Record
             END-READ
          END-PERFORM 
(For an explanation of the READ construct, click
here.) Here's how you could write it using the condition name Eof:
          PERFORM UNTIL Eof
             READ In-File
                AT END     MOVE 'T' TO End-of-File
                NOT AT END PERFORM Process-Record
             END-READ
          END-PERFORM 
This is somewhat confusing, however, because the value of Eof is being changed implicitly by changing the value of End-of-File. By using the SET verb, we can avoid this by writing the above as
          PERFORM UNTIL Eof
             READ In-File
                AT END     SET Eof TO TRUE
                NOT AT END PERFORM Process-Record
             END-READ
          END-PERFORM 

The effect of SET Eof TO TRUE is to change the value of End-of-File to 'T', thereby giving Eof the value true. But now a similar criticism can be made, namely that the value of End-of-File is being changed without explicit reference to it! The answer to this is that we follow the rule that no reference is ever made to End-of-File, except in its declaration. That is, all manipulation suffered by End-of-File is as a result of applying the SET verb to one or another of its subordinate 88-level items. In fact, we never need to reference End-of-File, even in a declaration, because we can choose to make it an anonymous data item (using FILLER instead of a data-name). The declaration would now be as follows:

       01 FILLER  PIC X VALUE 'F'.
          88 Eof  VALUE 'T'.  

Note that you may not write SET Eof TO FALSE. That is, you may set a condition-name to true, but not to false! (To get that effect, you would need at least one other condition-name subordinate to the same data item, which you could set to true in order to make the former false.)

Here is an example in which several condition-names, under a single data item, are employed:

         01 Student.
            02 Name.
               ...
               ...
            02 Standing  PIC 9.
               88 Freshman  VALUE 1.
               88 Sophomore VALUE 2.
               88 Junior    VALUE 3.
               88 Senior    VALUE 4.
            02 ... 

Now you can write code such as:

          IF Freshman
             some code (e.g., possibly SET Sophomore TO TRUE)
          ELSE IF Sophomore
             some code
          ELSE IF Junior
             some code
          ELSE IF Senior
             some code
          ELSE
             some code
          END-IF
          END-IF
          END-IF
          END-IF 

The values associated to condition-names need not be singular; that is, you can associate a set of different values to a given condition-name. The simplest kind of set, aside from a single value, is a contiguous range of values. Example:

         01 Student.
            02 Name.
               ...
               ...
            02 Grade-Level PIC 99.
               88 Elementary VALUES 0 THRU 5.
               88 Middle     VALUES 6 THRU 8.
               88 High       VALUES 9 THRU 12.
               88 College    VALUES 13 THRU 25.
               88 Sentinel   VALUE 99.
            02 ... 

The value of High, for example, is true when (and only when) the value of Grade-Level is 9, 10, 11, or 12. Note that it is legal for distinct condition-names to have overlapping TRUE sets (if we may call them that). For example, according to the following definitions, both Good and Average are true when Evaluation has value 6.

         01 Evaluation PIC 9.
            88 Excellent VALUE  9.
            88 Good      VALUES 6 THRU 9.
            88 Average   VALUES 4 THRU 6.
            88 Poor      VALUES 2 THRU 4.
            88 Lousy     VALUES 0 THRU 2. 

Allowing a condition name to be associated with a set of values, as opposed to a single value, raises the following. Question: What is the result of executing, for example,  SET Average TO TRUE ? Answer: The convention COBOL follows is to change the value of Evaluation to the smallest value in the set associated to Average, which is 4.

See Chapters 5 and 8 of Comprehensive COBOL for more about conditional (i.e., boolean) data in COBOL.