extensible-transformers

Hi cafe, I whipped up extensible-transformers ( https://github.com/RobotGymnast/extensible-transformers) this afternoon. The idea is to make Monad transformer code more like extensible-effects code (http://hackage.haskell.org/package/extensible-effects). Here's a sample: {-# LANGUAGE FlexibleContexts #-} module Main(main) where import Control.Monad.Trans.Flexible import Control.Monad.Trans.List import Control.Monad.Trans.State.Strict -- A flexible transformer stack built from existing transformers using `liftT`. bar :: (In (StateT Int) t, In ListT t) => t () bar = do n <- liftT get liftT $ ListT $ return $ replicate n () -- A flexible transformer stack built from existing transformers using `liftT`. baz :: In (StateT Int) t => t () baz = do liftT $ state $ \i -> ((), i + (1 :: Int)) -- A flexible transformer monad stack composed of two other flexible -- transformer monad stacks. foo :: (In (StateT Int) t, In ListT t) => t () foo = do bar baz main :: IO () main = do evalStateT (runListT foo) (1 :: Int) >>= putStrLn . show runListT (evalStateT foo (2 :: Int)) >>= putStrLn . show Any feedback on this? Does such a package already exist? Thanks, Ben

Hi Ben,
I recently wrote a package with the same intent, called monad-classes
https://github.com/feuerbach/monad-classes
First, I am astonished with the simplicity of your approach. My library is much more
complicated, and uses closed type families to find the right layer.
I honestly didn't expect anything as simple as that to work — and yet is seems
to do well, at least in simple cases that I checked. I am not sure about more
complex ones — the use of IncoherentInstances somewhat bothers me, and I wonder
if it's going to backfire in more complex settings.
monad-classes also allows more flexibility regarding which transformers can
handle given effects:
* @MonadState s@ constraint can be handled by both lazy and strict StateT
* @MonadReader r@ can be handled by @StateT r@ (and similarly for
MonadWriter)
* Given a lens from s' to s, @MonadState s@ can be handled by @StateT s'@
Roman
* Ben Foppa
Hi cafe, I whipped up extensible-transformers ( https://github.com/RobotGymnast/extensible-transformers) this afternoon. The idea is to make Monad transformer code more like extensible-effects code (http://hackage.haskell.org/package/extensible-effects). Here's a sample:
{-# LANGUAGE FlexibleContexts #-} module Main(main) where
import Control.Monad.Trans.Flexible import Control.Monad.Trans.List import Control.Monad.Trans.State.Strict
-- A flexible transformer stack built from existing transformers using `liftT`. bar :: (In (StateT Int) t, In ListT t) => t () bar = do n <- liftT get liftT $ ListT $ return $ replicate n ()
-- A flexible transformer stack built from existing transformers using `liftT`. baz :: In (StateT Int) t => t () baz = do liftT $ state $ \i -> ((), i + (1 :: Int))
-- A flexible transformer monad stack composed of two other flexible -- transformer monad stacks. foo :: (In (StateT Int) t, In ListT t) => t () foo = do bar baz
main :: IO () main = do evalStateT (runListT foo) (1 :: Int) >>= putStrLn . show runListT (evalStateT foo (2 :: Int)) >>= putStrLn . show
Any feedback on this? Does such a package already exist?
Thanks, Ben
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Interesting, monad-classes does seem more potentially powerful - I've kind of pushed the limits of these parts of the type system just constructing this. It's fantastic that it asymptotically reduces the number of typeclass instances required. The IncoherentInstances in extensible-transformers bothers me as well - especially since I'm not very familiar with the unhappy cases of IncoherentInstances. One big problem with extensible-transformers is that it doesn't expose the inner Monad itself (mainly because there isn't one), which creates an issue for code that needs its transformers to transform more than just "something" The big plus (and minus) for extensible-transformers is that it can lift into the existing transformers stacks - it doesn't require rewriting the effects like extensible-effects or monad-classes. It's bound by the same pros and cons as transformers, but it's easy to integrate into existing code.

* Ben Foppa
The IncoherentInstances in extensible-transformers bothers me as well - especially since I'm not very familiar with the unhappy cases of IncoherentInstances.
The problem with IncoherentInstances is that when there's no reason to pick a specific instance, the compiler is happy to pick a general one, even if the more specific one is intended. In your case it is not obvious that this can be a problem. Unlike many "applications" of IncoherentInstances, that look like instance Cls a where ... yours have a superclass constraint involving the same class, so it's not trivial to discharge. I *think* that as soon as a monad stack doesn't contain two identical transformers, the bad case shouldn't happen. But I am not too confident here.
One big problem with extensible-transformers is that it doesn't expose the inner Monad itself (mainly because there isn't one), which creates an issue for code that needs its transformers to transform more than just "something"
Not sure what you mean. Can you give an example?
The big plus (and minus) for extensible-transformers is that it can lift into the existing transformers stacks - it doesn't require rewriting the effects like extensible-effects or monad-classes. It's bound by the same pros and cons as transformers, but it's easy to integrate into existing code.
monad-classes builds on transformers, too. It sits on the same layer as mtl, providing classes around transformers' types. That was the main motivation behind monad-classes — it turned out that the free monad approach is much slower than plain transformers. Roman

Hi Ben (and others), I'm covering the alternative approaches to the extensible effects problem in this series of articles: http://ro-che.info/articles/2014-06-11-problem-with-mtl.html http://ro-che.info/articles/2014-06-14-extensible-effects-failed.html http://ro-che.info/articles/2014-07-15-type-based-lift.html (to be continued) I thought you may be interested. Roman
participants (2)
-
Ben Foppa
-
Roman Cheplyaka