CTP 108 - Computer Programming For Business
Midterm 1

21st Nov, 1996
ANSWER KEY



Q1. Write the COBOL PROCEDURE DIVISION statement (or set of statements) to calculate following expressions :

(10 pts)
COMPUTE R = (A*A - B*B) / (D - C) - C.

(10 pts)

           MOVE ZERO TO R.
           PERFORM CALC VARYING I FROM 1 BY 1 UNTIL I > 11.
           ........
           ........
       CALC.
           ADD I*I TO R.

(USING the PERFORM stmt is not necessary; any correct loop will be accepted)

Q2. Trace the following COBOL code and determine what values will be displayed for FIELD-A, FIELD-B and FIELD-C : (20 pts)
     0        1         2         3         4         5         6         7         8
     1234567890123456789012345678901234567890123456789012345678901234567890123456789
            PROCEDURE DIVISION.
            FIRST-PARAG.
                MOVE ZEROS TO FIELD-A FIELD-B.
                PERFORM SECOND-PARAG THRU THIRD-PARAG.
                PERFORM SECOND-PARAG.
                DISPLAY FIELD-A, FIELD-B, FIELD-C.
                STOP RUN.
            SECOND-PARAG.
                ADD 10 TO FIELD-A
                ADD 20 TO FIELD-B.
            THIRD-PARAG.
                MULTIPLY FIELD-A BY FIELD-B GIVING FIELD-C.
                DIVIDE FIELD-B BY FIELD-A GIVING FIELD-D.

FIELD A FIELD B FIELD C
     20      40    200


Q3. Write PROCEDURE DIVISION code for the following flowchart: ( 30 pts)


           COMPUTE N = B * 2.
           IF A > B  COMPUTE N = 2 * A.
           MOVE ZERO TO SUM-OF-ORDERS. (Also can be initialized with VALUE clause)
           OPEN INPUT ORDERS.
           MOVE ZERO TO N-REC.
           PERFORM READ-AND-ADD UNTIL N-REC > N.
           DISPLAY "TOTAL ORDERS =" SUM-OF-ORDERS.
           CLOSE ORDERS.
           STOP RUN.

       READ-AND-ADD.
           READ ORDERS AT END MOVE N+1 TO N-REC
                              EXIT.
           ADD AMOUNT TO SUM-OF-ORDERS.
           ADD 1 TO N-REC. 

           
             

Q4. Find and identify the SYNTAX errors in the following COBOL code : (You can mark the errors on the program source). (30 pts)

     0        1         2         3         4         5         6         7         8
     1234567890123456789012345678901234567890123456789012345678901234567890123456789
            IDENTIFICATION DIVISION.
            PROGRAM-ID. PGM-WITH-ERRORS.

            ENVIRONMENT DIVISION.
            CONFIGURATION-SECTION. ( The "-" shouldn't be there! )
            SOURCE-COMPUTER. PC.
            OBJECT-COMPUTER. PC.
            INPUT-OUTPUT SECTION.
            FILE-CONTROL.
                SELECT EMPLOYEE-FILE ASSIGN TO DISK. ( No "Actual File Name" is specified! 
                                                       Something like "EMPFILE.DAT" is missing.   
                SELECT REPORT-FILE ASSIGN TO PRINTER.  
            DATA DIVISION.
            FILE-SECTION. (The "-" shouldn`t be there)
            FD  EMPLOYEE-FILE.
                EMPLOYEE-FILE-REC. ( A "01" level record description needed!)
                02 EMP-NAME          PIC X(16).
                02 EMP-NUMBER        PIC XXXX999. ("X" and "9" Pictures cannot be mixed!)
                02 FILLER            PIC X(20).
            ("FD" Statement for "REPORT-FILE" is missing!)  
            WORKING-STORAGE SECTION.
            02  EOF-FLAG             PIC X VALUE ZERO. (Should be either "01" or "77" level.)

            01  HEADER-LINE.
                02 FILLER            PIC X(29) VALUE ALL “-“.

            77  TOTAL-RECORDS        PIC 99 VALUE BLANKS.(Should be "ZEROS" or any other decimal
                                                          integer!)

            PROCEDURE DIVISION.
            (Missing Paragraph name!)
                OPEN INPUT REPORT-FILE.( A printer file cannot be opened as "INPUT")
                WRITE  REPORT-FILE FROM HEADER-LINE.
                       (A "Record Name" should be given in a WRITE statement, not a "file name"!)

                OPEN INPUT EMPLOYEE-FILE.

            READ-ALL-RECORDS.
                READ EMPLOYEE-FILE AT END
                               CLOSE ALL FILES (No such COBOL stmt. Should be 
                                                  "CLOSE EMPLOYEE-FILE REPORT-FILE.")
                               DISPLAY “NUMBER OF RECS” NUMBER-OF-RECORDS(Variable NOT declared!)
                               STOP RUN.
                ADD 1 TO NUMBER-OF-RECORDS.(Variable NOT declared!)
                GO TO READ-ALL-RECORDS.


BONUS QUESTION. (10 pts)

B1. Consider the following COBOL code. The programmer intended to write this code to calculate total costs of items to customers; such that, if the total amount of an order is greater than 20,000,000 TL, the program should calculate a 10 % discount, otherwise a zero discount.

When the programmer runs the program, the shown surprising and wrong output is produced on the screen.

Can you find why the program produces this wrong output?(Assume that all variable declarations have been made properly and correctly.)
The code :
     0        1         2         3         4         5         6         7
     1234567890123456789012345678901234567890123456789012345678901234567890123456789
                IF AMOUNT-ORDERED-THISWEEK < 20000000
                   MOVE ZEROS TO CUSTOMER-DISCOUNT
                ELSE
                    COMPUTE CUSTOMER-DISCOUNT = AMOUNT-ORDERED-THISWEEK *0.01.

                COMPUTE NET = AMOUNT-ORDERED-THISWEEK - CUSTOMER-DISCOUNT.
                DISPLAY AMOUNT-ORDERED-THISWEEK CUSTOMER-DISCOUNT NET.


Output Produced :

     Amount Ordered      Discount  Net

          30000000             3000000     27000000
          40000000             4000000     36000000  
          10000000                   0     36000000   (Incorrect "NET"`s.)
          50000000             5000000     45000000
          12000000                   0     45000000   (Incorrect "NET"`s.)
The reason actually is very very SIMPLE! The "full stop" at the end of "COMPUTE CUSTOMER-
DISCOUNT=" statement is typed on column 73 and therefore not SEEN by the compiler. For this 
reason, the IF statements ELSE part is terminated by the "COMPUTE-NET=" statement instead of
the intended "COMPUTE CUSTOMER-DISCOUNT=" statement.

The NET variable is calculated ONLY for orders > 20000000. When the code finds a zero discount amount, it displays the NET value that was calculated for the last discounted record.
Back to first page...