Proposal: make liftF a method of MonadFree

David Feuer david.feuer at gmail.com
Fri Jul 16 20:55:17 UTC 2021


We have

class Monad m => MonadFree f m | m -> f where
  wrap :: f (m a) -> m a

liftF :: (Functor f, MonadFree f m) => f a -> m a
liftF = wrap . fmap pure

I propose we change this to

class Monad m => MonadFree f m | m -> f where
  wrap :: f (m a) -> m a

  liftF :: f a -> m a
  default liftF :: Functor f => f a -> m a
  liftF = wrap . fmap pure

and add a function

defaultWrap :: MonadFree f m => f (m a) -> m a
defaultWrap = join . liftF

This change is not strictly backwards compatible. Some instances might,
hypothetically, have to add a Functor constraint. For example, the classic
Control.Monad.Free and Control.Monad.Trans.Free would need them. However,
those instances already have (currently redundant) Functor constraints, so
that doesn't seem like a big deal.

An alternative would be to hew more strictly to backwards compatibility by
placing a Functor f constraint on liftF. This seems a bit sad for "freer"
instances that don't need it. For example, we have

newtype FT f m a = FT
  { runFT :: forall r. (a -> m r) -> (forall x. (x -> m r) -> f x -> m r)
-> m r }

for which

liftF :: f a -> FT f m a
liftF fa = FT $ \pur bndf -> bndf pur fa

Pull request at https://github.com/ekmett/free/pull/208
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20210716/fcb1326c/attachment.html>


More information about the Libraries mailing list