lmm
lmm

Reputation: 17431

Recursion-schemes generalization of `tails`

I've got a recursion-schemes style structure and I'd like to obtain a list of all substructures including the full structure - i.e. the equivalent of what the tails function does on a List. I think it would be possible to implement this by calling para, mapping back to the original structure at each step, and then sticking the original structure on the front separately, but that seems very cumbersome: (untested, apologies if the Haskell is incorrect; written in terms of Mu as I haven't really understood the Base construct yet)

gtails :: Functor f => Mu f -> [Mu f]
gtails = para (\a -> (fmap fst a) : (foldMap snd a))

(i.e. in the case f=Prim this is tails, for other f it's a generalization)

Is there a nicer way? I realise this isn't so bad, but the fmap fst a to recover the "original" structure at that step feels quite cumbersome, and the foldMap snd a is something I find myself repeating a lot when using para (likewise fold a when using cata which again feels like it should be unnecessary).

Upvotes: 7

Views: 174

Answers (2)

gallais
gallais

Reputation: 12093

para is indeed the right function to use here. I have put everything in a self-contained gist augmented with examples if you want to play with it.

We start with the definition of the fixpoint Mu and the usual fold and para.

module Tails where

import Data.Function

newtype Mu f = In { out :: f (Mu f) }

fold :: Functor f => (f a -> a) -> Mu f -> a
fold alg = alg . fmap (fold alg) . out

para :: Functor f => (f (a, Mu f) -> a) -> Mu f -> a
para alg = alg . fmap (\m -> (para alg m, m)). out

We can then implement tails using para and an additional Foldable constraint allowing us to use foldMap to collect the intermediate result in the list monoid:

tails :: (Functor f, Foldable f) => Mu f -> [Mu f]
tails m = m : para (foldMap $ uncurry $ flip (:)) m

Upvotes: 1

András Kovács
András Kovács

Reputation: 30103

I don't see any issue with para. Just cons back the head and the tail at each Cons step:

import Data.Functor.Foldable

tails :: [a] -> [[a]]
tails = para (\case Nil -> [[]]; Cons a (as, res) -> (a : as) : res)

For clarity, specialized to lists and without recursion-schemes:

para :: (a -> [a] -> b -> b) -> b -> [a] -> b
para f z []     = z
para f z (a:as) = f a as (para f z as)

tails :: [a] -> [[a]]
tails = para (\a as res -> (a : as) : res) [[]]

However, if you'd like to be more general, the less nice para formulation comes handy:

import qualified Data.Functor.Foldable as Rec (Foldable)

tails :: (Rec.Foldable t, Base t ~ Prim [a]) => t -> [t]
tails as = as : para (\case Nil -> []; Cons a (as, res) -> as : res) as

This works for lists as usual, but you can also give type instance Base t = Prim [a] for other t-s, along with the Foldable instance, and use them as well.

Alternatively, we can keep the first tails definition at the cost of introducing an Unfoldable constraint:

tails' :: (Unfoldable t, Rec.Foldable t, Base t ~ Prim [a]) => t -> [t]
tails' = para (\case Nil -> [embed Nil]; Cons a (as, res) -> embed (Cons a as) : res)

This isn't too bad, since for each project there should be an inverse embed for fixpoints of functors anyway, so the Foldable and Unfoldable instances naturally come in pairs.

Upvotes: 10

Related Questions