Friday 12 December 2014

Recursion Schemes: Excursion 2

Unfolding:

We're required to implement embed in order to use Unfoldable.
embed puts our base functor into the recursive type.


For a list for example we have:

embed :: Base [a] [a] -> [a]
embed (Cons a l) = a:l
embed Nil = []

And this allows us to infinitely unfold our base functor into the recursive type with an anamorphism.

ana :: Unfoldable t => (a -> Base t a) -> a -> t
ana f = m where m = embed . fmap m . f

The anamorphism is the inverse of the catamorphism. In a catamorphism, we project onto the base functor, then fold the values encased in the functor and then fold the outer. In an anamorphism we unfold once, then use the values inside the functor as seeds for the next unfolds, and then inject it into a recursive type.

The generalized anamorphism is a bit more fun:
gana :: (Unfoldable t, Monad m) => (forall b. m (Base t b) -> Base t (m b))
             -> (a -> Base t (m a)) -> a -> t
Constructing a value for this type follows similarly from the anamorphism except the monad now gives us a bit more trouble. We want something of the form Base t(Base t(Base t ....

We proceed using the same structure as before, first unfurling one layer to get Base t (m a).
Now we need to recursively unfold the inner layers. So we're going to need a function f that does that.
f will eventually need to inject the base functor into the recursive type, so we're going to need a value
Base t t. What the monad does is provide us with an additional little algebra over the 'a'. So our function that collapses the base functor must evaluate the monad and then fold that into the recursive type. So f must have type : Base t (m a) -> Base t t. In order to evaluate the monad we have been provided with a distributive law, that pushes the monad inside the functor.

m : Base t (m a) -> Base t t
m x = fmap (embed . m . fmap join . f . fmap g) x

We first unfurl the inner 'a' one more time to obtain a Base t (m (Base t (m a)). Now we distribute the monad across our base functor to obtain Base t(Base t( m (m a)). We can now evaluate the monad using join to get Base t(Base t(m a)). Now the inner functor is in the exact form we need to unfurl it further using m. Finally we can embed this fixed form of our base functor into our recursive type, and we are done.

gunfold' :: (Unfoldable t, Monad m, Functor m) =>
          (forall b. m (Base t b) -> Base t (m b))
          -> (a -> Base t (m a)) -> a -> t
gunfold' f g a = embed $ m (g a)
    where
      m x = fmap (embed . m . fmap join . f . fmap g) x


Recursion Schemes Excursions

I thought I'd document my excursion into recursion schemes.
For ever and always, recursive patterns have and will pop up, but I had to squash the combinators to fit. I thought I'd finally cut a swathe through the higher dimensional morph-ine like haze recursion schemes induces.

So, to be terse:
Recursion schemes maps our recursive type into its base functor using a type family 'Base'.
In order to use harness the power of its combinators we need to create instances of the classes Foldable and Unfoldable.
An instance of Foldable implies that we can 'project' our recursive type onto the base functor.
An instance of Unfoldable implies we can embed our base functor into the recursive type.
Instances of both mean that the recursive type and the base functor are isomorphic. The base-functor should always be <= the recursive type.

So onto the first of them:
A catamorphism is a fold, it builds up a tower of applications of f and then collapses them from the inside - a right fold. The projection allows us to talk in terms of the base functor which we know how to reach inside of and twiddle around in. The 'fmap m' folds the inner part and provides the folded version to our algebra which simply performs a single step of the fold.

cata :: Foldable t => (Base t a -> a) -> t -> a
cata f = m where m = f . fmap m . project


Next post, para-morphisms.

Wednesday 10 December 2014

TopSort


Our story today begins with the rather unmotivated type

eval :: Functor f => f (f a -> a) -> f a

Lets construct a value of the type,
eval f = xs where xs = fmap ($ xs) f

Plugging the list functor in, we have:

eval :: [[a] -> a] -> [a]

It becomes a little clearer from looking at the function that what we're doing is creating a list where each value in the list is a function of the list itself. The base case would be the constant function.
Creating a value of the argument to eval we have something like:

arg = [\list -> list !! 1, const 3, \list -> list !! 0 + list !! 1 + list !! 5const 2const 5const 4]

If we eval arg , it provides arg as the argument to each index in arg . If the graph isn't acyclic we're going to <<loop>>; this is very reminiscent of a spreadsheet.

Thus eval provides a method of traversal of a directed acyclic graph when the functor is a list. Among the many algorithms related to graph traversal I'm going to pick topological sort.
So each element in the list has a list of dependencies.

type AdjList = [[[Int]] -> [Int]]

topSort :: AdjList -> [Int]
topSort a = map fst res
    where 
     indices = [0..]
     res = sortBy comparator $ zip indices (eval a)
      comparator x y = compare (length (snd x)) (length (snd y))

We evaluate the dependencies and tag them with their indices. Then we sort them by the number of dependencies. The algorithm works because for any two nodes u and v, if there is a directed path from u to v, the number of dependencies associated with u is strictly greater than that of v.

What remains is to construct sample adjacency lists for which we will need to construct a list of dependencies:

ref = flip (!!)

deps l = foldl f (const []) l
   where
      f g e = (++) <$> g <*> fmap (e:) (ref e)

adj1 = [deps [1, 2, 3], const [], deps [1, 3], const []]

Full code at https://github.com/joshcc3/HaskellExperiments/blob/master/interestingTypes/Loeb.hs