Skip to content

Instantly share code, notes, and snippets.

@blankhart
Created December 25, 2019 13:18
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 2 You must be signed in to fork a gist
  • Save blankhart/ea84d43489d4799a4fe98cf232d4d6eb to your computer and use it in GitHub Desktop.
Save blankhart/ea84d43489d4799a4fe98cf232d4d6eb to your computer and use it in GitHub Desktop.
{-# LANGUAGE DeriveFunctor #-}
module Main where
type Algebra f a = f a -> a
type Coalgebra f a = a -> f a
newtype Fix f = In { out :: f (Fix f) }
cata :: Functor f => Algebra f a -> Fix f -> a
cata alg = alg . fmap (cata alg) . out
ana :: Functor f => Coalgebra f a -> a -> Fix f
ana coalg = In . fmap (ana coalg) . coalg
hylo :: Functor f => Algebra f b -> Coalgebra f a -> a -> b
hylo alg coalg = h where h = alg . fmap h . coalg
data NatF a = ZeroF | SuccF a deriving (Functor)
fib :: (Show a, Integral a) => Algebra NatF (a, a)
fib ZeroF = (0, 1)
fib (SuccF (prev, next)) = (next, prev + next)
nth :: (Show a, Integral a) => Coalgebra NatF a
nth 0 = ZeroF
nth n = SuccF (n-1)
getNthFib :: Integer -> Integer
getNthFib n = fst $ hylo fib nth (n - 1)
-- [0,1,1,2,3,5,8,13,21,34,55]
main = print $ getNthFib <$> [1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment