Wednesday, December 15, 2010

Procedure Division

3.1 Data Movement Verbs
3.1.1 MOVE Statement

The MOVE statement copies data from one area of storage to one  (more) other areas.

MOVE identifier-1 TO identifier-2 ????.
MOVE literal    TO identifier-2 ????.
Identifiers may be either elementary or group items.
A POINTER data-item, or an index data-item, cannot be specified in a MOVE.

3.1.2  Elementary Moves

  • Both sending and receiving data-items are elementary items.
  • Data conversion may take place, as well as editing or de-editing.
  • On alphabetic moves, may necessary space-fill or truncation will
occur.
3.1.3  Group Moves

  • Both sending and receiving data-items are group items.
  • No data conversion takes place.

MOVE EXAMPLE
WORKING-STORAGE SECTION.
01                GROUP-VARIABLES.
04        VAR-1                                                PIC    X(1).
04        VAR-2                                                PIC    X(2).
04        VAR-3                                                PIC    X(3).
04        VAR-4                                                PIC    X(4).

PROCEDURE DIVISION.

MOVE  SPACES TO  GROUP-VARIABLES-1.


bbbbbbbbbb


MOVE  ?XY? TO  VAR-1   VAR-3.


XbbXYbbbbb


MOVE  ALL ?*? TO  VAR-4.


XbbXYb****


MOVE  ALL ?AB? TO  VAR-3.


XbbABA****




3.2  Arithmetic verbs
Intermediate results of arithmetic statements are possible when:

  • ADD or SUBTRACT with multiple operands following the verb.
  • COMPUTE with multiple result fields.
  • Arithmetic expressions in reference modifications
  • Use of multiple results in the GIVING phrase of ADD, SUBTRACT,
MULTIPLY, or DIVIDE statements.

The maximum size of each arithmetic operand is 18 decimal digits, but a hypothetical ?composite of operands? can be up to 30 decimal digits.
The following example has a composite of operands with implicit description of PIC  9(12)V9(5) or 17 decimal digits.

DATA DIVISION.
77        FLD1  PIC      9(7)V9(5).
77        FLD2  PIC      9(11)V99.
77        FLD3  PIC      9(12)V9(3).

PROCEDURE DIVISION.
ADD FLD1, FLE2  GIVING FLD3


ADD Statement
ADD  identifier-1A   identifier-1B  ????.
To identified ? 2A [ROUNDED]
identifier-2B   ????.
[ON SIZE ERROR??..]
[NOT ON SIZE ERROR??..]
[END-ADD]
  • The identifiers (or literals) preceding the word TO are added together, and then this sum is added to, and replaces, each identifier-2. The action is repeated, In left-to-right order, for each identifier-2.
  • Identifiers must be elementary numeric items.
  • ADD is not allowed with items having USAGE POINTER.
Example
ADD   amount-1  amount-2   TO amount-3
ADD amount-1  TO  amount-2  amount-3.
ADD 1  TO  employee-count.
SUBTRACT Statement

SUBTRACT   identifier-1A   identifier-1B  ???FROM  identifier-2A   [ROUNDED]
identifier-2B    identifier-2C   ????.
[ON SIZE ERROR??..]
[NOT ON SIZE ERROR??..]
[END-SUBTRACT]
  • All identifiers (or literals) preceding the word FROM are added together, and then this sum is subtracted from, and replaces, identifier-2. The action is repeated, in left-to-right order, for each identifier-2.

  • Identifiers must be elementary numeric items.

  • SUBTRACT is not allowed with items having USAGE POINTER.

MULTIPLY Statement
MULTIPLY   identifier-1   BY  identifier-2A   [ROUNDED] identifier-2B    identifier-2C   ????.
[ON SIZE ERROR??..]
[NOT ON SIZE ERROR??..]
[END- MULTIPLY]
  • The identifier (or literal) is multiplied by identifier-2; the product replaces.identifier-2. The action is repeated, in left-to-right order, for each identifier-2.
  • Identifiers must be elementary numeric items.
DATA DIVISION.

77 SALES-TAX                   PIC   99999V99.
77 MERCHANDISE           PIC   99999V99.

PROCEDURE DIVISION.

MULTIPLY  MERCHANDISE  BY  .0675             GIVING SALES-TAX  ROUNDED.

DIVIDE Statement
DIVIDE   identifier-1
INTO   identifier-2A   [ROUNDED]
identifier-2B       identifier-2C ??..
[ON SIZE ERROR??..]
[NOT ON SIZE ERROR??..]
[REMAINDER identifier-3]
[END- DIVIDE]

  • The value of the first identifier (or literal) is divided into the value of
identifier-2; the quotient replaces identifier-2. The action is
repeated, in left-to-right order, for each identifier-2.
  • Identifiers must be elementary numeric items.
  • The SIZE ERROR execution occurs if division by zero is attempted.
DIVIDE Statement
DIVIDE   identifier-1    INTO       identifier-2    GIVING    identifier-3A   [ROUNDED]
Identifier-3B   identifier-3C ??..
[ON SIZE ERROR??..]
[NOT ON SIZE ERROR??..]
[END- DIVIDE]

DIVIDE   identifier-1
BY   identifier-2
GIVING   identifier-3A   [ROUNDED]
Identifier-3B       identifier-3C ??..
[END- DIVIDE]

  • The value of the first identifier (or literal) is divided into (or by) the value of identifier-2; the quotient replaces identifier-3. The action is repeated, in left-to-right order, for each identifier-3.
  • Identifiers-1 and -2 must be elementary numeric items.
  • Identifier-3 may be a numeric-edited item.
COMPUTE Statement
COMPUTE   identifier-1A   [ROUNDED]
identifier-1B       identifier-1C ??..
EQUAL(=)   arithmetic-expression
[ON SIZE ERROR??..]
[NOT ON SIZE ERROR??..]
[END- COMPUTE]

  • Identifier-1 may name elementary numeric items or numeric-edited items.
  • The arithmetic expression is calculated and replaces the value for each identifier-1item.
  • Arithmetic operators allowed in the expression are:
+     (addition)
-     (subtraction)
*    (multiplication)
/     (division)
**  (exponentiation)

Example
COMPUTE
FINAL-VAL  ROUNDED  = BASIC-VAL  *  1.5
END-COMPUTE.

3.3  Table handling
Table-handling is fundamental to data processing. A table is a collection of logically related entries. A table is a set of values stored in consecutive storage locations and assigned one variable. Any reference to specific entries in the table, is made by the use of the variable along with a subscript that identifies the location of a particular entry. While an array stores data to be output, a table is used for looking up or referencing data.
So, instead of defining n data-names in the WORKING-STORAGE SECTION the same can be defined like this  :
E.g. 01  WEEK-TABLE.
05   DAY OCCURS 7 TIMES PIC X(9).
Use of the OCCURS clause along with the PICTURE clause, helps the programmer to create  tables so that reference can be made to entire tables  or individual values by means of a subscript. In the example, 7 memory locations are set aside, each of which will hold a 9 character alphabetic string.
A DATA DIVISION entry involving an OCCURS clause, includes the name assigned to the table, the number of rows and columns (the dimension), the number of entries in each dimension, and the field characteristics of each entry. An individual entry is indicated by assigning a subscript within brackets after the data-name. These individual entries are called elements.
Now the first DAY in the WEEK-TABLE can be referred as DAY(1). Similarly the 7th entry in the table can be referred to as DAY(7). Thus each element is assigned a numeric value which is called the subscript. Now, a specific element in the table is accessed by the use of subscripts. The subscript can be represented either by a literal or by a data-name which is defined elsewhere as a numeric elementary data-item.
E.g. DAY(1)  or DAY(CTR)
where CTR is a data-item defined as a numeric data-name. So, if the value
of CTR is 1, then you are actually referring to the first occurrence in the
WEEK-TABLE.
WEEK-TABLE

SUNDAY



MOND A Y



TUE SDAY


WEDNESDAY
THURSDAY

FRIDAY



SATURDAY


E.g.
*The program creates a table of student marks, calculates the total and average.
IDENTIFICATION DIVISION.
PROGRAM-ID. MARK-CAL.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01   TOT              PIC  9(4) VALUE 0.
01   AVG             PIC  9(3) VALUE 0.
01   CTR              PIC  9(2) VALUE 0.
01   MARKS-TABLE.
03  MARKS OCCURS 7 TIMES PIC  9(3).
PROCEDURE DIVISION.
MAIN-PARA.
PERFORM ENTER-PARA VARYING CTR FROM 1 BY 1 UNTIL CTR > 7.
MOVE 0 TO TOT.
PERFORM TOTAL-PARA VARYING CTR FROM 1 BY 1 UNTIL CTR > 7.
PERFORM  DISPLAY-PARA.
GOBACK.
ENTER-PARA.
DISPLAY "ENTER MARKS FOR SUBJECT : ", CTR.
ACCEPT MARKS(CTR).
TOTAL-PARA.
ADD MARKS(CTR) TO TOT.
DISPLAY-PARA.
COMPUTE AVG ROUNDED = TOT / 7.
DISPLAY "THE TOTAL MARK IS  : ", TOT.
DISPLAY "THE AVERAGE IS     : ", AVG.
IF AVG >= 60
DISPLAY "FIRST CLASS"
ELSE  IF AVG >= 50
DISPLAY "SECOND CLASS"
ELSE IF AVG >= 40
DISPLAY "THIRD CLASS"
ELSE
DISPLAY "FAIL".
STOP " ".
Here,  MARKS-TABLE is a group data-item and is therefore defined as a 01 level entry.  Each data-item is called MARKS which has 7 items.
OCCURS clause
The OCCURS clause, on a data definition, specifies tables whose elements can be referred to by indexing or subscripting.



OCCURS integer [ TIMES ]
[ ASCENDING  [ KEY IS ] data-name-2 ]
[ INDEXED BY index-name-1 ]

OCCURS integer [ TIMES ]
[ DESCENDING [ KEY IS ] data-name-2 ]
[ INDEXED BY index-name-1 ]


  • Fixed-length tables allow 7 level of nesting.
  • ?integer? is the exact number of occurrences (must be > 0).
  • The ASCENDING / DESCENDING KEY phrase is needed for a ?binary search? of the table with SEARCH ALL statement.
  • A key-field may have USAGE DISPLAY, BINARY, PACKED-DECIMAL, amongst others.

 SUBSCRIPTING
 Subscripting is a means of providing table references. A subscript is a positive number whose value indicates the occurrence of a table element.
 Seven levels of subscripting are allowed.
 Subscripts are enclosed in parentheses.
 The number of subscripts must equal the number of dimensions in the table being referenced.
 Example

 01                TABLE-THREE.
05                                        ELEMENT-1 OCCURS nn TIMES.
10                                                                ELEMENT-2 OCCURS nn TIMES.
15        ELEMENT-3 OCCURS nn TIMES    PIC    X(8).
MOVE ELEMENT-3 (1,  2,  1)    TO   ???..
MOVE ELEMENT-3 (SUB1 SUB1 SUB1)  TO ??.
Indexing
An ?index-name? is an identifier that becomes associated with a particular table. The value in an index is the displacement from the beginning of the table based upon the length of the table element.

An ?index-name? may appear on an OCCURS clause, e.g.
01                TABLE-OF-MONTHS.
02 MONTHS OCCURS 12  TIMES  PIC  X(10)  INDEXED  BY  NDX.
The ?index-name? is created by the compiler; it does not have to be defined elsewhere in the program.
The actual value in an index is determined by the following formula;

I = L * ( S ? 1 )

Where I is the index value; L is the length of a table element; S is the occurrence number of the entry.
The contents of an index may be changed by the SET TO statement. An index may not be used in a MOVE statement or an INITIALIZE statement.
Subscript Vs Index


SubscriptIndex
Represents an occurance of a Table elementRepresents the displacement from the address of the first element in table.
Is defined explicitly in working-storage sectionAn index is a special subscript created and
Maintained by the OS.
To change value of subcript, use a PERFORM .. VARYING or a MOVE , ARITHMETIC statementTo change the value of Index use PERFORM .. VARYING or a SET statement.


SEARCH statement ? serial

SEARCH identifier
[ VARYING index-name ]
[  AT END imperative ?.]   -?  when no occurrence found
WHEN condition-1 imperative ?.
[ WHEN condition-1 NEXT SENTENCE  ]
[END-SEARCH ]

SEARCH statement ? binary
SEARCH ALL identifier
[ AT END imperative  ]
WHEN condition-1
[AND condition-2]?.
Imperative     [END-SEARCH]
Condition : The identifier must contain an OCCURS clause with KEY IS phrase.


SET INDEX STATEMENT
Different SET statements.
SET index-name TO integer
SET index-name to identifier
SET index-name to index-name-1
SET index-name-1 UP/DOWN  BY integer / identifier

SERIAL SEARCH.
WORKING-STORAGE SECTION.
01                                        WHOLE-TABLE.
02                                        TABLE-ELMT    OCCURS  nn   TIMES
INDEXED BY NDX.
10                                                                                        KEYFIELD ?
PROCEDURE DIVISION.
SEARCH TABLE-ELMT VARYING NDX
WHEN KEYFIELD(NDX) = SEARCH-ARG
SET FOUND TO TRUE
WHEN KEYFIELD(NDX) = HIGH-VALUES
SET NOT-FOUND TO TRUE
END-SEARCH
IF  FOUND
???.
ELSE
DISPLAY SEARCH-ARG ?NOT IN TABLE ?
END-IF

BINARY SEARCH
LINKAGE SECTION.
01       WHOLE-TABLE.
03        TABLE-ELMT           OCCURS 1 TO 250 TIMES
DEPENDING ON PARM2
ASCENDING KEY IS KEYFIELD INDEXED BY NDX.
05        KEYFIELD    PIC      X(n).
05                                                                                        ??
PROCEDURE DIVISION.
MOVE   ?.    TO PARM2
SET ADDRESS OF WHOLE-TABLE TO TABLE-POINTER
SEARCH ALL TABLE-ELMT
WHEN KEYFIELD(NDX) = SEARCH-ARG
SET FOUND TO TRUE
END-SEARCH
IF FOUND
END-IF.
PERFORM Statement
PERFORM  is a sequence control statement that causes the program to branch out to another procedure or a series of procedures and following the execution, it returns to the point it branched out from. The  procedure is treated as a sub-routine, and the PERFORM statement in the main routine provides a link to and from the sub-routines.

1.                  SIMPLE PERFORM
PERFORM PARA-1.
DISPLAY ?PARA-1 executed?
STOP RUN.
PARA-1.
Statement1

Statement2.
It executes all the instructions coded in PARA-1 and then transfers the control to the next instruction in sequence.


2.                  INLINE PERFORM.
When sets of statements are used only in one place then we can group all of them within PERFORM END-PERFORM structure. This is called INLINE PERFORM. This is equal to DO..END structure of other languages.
PERFORM
ADD A TO B
MULTIPLY B BY C
DISPLAY ?VALUE OF A+B*C? C
END-PERFORM

3.                  PERFORM PARA-1 THRU PARA-N.
All the paragraphs between PARA-1 and PARA-N are executed once.

4.                  PERFORM PARA-1 THRU PARA-N UNTIL conditions(s).
The identifiers used in the UNTIL condition(s) must be altered within the paragraph(s) being performed; otherwise the paragraphs will be performed indefinitely. If the condition in the UNTIL clause is met at first time of execution, then named paragraph(s) will not be executed at all.

5.                  PERFORM PARA-1 THRU PARA-N N TIMES.
N can be literal defined as numeric item in working storage or hard coded constant.

6.                  PERFORM PARA-1 THRU PARA-N VARYING identifier1
FROM identifier 2 BY identifier3 UNTIL condition(s)
Initialize identifier1 with identifier2 and test the conditions(s). If the condition is false execute the statements in PARA-1 thru PARA-N and increment identifiere1 BY identifier3 and check the condition(s) again. If the condition is again false, repeat this process till the condition is satisfied.

7.                  PERFORM PARA-1 WITH TEST BEFORE / AFTER UNTIL conditions
With TEST BEFORE condition is checked first if it is found to be false then PARA-1 will be executed and this is the default.
With TEST AFTER PARA-1 is executed once and then the condition is checked.

3.4  Input ? Output statement
OPEN Statement
OPEN  INPUT  filename ???
OPEN  OUTPUT  filename  ???
OPEN  I-O     filename???
OPEN  EXTEND    filename  ???

The phrase INPUT, OUTPUT, I-O, or EXTEND must appear at least once (but may be in any order).
Example
DATA DIVISION.
FILE SECTION.
FD       INVOICE
RECORD CONTAINS 80
RECORDING MODE F.

FD       PRINTOUT
RECORD CONTAINS 132.

PROCEDURE DIVISION.
OPEN INPUT         INVOICE
OPEN OUTPUT     PRINTOUT
 CLOSE Statement



CLOSE filename1  ,
filename2??.

CLOSE   filename1
filename2


The CLOSE statement terminates the processing of files; a close may be executed only for file in open mode.
 After CLOSE processing, the record area associated with the file is no longer available.
The CLOSE WITH LOCK phrase ensures that the file cannot be opened again during the execution.
The CLOSE WITH NO REWIND phrase exists to ensure that the volume is left in its current position.

Example
DATA DIVISION.
FILE SECTION.
FD       INVOICE
RECORD CONTAINS 80
RECORDING MODE F.
 FD       PRINTOUT
RECORD CONTAINS 132.
RECORDING MODE F.
 PROCEDURE DIVISION.
??????
??????..
CLOSE INVOICE  PRINTOUT
 READ ? SEQUENTIAL ACCESS

READ filename
[NEXT] [RECORD]
[AT END??..]
[NOT AT END???]
[END-READ]
 For sequential access, the READ statement makes the next logical record available to the program. The NEXT RECORD accessed is determined by the file organization.
 When the READ statement is executed, the file already be open in INPUT or I-O mode
 If SELECT OPTIONAL was specified in FILE-CONTROL, and the file is absent, execution of the first READ cause an AT END condition.
 The ?AT END ?.? Clause must appear before the ?NOT AT END?? clause.
SEQUENTIAL PROCESSING SAMPLE
 ( Pseudocode )
 PERFORM UNTIL end-of file
READ next-record
AT END SET end-of-file TO TRUE
NOT AT END process-the-record
END-PERFORM.
 READ ? RANDOM  ACCESS
 READ  filename
[  RECORD  ]
[ INTO identifier  ]
[  KEY IS dataname  ]
[  INVALID KEY . . . ]
[  NOT  INVALID  K. . .]
[  END-READ  ]

FORMAT 2
Format 2 must be specified for random record retrieval.

  • For a VASAM  INDEXED file ,the KEY field contains a data value that will be matched against the key field in the records until the first record having an equal value is found.

  • For a VSAM RELATIVE file ,the KEY phrase must  not be specified.

  • When the READ statement is executed, the file must  already open in INPUT or I-O mode.

READ ? DYNAMIC ACCESS



READ filename
NEXT   [RECORD]
[INTO  identifier]
[AT END??..]
[NOT AT END???]
[END-READ]

READ filename
[RECORD]
[INTO  identifier]
[key is DATANAME]
[INVALID KEY?..]
[NOT INVALID KEY?..]
[END-READ]


For dynamic access, either sequential or random access is possible, depending upon the format of the READ statement.
  • Dynamic access is allowed only for VSAM indexed or VSAM relative organization. (Established by ACCESS IS DYNAMIC in FILE-CONTROL SECTION statement).
  • The NEXT phrase must be specified for sequential access with dynamic mode. In order to READ NEXT, ?position? must have been established in the file by a successful OPEN, START, or READ statement.

WRITE  STATEMENT


WRITE  record-name
[  FROM  identifier  ]
[  AFTER  ADVANCING  nnn  LINES   ]
[  AT  END-OF ?PAGE . . . ]
[  NOT AT END ?OF- PAGE . . .  ]
[  END- WRITE  ]
WRITE   record ? name
[   FROM  identifier   ]
[   BEFORE  ADVANCING   nnn   LINE [ S ]  ]
[   AT  END-OF-PAGE . . .  ]
[   NOT  AT  END-OF-PAGE   ]
[   END- WRITE   ]


FORMAT  (QSAM)
RECORD-NAME mist be defined via Data Division FD entry.
FROM option yields results identical to:
MOVE  identifier TO record-name
WRITE  record ?name
  • When the ADVANCING clause is omitted automatic line advancing is provided
Equivalent to:
WRITE  . . . . .AFTER  ADVANCING  1  LINE.
  • A further positioning operand is AFTER / BEFORE ADVANCING PAGE.
ACCEPT Statement
ACCEPT identifier
[FROM  mnemonic-name]
The ?mnemonic-name? must be associated with a device in the SPECIAL-NAMES paragraph.
When FROM phrase is omitted, SYSIN is the default.
The identifier may be a group or elementary item.

EXAMPLE

77   SEARCH-VALUE     PIC    X(10).
??????..
PROCEDURE DIVISION.
ACCEPT  SEARCH-VALUE  FROM  SYSIN.
???
ACCEPT Statement
ACCEPT       identifier    FROM   DATE
ACCEPT       identifier    FROM   DAY
ACCEPT       identifier    FROM   DAY-OF-WEEK
ACCEPT       identifier    FROM   TIME
DATE has implicit PICTURE  9(6)  (YYMMDD).
DAY has implicit PICTURE  9(5)  (YYDDD).
DAY-OF-WEEK has implicit PICTURE  9(1)  where the value ?1? represents Monday, ?2? implies Tuesday, etc.
  • TIME has implicit PICTURE  9(8)  (HHMMSSTH).
________________________________________________________________
01                TODAY.
02        THIS-YEAR               PIC      99.
02        THIS-MONTH           PIC      99.
02        THIS-DAY                 PIC      99.
01                CURRENT-DATE.
02        THIS-MONTH           PIC      Z9.
02        FILLER                      PIC      X   VALUE   ?/?.
02        THIS-DAY                 PIC      99.
02        FILLER                      PIC      X   VALUE   ?/?.
02        THIS-YEAR               PIC      99.
PROCEDURE DIVISION.
ACCEPT TODAY FROM DATE
MOVE CORR TODAY TO CURRENT-DATE
___________________________________________________________
DISPLAY STATEMENT
DISPLAY   identifier ?1  identifier ?2. . . .
[  UPON  mnemonic-name   ]
If  the identifier is numeric (but not external decimal), the contents are converted to an external format.
When the UPON phrase in omitted, the default device in SYSOUT.
Example

ENVIROMENT  DIVISION.
CONFIGURATION  SECTION.
SPECIAL-NAMES . SYSOUT  IS  SYSPRINT.. . . . .
PROCEDURE
DISPLAY  SRCH-ARG  ?  NOT  IN  TABLE. ?
DISPLAY  SRCH-ARG  SPACES  ?  NOT  IN  TABLE. ?

When a figurative constant is specified, only a single occurance is displayed.
3.5  Conditional Verbs & sequence control verbs
3.5.1  IF Statement

IF EMPNO  <  PREV-EMPNO
MOVE ?OUT OF  ORDER? TO MESSAGE-TXT
PERFORM  ERROR-MESSAGE
ADD 1 TO  INVALID-COUNTER
ELSE
MOVE  EMPNO  TO PREV-EMPNO
END-IF.

IF Statement
05        EMPL-STATUS        PIC    X.
88     SECRATARY            VALUE    ?S?.
88     APPRENTICE            VALUE   ?A?.
88     WORKER                   VALUE   ?W?.
88     MANAGER                VALUE   ?M?.
88     NONE-OF-ABOVE   VALUE   ?N?.
IF SECRETARY
PERFORM ADMIN-PROCESS
_________________________________________________________________
05        EMPL-STATUS        PIC    X.
88     SECRATARY            VALUE    ?S?.
88     APPRENTICE            VALUE   ?A?.
88     WORKER                   VALUE   ?W?.
88     MANAGER                VALUE   ?M?.
88     NONE-OF-ABOVE   VALUE    ?N?.
IF EMPL-STATUS  =  ?S?
PERFORM ADMIN-PROCESS
The two techniques for testing are equivalent.
3.5.2  CONTINUE  Statement
The  CONTINUE statement allows you to specify  ?no operation ? where an imperative statement is expected.
Example1 ? ?NEXT SENTENCE ?
IF  A = B
IF C = D
NEXT SENTENCE
ELSE
MOVE  ERR-MSG TO RPT-ERR-MSG
END-IF
ADD C TO TOTAL
IF E = F
MOVE MESSAGE-4 TO RPT-MESSAGE-2
END-IF
END-IF
Control comes here
Next instruction
Example 2 ? ?CONTINUE ?
IF  A = B
IF C = D
CONTINUE
ELSE
MOVE  ERR-MSG TO RPT-ERR-MSG
END-IF
Control comes here
ADD C TO TOTAL
IF E = F
MOVE ERR-MSG    TO RPT-ERR-MSG
END-IF
END-IF
Next instruction
3.5.3  EVALUATE Statement
The COBOL II EVALUATE statement provides a technique for coding similarly to the structured design CASE construct.
EVALUATE is an alternative to nested IF?s.
?WHEN? phrase can be written similar to a logic table.
The organization of the EVALUATE STATEMENT IS:
EVALUATE
Identifier
Literal
Expression
True
FALSE
WHEN
Condition
TRUE
FALSE
ANY
Literal
Identifier
Arithmetic expression
Operand(s) before the WHEN phrase is/are called selection subject(s)
Operand(s) within the WHEN phrase is/are called selection subject(s)
The must be the same number of selection subjects as selection objects.

PERFORM Statement
PERFORM  is a sequence control statement that causes the program to branch out to another procedure or a series of procedures and following the execution, it returns to the point it branched out from. The  procedure is treated as a sub-routine, and the PERFORM statement in the main routine provides a link to and from the sub-routines.
1.                  SIMPLE PERFORM
PERFORM PARA-1.
DISPLAY ?PARA-1 executed?
STOP RUN.
PARA-1.
Statement1
Statement2.
It executes all the instructions coded in PARA-1 and then transfers the control to the next instruction in sequence.

2.                  INLINE PERFORM.
When sets of statements are used only in one place then we can group all of them within PERFORM END-PERFORM structure. This is called INLINE PERFORM. This is equal to DO..END structure of other languages.
PERFORM
ADD A TO B
MULTIPLY B BY C
DISPLAY ?VALUE OF A+B*C? C
END-PERFORM
3.                  PERFORM PARA-1 THRU PARA-N.
All the paragraphs between PARA-1 and PARA-N are executed once.
4.                  PERFORM PARA-1 THRU PARA-N UNTIL conditions(s).
The identifiers used in the UNTIL condition(s) must be altered within the paragraph(s) being performed; otherwise the paragraphs will be performed indefinitely. If the condition in the UNTIL clause is met at first time of execution, then named paragraph(s) will not be executed at all.
5.                  PERFORM PARA-1 THRU PARA-N N TIMES.
N can be literal defined as numeric item in working storage or hard coded constant.
6.                  PERFORM PARA-1 THRU PARA-N VARYING identifier1
FROM identifier 2 BY identifier3 UNTIL condition(s)
Initialize identifier1 with identifier2 and test the conditions(s). If the condition is false execute the statements in PARA-1 thru PARA-N and increment identifiere1 BY identifier3 and check the condition(s) again. If the condition is again false, repeat this process till the condition is satisfied.
7.                  PERFORM PARA-1 WITH TEST BEFORE / AFTER UNTIL conditions
With TEST BEFORE condition is checked first if it is found to be false then PARA-1 will be executed and this is the default.
With TEST AFTER PARA-1 is executed once and then the condition is checked.

3.4  Input ? Output statement
OPEN Statement
OPEN  INPUT  filename ???
OPEN  OUTPUT  filename  ???
OPEN  I-O     filename???
OPEN  EXTEND    filename  ???

The phrase INPUT, OUTPUT, I-O, or EXTEND must appear at least once (but may be in any order).
Example
DATA DIVISION.
FILE SECTION.
FD       INVOICE
RECORD CONTAINS 80
RECORDING MODE F.
FD       PRINTOUT
RECORD CONTAINS 132.
PROCEDURE DIVISION.
OPEN INPUT         INVOICE
OPEN OUTPUT     PRINTOUT
CLOSE Statement



CLOSE filename1  ,
filename2??.

CLOSE   filename1
filename2

The CLOSE statement terminates the processing of files; a close may be executed only for file in open mode.
After CLOSE processing, the record area associated with the file is no longer available.
The CLOSE WITH LOCK phrase ensures that the file cannot be opened again during the execution.
The CLOSE WITH NO REWIND phrase exists to ensure that the volume is left in its current position.
Example
DATA DIVISION.
FILE SECTION.
FD       INVOICE
RECORD CONTAINS 80
RECORDING MODE F.
FD       PRINTOUT
RECORD CONTAINS 132.
RECORDING MODE F.
PROCEDURE DIVISION.
??????
??????..
CLOSE INVOICE  PRINTOUT

READ ? SEQUENTIAL ACCESS
READ filename
[NEXT] [RECORD]
[AT END??..]
[NOT AT END???]
[END-READ]
For sequential access, the READ statement makes the next logical record available to the program. The NEXT RECORD accessed is determined by the file organization.
When the READ statement is executed, the file already be open in INPUT or I-O mode
If SELECT OPTIONAL was specified in FILE-CONTROL, and the file is absent, execution of the first READ cause an AT END condition.
The ?AT END ?.? Clause must appear before the ?NOT AT END?? clause.
SEQUENTIAL PROCESSING SAMPLE
( Pseudocode )
PERFORM UNTIL end-of file
READ next-record
AT END SET end-of-file TO TRUE
NOT AT END process-the-record
END-PERFORM.
READ ? RANDOM  ACCESS
READ  filename
[  RECORD  ]
[ INTO identifier  ]
[  KEY IS dataname  ]
[  INVALID KEY . . . ]
[  NOT  INVALID  K. . .]
[  END-READ  ]

FORMAT 2
Format 2 must be specified for random record retrieval.

  • For a VASAM  INDEXED file ,the KEY field contains a data value that will be matched against the key field in the records until the first record having an equal value is found.
  • For a VSAM RELATIVE file ,the KEY phrase must  not be specified.
  • When the READ statement is executed, the file must  already open in INPUT or I-O mode.

READ ? DYNAMIC ACCESS



READ filename
NEXT   [RECORD]
[INTO  identifier]
[AT END??..]
[NOT AT END???]
[END-READ]

READ filename
[RECORD]
[INTO  identifier]
[key is DATANAME]
[INVALID KEY?..]
[NOT INVALID KEY?..]
[END-READ]


For dynamic access, either sequential or random access is possible, depending upon the format of the READ statement.

  • Dynamic access is allowed only for VSAM indexed or VSAM relative organization. (Established by ACCESS IS DYNAMIC in FILE-CONTROL SECTION statement).
  • The NEXT phrase must be specified for sequential access with dynamic mode. In order to READ NEXT, ?position? must have been established in the file by a successful OPEN, START, or READ statement.

WRITE  STATEMENT


WRITE  record-name
[  FROM  identifier  ]
[  AFTER  ADVANCING  nnn  LINES   ]
[  AT  END-OF ?PAGE . . . ]
[  NOT AT END ?OF- PAGE . . .  ]
[  END- WRITE  ]
WRITE   record ? name
[   FROM  identifier   ]
[   BEFORE  ADVANCING   nnn   LINE [ S ]  ]
[   AT  END-OF-PAGE . . .  ]
[   NOT  AT  END-OF-PAGE   ]
[   END- WRITE   ]


FORMAT  (QSAM)
RECORD-NAME mist be defined via Data Division FD entry.
FROM option yields results identical to:
MOVE  identifier TO record-name
WRITE  record ?name
  • When the ADVANCING clause is omitted automatic line advancing is provided
Equivalent to:

WRITE  . . . . .AFTER  ADVANCING  1  LINE.

  • A further positioning operand is AFTER / BEFORE ADVANCING PAGE.
ACCEPT Statement
ACCEPT identifier
[FROM  mnemonic-name]
The ?mnemonic-name? must be associated with a device in the SPECIAL-NAMES paragraph.
When FROM phrase is omitted, SYSIN is the default.
The identifier may be a group or elementary item.
EXAMPLE
77   SEARCH-VALUE     PIC    X(10).
??????..
PROCEDURE DIVISION.
ACCEPT  SEARCH-VALUE  FROM  SYSIN.
???
ACCEPT Statement
ACCEPT       identifier    FROM   DATE
ACCEPT       identifier    FROM   DAY
ACCEPT       identifier    FROM   DAY-OF-WEEK
ACCEPT       identifier    FROM   TIME
DATE has implicit PICTURE  9(6)  (YYMMDD).
DAY has implicit PICTURE  9(5)  (YYDDD).
DAY-OF-WEEK has implicit PICTURE  9(1)  where the value ?1? represents Monday, ?2? implies Tuesday, etc.
  • TIME has implicit PICTURE  9(8)  (HHMMSSTH).
________________________________________________________________

01                TODAY.
02        THIS-YEAR               PIC      99.
02        THIS-MONTH           PIC      99.
02        THIS-DAY                 PIC      99.
01                CURRENT-DATE.
02        THIS-MONTH           PIC      Z9.
02        FILLER                      PIC      X   VALUE   ?/?.
02        THIS-DAY                 PIC      99.
02        FILLER                      PIC      X   VALUE   ?/?.
02        THIS-YEAR               PIC      99.
PROCEDURE DIVISION.
ACCEPT TODAY FROM DATE
MOVE CORR TODAY TO CURRENT-DATE
___________________________________________________________
DISPLAY STATEMENT
DISPLAY   identifier ?1  identifier ?2. . . .
[  UPON  mnemonic-name   ]
If  the identifier is numeric (but not external decimal), the contents are converted to an external format.
When the UPON phrase in omitted, the default device in SYSOUT.
Example

ENVIROMENT  DIVISION.
CONFIGURATION  SECTION.
SPECIAL-NAMES . SYSOUT  IS  SYSPRINT.. . . . .
PROCEDURE
DISPLAY  SRCH-ARG  ?  NOT  IN  TABLE. ?
DISPLAY  SRCH-ARG  SPACES  ?  NOT  IN  TABLE. ?

When a figurative constant is specified, only a single occurance is displayed.

3.5  Conditional Verbs & sequence control verbs
3.5.1  IF Statement
IF EMPNO  <  PREV-EMPNO
MOVE ?OUT OF  ORDER? TO MESSAGE-TXT
PERFORM  ERROR-MESSAGE
ADD 1 TO  INVALID-COUNTER
ELSE
MOVE  EMPNO  TO PREV-EMPNO
END-IF.
IF Statement
05        EMPL-STATUS        PIC    X.
88     SECRATARY            VALUE    ?S?.
88     APPRENTICE            VALUE   ?A?.
88     WORKER                   VALUE   ?W?.
88     MANAGER                VALUE   ?M?.
88     NONE-OF-ABOVE   VALUE   ?N?.
IF SECRETARY
PERFORM ADMIN-PROCESS
________________________________________________________________
05        EMPL-STATUS        PIC    X.
88     SECRATARY            VALUE    ?S?.
88     APPRENTICE            VALUE   ?A?.
88     WORKER                   VALUE   ?W?.
88     MANAGER                VALUE   ?M?.
88     NONE-OF-ABOVE   VALUE    ?N?.
IF EMPL-STATUS  =  ?S?
PERFORM ADMIN-PROCESS
The two techniques for testing are equivalent.
3.5.2  CONTINUE  Statement
The  CONTINUE statement allows you to specify  ?no operation ? where an imperative statement is expected.
Example1 ? ?NEXT SENTENCE ?
IF  A = B
IF C = D
NEXT SENTENCE
ELSE
MOVE  ERR-MSG TO RPT-ERR-MSG
END-IF
ADD C TO TOTAL
IF E = F
MOVE MESSAGE-4 TO RPT-MESSAGE-2
END-IF
END-IF
Control comes here
Next instruction
Example 2 ? ?CONTINUE ?
IF  A = B
IF C = D
CONTINUE
ELSE
MOVE  ERR-MSG TO RPT-ERR-MSG
END-IF
Control comes here
ADD C TO TOTAL
IF E = F
MOVE ERR-MSG    TO RPT-ERR-MSG
END-IF
END-IF
Next instruction
3.5.3  EVALUATE Statement
The COBOL II EVALUATE statement provides a technique for coding similarly to the structured design CASE construct.
EVALUATE is an alternative to nested IF?s.
?WHEN? phrase can be written similar to a logic table.
The organization of the EVALUATE STATEMENT IS:
EVALUATE
Identifier
Literal
Expression
True
FALSE
WHEN
Condition
TRUE
FALSE
ANY
Literal
Identifier
Arithmetic expression
Operand(s) before the WHEN phrase is/are called selection subject(s)
Operand(s) within the WHEN phrase is/are called selection subject(s)
The must be the same number of selection subjects as selection objects.
EVALUATE Statement
Examples

EMPLOYEE-REC.
?????.
02        SHIFT                         PIC  X.
88        DAY               VALUE  ?D?.
88        NIGHT           VALUE  ?N?.
02        ??????
 PROCEDURE DIVISION.
?????????..
EVALUATE  TRUE
WHEN  DAY               PERFORM  DAY-PARA
WHEN  NIGHT           PERFORM  NIGHT-PARA
END-EVALUATE
 The above EVALUATE could also have been written in either ft the following ways:
 EVALUATE SHIFT
WHEN            ?D?      PERFORM     DAY-PARA
WHEN            ?N?      PERFORM     NIGHT-PARA
END-EVALUATE
EVALUATE  TRUE
WHEN  SHIFT           = ?D?       DAY-PARA
WHEN  SHIFT           =  ?T?       NIGHT-PARA
END-EVALUATE

3.6    Sorting and merging of files
SORTING
In order to update sequential files it is necessary to sort the records.  COBOL provides the SORT verb to accomplish this. In this operation, the file to be sorted is input to be sorted and  a new file is created in a different sequence. In addition to these 2 files a temporary file is also defined. A file may be sorted either in the ascending or the descending orders of a defined key field.
The format of the SORT statement is :

