[Haskell-cafe] Is there a recursion-scheme function to push info down one level?

Robin Palotai palotai.robin at gmail.com
Fri Jan 25 21:48:33 UTC 2019


I came up with this utility function so I can access some info (`n`) from
the parent's level:

hoistWithUpper
    :: forall f g s t n
     . (Functor g)
    => (forall a. f a -> n)
    -> n
    -> (forall a. n -> f a -> g a)
    -> (n -> s -> t)
    -> Free f s
    -> Free g t
hoistWithUpper fu n0 hoistFr hoistPure = go n0
  where
    go :: n -> Free f s -> Free g t
    go n fr = case fr of
        Pure s -> Pure (hoistPure n s)
        Free f -> let n2 = fu f
                  in Free (go n2 <$> (hoistFr n f :: g (Free f s)))

I wonder if there's already a generalized form of this in
recursion-schemes? Admittedly I'm fine with my helper so don't loose nights
on this, but a little type golfing never hurts.

There's a similar function `inherit` [1] in fixplate, but that operates on
Fix (Mu there), not Free. With Free I guess the complication is managing
the different way of maintaining annotation at the Free and Pure ctors.

Practically I pass in

   (\n f -> ConstProd (Pair (Const n) f))  -- for hoistFr
   (\n u -> (n,u))  -- for hoistPure.

where

    newtype ConstProd c f a = ConstProd (Product (Const c) f a)

Thanks!
Robin

[1]:
http://hackage.haskell.org/package/fixplate-0.1.7/docs/src/Data-Generics-Fixplate-Attributes.html#inherit
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20190125/f22decf9/attachment.html>


More information about the Haskell-Cafe mailing list