308-208 - Computers in Engineering - Previous Midterms

Midterm Winter 1996


Question 1. (6 minutes, 15 points)

What will the following program output?

program question1
implicit none
integer :: a, c, d
real ::  b, e, f
a = 38/15
b = 38.0/15.0
c = (a*b)**3
d = 13.5/3*3
e =  mod(c,d)
f =  16**(0.25)
print *, e, c, d, f, a**4, b
stop
end program question1


Question 2: (6 minutes, 10 points)

What does this program print?

program question2
implicit none
real :: w, v, u
integer :: z, y, x, m
y = 17./5
v = 3**(2+4)/5
u = 1.1E1+1.1E-1
m = 1.2E1+0.000002E6
w = mod(m,y)
print *, w
print *, m , u
print *, y, v
stop
end program question2


Question 3: (11 minutes, 15 points)

What will the following program print, given the input data below.

Program Question3
implicit none
real :: I, J, K, L
integer :: A, B, C
interface   ! You can ignore this

subroutine THIS (U, V)   ! interface section
        implicit none
        integer, intent(in out) :: U
        integer, intent(in) :: V
end subroutine THIS

subroutine THAT ( X,Y )
        implicit none
        real, intent(in out) :: X
        real, intent(in) :: Y
end subroutine THAT
end interface   !  ELF90 wants it

!
! Program begins
!
A = 10
I = 0
B = 2
C = 4
K = 4.0
J = 4.0
L = 0.0

CALL THIS(B,C)
CALL THAT(J,K)
CALL THAT(L,3.0)
PRINT *,A,B,C
PRINT *,I,J,K,L
Stop
End Program Question3
!
!  End program, Start subs
!
SUBROUTINE THIS (U,V)
        implicit none
        integer, intent(in out) :: U
        integer, intent(in) :: V
        integer :: A
        U = V**2
        A = A+U+V
        RETURN
END SUBROUTINE THIS

SUBROUTINE THAT (X,Y)
        implicit none
        real, intent(in out) :: X
        real, intent(in) :: Y
        real :: I
        X= Y**3
        I= I+X+Y
        RETURN
END SUBROUTINE THAT


Question 4: (11 minutes, 15 points)

What does this program print?

     Program Question4
     implicit none
     integer :: i , j(100), k(100), a, b  ,n

     read *,n
     do i = 1,n
       read * ,j(i), k(i)
     end do
     do i = 1, n-1
       a=k(j(i))
       b=k(j(i+1))
       print *,i,a,b, (a+b)
     end do
     Stop
     End Program Question4

DATA :

6
3 15
5 12
6 18
1 10
2 14
4 16


Question 5: (11 minutes, 15 points)

What does this program print?

program test1
implicit none
       integer :: A, B
l1:    do a=8,19,4
l2:      do b=1,3
           if (mod(a,b) .ge. b/3) then
             if (a/4 .le. b+1) then
               print *, 'homer'
             else
               print *, 'marge'
             end if
           else
             print *, 'bart'
          end if
         end do l2
       end do l1
       stop
       end program test1


Question 5: (40 minutes, 33 points)

The results of an English test are many data records in the following format:

          Columns   1 - 20  Name
          Columns  21 - 22  Score - a 2 digit integer from 0 to 99 inclusive

Write a FORTRAN 90 program to draw a bar graph like the following mock
printout. The bar indicates the percentage of the students who falls in
that category. The number after the bar is the actual number of
students in that category.  Your program should also produce a
neat classlist of student names and marks - this can be
printed before or after the bar chart.


            10    20    30    40    50    60    70    80    90    100%
        . . . . . . . . . . . . . . . . . . . . . . . . . . . . . . .
        .
 0 - 50 . * * 15
        .
51 - 60 . * * * 30
        .
61 - 70 . * * * * * * * * * * * 105
        .
71 - 80 . * * * * * * * * * 90
        .
81 - 90 . * * * * * 45
        .
91 -100 . * * 15


.
WRITE your program, with Control Lines, neatly here:
(Use the back of pages if needed)


End of Midterm