+ All Categories
Home > Documents > IBM Mainframe - Cobol Material

IBM Mainframe - Cobol Material

Date post: 18-Oct-2015
Category:
Upload: usersupreeth
View: 132 times
Download: 18 times
Share this document with a friend
Description:
IBM cobol

of 172

Transcript
  • 5/28/2018 IBM Mainframe - Cobol Material

    1/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    Table of Contents

    UNIT 1. Introduction to Language Features

    COMMON BUSINESS ORIENTED LANGUAGECOBOL PROGRAM ORGANIZATION

    COBOL LANGUAGE STRUCTURESTRUCTURE OF COBOL PROGRAM

    CHARACTER SET OF COBOLSAMPLE COBOL PROGRAM

    CODING FORMATUSER-DEFINED WORDS

    UNIT 2. The Organization of a COBOL Program

    IDENTIFICATION DIVISION

    ENVIRONMENT DIVISIONDATA DIVISIONDATA-ITEMS

    LEVEL NUMBERSSPECIAL LEVEL NUMBERS

    W-S DECLARATIONSFILLER

    PICTURE CLAUSEUSAGE CLAUSE

    VALUE CLAUSEREDEFINES CLAUSE

    DUPLICATE DATA NAMESRENAMES CLAUSE

    FIGURATIVE CONSTANTSEDITED FIELDS

    MORE EDITING CHARACTEREXAMPLES

    UNIT 3. PROCEDURE DIVISIONPROCEDURE DIVISION

    COBOL VERBSPARAGRAPHS

    TERMINATOR STATEMENTSSCOPE TERMINATORS

    DISPLAY VERBACCEPT VERB

    MOVE VERBELEMENTARY & GROUP MOVES

    CORRESPONDING PHASEREFERENCE MODIFICATION

  • 5/28/2018 IBM Mainframe - Cobol Material

    2/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    ADD VERB

    ADD CORRESPONDING STATEMENTON SIZE ERROR PHRASE

    NUMERIC DATA

    SUBTRACT VERBSUBTRACT CORRESPONDING STATEMENTMULTIPLY VERB

    DIVIDE VERBCOMPUTE STATEMENT

    PERFORM STATEMENTPERFORM THROUGH

    PERFORMN TIMESPERFORMVARYING

    IN-LINE PERFORMRELATIONAL EXPRESSIONS

    IF STATEMENTCOMPOUND CONDITIONALS

    CLASS CONDITIONCONTINUE & NEXT SENTENCE STATEMENT

    EVALUATE STATEMENTSET TO TRUE

    INITIALIZE

    UNIT 4. FILE HANDLING IN COBOLFILES

    FIXED VS VARIABLE LENGTH RECORDS

    FILE-CONTROL PARAGRAPHACCESS MODEFILE STATUS CLAUSE

    I-O CONTROL PARAGRAPHFILE SECTION

    FILE OPERATIONSOPEN MODES

    READ-SEQUENTIAL ACCESSEND OF FILE PROCESSING

    READ RANDOM ACCESSREAD DYNAMIC ACCESS

    START STATEMENTWRITE STATEMENT

    WRITEFROMREADINTO

    REWRITE & DELETEAPPENDING TO SEQUENTIAL FILES

    FILE COMPARISONCLOSE STATEMENT

  • 5/28/2018 IBM Mainframe - Cobol Material

    3/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    SEQUENTIAL FILES

    INDEXED FILESINVALID KEY

    ACCESS MODE: SEQUENTIAL & RANDOM

    ACCESS MODE: DYNAMICRELATIVE FILES

    UNIT 5. TABLE HANDLINGINTRODUCTION: TABLE HANDLING

    OCCURS CLAUSESUBSCRIPT

    INDEXINGONE DIMENSIONAL TABLE

    TWO DIMENSIONAL TABLEMULTIDIMENTIONAL TABLE

    TABLE-SORTINGSET

    SEARCHBINARY SEARCH

    UNIT 6. Library ServicesCOPY STATEMENTNESTED COPY

    COPY REPLACINGCOPY PSEUDO-TEST

    REPLACE PSEUDO-TEST

    UNIT 7. CHARACTER HANDLINGSTRING

    UNSTRING STATEMENTEXAMINE STATEMENT

    INSPECT TALLYING STATEMENTINSPECT REPLACING STATEMENT

    UNIT 8. SORT / MERGESORT/MERGESORT STATEMENT

    MERGE STATEMENTSORT PROCEDURES

    RELEASE STATEMENTRETURN STATEMENT

    Cobol Lab

  • 5/28/2018 IBM Mainframe - Cobol Material

    4/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    1

    UNIT 1

    Introduction To Language Features

  • 5/28/2018 IBM Mainframe - Cobol Material

    5/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    2

    Common Business Oriented Language

    1959 New Language is named COBOL 1960 Codasyl established COBOL maintenance committee

    (Conference on data system language).

    1961 1st version of complier made available. Users startedwriting programs (1962).

    1968 2nd version of cobol was approved and standardized byANSI

    1974 Revised and released as COBOL-74 1985- Revised and released as COBOL-85

    Notes:

    To meet the increasing demands for a high level language suitable for business

    data processing, the United States Department of Defense Convened a

    Conference on 28thand 29thof May 1958.

    Three committee were formed for the actual design of the language.

    In September 1959 the short term committee submitted a report to the Defense

    Directorate thus COBOL came into existence.

    COBOL is known as a structured programming language because it allows

    programmers to segregate the modules and put them into different paragraphs in

    a more efficient way.

    Some of the features of COBOL are It is English-like and more easily readable Efficient file handling capabilities. More than 70% of business applications are running on COBOL Reduces the efforts required for documentation of the program.

    The following features are available with VS COBOL II:

  • 5/28/2018 IBM Mainframe - Cobol Material

    6/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    3

    MVS/XA and MVS/ESA support The compiler and the object programs it produces can be run in either 24- or 31-bit addressing mode

  • 5/28/2018 IBM Mainframe - Cobol Material

    7/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    4

    COBOL Program Organization

    The basic structure of any cobol program contains four divisions namely:

    IDENTIFICATION DIVISION

    ENVIRONMENT DIVISION

    DATA DIVISION

    PROCEDURE DIVISION

    Every cobol program must have these divisions.

    Notes:

    The four divisions of a COBOL source program are :

    IDENTIFICATION DIVISIONThe primary purpose of these program is to name the program.

    ENVIRONMENT DIVISIONThis division is primarily used to tell the computer about the input and

    output devices such as files or printers.

    DATA DIVISION

  • 5/28/2018 IBM Mainframe - Cobol Material

    8/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    5

    The division is used to define and describe the data items and being used

    in the program. Data items and data names refer to some storage space in

    memory to store data. Here you would distinguish between data, which

    will be used for a scratch pad area called WORKING-STORAGE and

    the holding area for data that will be used by the files.

    PROCEDURE DIVISIONThe PROCEDURE DIVISION is the section of our program where the

    logic or commands reside. This is also the place logic or rules we will use

    to manipulate the data defined in the DATA DIVISION to solve a

    business problem.

  • 5/28/2018 IBM Mainframe - Cobol Material

    9/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    6

    Cobol Language Structure

    Characters

    Character String COBOL Words User-Defined Words Reserved Words Figurative Words Special Registers

    IBM Extensions Non-numeric and numeric Literals

    Notes:

  • 5/28/2018 IBM Mainframe - Cobol Material

    10/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    7

    Structure of a Cobol Program

    Examples

    Divisions DATA DIVISION

    Sections or Paragraphs PROGRAM-ID

    FILE SECTION, 100-PARA

    Statements MOVE A TO B

    Sentences IF A>B MOVE A TO B ELSEADD C TO D

    Notes:

    All COBOL programs should follow the structure. Rules of coding varies,

    depending on the compiler versions but the structure remains same. A period (.)

    is a must at the end of each sentence and indicates the end of the sentence.

    A typical program could contain divisions, sections or paragraphs within

    divisions, and statements within sections or paragraphs. There are both systemand user defined sections and paragraphs.

    Eg: PROCEDURE DIVISION.

    ADD-PARA.

    ADD A,B GIVING C.

    SUB-PARA.

    Where A,B and C are dada items defined in the data divisions.

  • 5/28/2018 IBM Mainframe - Cobol Material

    11/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    8

    Character Set of COBOL

    COBOL supports the following characters

    Numbers : 0-9 (10 Numericals)

    Alphabets : a-z, A-Z (26 English letters)

    Spaces or blanks : Some times denoted by blanks

    Arithmetic operators : ex: **, *, +, -, /

    Special characters : ex: - \ / , ;

    Notes:

    The character 0-9 are called numeric characters or digits.

    The characters A-Z are called letters and remaining are called special characters.

    The COBOL dictionary words used for coding are called COBOL reserved words

    and they should not be used as user-defined words.

    Lower case alphabets can be used for coding depending on the compiler version.

    Comma (,) or space is used as separators for user-defined words.

  • 5/28/2018 IBM Mainframe - Cobol Material

    12/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    9

    Sample COBOL Program

    Notes:

    1-6 -------------- Sequence numbers

    7 -------------- Indicator/Comment/Continuation

    8-11 -------------- Area A

    12-72 -------------- Area B

    73-80 -------------- Descriptor

    This foil shows a sample COBOL program to ADD two numbers and

    DISPLAY the sum. SAMPLE is the program name.

    SAMPLE, A, B AND C are called user-defined words.

    A, B,C are called variables or data-items.

    Columns

    1 6 7 8 11 12 72 73 80

    * This is a sample program

    IDENTIFICATION DIVISION.

    PROGRAM-ID. SAMPLE.

    ENVIRONMENT DIVISION.

    DATA DIVISION.

    WORKING-STORAGE SECTION.01 A PIC 9(2) VALUE 20.

    01 B PIC 9(2) VALUE 3O.

    01 C PIC 9(3) VALUE ZEROS.

    PROCEDURE DIVISION.

    DISPLAY THE SUM IS.

    ADD A ,B GIVING C.

    DISPLAY C.

    STOP RUN.

  • 5/28/2018 IBM Mainframe - Cobol Material

    13/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    10

    Coding Format

    01 06 Sequence Sequence numbers are generated by

    cobol compiler for each line

    07 Indicator To mark an asterisk (*) or a slash (/)

    for comment line, or a hyphen (-) for

    continuation of a statement.

    08 11 Area A All division headings, section and

    paragraph headings and 01 level

    entries should begin from this area.

    12 72 Area B All Cobol statements and sentences

    should lie within this area

    73 80 Description Any thing written in this area is

    ignored.

    Notes:

    COBOL coding should follow the standard format.

    The Screen is divided into different areas for the purposes explained above.

    All statements indicating action are called COBOL verbs and should begin from

    12th

    column or after.

    -E.g MOVE, ADD, DIVIDE, STOP RUN

  • 5/28/2018 IBM Mainframe - Cobol Material

    14/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    11

    User-defined Words

    Valid Invalid Reason

    TOTAL-OF-FIGURES DATA Cobol reserved word

    34B100-PARA1 -48B Hyphen in beginning

    GROSS-PAY GROSS PAY space in b/w 2 words

    Literals Examples

    Numeric constants 35, -345.67Alphanumeric constants Leo talstoy

    ka01-h215

    Paragraph names, Identifiers, File names can be defined byusers.

    The terms identifiers, data-names, variables, data-items are oftenused interchangeably indicates memory.

    Notes:

    All user-defined words should conform to following rules:

    Length should not exceed 30 characters.

    At least one character must be an alphabet. Spaces and special characters are not allowed. Word can contain hyphens (-) but not in the beginning or at the end Cannot be a COBOL reserved word.

  • 5/28/2018 IBM Mainframe - Cobol Material

    15/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    12

    UNIT 2

    The Organization of a COBOL Program

  • 5/28/2018 IBM Mainframe - Cobol Material

    16/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    13

    IDENTIFICATION DIVISION

    Notes:

    The Identification Division must be the first division in every COBOL source

    program. It must be coded as IDENTIFICATION DIVISION or ID DIVISIONfollowed by a separator period.

    The Identification Division identifies the source program and the resultant outputlisting. The user can include the date the program is written and other information asdesired under the paragraphs in the general format. This entire division (includingthe division header) is optional.

    IDENTIFICATION DIVISION.PROGRAM-ID. AUTHOR. DATE WRITTEN. DATE-COMPILED. SECURITY.

    RequiredRequiredOptionalOptionalOptionalOptional

    At least one space required after the period

  • 5/28/2018 IBM Mainframe - Cobol Material

    17/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    14

    ENVIRONMENT DIVISION

    ENVIRONMENT DIVISION.

    CONFIGURATION SECTION.SOURCE-COMPUTER. .

    OBJECT-COMPUTER. .

    INPUT-OUTPUT SECTION.

    FILE-CONTROL.

    ----------------------------

    ----------------------------

    I-O-CONTROL.

    -----------------------------

    -----------------------------

    Notes:

    The Environment Division is divided into two sections:

    The CONFIGURATION SECTIONThe Configuration Section is an optional section for programs which describe thecomputer environment on which the program is compiled and executed.

    The Configuration Section can be specified only in the ENVIRONMENTDIVISION of the outermost program of a COBOL source program.

    The INPUT-OUTPUT SECTIONThe Input-Output Section of the Environment Division contains two paragraphs:

    o FILE-CONTROL paragrapho I-O-CONTROL paragraph

    FILE-CONTROL paragraphThe keyword FILE-CONTROL can appear only once, at the beginning of the

    FILE-CONTROL paragraph. It must begin in Area A, and be followed by aseparator period. The FILE-CONTROL paragraph is optional.

    The FILE-CONTROL paragraph associates each file in the COBOL program withan external data set, and specifies file organization, access mode, and otherinformation.

  • 5/28/2018 IBM Mainframe - Cobol Material

    18/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    15

    There are three formats for the FILE-CONTROL paragraph:

    QSAM, SAM, and VSAM sequential file entries VSAM indexed file entries VSAM relative file entries.

    The FILE-CONTROL paragraph begins with the word "FILE-CONTROL",followed by a separator period. It must contain one and only one entry foreach file described in an FD or SD entry in the Data Division. Within eachentry, the SELECT clause must appear first, followed by the ASSIGN clause.The other clauses can appear in any order.

    I-O-CONTROL paragraphSpecifies information needed for efficient transmission of data between the

    external data set and the COBOL program. The series of entries must end witha separator period

    The keyword I-O-CONTROL can appear only once, at the beginning of theparagraph. The word I-O-CONTROL must begin in Area A, and must befollowed by a separator period.

    Each clause within the paragraph can be separated from the next by a separatorcomma or a separator semicolon. The order in which I-O-CONTROL

    paragraph clauses are written is not significant

  • 5/28/2018 IBM Mainframe - Cobol Material

    19/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    16

    DATA DIVISION

    Data division is the third and most frequently used division in all

    programs. Every data items or variable required by the program shouldbe declared in appropriate section of the data division, before using in

    procedure division. The Data Division is divided into three sections:

    File Section:

    Defines the structure of data files (including sort-merge files). If the

    program is accessing files.

    Working-Storage Section:

    Describes records and subordinate data items that are not part of

    data files but are required by the program.

    Linkage Section:

    Describes data made available by another program. It usually

    appears in the called program and describes data items that are referred

    to by the calling and the called programs.

    Each section has a specific logical function within a COBOL source

    program, and each can be omitted from the source program when that

    logical function is not needed. If included, the sections must be written inthe order shown.

  • 5/28/2018 IBM Mainframe - Cobol Material

    20/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    17

    DATA DIVISION.FILE SECTION.FD . ---------------

    ---------------WORKING-STORAGE SECTION. DATA TYPES01 VAR-1 PIC A(5). -Alphabetic01 ID-1 PIC X(10) -Alphanumeric01 DATA-NAME PIC 9(5) -Numeric

    Level number pictureClause data type (length)

    LINKAGE SECTION.record-description-entrydata-item-description-entry

  • 5/28/2018 IBM Mainframe - Cobol Material

    21/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    18

    DATA-ITEMS

    Explicitly identifies the data being described

    The data-item must be the first word following the level-number.

    The data-item values can be changed during program execution.

    A data-item name cannot be the same as a section-name or aparagraph name

    Notes:

    Data item is a user-defined word which is associated with Level number.

    COBOL Reserved words should not be Data items.

    The data division of a COBOL source program describes, in a structured manner, allthe data to be processed by the program.

    This division allocates memory locations for the data items that a program requires.There are several types of storage locations in COBOL: file buffers, misc. scratchdata, communication buffers, screen paint data and report format data.

  • 5/28/2018 IBM Mainframe - Cobol Material

    22/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    19

    Level Numbers

    Range of level numbers available are 01 to 49 and

    66 level specified for RENAMING CLAUSE

    77 levels specified exclusively for elementary items

    88 levels specified for CONDITION NAMES.

    An elementary item can be declared with level numbers 01 and 77

    01 and 77 level entries must begin from area A and other levelentries can begin from any where in area A or area B

    Notes:

    Level represents the nature of a data item.

    The level-number specifies the hierarchy of data within a record, and identifiesspecial-purpose data entries. A level-number begins a data description entry, arenamed or redefined item, or a condition-name entry. A level-number has a valuetaken from the set of integers between 01 and 49, or from one of the special level-numbers, 66, 77, or 88.

    Level-number 01 and 77 must begin in Area A and must be followed either by aseparator period; or by a space, followed by its associated data-name, FILLER, orappropriate data description clause.

  • 5/28/2018 IBM Mainframe - Cobol Material

    23/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    20

    Level numbers 02 through 49 can begin in Areas A or B and must be followed by aspace or a separator period.Level number 66 and 88 can begin in Areas A or B and must be followed by a space.

    Single-digit level-numbers 1 through 9 can be substituted for level-numbers 01

    through 09.

    Successive data description entries can start in the same column as the first or theycan be indented according to the level-number. Indentation does not affect themagnitude of a level-number.

    When level-numbers are indented, each new level-number can begin any number ofspaces to the right of Area A. The extend of indentation to the right is limited only

    by the width of Area B.

    Higher numbered level(s) represent subordinate definition(s).

    Level numbers need not be consecutive (but should be in ascending order)

  • 5/28/2018 IBM Mainframe - Cobol Material

    24/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    21

    Special Level Numbers

    LEVEL-66 Identifies items that must contain a RENAMES clause;such items regroup previously defined data items.

    LEVEL-77 Identifies data item description entries that areindependent working-storage, local-storage, or linkage section items;

    they are not subdivisions of other items and are not subdivided

    themselves. Level-77 items must begin in Area A.

    LEVEL-88 identifies any condition-name entry that is associatedwith a particular value of a conditional variable.

    Notes:

    LEVEL-66regroups previously defined items.

    A level-66 entry cannot rename another level-66 entry, nor can it rename a level-01,level-77, or level-88 entry.

    All level-66 entries associated with one record must immediately follow the last data

    description entry in that record.

    LEVEL-77 items are ELEMENATARY items with no subdivision. LEVEL-77names are unique because they can not be qualified.

    LEVEL-88describes condition-names.LEVEL-88 can be used to describe both elementary and group items.

    Level-77 and level-01 entries in the working-storage, local-storage, and linkagesections that are referenced in a program or method must be given unique data-

    names because level-77 and level-01 entries cannot be qualified. Subordinate data-names that are referenced in the program or method must be either uniquely defined,or made unique through qualification. Unreferenced data-names need not beuniquely defined.

  • 5/28/2018 IBM Mainframe - Cobol Material

    25/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    22

    Picture Clause

    Describes the characteristics of the data

    CODE meaning

    A alphabetic or spaceB Blanks or spacesG or N Graphical data9 Indicates a NumericX Indicates an Alpha NumericP Indicates the position of the assumed

    decimal point when the point lies outsidethe data item.V Indicates the position of assumed decimal

    point of numeric field.S Indicates whether the data item signed.

    Notes:

    Picture clause specifies the data type of an identifier.

    Identifier with PIC clause 9 implies that it is numeric data type, which can takeart in arithmetic computations. V and S clauses are allowed with numeric datatypes only.

    X clause represents an alphanumeric data type which can hold any characterincluding numbers also.

    A clause indicates an alphabetic data type.

    Group items are always considered as alphanumeric only. Therefore GROSS-PAY,DEDUCTIONS can not be used for computations.

  • 5/28/2018 IBM Mainframe - Cobol Material

    26/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    23

    W-S Declarations

    WOKING-STORAGE SECTION.

    01 PAY.

    05 GROSS-PAY. Alternatively

    10 BASIC PIC 9(4)V99.

    10 DA PIC 9(4)V99. 9(4)V9(2)

    10 HRA PIC 9(4)V99 9999V99

    05 DEDUCTIONS.

    07 PF-DED PIC 9(3)V99.

    07 IT-DED PIC 9(3)V99.

    05 NET-PAY PIC 9(4)V99.

    05 NAME PIC A(5). AAAAA

    05 E-CODE PIC X(6). XXXXXX

    Notes:

    Use the WORKING-STORAGE SECTION in the DATA DIVISION of theOBJECT paragraph to describe the instance datathat a COBOL class needs, that is,

    the data to be allocated for each instance of the class. The OBJECT keyword, whichyou must immediately precede with an IDENTIFICATION DIVISION declaration,indicates the beginning of the definitions of the instance data and instance methodsfor the class.

    Pay, gross-pay, deductions are called group items and they dont have PICTUREclause. Other elements with picture clause are called elementary items, which cannot

    be broken further.

    Pay is a Group item is divided into Gross-pay, Deductions, net-pay, name, e-codefurther Gross-pay sub-divided into Basic, DA, HRA and DEDUCTIONS sub-divided into PF-DED and IT-DED.

  • 5/28/2018 IBM Mainframe - Cobol Material

    27/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    24

    FILLER

    FILLER is a COBOL Reserved Word used to describe data fields that

    will not be referenced in the PROCEDURE DIVISION.

    If the data-name of FILLER clause is omitted, the data item being

    described is treated as though it was FILLER

    01 EMPLOYEE-RECORD.

    05 EMPLOYEE-TYPE PIC X.

    05 EMPLOYEE-SERIAL PIC X(6).

    05 EMPLOYEE-NAME PIC X(30).PIC X(2).

    05 EMPLOYEE-ADDRESS PIC X(60).

    05 FILLER PIC X(34).

    Notes:

    FILLER is a data item that is not explicitly referred to in a program. The key wordFILLER is optional. If specified, FILLER must be the first word following the level-number.

    IF data-name or FILLER clause is omitted, the data item being described is treatedas though FILLER had been specified.

    The VALUE clause may be used on FILLER items, e.g. to assure BLANKS inheader lines between fields.

    In a MOVE CORRESPONDING statement, or in an ADD CORRESPONDING orSUBTRACT CORRESPONDING statement, FILLER items are ignored.

    In an INITIALIZE statement, elementary FILLER items are ignored.

  • 5/28/2018 IBM Mainframe - Cobol Material

    28/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    25

    USAGE Clause

    data-name [PIC X(n)] [USAGE] COMPCOMP-1

    COMP-2COMP-3

    COMP - Binary Representation Size: Half/Full/Double word

    COMP-1 - Hexa Decimal Representation Size: Full word for Float

    COMP-2 - Hexa Decimal Representation Size: Double word for Float

    COMP-3 - Packed Decimal Representation Size: round(n/2)+1Where n is number of digits.

    Notes:

    The usage description must match the data-field type described in the FD descriptor

    of the COBOL program. If the COBOL program does not include a usage clause,select the Chars (character) option for the usage.

    The USAGE clause can be specified for a data description entry with a level-numberother than 66 or 88. However, if it is specified at the group level, it applies to eachElementary item in the group. The usage of an elementary item must not contradictthe usage of a group to which the elementary item belongs.

    The USAGE clause specifies the format in which data is represented in storage. Theformat can be restricted if certain Procedure Division statements are used.

    When the USAGE clause is not specified at either the group or elementary level, itassumed that the usage is DISPLAY.

  • 5/28/2018 IBM Mainframe - Cobol Material

    29/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    26

    Computational (COMP) Usage

    When usage is specified as COMP, the numeric data item is represented in pure binary. Theitem must be an integer (no assumed decimal point is allowed). Such that data items areoften used as subscripts. The PICTURE of a COMP item should not contain any character

    other than 9, S. This is the equivalent of BINARY. The COMPUTATIONAL phrase issynonymous with BINARY.

    COMPUTATIONAL-1 (COMP-1) Usage

    If the usage of a numeric data item is specified as COMP-1, it will be represented in oneword in the floating point form. The number is actually represented in Hexa decimal (base16). Such representation is suitable for arithmetic operations. The PICTURE clause cannotbe specified for COMP-1 items. Specified for internal floating-point items (singleprecision). COMP-1 items are 4 bytes long.

    COMPUTATIONAL-2(COMP-2) Usage

    This usage is same as COMP-1, except that the data is represented internally in two words.The advantage is that this increases the precision of the data which means that moresignificant digits can be available for the item. The PICTURE clause cannot be specified forCOMP-2 items. Specified for internal floating-point items (double precision). COMP-2items are 8 bytes long.

    COMPUTATIONAL-3(COMP-3) Usage

    In this form of internal representation the numeric data is the decimal form, but one digittakes half-a-byte. The sign is stored separately as the right most half a-byte regardless ofwhether S is specified in the PICTURE or not. The hexa decimal number C or F denotes apositive sign and the Hexa decimal number D denotes a negative sign. Inorder that datafields can start and end on byte boundaries, numbers with an even number of digits arestored with an extra half-byte of zeroes on the left hand side. Thus an item with

    PICTURE S9(5)V9(3) USAGE IS COMP-3

    will require 5 bytes to be stored internally. Only the characters 9, S, V and P can be used inthe PICTURE of a COMP-3 item. This is the equivalent of PACKED-DECIMAL.

  • 5/28/2018 IBM Mainframe - Cobol Material

    30/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    27

    Value Clause

    Value Clause defines the initial value of a data item must not be used for

    items declared in FILE SECTION. Can also specify FIGURATIVECONSTANTS. If defined at the group level can be used for array

    declaration also

    EXAMPLES

    01 NUM-1 PIC 9(3) VALUE 245.

    01 E-CODE PIC X(6) VALUE E10K3.

    At group level contents01 GROUP-ITEM VALUE IS ER34155

    05 E-ITEM-1 PIC X(2). ER

    05 E-ITEM-2 PIC XXX 341

    05 E-ITEM-3 PIC X(3) 55

    Group item is considered as alphanumeric.

    Notes:

    Assigning values to identifiers is called initialization. If variables are not initialized,then they may contain any value, which was stored at the time of last execution of

    program. It is advised to always initialize working-storage variables.

    The VALUE clause specifies the initial contents of a data item or the valuesassociated with a condition-name. The use of the VALUE clause differs dependingon the data division section in which it is specified.

    A VALUE clause that is used in the file section or the linkage section in an entryother than a condition-name entry is syntax checked, but has no effect on the

    execution of the program.

    In the working-storage section and the local-storage section, the VALUE clause canbe used in condition-name entries or in specifying the initial value of any data item.The data item assumes the specified value at the beginning of program execution. Ifthe initial value is not explicitly specified, the value is unpredictable.

  • 5/28/2018 IBM Mainframe - Cobol Material

    31/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    28

    REDEFINES Clause

    Two or more data items can share the same working storage area by

    REDEFINING a storage area.

    Level number data name-1 REDEFINES data-name-2

    Level numbers of data-name-1 and data-name-2 must be identical

    The redefines clause must immediately follow data-name-I

    Must not be used for level number 66 or 88 items.

    Data-name-1 should not contain VALUE clause

    Multiple redefinition is allowed

    Notes:

    Two or more storage areas defined in the data sometimes may not be usedsimultaneously, in such cases; only one storage area can serve the purpose oftwo or more areas if the area is defined.

    The REDEFINES clause used allows the said area to be referred to by morethan one data name with different sizes and pictures.

    ILLUSTRATES REDEFINES CLAUSE

  • 5/28/2018 IBM Mainframe - Cobol Material

    32/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    29

    DATA DIVISION.

    WORKING-STORAGE SECTION.

    01 X1

    02 Y PIC 99.

    02 Y1 REDEFINES Y PIC XX.

    01 X3

    02 Z PIC X VALUE M.

    02 ZZ PIC X (25) VALUE ALL *.

    02 ZZZ PIC X (45) VALUE ALL - .

    01 X4 REDEFINES X3.

    02 FILL1 PIC X.

    02 FILL2 PIC X (70).01 X5 REDEFINES X4.

    02 BUFFER PIC X (71).

    PROCEDURE DIVISION

    PARA 1.

    MOVE 20 TO Y.

    DISPLAY X1.

    MOVE A1 TO Y1.

    DISPLAY X1

    DISPLAY X3.

    DISPLAY X4.

    DISPLAY X5.

    STOP RUN.

    Duplicate Data Names

  • 5/28/2018 IBM Mainframe - Cobol Material

    33/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    30

    Are allowed, provided they belong to a group item

    01 Pay-Rec.

    02 Id-numbers PIC 9(5).

    02 Name PIC X (25).

    02 Dept PIC X (20).

    01 Print-Rec.

    02 Filler PIC X (5).

    02 Id-numbers PIC X (5)

    02 Filler PIC X (5).

    02 Name PIC X (25).

    02 Dept PIC X (920).

    MOVE Id-Numbers (OF | IN) Pay-Rec TO Id-Numbers (OF | IN)Print-

    Rec.

    * OF and IN are called Qualifiers.

    To move the data stored in the four fields of Pay-Rec. the four MOVEstatements serve the purpose.

    Using the MOVE CORRESPONDING statement the same can beaccomplished.

    RENAMES Clause

    Syntax:

  • 5/28/2018 IBM Mainframe - Cobol Material

    34/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    31

    66 data-name-1 RENAMES data-name-2 THRU data-name-3

    E.g. :

    01 PAY REC.

    02 FIXED-PAY.05 BASIC PIC 9(6) V99.

    05 DA PIC 9(6) V99.

    02 ADDITIONAL-PAY.

    05 HRD PIC 9(4) V99.

    05 INCENT PIC 9(3) V99.

    02 DEDUCTIONS.

    05 PF PIC 9(3) V99.

    05 IT PIC 9(4) V99.

    05 OTHER PIC 9(3) V99.

    66 PAY-OTHER-THAN-BASIC RENAMES DA THRU INCENT.

    66 IT-AND-PF-DEDUCTIONS RENAMES PF THRU IT.

    Notes:

    In order to re-group elementary data items in a record, so that they can belong to theoriginal as well as to the new group, the RENAMES clause is used.

    The RENAMES clause specifies alternative and possibly overlapping groupings ofelementary data items.

    LEVEL-66regroups previously defined items.

    A level-66 entry cannot rename another level-66 entry, nor can it rename a level-01,level-77, or level-88 entry.

    All level-66 entries associated with one record must immediately follow the last datadescription entry in that record.

    ILLUSTRATES RENAMES CLAUSE

    DATE DIVISION.

    WORKING-STORAGE SECTION.

    01 PAY

  • 5/28/2018 IBM Mainframe - Cobol Material

    35/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    32

    02 FIXED-PAY

    10 E-BASIC PIC 9(6). 99

    10 E-DA PIC 9(6). 99.

    05 ADDL-PAY.

    10 HRA PIC 9(4). 99.

    10 INCENTIVE PIC 9(3). 99.

    05 DEDUCTIONS.

    10 E-PF PIC 9(3). 99.

    10 E-IT PIC 9(4). 99.

    10 OTHERS PIC 9(3). 99.

    66 PAY-LESS-BASIC RENAMES E-DA THRU INCENTIVE.

    66 IT-AND-PF RENAMES E-PF THRU E-IT.

    PROCEDURE DIVISION.

    MAIN-PARA

    MOVE-123456.78 TO E-BASIC.

    MOVE 234567.89 TO E-DA.

    MOVE 1234.56 TO HRA.

    MOVE 123.45 TO INCENTIVE.

    MOVE 123.45 TO E-PF.

    MOVE 1234.56 TO E-IT.

    MOVE 123.45 TO OTHERS.

    DISPLAY PAY.

    DISPLAY FIXED-PAY.DISPLAY ADDL-PAY.

    DISPLAY DEDUCTIONS.

    DISPLAY PAY-LESS-BASIC.

    DISPLAY IT-AND-PF.

    STOP RUN.

    Figurative Constants

    Constants frequently used by most programs

  • 5/28/2018 IBM Mainframe - Cobol Material

    36/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    33

    Collating sequence is the order in which the characters arecompared by the system.

    Figurative Constants Meaning

    HIGH-VALUE(S) Represents the highest and lowest

    LOW-VALUES (S) value in the collating sequence.

    ZERO, ZEROS, ZEROES One or more Zeroes

    SPACE (S) One or more blanks

    Example: 01 ID-1 PIC X(3) VALUE SPACES.

    Notes:

    Figurative constants are reserved words that name and refer to specific constantvalues.

    ZERO, ZEROS, ZEROES:

    Represents the numeric value zero (0) or one or more occurrences of the characterzero, depending on context. When the figurative constant ZERO, ZEROS, orZEROES is used in a context that requires an alphanumeric character, analphanumeric character zero is used.

    SPACE:

    Represents one or more blanks or spaces. SPACE is treated as an alphanumericliteral when used in a context that requires an alphanumeric character, as a DBCSliteral when used in a context that requires a DBCS character, and as a nationalliteral when used in a context that requires a national character.

    HIGH-VALUE:

    Represents one or more occurrences of the character that has the highest ordinalposition in the collating sequence used. HIGH-VALUE is treated as an alphanumericliteral in a context that requires an alphanumeric character.

  • 5/28/2018 IBM Mainframe - Cobol Material

    37/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    34

    LOW-VALUE:

    Represents one or more occurrences of the character that has the lowest ordinalposition in the collating sequence used. LOW-VALUE is treated as an alphanumeric

    literal in a context that requires an alphanumeric character.

    Edited Fields

    Move 345.46 to a field of picture 9(3)v99 & display or print Youmay see different number in result

  • 5/28/2018 IBM Mainframe - Cobol Material

    38/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    35

    Characters must be edited before report is taken to suppressleading zeros, to include currency signs or to include date

    separators.

    Editing Codes Effect

    Z Leading Zeros if any will be suppressed

    * Leading Zeros are replaced by asterisks(*)

    $ Currency sign appears in the left most of

    the field.- Appears at left or right of the field as

    specified in the picture clause if value is

    negative

    + Appears if value is positive, else minus sign

    appears

    Editing Codes are specified in the picture clause for variables intended for

    report purpose.

    These variables cannot be used for arithmetic calculations.

    More Editing Characters

    EDIT CODES Meaning

  • 5/28/2018 IBM Mainframe - Cobol Material

    39/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    36

    CR or DB To be specified in the right most position of

    the pic clause. Appears only if the value is

    negative it replaced by two characters.

    . Stands for decimal point. Cannot specify

    with V clasue.

    , Insert in position where specified.

    B Blank is appeared.

    0 Zero is also appeared. To be specified left

    most position of pic clasue.

    - (hyphen) /(slash) Used as date separator. Appears wherespecified.

    BLANK WHEN ZERO Sets all null values to blanks.

    EXAMPLES

    DATAPIC CLAUSEUNEDITED

    PIC CLAUSEEDITED

    EDITEDVALUE

    02346 9(5) ZZ999 2346

    0005 9(4) ZZ99 05

  • 5/28/2018 IBM Mainframe - Cobol Material

    40/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    37

    03.42 99V99 Z999 003

    0.007 9V999 ZV999 007

    05634 9(5) **999 *5634

    00143 9(5) $9(5) $00143

    453 9(3) $**999 $**453-0453 9(4) -ZZ9(2) -453

    -0453 9(4) 9999- 0453-

    453 9(3) 999- 453

    -453 9(3) 999+ 453-

    70.46 99V99 99.99- 70.46

    156758 9(6) 99/99/99 15/67/58

    00 99V9 99.9 Blank whenzero

    8654 9(4) 99b9b9 86b5b424 99 9900 2400

    Notes:

    The above table shows contents of unedited fields in the first column. Contents ofedited fields after moving the data-1 shown in last column.

    Edited fields (Fields with editing codes) cannot take part in arithmetic computations.

    Moving of numeric edited fields to unedited fields is illegal.

  • 5/28/2018 IBM Mainframe - Cobol Material

    41/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    38

    UNIT 3

    PROCEDURE DIVISION

  • 5/28/2018 IBM Mainframe - Cobol Material

    42/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    39

    PROCEDURE DIVISION

    PROCEDURE DIVISION[USING , .

    MAIN-PARA.

    DISPLAY ENTER VALUE OF A:.ACCEPT A.

    DISPLAY ENTER VALUE OF B:.

    ACCEPT A.

    MOVE A TO B.

    ADD A TO B.

    DISPLAY A VALUE : A.

    DISPLAY B VALUE : B.

    ---------------------------------

    --------------------------------

    STOP RUN.

    Notes:

    Procedure Division can consists ofSections (Optional)Paragraphs (Optional)Statements.

    While coding, we must follow the following Hierarchy:SECTION------- PARAGRAPHS ------STATEMENTS

    OrPARAGRAPH------- STATEMENTS

    OrSTATEMENTS

  • 5/28/2018 IBM Mainframe - Cobol Material

    43/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    40

    COBOL VERBS

    All instructions are coded in Procedure division.

    BASIC COBOL VERBS

    MOVE ACCEPT DISPLAY PERFORM GO TO STOP RUN CALL COPY SORT MERGE FILE OPERATIONS CHARACTER HANDLING TABLE HANDLING CONDITIONS ARITHMETIC VERBS

    Notes:

    Arithmetic Verbs : ADD, SUBTRACT, MULTIPLY, DIVIDE, COMPUTEConditions : IF.ELSE, EVALUATEFile handling : READ, WRITE, REWRITE, DELETECharacter handling : INSPECT, STRING, UNSTRINGTable handling : SET, SEARCH

    Paragraphs

    Paragraphs are building blocks of the PROCEDURE DIVISION

  • 5/28/2018 IBM Mainframe - Cobol Material

    44/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    41

    PROCEDURE DIVISION.

    MAIN-PARA.

    STATEMENT1.

    STATEMENT2.

    ------------------------------------------

    ---------------------

    PARA-100.

    ---------------------

    ---------------------

    Notes:

    A paragraph-name must begin in Area A and must be followed by a separatorperiod.

    A paragraph-name need not be unique because it can qualified by a SECTIONname.

    Paragraph-names need NOT contain any alphabetic character (i.e. can be allnumeric).

    A paragraph ends at:

    The next paragraph-name or section header The end of the PROCEDURE DIVISION The Scope terminator END-PARAGRAPH

    Terminator Statements

    EXIT PROGRAM

  • 5/28/2018 IBM Mainframe - Cobol Material

    45/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    42

    The EXIT PROGRAM statement specifies the end of a called program

    and returns control to the calling program

    STOP RUN

    The STOP RUN statements halts the execution of the object program,

    and returns control to the system

    GOBACK

    The GOBACK statement functions like the EXIT PROGRAM

    statement. When it is coded as part of a called program and like the

    STOP RUN when coded in a main program

    Notes:

    If these statements are not the last statements in a sequence, statements following

    them will not be executed.

    Scope Terminators

    Explicit scope terminators mark the end of certain PROCEDURE

    DIVISION statements.

    Explicit scope terminators are COBOL Reserved Words.

  • 5/28/2018 IBM Mainframe - Cobol Material

    46/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    43

    END-ADD

    END-SEARCH

    END-CALL

    END-MULTIPLY

    END-START

    END-COMPUTEEND-PERFORM

    END-STRING

    END-DELETE

    END-READ

    END-DIVIDE

    END-UNSTRING

    END-EVALUATE

    END-REWRITE

    END-WRITE

    END-IF

    An explicit Scope Terminator is paired with the unpaired occurrence of

    the verb. An implicit Scope Terminator is a separator period.

    Notes:

    Example:

    PERFORM PARA-1 UNTIL A > 10STATEMENT1STATEMENT2---------------------------------------

    END-PERFORM.

    Period (.) should not encounter in between PERFORM and END-PERFORM.Since it indicates end of the PERFORM statement, then compiler error will raise.

    DISPLAY Verb

    The function of the DISPLAY statement is to display low-volume results

    on the operators console or some other hardware device.

  • 5/28/2018 IBM Mainframe - Cobol Material

    47/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    44

    Syntax:

    >>____DISPLAY_____ __identifier-1___ __ |

    _____________________________________________>

    | _ literal-1______|

    E.g:

    PROCEDURE DIVISION.

    DISP-PARA.

    DISPLAY SRCH-ARG NOT IN TABLE..

    ----------------------------------

    -------------------------------

    DISPLAY HELLO HOW ARE YOU.

    Notes:

    The DISPLAY statement transfers the contents of each operand to the outputdevice. The contents are displayed on the output device in the order, left to right,in which the operands are listed.

    WITH NO ADVANCING when specified, the positioning of the output devicewill not be changed in any way following the display of the last operand.

    ACCEPT Verb

    Format 1 transfers data from an input/output device into identifier-1.

    When the FROM phrase is omitted, the system input device isassumed.

  • 5/28/2018 IBM Mainframe - Cobol Material

    48/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    45

    Format 1 is useful for exceptional situations in a program whenoperator intervention (to supply a given message, code, or

    exception indicator) is required.

    Format 1 :

    >>__ACCEPT______identifier-1__________________________________ ______________>>___ADD_______ identifier-1_ _|__ To _____identifier-2__ ________

    ____________ __|_________>

    |_literal-1___| |_ROUNDED _|

    >___ ____________________________________________________

    ___________________________>

    |_ ____ __SIZE ERROR imperative-statement-1______|

    >___ _____________________________________________________

    ___________________________>

    |_ NOT___ ______ ___SIZE ERROR__imperative statement_2_|

    >___ _______ _________________________________________________>

    |_ END-ADD_|

    In Format 1, all identifiers or literals preceding the key word TO be

    added together and this sum is stored in a temporary data item. This|temporary data item is then added to each successive occurrence of

    identifier-2, in the left-to-right order in which identifier-2 is specified.

    Identifier must name an elementary numeric item. Literal must be a

    numeric. The ADD statement sums two or more numeric operands and

    stores the result.

    Example:ADD A TO B.

    ADD 112 TO B.

    ADD A TO B ON SIZE ERROR GO TO ERR-PARA.

  • 5/28/2018 IBM Mainframe - Cobol Material

    56/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    53

    ADD Verb (Continue.)

    The operands preceding the GIVING are added together and thesum replaces the value of each identifier-3

  • 5/28/2018 IBM Mainframe - Cobol Material

    57/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    54

    Identifiers must be elementary numeric items, except whenfollowing GIVING then they may also be numeric edited.

    Format 2:

    >>___ADD_______ identifier-1_ _|__ ___ _ ____ _ __ _ identifier-2____________________________>

    |_literal-1___| |_TO_| |_literal-2______|

    >___ GIVING ___________identifier-3__ ______________ _|

    ___________________________________ >

    |_ ROUNDED__|

    >___ _____________________________________________________

    ____________________________ >

    |_ _________ ___SIZE ERROR__imperative statement_1_|

    >___ _____________________________________________________

    ___________________________ >

    |_ NOT___ ______ _SIZE ERROR__imperative statement_2_|

    |_ ON_|

    >___ _______ _________________________________________________ >

    |_ END-ADD_|

    In Format 2, the values of the operands preceding the word GIVING

    are added together, and the sum is stored as the new value of each data

    item referenced by identifier-3.

    Identifier must name an elementary numeric item, except when

    following the word GIVING. Each identifier following the word

    GIVING must name an elementary numeric or numeric-edited item

    Literal must be a numeric.

  • 5/28/2018 IBM Mainframe - Cobol Material

    58/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    55

    Example:ADD A TO B GIVING C

    ADD CORRESPONDING Statement

    Elementary data items within identifer-1 are added to, and storedin the corresponding elementary data items with identifer-2.

    ADD CORRESPONDING identifiers must be group items

  • 5/28/2018 IBM Mainframe - Cobol Material

    59/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    56

    Format:

    >>___ADD_______ CORRESPONDING_ ___identifier-1___ TO___ identifier-

    2____________________>

    |_CORR__________|

    >___ ______________ __ ______________________________________________

    ________________ >

    |_ ROUNDED__| | _ ___ __SIZE ERROR____ imperative-statement-1_|

    |_ ON_ |

    >___ _____________________________________________________

    ___________________________ >

    |_NOT___ ______ __SIZE ERROR__imperative statement_1_|

    |_ON___|

    >___ _____________________________________________________

    ___________________________ >|_ NOT___ ______ _SIZE ERROR__imperative statement_2_|

    |_ ON_|

    >___ _______ _________________________________________________ >

    |_ END-ADD_|

    In Format 3, elementary data items within identifier-1 are added to and

    stored in the corresponding elementary items within identifier-2.

    Identifier must name a group item. Literal must be a numeric.

    Notes:

    ON SIZE ERROR Phrase

    If the value of an arithmetic evaluation exceeds the largest valuethat can be contained in a result, then a size error condition exists.

    The SIZE ERROR condition applies to final results, notintermediate calculations

  • 5/28/2018 IBM Mainframe - Cobol Material

    60/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    57

    If ON SIZE ERROR phrase is not specified, then truncation of theresults will occur.

    If ON SIZE ERROR phrase is specified, the imperative statement(in ON SIZE ERROR) is taken, following which control is

    transferred to the end of the arithmetic statement.

    For ADD CORRESPONDING or SUBTRACTCORRESPONDING, the ON SIZE ERROR imperative is not

    taken until all individual additions or subtractions have been

    completed.

    A size error condition can occur in three different ways:

    When the absolute value of the result of an arithmetic evaluation,after decimal point alignment, exceeds the largest value that can be

    contained in the result field

    When division by zero occurs In an exponential expression, as indicated in the following table:

    Sizeerror Actiontakenwhen aSIZEERRORclause is present

    ActiontakenwhenaSIZEERROR clause is not present

    Zero raised to zero

    power

    The SIZE ERROR

    imperative is executed.

    The value returned is 1, and

    message is issued.Zero raised to anegative number

    The SIZE ERRORimperative is executed.

    Program is terminatedabnormally.

    A negative numberraised to a fractional

    power

    The SIZE ERROR imperativeis executed

    The absolute value of the base iused, and a message is issued

  • 5/28/2018 IBM Mainframe - Cobol Material

    61/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    58

    The size error condition applies only to final results, not to any

    intermediate results.

    NUMERIC Data

    Types of numeric items are:

    Binary Packed decimal. (Internal decimal) Floating point representation.

  • 5/28/2018 IBM Mainframe - Cobol Material

    62/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    59

    The PICTURE character-string can contain only the symbols 9, P,S and V

    The number of digit positions must range from 1 through 18,inclusive

    If unsigned, the contents of the item in standard data format mustcontain a combination of the Arabic numerals 0-9. If signed, it may

    also contain a +, - or other representation of the operation sign

    Notes:

    A VALUE clause can specify a figurative constant ZERO.

    SUBTRACT Verb

    Format 1:

    >>___SUBTRACT_______ identifier-1_ _|__

    FROM_________________________________________>|_literal-1___|

    > ______identifier-2__ _______________

    _|________________________________________________>

    | _ ROUNDED ____|

  • 5/28/2018 IBM Mainframe - Cobol Material

    63/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    60

    >___ ____________________________________________________

    ___________________________>

    |_ ____ __SIZE ERROR imperative-statement-1______|

    |_ON _|

    >___ _____________________________________________________

    ___________________________>

    |_ NOT___ ______ ___SIZE ERROR__imperative statement_2_|

    >___ _______ _________________________________________________>

    |_ END-SUBTRACT_|

    All identifiers or literals preceding the key word FROM are added

    together and this sum is subtracted from and stored immediately in

    identifier-2. This process is repeated for each successive occurrence of

    identifier-2, in the left-to-right order in which identifier-2 is specified.

    Notes:

    SUBTRACT Verb (Continue.)

    Format 2:

    >>___SUBTRACT_______ identifier-1_ _|__ FROM ___ _ identifier-2__

    __________________________>|_literal-1___| |_literal-2______|

    >___ GIVING ___________identifier-3__ ______________ _|

    ___________________________________ >

    |_ ROUNDED__|

  • 5/28/2018 IBM Mainframe - Cobol Material

    64/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    61

    >___ _____________________________________________________

    ____________________________ >

    |_ _______ ___SIZE ERROR__imperative statement_1_|

    |_ ON _|

    >___ _____________________________________________________

    ____________________________ >|_ NOT___ ______ _SIZE ERROR__imperative statement_2_|

    |_ ON_|

    >___ _______ __________________________________________________ >

    |_ END-SUBTRACT_|

    All identifier or literals preceding the key word FROM are added

    together and this sum is subtracted from identifier-2 or literals-2. The

    result of the subtraction is stored as the new value of each data item

    referenced by identifier-3.

    Notes:

    Example:

    1. SUBTRACT A FROM B.The value of a subtracted from the value of B and then the resultant value will bestored in B.

    2. SUBTRACT 9 FROM C.3. SUBTRACT C FROM 9. Is not valid because 9 is a Literal.

    SUBTRACT CORRESPONDING Statement

    Format:

    >>___SUBTRACT_______ CORRESPONDING_ ___identifier-1___

    FROM________________________>

    |_CORR__________|

    >___ identfier-2____ __ ___________

    _____________________________________________________ >

    |_ ROUNDED__|

    >___ _____________________________________________________

    ____________________________ >

    |____ ______ __SIZE ERROR__imperative statement_1_|

  • 5/28/2018 IBM Mainframe - Cobol Material

    65/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    62

    |_ON___|

    >___ _____________________________________________________

    ____________________________ >

    |_ NOT___ ______ _SIZE ERROR__imperative statement_2_|

    |_ ON__|

    >___ _______ __________________________________________________ >

    |_ END-SUBTRACT_|

    Elementary data items within identifier-1 are subtracted from, and the

    results are stored in, the corresponding elementary data items within

    identifier-2.

    Notes:

    MULTIPLY Verb

    Format 1:

    >>___MULTIPLY_______ identifier-1___ ___BY____identifier-2___

    __________________| __________>

    |_ literal-1________|

    >___ _____________________________________________________

    ____________________________ >|____ ______ __SIZE ERROR__imperative statement_1_|

    |_ON___|

    >___ _____________________________________________________

    ____________________________ >

    |_ NOT___ ______ _SIZE ERROR__imperative statement_2_|

    |_ ON__|

    >___ _______ _________________________________________________ >

  • 5/28/2018 IBM Mainframe - Cobol Material

    66/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    63

    |_ END-MULTIPLY_|

    In Format 1, the value of identifier-1 or literal-1 is multiplied by the value of

    identifier-2; the product is then placed in identifier-2. For each successive

    occurrence of identifier-2, the multiplication takes place in the left-to-right

    order in which identifier-2 is specified.

    Notes:

    The MULTIPLY statement multiplies numeric items and sets the values of dataitems equal to the results.

    MULTIPLY Verb (continue..)

    Format 2:

    >>___MULTIPLY_______ identifier-1_ _|__ BY_______ _ identifier-2__

    __________________________>

    |_literal-1___| |_literal-2______|

    >___ GIVING ___________identifier-3__ ______________ _|

    ___________________________________ >

    |_ ROUNDED__|

    >___ _____________________________________________________

    ____________________________ >

    |_ _______ ___SIZE ERROR__imperative statement_1_|

    |_ ON _|

  • 5/28/2018 IBM Mainframe - Cobol Material

    67/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    64

    >___ _____________________________________________________

    ____________________________>

    |_ NOT___ ______ _SIZE ERROR__imperative statement_2_|

    |_ ON_|

    >___ _______ _________________________________________________ >

    |_ END-MULTIPLY_|

    In Format 2, the value of identifier-1 or literal-1 is multiplied by the

    value of identifier-2 or literal-2. The product is then stored in the data

    item(s) referenced by identifier-3.

    Notes:

    DIVIDE Verb

    Format 1:

    >>___DIVIDE_____ _____ identifier-1_ _|__ INTO__________identifier-2_____________ __ |____>

    |_literal-1___||_ROUNDED _|

    >___ ________________________________________________________________________________>

    |_ ____ __SIZE ERROR imperative-statement-1____________|

    |_ON _|>___ _____________________________________________________

    ____________________________>|_ NOT___ ______ ___SIZE ERROR__imperative statement_2_|

    |_ON __|>___ _______ __________________________________________________>

    |_ END-DIVIDE_|

  • 5/28/2018 IBM Mainframe - Cobol Material

    68/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    65

    In Format 1, the value of identifier-1 or literal is divided into the value

    of identifier-2, and the quotient is then stored in identifier-2. For each

    successive occurrence of identifier-2, the division takes place in the left-

    to-right order in which identifier-2 is specified.

    Notes:

    The DIVIDE statement divides one numeric data item into or by other(s) and setsthe values of data items equal to the quotient and remainder

    DIVIDE Verb (Continue)

    Format 2:

    >>___DIVIDE_______ identifier-1_ _|__ INTO_______ _ identifier-2__

    ___________________________>

    |_literal-1___| |_literal-2______|

    >___ GIVING ___________identifier-3__ ______________ _|

    ___________________________________ >

    |_ ROUNDED__|

    >___ _____________________________________________________

    ____________________________ >|_ _______ ___SIZE ERROR__imperative statement_1_|

    |_ ON _|

    >___ _____________________________________________________

    ____________________________>

    |_ NOT___ ______ _SIZE ERROR__imperative statement_2_|

    |_ ON_|

  • 5/28/2018 IBM Mainframe - Cobol Material

    69/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    66

    >___ _______ _________________________________________________ >

    |_ END-DIVIDE_|

    In Format 2, the value of identifier-1 or literal-1 is divided into or by the

    value of identifier-2 or literal-2. The value of the result is stored in each

    data item referenced by identifier-3.

    Notes:

    COMPUTE Verb

    Format:

    >>___COMPUTE_______ identifier-1_ ____________ _|____ _ =______

    __________________________>|_ ROUNDED _| |_ EQUAL_|

    >___ arithmetic

    expression_______________________________________________________________

    _ >

    ____________________________ >

    |_ _______ ___SIZE ERROR__imperative statement_1_|

    |_ ON _|

    >___ _________________________________________________________________________________ >

    |_ NOT___ ______ _SIZE ERROR__imperative statement_2_|

    |_ ON_|

    >___ _______ __________________________________________________ >

    |_ END-COMPUTE_|

  • 5/28/2018 IBM Mainframe - Cobol Material

    70/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    67

    The arithmetic expression is calculated and replaces the value for each

    identifier-1 item. Valid operators allowed in the expression are:

    + addition - subtraction

    * multiplication / division

    ** exponentiation

    Notes:

    The COMPUTE statement assigns the value of an arithmetic expression to one ormore data items.

    With the COMPUTE statement, arithmetic operations can be combined withoutthe restrictions on receiving data items imposed by the rules for the ADD,

    SUBTRACT, MULTIPLY, and DIVIDE statements.

    Identifier-1

    Must name elementary numeric item(s) or elementary numeric-edited item(s). Canname an elementary floating-point data item. The word EQUAL can be used in

    place of =.

    An arithmetic expression ca consists of any of the following:

    1. An identifier described as a numeric elementary item2. A numeric literal3. The figurative constant ZERO4. Identifiers are literals, as defined in terms 1,2, and 3, separated by

    arithmetic operators5. Two arithmetic expressions, as defined in items 1,2,3, and/or 4, separated

    by an arithmetic operator6. An arithmetic expression, as defined in items 1,2,3,4 and/or 5, enclosed in

    parentheses.

    When the COMPUTE statement is executed, the value of the arithmetic expressionis calculated, and this value is stored as the new value of each data item referenced

    by identifier-1.

  • 5/28/2018 IBM Mainframe - Cobol Material

    71/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    68

    PERFORM Statement

    PERFORM Paragraph-name/Section-header

    Transfer the control to the specified paragraph or section and expects

    the control back after executing the paragraph.

    PERFORM Para-name-1 [ THROUGH (or) THRU Para-name-n]

    Notes:

  • 5/28/2018 IBM Mainframe - Cobol Material

    72/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    69

    PERFORM types

    PERFORM Para-name PERFORM Para-name N TIMES PERFORM Para-name VARYING K FROM M BY N UNTIL CONDITION

    K>20 PERFORM Para-name VARYING K FROM M BY N UNTIL CONDITION

    K>20 AFTER VARYING.

    PERFORM THROUGH

    PROCEDURE DIVISION.

    100-MAIN-PARA.

    PERFORM 200-PARA THRU 500-PARA.

    STOP RUN.

    200-PARA.

    * Statements.

    400-PARA.

    * Statements

    500-PARA.

    * Statements

    300-PARA.

    * Statement - Not executed

    All the paragraphs between 200-PARA and 500-PARA are executed.

    Notes:

  • 5/28/2018 IBM Mainframe - Cobol Material

    73/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    70

    PERFORMN times

    PERFORM PARA-NAME-1[THROUGH (or) THRU PARA-NAME-N]

    N TIMES.

    EX:

    PERFORM PARA-1000 15 TIMES.

    PERFORM PARA-1000 THRU PARA-4000 15 TIMES.

    PARA-1000.

    ADD A TO B.

    ------------------------

    -------------------------

    PARA-2000.

    SUBTRACT A FROM B.

    -------------------------------

    -------------------------------

    PARA-4000.

    MULTIPLY A BY B.

    ----------------------------

    Notes:

  • 5/28/2018 IBM Mainframe - Cobol Material

    74/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    71

    PERFORMVARYING

    PERFORM PARA-NAME-1 [THRU (or) THROUGH PARA-NAME-N]VARYING { identifier- 1 } {identifier-2 }

    {Index-name-1} FROM {index-name-2}

    { Literal-1 }

    BY {identifier-3 } UNTIL Condition

    {Literal-2 }

    EX:

    PERFORM PARA-2000 THRU PARA-5000 VARYING A FROMM BY N UNTIL A > Y

    PERFORM para-1 Varying K FROM 10 BY 5 UNTIL K>100

    Notes:

    Example 2 says:

    Sets the value of K to 10 initiallyExecute para-1

  • 5/28/2018 IBM Mainframe - Cobol Material

    75/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    72

    Check the condition K > 100If condition is true, transfer the control to next lineIf condition is false, increment K by 5Execute para-1 againCheck the condition K > 100Repeat steps from 2 through 7 until Condition K > 100 becomes true

    Flow Chart for PERFORM .. VARYING

    False

    True

    Enter

    Set identifier 1to initial value

    Condition

    Execute range

    Add increment to -identifier.

    Exit

    False

    True

  • 5/28/2018 IBM Mainframe - Cobol Material

    76/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    73

    PERFORM with the VARYING-AFTER Option

    PERFORM PARA-NAME-1 [THRU (or) THROUGH PARA-NAME-N]VARYING { identifier- 1 } {identifier-2 }

    {Index-name-1} FROM {index-name-2}

    {Literal-1 }

    BY {identifier-3 } UNTIL Condition-1{Literal-2 }

    AFTER { identifier- 4 } {identifier-5 }{ Index-name-3} FROM {index-name-4}

    { Literal-3 }

    BY {identifier-6} UNTIL Condition-2{Literal-4 }

    AFTER { identifier- 7 } {identifier-8 }{Index-name-5} FROM {index-name-6}

    { Literal-5 }

    BY {identifier-9 } UNTIL Condition-3{Literal-6 }

    This form is used when a nested repetition of the range is required while varyingmore than one identifier.

  • 5/28/2018 IBM Mainframe - Cobol Material

    77/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    74

    For example:PERFORM RANGE-TO-BE-EXECUTED

    VARYING I FROM 1 BY 1 UNTIL I > 50AFTER J FROM 1 BY 1 UNTIL J > 10.

    The range RANGE-TO-BE-EXECUTED will be performed 500 times,.

    In-Line PERFORM

    The in-line PERFORM will be coded using END-PERFORM.

    Named Paragraph

    PERFORM MOVEIT

    VARYING X FROM 1 BY 1 UNTIL X = 5.. . .

    MOVEIT.MOVE DATA-FLD (X) TO PRINT (X).

    In-line PERFORM

    PERFORM VARYING X FROM 1 BY 1 UNTIL X = 5.MOVE DATA-FLD (X) TO PRINT (X).

    END-PERFORM.

    Notes:

    An In-line PERFORM requires the END-PERFORM terminator. Conversely theEND-PERFORM phrase must not be specified when the statement is PERFORM

    procedure name.

  • 5/28/2018 IBM Mainframe - Cobol Material

    78/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    75

    IN-LINE PERFORM Considerations

    DO not use for procedures executed from several places/ Use for procedures referenced only once. Consider not using if readability is affected , such as multiple-page

    PERFORM,

    No periods may appear within the in-line PERFORM. Delimited by END-PERFORM. END-PERFORM cannot be used at end of an out-of-line PERFORM. The OPTIMIZE compile option may move the PERFORM in-line in

    the object code at the compile time.

  • 5/28/2018 IBM Mainframe - Cobol Material

    79/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    76

    IF... ELSE Statement

    The IF statement evaluates a condition and provides for alternative actions in

    the object program, depending on the evaluation.

    Format :

    >>_______IF_____Condition-1____ __________ _____ ___statement-1___|__ ____________________>

    |_THEN_____| |_NEXT SENTENCE _|>___ ____________________________ ____ ________________

    ______________________________>

    |

  • 5/28/2018 IBM Mainframe - Cobol Material

    80/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    77

    Compound Conditionals

    Conditional expressions can be compound using the AND and OR

    logical operators

    Conditional conditions can also use parentheses to group conditions.

    IF ITEM-1 = DOMESTIC-ITEM-NOAND ITEM-2 = OVERSEAS-ITEM-NO

    ORITEM-1 = OVERSEAS-ITEM-NO

    AND ITEM-2 = DOMESTIC-ITEM-NOSET MIXED-SHIPMENT-FLAG TO TRUE

    END-IF

    .SEARCH TABLEPAIR VARYING NDXWHEN ITEM-1(NDX) = FROM-CITY AND ITEM-2(NDX) = TO-CITY

    MOVE WHEN ITEM-2(NDX) = FROM-CITY AND ITEM-1(NDX) = TO-CITY

    MOVE ..END-SEARCH

    Notes:

    Relational Expressions

  • 5/28/2018 IBM Mainframe - Cobol Material

    81/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    78

    Relational tests (comparisons) can be express as:

    IS LESS THAN IS EQUAL TO =

    IS NOT EQUAL TO NOT =

    IS GREATER THAN OR EQUAL TO >=

    IS LESS THAN OR EQUAL TO

  • 5/28/2018 IBM Mainframe - Cobol Material

    82/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    79

    IF C = DNEXT SENTENCEELSE

    MOVE MESSAGE-1 TO RPT-MESSAGE-1END-IF

    ADD C TO TOTAL

    DISPLAY TOTALIF E = FMOVE MESSAGE-4 TO RPT-MESSAGE-2

    END-IFEND-IF.

    Example 2 - CONTINUEIF A = B

    IF C = DCONTINUE

    ELSE

    MOVE MESSAGE-1 TO RPT-MESSAGE-1END-IFADD C TO TOTALDISPLAY TOTALIF E = F

    MOVE MESSAGE-4 TO RPT-MESSAGE-2END-IFEND-IF.

    Notes:

    EVALUATE Statement

    EVALUATE is a great way to implement the case programming

    construct

    EVALUATE datanameWHEN value-1 .WHEN value-2 {THROUGH | THRU} value-3 .

    WHEN NOT value-4

  • 5/28/2018 IBM Mainframe - Cobol Material

    83/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    80

    Basic EVALUATE Example:

    The scope of a WHEN clause is all statements UNTIL the next WHEN

    clause, the END-EVALUATE, or a period

    Notes:

    The EVALUATE statement provides a shorthand notation for a series of nested IFstatements. It can evaluate multiple conditions. That is, the IF Statements can bemade up of compound conditions.

    Examples:

    Working-Storage for all Examples:

    01 PLANET.05 PLANET-NUMBER PIC 9.05 PLANET-NAME PIC X(7).

    Evaluate Example Number 1: (Evaluate a PIC 9 field)

    EVALUATE datanameWHEN A Perform add-transWHEN D Perform delete-transWHEN UWHEN W Perform update-transWHEN OTHER Perform bad-trans

    END-EVALUATE

  • 5/28/2018 IBM Mainframe - Cobol Material

    84/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    81

    EVALUATEPLANET-NUMBERWHEN 1 MOVE "Mercury" TO PLANET-NAMEWHEN 2 MOVE "Venus " TO PLANET-NAMEWHEN 3 MOVE "Earth " TO PLANET-NAMEWHEN 4 MOVE "Mars " TO PLANET-NAMEWHEN 5 MOVE "Jupiter" TO PLANET-NAME

    WHEN 6 MOVE "Saturn " TO PLANET-NAMEWHEN 7 MOVE "Uranus " TO PLANET-NAMEWHEN 8 MOVE "Neptune" TO PLANET-NAMEWHEN 9 MOVE "Pluto " TO PLANET-NAMEWHEN OTHER MOVE " " TO PLANET-NAME

    END-EVALUATE.

    Evaluate Example Number 2: (Evaluate a PIC X field)

    EVALUATEPLANET-NAMEWHEN "Mercury" MOVE 1 TO PLANET-NUMBER

    WHEN "Venus " MOVE 2 TO PLANET-NUMBERWHEN "Earth " MOVE 3 TO PLANET-NUMBERWHEN "Mars " MOVE 4 TO PLANET-NUMBERWHEN "Jupiter" MOVE 5 TO PLANET-NUMBERWHEN "Saturn " MOVE 6 TO PLANET-NUMBERWHEN "Uranus " MOVE 7 TO PLANET-NUMBERWHEN "Neptune" MOVE 8 TO PLANET-NUMBERWHEN "Pluto " MOVE 9 TO PLANET-NUMBERWHEN OTHER MOVE 0 TO PLANET-NUMBER

    END-EVALUATE.

    Evaluate Example Number 3:Let each of MONTH and NO-OF-Days be two-digited numeric integer fields. The values1,2,3, etc. for MONTH denote respectively, January, February, March etc. depending onthe value of MONTH , we wish to ove 30,31 or 28 to NO-OF-DAYS. For example , ifthe value of MONTH is 1, we shall move 31; if it is 2, we shall move 28 and so on. TheEVALUATE statement for the purpose is as follows:

    EVALUATETRUEWHEN MONTH = 4 OR 6 OR 9 OR 11

    MOVE 30 TO NO-OF-DAYSWHEN MONTH = 2

    MOVE 28 TO NO-OF- DAYSWHEN OTHER MOVE 31 TO NO-OF-DAYSEND EVALUATE.

    In this case, we have assumed that MONTH has a correct value.

    Evaluate Example Number 4:

    Suppose MARKS contains the marks obtained by a student. GRADE is an one- characteralphanumeric field. We wish to calculate GRADE according to the following rules

  • 5/28/2018 IBM Mainframe - Cobol Material

    85/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    82

    MARKS GRADE

    80 100 A60 - 79 B45 - 59 C30 - 44 D

    0 - 29 EThe EVALUATE statement for the purpose is shown below.EVALUATE MARKS

    WHEN 80 THRU 100 MOVE A TO GRADEWHEN 60 THRU 79 MOVE B TO GRADEWHEN 45 THRU 59 MOVE C TO GRADEWHEN 30 THRU 44 MOVE D TO GRADEWHEN ZERO THRU 29 MOVE E TO GRADEWHEN OTHER MOVE W TO GRADE

    END-EVALUATE.

    The literal W is moved to GRADE in the case of wrong marks.

    ILLUSTRATES CONDITION NAMES

    DATA DIVISION.

    WORKING-STORAGE SECTION.

    77 MARTIAL-STATUS PIC 9.88 SINGLE VALUE 0.88 MARRIED VALUE 1.88 WIDOWED VALUE 2.88 DIVORCED VALUE 3.88 ONCE-MARRIED VALUES ARE 1, 2, 3.

  • 5/28/2018 IBM Mainframe - Cobol Material

    86/172

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    83

    88 VALID-STATUS VALUES ARE 0 THRU 3.77 AMOUNT PIC 9 (4) VALUE 1000.

    PROCEDURE DIVISION.

    MAIN-PARA.DISPLAY Martial Status:DISPLAY 0- Single / 1- Married / 2- Widowed / 3- Divorced.ACCEPT MARTIAL-STATUS.IF NOT VALI-STATUS DISPLAY Error in Entry.IF SINGLE SUBTRACT 100 TO AMOUNT.IF MARRIED ADD 100 TO AMOUNT.IF WIDOWED ADD 200 TO AMOUNT.IF DIVORCED SUBTRACT 200 FROM AMOUNT.IF ONCE-MARRIED ADD 250 TO AMOUNT

    DISPLAY AMOUNT.STOP RUN.

    INITIALIZE Statement

    The INITIALIZE statement sets selected categories of data fields topredetermined values. It is functionally equivalent to one or more MOVEstatements.

    When the REPLACING phrase is not used:

    SPACE is the implied sending field for alphabetic alphanumeric,alphanumeric-edited, and DBCS items. ZERO is the implied sending fieldfor numeric and numeric-edited items.

    >>___INITIALIZE____identifier-1_________________________________________________________________>

    _______>>__SET____condition-name-1_|_ TOTRUE_________________________>>____READ__file-name-1___ _________________ __ __________ ___________________>|_ NEXT __________| |_RECORD__||_ (1)||_ PREVIOUS______|

    >_____ _______________________ ______________________________________________>|____ INTO___identifier-1____|

    >_____ ___________________________________ __________________________________>|_ ____ __END_imperative statement-1_|

    |_ AT _|>_____ ____________________________________________ ____ __________ _______>>_____READ______file-name-1____ __________ ___ _______________ _____________>

    >____ _____________________________ ________________________________________>|_KEY_____ ___ __data-name-1__|

    |_TO_|

    >_____ _______________________________________________ ______________________>|_INVALID_____ ______ ____imperative-statement-3__|

    |_KEY __|

    >____ ___________________________________________ ___ ____________ _______>>___START___file-name-1___________________________________________________________>

    >__ _____________________________________________________________________ ________>|_KEY___ ______ ____ __EQUAL___ ___ ________________ _data-name-1____|

    |__TO _| | |_ TO_| ||_ = ______________________________||_LESS__ _______ ________________|| |_THAN_| ||_GREATER__ ____ _____________|| |_THAN_| ||_NOT LESS___ _______ ___________|| |_THAN _| ||_NOT < ___________________________||_NOT GREATER__ _______ ________|| |_THAN_| |

    |_NOT > ___________________________||_LESS_ ____ _ OR EQUAL_ __ _____|| |THAN| |_TO_| ||_GREATER__ ____ _OR EQUAL_ __ _|| |_THAN_| \TO||_>+_______________________________|

    >__ _______________________________________ _____________________________________>|_INVALID___ _____ _imperative-statement-1_|

    |_KEY_|>__ _______________________________________ ___________ ____________ _____________>

    |_NOT INVALID___ _____ imperative-statement-1_| |_END-START_||_KEY_|

    Notes:

    The START statement provides a means of positioning within an indexed orrelative file for subsequent sequential record retrieval. When the STARTstatement is executed, the associated indexed or relative file must be open in eitherINPUT or I-O mode.

    file-name-1

    Must name a file with sequential or dynamic access. File-name-1 must be definedin an FD entry in the Data Division, and must not name a sort file.

    END-START Phrase

    This explicit scope terminator delimits the scope of the START statement. END-START converts a conditional START statement to an imperative statement sothat it can be nested in another conditional statement. END-START can also beused with an imperative START statement.

  • 5/28/2018 IBM Mainframe - Cobol Material

    108/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    106

    WRITE Statement

    The WRITE statement releases a logical record for an output orinput/output file.

    When the WRITE statement is executed:- The associated sequential file must be open in OUTPUT or

    EXTEND mode.- The associated indexed or relative file must be open in OUTPUT, I-

    O, or EXTEND mode. Record-name must be defined in a Data Division FD entry. Record-

    name can be qualified. It must not be associated with a sort or merge

    file.

    Notes:

  • 5/28/2018 IBM Mainframe - Cobol Material

    109/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    107

    WRITE.FROM

    PROCEDURE DIVISION.

    WRITE File-rec FROM Identifier.

    File-rec is record-name declared in FILE-SECTION. Identifier is a working-storage section variable The length of the identifier should be equal to the length of the

    record.

    Notes:

    To Create a file, program can accept the data from the terminal into file record andwrite it.

    If the data need to be processed, it can be accepted in a W-S identifier. Afterprocessing the data the above WRITE..FROM statement can be issued.

    Each WRITE statement writes one record at a time.

  • 5/28/2018 IBM Mainframe - Cobol Material

    110/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    108

    READ.INTO

    PROCEDURE DIVISION.

    READ FILE-name (INTOW-S-Rec) | (AT END Statement)

    File name is defined in SELECT clause. W-S-Rec is working-Storage section identifier. INTO clause moves the file record to W-S-rec. AT END clause if used, indicates the next action after the last record

    is read.

    OPEN INPUT Mode

    Notes:

    READ statement on sequential files reads one record at a time and makes itavailable to program.

    Reading begins from first record and if the READ statement is put in a loop. Thatis executing the statement repeatedly, then it is possible to read consecutiverecords.

    Loop can be terminated before AT END condition is reached if required so by theprogram.

    If the file is left open next time when the read statement executes, readingcontinuous from where it was stopped before the termination of loop.

    If the file is closed then it is to be opened again before reading it.

  • 5/28/2018 IBM Mainframe - Cobol Material

    111/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    109

    REWRITE & DELETE

    REWRITE record-name (FROM identifier)

    Updates an existing record from W-S identifier.

    OPEN I-O File-name

    DELETE record-name -----------------not allowed

    Deleting of a record in sequential files not allowed.

    Notes:

    It is often required to change the existing data and the process is calledUPDATING.

    COBOL provides REWRITES verb to modify an existing record.

    For example, changing the address field of an employee requires reading ofemployee number. Every record to be updated needs to be read first. To searchthe record of an employee, whose employee number is known, the process is asfollows

    Store the employee number in a variable Open the file Read first record Compare the variable with Emp-No field of the file If it matches update his address by REWRITE Else read next record his address by REWRITE Repeat the process until the require record is read.

  • 5/28/2018 IBM Mainframe - Cobol Material

    112/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    110

    Appending to sequential files

    Adding new records to the existing file.

    OPEN EXTEND Mode

    WRITE records.

    When new records to be added to file open the file in EXTEND modeEXTEND mode causes the pointer to move to the end of the file.

    Notes:

  • 5/28/2018 IBM Mainframe - Cobol Material

    113/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    111

    CLOSE Statement

    Format :

    CLOSE File-name-1, [File-name-2 .]

    CLOSE Statement Releases the Resourcces which are assigned to that file.

    Cannot Close the file which is not opened.

    After performing the operations on the file (I,e no longer usedin a program) needs to beclosed but not necessary.

    If the FILE STATUS clause is specified in the FILE-CONTROL entry, the associatedstatus key is updated when the CLOSE statement is executed.

    If the file is in an open status and the execution of a CLOSE statement is unsuccessful,the EXCEPTION/ERROR procedure (if specified) for this file is executed.

    Notes:

  • 5/28/2018 IBM Mainframe - Cobol Material

    114/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part

    without the prior written permission.

    112

    Sequential Files

    ENVIRONMENT DIVISION.INPUT-OUTPUT SECTION.

    FILE-CONTROLSELECT file-name ASSIGN TO DEVICE-NAMEORGANIZATION IS SEQUENTIAL.ACCESS MODE IS SEQUENTIAL. AreaFILE STATUS IS data-name. B

    Notes:

    All the files used in the program should have an entry in FILE CONTROLparagraph.

    For each file used, there should be one SELECT..ASSIGN clause.

    The file-name is select clause is user defined word and can be used throughout theprogram wherever required.

    ASSIGN clause specifies the device on which file stored.

  • 5/28/2018 IBM Mainframe - Cobol Material

    115/172

    Student Notebook

    CopyrightCourse materials may not be produced in whole or in part


Recommended