Skip to content

Instantly share code, notes, and snippets.

@emilypi
Last active September 6, 2024 05:43
Show Gist options
  • Save emilypi/6fa5b492de9f859fff070867f504c6cc to your computer and use it in GitHub Desktop.
Save emilypi/6fa5b492de9f859fff070867f504c6cc to your computer and use it in GitHub Desktop.
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
module MyLib where
import Data.Kind (Type)
-- This is how we're normally write a recursive list data structure
--
data List a = Nil | Cons a (List a)
-- Consider this equivalent data structure:
--
data L h t = N | C h t
-- when h ~ a and t ~ List a, you have the same thing as a List as defined above.
-- however, there is one key difference when you consider the following struct:
newtype Fix f = Fix { unfix :: f (Fix f) }
-- this data type represents the "fixed point" of an endofunctor `f` (e.g. a haskell 'Functor'). An
-- "algebra" for an endofunctor is a pair (a, h: f a -> a) that honors a particular coherence property
-- with respect to other algebras.
--
-- There is a theorem that says that if `f` has an -initial- algebra `i: f a -> a`, then a is isomorphic
-- to `f a`. `Fix` is that initial structure, along with `unfix`. That is, `L h ~ Fix (L h)`, and further
-- when `h ~ a` and `t ~ List a`, you have `L h t ~ List a`.
--
-- The 'base` functor with respect to the `Fix`able `L` is `List`.
--
-- Thus, you can think of a (co)recursion scheme as "projecting" (vis: embedding) a `List` onto `L`, and then `Fix`
-- takes care of recursion that projects `List` along `t` in `L h t` and rolls up the (co)recursion
-- principle in a nice little data structure.
--
-- You get the following:
-- Fixed point of a list
type ListF a = Fix (L a)
nil :: ListF a
nil = Fix N
-- example: [1,2,3] ~ Fix (C 1 (Fix (C 2 (Fix (C 3 (Fix N)))))
cons :: a -> ListF a -> ListF a
cons a l = Fix (C a l)
cata :: Functor f => (f a -> a) -> Fix f -> a
cata phi = phi . fmap (cata phi) . unfix
ana :: Functor f => (a -> f a) -> a -> Fix f
ana psi = Fix . fmap (ana psi) . psi
-- likewise, you can embed the information of the associated "base" functor directly into the
-- signature and just use the usual functor by writing a type family for it. Then, you have
-- the "class of things that can be projected onto things that are amenable to being recursed
-- over with `Fix`, except now you don't need `Fix` cuz you know how to `unfix` to an isomorphic functor":
--
type family Base f :: Type -> Type
class Functor (Base f) => Recursive f where
-- e.g. Base (Fix f) = f
-- and `project` = `unfix`
project :: f -> Base f f
cataB :: (Base f a -> a) -> f -> a
cataB phi = phi . fmap (cataB phi) . project
-- and likewise, for corecursion (i.e. ana and friends),
class Functor (Base f) => Corecursive f where
embed :: Base f f -> f
anaB :: (a -> Base f a) -> a -> f
anaB psi = embed . fmap (anaB psi) . psi
hylo :: Functor f => (f b -> b) -> (a -> f a) -> a -> b
hylo phi psi = cata phi . ana psi
-- So to answer the question directly:
--
-- A base functor is the "the functor we really want to work with" (i.e. List, Maybe whatever)
-- and an "algebra" (or coalgebra) is "way to take a functor and produce a value we want" or "the structure we want to
-- build using a seed value", and all of the `Fix` and families of associated haskell
-- functors are the functors that embed or project their (co)recursion principles nicely when
-- using `Fix` or just doing the recursion itself. Try writing these out by hand for small examples!
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment