COBOL Lab

60
Sheet No: 1 Program No: 1 Aim: To print sum of natural numbers, sum of odd, sum of even, no of odd, no of even from 1 to 10. Analysis: An identifier runs from 1 to 10 and test each number is even or odd. If it is even calculate sum of even and number of even else calculate sum of odd and number of odd. At last add both sum of even and sum of odd we get sum of the natural numbers. Source Code: IDENTIFICATION DIVISION. PROGRAM-ID. DATA DIVISION. WORKING-STORAGE SECTION. 77 N PIC 9(5). 77 I PIC 9(5). 77 SN PIC 9(5) VALUE 0. 77 SE PIC 9(5) VALUE 0. 77 SO PIC 9(5) VALUE 0. 77 NE PIC 9(5) VALUE 0. 77 NOD PIC 9(5) VALUE 0. 77 R PIC 9(5). 77 T PIC 9(5). PROCEDURE DIVISION. MP. DISPLAY "ENTER ANY NUMBER :". ACCEPT N. PERFORM EP VARYING I FROM 1 BY 1 UNTIL I>N. DISPLAY "SUM OF EVEN NUMBERS :", SE. DISPLAY "SUM OF ODD NUMBERS:", SO. COMPUTE SN = SE + SO. DISPLAY "SUM OF THE NATURAL NUMBERS :", SN. DISPLAY "NUMBER OF EVEN NUMBERS :", NE. DISPLAY "NUMBER OF ODD NUMBERS :", NOD. STOP RUN. EP.

Transcript of COBOL Lab

Page 1: COBOL  Lab

Sheet No: 1

Program No: 1

Aim: To print sum of natural numbers, sum of odd, sum of even, no of odd, no of even from 1 to 10.

Analysis: An identifier runs from 1 to 10 and test each number is even or odd. If it is even calculate sum of even and number of even else calculate sum of odd and number of odd. At last add both sum of even and sum of odd we get sum of the natural numbers.

Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. DATA DIVISION. WORKING-STORAGE SECTION. 77 N PIC 9(5). 77 I PIC 9(5). 77 SN PIC 9(5) VALUE 0. 77 SE PIC 9(5) VALUE 0. 77 SO PIC 9(5) VALUE 0. 77 NE PIC 9(5) VALUE 0. 77 NOD PIC 9(5) VALUE 0. 77 R PIC 9(5). 77 T PIC 9(5). PROCEDURE DIVISION. MP. DISPLAY "ENTER ANY NUMBER :". ACCEPT N. PERFORM EP VARYING I FROM 1 BY 1 UNTIL I>N. DISPLAY "SUM OF EVEN NUMBERS :", SE. DISPLAY "SUM OF ODD NUMBERS:", SO. COMPUTE SN = SE + SO. DISPLAY "SUM OF THE NATURAL NUMBERS :", SN. DISPLAY "NUMBER OF EVEN NUMBERS :", NE. DISPLAY "NUMBER OF ODD NUMBERS :", NOD. STOP RUN. EP. DIVIDE I BY 2 GIVING T REMAINDER R. IF R=0 COMPUTE SE = SE + I COMPUTE NE = NE + 1 ELSE COMPUTE SO = SO + I COMPUTE NOD = NOD + 1.

Page 2: COBOL  Lab

Sheet No: 2

Output:

ENTER ANY NUMBER :10SUM OF EVEN NUMBERS:00030SUM OF ODD NUMBERS :00025SUM OF THE NATURAL NUMBERS :00055NUMBER OF EVEN NUMBERS:00005NUMBER OF ODD NUMBERS:00005

Conclusion: First accepting the integer N for range to calculate i.e., from 1 to N now

calculating the required and the sum of even, odd and number of even, odd and the sum of natural numbers are printed.

Page 3: COBOL  Lab

Sheet No: 3

Program No: 2

Aim: To print the big & smallest digit, sum of digits and number of digits in a given number.

Analysis: Accept a number N. Divide the number with 10 then we get an individual digit check the every digit to get biggest and smallest digit in a given number and add each digit to a sum identifier to get the sum of the digits and add 1 to a counter identifier to get the number of digits. The quotient is stored in the same identifier and repeat this process until the identifier value becomes 0.

Source Code: IDENTIFICATION DIVISION. PROGRAM-ID. DATA DIVISION. WORKING-STORAGE SECTION. 77 N PIC 9(5). 77 R PIC 9(5). 77 I PIC 99. 77 S PIC 99 VALUE 9. 77 B PIC 99 VALUE 0. 77 SUM PIC 99 VALUE 0. 77 ND PIC 99 VALUE 0. PROCEDURE DIVISION. MP. DISPLAY "ENTER ANY NUMBER :". ACCEPT N. PERFORM DP VARYING I FROM 1 BY 1 UNTIL N=0. DISPLAY "BIGGEST DIGIT IS:", B. DISPLAY "NUMBER OF DIGITS:", ND. DISPLAY "SMALLEST DIGIT IS:", S. DISPLAY "SUM OF THE DIGITS:", SUM. STOP RUN. DP. DIVIDE N BY 10 GIVING N REMAINDER R. COMPUTE SUM = SUM + R. COMPUTE ND = ND + 1. IF B<R MOVE R TO B. IF S>R MOVE R TO S.

Page 4: COBOL  Lab

Sheet No: 4

Output:

ENTER ANY NUMBER:123000030000200001BIGGEST DIGIT IS: 03SMALLEST DIGIT IS: 01NUMBER OF THE DIGITS: 03SUM OF THE DIGITS: 06

Conclusion: First accepting the integer and the calculation is done as mentioned above

and the biggest digit and smallest digits in the given integer are printed and the number of digits, sum of the digits that are present in the given integer are printed after that.

Page 5: COBOL  Lab

Sheet No: 5

Program No: 3

Aim: Accept any integer check whether it is a PALINDROME number or not.

Analysis: Accept the natural number N. Move N to another identifier X. Divide the number N with 10 then we get the individual digit. Multiply it by 10 and add it to an identifier S and the process is continued until N becomes 0. Finally comparing S and X we can confirm it is Palindrome or not.

Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. DATA DIVISION. WORKING-STORAGE SECTION. 77 N PIC 9(5). 77 X PIC 9(5). 77 S PIC 9(5) VALUE 0. 77 R PIC 9(5). PROCEDURE DIVISION. PARA-A. DISPLAY "ENTER THE NUMBER :". ACCEPT N. MOVE N TO X. PERFORM PARA-B UNTIL N=0. IF X=S DISPLAY "NUMBER IS PALLINDROME." ELSE DISPLAY "NUMBER IS NOT PALLINDROME.". STOP RUN. PARA-B. DIVIDE N BY 10 GIVING N REMAINDER R. COMPUTE S = S * 10 + R.

Output:ENTER THE NUMBER :121NUMBER IS PALLINDROME.

Conclusion:Accepting an integer and calculated as mentioned above. After process is

completed comparing S and X the result is printed as given number is Palindrome.

Page 6: COBOL  Lab

Sheet No: 6

Program No: 4

Aim: Accept a number and check whether it is AMSTRONG number or not.

Analysis: Accept the natural number N. Move N to another identifier X. Divide the number with 10 then we get the individual digit and calculate its cube and add it to an identifier S and the process is continued until N becomes 0. Finally comparing S and X we can confirm it is Armstrong or not.

Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. 77 N PIC 9(3). 77 R PIC 9(3). 77 X PIC 9(3) VALUE 1. 77 S PIC 9(3) VALUE 0. PROCEDURE DIVISION. PARA-A. DISPLAY "ENTER THE VALUE FOR N: ". ACCEPT N. MOVE N TO X. PERFORM PARA-B UNTIL N=0. DISPLAY "S IS :", S. IF X=S DISPLAY "N IS AMSTRONG NO." ELSE DISPLAY "N IS NOT A AMSTRONG NO.". STOP RUN. PARA-B. DIVIDE N BY 10 GIVING N REMAINDER R. COMPUTE R = R * R * R. COMPUTE S = S + R.Output:

ENTER THE VALUE FOR N:153S IS :153N IS AMSTRONG NO.

Conclusion:Accepting an integer calculated as mentioned above. After process is

completed comparing S and X result is printed as the given number is Armstrong.

Page 7: COBOL  Lab

Sheet No: 7

Program No: 5

Aim: Accept a number and check whether it is a PRIME number or not.

Analysis: Accept any integer N. Divide N with every integer from 2 to N-1 and check the remainder at every step is 0 or not. If it is 0 then move 1 to an identifier flag. Check the identifier flag if equal to 1 then the given number is not prime.

Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. DATA DIVISION. WORKING-STORAGE SECTION. 77 N PIC 99. 77 I PIC 99 VALUE 2. 77 T PIC 99. 77 R PIC 99. 77 FLAG PIC 9 VALUE 0. PROCEDURE DIVISION. MP. DISPLAY "ENTER THE VALUE :". ACCEPT N. PERFORM PRIME VARYING I FROM 2 BY 1 UNTIL I=N. IF FLAG=1 DISPLAY "GIVEN NUMBER IS NOT PRIME." ELSE DISPLAY "GIVEN NUMBER IS PRIME.". STOP RUN. PRIME. DIVIDE N BY I GIVING T REMAINDER R. IF R=0 MOVE 1 TO FLAG.

Output:

ENTER THE VALUE :11GIVEN NUMBER IS PRIME.

Conclusion: Accepting an integer N and calculated as explained above. After completion

of the process checking the flag identifier is 0 the result is printed that the given integer is prime.

Page 8: COBOL  Lab

Sheet No: 8

Program No: 6

Aim: Accept a number and check whether it is a PERFECT number or not.Analysis: Accept the natural number N. Move N to another identifier X. Divide the number from 1 to N-1 and check the remainder if it is 0 or not i.e., whether it is a factor or not if yes then add it to an identifier S which is initialized to 0. Finally compare S and X.Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. 77 N PIC 9(3). 77 R PIC 9(3). 77 T PIC 9(3) VALUE 1. 77 I PIC 9(3). 77 X PIC 9(3) VALUE 1. 77 S PIC 9(3) VALUE 0. PROCEDURE DIVISION. PARA-A. DISPLAY "ENTER THE VALUE FOR N: ". ACCEPT N. MOVE N TO X. PERFORM PARA-B VARYING I FROM 1 BY 1 UNTIL I=N. IF X=S DISPLAY "N IS PERFECT NO." ELSE DISPLAY "N IS NOT A PERFECT NO.". STOP RUN. PARA-B. DIVIDE N BY I GIVING T REMAINDER R. IF R=0 COMPUTE S = S + I.

Output:

ENTER THE VALUE FOR N: 6N IS PERFECT NO.

Conclusion: Accepting an integer calculated as mentioned above. After the process is

completed S and X are compared and the result is printed as the given number N is PERFECT.

Page 9: COBOL  Lab

Sheet No: 9

Program No: 7

Aim: Accept a number and check whether it is a STRONG number or not.

Analysis: Accept the natural number N. Move N to another identifier X. Divide the number with 10 to get the remainder digit, find the factorial of the digit and add it to an identifier S which is initialized to 0 continue the process until N is equal to 0 and finally compare S and X.

Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. 77 N PIC 9(3). 77 R PIC 9(3). 77 F PIC 9(3) VALUE 1. 77 X PIC 9(3) VALUE 1. 77 S PIC 9(3) VALUE 0. PROCEDURE DIVISION. PARA-A. DISPLAY "ENTER THE NUMBER: ". ACCEPT N. MOVE N TO X. PERFORM PARA-B UNTIL N=0. IF X=S DISPLAY "N IS STRONG NUMBER." ELSE DISPLAY "N IS NOT A STRONG NUMBER.". STOP RUN. PARA-B. DIVIDE N BY 10 GIVING N REMAINDER R. PERFORM PARA-F UNTIL R=1. COMPUTE S = S + F. MOVE 1 TO F. PARA-F. COMPUTE F = F * R. COMPUTE R = R - 1.

Page 10: COBOL  Lab

Sheet No: 10

Output:

ENTER THE NUMBER: 145N IS STRONG NUMBER.

Conclusion: Accepting an integer calculation is done as mentioned above. After the

process is completed S and X are compared and the result is displayed as the given number N is STRONG.

Page 11: COBOL  Lab

Sheet No: 11

Program No: 8

Aim: Accept the number of terms in the series and display the Fibonacci series.

Analysis: Take two identifiers a, b and initialize them to 0 and 1 and display them. Take another identifier c and store the sum of a, b and display c and then swap the three identifiers b to a and c to b and repeat the sum of c=a+b and display c until the series comes to the end i.e., the given number of terms comes.

Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. DATA DIVISION. WORKING-STORAGE SECTION. 77 A PIC 999 VALUE 0. 77 B PIC 999 VALUE 1. 77 C PIC 999 VALUE 0. 77 I PIC 99. 77 N PIC 99. PROCEDURE DIVISION. MP. DISPLAY "ENTER THE NUMBER OF FIBONACCI TERMS:". ACCEPT N. DISPLAY "THE FIBONACCI SIRES:". DISPLAY ( , ) A " ". DISPLAY ( , ) B " ". PERFORM FP VARYING I FROM 3 BY 1 UNTIL I>N. STOP RUN. FP. COMPUTE C = A + B. DISPLAY (, ) C " ". MOVE B TO A. MOVE C TO B.

Output:

ENTER THE NUMBER OF FIBONACCI TERMS. :10THE FIBONACCI SIRES:00 01 01 02 03 05 08 13 21 34

Conclusion: Accept the number of terms N of Fibonacci series. Display the first two

terms and then starting from 3 until I is greater than N repeat the given process and finally the series is displayed upto the given number of terms.

Page 12: COBOL  Lab

Sheet No: 12

Program No: 9

Aim: Accept the number and display the factorial of the number.

Analysis: Accept a number N. Initialize an identifier F to 1 multiply the identifier with N and decrementing the N by 1 and again multiplying to f and continue the process until N is greater than 0. Finally the result is stored in the identifier F and display it.

Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. ENVIRONMENT DIVISION. DATA DIVISION. WORKING-STORAGE SECTION. 77 N PIC 9(2). 77 F PIC 9(4) VALUE 1. PROCEDURE DIVISION. PARAA. DISPLAY "ENTER THE VALUE FOR N: ". ACCEPT N. PERFORM PARAB UNTIL N > 0. DISPLAY "FACTORIAL OF A GIVEN NUMBER :", F. STOP RUN. PARAB. COMPUTE F = N * F. COMPUTE N = N - 1. Output:

ENTER THE VALUE FOR N:5FACTORIAL OF A GIVEN NUMBER: 0120

Conclusion: Accept any integer to which the factorial is to be found. Process is done as

given and the final result is displayed.

Page 13: COBOL  Lab

Sheet No: 13

Program No: 10

Aim: To print 20 mathematical tables from 1 to 20.

Analysis: Consider three identifiers I,J and N. Run the identifiers I and J from 1 to 20 one after the other and multiply them and result is stored in N. Display them interactively and stop the execution for each table i.e., when J reaches to 20.

Source Code: IDENTIFICATION DIVISION. PROGRAM-ID. DATA DIVISION. WORKING-STORAGE SECTION. 77 I PIC 99. 77 N PIC 99. 77 J PIC 99. PROCEDURE DIVISION. MP. PERFORM MT VARYING I FROM 1 BY 1 UNTIL I > 20 AFTER J FROM 1 BY 1 UNTIL J > 20. STOP RUN. MT. COMPUTE N = J * I. DISPLAY I "*", J "=", N. IF J = 20 STOP "PRESS ANY KEY TO CONTINUE...".

Output:1 * 1 = 11 * 2 = 2... ...1 * 20 = 20PRESS ANY KEY TO CONTINUE…2 * 1 = 22 * 2 = 4………20 * 1 = 2020 * 2 = 40……PRESS ANY KEY TO CONTINUE…

Conclusion: Following the given process the output is displayed as shown above and the execution stops temporarily for each and every table and continues by pressing any key on the key board.

Page 14: COBOL  Lab

Sheet No: 14

Program No: 11

Aim: To print student marks statement using filler clause.

Analysis: Create a group of items for each line in the statement. To calculate, take individual identifiers in addition. Calculate and move the result to the identifier in a group.

Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. DATA DIVISION. WORKING-STORAGE SECTION. 01 BL. 02 F PIC X(79) VALUE SPACE. 01 LI. 02 F PIC X(79) VALUE ALL "-". 01 H1-REC. 02 F PIC X(10) VALUE SPACE. 02 F PIC X(15) VALUE "SRKSIT LIMITED.". 01 H2-REC. 02 F PIC X(10) VALUE SPACE. 02 F PIC X(11) VALUE "VIJAYAWADA.". 01 H3-REC. 02 F PIC X(10) VALUE SPACE. 02 F PIC X(24) VALUE "STUDENT MARKS STATEMENT.". 01 H4-REC. 02 F PIC X(5) VALUE SPACE. 02 F PIC X(11) VALUE "STUDENT NO:". 02 SNO PIC 99999. 02 F PIC X(5) VALUE SPACE. 02 F PIC X(4) VALUE "NAME". 02 NAME PIC A(10). 01 H5-REC. 02 F PIC X(5) VALUE SPACE. 02 F PIC X(6) VALUE "COBOL:". 02 COB PIC 99. 02 F PIC X(5) VALUE SPACE. 02 F PIC X(2) VALUE "C:". 02 C PIC 99. 02 F PIC X(5) VALUE SPACE. 02 F PIC X(4) VALUE "CPP:". 02 CPP PIC 99. 01 H6-REC. 02 F PIC X(5) VALUE SPACE.

Page 15: COBOL  Lab

Sheet No: 15

02 F PIC X(6) VALUE "TOTAL:". 02 TOT PIC 999. 02 F PIC X(5) VALUE SPACE. 02 F PIC X(4) VALUE "AVG:". 02 AVG PIC 999V99. 01 H7-REC. 02 F PIC X(5) VALUE SPACE. 02 F PIC X(7) VALUE "RESULT:". 02 RES PIC A(5). 02 F PIC X(5) VALUE SPACE. 02 F PIC X(9) VALUE "DIVISION:". 02 DIV PIC X(5).

PROCEDURE DIVISION. MP. DISPLAY "ENTER THE STUDENT NUMBER: ". ACCEPT SNO. DISPLAY "ENTER THE STUDENT NAME :". ACCEPT NAME. DISPLAY "ENTER THE MARKS IN COBOL,C&CPP :". ACCEPT COB. ACCEPT C. ACCEPT CPP. COMPUTE TOT = COB + C + CPP. COMPUTE AVG = TOT / 3. IF COB>50 AND C>50 AND CPP>50 PERFORM DP ELSE MOVE "FAIL" TO RES MOVE "NILL" TO DIV.

DISPLAY (1, 1)ERASE. DISPLAY H1-REC. DISPLAY H2-REC. DISPLAY H3-REC. DISPLAY LI. DISPLAY H4-REC. DISPLAY LI. DISPLAY H5-REC. DISPLAY LI. DISPLAY H6-REC. DISPLAY LI. DISPLAY H7-REC. STOP RUN. DP. MOVE "PASS" TO RES.

Page 16: COBOL  Lab

Sheet No: 16

IF AVG>75 MOVE "DISTIGUISH" TO DIV ELSE IF AVG >60 MOVE "IST" TO DIV ELSE MOVE "IIND" TO DIV.

Output:

ENTER THE STUDENT NUMBER:11ENTER THE STUDENT NAME:RAGHUENTER THE MARKS IN COBOL, C & CPP:404040

SRK LIMITED. VIJAYAWADA. STUDENT MARKS STAEMENT.---------------------------------------------------------------------------------------- STUDENT NO: 11 STUDENT NAME: RAGHU---------------------------------------------------------------------------------------- COBOL: 80 C: 80 CPP: 80----------------------------------------------------------------------------------------- TOTAL: 240 AVARAGE: 80.00----------------------------------------------------------------------------------------- RESULT: PASS DIVISION: DISTINTION.

Conclusion: Accept no, name, marks and calculate the total and average store to the

identifiers in the group. And display the record using the group name as in the statement.

Page 17: COBOL  Lab

Sheet No: 17

Program No: 12

Aim: To print a power bill statement using the filler clause.

Analysis: Create a group of items for each line in the statement. To calculate, take individual identifiers in addition. Calculate and move the result to the identifier in a group.

Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. DATA DIVISION. WORKING-STORAGE SECTION. 01 BL. 02 F PIC X(79) VALUE SPACE. 01 LI. 02 F PIC X(79) VALUE ALL "-". 01 H1-REC. 02 F PIC X(10) VALUE SPACE. 02 F PIC X(10) VALUE "APSE BOARD". 01 H2-REC. 02 F PIC X(10) VALUE SPACE. 02 F PIC X(11) VALUE "VIJAYAWADA.". 01 H3-REC. 02 F PIC X(10) VALUE SPACE. 02 F PIC X(10) VALUE "POWER BILL". 01 H4-REC. 02 F PIC X(5) VALUE SPACE. 02 F PIC X(11) VALUE "SERVICE NO:". 02 SNO PIC 99999. 02 F PIC X(5) VALUE SPACE. 02 F PIC X(13) VALUE "CUSTOMER NAME". 02 CNAME PIC A(10). 01 H5-REC. 02 F PIC X(3) VALUE SPACE. 02 F PIC X(3) VALUE "LMR". 02 LMR PIC 99999. 02 F PIC X(3) VALUE SPACE. 02 F PIC X(4) VALUE "CMR:". 02 CMR PIC 99999. 02 F PIC X(3) VALUE SPACE. 02 F PIC X(5) VALUE "CODE:". 02 CODE PIC A. 02 F PIC X(3) VALUE SPACE. 02 F PIC X(5) VALUE "COST:".

Page 18: COBOL  Lab

Sheet No: 18

02 COS PIC 99999.99. 02 F PIC X(3) VALUE SPACE. 02 F PIC X(6) VALUE "UNITS:". 02 UNI PIC 99999V99. 77 COST PIC 99999V99. 01 H6-REC. 02 F PIC X(5) VALUE SPACE. 02 F PIC X(14) VALUE "BILL AMOUNT :". 02 BILL PIC 99999.99. 77 AMT PIC 99999V99. PROCEDURE DIVISION. MP. DISPLAY "ENTER THE SERVICE NO: ". ACCEPT SNO. DISPLAY "ENTER THE CUSTOMER NAME :". ACCEPT CNAME. DISPLAY "ENTER CODE:". ACCEPT CODE. DISPLAY "ENTER LMR:". ACCEPT LMR. DISPLAY "ENTER CMR:". ACCEPT CMR. COMPUTE UNI = CMR - LMR. IF CODE="D" MOVE 2.50 TO COST ELSE IF CODE="B" MOVE 3.05 TO COST ELSE IF CODE="I" MOVE 5.00 TO COST. COMPUTE AMT = COST * UNI. MOVE COST TO COS. MOVE AMT TO BILL. DISPLAY (1, 1)ERASE. DISPLAY H1-REC. DISPLAY H2-REC. DISPLAY H3-REC. DISPLAY LI. DISPLAY H4-REC. DISPLAY LI. DISPLAY H5-REC. DISPLAY LI. DISPLAY H6-REC. DISPLAY LI. STOP RUN.

Page 19: COBOL  Lab

Sheet No: 19

Output:

ENTER THE SERVICE NUMBER :11ENTER THE CUSTOMER NAME:RAGHUENTER CODE :BENTER LMR :100ENTER CMR :200

APSE BOARD. VIJAYAWADA. POWER BILL.--------------------------------------------------------------------------------------------------- SERVICE NO: 11 CUSTMOER NAME: RAGHU----------------------------------------------------------------------------------------------------LMR : 100 CMR : 200 CODE : B COST : 03.00 UNITS : 000100 ----------------------------------------------------------------------------------------------------- TOTAL BILL AMOUNT : 00300.00-----------------------------------------------------------------------------------------

Conclusion: Accept no, name, code, lmr, cmr and calculate the cost and units. Calculate

the bill amount using cost and units. Store the result in identifier in the group and display the record using the group name as in the statement.

Page 20: COBOL  Lab

Sheet No: 20

Program No: 13

Aim: To create a table of 10 cells input values in it & print the biggest & smallest values in it. And sort the elements.

Analysis: Create an array of size 10 and compare each element with 0 and if the element is greater than 0 then swap the elements. To obtain the smallest element compare each element with 9 and obtain the smallest elements. Sort the array compare the element with other elements and place the smallest element in lower position by swaping the elements and the first element is small and last element is biggest element in the array.

Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. DATA DIVISION. WORKING-STORAGE SECTION. 01 ARR. 02 A PIC 9(2) OCCURS 10 TIMES. 77 I PIC 9(2). 77 J PIC 99. 77 B PIC 9(2) VALUE 0. 77 S PIC 9(2) VALUE 0. 77 T PIC 99. PROCEDURE DIVISION. PARA-A. DISPLAY "ENTER THE ARRAY ELEMENTS :". PERFORM AP VARYING I FROM 1 BY 1 UNTIL I>10. PERFORM SP VARYING I FROM 1 BY 1 UNTIL I>10 AFTER J FROM 1 BY 1 UNTIL J>10. DISPLAY "THE SORTED ARRAY :". PERFORM DP VARYING I FROM 1 BY 1 UNTIL I>10. DISPLAY "BIGGEST ELEMENT IS :", A(10). DISPLAY "SMALLEST ELEMENT IS :", A(1). STOP RUN. AP. ACCEPT A(I). SP. IF A(I)<A(J) MOVE A(I) TO T MOVE A(J) TO A(I) MOVE T TO A(J). DP. DISPLAY (, )A(I) " ".

Page 21: COBOL  Lab

Sheet No: 21

Output:

ENTER THE ARRAY ELEMENTS: 55224499887733116615THE SORTED ARRAY:11 15 22 33 44 55 66 77 88 99BIGGEST ELEMENT IS: 99SMALLEST ELEMENT IS:11

Conclusion: Accept the array elements. Compare one element with remaining elements

and if smallest occurs then swap both elements and print the elements after swap. To get the biggest print the last element of the array. To get the smallest element print the first element of the array.

Page 22: COBOL  Lab

Sheet No: 22

Program No: 14

Aim: Accept the values in the array and perform the linear search & binary search.

Analysis: Accept the elements into an array and then accept the element to be searched in the array and then search for it using the linear search and binary search. In the linear search each and every element is compared with the key element and then if matches any where a flag variable is given the value 1 and then finally if the flag value is 1 the element is found else not found. In the binary search the elements are sorted and the key element is compared with the mid element and if the element matches then ok else if the key element is greater (smaller) than the mid element then the array is divided into two halves and search process continues in the same way in the second (first) half for the element finally the result is displayed.

Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. DATA DIVISION. WORKING-STORAGE SECTION. 01 ARR. 02 A PIC 9(2) OCCURS 5 TIMES. 77 I PIC 9(2). 77 J PIC 99. 77 K PIC 9(2). 77 TEMP PIC 99. 77 T PIC 99 VALUE 5. 77 B PIC 99 VALUE 1. 77 M PIC 99 VALUE 3. 77 N PIC 99. 77 F PIC 99 VALUE 0. PROCEDURE DIVISION. PARA-A. DISPLAY "LINEAR SEARCH ". DISPLAY "ENTER THE ARRAY ELEMENTS :". PERFORM AP VARYING I FROM 1 BY 1 UNTIL I>5. DISPLAY "ENTER THE ELEMENT TO BE FOUND". ACCEPT K. PERFORM LS VARYING I FROM 1 BY 1 UNTIL I>5. IF F=0 DISPLAY "THE ELEMENT IS NOT FOUND" ELSE DISPLAY "ELEMENT FOUND". DISPLAY "BINARY SEARCH ". DISPLAY "ENTER THE ELEMENT TO BE FOUND IN THE SAME ARRAY". ACCEPT N.

Page 23: COBOL  Lab

Sheet No: 23

PERFORM TP VARYING I FROM 1 BY 1 UNTIL I > 5 AFTER J FROM 1 BY 1 UNTIL J > 4. DISPLAY "ELEMENTS AFTER SORTING IN THE ARRAY ARE:". PERFORM DP VARYING I FROM 1 BY 1 UNTIL I > 5. PERFORM BS UNTIL B > T OR A(M) = N. IF A(M) = N DISPLAY "ELMENT IS FOUND" ELSE DISPLAY "ELMENT IS NOT FOUND". STOP RUN. AP. ACCEPT A(I). TP. COMPUTE K = J + 1. IF A(J) > A(K) MOVE A(J) TO TEMP MOVE A(K) TO A(J) MOVE TEMP TO A(K). BS. COMPUTE M = (T + B) / 2. IF N > A(M) COMPUTE B = M + 1 ELSE IF N < A(M) COMPUTE T = M - 1. LS. IF K=A(I) DISPLAY "THE ELEMENT IS FOUND." MOVE 1 TO F. DP. DISPLAY ( , ) A(I) " ".

Out Put:

LINEAR SEARCHENTER THE ARRAY ELEMENTS :15759314328644389154

Page 24: COBOL  Lab

Sheet No: 24

ENTER THE ELEMENT TO BE FOUND56ELEMENT IS NOT FOUNDBINARY SEARCHENTER THE ELEMENT TO BE FOUND IN THE SAME ARRAY14ELEMENTS AFTER SORTING IN THE ARRAY ARE:14 15 32 38 44 54 75 86 91 93 ELEMENT IS FOUND

Conclusion:Accepting the elements into the array the element to be found are also

accepted in the linear and binary search techniques they are verified and the results are displayed.

Page 25: COBOL  Lab

Sheet No: 25

Program No: 15

Aim: Linear search using Indexed table.

