]> git.rkrishnan.org Git - yorgey.git/commitdiff
hw6: Fibonacci - mostly done till half of exercise 6
authorRamakrishnan Muthukrishnan <ram@rkrishnan.org>
Mon, 22 Dec 2014 15:36:30 +0000 (21:06 +0530)
committerRamakrishnan Muthukrishnan <ram@rkrishnan.org>
Mon, 22 Dec 2014 15:36:30 +0000 (21:06 +0530)
hw6/Fibonacci.hs [new file with mode: 0644]

diff --git a/hw6/Fibonacci.hs b/hw6/Fibonacci.hs
new file mode 100644 (file)
index 0000000..9a15712
--- /dev/null
@@ -0,0 +1,88 @@
+{-# OPTIONS_GHC -Wall #-}
+{-# OPTIONS_GHC -fno-warn-missing-methods #-}
+{-# LANGUAGE InstanceSigs #-}
+{-# LANGUAGE FlexibleInstances #-}
+module Fibonacci where
+
+-- exercise 1
+fib :: Integer -> Integer
+fib 0 = 0
+fib 1 = 1
+fib n = fib (n - 1) + fib (n - 2)
+
+fibs1 :: [Integer]
+fibs1 = map fib [0..]
+
+-- exercise 2: define a more efficient fibs
+fibs2 :: [Integer]
+fibs2 = 0 : 1 : fs
+    where fs = zipWith (+) fibs2 (tail fibs2)
+
+-- exercise 3 -- streams
+data Stream a = Cons a (Stream a)
+
+-- stream to infinite list
+streamToList :: Stream a -> [a]
+streamToList (Cons x sx) = x : streamToList sx
+
+-- instance of Show for Stream
+instance Show a => Show (Stream a) where
+  show :: Stream a -> String
+  show sx = init (tail (show (take 20 (streamToList sx)))) ++ "..."
+  
+-- exercise 4 - stream repeat
+streamRepeat :: a -> Stream a
+streamRepeat x = Cons x (streamRepeat x)
+
+-- streamMap
+streamMap :: (a -> b) -> Stream a -> Stream b
+streamMap f (Cons x xs) = Cons (f x) (streamMap f xs)
+
+-- streamFromSeed
+streamFromSeed :: (a -> a) -> a -> Stream a
+streamFromSeed f x = Cons x (streamFromSeed f (f x))
+
+-- exercise 5: define a few streams
+
+-- nats
+nats :: Stream Integer
+nats = streamFromSeed (+1) 0
+
+-- ruler
+{- | ruler stream
+Define the stream
+
+ruler :: Stream Integer
+
+which corresponds to the ruler function
+0, 1, 0, 2, 0, 1, 0, 3, 0, 1, 0, 2, 0, 1, 0, 4, . . .
+
+where the nth element in the stream (assuming the first element
+corresponds to n = 1) is the largest power of 2 which evenly
+divides n
+
+-}
+interleaveStreams :: Stream a -> Stream a -> Stream a
+interleaveStreams (Cons x xs) ys = (Cons x (interleaveStreams ys xs))
+
+ruler :: Stream Integer
+ruler = interleaveStreams (streamRepeat 0) (foldr interleaveStreams (streamRepeat 0) (map streamRepeat [1..]))
+
+-- fibonacci numbers via generating functions
+-- exercise 6
+
+-- define x :: Stream Integer
+-- x = 0 + 1.x + 0.x^2 + 0.x^3 + 0.x^4 + ...
+x' :: Stream Integer
+x' = Cons 0 (Cons 1 (streamRepeat 0))
+
+-- implement an instance of Num type class for Stream Integer
+instance Num (Stream Integer) where
+  fromInteger :: Integer -> Stream Integer
+  fromInteger n = Cons n (streamRepeat 0)
+  negate :: Stream Integer -> Stream Integer
+  negate sx = streamMap (* (-1)) sx
+  (+) :: Stream Integer -> Stream Integer -> Stream Integer
+  (+) (Cons x sx) (Cons y sy) = (Cons (x+y) ((+) sx sy))
+  (*) :: Stream Integer -> Stream Integer -> Stream Integer
+  (*) (Cons x sx) (Cons y sy) = Cons (x*y) ((streamMap (* x) sy) + sx*(Cons x sx))