CS 101 End Semester Examination

Model Answers

 

Q.1 a) There are actually 6 mistakes in the function.  1 mark for identifying each mistake with a maximum of 5 marks. (Any 5 may be given).

 

1)      Duplicate function declaration. Function name is declared to be real as well as result variable.

2)      Result variable cannot have intent attribute.

3)      Variable I is not declared.

4)      The name sum is used in more than one sense. Since sum is a variable the intrinsic function SUM cannot be used.

5)      1/ I is 0 for I > 1 due to integer division.

6)      Syntax error in implied do loop, should be enclosed in brackets (1/ I, I = 1,n).

 

b) Two marks each for outputs of first two print statements and 1 mark for the third.

Outputs

15, 10              (one mark for each output in correct order)

30, 30              (one mark for each output)

60, 60              (1 Mark)

 

Q.2

MODULE geometric

IMPLICIT NONE

TYPE :: point

REAL :: x, y

END TYPE point                                                                     (1 mark for defining type point)

TYPE :: circle

            TYPE(point) :: center

REAL :: radius                                      ( Give 1 mark if alternative representation used)

END TYPE circle                                                                                 (1 mark for circle)

TYPE :: triangle

            TYPE(point) ::  a, b, c

END TYPE triangle

TYPE :: quadrilateral

            TYPE(point) :: p, q, r, s                        ( Give one mark if alternative correct representations used)

END TYPE quadrilateral                                  (1 mark for both together, array of points may also be used)

INTERFACE area

MODULE PROCEDURE area_circle

MODULE PROCEDURE area_triangle

MODULE PROCEDURE area_quadrilateral

END INTERFACE                                                                              (1 mark, syntax should be correct)

PUBLIC :: area, circle, triangle, quadrilateral, point

PRIVATE ::  area_circle, area_triangle, area_quadrilateral                     (1 mark for specifying access)

CONTAINS

 

FUNCTION area_circle(c) RESULT(a)

TYPE(circle), INTENT(IN) :: c

REAL :: a

REAL, PARAMETER :: pi = 3.1415926

a = pi * c% radius ** 2

END FUNCTION area_circle                                                                                     (1 mark)

 

FUNCTION area_triangle(t) RESULT(a)

TYPE(triangle), INTENT(IN) :: t

REAL :: a, x, y, z, w

x = t%b%x – t%a%x

y = t%b%y – t%a%y

z = t%c%x – t%b%x

w = t%c%y – t%b%y

a = 0.5 * abs(x * w – y * z)

END FUNCTION area_triangle           (2 marks, give 1 mark if expression for area uses sin, sqrt etc.)

 

FUNCTION area_quadrilateral(q) RESULT(a)

TYPE(quadrilateral), INTENT(IN) :: q

REAL :: a, x, y, z, w

x = q%q%x – q%p%x

y = q%q%y – q%p%y

z = q%r%x – q%q%x

w = q%r%y – q%q%y

a = x * w – y * z                                                          Compute the signed area of two triangles and add

x = q%s%x – q%r%x

y = q%s%y – q%r%y

z = q%p%x – q%s%x

w = q%p%y – q%s%y

a = 0.5 * abs(a + x * w – y * z)

END FUNCTION area_quadrilateral               (2 marks, do not give marks for complicated expressions)

(Give marks only if for even integer coordinates, results are integer for triangles and quadrilaterals)

END MODULE geometric

 

Q.3 Recursive subroutine exclusive_or

4.         list => list_2

7.         list => list_1                                                                  (1 mark if both 4 and 7 are correct)

11.       list_1 => list_1%next                                                    (1 mark)

12.       CALL exclusive_or(list_1, list_2, list% next)     (1 mark)

15.       list_2 => list_2%next

16.       CALL exclusive_or(list_1, list_2, list% next)     (1 mark if both 15 and 16 are correct)

20.       CALL exclusive_or(list_1, list_2, list)                (1 mark)

 

Recursive subroutine select

4.         FUNCTION p(i) RESULT(l)                                       (1 mark)

9.         IF (p(list% value) ) THEN                                            (2 marks, 1 mark if list% value is correct )

10.       CALL select(list% next, p)                                            (1 mark)

13.       CALL select(list, p)                                                      (1 mark)

 

 

Q.4 a) 2 marks for method: keep an array of size 26 to keep a count of difference between number of occurrences of each letter in s_1 and s_2.  The strings are anagrams iff the difference is 0 for all letters. (Give 2 marks if any equivalent method used, 1 mark if method is correct but not linear time).

FUNCTION anagram(s_1, s_2) RESULT(l)                (result variable need not be used)

CHARACTER(LEN = *), INTENT(IN) :: s_1, s_2

LOGICAL :: l                                                               (1 mark for function and argument declaration)

INTEGER, DIMENSION(0:25) :: number                               

INTEGER :: i, j, k

IF ( LEN(s_1) /= LEN(s_2)) THEN                                                     (1 mark for checking lengths)

l = .FALSE.

ELSE

number = 0

DO i = 1,  LEN(s_1)

j = iachar(s_1(i : i)) – iachar(“a”)           (Give mark if intrinsic function name is incorrect but is explained)

k = iachar(s_2(i : i)) – iachar(“a”)                                              (1 mark for  correct computation)

number(j) = number(j) + 1

number(k) = number(k) – 1

END DO

ENDIF

l = COUNT(number /= 0) = = 0

END FUNCTION anagram

 

b) Again 2 marks for correct method. Find the rightmost character that is less than the character to its right.  Exchange it with the smallest character greater than it to its right and reverse the string to the right of this position. If there is no such character return all-blank string. Give 2 marks even if method is explained in words.

 

FUNCTION next(s_1) RESULT(s_2)

CHARACTER(LEN=*), INTENT(IN) :: s_1

CHARACTER (LEN = LEN(s_1)) :: s_2                     (1 mark for function and argument declaration)

INTEGER :: i, j, k

i = LEN(s_1) – 1

DO

IF (i  <= 0) EXIT

IF (s_1(i : i) < s_1(i+1 : i+1)) EXIT

i = i – 1                                                                       

END DO

IF ( i <= 0) THEN

s_2 = “ ”                                                          (1 mark for correctly finding i and returning blank)

RETURN

ELSE

DO j = LEN(s_1),  i+1, -1

IF (s_1(j : j) > s_1(i : i)) EXIT

END DO

s_2(1 :  i-1) = s_1(1 : i-1)

s_2(i : i) = s_1(j : j)

DO k = i+1,  LEN(s_1)

s_2(k : k) =  s_1(LEN(s_1) + i + 1 - k : LEN(s_1) + i + 1 - k)

END DO

s_2(LEN(s_1) + i + 1 - j : LEN(s_1) + i + 1 -j) = s_1(i : i)       (1 mark for finding j and reversing  string)

ENDIF                                                                                    

END FUNCTION next

 

 

Q.5 Main idea: Assume that the center is the origin and the planets are on the x-axis at time t = 0, i.e. at angle 0 or pi.  At time t, the ith planet will make an angle 2*pi*t / ti  + initial angle. For the planets to be in a straight line, their angles must differ by multiples of pi.  Therefore required t is the smallest number such that 2*pi*t*(1/ti – 1/tj) is a multiple of pi for all i /= j.  Note that ti may be taken negative if planets rotate in opposite direction. Also assume ti /= tj for i /= j.

(3 marks for correctly realizing required time t. Give only 2 marks if difference is taken to be a multiple of 2*pi rather than pi.  Give only 1 mark if it is assumed that the planets must be in the same straight line as initially.)

To compute t, compute k –1 differences 2/ti – 2/tj as rational numbers. Any k-1 differences (i,j) such that they form a spanning tree may be used. Most convenient is to use consecutive numbers ti, ti+1 or difference with a fixed number t1. The required number is then the smallest number such that multiplying each of these k-1 rational numbers by it gives an integral value. This is nothing but the lcm of all denominators divided by the gcd of the numerators, assuming each rational number is in reduced form.

(3 marks for correctly computing this. Note that marks may be given even if these ideas are stated in words.  You can cut marks if the ideas are not stated clearly or if they are not clear from the program.)

(Give only 1 mark if only lcm is computed and not the gcd. If they have assumed the same straight line as at t =0, the same computation has to be done with the original ti rather than the differences.)

(2 marks are for using appropriate subprograms in the program. At least 3 subprograms for reducing a rational, lcm and gcd would be required. Use of rational type is not required. It is okay if they have assumed rational operations and type definitions. Give marks if any two of the above subprograms have been written.)

(Remaining 2 marks are for correctness/ clarity of the program and subprograms.)

In general, do not give marks unless the writing is very clear even for the ideas.