Three Homework Problems

August 4, 2015

1. If a is no larger than b or c, then it is the smallest, so the answer is the sum of the squares of b and c. Otherwise, rotate the input and try again. This is one of the simplest examples of recursion that I know, and one of the best for introducing recursion to students, better than a factorial or fibonacci number:

(define (f a b c)
  (if (and (<= a b) (<= a c))
      (+ (* b b) (* c c))
      (f b c a)))

> (f 1 2 3)
13
> (f 2 1 3)
13
> (f 3 1 2)
13
> (f 3 3 3)
18

2. We repeatedly strip the trailing digit, building its reversal as we go, and compare at the end:

(define (palin? n)
  (let loop ((m n) (r 0))
    (if (zero? m)
        (= r n)
        (loop (quotient m 10)
              (+ (* 10 r) (remainder m 10))))))

> (palin? 12345)
#f
> (palin? 12321)
#t

3. This is more of a math problem than a programming problem, but I’ve seen it in more than one beginning programming textbook, so here it is. I’m not entirely sure it’s fair to give the problem without explaining the math, but I usually see the problem in exactly the form given on the previous page.

You don’t want to compute the factorial and count zeroes; the intermediate calculation of the factorial is huge. Instead, observe that the number of trailing zeroes depends on the number of factors of 10 = 2 × 5, and since there are more factors of 2 than of 5, the number of trailing zeroes is the same as the number of factors of 5. And that’s easy to calculate: for example, 973! has ⌊973/5⌋ = 194 factors of 5, plus ⌊973/25⌋ = 38 additional factors of 5 in the 52 terms, plus ⌊973/125⌋ = 7 additional factors of 5 in the 53 terms, plus ⌊973/625⌋ = 1 additional factor of 5 in the 54 terms, a total of 240 factors of 5. Given that, the program is easy to write:

(define (tens n)
  (let loop ((n n) (z 0))
    (if (zero? n) z
      (let ((n (quotient n 5)))
        (loop n (+ z n))))))

> (tens 973)
240

You can run the program at http://ideone.com/VDLHqW.

Students: If you use these solutions in your programs, be sure to give proper attribution.

Advertisement

Pages: 1 2