Analysis: Create the array which is indexed with I. To search the element in indexed table use the reserved word SEARCH. Before start the search process set the value of I to 1.

Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. DATA DIVISION. WORKING-STORAGE SECTION. 01 ARR. 02 A PIC 99 OCCURS 5 TIMES INDEXED BY I. 77 K PIC 99. PROCEDURE DIVISION. MP. DISPLAY "ENTER THE ELEMENTS :". PERFORM AP VARYING I FROM 1 BY 1 UNTIL I>5. DISPLAY "ENTER THE ELEMENT TO BE SEARCHED:". ACCEPT K. SET I TO 1. SEARCH A AT END DISPLAY "ELEMENT NOT FOUND" WHEN K=A(I) DISPLAY "ELEMENT FOUND.". STOP RUN. AP. ACCEPT A(I).

Output:ENTER THE ELEMENTS :94876ENTER THE ELEMENT TO BE SEARCHED:4ELEMENT FOUND.

Conclusion: Accept the elements in the array and after the element to be searched is

entered using the SEARCH reserved word and in that statement the element is found or not are included and through the internal process the result is displayed as element is found.

Page 26: COBOL  Lab

Sheet No: 26

Program No: 16

Aim: Binary search using Indexed table.

Analysis: Create the array which is indexed with I. To search the element in indexed table uses the reserved word SEARCH ALL. Before start the search process set the value of I to 1.

Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. DATA DIVISION. WORKING-STORAGE SECTION. 01 ARR. 02 A PIC 99 OCCURS 5 TIMES ASCENDING KEY IS K INDEXED BY I. 77 K PIC 99. PROCEDURE DIVISION. MP. DISPLAY "ENTER THE ELEMENTS:". PERFORM AP VARYING I FROM 1 BY 1 UNTIL I>5. DISPLAY "ENTER THE KEY:". ACCEPT K. SET I TO 1.

SEARCH ALL A AT END DISPLAY "ELEMENT NOT FOUND" WHEN K=A(I) DISPLAY "ELEMENT FOUND.".

STOP RUN. AP. ACCEPT A(I).

Output:

ENTER THE ELEMENTS:57629ENTER THE KEY:6ELEMENT FOUND.

Conclusion: Accept the elements in array and after the element to be found is entered

using the SEARCH ALL reserved word and in that statement, the element is found or not is included and the final result is displayed as the element is found.

Page 27: COBOL  Lab

Sheet No: 27

Program No: 17

Aim: Addition of two matrices.

Analysis: Create three matrices for entering the elements two and to store the addition of those two the other. Add the elements in the same position and store the result in the same position in the third matrix.

Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. DATA DIVISION. WORKING-STORAGE SECTION. 01 ARR. 02 AA OCCURS 2 TIMES. 03 A PIC 99 OCCURS 2 TIMES. 03 B PIC 99 OCCURS 2 TIMES. 03 C PIC 99 OCCURS 2 TIMES. 77 I PIC 9. 77 J PIC 9. 77 K PIC 9. 77 T PIC 99 VALUE 0. PROCEDURE DIVISION. MP. DISPLAY "ENTER THE FIRST MATRIX ELEMENTS:". PERFORM AP VARYING I FROM 1 BY 1 UNTIL I>2 AFTER J FROM 1 BY 1 UNTIL J>2. DISPLAY "ENTER THE SECOND MATRIX ELEMENTS:". PERFORM BP VARYING I FROM 1 BY 1 UNTIL I>2 AFTER J FROM 1 BY 1 UNTIL J>2. DISPLAY (1, 1) ERASE. DISPLAY (1, 5) "FIRST". DISPLAY (2, 5) "------". DISPLAY (1, 18) "SECOND". DISPLAY (2, 18) "--------". DISPLAY (1, 30)"MATRIX ADDITION." DISPLAY (2, 30)"-------------------------". PERFORM ADP VARYING I FROM 1 BY 1 UNTIL I>2 AFTER J FROM 1 BY 1 UNTIL J>2. STOP RUN. AP. ACCEPT A(I, J).

BP. ACCEPT B(I, J).

Page 28: COBOL  Lab

Sheet No: 28

MOVE 0 TO C(I, J). ADP. COMPUTE LIN = I * 2 + 1. COMPUTE COL = J * 3 + 2. DISPLAY (LIN, COL)A(I, J). COMPUTE COL = J * 3 + 15. DISPLAY (LIN, COL)B(I, J). COMPUTE C(I, J) = A(I, J) + B(I, J). COMPUTE COL = J * 3 + 30. DISPLAY (LIN, COL)C(I, J). MOVE 0 TO C(I, J).

Out Put:

ENTER THE FIRST MATRIX ELEMENTS:1234ENTER THE SECOND MATRIX ELEMENTS:5678 FIRST SECOND MATRIX ADDITION: ------------ ------------- -----------------------------

01 02 05 06 06 0803 04 07 08 10 12

Conclusion: Accept the first matrix and second matrices elements and the addition is

performed and the output is shown as the first, second and the result matrix are printed.

Page 29: COBOL  Lab

Sheet No: 29

Program No: 18

Aim: Multiplication of two matrices.

Analysis: Create three matrices for entering the elements two and to store the multiplication of those two the other. Multiply the elements in the first and second matrices following the matrix multiplication rules i.e., multiplying the rows of the first matrix to the columns of the second one and summing them. For this the number of columns in the firs matrix must be equal to the number of rows in the second one.

Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. DATA DIVISION. WORKING-STORAGE SECTION. 01 ARR. 02 AA OCCURS 2 TIMES. 03 A PIC 99 OCCURS 2 TIMES. 03 B PIC 99 OCCURS 2 TIMES. 03 C PIC 99 OCCURS 2 TIMES. 77 I PIC 9. 77 J PIC 9. 77 K PIC 9. PROCEDURE DIVISION. MP. DISPLAY "ENTER THE FIRST MATRIX ELEMENTS:". PERFORM AP VARYING I FROM 1 BY 1 UNTIL I>2 AFTER J FROM 1 BY 1 UNTIL J>2. DISPLAY "ENTER THE SECOND MATRIX ELEMENTS:". PERFORM BP VARYING I FROM 1 BY 1 UNTIL I>2 AFTER J FROM 1 BY 1 UNTIL J>2. DISPLAY (1, 1) ERASE. DISPLAY (1, 5) "FIRST". DISPLAY (2, 5) "------". DISPLAY (1, 18) "SECOND". DISPLAY (2, 18) "--------". DISPLAY (1, 30)"MATRIX MULTIPLICATION:". DISPLAY (2, 29)"-----------------------". PERFORM MULP VARYING I FROM 1 BY 1 UNTIL I>2 AFTER J FROM 1 BY 1 UNTIL J>2 AFTER K FROM 1 BY 1 UNTIL K>2. PERFORM ADP VARYING I FROM 1 BY 1 UNTIL I>2 AFTER J FROM 1 BY 1 UNTIL J>2. STOP RUN. AP.

Page 30: COBOL  Lab

Sheet No: 30

ACCEPT A(I, J). BP. ACCEPT B(I, J). MOVE 0 TO C(I, J). ADP. COMPUTE LIN = I * 2 + 1. COMPUTE COL = J * 3 + 2. DISPLAY (LIN, COL)A(I, J). COMPUTE COL = J * 3 + 15. DISPLAY (LIN, COL)B(I, J). COMPUTE COL = J * 3 + 30. DISPLAY (LIN, COL)C(I, J). MULP. COMPUTE C(I, J) = C(I, J) + A(I, K) * B(K, J). Output:

ENTER THE FIRST MATRIX ELEMENTS:1234ENTER THE SECOND MATRIX ELEMENTS:5678 FIRST SECOND MATRIX MULTIPLICATION: ------------ ------------- ----------------------------------------

01 02 05 06 19 2203 04 07 08 43 50

Conclusion: The elements are accepted in the two matrices simultaneously at the same

time. The multiplication is done using another inner loop following the matrix multiplication rules and last the three matrices are printed.

Page 31: COBOL  Lab

Sheet No: 31

Program No: 19

Aim: Program to store the product details in a file named ITEM.DAT.

Analysis: In this program we can create a file by the COBOL program to write into the file. We have to name the file and records of the file and later during the execution i.e., during the runtime we can enter the records into the file through the keyboard and can store in the file. But we can display the contents of the file by another program. Source Code: IDENTIFICATION DIVISION. PROGRAM-ID. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL SELECT ITEM-FILE ASSIGN TO DISK ORGANIZATION IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD ITEM-FILE LABEL RECORDS ARE STANDARD VALUE OF FILE-ID IS "ITEM.DAT" DATA RECORD IS ITEM-REC. 01 ITEM-REC. 02 ICODE PIC 9(4). 02 INAME PIC X(10). 02 IQTY PIC 9(4). 02 IRATE PIC 9(5)V99. WORKING-STORAGE SECTION. PROCEDURE DIVISION. MAIN-PARA. OPEN OUTPUT ITEM-FILE. PERFORM PARA-1 5 TIMES. CLOSE ITEM-FILE. STOP RUN. PARA-1. DISPLAY (1 , 1) ERASE. DISPLAY (9 , 15) "ENTER THE ITEM CODE:". ACCEPT (9 , 45) ICODE WITH PROMPT. DISPLAY (11 , 15) "ENTER THE ITEM NAME:". ACCEPT (11 , 45) INAME WITH PROMPT. DISPLAY (13 , 15) "ENTER THE ITEM QUANTITY:". ACCEPT (13 , 45) IQTY WITH PROMPT. DISPLAY (15 , 15) "ENTER THE ITEM RATE:". ACCEPT (15 , 45) IRATE WITH PROMPT. WRITE ITEM-REC.

Page 32: COBOL  Lab

Sheet No: 32

Output:

ENTER THE ITEM CODE: __45 ENTER THE ITEM NAME: cosmetics ENTER THE ITEM QUANTITY: __10 ENTER THE ITEM RATE: ___35.50

………………………………………………………………………………………………………………………………………………

ENTER THE ITEM CODE: _142 ENTER THE ITEM NAME: homeneeds ENTER THE ITEM QUANTITY: __50 ENTER THE ITEM RATE: ___12.30

Conclusion:From the program we observe that the file is created and the five records

of the five products are entered into the file and are stored in the file.

Page 33: COBOL  Lab

Sheet No: 33

Program No: 20

Aim: Program to display the product details stored in a file named ITEM.DAT.

Analysis: In this program we can display a file by the COBOL program to read from the file. We have to read the name of file and records of the file and later during the execution i.e., during the runtime we can display the records from the file one by one and have a counter variable and during the end of the file we can quit from the execution. Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL SELECT ITEM-FILE ASSIGN TO DISK ORGANIZATION IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD ITEM-FILE LABEL RECORDS ARE STANDARD VALUE OF FILE-ID IS "ITEM.DAT" DATA RECORD IS ITEM-REC. 01 ITEM-REC. 02 ICODE PIC 9(4). 02 INAME PIC X(10). 02 IQTY PIC 9(4). 02 IRATE PIC 9(5)V99. WORKING-STORAGE SECTION. 01 CH PIC X VALUE "N". PROCEDURE DIVISION. MAIN-PARA. OPEN INPUT ITEM-FILE. READ ITEM-FILE AT END MOVE "Y" TO CH. PERFORM PARA-1 UNTIL CH = "Y" OR "y". CLOSE ITEM-FILE. STOP RUN. PARA-1. DISPLAY (1 , 1) ERASE. DISPLAY (9 , 15) "ITEM CODE:". DISPLAY (9 , 45) ICODE. DISPLAY (11 , 15) "ITEM NAME:". DISPLAY (11 , 45) INAME. DISPLAY (13 , 15) "ITEM QUANTITY:". DISPLAY (13 , 45) IQTY.

Page 34: COBOL  Lab

Sheet No: 34

DISPLAY (15 , 15) "ITEM RATE:". DISPLAY (15 , 45) IRATE. STOP " ". DISPLAY (17 , 40) "PRESS ENTER TO CONTINUE...". READ ITEM-FILE AT END MOVE "Y" TO CH.

Output:

ITEM CODE: 0045 ITEM NAME: cosmetics ITEM QUANTITY: 0010 ITEM RATE: 00035.50

PRESS ENTER TO CONTINUE…………………………………………………………………………………………………………………………………………………

ITEM CODE: 0142 ITEM NAME: homeneeds ITEM QUANTITY: 0050 ITEM RATE: 00012.30

PRESS ENTER TO CONTINUE…

Conclusion:From the program we observe that the file created is opened and the five

records of the five products are read from the file and are displayed on the screen.

Page 35: COBOL  Lab

Sheet No: 35

Program No: 21

Aim: Program to store the account details in an indexed file named ACCOUNT.DAT.

Analysis: In this program we can create an indexed file by the COBOL program to write into the file. We have to name the file and records of the file and set one field as the key to access the file records and later during the execution i.e., during the runtime we can enter the records into the file through the keyboard and can store in the file. But we can display the contents of the file by another program. Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL SELECT ACC-FILE ASSIGN TO DISK ORGANIZATION IS INDEXED RECORD KEY IS ACC-CODE ACCESS MODE IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD ACC-FILE LABEL RECORDS ARE STANDARD VALUE OF FILE-ID IS "ACCOUNT.DAT" DATA RECORD IS ACC-REC. 01 ACC-REC. 02 ACC-CODE PIC 9(4). 02 ACC-NAME PIC X(20). 02 ACC-ADDR PIC X(50). 02 ACC-AMT PIC 9(7)V99. WORKING-STORAGE SECTION. PROCEDURE DIVISION. MAIN-PARA. OPEN OUTPUT ACC-FILE. PERFORM PARA-1 5 TIMES. CLOSE ACC-FILE. STOP RUN. PARA-1. DISPLAY (1 , 1) ERASE. DISPLAY (9 , 15) "ENTER THE ACCOUNT CODE:". ACCEPT (9 , 45) ACC-CODE WITH PROMPT. DISPLAY (11 , 15) "ENTER THE ACCOUNTEE NAME:". ACCEPT (11 , 45) ACC-NAME WITH PROMPT. DISPLAY (13 , 15) "ENTER THE ACCOUNTEE ADDRESS:". ACCEPT (13 , 45) ACC-ADDR WITH PROMPT.

Page 36: COBOL  Lab

Sheet No: 36

DISPLAY (15 , 15) "ENTER THE ACCOUNT BALANCE:". ACCEPT (15 , 45) ACC-AMT WITH PROMPT. WRITE ACC-REC.

Output:

ENTER THE ACCOUNT CODE: 1002 ENTER THE ACCOUNTEE NAME: raja rao ENTER THE ACCOUNTEE ADDRESS: malakpet,hyd ENTER THE ACCOUNT BALANCE: __50000.48

…………………………………………………………..…………………………………………………………..…………………………………………………………..

ENTER THE ACCOUNT CODE: 1020 ENTER THE ACCOUNTEE NAME: krishna rao ENTER THE ACCOUNTEE ADDRESS: ameerpet,hyd ENTER THE ACCOUNT BALANCE: __10100.56

Conclusion:From the program we observe that the file is created as indexed and the

five records of the five accountees are entered into the file and are stored in the file.

Page 37: COBOL  Lab

Sheet No: 37

Program No: 22

Aim: Program to display the accountees details stored in an indexed file named ACCOUNT.DAT.

Analysis: In this program we can display an indexed file by the COBOL program to read from the file. We have to read the name of file and records of the file and later during the execution i.e., during the runtime we can display the records from the file one by one and have a counter variable and during the end of the file we can quit from the execution. Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL SELECT ACC-FILE ASSIGN TO DISK ORGANIZATION IS INDEXED RECORD KEY IS ACC-CODE ACCESS MODE IS SEQUENTIAL. DATA DIVISION. FILE SECTION. FD ACC-FILE LABEL RECORDS ARE STANDARD VALUE OF FILE-ID IS "ACCOUNT.DAT" DATA RECORD IS ACC-REC. 01 ACC-REC. 02 ACC-CODE PIC 9(4). 02 ACC-NAME PIC X(20). 02 ACC-ADDR PIC X(50). 02 ACC-AMT PIC 9(7)V99. WORKING-STORAGE SECTION. 01 CH PIC X VALUE "N". PROCEDURE DIVISION. MAIN-PARA. OPEN INPUT ACC-FILE. READ ACC-FILE AT END MOVE "Y" TO CH. PERFORM PARA-1 UNTIL CH = "Y" OR "y". CLOSE ACC-FILE. STOP RUN. PARA-1. DISPLAY (1 , 1) ERASE. DISPLAY (9 , 15) "ACCOUNT CODE:". DISPLAY (9 , 45) ACC-CODE. DISPLAY (11 , 15) "ACCOUNTEE NAME:". DISPLAY (11 , 45) ACC-NAME.

Page 38: COBOL  Lab

Sheet No: 38

DISPLAY (13 , 15) "ACCOUNTEE ADDRESS:". DISPLAY (13 , 45) ACC-ADDR. DISPLAY (15 , 15) "ACCOUNT BALANCE:". DISPLAY (15 , 45) ACC-AMT. STOP " ". DISPLAY (17 , 40) "PRESS ENTER TO CONTINUE...". READ ACC-FILE AT END MOVE "Y" TO CH.

Output:

ACCOUNT CODE: 1002 ACCOUNTEE NAME: raja rao ACCOUNTEE ADDRESS: malakpet,hyd ACCOUNT BALANCE: 0050000.48

…………………………………………………………..…………………………………………………………..…………………………………………………………..

ACCOUNT CODE: 1020 ACCOUNTEE NAME: krishna rao ACCOUNTEE ADDRESS: ameerpet,hyd ACCOUNT BALANCE: 0010100.56

Conclusion:From the program we observe that the file created is opened and the five

records of the five accounts are read from the file and are displayed on the screen.

Page 39: COBOL  Lab

Sheet No: 39

Program No: 23

Aim: Program to store the customer details in a relative file named CUSTOMER.DAT.

Analysis: In this program we can create a relative file by the COBOL program to write into the file. We have to name the file and records of the file and set one field as the key to access the file records and later during the execution i.e., during the runtime we can enter the records into the file through the keyboard and can store in the file. But we can display the contents of the file by another program. Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL SELECT CUST-FILE ASSIGN TO DISK ORGANIZATION IS RELATIVE RELATIVE KEY IS REC-NO ACCESS MODE IS DYNAMIC. DATA DIVISION. FILE SECTION. FD CUST-FILE LABEL RECORDS ARE STANDARD VALUE OF FILE-ID IS "CUSTOMER.DAT" DATA RECORD IS CUST-REC. 01 CUST-REC. 02 C-NO PIC 9(4). 02 C-NAME PIC X(20). 02 DUE PIC 9(7)V99. WORKING-STORAGE SECTION. 01 REC-NO PIC 9(3) VALUE 0. PROCEDURE DIVISION. MAIN-PARA. OPEN OUTPUT CUST-FILE. PERFORM PARA-1 5 TIMES. CLOSE CUST-FILE. STOP RUN. PARA-1. ADD 1 TO REC-NO. DISPLAY (1 , 1) ERASE. DISPLAY (9 , 15) "ENTER THE CUSTOMER NUMBER:". ACCEPT (9 , 45) C-NO WITH PROMPT. DISPLAY (11 , 15) "ENTER THE CUSTOMER NAME:". ACCEPT (11 , 45) C-NAME WITH PROMPT.

Page 40: COBOL  Lab

Sheet No: 40

DISPLAY (13 , 15) "ENTER THE DUE AMOUNT:". ACCEPT (13 , 45) DUE WITH PROMPT. WRITE CUST-REC.

Output:

ENTER THE CUSTOMER NUMBER: ___1 ENTER THE CUSTOMER NAME: ramarao ENTER THE DUE AMOUNT: ___1002.34

…………………………………………………….…………………………………………………….…………………………………………………….

ENTER THE CUSTOMER NUMBER: ___5 ENTER THE CUSTOMER NAME: raghava ENTER THE DUE AMOUNT: ___1254.36

Conclusion:From the program we observe that the file is created as relative and the

five records of the five customers are entered into the file and are stored in the file.

Page 41: COBOL  Lab

Sheet No: 41

Program No: 24

Aim: Program to display the customer details stored in a relative file named ACCOUNT.DAT.

Analysis: In this program we can display a relative file by the COBOL program to read from the file. We have to read the name of file and records of the file and later during the execution i.e., during the runtime we can display the records from the file one by one by giving the customer number and can quit out of the execution only if we enter N option at the prompt for continuation. Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL SELECT CUST-FILE ASSIGN TO DISK ORGANIZATION IS RELATIVE RELATIVE KEY IS REC-NO ACCESS MODE IS DYNAMIC. DATA DIVISION. FILE SECTION. FD CUST-FILE LABEL RECORDS ARE STANDARD VALUE OF FILE-ID IS "CUSTOMER.DAT" DATA RECORD IS CUST-REC. 01 CUST-REC. 02 C-NO PIC 9(4). 02 C-NAME PIC X(20). 02 DUE PIC 9(7)V99. WORKING-STORAGE SECTION. 01 REC-NO PIC 9(3) VALUE 0. 01 F PIC X VALUE "Y". 01 CH PIC X VALUE "Y". PROCEDURE DIVISION. MAIN-PARA. OPEN INPUT CUST-FILE. PERFORM PARA-1 UNTIL CH = "N" OR "n". CLOSE CUST-FILE. STOP RUN. PARA-1. ADD 1 TO REC-NO. DISPLAY (1 , 1) ERASE. DISPLAY (9 , 15) "ENTER THE CUSTOMER NUMBER:".

Page 42: COBOL  Lab

Sheet No: 42

ACCEPT (9 , 45) REC-NO WITH PROMPT. READ CUST-FILE INVALID KEY MOVE "N" TO F. IF F="N" PERFORM PARA-2 ELSE PERFORM PARA-3 PERFORM PARA-4. PARA-2. DISPLAY (13 , 25) "INVALID CUSTOMER NUMBER". PARA-3. DISPLAY (13 , 15) "CUSTOMER NAME:". DISPLAY (13 , 45) C-NAME. DISPLAY (15 , 15) "DUE AMOUNT:". DISPLAY (15 , 45) DUE. PARA-4. DISPLAY (20 , 10) "ANY MORE[Y/N]:". ACCEPT (20 , 30) CH WITH AUTO-SKIP.

Output:

ENTER THE CUSTOMER NUMBER: __1

CUSTOMER NAME: ramarao DUE AMOUNT: 000100234

ANY MORE[Y/N]: Y………………………………………………..………………………………………………..………………………………………………..

ENTER THE CUSTOMER NUMBER: __5

CUSTOMER NAME: raghava DUE AMOUNT: 000125436

ANY MORE[Y/N]:N

Conclusion:From the program we observe that the relative file created is opened and

the five records of the five customers are read from the file and are displayed on the screen by reading the customer number.

Page 43: COBOL  Lab

Sheet No: 43

Program No: 25

Aim: Program to merge the files DEPT1.DAT, DEPT2.DAT into DEPT3.DAT.

Analysis: In this program we can merge two data files created already with some records in it and display the merged file one by one in a sequence. Here we merge the first and second files into a third file and display records in the third file that is the merged file one by one at runtime. Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT DEPT1-FILE ASSIGN TO DISK ORGANIZATION IS LINE SEQUENTIAL. SELECT DEPT2-FILE ASSIGN TO DISK ORGANIZATION IS LINE SEQUENTIAL. SELECT DEPT3-FILE ASSIGN TO DISK ORGANIZATION IS LINE SEQUENTIAL. SELECT WORKING-FILE ASSIGN TO DISK ORGANIZATION IS LINE SEQUENTIAL. DATA DIVISION. FILE SECTION. FD DEPT1-FILE LABEL RECORDS ARE STANDARD VALUE OF FILE-ID IS "DEPT1.DAT" DATA RECORD IS DEPT1-REC. 01 DEPT1-REC. 02 AENO PIC 9(3). 02 AENA PIC X(15). 02 ABS PIC 9(7)V99. 02 AHRA PIC 9(7)V99. 02 ADA PIC 9(7)V99. FD DEPT2-FILE LABEL RECORDS ARE STANDARD VALUE OF FILE-ID IS "DEPT2.DAT" DATA RECORD IS DEPT2-REC. 01 DEPT2-REC. 02 BENO PIC 9(3). 02 BENA PIC X(15). 02 BBS PIC 9(7)V99. 02 BHRA PIC 9(7)V99. 02 BDA PIC 9(7)V99.

Page 44: COBOL  Lab

Sheet No: 44

FD DEPT3-FILE LABEL RECORDS ARE STANDARD VALUE OF FILE-ID IS "DEPT3.DAT" DATA RECORD IS DEPT3-REC. 01 DEPT3-REC. 02 CENO PIC 9(3). 02 CENA PIC X(15). 02 CBS PIC 9(7)V99. 02 CHRA PIC 9(7)V99. 02 CDA PIC 9(7)V99. SD WORKING-FILE DATA RECORD IS WORKING-REC. 01 WORKING-REC. 02 WENO PIC 9(3). 02 WENA PIC X(15). 02 WBS PIC 9(7)V99. 02 WHRA PIC 9(7)V99. 02 WDA PIC 9(7)V99. WORKING-STORAGE SECTION. 01 CH PIC X VALUE "N". PROCEDURE DIVISION. MAIN-PARA. MERGE WORKING-FILE ON ASCENDING KEY WENO USING DEPT1-FILE DEPT2-FILE GIVING DEPT3-FILE. OPEN INPUT DEPT3-FILE. READ DEPT3-FILE AT END MOVE "Y" TO CH. PERFORM PARA-1 UNTIL CH = "Y". STOP RUN. PARA-1. DISPLAY (1 , 1) ERASE. DISPLAY (9 , 15) "EMPLOYEE NO:". DISPLAY (9 , 45) CENO. DISPLAY (11 , 15) "EMPLOYEE NAME:". DISPLAY (11 , 45) CENA. DISPLAY (13 , 15) "BASIC SALARY:". DISPLAY (13 , 45) CBS. DISPLAY (15 , 15) "H.R.A.:". DISPLAY (15 , 45) CHRA. DISPLAY (17 , 15) "D.A.:". DISPLAY (17 , 45) CDA. DISPLAY (20 , 10) " ". STOP "PRESS ENTER TO CONTINUE...". READ DEPT3-FILE AT END MOVE "Y" TO CH.

Page 45: COBOL  Lab

Sheet No: 45

Output:

EMPLOYEE NO: 01 EMPLOYEE NAME: Amar BASIC SALARY: 0005000 H.R.A.: 000000500 D.A.: 000000050 PRESS ENTER TO CONTINUE...

…………………………………………………….…………………………………………………….…………………………………………………….

EMPLOYEE NO: 06 EMPLOYEE NAME: Feroj BASIC SALARY: 0004000 H.R.A.: 000000200 D.A.: 000000020 PRESS ENTER TO CONTINUE...

Conclusion:From the above program we observe that the first two files are merged in a

third file and are displayed on the screen one by one until the end of the file.

Page 46: COBOL  Lab

Sheet No: 46

Program No: 26

Aim: Program to sort a file ACCOUNT.DAT into the file SACCOUNT.DAT.

Analysis: In this program we can we can sort a file which is already created into another file. Here in this program the records are sorted according to their account number in the ascending order and are stored in the other file. But we can display the sorted records by another program to display the records of the file. Source Code:

IDENTIFICATION DIVISION. PROGRAM-ID. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT ACCOUNT-FILE ASSIGN TO DISK ORGANIZATION IS LINE SEQUENTIAL. SELECT SACCOUNT-FILE ASSIGN TO DISK ORGANIZATION IS LINE SEQUENTIAL. SELECT WORKING-FILE ASSIGN TO DISK ORGANIZATION IS LINE SEQUENTIAL. DATA DIVISION. FILE SECTION. FD ACCOUNT-FILE LABEL RECORDS ARE STANDARD VALUE OF FILE-ID IS "ACCOUNT.DAT" DATA RECORD IS ACCOUNT-REC. 01 ACCOUNT-REC. 02 ACC-NO PIC 9(5). 02 ACC-NAME PIC X(20). 02 ACC-DATE PIC X(8). 02 TRAN-DATE PIC X(8). FD SACCOUNT-FILE LABEL RECORDS ARE STANDARD VALUE OF FILE-ID IS "SACCOUNT.DAT" DATA RECORD IS SACCOUNT-REC. 01 SACCOUNT-REC. 02 SACC-NO PIC 9(5). 02 SACC-NAME PIC X(20). 02 SACC-DATE PIC X(8). 02 STRAN-DATE PIC X(8). SD WORKING-FILE. 01 WORKING-REC. 02 WACC-NO PIC 9(5). 02 WACC-NAME PIC X(20).

Page 47: COBOL  Lab

Sheet No: 47

02 WACC-DATE PIC X(8). 02 WTRAN-DATE PIC X(8). WORKING-STORAGE SECTION. PROCEDURE DIVISION. MAIN-PARA. SORT WORKING-FILE ON ASCENDING KEY WACC-NO USING ACCOUNT-FILE GIVING SACCOUNT-FILE. STOP RUN.

Output:

(Displayed using the program to display the records of the file)

ACCOUNT NO: 00001 ACCOUNT NAME: AMAR ACCOUNT DATE: 11.02.06 TRANSACTION DATE: 12.03.06

PRESS ENTER TO CONTINUE………………………………………………….……………………………………………….……………………………………………....

ACCOUNT NO: 00005 ACCOUNT NAME: FEROJ ACCOUNT DATE: 10.10.06 TRANSACTION DATE: 03.12.06

PRESS ENTER TO CONTINUE…

Conclusion:From the above program we can observe that the records in one file are

sorted and are stored in the other file according to the account number. They are displayed using the other program to display the records of the file.