Selecting a transformer in a monad transformer stack

Hello, I have a newtype for a monad transformer stack: newtype MyMonad a = MyMonad { runMyMonad :: ((ReaderT Env (ExceptT String (StateT Store (ListT Identity)))) a) } and I'd like to it derive MonadPlus. The default instance for MonadPlus I get via GeneralizedNewtypeDeriving is the ExceptT one because it is the outermost transformer implementing MonadPlus. I would like to use the ListT instance instead. The best solution I have come up with is to define: instance MonadPlus MyMonad where mzero = MyMonad $ ReaderT $ \e -> ExceptT $ StateT $ \s -> ListT $ Identity [] mplus a b = MyMonad $ ReaderT $ \e -> ExceptT $ StateT $ \s -> ListT $ Identity $ let run x = runIdentity (runListT (runStateT (runExceptT (runReaderT (runAbstract x) e)) s)) as = run a bs = run b in as ++ bs My questions are: - Is there a shorter way to define mplus? - Is there maybe some variation of monad transformer stacks where the layers are named and can be accessed by name? (I know of effects handlers but I'd like to stick to monad transformers for now.) Paul

There is a typo in the definition of mplus in my previous message:
"runAbstract" should be "runMyMonad".
On Tue, May 29, 2018 at 6:06 PM Paul Brauner
Hello,
I have a newtype for a monad transformer stack:
newtype MyMonad a = MyMonad { runMyMonad :: ((ReaderT Env (ExceptT String (StateT Store (ListT Identity)))) a) }
and I'd like to it derive MonadPlus. The default instance for MonadPlus I get via GeneralizedNewtypeDeriving is the ExceptT one because it is the outermost transformer implementing MonadPlus. I would like to use the ListT instance instead. The best solution I have come up with is to define:
instance MonadPlus MyMonad where mzero = MyMonad $ ReaderT $ \e -> ExceptT $ StateT $ \s -> ListT $ Identity [] mplus a b = MyMonad $ ReaderT $ \e -> ExceptT $ StateT $ \s -> ListT $ Identity $ let run x = runIdentity (runListT (runStateT (runExceptT (runReaderT (runAbstract x) e)) s)) as = run a bs = run b in as ++ bs
My questions are: - Is there a shorter way to define mplus? - Is there maybe some variation of monad transformer stacks where the layers are named and can be accessed by name? (I know of effects handlers but I'd like to stick to monad transformers for now.)
Paul

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

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
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.
participants (2)
-
Li-yao Xia
-
Paul Brauner