Program Organization
A COBOL program is coded in four divisions: IDENTIFICATION DIVISION. ENVIRONMENT DIVISION. DATA DIVSION. PROCEDURE DIVISION. within each division we find one or more sections. For example, the DATA DIVISION normally has a FILE SECTION and a WORKING-STORAGE SECTION. This subdivision continues: Program Division Sections One or more paragraphs One of more sentences. <-- terminated by period Statement (verb) Clause (modifiers) Words Characters The individual divisions will be described in more detail below.
Character set
The actual character set available to a COBOL programmer depends upon the implementation used; however, all versions of COBOL support the following characters, blank .<(+$*);-/,>=" ABCDEFGHIJKLMNOPQRSTUVWXYZ 0123456789
Identifiers
COBOL identifers are 1-30 alphanumeric characters, at least one of which must be non-numeric. In certain contexts it is permissible to use a totally numeric identifier; however, that usage is discouraged. Hyphens may be included in an identifier anywhere except the first of last character.
Reserved words
Our version of COBOL has more than 500 of reserved words which cannot be used for other purposes in a program. Click here for a list of all reserved words in Compaq COBOL. Reserved words may not be used for any purpose other than that proscribed by the language definition.
Data types and Variables
COBOL supports variables which are either alphabetic, numeric, or alphanumeric. Variable declaration Variables must be declared in a COBOL program prior to their use. Declarations occur in the DATA DIVISION. Data items are either "elementary data items" or "record description entries." Elementary items An elementary data item is a variable which contains a single value. For example, one might define a variable HOURS-WORKED to be an integer with up to 2 digits as follows: DATA DIVISION. WORKING-STORAGE SECTION. 77 HOURS-WORKED PICTURE 99 IS ZERO. The 77 above is referred to as a level number. Level 77 is specific level number used to describe elementary items in the working storage section of the data division. Note that this data item also has included an optional initialization value. Values may be either literal or figurative. Literal values are written as follows. Numeric 1-18 digits Option: may be preceeded by + or - sign Option: may include an embedded decimal point Alphabetic 0 or more characters enclosed in quotes ("). Option: to include a quote in a literal string, type two quotes. Figurative values are: ZERO ZEROES ZEROS SPACE SPACES ALL "string" the ALL modifier is used to fill an alphabetic variable with copies of the string. For example, 77 OUTPUT-STRING PICTURE X(21) IS ALL "+-". would be the same as 77 OUTPUT-STRING PICTURE X(21) IS "+-+-+-+-+-+-+-+-+-+-+". Group items A record is a group of items which contain related data values. For example, we might define a record as follows: DATA DIVISION. WORKING-STORAGE SECTION. 01 ALBUM. 05 TITLE PICTURE X(30). 05 GENRE PICTURE X(10). 05 ARTIST. 10 FIRST-NAME PICTURE X(20). 10 LAST-NAME PICTURE X(20). 10 BAND-NAME PICTURE X(20). 05 ID-NUMBER PICTURE X(10). 05 YEAR PICTURE 9999. The level numbers above are used to show subordination of groups of values. Level 01 is the uppermost level in the hierarchy. Other numbers can be chosen as the programmers preference in the range of 02-49. All items with the same level number are at the same hierarchical level in the record, referenced through the data name that subordinates them. In other words, this data description shows a group called ALBUM with the five subordinate items, TITLE, GENRE, ID-NUMBER and YEAR (all elementary) and another group called ARTIST with three elementary items, FIRST-NAME, LAST-NAME, and BAND-NAME. Note: all user-defined names at the 01-level must be unique; however, it is permissible to use the same subordinate names in other group variables. Group items can be referenced in a program as an entire unit, for example, ALBUM or by the items within the structure. For example, we may have, TITLE OF ALBUM or BAND-NAME OF ARTIST OF ALBUM to refer to specific data items. Boolean data items COBOL does not directly support logical/boolean variables; however, level-88 is used to define condition names which have the same effect. For example, suppose we have a variable called CLASS-YEAR which is a number in the range 0-5 with the following interpretation: 0 a student who has been accepted but has not yet registered for courses 1 a student in the freshman year 2 sophomore 3 junior 4 senior 5 graduate 77 CLASS-YEAR PIC 9. 88 NON-MATRICULATED VALUE 0. 88 FROSH VALUE 1. 88 SOPH VALUE 2. 88 JUNIOR VALUE 3. 88 SENIOR VALUE 4. 88 GRADUATE VALUE 5. 88 INVALID-CLASS VALUES 6,7,8,9. which would allow statements like IF GRADUATE ... whose result would be determined by the value currently stored in CLASS-YEAR when this statement is processed. Note that it is possible to have more than one value associated with a condition. For example, above, if any number outside 0 through 5 is stored in CLASS-YEAR the data name INVALID-CLASS will become true. PICTURE clause All elementary items havea PICTURE which defines the type of data which can be stored in the variable. PICTURE clauses are built from PICTURE characters whose function is shown below.
| Numeric items 9 a single numeric digit V the virtual decimal point S the number will be signed; note: if omitted the value is interpreted as positive regardless of the sign included P special topic | 
| Actual last digit Symbol entered | 
| 0 } 1 J 2 K 3 L 4 M 5 N 6 O <-- letter "O" 7 P 8 Q 9 R | 
| Class | Data values may contain | Picture clause characters | 
|---|---|---|
| Numeric | Only digits | 9 V S P | 
| Alphabetic | Only letters and spaces | A | 
| Alphanumeric | Any characters | 9 A X | 
| Numeric edited | Digits and editing characters | + $ Z 9 . CR - * B ) , / DB | 
| Alphanumeric edited | Any COBOL character and editing characters B and 0 | 9 A X B 0 / | 
| Reference: COBOL for Students: A Programming Primer, Robert G Finkenaur, Winthrop Publishers, Cambridge, MA, 1977, page 136 | ||
| source value destination's PIC clause destination value (numeric) (numeric edited) | 
Selection COBOL uses the IF statement for selection. IF condition statement IF condition statement1 ELSE statement2
Repetition The PERFORM verb is used for repetition in COBOL. The PERFORM verb has several forms, such as, PERFORM sentence numericVal TIMES where the numericVal can be either literal values or data items. PERFORM sentence UNTIL condition Even though this looks like a post-test loop, it is not. The condition is tested before the first iteration is PERFORMed. The construct, PERFORM sentence VARYING numericItem FROM numericVal1 BY numericVal2 UNTIL condition implements a counter-controlled loop. Multiple counters can be nested, PERFORM sentence VARYING numericItem1 FROM numericVal1 BY numericVal2 UNTIL condition1 AFTER numericItem2 FROM numericVal3 BY numericVal4 UNTIL condition2
Termination of programs and paragraphs.
A COBOL program terminates when the last paragraph in the code is executed, unless termination 
occurs earlier by the 
    STOP RUN
    
sentence.  A COBOL paragraph may be prematurely terminated with the
    EXIT
    
sentence.
1. Create links between logical file names FILE CONTROL and physical files (ENVIRONMENT DIVISION) 2. Create a description of the file FD (DATA DIVISION) 3. Open the files for I/O OPEN (PROCEDURE DIVISION) 4. Use the opened files READ/WRITE (PROCEDURE DIVISION) 5. Close the files when finished CLOSE (PROCEDURE DIVISION)File Control Each file to be accessed by the program must be declared in the FILE-CONTROL paragraph of the INPUT-OUTPUT SECTION of the ENVIRONMENT DIVISION. In specific, each external file must be declared using the form, ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT logicalFilename ASSIGN TO "systemFilename" For example, an actual select sentence might be, SELECT DATA-FILE ASSIGN TO "COBOL_PROJ.IN" to associate the local file COBOL_PROJ.IN with the program name DATA-FILE.
File Description The FILE SECTION of the DATA DIVISION lays out the format expected/desired for the input/output files in the program. These descriptions follow the same rules as the WORKING-STORAGE descriptions; however, each file must also declare its basic format using an FD description. In general, to read or write to a disk file, this section will be, FILE SECTION. FD logicalFilename LABEL RECORDS ARE STANDARD DATA RECORD IS dataFormat. 01 dataFormat * Normal data description as in previous examles An important addition is available for output files, the LINAGE clause allows one to define the way a page will be laid out. For example, FILE SECTION. FD MY-OUTPUT-FILE LABEL RECORDS ARE STANDARD DATA RECORD IS PRINT-LINE LINAGE IS 52 LINES LINES AT TOP 5 LINES AT BOTTOM 3. 01 PRINT-LINE PIC X(80). which would define output pages to be 60 lines, 5 unused at the top, 3 unused at the bottom and the remainder used for printing the individual lines of output.
Opening files for access The OPEN verb is used to actually activate the file which was previously declared and defined, OPEN INPUT logicalFilename or OPEN OUTPUT logicalFilename Using the files: READ a file, WRITE a record The READ verb is used to get data from the input files, READ logicalFilename AT END statement This causes one record to be read from the file into the dataItem defined in the FILE SECTION. The AT END clause defines the action to be taken if the file READ encounters the end-of-file. Without this clause, the end-of-file could cause a runtime crash. The WRITE verb is used to send data to the output files, WRITE dataItem Note an important difference between reading and writing. In COBOL you READ a file, but WRITE a record. There are some important clauses used with the WRITE verb that control the display of the output. For example, WRITE dataItem BEFORE ADVANCING numericItem LINES WRITE dataItem BEFORE ADVANCING PAGE WRITE dataItem AFTER ADVANCING numericItem LINES WRITE dataItem AFTER ADVANCING PAGE Note the general usage of WRITE involves first constructing the desired data items then placing them all into a generic string which can be printed. This is done by MOVEing various WORKING MEMORY structures into a single structure which is the generic record for all output, typically a single item with a PICTURE such as X(80). See the demo programs for more details.
Closing the files Easy... CLOSE logicalFilenames For example, CLOSE MY-INPUT-FILE, MY-OUTPUT-FILE. Miscellaneous When building print lines, it is often useful to have fields filled with spaces, but it is inconvenient to have to make up unique names for each of these little blocks of space. COBOL includes a RESERVED word FILLER which can be used as often as desired to handle this problem. For example, FILE SECTION. FD MY-OUTPUT-FILE LABEL RECORDS ARE STANDARD DATA RECORD IS PRINT-LINE. 01 PRINT-LINE PIC X(80). WORKING-MEMORY SECTION. 01 ONE-OUTPUT-STYLE. 05 FILLER X(20). 05 THE-DATA $$$$,$$9.99. 05 FILLER X(49). 01 OTHER-OUTPUT-STYLE. 05 FILLER X(30). 05 THE-DATA 999,999.99. 05 FILLER X(40). . . . MOVE 2233.44 TO THE-DATA OF ONE-OUTPUT-STYLE. MOVE ONE-OUTPUT-STYLE TO PRINT-LINE. WRITE PRINT-LINE. MOVE CORRESPONDNING ONE-OUTPUT-STYLE TO OTHER-OUTPUT-STYLE. MOVE OTHER-OUTPUT-STYLE TO PRINT-LINE. WRITE PRINT-LINE. . . . which would result in the output: $2,233.44 002,233.44 Using the two formats, 123456789|123456789|123456789|123456789|123456789|123456789|123456789|123456789| | | | | | | | | <---FILLER X(20)--->$$$$,$$9.99<----------------FILLER X(49)-------------------> <--------FILLER X(30)-------->999,999.99<------------FILLER X(40)-------------->
For further experimentation Several interactive I/O operations are possible. Try experimenting with, DISPLAY "string" [WITH NO ADVANCING] ACCEPT dataItem ACCEPT dataItem FROM DATE YYMMDD format ACCEPT dataItem FROM DAY YYDDD format ACCEPT dataItem FROM TIME HHMMSSVSS format
References
AVERAGE.COB GRADES.COB Prof. Bjork's Demos