Vous êtes sur la page 1sur 13

Structured programming

- The

main objectives of structured programming are:


to increase the accuracy of the programs, for better readability and understandability of the programs, to modify a portion of the program without upsetting the functions of other programs.

-The

principles of structured programming are:


For the structuring of control flow:
It helps in reducing the complexity of the program, thereby ensures that the program logic is more easier and understandable. The basic control structures are: 1. SEQUENCE : A sequence of two or more operations. 2. IFTHENELSE : Execution of one or two operations depending on a condition. 3. DOWHILE : the repetitive execution of an operation as long as a condition is true.

Modular Programming:
It is a strategy in which a program is divided into a number of 'partitions' or 'modules'. A module can further be divided into subordinate modules (called module) within itself, also, a number of modules can be combined together forming a superior module (calling module).

Top-down Approach:
In the top-down approach, the calling module is always designed before the called module. The functions are successfully refined and this process of refinement continues until the lowest modules can be designed without further analysis.

- SUBROUTINES:
A module can also be coded in the form of a subroutine, which is a cobol program having all the four sections but cannot be executed independently. A subroutine may be 'called' in the calling modules by means of a CALL statement. By using subroutines we can alter size of the program and re-use the same data items in 2 or more programs. * STRUCTURE OF A SUBROUTINE The subprogram must have a 'USING' phrase in the procedure division header which distinguishes a subprogram from a main program. Syntax: PROCEDURE DIVISION USING data-name1, data-name2, The operands data-name1, data-name2, etc. in USING phrase of the subroutine are connected to the corresponding data names of the main program or the calling program. The operands of the USING phrase must be defined in the LINKAGE-SECTION under DATA DIVISION at 01-level or 77-level. Syntax: LINKAGE SECTION. 01 data-name1 PIC 99. 01 data-name2 PIC XX. Another distinguishing feature of the subprogram is, it does not have STOP-RUN which marks the end of the program. EXIT PROGRAM statement can be used for this purpose. Syntax: EXIT PROGRAM

* CALLING OF A SUBROUTINE In-order to call a subprogram from a main program or another subprogram, a name must be given to it. The PROGRAM-ID entry in the subprogram is used for this. Syntax: PROGRAM-ID. SUBPGM. The subprogram is invoked in the main program using a 'CALL' statement. It transfers the control to the first statement in the PROCEDURE DIVISION of the called subroutine. The EXIT PROGRAM statement in the subroutine transfers back the control to the main program. Syntax: CALL 'SUBPGM' USING DATA-NAME1, DATA-NAME2. A program can call another program which in turn calls another program and so on. But it cannot call itself or its calling program nor any program that is a calling program.

* ACTUAL AND FORMAL PARAMETERS Data-name1, data-name2 are the data names that connect the main program and the subprogram. These operands in the CALL statement of the main program are called actual parameters. The operands in the USING phrase of the PROCEDURE DIVISION of the called program are called formal parameters. The number of actual parameters must be same as the number of formal parameters and size, class and the usage of the corresponding actual and formal parameters must be identical. Syntax: PROCEDURE DIVISION of a subroutine having name SUBPGM. PROCEDURE DIVISION USING DATA-NAME1, DATA-NAME2. The subroutine can be called in the calling program as shown below, CALL 'SUBPGM' USING DATA-NAME1, DATA-NAME2. In the above example the actual and the formal parameters are correspondingly linked. The process of establishing connection between the called and the calling program is called parameter passing. EXAMPLE: Subprogram: IDENTIFICATION DIVISION. PROGRAM-ID. SUBPROG. DATA DIVISION. LINKAGE SECTION. 01 L-GRS PIC 9(05). 01 L-NET PIC 9(05). 01 L-BASIC PIC 9(04). 01 L-DED PIC 9(04). 01 L-ALW PIC 9(04). PROCEDURE DIVISION USING L-BASIC L-ALW L-DED L-GRS L-NET. 0000-MAIN-PARA. COMPUTE L-GRS = L-BASIC + L-ALW. COMPUTE L-NET = L-GRS - L-DED. EXIT PROGRAM. Main program: IDENTIFICATION DIVISION. PROGRAM-ID. MAINPG. DATA DIVISION. WORKING-STORAGE SECTION. 01 WORK-AREA. 03 W-GROSS PIC 9(05). 03 W-NET PIC 9(05). 03 W-BASIC PIC 9(04). 03 W-ALW PIC 9(04). 03 W-DED PIC 9(04). PROCEDURE DIVISION. 0000-MAINLINE. PERFORM 1000-CALL-PARA. STOP RUN. 1000-CALL-PARA. * ACCEPT W-BASIC. * ACCEPT W-ALW. * ACCEPT W-DED. MOVE 9000 TO W-BASIC. MOVE 1000 TO W-ALW. MOVE 2000 TO W-DED. CALL "SUBDAT" USING W-BASIC W-ALW W-DED W-GROSS W-NET. DISPLAY " THE GROSS IS " W-GROSS. DISPLAY " THE NET IS " W-NET.

Only call by reference is implemented in cobol and not call by value. There are two types of CALL's in cobol, Static call and the Dynamic call. 1. STATIC CALL: In a static call the main program and the subprogram are bound during the compilation. NO-DYNAM is used for a static call. 2. DYNAMIC CALL: In case of dynamic call the main program and the subprograms are bound during the run time. DYNAM is used for a dynamic call. *PERFORMANCE OF STATIC AND DYNAMIC CALL: The performance of static call is better because dynamic call encounters overheads problem. The size of the load module increases during the static call. Whenever any changes are made in the subprogram or the main program both of them should be compiled in case of a static call. Whereas for a dynamic call, only the changed program needs to be compiled.

Sequential Files
* FILE CONTROL FOR SEQUENTIAL FILES FILE-CONTROL. SELECT EMP-RD-FILE ASSIGN TO OUTFILE ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS W-STATUS. The characteristics of the files handled are placed here. File control paragraph is coded in the input-output section of the environment division. SELECT clause identifies a file in the cobol program to be associated with an external data set. In the above example, EMP-RD-FILE is the logical file and OUTFILE is the physical file. ASSIGN clause associates the name of a file in a program with the actual external name of the data file. SELECT and ASSIGN verbs map the logical files with the physical files. ORGANIZATION clause identifies the logical structure of the file. The logical structure is established at the time of file creation and cannot be changed. If ORGANIZATION clause is omitted, the compiler assumes ORGANIZATION IS SEQUENTIAL. ACCESS MODE clause defines the manner in which the records of the file are made available for processing. The default ACCESS MODE is SEQUENTIAL. FILE STATUS clause monitors the execution of each input-output operation for the file. The value indicates the status of execution of the statement. Its size is always 2. Some of the file status codes are mentioned below: FILE STATUS CODE 00 10 30 34 22 23 MEANING Successful operation At end condition Permanent error condition Boundary violation Duplicate key Record not found

*FILE DESCRIPTION FD EMP-RD-FILE RECORD CONTAINS 80 CHARACTERS BLOCK CONTAINS 0 RECORDS RECORDING MODE IS F. FD is abbreviated from file description. RECORD CONTAINS clause specifies the length of the logical records. In the above example the record length is 80 characters. BLOCK CONTAINS clause specifies the size of the buffer to be set up for the file. However, this clause is optional. RECORDING MODE clause specifies whether the records have fixed-length or variable-length. Fixed length records are represented by F and variable length records are represented by V.

*For handling sequential files 3 steps must be followed they are

OPEN A FILE
The OPEN statement initiates the processing of files. The successful execution of OPEN statement marks the availability of the file for processing. The FILE STATUS clause in the FILE-CONTROL entry is updated when the OPEN statement is executed successfully. A Sequential file can be opened in any of the following 4 modes: 1. INPUT MODE A file can be opened in INPUT mode only if it exists. Such a file becomes input file from which records can be read sequentially. 2. OUTPUT MODE When a file is to be created for the first time, it must be opened in the OUTPUT mode. File can be only written in this mode. Opening an already existing file in OUTPUT mode results in loss of existing data. 3. EXTEND MODE EXTEND mode opens a file for writing, the file pointer is positioned after the end of the last record. Thus any records written will get appended to the file.

4. I-O MODE Whenever the file is needed to be updated, it is opened in I-O mode. This mode provides both reading and re-writing of records.

PERFORM PROCESS

After opening the file in required mode, process needs to be performed. Process may be reading, writing, updating or deleting the records. The above operations can be performed using READ, WRITE and RE-WRITE statements 1. READ statement If a file is opened in the INPUT or the I-O mode, the READ statements fetches records from a file. The READ statement can be used with an AT END and NOT AT END clause. The AT END determines what action is to be done when the file reaches the end. The NOT AT END can be used to accomplish specific tasks before AT END has been reached. Format: READ file-name INTO data-name [ AT END imperative statements] [NOT AT END imperative statements] [END-READ] 2. WRITE statement If a file is opened in the OUTPUT or the EXTEND mode, then we can use the WRITE statement to send the data to the physical file. Once a record has been written to a file, it is no longer available in the record buffer. The WRITE statement can be used with FROM option for writing data directly from a WORKING-STORAGE variable to the required file. Format: WRITE record-name [FROM identifier] 3. RE-WRITE statement If a file is opened in the I-O mode and a record has been read successfully into the record buffer, then we can use the REWRITE statement to update an existing record. Similar to the WRITE statement, the REWRITE statement can be used with FROM option for writing data directly from a WORING-STORAGE variable to the required file, Format: REWRITE record-name [FROM identifier]

CLOSE A FILE
This statement terminates the processing of a file. The CLOSE statement marks the termination of link between the physical and the logical file.

EXAMPLE: The below program explains how the records from an input file are written into an output file. All the statements that were explained above are used in this example. IDENTIFICATION DIVISION. PROGRAM-ID. RDWRPG. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT EMP-RD-FILE ASSIGN TO OUTFILE ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS W-STATUS. SELECT EMP-WR-FILE ASSIGN TO INFILE ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS W-STATUS. DATA DIVISION. FILE SECTION. FD EMP-RD-FILE RECORD CONTAINS 80 CHARACTERS BLOCK CONTAINS 0 RECORDS RECORDING MODE IS F. 01 R-EMP-REC. 03 R-EMP-ID PIC 9(05). 03 R-EMP-NAME PIC X(20). 03 R-EMP-SAL PIC 9(05). 03 FILLER PIC X(50).

FD EMP-WR-FILE RECORD CONTAINS 80 CHARACTERS BLOCK CONTAINS 0 RECORDS RECORDING MODE IS F. 01 W-EMP-REC. 03 W-EMP-ID PIC 9(05). 03 W-EMP-NAME PIC X(20). 03 W-EMP-SAL PIC 9(05). 03 FILLER PIC X(50). WORKING-STORAGE SECTION. 01 WORK-AREA. 03 W-STATUS PIC X(02). 03 W-EMP-INFO. 05 A-EMP-ID PIC 9(05). 05 A-EMP-NAME PIC X(20). 05 A-EMP-SAL PIC 9(05). 03 W-EOF PIC X VALUE 'Y'. PROCEDURE DIVISION. 0000-MAINLINE. PERFORM 1000-INIT-PARA. PERFORM 2000-READ-PARA UNTIL W-EOF = 'N'. * PERFORM 3000-WRITE-PARA. PERFORM 4000-CLOSE-PARA. STOP RUN. 1000-INIT-PARA. OPEN INPUT EMP-RD-FILE OUTPUT EMP-WR-FILE. EVALUATE TRUE WHEN W-STATUS = 00 CONTINUE WHEN OTHER PERFORM 9999-ERR-PARA END-EVALUATE. 2000-READ-PARA. READ EMP-RD-FILE AT END MOVE 'N' TO W-EOF NOT AT END EVALUATE TRUE WHEN W-STATUS = 00 PERFORM 2100-MOVE-DATA WHEN W-STATUS = 10 PERFORM 4000-CLOSE-PARA WHEN OTHER PERFORM 9999-ERR-PARA END-EVALUATE END-READ. 2100-MOVE-DATA. MOVE R-EMP-ID TO W-EMP-ID. MOVE R-EMP-NAME TO W-EMP-NAME. MOVE R-EMP-SAL TO W-EMP-SAL. WRITE W-EMP-REC. 4000-CLOSE-PARA. CLOSE EMP-RD-FILE EMP-WR-FILE. EVALUATE TRUE WHEN W-STATUS = 00 CONTINUE WHEN OTHER PERFORM 9999-ERR-PARA END-EVALUATE. 9999-ERR-PARA. DISPLAY " THE ERROR IS : " W-STATUS. STOP RUN.

CHARACTER HANDLING
This topic deals with string-handling verbs such as EXAMINE, INSPECT, STRING and UNSTRING. EXAMINE VERB The EXAMINE statement replaces or counts the number of occurrences of a given character in a data item. SYNTAX: 1. EXAMINE identifier TALLYING {ALL } {LEADING} literal-1 {UNTIL FIRST} {ALL } {LEADING} literal-1 BY literal-2 {UNTIL FIRST}

2. EXAMINE identifier REPLACING

When the EXAMINE statement is executed, it acts differently depending upon whether identifier names a numeric or a nonnumeric data item. If identifier is a nonnumeric data item, examination begins with the leftmost character, and proceeds to the right. Each character is examined in turn. If identifier is a numeric data item, the data item may contain a sign, and examination proceeds on a digit by digit basis. This examination starts with the leftmost digit and proceeds to the right. If a sign is included in the data item being examined, it is ignored regardless of its physical location. TALLYING Phrase When the TALLYING phrase is used in an EXAMINE statement, a count is placed in the special HP COBOL II register named TALLY. This count is an integer and represents a value that is dependent upon the keywords following the word TALLYING If TALLYING UNTIL FIRST is specified, the integer in the TALLY register after execution of an EXAMINE statement is the number of occurrences of characters in identifier before the first occurrence of literal-1. If TALLYING ALL is specified, every occurrence of literal-1 is counted and the result of this counting is placed in the TALLY register. If TALLYING LEADING is specified, only those occurrences of literal-1 that precede any other characters in the data item named by identifier are counted. For example, if the first character of identifier is not literal-1, the EXAMINE statement ceases execution immediately. If the REPLACING phrase is used in conjunction with the TALLYING phrase, then, depending upon which keywords are used with the TALLYING phrase, those occurrences of literal-1 that participate in the tallying are replaced by literal-2. For example, if the EXAMINE statement: SYNTAX: EXAMINE ABMASK TALLYING ALL A REPLACING BY B. RESULT : BBMBSK REPLACING Phrase The REPLACING phrase acts in the same manner as the REPLACING verb in the TALLYING phrase. However, since no tallying takes place, the TALLY register remains unchanged. The rules of the REPLACING phrase are stated below: * If REPLACING ALL is specified, all occurrences of literal-3 in identifier are replaced by literal-4. * If REPLACING LEADING is specified, each occurrence of literal-3 is replaced by literal-4 until the first occurrence of a character other than literal-3 or the rightmost character of the data item is examined. * If REPLACING UNTIL FIRST is specified, every character of the data item represented by identifier is replaced by literal-4 until literal-3 is encountered in the data item. If literal-3 does not appear in the data item, the entire data item is filled with literal-4. * If REPLACING FIRST is specified, only the first occurrence of literal-3 is replaced by literal-4. If literal-3 does not appear in the data item represented by identifier, the data item is unchanged after execution of the EXAMINE statement. SYNTAX: EXAMINE EXAMINATION REPLACING FIRST I BY P RESULT: EXAMPNATION

INSPECT VERB INSPECT verb allows to count and replace a character or a group of characters. Like EXAMINE, INSPECT is used with TALLYING and REPLACING. *INSPECT with TALLYING option This counts/tally a character or a group of characters in source string. Examples: Source string: AABAbbACABA 1. INSPECT source-string TALLYING tally-counter FOR CHARACTERS BEFORE INITIAL C In the above example tally counter will have count of all characters before first occurrence of C in source -string. Tally-counter will be 7. AABAbbACABA 2. INSPECT source-string TALLYING tally-counter FOR ALL A In this example tally counter will have count of all occurences of A in source-string. Tally-counter will be 6. AABAbbACABA 3. INSPECT source-string TALLYING tally-counter FOR ALL A AFTER INITIAL B In this example tally counter will have no count of all occurences of A after first occurrence of B. Tally-counter will be 4. AABAbbACABA 4. INSPECT source-string TALLYING tally-counter FOR LEADING A In this example tally counter will have count of leading As. Tally-counter will be 2. AABAbbACABA 5. Source-string = SET If we need to get a string without any spaces, we can use following logic INSPECT FUNCTION REVERSE (source-string) TALLYING space-count FOR LEADING SPACES. COMPUTE length-of-string = 6 space-count. Move source-string(space-count+1 :length-of-string) to ws-target-string. Above INSPECT command gets the no.of leading spaces from the string. After executing the INSPECT command spacecount variable contains 2. In compute statement, space count is subtracted from the length of the source string. Value 4 will be stored in length-ofstring. Move statement using reference modification is moved into the working storage variable removing spaces. *INSPECT with REPLACING option This form replaces a character or a group of characters EXAMPLE 1. INSPECT source-string REPLACING CHARACTERS BY # BEFORE INITIAL C. All characters before first occurrence of C in source-string are replaced by #. Input : AABAbbACABA Output : #######CABA. 2. INSPECT source-string REPLACING ALL A BY # All As in source-string are replaced by #. Input : AABAbbACABA Output : ##B#bb#C#B# *INSPECT with TALLYING and REPLACING options This form counts/tallys a character or group of characters and replaces a character or group of characters. EXAMPLE: INSPECT source-string TALLYING tally-counter FOR ALL A AFTER INITIAL B REPLACING ALL A BY # AFTER INITIAL B All occurences of A after first B in source-string are counted and replaced by #. Tally-counter : 3 Source-string: AAB#bb#C#B.

STRING VERB
The STRING verb concatenates the partial or complete contents of two or more strings or literals into one single data item. Example: 01 ws-data-1 pic x(10) value this is. 01 ws-data-2 pic x(20) value first string. STRING ws-data-1 DELIMITED BY SIZE. ws-data-2 DELIMITED BY SPACES EXAMPLE. DELIMITED BY SIZE INTO ws-destination Result: ws-destination will contain this is first example Since the first string is delimited by size whole string is moved to ws-destination . The second string is delimited by space so, characters upto first space is moved into the ws-destination. And complete literal EXAMPLE will be moved. Syntax: STRING source-string1[DELIMITED BY [delimiter,literal,SIZE,SPACE..]] [source-string2[DELIMITED BY[delimiter,literal,SIZE,SPACE..]].. INTO destination-string [WITH POINTER pointer-integer] [ON OVERFFLOW statements block] [NOT ON OVERFLOW statements block] [END-STRING]

UNSTRING VERB

The UNSTRING verb is used to divide a string into sub-strings. The UNSTRING copies characters from the source string to the destination strings until a delimiter is encountered that determines data transfer. Example: UNSTRING userid@company.com DELIMITED BY @ OR . INTO ws-user-id ws-company ws-domain END-UNSTRING. In this example unstrings the literal userid@company.com into different strings ws-user-id, ws-company, ws-domain based on delimiters @ and .. The characters will be moved to the corresponding strings based on the delimiters. SYNTAX: UNSTRING source-string1[DELIMITED BY [ALL] delimiter1[OR[ALL]]delimiter2..]] INTO destination-string1[DELIMITER IN hold-delimiter1][COUNT IN char-counter1] destination-string2[DELIMITER IN hold-delimiter2][COUNT IN char-counter2] [WITH POINTER pointer-integer] [TALLYING IN pointer-integer] [ON OVERFFLOW statements block] [NOT ON OVERFLOW statements block] [END-UNSTRING]

INITIALIZE VERB

INITIALIZE verb initializes values in a data item to default value. Numeric data items are initialized with ZEROS. Alpha numeric characters are initialized with spaces. It does not initialize FILLER. EXAMPLE: 01 EMPLOYEE-RECORD. 03 EMPLOYEE-NAME. 05 FIRST-NAME 05 MIDDLE-NAME 05 LAST-NAME 03 EMPLOYEE-DOJ. 05 MONTH 05 FILLER 05 DAY 05 FILLER 05 YEAR

PIC X(10). PIC X(10). PIC X(10). PIC PIC PIC PIC PIC 99. X VALUE /. 99. X VALUE /. 99.

INITIALIZE EMPLOYEE-RECORD. The above statement will initialize all values to the default values. The FIRST-NAME, MIDDLE-NAME and LAST-NAME will be initialized with SPACES. The MONTH, DAY and YEAR are initialized with ZEROS. INITIALIZE YEAR REPLACING NUMERIC-DATA BY 12 Using the above statement we can initialize the value of YEAR to 12 which initially had zeros.

REDIFINES CLAUSE

This clause allows the same area of memory to be referenced by more thanone data-name with different formats and sizes. SYNTAX: <LEVEL> <DATA-NAME-1> <LEVEL> <DATA-NAME-2> REDEFINES <DATA-NAME-1> This clause must immediately follow <DATA-NAME-1> Level Numbers of <DATA-NAME-1> and <DATA-NAME-2> must be identical and cannot be used in 66 level OR 88 level. 01 DAYS-IN-WEEK. 05 DAY-NAMES PIC X(21) VALUE SUNMONTUEWEDTHUFRISAT. 05 W-NAMES REDEFINES DAY-NAMES. 01 W-DAYS PIC X(3) OCCURS 7 TIMES. The days can be accessed as W-DAYS(1), W-DAYS(2), etc.

REDEFINES CLAUSE RULES At 01 level, REDEFINES and OCCURS cannot be combined. Original data name and redefined data names should be different. Entries giving new descriptions cannot have VALUE clause except in the case of condition names. Redefines should not be used for records defined in the file section.

REFERENCE MODIFICATION

Reference Modification allows us to treat a numeric (PIC 9) or alphanumeric (PIC X) data-item as if it were an array of characters. To access sub-strings using Reference Modification you must specify;


SYNTAX

the name of the data-item the start character position of the sub-string the number of characters in the sub-string

DataName(StartPos [:SubStrLength]) StartPos is the character position of the first character in the sub-string and SubStrLength is number of characters in the substring. As the square brackets indicate, the SubStrLength may be omitted, and in that case the substring from StartPos to the end of the string is assumed. EXAMPLE 03 DATA-FIELD PIC X(15) VALUE MATHEMATICS. TO NEW-FIELD . will move the 2 characters from the 4th position into

Consider the statement MOVE DATA-FIELD (4:2) the NEW-FIELD ie. HE will be moved.

Consider the statement MOVE DATA-FIELD (4: ) TO NEW-FIELD . will move all the characters that follow the character in the 4th position ie. HEMATICS will be moved to the NEW-FIELD. Whenever the substring length is not specified, the substring from the start position until the end of the string is assumed.

EVALUATE VERB

EVALUATE VERB is used whenever a series of conditions are to be checked. IF verb is replaced by the EVALUATE verb because the performance of evaluate verb is high when compared to IF. SYNTAX EVALUATE identifier-1/expression-1 WHEN condition-1 Imperative statement-1 WHEN condition-2 Imperative statement-2 . . WHEN OTHER Imperative statement END-EVALUTE. EXAMPLES: 1. TRUE: The list of subject consists of only one element which will evaluate to the conditional value TRUE. Consider the example below, it aims at calculating the number of days in a particular month. For a given input only one condition will be satisfied. EVALUATE TRUE WHEN MONTH = 4 OR 6 0R 9 OR 11 MOVE 30 TO NO-OF-DAYS WHEN MONTH= 2 MOVE 28 TO NO-OF-DAYS WHEN OTHER MOVE 31 TO NO-OF-DAYS END-EVALUATE. 2. TRANS-CODE: it is an identifier. The list of subjects consists of only one element which will evaluate to the value of TRANS-CODE. In the example below, the evaluate statement checks for the following range of marks and moves the corresponding grade into GRADE. EVALUATE MARKS WHEN MARKS WHEN MARKS WHEN MARKS WHEN MARKS WHEN MARKS WHEN MARKS END-EVALUATE. 3. 80 THRU 100 MOVE A 60 THRU 79 MOVE B 45 THRU 59 MOVE C 30 THRU 44 MOVE D ZERO THRU 100 MOVE E OTHER MOVE WRONG-MARKS TO TO TO TO TO TO GRADE GRADE GRADE GRADE GRADE GRADE

TRANS-CODE ALSO PRODUCT-TYPE ALSO CUSTOMER-CATEGORY: Here the list of subject is having 3 elements namely, TRANS-CODE, PRODUCT-TYPE and CUSTOMER-CATEGORY. These elements need not be of same class ie. One can be of numeric type and the other of alpha numeric type.

EVALUATE PRODUCT-TYPE ALSO CUSTOMER-CATEGORY WHEN 1 ALSO 1 MOVE 10 TO COMMISSION WHEN 2 ALSO 2 MOVE 20 TO COMMISSION WHEN 3 ALSO 1 MOVE 30 TO COMMISSION WHEN 2 ALSO 1 MOVE 40 TO COMMISSION WHEN OTHER MOVE 00 TO COMMISSION END-EVALUATE. In the above example only when the 2 conditions satisfy, the value is moved to the COMMISSION. EXAMPLE PROGRAM: IDENTIFICATION DIVISION. PROGRAM-ID. EV1PGM. DATA DIVISION. WORKING-STORAGE SECTION. 01 WORK-AREA. 03 MARITAL-STATUS. 05 SINGLE PIC X VALUE 'S'. 05 MARRIED PIC X VALUE 'M'. 05 DIVORCED PIC X VALUE 'D'. PROCEDURE DIVISION. 0000-MAIN-LINE. ACCEPT MARITAL-STATUS. EVALUATE MARITAL-STATUS WHEN 'S' DISPLAY "THE PERSON IS SINGLE" WHEN 'M' DISPLAY "THE PERSON IS MARRIED" WHEN 'D' DISPLAY "THE PERSON IS DIVORCED" WHEN OTHER DISPLAY "INVALID OPTION" END-EVALUATE. STOP RUN.

COBOL SORT

Records in files must be sorted into specific sequences for Updating,Querying or Generating Reports. Sorting is a common procedure used for arranging records into a specific order so that sequential processing can be performed. Sorting is done on the basis of a key field. Multiple keys can be used for sorting Records may be sorted using either numeric or non-numeric key fields. Syntax : SORT File-name-1 { ON DESCENDING KEY Data-name-1. . . } ASCENDING USING File-name-2 GIVING File-name-3. Example : SORT SORT-FILE ON ASCENDING KEY EMP-NO ON ASCENDING KEY E-NAME ON ASCENDING KEY E-LEVEL USING INPUT-FILE GIVING OUTPUT-FILE. INPUT FILE : File of unsorted records. SORT FILE : File for temporary storage during sorting. OUTPUT FILE : File of sorted output records. SORT VERB: Sort file is defined with an SD entry and has no label records clause. Example : SD SORT-FILE. 01 SORT-REC. 05 S-DEPTNO PIC 99. 05 S-DEPTNAME PIC X(10). INPUT PROCEDURE Sort statement can also be used to perform some processing of incoming records just before they are sorted. The input procedure processes data from the incoming file prior to sorting Syntax : SORT File-name-1 { ON ASCENDING KEY Data-name-1 } DESCENDING { INPUT PROCEDURE IS Procedure-name-1 [ { THRU / THROUGH } ] Procedure-name-2 ] } { USING File-name-2 } GIVING File-name-3. Example : MAIN-PARA. SORT W-FILE. INPUT PROCEDURE CHECK-VALID-PARA GIVING SORT-FILE. STOP RUN. In the paragraph CHECK-VALID-PARA : Open input file, Check for validity, Release the record Close the file After that control is passed to SORT. RELEASE STATEMENT The input procedure opens the input file, processes input records and releases them into the sort file .It is similar to writing a record to the sort file. SYNTAX: RELEASE Sort-record-name-1 [ FROM Identifier-1 ] For releasing the processed record for Sorting : - Move input record to the sort record. - Release each sort record, which makes it available for sorting. Example : RELEASE-PARA. MOVE IN-REC TO SORT-REC. RELEASE SORT-REC. MAIN-PARA.

SORT SORT-FILE ON ASCENDING KEY ORDER-NO INPUT PROCEDURE TEST-PARA GIVING OUT-FILE. STOP RUN. TEST-PARA. OPEN INPUT IN-FILE. PERFORM UNTIL NO-MORE-RECORDS = NO READ IN-FILE AT END MOVE NO TO NO-MORE-RECORDS NOT AT END PERFORM PROCESS-PARA END-READ. END-PERFORM. CLOSE IN-FILE. PROCESS-PARA. IF QTY = ZEROS CONTINUE ELSE MOVE IN-REC TO SORT-REC RELEASE SORT-REC END-IF. OUTPUT PROCEDURE: In case of sort if the giving option is used, then the sorted records are automatically written onto the Outfile after they are used. Instead of giving option an output procedure can be used. 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. Syntax SORT File-1 { ON DESCENDING KEY Data-name-1 } ASCENDING { INPUT PROCEDURE Proc-1 THROUGH Proc-2 } THRU { USING File-2 { OUTPUT PROCEDURE IS Proc-3 THROUGH Proc-4 } THRU { GIVING File-2 Records are returned from the sort file using RETURN statement. RETURN SORT-FILE-NAME-1 AT END <Imperative statement-1> [ NOT AT END <imperative statement-2> ] [END-RETURN]. Example : MAIN-PARA. SORT WORK-FILE USING IN-FILE OUTPUT PROCEDURE CHECK-PARA. STOP RUN. In the paragraph CHECK-PARA: Open output file. Return records from sort file. Process records before writing to Out-file. Close the file. After the records have been sorted but before they are written into the OUTPUT FILE : Move sort record to the output area. Write each sort record to the output file. EXAMPLE: WRITE-PARA. WRITE SORT-REC FROM WORK-REC. MAIN-PARA. SORT SORT-FILE ON ASCENDING KEY TRANS-NO USING INPUT-FILE OUTPUT PROCEDURE CALC-PARA. STOP RUN. CALC-PARA. OPEN OUTPUT OUTPUT-FILE. PERFORM UNTIL NO-MORE-RECORDS = NO RETURN SORT-FILE AT END MOVE NO TO NO-MORE-RECORDS NOT AT END

PERFORM PROCESS-PARA END-RETURN END-PERFORM. CLOSE OUTPUT-FILE. PROCESS-PARA. IF AMT-OF-PURCHASE > 656 MOVE 0.02 TO DISCOUNT ELSE MOVE 0.00 TO DISCOUNT END-IF. WRITE OUT-REC FROM SORT-REC.

Vous aimerez peut-être aussi