I think monad-control is what I was looking for but was missing when trying to come up with a solution involving lift. Thanks!

Paul

On Tue, May 29, 2018 at 11:15 PM Li-yao Xia <lysxia@gmail.com> wrote:
Hi Paul,

We can use Data.Coerce.coerce to do the (un)wrapping and defer to the
Alternative/MonadPlus instance at the right level.

(MyMonad a) is representationally equivalent to (Stack (Either String
a)), where Stack is defined as

type Stack = ReaderT Env (StateT Store (ListT Identity))

Thus, we can coerce Stack's MonadPlus methods (which lift ListT's
methods) as follows:


import Data.Coerce

instance MonadPlus MyMonad where
   mzero :: forall a. MyMonad a
   mzero = coerce (mzero @Stack @(Either String a))

   mplus :: forall a. MyMonad a -> MyMonad a -> MyMonad a
   mplus = coerce (mplus @Stack @(Either String a))


The upcoming DerivingVia generalizes this pattern somewhat, although it
will be necessary to pick a different equivalent type than above.


newtype MyMonad = MyMonad {
   runMyMonad :: ((ReaderT Env (ExceptT String
     (StateT Store (ListT Identity)))) a) }
   deriving (Functor, Applicative, Monad)
   deriving (Alternative, MonadPlus)
     via (ReaderT Env (ExceptT' String (StateT Store (ListT Identity))))


where ExceptT' is a transformer identical to ExceptT, but it lifts the
transformed monad's MonadPlus instance instead of providing its own.

A different solution is monad-control, which generalizes MonadTrans.
Like `lift`, `liftWith` moves an action "up" one level in a transformer
stack, but in addition, it provides a way to move "down" as well, as a
continuation given to the wrapped action.

Although powerful, it is certainly not an easy interface to grasp, but
my point here is to demonstrate one use of it.


liftControl
   :: (MonadTransControl t, Monad m, Monad (t m))
   => (Run t -> m (StT t a)) -> t m a
liftControl f = liftWith f >>= restoreT . return

instance Alternative MyMonad where
   empty = MyMonad ((lift . lift) empty)
   MyMonad a <|> MyMonad b = MyMonad $
     liftControl $ \run1 -> liftControl $ \run2 ->
       (run2 . run1) a <|> (run2 . run1) b


It's also not quite obvious this does the right thing so here are some
QuickCheck tests that these two implementations are equivalent to the
original one:

https://lpaste.net/2697355636458389504

Cheers,
Li-yao
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.