
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