[Haskell-cafe] extensible-transformers

Ben Foppa benjamin.foppa at gmail.com
Wed Jul 9 23:52:17 UTC 2014


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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140709/195fa960/attachment.html>


More information about the Haskell-Cafe mailing list