Skip to content

Instantly share code, notes, and snippets.

@anthonybrice
Created September 26, 2018 02:28
Show Gist options
  • Save anthonybrice/41e538fab495d68bcbbc57e8c0ed70e9 to your computer and use it in GitHub Desktop.
Save anthonybrice/41e538fab495d68bcbbc57e8c0ed70e9 to your computer and use it in GitHub Desktop.
{-# LANGUAGE FlexibleInstances #-}
{-# OPTIONS_GHC -fno-warn-missing-methods #-}
module Homework.Week06.Assignment (
fib,
fibs1,
fibs2,
streamToList,
streamRepeat,
streamMap,
streamFromSeed,
nats,
ruler,
fibs3,
fib4,
Stream(..)
) where
import Data.List (elemIndices)
import Data.Maybe (fromMaybe)
-- #1a
fib :: Integer -> Integer
fib 0 = 0
fib 1 = 1
fib x = fib (x - 1) + fib (x - 2)
fibs1 :: [Integer]
fibs1 = map fib [0..]
-- #2
fibs2 :: [Integer]
fibs2 = 0 : 1 : (map (uncurry (+)) $ zip fibs2 $ tail fibs2)
-- #3
data Stream a = Cons a (Stream a)
streamToList :: Stream a -> [a]
streamToList (Cons x s) = x : streamToList s
instance Show a => Show (Stream a) where
show = show . take 20 . streamToList
-- #4
streamRepeat :: a -> Stream a
streamRepeat x = Cons x (streamRepeat x)
streamMap :: (a -> b) -> Stream a -> Stream b
streamMap f (Cons x s) = Cons (f x) (streamMap f s)
streamFromSeed :: (a -> a) -> a -> Stream a
streamFromSeed f x = Cons x (streamFromSeed f (f x))
-- #5
nats :: Stream Integer
nats = streamFromSeed (+1) 0
ruler :: Stream Integer
ruler = interleaveStreams (streamRepeat 0) $ listToStream $ map ruler' [2*x | x <- [1..]]
where ruler' x =
let twos = [2^i | i <- [1..]]
f = map (x `rem`) $ take (fromIntegral x) twos
g = elemIndices 0 f
in if g /= [] then fromIntegral $ 1 + (last g) else 0
listToStream (x:xs) = Cons x (listToStream xs)
interleaveStreams :: Stream a -> Stream a -> Stream a
interleaveStreams (Cons a0 a') (Cons b0 b') = Cons a0 (Cons b0 (interleaveStreams a' b'))
x :: Stream Integer
x = Cons 0 (Cons 1 (streamRepeat 0))
instance Num (Stream Integer) where
fromInteger i = Cons i (streamRepeat 0)
negate (Cons s ss) = Cons (-s) (negate ss)
(+) (Cons a as) (Cons b bs) = Cons (a + b) (as + bs)
(*) (Cons a0 a') b@(Cons b0 b') = Cons (a0 * b0) ((fromInteger a0) * b' + a' * b)
instance Fractional (Stream Integer) where
(/) a@(Cons a0 a') b@(Cons b0 b') =
Cons (a0 `div` b0) (a' - ((a/b) * b') / fromInteger b0)
fibs3 :: Stream Integer
fibs3 = x / (1 - x - x^2)
data Matrix = Matrix Integer Integer Integer Integer deriving Show
instance Num Matrix where
(*) (Matrix m0 m1 m2 m3) (Matrix n0 n1 n2 n3) =
Matrix (m0*n0 + m1*n2) (m0*n1 + m1*n3) (m2*n0 + m3*n2) (m2*n1 + m3*n3)
f :: Matrix
f = Matrix 1 1 1 0
fib4 :: Integer -> Integer
fib4 0 = 0
fib4 n = let Matrix _ x _ _ = f^n in x
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment