Wednesday, April 8, 2009

Beware the monads!

It seems that every noob learning Haskell has put up a blog raving about how monads are great. This might make you think twice about whether monads are the right approach to computation:

Boojum writes on Programming Reddit:

I can get along with the IO monad just fine, for example. But then I also need to carry some state of my own around. For one of my projects, Parsec would be pretty handy, but then that has its own monad too. Fairly quickly I find myself overwhelmed by the proliferation of monads to juggle.

I'm aware that monad transformers are supposed mitigate this problem but I've yet to find a tutorial on them that doesn't leave me even more confused about how to put them all together. I think there's definitely room for a better tutorial on this. If anyone knows of a good one, I'd love to see it.


Oleg Kiselyov, a functional programming researcher and practitioner had this to say:

... it seems that the unending stream of monad tutorials explaining once again what is essentially a functional composition (or the A-normal form, to be more precise) points out that perhaps the concept of a Monad isn't at all a good match for a programming language practice. Monads may be deeply rooted in Category Theory -- but then Peano numerals are too have the clearest mathematical foundations and yet nobody seriously proposes to use them for practical numerical computations.


DDS Manual describes the difficulties of using monads in Haskell:

This puts us in a situation where we really need two copies of every higher-order function, one pure and one monadic. This is even more of a problem when a library (like Data.Map) exports a pure version but not a monadic one. In this case we either have to refactor our code to be less monadic, or spend time writing a function that should really be in the library.

5 comments:

  1. In response to the first point, I would agree and say, yes, there is a profusion of "Monads are space spacesuits" or "Monads are like..." tutorials that don't do a very good job of explaining how to use monad transformers, in part because they are usually written shortly after the author started to understand monads himself.

    A large number of Oleg's points are also valid. Monad Transformers are not universal, monads are not closed under composition like many other data structures and the result is rarely commutative, so the need for monad transformers to cover the common cases where monads do compose cleanly is a bit of a wart, but one mandated by a lot of theory. The problem of having both backtracked and unbacktracked state and requiring disambiguation with multiple applications of lift is also a wart, but one that in the few situations where it happens can be encapsulated by defining a couple of helper functions and using them consistently to get proper lifting.

    In response to Oleg's point advocating type and effect systems, Oleg has his own particular axe to grind with respect to control structures involving delimited continuations and dynamic binding that makes sense to him and a handful of others and is unfortunately completely opaque to a large part of the community. Of course he likes type and effect systems, they match very cleanly with his world view, but there aren't any really usable such systems in the wild. The closest thing is DDC.

    In response to the DDC manual, I would say that if you are capable of a pure interface you should very much NOT provide a random monadic wrapper! That wrapper would imply ordering that simply is not present in the work flow.

    If the problem is that you don't have a monad that represents how to work with your map? you can always toss it into a StateT (Map k v) wrapped around your existing monad. and use get, gets, put, and modify. It not that you need to write these non-existent functions, you just need to compose a couple of very small ones.

    Using a Map monadically isn't hard!

    do {
    modify (insert 2 "Hello");
    Just x <- gets (lookup 2);
    modify (insert 3 (x ++ " World"))
    }

    It reads cleanly and just requires you to use the building blocks that are already in the room.

    Creating insertM and lookupM to replace the calls to modify and gets costs you functionality, because now you are limited to the scenario where you only have one piece of state. How often is that really the case?

    Inside of DDC this can make a lot more sense than inside of Haskell the map might exist in a mutable region and allow you to directly update it.

    I love the work that Lippmeier is doing on DDC, but I worry that the costs of the approach in terms of insanely large type annotations is perhaps great enough to outweigh the benefits. I say this from the perspective of having gone down a similar programming language design path using substructural logic in many of the ways he is using his type and effect system.

    The cure is very likely worse than the disease.

    ReplyDelete
  2. The following is a file that I refer to constantly. It shows how to combine State and Error with IO in various combinations and orders and shows the effects thereof. Use freely. It's not too polished because I stopped working on it shortly after I figured out what the heck I was doing!

    {-
    A demonstration of combining different permutations of State, Error, and IO monads.
    Shows the results of such combinations.
    -}

    module Main where

    import System.IO

    import Control.Monad.State
    import Control.Monad.Error

    -- runErrorT :: (m (Either e a))
    -- runStateT :: (s -> m (a, s))

    -- The state for state monad examples

    data TestState = TestState { value :: Int }
    deriving (Show)

    data TestState2 = TestState2 { state2 :: String }
    deriving (Show)

    -- Must use this form of signature rather than "State TestState ()"
    increment :: (MonadState TestState m) => m ()
    increment = modify $ \ s -> TestState (1 + (value s))

    increment2 :: (MonadState TestState2 m) => m ()
    increment2 = modify $ \ s -> TestState2 ('x' : (state2 s))

    -- The error type for error monad examples

    data TestError
    = TestError String
    deriving (Show)

    instance Error TestError where
    noMsg = TestError "<unknown error>"
    strMsg s = TestError s

    -------------------------------------------------------------------------------
    -- Lifted IO

    cout :: (MonadIO m) => String -> m ()
    cout = liftIO . hPutStr stdout

    coutLn :: (MonadIO m) => String -> m ()
    coutLn = liftIO . hPutStrLn stdout

    -------------------------------------------------------------------------------
    -- Main

    main :: IO ()
    main =
    do
    testStateError
    testErrorState
    testStateState
    testState
    testStateIO
    testErrorIO
    testStateErrorIO
    testErrorStateIO

    -------------------------------------------------------------------------------
    -- MONAD: State

    runState' :: State TestState ()
    runState' = do
    increment
    increment

    testState :: IO ()
    testState =
    do
    putStrLn "-- State"
    r <- return $ runState runState' $ TestState 0
    putStrLn $ show r

    -------------------------------------------------------------------------------
    -- COMBONAD: StateState

    type StateState a = StateT TestState (State TestState2) a

    runStateState :: StateState ()
    runStateState =
    do
    increment
    --increment2

    testStateState :: IO ()
    testStateState =
    do
    putStrLn "-- StateState"
    r <- return $ runStateT (runState runStateState (TestState 0)) (TestState2 "")
    putStrLn $ show r

    -------------------------------------------------------------------------------
    -- COMBONAD: StateError

    type StateError a = StateT TestState (Either TestError) a

    runStateError1 :: StateError ()
    runStateError1 =
    do
    increment
    throwError $ noMsg
    increment

    runStateError2 :: StateError ()
    runStateError2 =
    do
    increment
    increment

    testStateError :: IO ()
    testStateError =
    do
    putStrLn "-- StateError"
    r <- return $ runStateT runStateError1 $ TestState 0
    putStrLn $ show r
    r <- return $ runStateT runStateError2 $ TestState 0
    putStrLn $ show r

    -------------------------------------------------------------------------------
    -- COMBONAD: ErrorState

    type ErrorState a = ErrorT TestError (State TestState) a

    runErrorState1 :: ErrorState ()
    runErrorState1 =
    do
    increment
    throwError $ TestError "biffed"
    increment

    runErrorState2 :: ErrorState ()
    runErrorState2 =
    do
    increment
    increment

    testErrorState :: IO ()
    testErrorState =
    do
    putStrLn "-- ErrorState"
    r <- return $ runState (runErrorT runErrorState1) $ TestState 0
    putStrLn $ show r
    r <- return $ runState (runErrorT runErrorState2) $ TestState 0
    putStrLn $ show r

    -------------------------------------------------------------------------------
    -- COMBONAD: StateIO

    type StateIO a = StateT TestState IO a

    runStateIO :: StateIO ()
    runStateIO =
    do
    coutLn $ "hola, amigos"
    increment

    testStateIO :: IO ()
    testStateIO =
    do
    putStrLn "-- StateIO"
    r <- runStateT runStateIO $ TestState 0
    putStrLn $ show r

    -------------------------------------------------------------------------------
    -- COMBONAD: ErrorIO

    type ErrorIO a = ErrorT TestError IO a

    runErrorIO1 :: ErrorIO ()
    runErrorIO1 =
    do
    coutLn $ "step 1"
    coutLn $ "step 2"

    runErrorIO2 :: ErrorIO ()
    runErrorIO2 =
    do
    coutLn $ "step 1"
    throwError $ strMsg "biffed"
    coutLn $ "step 2"

    testErrorIO :: IO ()
    testErrorIO =
    do
    putStrLn "-- ErrorIO"
    r <- runErrorT runErrorIO1
    putStrLn $ show r
    r <- runErrorT runErrorIO2
    putStrLn $ show r

    -------------------------------------------------------------------------------
    -- COMBONAD: StateErrorIO

    type StateErrorIO a = StateT TestState (ErrorT TestError IO) a

    runStateErrorIO1 :: StateErrorIO ()
    runStateErrorIO1 =
    do
    coutLn $ "with error"
    increment
    throwError $ TestError "biffed"
    increment

    runStateErrorIO2 :: StateErrorIO ()
    runStateErrorIO2 =
    do
    coutLn $ "without error"
    increment
    increment

    testStateErrorIO :: IO ()
    testStateErrorIO =
    do
    putStrLn "-- StateErrorIO"
    r <- runErrorT $ runStateT runStateErrorIO1 $ TestState 0
    putStrLn $ show r
    r <- runErrorT $ runStateT runStateErrorIO2 $ TestState 0
    putStrLn $ show r

    -------------------------------------------------------------------------------
    -- COMBONAD: ErrorStateIO

    type ErrorStateIO a = ErrorT TestError (StateT TestState IO) a

    runErrorStateIO1 :: ErrorStateIO ()
    runErrorStateIO1 =
    do
    coutLn $ "with error"
    increment
    throwError $ TestError "biffed"
    increment

    runErrorStateIO2 :: ErrorStateIO ()
    runErrorStateIO2 =
    do
    coutLn $ "without error"
    increment
    increment

    testErrorStateIO :: IO ()
    testErrorStateIO =
    do
    putStrLn "-- ErrorStateIO"
    r <- runStateT (runErrorT runErrorStateIO1) $ TestState 0
    putStrLn $ show r
    r <- runStateT (runErrorT runErrorStateIO2) $ TestState 0
    putStrLn $ show r

    ReplyDelete
  3. Yeah, Haskell isn't the greatest language for sticking in blog comments...

    ReplyDelete
  4. @Bob

    You can always link to hpaste for large fragments of code.

    @Edward, Haskellx

    Thanks for commenting! I don't have time to write a reply right now.

    ReplyDelete
  5. COMBONAD ? A combo of monads through long compositions of monad transformers ?? Loved it ;-)

    ReplyDelete