1 {-# OPTIONS_GHC -Wall #-}
2 {-# OPTIONS_GHC -fno-warn-missing-methods #-}
3 {-# LANGUAGE InstanceSigs #-}
4 {-# LANGUAGE FlexibleInstances #-}
5 {-# LANGUAGE FlexibleContexts #-}
9 fib :: Integer -> Integer
12 fib n = fib (n - 1) + fib (n - 2)
17 -- exercise 2: define a more efficient fibs
20 where fs = zipWith (+) fibs2 (tail fibs2)
22 -- exercise 3 -- streams
23 data Stream a = Cons a (Stream a)
25 -- stream to infinite list
26 streamToList :: Stream a -> [a]
27 streamToList (Cons x sx) = x : streamToList sx
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)))) ++ "..."
34 -- exercise 4 - stream repeat
35 streamRepeat :: a -> Stream a
36 streamRepeat x = Cons x (streamRepeat x)
39 streamMap :: (a -> b) -> Stream a -> Stream b
40 streamMap f (Cons x xs) = Cons (f x) (streamMap f xs)
43 streamFromSeed :: (a -> a) -> a -> Stream a
44 streamFromSeed f x = Cons x (streamFromSeed f (f x))
46 -- exercise 5: define a few streams
49 nats :: Stream Integer
50 nats = streamFromSeed (+1) 0
56 ruler :: Stream Integer
58 which corresponds to the ruler function
59 0, 1, 0, 2, 0, 1, 0, 3, 0, 1, 0, 2, 0, 1, 0, 4, . . .
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
66 interleaveStreams :: Stream a -> Stream a -> Stream a
67 interleaveStreams (Cons x xs) ys = (Cons x (interleaveStreams ys xs))
69 ruler :: Stream Integer
70 ruler = interleaveStreams (streamRepeat 0) (foldr interleaveStreams (streamRepeat 0) (map streamRepeat [1..]))
72 -- fibonacci numbers via generating functions
75 -- define x :: Stream Integer
76 -- x = 0 + 1.x + 0.x^2 + 0.x^3 + 0.x^4 + ...
78 x' = Cons 0 (Cons 1 (streamRepeat 0))
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))
91 -- instance Fractional Integer => Fractional (Stream Integer) where
92 instance Fractional (Stream Integer) where
93 (/) :: Stream Integer -> Stream Integer -> Stream Integer
94 (/) (Cons x xs) (Cons y ys) = let r = streamMap (`div` y) $ Cons x ((xs - r*ys))
97 fibs3 :: Stream Integer
98 fibs3 = x' / (streamRepeat 1 - x' - x' * x')
101 data Matrix = Matrix Integer Integer Integer Integer
103 instance Num Matrix where
104 (*) :: Matrix -> Matrix -> Matrix
105 (*) (Matrix a1 b1 c1 d1) (Matrix a2 b2 c2 d2) =
106 Matrix (a1*a2 + b1*c2) (a1*b2 + b1*d2) (c1*a2 + d1*c2) (c1*b2 + d1*d2)
108 fib4 :: Integer -> Integer
110 fib4 n = let f0 = (Matrix 1 1 1 0)
111 (Matrix _ b _ _) = f0 ^ n