Skip to content

Instantly share code, notes, and snippets.

@wbadart
Created November 12, 2020 22:32
Show Gist options
  • Save wbadart/25e14abf4a682b0b8021c6909f615d98 to your computer and use it in GitHub Desktop.
Save wbadart/25e14abf4a682b0b8021c6909f615d98 to your computer and use it in GitHub Desktop.
Example of using an anamorphism (with helper catamorphism)
{-# LANGUAGE BlockArguments,DeriveFunctor,LambdaCase,ScopedTypeVariables,NoImplicitPrelude #-}
import Control.Arrow
import Prelude hiding (replicate)
newtype Fix f = In { out :: f (Fix f) }
type FAlgebra f a = f a -> a
cata :: (Functor f) => FAlgebra f a -> Fix f -> a
cata f = out >>> fmap (cata f) >>> f
type FCoAlgebra f a = a -> f a
ana :: (Functor f) => FCoAlgebra f a -> a -> Fix f
ana f = In <<< fmap (ana f) <<< f
-- ==========
data List a f
= Cons a f
| Nil
deriving Functor
replicate :: forall a. Int -> a -> Fix (List a)
replicate n a = ana go n where
go :: FCoAlgebra (List a) Int
go 0 = Nil
go n = Cons a (n - 1)
main = print $ len (replicate 10 'a') -- "10"
where len = cata \case
Nil -> 0
Cons _ rest -> 1 + rest
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment