]> git.rkrishnan.org Git - yorgey.git/blob - hw6/Fibonacci.hs
hw6: implement instance of Fractional for Stream Integer
[yorgey.git] / hw6 / Fibonacci.hs
1 {-# OPTIONS_GHC -Wall #-}
2 {-# OPTIONS_GHC -fno-warn-missing-methods #-}
3 {-# LANGUAGE InstanceSigs #-}
4 {-# LANGUAGE FlexibleInstances #-}
5 {-# LANGUAGE FlexibleContexts #-}
6 module Fibonacci where
7
8 -- exercise 1
9 fib :: Integer -> Integer
10 fib 0 = 0
11 fib 1 = 1
12 fib n = fib (n - 1) + fib (n - 2)
13
14 fibs1 :: [Integer]
15 fibs1 = map fib [0..]
16
17 -- exercise 2: define a more efficient fibs
18 fibs2 :: [Integer]
19 fibs2 = 0 : 1 : fs
20     where fs = zipWith (+) fibs2 (tail fibs2)
21
22 -- exercise 3 -- streams
23 data Stream a = Cons a (Stream a)
24
25 -- stream to infinite list
26 streamToList :: Stream a -> [a]
27 streamToList (Cons x sx) = x : streamToList sx
28
29 -- instance of Show for Stream
30 instance Show a => Show (Stream a) where
31   show :: Stream a -> String
32   show sx = init (tail (show (take 20 (streamToList sx)))) ++ "..."
33   
34 -- exercise 4 - stream repeat
35 streamRepeat :: a -> Stream a
36 streamRepeat x = Cons x (streamRepeat x)
37
38 -- streamMap
39 streamMap :: (a -> b) -> Stream a -> Stream b
40 streamMap f (Cons x xs) = Cons (f x) (streamMap f xs)
41
42 -- streamFromSeed
43 streamFromSeed :: (a -> a) -> a -> Stream a
44 streamFromSeed f x = Cons x (streamFromSeed f (f x))
45
46 -- exercise 5: define a few streams
47
48 -- nats
49 nats :: Stream Integer
50 nats = streamFromSeed (+1) 0
51
52 -- ruler
53 {- | ruler stream
54 Define the stream
55
56 ruler :: Stream Integer
57
58 which corresponds to the ruler function
59 0, 1, 0, 2, 0, 1, 0, 3, 0, 1, 0, 2, 0, 1, 0, 4, . . .
60
61 where the nth element in the stream (assuming the first element
62 corresponds to n = 1) is the largest power of 2 which evenly
63 divides n
64
65 -}
66 interleaveStreams :: Stream a -> Stream a -> Stream a
67 interleaveStreams (Cons x xs) ys = (Cons x (interleaveStreams ys xs))
68
69 ruler :: Stream Integer
70 ruler = interleaveStreams (streamRepeat 0) (foldr interleaveStreams (streamRepeat 0) (map streamRepeat [1..]))
71
72 -- fibonacci numbers via generating functions
73 -- exercise 6
74
75 -- define x :: Stream Integer
76 -- x = 0 + 1.x + 0.x^2 + 0.x^3 + 0.x^4 + ...
77 x' :: Stream Integer
78 x' = Cons 0 (Cons 1 (streamRepeat 0))
79
80 -- implement an instance of Num type class for Stream Integer
81 instance Num (Stream Integer) where
82   fromInteger :: Integer -> Stream Integer
83   fromInteger n = Cons n (streamRepeat 0)
84   negate :: Stream Integer -> Stream Integer
85   negate sx = streamMap (* (-1)) sx
86   (+) :: Stream Integer -> Stream Integer -> Stream Integer
87   (+) (Cons x sx) (Cons y sy) = (Cons (x+y) ((+) sx sy))
88   (*) :: Stream Integer -> Stream Integer -> Stream Integer
89   (*) (Cons x sx) (Cons y sy) = Cons (x*y) ((streamMap (* x) sy) + sx*(Cons x sx))
90
91 instance Fractional Integer => Fractional (Stream Integer) where
92   (/) :: Stream Integer -> Stream Integer -> Stream Integer
93   (/) (Cons x xs) (Cons y ys) = let r = streamMap (/ y) $ Cons x ((xs - r*ys))
94                                 in
95                                   r