Skip to content

Instantly share code, notes, and snippets.

@purefunctor
Created September 18, 2021 04:06
Show Gist options
  • Save purefunctor/54ff6e94552d96e2779e1d20adfa3150 to your computer and use it in GitHub Desktop.
Save purefunctor/54ff6e94552d96e2779e1d20adfa3150 to your computer and use it in GitHub Desktop.
`cata` and `transCata`
module Main where
import Prelude
import Matryoshka
import Effect (Effect)
import Effect.Console (logShow)
import Data.Functor.Mu (Mu(..))
data ListF a n = NilF | ConsF a n
derive instance Functor (ListF a)
instance (Show a, Show n) => Show (ListF a n) where
show NilF = "NilF"
show (ConsF h t) = "(ConsF " <> show h <> " " <> show t <> ")"
type List a = Mu (ListF a)
nil :: forall a. List a
nil = In NilF
cons :: forall a. a -> List a -> List a
cons a n = In (ConsF a n)
mapShow :: List Int -> List String
mapShow = cata go
where
go NilF = nil
go (ConsF h t) = cons (show h) t
mapShow' :: List Int -> List String
mapShow' = transCata go
where
go NilF = NilF
go (ConsF h t) = ConsF (show h) t
xs :: List Int
xs = cons 1 (cons 2 (cons 3 (nil)))
main :: Effect Unit
main = do
logShow (mapShow xs)
logShow (mapShow' xs)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment