I have defined an F-Algebra, as per Bartosz Milewski's articles (one, two):
(This is not to say my code is an exact embodiment of Bartosz's ideas, it's merely my limited understanding of them, and any faults are mine alone.)
module Algebra where
data Expr a = Branch [a] | Leaf Int
instance Functor Expr where
fmap f (Branch xs) = Branch (fmap f xs)
fmap _ (Leaf i ) = Leaf i
newtype Fix a = Fix { unFix :: a (Fix a) }
branch = Fix . Branch
leaf = Fix . Leaf
-- | This is an example algebra.
evalSum (Branch xs) = sum xs
evalSum (Leaf i ) = i
cata f = f . fmap (cata f) . unFix
I can now do pretty much anything I want about it, for example, sum the leaves:
λ cata evalSum $ branch [branch [leaf 1, leaf 2], leaf 3]
6
This is a contrived example that I made up specifically for this question, but I actually tried some less trivial things (such as evaluating and simplifying polynomials with any number of variables) and it works like a charm. One may indeed fold and replace any parts of a structure as one runs a catamorphism through, with a suitably chosen algebra. So, I am pretty sure an F-Algebra subsumes a Foldable, and it even appears to subsume Traversable as well.
Now, can I define Foldable / Traversable instances in terms of an F-Algebra?
It seems to me that I cannot.
- I can only run a catamorphism on an initial algebra, which is a nullary type constructor. And the algebra I give it has a type
a b -> b
rather thana -> b
, that is to say, there is a functional dependency between the "in" and "out" type. - I don't see an
Algebra a => Foldable a
anywhere in type signatures. If this is not done, it must be impossible.
It seems to me that I cannot define Foldable
in terms of an F-Algebra for the reason that an Expr
must for that be a Functor
in two variables: one for carrier, another for values, and then a Foldable
in the second. So, it may be that a bifunctor is more suitable. And we can construct an F-Algebra with a bifunctor as well:
module Algebra2 where
import Data.Bifunctor
data Expr a i = Branch [a] | Leaf i
instance Bifunctor Expr where
bimap f _ (Branch xs) = Branch (fmap f xs)
bimap _ g (Leaf i ) = Leaf (g i)
newtype Fix2 a i = Fix2 { unFix2 :: a (Fix2 a i) i }
branch = Fix2 . Branch
leaf = Fix2 . Leaf
evalSum (Branch xs) = sum xs
evalSum (Leaf i ) = i
cata2 f g = f . bimap (cata2 f g) g . unFix2
It runs like this:
λ cata2 evalSum (+1) $ branch [branch [leaf 1, leaf 2], leaf 3]
9
But I still can't define a Foldable. It would have type like this:
instance Foldable \i -> Expr (Fix2 Expr i) i where ...
Unfortunately, one doesn't get lambda abstractions on types, and there's no way to put an implied type variable in two places at once.
I don't know what to do.
foldMap
? I believe myevalSum
is the algebra you're talking about, but it kind of doesn't help. – Unvoiced