SORT file-name ON (ASCENDING) KEY data-name1, data-name2,....
(DESCENDING)
[ON (ASCENDING/DESCENDING) KEY data-name3,
data-name4]
USING file-name2          GIVING         file-name3.
file-name1  :  the sort file defined by an SD description in the DATA DIVISION
Format :  SD filename
file-name2  :  the file on which the unsorted input records are found
file-name3  :  the output file of sorted records
 Records may be sorted using either numeric or non-numeric key fields. Ascending sequence used with an alphabetic field will cause sorting from A - Z, and descending sequence will cause sorting from Z - A.
 The program below illustrates the SORT statement :
IDENTIFICATION DIVISION.
PROGRAM-ID.  PRNT-MKS.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT SORTFILE ASSIGN TO "SORTE.DAT".
SELECT STUDFILE ASSIGN TO "STUDENT.DAT".
SELECT TEMPFILE ASSIGN TO "TEMP.DAT".
DATA DIVISION.
FILE SECTION.
FD  STUDFILE
LABEL RECORDS ARE STANDARD.
01  STUDBUF.
05 STUD-NO                      PIC 9(4).
05 STUD-NAME    PIC A(20).
05 ADDRS              PIC X(30).
05 DATE-OF-BIRTH         PIC 9(6).
FD  TEMPFILE
LABEL RECORDS ARE STANDARD.
01  TEMPBUF.
05   T-STUD-NO                 PIC 9(4).
05   T-STUD-NAME                       PIC A(20).
05   T-ADDRS                                 PIC X(30).
05   T-DATE-OF-BIRTH                PIC 9(6).
SD  SORTFILE.
01  SORTBUF.
05   S-STUD-NO                 PIC 9(4).
05   S-STUD-NAME                       PIC A(20).
05   S-ADDRS                              PIC X(30).
05   S-DATE-OF-BIRTH    PIC 9(6).

WORKING-STORAGE SECTION.

01   EOF PIC X VALUE "N".
PROCEDURE DIVISION.
MAIN-PARA.
PERFORM SORT-PARA.
PERFORM INIT.
PERFORM PROG-EXEC UNTIL EOF = "Y".
PERFORM TERMIN.
GOBACK.
SORT-PARA.
SORT SORTFILE ON ASCENDING KEY S-STUD-NO
USING STUDFILE GIVING TEMPFILE.
INIT.
OPEN INPUT TEMPFILE.
PROG-EXEC.
READ TEMPFILE AT END MOVE "Y" TO EOF.
IF EOF = "N"
DISPLAY "STUDENT NUMBER : ", T-STUD-NO
DISPLAY "STUDENT NAME   : ", T-STUD-NAME
DISPLAY "ADDRESS        : ", T-ADDRS
DISPLAY "DATE OF BIRTH  : ", T-DATE-OF-BIRTH
STOP " ".
TERMIN.
CLOSE TEMPFILE.

The SORT-FILE is defined with an SD and has no LABEL RECORDS clause.
PROCESSING DATA BEFORE  AND/OR  AFTER SORTING
Consider the following SORT statement :
SORT  SORT-FILE
ON ASCENDING KEY TERR
USING IN-FILE GIVING SORTED-MSTR.
This statement performs the following operations :
1. Opens IN-FILE and SORTED-MSTR.
2. Moves IN-FILE records to the SORT-FILE.
3. Sorts SORT-FILE into ascending sequence by TERR, which is a field defined as part of the SD SORT-FILE record.
4. Moves the sorted SORT-FILE to the output file called SORTED-MSTR.
5. Closes IN-FILE and SORTED-MSTR after all records have been processed.
The SORT statement can however, be used in conjunction with procedures that process records before they are sorted and/or process records after they are sorted.
 INPUT PROCEDURE
Here, the SORT statement is used to perform processing of incoming records just before they are sorted. This is accomplished with an INPUT PROCEDURE clause in place of the USING clause. The format is :
 SORT file-name1
ASCENDING
ON                                             KEY  data-name1.....
DESCENDING
INPUT PROCEDURE IS procedure-name1  THRU  procedure name2

USING file-name2 ....                                         THROUGH
 The INPUT PROCEDURE  processes data from the incoming file prior to sorting.
An INPUT PROCEDURE may be used to perform the following operations prior to sorting :  (1) validate data in the input records, (2) eliminate records with blank fields, (3) remove unnecessary fields from the input records, and (4) count input records.
INPUT PROCEDURE CODING RULES

1.  The entire program should consist of SECTIONs. Each SECTION is followed by a paragraph-name. The INPUT PROCEDURE of the SORT refers to  SECTION-name followed by a paragraph-name.
E.g.
MAIN SECTION.
MAIN-PARA.
SORT WORK-FILE
INPUT PROCEDURE PRIOR-TO-SORT
GIVING SORTED-FILE.
GOBACK.
PRIOR-TO-SORT SECTION.
PRIOR-TO-SORT-MAIN-PARA.
 2. In the main paragraph of the section specified in the INPUT PROCEDURE :
a) OPEN the input file.
b) READ an initial record from the input file.
c) PERFORM a paragraph within the INPUT PROCEDURE section that will
process input records, release them to the sort file, and continue to read
records until there is no more data.
d) After all records have been processed CLOSE the input file.
e)  In order for the INPUT PROCEDURE  to be terminated, the last statement in
the last paragraph of the section must be executed. We must use a GO TO
for branching to the paragraph that contains this last statement.
E.g.
PRIOR-TO-SORT SECTION.
PRIOR-TO-SORT-MAIN-PARA.
OPEN INPUT IN-FILE.
READ IN-FILE AT END MOVE ?N? TO ANS.
PERFORM PROCESS-IN-RECS UNTIL ANS = ?Y?.
CLOSE IN-FILE.
GO TO END-OF-SECTION.
3. At the paragraph within the INPUT PROCEDURE section that processes input records prior to sorting:
a)  MOVE input data to the sort record.
b)  RELEASE each sort record, which writes the record to the sort file. This
RELEASE makes the record available for sorting. RELEASE ... FROM .... can
be used in place of a MOVE and RELEASE.
c)  Continue to read and process input until there is no more data.

E.g.
PROCESS-IN-RECS.
MOVE IN-REC TO SORT-REC.
RELEASE SORT-REC.
READ IN-FILE AT MOVE ?N? TO REPLY.
4. The paragraph located physically at the end of the INPUT PROCEDURE section must be the last one executed. Hence, a GO TO in the section?s main para  is required to transfer control to this last paragraph. If no processing is required, code an EXIT statement as the only entry in this last paragraph of the section.
E.g.
MAIN SECTION.
MAIN-PARA.
SORT WORK-FILE
INPUT PROCEDURE PRIOR-TO-SORT GIVING SORTED-FILE.
GOBACK.
PRIOR-TO-SORT SECTION.
PRIOR-TO-SORT-MAIN-PARA.
GO TO END-OF-SECTION.
PROCESS-INP-RECS.
:END-OF-SECTION.
EXIT.
A SORT routine that eliminates records with a quantity field = 0 before sorting.
The test for zero quantity will be performed in an INPUT PROCEDURE.
* SORT with INPUT PROCEDURE
IDENTIFICATION DIVISION.
PROGRAM-ID.  SORT-I.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT STUDFILE ASSIGN TO "STUDENT.DAT".
SELECT SORTFILE ASSIGN TO "SORTE.DAT".
SELECT TEMPFILE ASSIGN TO "TEMP.DAT".
DATA DIVISION.
FILE SECTION.
FD  STUDFILE
LABEL RECORDS ARE STANDARD.
01  STUDBUF.
05 STUD-NO                      PIC 9(4).
05 STUD-NAME    PIC A(20).
05 ADDRS              PIC X(30).
05 DATE-OF-BIRTH         PIC 9(6).
FD  TEMPFILE
LABEL RECORDS ARE STANDARD.
01  TEMPBUF.
05   T-STUD-NO     PIC 9(4).
05   T-STUD-NAME           PIC A(20).
05   T-ADDRS                     PIC X(30).
05   T-DATE-OF-BIRTH PIC 9(6).
SD  SORTFILE
01  SORTBUF.
05   S-STUD-NO     PIC 9(4).
05   S-STUD-NAME           PIC A(20).
05   S-ADDRS                  PIC X(30).
05   S-DATE-OF-BIRTH PIC 9(6).
WORKING-STORAGE SECTION.
01   EOF PIC X VALUE "N".
PROCEDURE DIVISION.
SORTING SECTION.
MAIN-PARA.
SORT SORTFILE ON ASCENDING KEY S-STUD-NO
INPUT PROCEDURE A-PARA THRU A-EXIT GIVING TEMPFILE.
GOBACK.
A-PARA SECTION.
PARA-1.
PERFORM OPEN-PARA.
PERFORM READ-PARA.
PERFORM CHECK-PARA UNTIL EOF = "Y".
GO TO CLOSE-PARA.
A-EXIT.
EXIT.
OPEN-PARA.
OPEN INPUT STUDFILE.
 READ-PARA.
READ STUDFILE AT END MOVE "Y" TO EOF.
IF EOF = "Y"
GO TO A-EXIT.
CHECK-PARA.
MOVE STUDBUF TO SORTBUF.
RELEASE SORTBUF.
PERFORM READ-PARA.
CLOSE-PARA.
CLOSE STUDFILE.

OUTPUT PROCEDURE
An OUTPUT PROCEDURE processes all sorted records in the sort file and handles the transfer of these records to the output file. While in an INPUT PROCEDURE we RELEASE records to a sort file rather than writing them, in an OUTPUT PROCEDURE, we RETURN records from the sort file rather than reading them. The format of the RETURN is as follows :
RETURN sort-file-name1
AT END  imperative-statement1.
 The format of the OUTPUT PROCEDURE is as below :
DESCENDING
SORT file-name1  ON                                        KEY   data-name1 .....
ASCENDING
THRU
OUTPUT PROCEDURE IS  procedure-name1                                 procedure-name1
THROUGH

OUTPUT PROCEDURE CODING RULES
1. The entire program should consist of sections. The OUTPUT PROCEDURE should refer to a section-name followed by a paragraph-name.
E.g.
MAIN SECTION.
MAIN-PARA.
SORT WORK-FILE USING IN-FILE
OUTPUT PROCEDURE AFTER-SORT.
GOBACK.
AFTER-SORT SECTION.
AFTER-SORT-MAIN-PARA.
2. In the main-para of the section specified in the OUTPUT PROCEDURE :
a)  OPEN the output file.
b)  RETURN an initial record from the sort file - the RETURN functions like a
READ.
c)  PERFORM a paragraph within the section that will process  records from
the sort file and continue to process them until there is no more data.
d)  After all records have been processed, CLOSE the output file.
e)  Code a GO TO, branching to the paragraph located physically at the end of
the section.
E.g.
AFTER-SORT SECTION.
AFTER-SORT-MAIN-PARA
OPEN OUTPUT SORTED-FILE.
RETURN WORK-FILE AT END MOVE ?N? TO REPLY.
PERFORM PROCESS-SORT-RECS UNTIL ANS = ?Y?.
CLOSE SORTED-FILE.
GO TO END-OF-SECTION.

3. At the paragraph that processes sort records after sorting :
a) Perform any operations on work or sort records.
b) Move the sort record to the output area.
c) WRITE each sorted record to the output file.
d) Continue to RETURN sort file records until there is no more data.
E.g.
PROCESS-SORT-RECS.
WRITE SORTED-REC FROM WORK-REC.
RETURN WORK-FILE AT END MOVE ?N? TO REPLY.

4. The paragraph located physically at the end of the OUTPUT PROCEDURE section must be the last one executed. Hence a GO TO in the section?s main-para is required to transfer control to this last paragraph. If no processing is required, code an EXIT statement as the only entry in this last paragraph.
E.g.
MAIN SECTION.
MAIN-PARA.
SORT WORK-FILE USING IN-FILE
OUTPUT PROCEDURE AFTER-SORT.
GOBACK.
AFTER-SORT SECTION.
AFTER-SORT-MAIN-PARA.
:
GO TO END-OF-SECTION.
PROCESS-SORT-RECS.
:
END-OF-SECTION.
EXIT.


Sample program illustrating output procedure
* SORT WITH OUTPUT PROCEDURE
IDENTIFICATION DIVISION.
PROGRAM-ID.  SORT-O.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT STUDFILE ASSIGN TO "STUDENT.DAT".
SELECT SORTFILE ASSIGN TO "SORTE.DAT".
SELECT TEMPFILE ASSIGN TO "TEMP.DAT".
DATA DIVISION.
FILE SECTION.
FD  STUDFILE
LABEL RECORDS ARE STANDARD.
01  STUDBUF.
05 STUD-NO                      PIC 9(4).
05 STUD-NAME    PIC A(20).
05 ADDRS              PIC X(30).
05 DATE-OF-BIRTH         PIC 9(6).
FD  TEMPFILE
LABEL RECORDS ARE STANDARD.
01  TEMPBUF.
05   T-STUD-NO     PIC 9(4).
05   T-STUD-NAME           PIC A(20).
05   T-ADDRS                     PIC X(30).
05   T-DATE-OF-BIRTH PIC 9(6).
SD  SORTFILE.
01  SORTBUF.
05   S-STUD-NO     PIC 9(4).
05   S-STUD-NAME           PIC A(20).
05   S-ADDRS                     PIC X(30).
05   S-DATE-OF-BIRTH PIC 9(6).
WORKING-STORAGE SECTION.
01   EOF              PIC X VALUE "N".
PROCEDURE DIVISION.
SORTING SECTION.
MAIN-PARA.
SORT SORTFILE ON ASCENDING KEY S-STUD-NO
USING STUDFILE
OUTPUT PROCEDURE A-PARA THRU A-EXIT.
GOBACK.
A-PARA SECTION.
PARA-1.
PERFORM OPEN-PARA.
PERFORM READ-PARA .
PERFORM CHECK-PARA UNTIL EOF = "Y".
GO TO CLOSE-PARA.
A-EXIT.
EXIT.
OPEN-PARA.
OPEN OUTPUT TEMPFILE.
READ-PARA.
RETURN SORTFILE AT END MOVE "Y" TO EOF.
CHECK-PARA.
WRITE TEMPBUF FROM SORTBUF.
PERFORM READ-PARA.
CLOSE-PARA.
CLOSE TEMPFILE.
When  to use INPUT and/or OUTPUT PROCEDURES
If there are many records that need to be eliminated, it is more efficient to remove them before sorting. In this way, we do not waste computer time numerous records that will later be removed from the sorted file. Thus, in the case where a large number  of records will be removed, an INPUT PROCEDURE should be used.
However, in order to eliminate records with blank fields, it is efficient to remove those records after sorting. After sorting, all blank field records will be at the beginning of the file. (A blank is the lowest printable character in a collating sequence and will appear first in a sorted file.) Here, the OUTPUT PROCEDURE should be used.
MERGING
COBOL has a MERGE statement that will combine two or more files into a single file. It?s format is similar to that of SORT.
MERGE file-name1
{ON ASCENDING KEY (data-name1,....)
DESCENDING KEY }
USING file-name2, file-name3,...
GIVING file-name4
The files to be merged must each be in sequence by the key field, and the records in the file to be merged must be of equal length. An output file is created containing all records from the input file in the correct sequence.
File-name1     :  the work-file specified as an SD
data-name?n?  :  the key-field
The MERGE statement automatically handles the opening, closing and READ/WRITE functions associated with files. However, for the MERGE operation to take place, the input files must be in the sorted order.
The program below illustrates the MERGE statement :
IDENTIFICATION DIVISION.
PROGRAM-ID. MERG-PRG.
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT FILE1 ASSIGN TO "FILE1.DAT".
SELECT FILE2 ASSIGN TO "FILE2.DAT".
SELECT MERGE-FILE ASSIGN  TO "MERGE.DAT".
SELECT OUTPUT-FILE ASSIGN TO "OUT.DAT".
DATA DIVISION.
FILE SECTION.
FD  FILE1
LABEL RECORDS ARE STANDARD.
01  FILE1-REC.
02 F-ITEM-NO            PIC 9(3).
02 F-AMT                    PIC 9(4)V99.
FD  FILE2
LABEL RECORDS ARE STANDARD.
01  FILE2-REC.
02  G-ITEM-NO      PIC 9(3).
02  G-AMT                          PIC 9(4)V99.
SD  MERGE-FILE.
01  MERGE-REC.
02  ITEM-NO                      PIC 9(3).
02  AMT                              PIC 9(4)V99.
FD  OUTPUT-FILE
LABEL RECORDS ARE STANDARD.
01  OUT-REC.
02  O-ITEM-NO      PIC 9(3).
02  O-AMT              PIC 9(4)V99.
WORKING-STORAGE SECTION.
77   EOF                          PIC X VALUE "N".
77   CHOICE                   PIC X VALUE "Y".
PROCEDURE DIVISION.
MAIN-PARA.
PERFORM OPEN-PARA.
PERFORM ACCEPT-APARA UNTIL CHOICE = "N".
CLOSE FILE1.
MOVE "Y" TO CHOICE.
PERFORM ACCEPT-BPARA UNTIL CHOICE = "N".
CLOSE FILE2.
PERFORM MERG-PARA.
GOBACK.

OPEN-PARA.
OPEN OUTPUT FILE1.
OPEN OUTPUT FILE2.
ACCEPT-APARA.
DISPLAY "F-ITEM-NO".
ACCEPT F-ITEM-NO.
DISPLAY "F-AMT".
ACCEPT F-AMT.
WRITE FILE1-REC.
DISPLAY "CONTINUE Y/N".
ACCEPT CHOICE.
ACCEPT-BPARA.
DISPLAY "G-ITEM-NO".
ACCEPT G-ITEM-NO.
DISPLAY "G-AMT".
ACCEPT G-AMT.
WRITE FILE2-REC.
DISPLAY "CONTINUE Y/N".
ACCEPT CHOICE.
MERG-PARA.
MERGE MERGE-FILE ON ASCENDING KEY ITEM-NO
USING FILE1, FILE2 GIVING OUTPUT-FILE.

3.7  Character handling
3.7.1  Inspect Tallying Statement
The INSPECT statement provides the capability to count (tally) or replace specific characters in a data-item.
INSPECT  identifier-1 TALLYING  identifier-2
FOR CHARACTERS BEFORE
[INITIAL]  identifier-4
INSPECT  identifier-1 TALLYING  identifier-2
FOR CHARACTERS AFTER
[INITIAL]  identifier-4
INSPECT  identifier-1 TALLYING  identifier-2
FOR  ALL identifier-3  |  literal
AFTER  [INITIAL]  identifier-4
INSPECT  identifier-1 TALLYING  identifier-2
FOR  LEADING   identifier-3  |  literal
AFTER  [INITIAL]  identifier-4
The inspected item must have USAGE DISPLAY (either elementary or group item).
?identifier-2? must be an elementary numeric item.

Inspection begins at the leftmost character of the inspected item and proceeds byte-by-byte to the rightmost position (except when BEFORE or AFTER used).
3.7.2  Inspect Replacing Statement
The INSPECT statement also provides the capability to replace specific characters in a data-item (must have USAGE DISPLAY).


INSPECT identifier-1 REPLACING
CHARACTERS BY  identifier-5
[BEFORE  |  AFTER   [INITIAL]  identifier-4]

INSPECT  identifier-1 REPLACING
ALL  |  LEADING   |   FIRST
Identifier-3   BY identifier-5    |   literal
[BEFORE  |  AFTER   [INITIAL]  identifier-4]

When REPLACING CHARACTERS is used, the identifier-5 (or literal) must be one character in length.

EXAMPLES
______________________________________________________
INSPECT        DATA1           REPLACING             ALL    ? ?  BY  ?0?
INSPECT        DATA2           REPLACING FIRST ZERO  BY  SPACES
INSPECT        DATA3           REPLACING             CHARACTERS  BY  ?X?
___________________________________________________________
3.7.3  Inspect Replacing/Converting
The COBOL II INSPECT verb formats REPLACING / CONVERTING operate differently:
INSPECT   FIELD1   CONVERTING  ?ABC?  TO  ?XYZ?
Changes ?ABC1234AAA?  TO  ?XYZ1234XXX?
INSPECT   FIELD1   REPLACING  ?ABC?  TO  ?XYZ?
Changes ?ABC1234AAA?  TO  ?XYZ1234AAA?
This syntax changes only instances of the complete character string.
3.7.4  String Example
The following example takes a 10-digit string of numbers and ?formats? it into the image of a telephone number, e.g.
0806675432   becomes  (080) 667-5432
WORKING-STORAGE SECTION.
TELNUMBER.
04        AREACODE  PIC  9(3).
04        LOCAL-NO   PIC  9(7).
77        FORMATTED-TELNUMBER          PIC  X(20).
PROCEDURE DIVISION.
????????
STRING
?(?   DELIMITED BY SIZE
AREACODE DELIMITED BY SIZE
?)?   DELIMITED BY SIZE
LOCAL-NO(1:3)  DELIMITED BY SIZE
?_?    DELIMITED BY SIZE
LOCAL-NO(4:4)  DELIMITED BY SIZE
INTO FORMATTED-TELNUMBER
END-STRING
DISPLAY FORMATTED-TELNUMBER
????
3.7.5  Unstring Statement
UNSTRING   identifier-1
[DELIMETED BY  [ALL]  identifier-2 ]
INTO identifier-4 ????..
[ON OVERFLOW??.]
[NOT  ON OVERFLOW???.]
END-UNSTRING

The UNSTRING statement is used to split a single data-item into several data-items.

EXAMPLE
To present an address like this:
ALIT
14 CHURCH ST
.
BANGALORE, INDIA 560001
01        ADDRESS1   PIC   X(84)  VALUE
?ALIT:
14 CHURCH ST.
:BANGALORE,INDIA 560001:?.
ADDRESS2.
05        LINE1 PIC   X(80).
05        LINE2 PIC   X(80).
05        LINE3 PIC   X(80).
UNSTRING ADDRESS1   DELIMITED  BY  ?;:  OR  ?\?
INTO LINE1 LINE2   LINE3
END-UNSTRING
3.8  COBOL subroutines
3.8.1  Linkage Section
Example
(Examples of definitions in CALLING program and CALLED program)
3.8.2  Calling Program

DATA DIVISION.

WORKING-STORAGE SECTION.
EMP-DET.
05    EMPNO               PIC   9(6).
05    EMPNAME         PIC   X(15)
05    DEPT                   PIC  9(5)
????..
?????
PROCEDURE DIVISION.
????.
????.
CALL CALLED-PGM  USING EMP-DET.             ????.
????.
3.8.3  Called Program

????.
????.
????.
????.
LINKAGE SECTION.
EMP-INFO.
05    EMPNUM           PIC   9(6).
05    EMPNAME         PIC   X(15)
05    DEPTNO             PIC  9(5)
 PROCEDURE DIVISION USING EMP-INFO.
????.
????.

No comments:

Post a Comment