Contents of COBOL Programs COBOL programs are written using the following :
|
A DIVISION is the largest unit in a Cobol program and is a collection of Sections and / or paragraphs. There are 4 divisions in a Cobol program. The four divisions of the COBOL source program are:
Identification division is mainly for identifying the program to the operating system. The only entry, which is a must in this division, is PROGRAM-ID. All the remaining entries are optional and are used mainly for documentation purpose. IDENTIFICATION DIVISION. PROGRAM-ID. SAMPLE. AUTHOR. ABC. DATE-WRITTEN. 15.07.03. DATE-COMPILED. 15.07.03. INSTALLATION. HTMT. SECURITY. USE OF HTMT. * IDENTIFICATION DIVISION is the DIVISION header * PROGRAM-ID is a paragraph-name which contains the PROGRAM-IDENTIFIER * SAMPLE is the programmer-defined name given to the program 2.1.2 Program-ID. The PROGRAM-ID paragraph specifies the name by which the program is known to the compiler. This is a mandatory field and must be the first paragraph in the identification division. 2.1.3 Author Refers to the name of the author has on effect on program execution 2.1.4 Installation Refers to the company or location has no effect on program execution. 2.1.5 Date-Written Refers to the date when the program was coded 2.1.6 Date Compiled Refers to the date when the program was compiled. Indicates the level of confidentiality of the program. It has no effect on the program execution. 2.2 Environment Division This is the most machine dependent division. Here we mention all the peripheral devices and the specification of computers used for the program. The ENVIRONMENT DIVISION consists of 2 SECTIONs, namely :
The CONFIGURATION SECTION specifies the hardware being used. 1. Source Computer. Computer ?name. This paragraph specifies the name of the computer used to compile the COBOL program. 2 Object Computer. Computer-name. This paragraph specifies the name of the computer used to execute the COBOL Program. 2.2.2 Input-Output Section The INPUT-OUTPUT SECTION consists of two paragraphs namely FILE-CONTROL paragraph and I-O CONTROL paragraph. In the FILE CONTROL paragraph a file name is selected for each file to be used in the program and assigned to a device. The I-O CONTROL paragraph specifies information needed for efficient transmission of data between the external file and the COBOL program ENVIRONMENT DIVISION. CONFIGURATION SECTION. SOURCE-COMPUTER. IBM. OBJECT-COMPUTER. IBM. INPUT-OUTPUT SECTION. FILE-CONTROL. File CONTROL entries I-O CONTROL. I-O CONTROL entries 2.3 Data DivisionThe DATA DIVISION describes all of the data to be processed by the program. The DATA DIVISION is divided into Seven sections: 2.3.1 File Section Declarations of FD (File Descriptor) or SD (Sort Descriptor) used in the program. Data areas in the FILE SECTION are not available to the program until the file is opened. 2.3.2 Working-Storage Section Defines the temporary variables and record structures used in the program. 2.3.3 Linkage Section Defines data items made available to this program from another program. It is important to note that storage is not allocated to the data structures defined in the Linkage Section as the data exists elsewhere. 2.3.4 Local Storage Section The Local Storage Section defines storage that is allocated and freed on a pre-invocation basis. On each invocation data items defined in the Local Storage are reallocated and initialized to the value assigned in their value clause 2.3.5 Communication Section The Communication Section is used to create a control block required for communication which is release dependent. 2.3.6 Report Section The Report Section is used to describe RD(Report Descriptor) entries, which will be required for Report Writer Module 2.3.7 Screen Section The Screen section is used to describe labels and data items which will be required for formatted input/output in case of application programs developed for personal computers. Each SECTION is optional: those that are present must be written in the order shown above. DATA DIVISION FILE SECTION FD entries. SD entries. WORKING-STORAGE SECTION Declaration of temporary variables and record structure LINKAGE SECTION Declaration of data items received from another program LOCAL-STORAGE SECTION Declaration of temporary variables and record structure COMMUNICATION SECTION Communication section entries REPORT SECTION RD entries SCREEN SECTION Screen section entries 2.3.8 Level IndicatorIn COBOL a distinction is made between elementary and group data items. A few elementary data may be used to form a group. Group level field is always of type alphanumeric. It cannot be used in computation. A comparison of group level with numeric field can give unexpected results. For example DAY, MONTH and YEAR may be three elementary data items. These may be combined to form a group data called DATE. Diagrammatically, this would look like below : DATE DAY MONTH YEAR The memory space referred to by DATE is the combined memory space for DAY, MONTH and YEAR. To describe this hierarchical structure, the concept of level number is employed in COBOL. A level number is a two-digit number starting from 01. The first subdivisions can have any level number between 02 and 49. Further subdivisions should follow the same range with a restriction that an item cannot have a level number less than or equal to the level numbers of the group that may include it.E.g. 1 01 DATE. 03 DAY PIC 9(2). 03 MONTH PIC 9(2). 03 YEAR PIC 9(2). E.g. 2 01 PAY. 03 GROSS-PAY. 05 BASIC PIC 9(5) . 05 DEARNESS PIC 9(3). 05 HOUSE-RENT PIC 9(4). 03 DEDUCTIONS. 05 PF PIC 9(3). 05 IT PIC 9(4). 03 NET-PAY PIC 9(7). Diagrammatically it would look like this :PAY GROSS-PAY DEDUCTIONS NET-PAY BASIC DEAR-HOUSE PF IT Elementary Level : The field that is not further subdivided is referred to as the elementary level. 2.3.9 DATA DESCRIPTION ENTRIES This entry describes a data item. It consists of a level number, data name (or FILLER) followed by a number of optional clauses terminated by a full-stop. One of the clauses is the PICTURE clause and the other is the VALUE clause. In the case of 01 and 77 level entries, the level number must begin in area A and the rest in area B. The BLANK WHEN ZERO clause in the WORKING-STORAGE SECTION will cause the computer to print a series of blanks when the display item contains zeros. E.g. 01 AMT PIC $ZZZ.99 BLANK WHEN ZERO.
EXAMPLE WORKING-STORAGE SECTION. 01 GRADE-CODE PIC 99. 88 WORKERS VALUES 1 THRU 8. 88 EXECUTIVES VALUES 9 THRU 12. 01 PRINT-LINE PIC X(132) VALUE SPACES. 01 RPT-HEADER PIC X(132) VALUE ALL ?_?. The USAGE clause The method selected for storing numeric data in COBOL is specified by the USAGE clause. The USAGE clause may be used with a group item or an elementary item. If it is used with a group item, then it refers to all elements within the group. If the USAGE clause is not specified, then the data-item will hold data only in the character mode and are assumed to be in the DISPLAY format. Data in numeric mode is described as being in COMPUTATIONAL mode. DISPLAY is the default mode. The format of the USAGE clause is : USAGE IS [DISPLAY] [COMPUTATIONAL]/[COMP] [COMPUTATIONAL-3]/[COMP-3] [PACKED DECIMAL] When USAGE IS DISPLAY, data is stored in character form, one character per single byte of storage. When numeric data is in DISPLAY form, it needs to be converted to another form before arithmetic operations are performed. Later, the arithmetic result is converted to DISPLAY form before storage in the appropriate form.When the clause USAGE IS COMP is used, numeric data is stored in the binary format. All fields designated as COMP, should be signed. E.g. TOTAL PIC S9(5) USAGE IS COMP. This format stores data in the binary format. COMP & COMP-4 are the same. The storage is in terms of half word, full word & double word. PIC 9(1) to PIC 9(4) - Half word PIC 9(4) to PIC 9(9) - Full word PIC 9(9) to PIC 9(16) - Double word These fields always start at their respective word boundaries i.e. a full-word field will always start at full-word boundary.COMP-1 is single-precision and COMP-2 is double precision. PACKED-DECIMAL means that each digit is represented as compactly or concisely as is possible given the computer?s configuration. This allows the computer to store two digits in each storage position, except for the right-most position, which holds the sign. COMP-3 is the same as PACKED DECIMAL. Each digit requires half byte. Another other half byte is required for the sign. Hence, PIC 9(3) COMP-3 will occupy 3+1 /2 = 2 bytes. E.g. BALANCE PIC 9(5)V99 USAGE IS COMP-3. Examples
Computational ? 1 Example : 2.5 is stored as .25000000E01 Computational ? 2 Example : 2.5 is stored as .25000000000000000E01 2.3.10 Special Level Numbers
The RENAMES CLAUSE helps regroup previously defined names. One or more RENAMES clause may be written for a record. · The RENAMES entries associated with a given logical record must immediately follow the last data description entry of that record · A level-66 may NOT rename a level-01, level-77, level-88 or another level-66 item.Example:01 MASTERRECORD. 05 ACCOUNT-NUMBER PIC X(6). 05 CHARGES-1 PIC 999V99. 05 CHARGES-2 PIC 999V99. 05 CHARGES-3 PIC 999V99. 05 TOTAL-CHARGES PIC 9999V99. 05 TOTAL-PAYMENTS PIC 9999V99. 05 PAYMENTS-1 PIC 9999V99. 05 PAYMENTS-2 PIC 9999V99. 66 CHARGE-INFO RENAMES CHARGES-1 THRU TOTAL-CHARGES. 66 TOTAL ?INFO RENAMES TOTAL-CHARGES THRU TOTAL-PAYMENTS. 66 PAST-DUE RENAMES PAYMENTS-2.
By using condition names, it is possible to define figurative constants for checking constants in conditions such as ?M? for Male and ?F? for Female. The variables used to hold these test values are often referred to as program switches as they can be used to take alternative action. Example. 01 QUAL PIC 9. 88 H-SCHOOL VALUE 0. 88 GRAD VALUE 1. 88 POST-GRAD VALUE 2. A condition name is always coded on the 88-level and has only a value clause associated with it and no Picture Clause. The PROCEDURE DIVISION statements would be :IF H-SCHOOL ADD 1 TO H-SCHOOL-TOT ELSE IF GRAD ADD 1 TO GRAD-TOT ELSE IF POST-GRAD ADD 1 TO P-GR-TOT. Example 02 STUDENT-RECORD. 05 STUDENT-TYPE PIC X. 88 EXEMPT VALUE ?E?. 88 NONEXEMPT VALUE ?N?. 88 SUPPLIMENTAL VALUE ?S?. 88 PARTTIME VALUE ?P?. 05 COURSE-TYPE PIC 9. 88 MFG VALUES 1 THRU 4. 88 SALES VALUES 5. 88 SERVICE VALUES 6 THRU 8. 05 STUDENT-ADDRESS. 77 CLASS-HOURS PIC S9(5)V99. 77 COUNTER PIC S9(5) VALUE 1.
USAGE IS POINTER items USAGE IS INDEX items Following are the general picture characters and their meanings
Edited Picture Symbols There are 4 types of 1. Simple Insertion 2. Special Insertion 3. Fixed Insertion and 4. Floating Insertion Suppression and Replacement This is of two kinds 1. Zero suppression and replacement with Asterisk and 2. Zero suppression and replacement with spaces
P (assumed decimal scaling position) S (indicates presence of a sign) V (indicates location of assumed decimal point) 2.3.12 Classes of Data All COBOL data items belongs to a class.
ALPHABETIC : Only a symbol A NUMERIC : Only symbols 9 P S V (Maximum 18 digits) NUMERIC-EDITED : Only symbols B P V Z 9 0 / , . + - CR DB * , $ Maximum : 18 digits ? and 249 editing characters Must be USAGE DISPLAY ALPHANUMERIC : Only symbols X or X with A 9 Must be USAGE DISPLAY ALPHANUMERIC-EDITED : Only symbols of A X 9 B 0 / Must be USAGE DISPLAY SOURCE FIELD RECEIVING FIELD
ZERO SUPPRESSION EDITING
2.3.14 Redefines Clause Level-nr data-name-1 REDEFINES data-name-2
Example 05 AAA PIC X(6). 05 BBBB REDEFINES AAA. 10 B-1 PIC X(2). 10 B-2 PIC X(4). 05 CCC REDEFINES AAA. 10 C-1 PIC X(4). 10 C-2 PIC X(2). 2.3.15 File Definition Files to be used in the COBOL program are identified in the ENVIRONMENT DIVISION?s FILE-CONTROL paragraph. The FILE-CONTROL paragraph must contain one entry for each file (i.e. every FD or SD entry) in the DATA DIVISION. Within each FILE-CONTROL entry, the select clause appears first. EXAMPLE ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT COMPONENT-MASTER ASSIGN TO SYSPRINT. SELECT ASSEMBLY-MASTER ASSIGN TO PRODFILE. ?????. DATA DIVISION. FILE SECTION. FD COMPONENT-MASTER ????
FD ASSEMBLY-MASTER ?????..
FILE-CONTROL. SELECT file-name ASSIGN [TO] name [ORGANIZATION IS SEQUENTIAL ] [ACCESS MODE IS SEQUENTIAL ] [FILE STATUS IS dataname] QSAM and VSAM SEQUENTIAL The FILE-CONTROL paragraph associates each file with an external data-set. The ?file-name? must be identified by an FD or SD entry in the data division. With the FILE STATUS clause you can set up to test for a non-zero return code after an input/output statement. Example ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT PRINT-FILE ASSIGN TO SYSPRINT. ?????. DATA DIVISION. FILE SECTION. FD PRINT-FILE RECORD CONTAINS 132.
2.3.17 File-Control (Indexed) FILE-CONTROL. SELECT [OPTIONAL] file-name ASSIGN [TO] name [ORGANIZATION IS ] INDEXED [ACCESS MODE IS SEQUENTIAL | RANDOM | DYNAMIC ] RECORD KEY IS data-name-2 [FILE STATUS IS data-name-1 ] VSAM INDEXED (KSDS) An indexed file means the position of each record is determined by indexes maintained by the system. Indexes are based upon ?keys? embedded within the logical records.
The FILE STATUS value should be checked after every input/output request.
The FILE STATUS data-item should be defined as 2-character alphanumeric item. EXAMPLE ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT IN-FILE ASSIGN TO ?? ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS FILE-STATUS. DATA DIVISION. WORKING-STORAGE SECTION. 77 FILE-STATUS PIC XX. PROCEDURE SECTION. OPEN INPUT IN-FILE IF FILE-STATUS = ?00? PERFORM ????.. ELSE PERFORM ???? FILE DEFINITIONS The connection between COBOL (compile-time ) and JCL (execution-time) specifications for files is illustrated below: ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT INPUT-FILE ASSIGN TO INFILE ORGANIZATION IS INDEXED ACCESS MODE IS RANDOM RECORD KEY IS EMPNO. DATA DIVISION. FILE SECTION. FD INPUT-FILE. 01 EMP-REC. 05 ?? 05 EMPNO 05 ????? PROCEDURE DIVISION. OPEN INPUT INPUT-FILE READ INPUT-FILE?????.. CLOSE INPUT-FILE STOP RUN. //INFILE DD DSN=EMPLOYEE.MASTER,DISP=SHR |
No comments:
Post a Comment