13 Responses to “Three Homework Problems”

  1. Jussi Piitulainen said

    Do they still make people start with Java? I wasn’t sure if I was expected to write javadoc comments and stuff, but this was quite enough sheer tedium for me already. Probably I should have written static tests instead of making it take arguments on the command line. Should I worry about overflowing int in the first problem? If yes, why? If not, why not?

    Today I give the sourcecode processor the actual lang.

    import static java.lang.Math.min;
    import static java.lang.Math.max;
    
    public class HW {
    
        private static int hw1(int p, int q, int r) {
            int m = max(p, max(q, r));
            /* Googled median of three: */
            int n = max(min(p, q), min(max(p, q), r));
            int result = m * m + n * n;
            return result;
        }
    
        private static boolean hw2(int p) {
            String s = new String(new Integer(p).toString().toString());
            boolean result = true;
            for (int k = 0 ; k < s.length() ; ++ k) {
                if (s.charAt(k) != s.charAt(s.length() - k - 1)) {
                    result = false;
                }
            }
            if (result == true) {
                return true;
    	}
            else {
                return false;
            }
            /* A ; here was an unreachable statement :) Quite right. */
        }
    
        private static int hw3(int p) {
            int result = 0;
            for (int n = 1 ; n <= p ; ++ n) {
                /* There will be twos. */
                int r = n;
                while ((r % 5 == 0) == true) {
                    r = r / 5;
                    ++ result;
                }
            }
        	return result;
        }
    
        public static void main(String ... args) {
            if (args.length == 0 ||
                (args[0].equals("1") && args.length != 4) ||
                (args[0].equals("2") && args.length != 2) ||
                (args[0].equals("3") && args.length != 2) ||
                (! args[0].equals("1") &&
                 ! args[0].equals("2") &&
                 ! args[0].equals("3"))) {
                System.out.println("Need one of the following arguments:");
                System.out.println("1 <positive integer>" +
                                   " <positive integer>" +
                                   " <positive integer>");
                System.out.println("2 <positive integer>");
                System.out.println("3 <positive integer>");
            }
            else if (args[0].equals("1")) {
                int p = Integer.parseInt(args[1]);
                int q = Integer.parseInt(args[2]);
                int r = Integer.parseInt(args[3]);
                if (p <= 0 || q <= 0 || r <= 0) {
                    System.out.println("The arguments must be positive.");
                }
                else {
                    System.out.println("The sum of the squares " +
                                       "of the largest two " +
                                       "of the arguments is " +
                                       hw1(p, q, r) + ".");
                }
            }
            else if (args[0].equals("2")) {
                int p = Integer.parseInt(args[1]);
                if (p <= 0) {
                    System.out.println("The argument must be positive.");
                }
                else {
                    System.out.println("The argument is " +
                                       (hw2(p) ? "" :  "not ") +
                                       "a base-10 palindrome.");
                }
            }
             else /* args[0].equals("3") */ {
                int p = Integer.parseInt(args[1]);
                if (p <= 0) {
                    System.out.println("The argument must be positive.");
                }
                else {
                    System.out.println("The number of trailing zeroes " +
                                       "in the factorial of the argument is " +
                                       hw3(p) + ".");
                }
            }
        }
    }
    
  2. programmingpraxis said

    @Jussi: I was just reading this morning that Python is now the dominant first language for programming students. And if you use Python, you don’t have to worry about integer overflow. I agree with you: Java is a horrible first language. Although probably not too much worse than FORTRAN, which was my first language.

  3. Jussi Piitulainen said

    @Praxis, thanks, I’m glad to hear that about Python. I was taught in Pascal in the CS department after I had already met some line-numbered Basics, 6502 assembler and Forth on my own. Then our CS folks switched to Java as the main teaching language. (Scheme was a candidate. I saw them talk about Scala later. Now I’m not up to date). We’ve used Lisp, Prolog, Perl in the linguistics department over the years, and now we have indeed Python. Scheme I got on my own, but it used to be a teaching language in a university of technology here. (And since Java became more a lawsuit than a programming language, I cut my personal ties to it as far as I could. Mainly by rewriting my largest project from scratch, in Scheme. It needed rewriting anyway.)

    Show us these problems in FORTRAN? :)

  4. mcmillhj said
    fun sumSquaresOfTwoLargest (a,b,c) = let
        fun square n = n * n 
        fun reduce (x,y) = (square x) + (square y)
        open Int
    in
        reduce(max(a, max(b,c)), min(max(a,b), max(a,c)))
    end
    
    fun integerIsPalindrome n = let
        fun intToDigits 0 ds = ds
          | intToDigits n ds = intToDigits (n div 10) ((n mod 10) :: ds)
        fun compareLists [] [] = true
          | compareLists _ []  = false
          | compareLists [] _  = false 
          | compareLists (x::xs) (y::ys) = if x = y then compareLists xs ys
                                           else false
        fun isPalindrome xs ds = let
            val xlen = length xs;
            val dlen = length ds;
        in
            if xlen = dlen then compareLists xs ds
            else if xlen = dlen + 1 then compareLists (tl xs) ds
            else isPalindrome (tl xs) ((hd xs) :: ds)
        end
    in
        isPalindrome (intToDigits n []) []
    end
    
    (* count the number of factors of 5 exist inside of N
    this will tell us in turn how many factors of this number are 10 which implies added 0s *)
    fun numberTrailingZerosFromFactorialOfN n = let
        fun numberFactorsXOfN count starting_factor factor =
            if (n div factor) <= 0 then count
            else numberFactorsXOfN (count + (n div factor)) starting_factor (factor*starting_factor)
    in
        numberFactorsXOfN 0 5 5
    end
    
  5. mcmillhj said

    @Jussi @Praxis Java was my first language in school as well, and I believe they have since switched to Python. Although I think Scheme would probably be a better choice.

  6. matthew said

    Here are some Haskell solutions. We should only need two comparisons to find the biggest two of three. The tens function just repeated divides by 5 and adds the results. The palindrome check uses the double-speed list iterator to only reverse the first half of the list (and keep the list comparison short).

    f a b c = if b < a then g a b c else g b a c
    g a b c = if c < b then h a b else h a c
    h a b = a*a+b*b
    
    tens = sum.tail.takeWhile(/=0).iterate(`div`5)
    
    pal n = pal' s [] s where s = show n
    pal' s t [] = s == t
    pal' (_:s) t [_] = s == t
    pal' (a:s) t (_:_:u) = pal' s (a:t) u
    
    main = 
      print(f 1 2 3) >>
      print(f 2 1 3) >>
      print(tens 973) >>
      print(pal 1234321) >>
      print(pal 123321) >>
      print(pal 123221)
    

    It was Pascal at university in my day (as well as Lisp, Prolog and some Occam, if anyone remembers that). The local place here has used ML for many years for introductory programming, though sadly there is some sort of Java option these days as well.

  7. Jaime said
    def one(a, b, c):
        m = min(a, b, c)
        return a*a + b*b + c*c - m*m
    
    def two(value):
        digits = []
        while value:
            value, digit = divmod(value, 10)
            digits.append(digit)
        return all(a == b for a, b in zip(digits, digits[::-1]))
    
    def three(n):
        count_5s = 0
        div = 5
        while div < n:
            count_5s += n // div
            div *= 5
        return count_5s
    
  8. Mike said

    In honor of my first programming language (a modified FORTRAN 77 on punch cards):

    C**************
    C
    C  HOMEWORK 1
    C
    C**************
           PROGRAM HOMEWORK
           INTEGER ONE, THREE
           LOGICAL TWO
           DATA I,J,K/3, 2, 4/
           DATA M, N / 123, 27 /
           WRITE(6, *) 'ONE(', I, ', ', J, ', ', K, ') = ', ONE(I, J, K)
           WRITE(6, *) 'TWO(', M, ') = ', TWO(M)
           WRITE(6, *) 'THREE(', N, ') = ', THREE(N)
           END
    C**************
    C
    C  FUNCTION ONE
    C
    C  INPUT   - 3 NON-NEGATIVE INTEGERS
    C  RETURNS - SUM OF SQUARES OF TWO LARGEST INPUTS
    C
    C**************       
           INTEGER FUNCTION ONE(I,J,K)
           M = MIN0(I, J, K)
           IF (M .NE. I) GOTO 1
           ONE = J*J+K*K
           GOTO 2
      1    IF (M.NE. J) GOTO 3
           ONE = I*I+K*K
           GOTO 2
       3   ONE = I*I+J*J
     2     RETURN
           END
    C**************
    C
    C  FUNCTION TWO
    C
    C  INPUT   - A NON-NEGATIVE INTEGER
    C  RETURNS - TRUE IF THE INPUT IS A PALINDROM IN BASE 10
    C            FALSE OTHERWISE
    C
    C**************       
           LOGICAL FUNCTION TWO(N)
           LOGICAL RESULT
           DIMENSION NN(10)
           I = 1
      5    IF (N .EQ. 0) GOTO 10
           NN(I) = MOD(N, 10)
           N = N / 10
           I = I+ 1
           GOTO 5
     10    J = 1
      11   IF (I.EQ.J) GOTO 23
           IF (NN(I) .NE.NN(J)) GOTO 27
           I = I - 1
           J = J+1
           GOTO 11
     23       RESULT = .TRUE.
           GOTO 29
      27   RESULT= .FALSE.
      29   TWO = RESULT
           RETURN
           END
    C**************
    C
    C  FUNCTION THREE
    C
    C  INPUT   - A NON-NEGATIVE INTEGER, N
    C  RETURNS - THE NUMBER OF TRAILING ZEROES IN FACTORIAL(N)
    C
    C**************       
           INTEGER FUNCTION THREE(N)
           N5S = 0
           J = 5
     69    IF (J.GT.N) GOTO 75
           N5S = N5S + N / J
           J = J * 5
           GOTO 69
      75   THREE = N5S
           RETURN
           END
    
  9. Mike said

    Didn’t test enough. There was a off by 1 bug in FUNCTION TWO.
    Here is an improved main program that reads data from standard input and a revised TWO().

    C**************
    C
    C  HOMEWORK 1
    C
    C**************
           PROGRAM HOMEWORK
           INTEGER ONE, THREE
           LOGICAL TWO, L
       5   CONTINUE
    	   READ(5, *) I,J,K
    	   IF (I.LT.0) GOTO 10
           WRITE(6, *) 'ONE(', I, ',', J, ',', K, ' ) = ', ONE(I, J, K)
    	   GOTO 5
      10   READ(5, *) M
           IF (M.LT.0) GOTO 20
    	   MM = TWO( M )
           WRITE(6, *) 'TWO(', M, ' ) = ', MM
    	   GOTO 10
       20  READ(5, *) N
           IF (N.LT.0) GOTO 30
           WRITE(6, *) 'THREE(', N, ' ) = ', THREE(N)
    	   GOTO 20
       30   CONTINUE
           END
    
    C  FUNCTION ONE - IS SAME AS ABOVE
    
    C**************
    C
    C  FUNCTION TWO
    C
    C  INPUT   - A NON-NEGATIVE INTEGER
    C  RETURNS - TRUE IF THE INPUT IS A PALINDROM IN BASE 10
    C            FALSE OTHERWISE
    C
    C**************       
           LOGICAL FUNCTION TWO(N)
           LOGICAL RESULT
           DIMENSION NN(10)
           I = 0
    	   N1 = N
      5    IF (N1 .EQ. 0) GOTO 10
           I = I+ 1
           NN(I) = MOD(N1, 10)
    C	   WRITE(6,*) 'N1 = ', N1, '; I = ', I, '; NN = [', (NN(K), K = 1,I), ']'
           N1 = N1 / 10
           GOTO 5
     10    J = 1
    C  11   WRITE(6, *) 'NN(', I, ') = ', NN(I), '; NN(', J ,') = ', NN(J)
      11   CONTINUE
           IF (I.LE.J) GOTO 23
           IF (NN(I) .NE.NN(J)) GOTO 27
           I = I - 1
           J = J+1
           GOTO 11
     23       RESULT = .TRUE.
           GOTO 29
      27   RESULT= .FALSE.
      29   TWO = RESULT
           RETURN
           END
    
    C  FUNCTION THREE - SAME AS ABOVE
    

    Here’s a sample input file (use redirections to feed the file to stdin).

    2    3    4
    4    3    2
    4    2    3
    -1  -1   -1
    121
    32
    12344321
    -1
    9
    11
    27
    35
    -1
    

    and a sample run

    C:\G77> a.exe < data.txt
     ONE( 2, 3, 4 ) =  25
     ONE( 4, 3, 2 ) =  25
     ONE( 4, 2, 3 ) =  25
     TWO( 121 ) =  T
     TWO( 32 ) =  F
     TWO( 12344321 ) =  T
     THREE( 9 ) =  1
     THREE( 11 ) =  2
     THREE( 27 ) =  6
     THREE( 35 ) =  8
    
  10. matthew said

    Here are some Python solutions.

    The sum of squares function is like the Haskell solution above, doing a partial sort of the three numbers in a couple of comparisons. The trailing zero computation is also similar: repeatedly divide by 5 and add. The palindromic number test now computes the digits from either end and stops when a discrepancy is found, so we can reject non-palindromes without converting each digit.

    def topsquares(a,b,c):
        if b > a: a,b = b,a
        if c > b: b,c = c,b
        return a*a+b*b
    
    def pal(n):
        p = 1 # p is largest power of 10 <= n
        while p*10 <= n: p *= 10
        while p > 1:
            a = n%10  # Bottom digit
            b = n//p  # Top digit
            if a != b: return False
            n -= b*p  # Remove top
            n //= 10  # Remove bottom
            p //= 100 # 2 digits less
        return True
    
    def tens(n):
        k = 0
        while n > 0: n /= 5; k += n
        return k
    
  11. FA said

    Scala:
    1. List(a,b,c).sorted.slice(1, 3).map(x=>x*x).sum
    2. n.toString().reverse==n.toString()
    3.
    def factorialTrailingZeroesCount(n: Long):Long = {
    if (n<5) 0
    else n/5 + factorialTrailingZeroesCount(n/5)
    }
    @Jaime: nice solution for the first :)

  12. Globules said

    Here’s another Haskell version. Maybe not quite in the manner of a beginning programmer (sorry!), but I still tried to keep it “naive”.

    import Data.List (sort)
    
    sum2 x y z = let [_, a, b] = sort [x, y, z] in a*a + b*b
    
    pal10 n = show n == reverse (show n)
    
    fac0s n = length . takeWhile (=='0') . reverse . show $ product [1..n]
    
  13. Dennis Decker Jensen said

    A solution in Modern Fortran. I picked a slightly different solution to problem 2. I don’t quite understand the solution to problem 3, so I re-used the one many others posted above.

    program homework
    &nbsp;&nbsp;&nbsp;implicit none
    
    &nbsp;&nbsp;&nbsp;write (*,10) 'one(2,3,4) = ', one(2,3,4)
    &nbsp;&nbsp;&nbsp;write (*,10) 'one(2,4,3) = ', one(2,4,3)
    &nbsp;&nbsp;&nbsp;write (*,10) 'one(3,2,4) = ', one(3,2,4)
    &nbsp;&nbsp;&nbsp;write (*,10) 'one(3,4,2) = ', one(3,4,3)
    &nbsp;&nbsp;&nbsp;write (*,10) 'one(4,2,3) = ', one(4,2,3)
    &nbsp;&nbsp;&nbsp;write (*,10) 'one(4,3,2) = ', one(4,3,2)
    10 format (A,I2)
    
    &nbsp;&nbsp;&nbsp;write (*,20) 'two(121)        = ', two(121)
    &nbsp;&nbsp;&nbsp;write (*,20) 'two(333)        = ', two(333)
    &nbsp;&nbsp;&nbsp;write (*,20) 'two(433)        = ', two(433)
    &nbsp;&nbsp;&nbsp;write (*,20) 'two(3333)       = ', two(3333)
    &nbsp;&nbsp;&nbsp;write (*,20) 'two(3433)       = ', two(3433)
    &nbsp;&nbsp;&nbsp;write (*,20) 'two(32)         = ', two(32)
    &nbsp;&nbsp;&nbsp;write (*,20) 'two(12344321)   = ', two(12344321)
    &nbsp;&nbsp;&nbsp;write (*,20) 'two(11)         = ', two(11)
    &nbsp;&nbsp;&nbsp;write (*,20) 'two(1239321)    = ', two(1239321)
    &nbsp;&nbsp;&nbsp;write (*,20) 'two(1239999321) = ', two(1239999321)
    &nbsp;&nbsp;&nbsp;write (*,20) 'two(0012332100) = ', two(0012332100)
    &nbsp;&nbsp;&nbsp;write (*,20) 'two(0)          = ', two(0)
    20 format (A,L1)
    
    &nbsp;&nbsp;&nbsp;write (*,30) 'tree(9)    = ', three(9)
    &nbsp;&nbsp;&nbsp;write (*,30) 'tree(11)   = ', three(11)
    &nbsp;&nbsp;&nbsp;write (*,30) 'tree(27)   = ', three(27)
    &nbsp;&nbsp;&nbsp;write (*,30) 'tree(35)   = ', three(35)
    &nbsp;&nbsp;&nbsp;write (*,30) 'tree(80)   = ', three(80)
    &nbsp;&nbsp;&nbsp;write (*,30) 'tree(1200) = ', three(1200)
    30 format (A,I3)
    
    contains
    
    &nbsp;&nbsp;&nbsp;! Square sum of 2 largest numbers
    &nbsp;&nbsp;&nbsp;integer function one(x, y, z)
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;integer, intent(in) :: x, y, z
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;integer hold, a, b, c
    
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;a = x; b = y; c = z
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;if (a &lt; b) then
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;hold = a
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;a = b
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;b = hold
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;end if
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;if (b &lt; c) then
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;hold = b
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;b = c
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;c = hold
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;end if
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;one = a * a + b * b
    &nbsp;&nbsp;&nbsp;end function one
    
    &nbsp;&nbsp;&nbsp;! Is the number a palindrome?
    &nbsp;&nbsp;&nbsp;! Examples of number palindroms:
    &nbsp;&nbsp;&nbsp;!    11, 121, 1239321, 1239999321, 0, 0012332100
    &nbsp;&nbsp;&nbsp;logical function two(num)
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;integer, intent(in) :: num
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;integer a, b, m
    
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;! Drop trailing zeroes
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;a = num; m = 0
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;if (num &gt; 0) then
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;do while(m == 0)
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;m = modulo(a, 10)
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;a = a / 10
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;end do
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;end if
    
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;! Move digits one by one into b
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;b = m
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;do while(a &gt; b)
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;m = modulo(a, 10)
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;a = a / 10
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;b = b * 10 + m
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;end do
    
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;two = a == b .or. a == b / 10
    &nbsp;&nbsp;&nbsp;end function two
    
    &nbsp;&nbsp;&nbsp;! Number of trailing zeroes in factorial(n)
    &nbsp;&nbsp;&nbsp;integer function three(n)
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;integer, intent(in) :: n
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;integer f
    
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;three = 0; f = 5
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;do while(f &lt;= n)
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;three = three + n / f
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;f = f * 5
    &nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;end do
    &nbsp;&nbsp;&nbsp;end function three
    
    end program homework
    

Leave a Reply

Fill in your details below or click an icon to log in:

WordPress.com Logo

You are commenting using your WordPress.com account. Log Out /  Change )

Facebook photo

You are commenting using your Facebook account. Log Out /  Change )

Connecting to %s

%d bloggers like this: