Skip to content

Instantly share code, notes, and snippets.

@314maro
Created August 22, 2013 15:55
Show Gist options
  • Save 314maro/6309099 to your computer and use it in GitHub Desktop.
Save 314maro/6309099 to your computer and use it in GitHub Desktop.
フィボナッチ数列を一般化したみたいなもの作れます
{-# LANGUAGE GADTs, TypeFamilies, ScopedTypeVariables, FlexibleInstances, FlexibleContexts #-}
import Data.List (tails)
-- 関数の名前わかりづらいのは見逃して
hoge :: (FromList (ListN (S a)), Num x) => ListN (S a) x -> [x]
hoge = iterateN sumN
fib = hoge $ 0 ::: 1 ::: N
lucas = hoge $ 2 ::: 1 ::: N
tri = hoge $ 0 ::: 0 ::: 1 ::: N
tetra = hoge $ 0 ::: 0 ::: 0 ::: 1 ::: N
data Z
data S a
data ListN n x where
N :: ListN Z x
(:::) :: x -> ListN n x -> ListN (S n) x
infixr 5 :::
instance Show x => Show (ListN n x) where
show N = "N"
show (x ::: l) = shows x $ " ::: " ++ show l
class FromList f where
fromList :: [a] -> f a
instance FromList (ListN Z) where
fromList _ = N
instance FromList (ListN a) => FromList (ListN (S a)) where
fromList (x:xs) = x ::: fromList xs
toList :: ListN a x -> [x]
toList N = []
toList (x ::: l) = x : toList l
foldlN :: (y -> x -> y) -> y -> ListN a x -> y
foldlN _ v N = v
foldlN f v (x ::: l) = foldlN f (f v x) l
sumN :: Num x => ListN a x -> x
sumN = foldlN (+) 0
transposeN :: ListN a [x] -> [ListN a x]
transposeN N = repeat N
transposeN (x ::: l) = zipWith (:::) x $ transposeN l
zipWithN :: (ListN (S a) x -> y) -> ListN (S a) [x] -> [y]
zipWithN f = map f . transposeN
iterateN :: FromList (ListN (S a)) => (ListN (S a) x -> x) -> ListN (S a) x -> [x]
iterateN f x = toList x ++ zipWithN f a
where a = fromList $ tails $ iterateN f x
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment