[Haskell-cafe] Auto elimination of MVars using a monad or monad transformer.

Chris Dew cmsdew at gmail.com
Fri Feb 25 07:41:35 CET 2011


Hello, just like everyone else, I have a question about monads.  I've
read the tutorials, written one monad myself (not in this email), but
I still consider myself a Haskell beginner.

* Does GHC eliminate unneeded MVars during compilation?

I'm expecting that it doesn't, as that would mean optimising away
ForkIOs, which would be quite a thing to do.  I've included example
code below.

* Is there a monad which allows their automatic elimination of MVars
(or their creation only when necessary)?

This would be similar to how the IO monad allows you to do purely
functional things with a do block, using let.

I've had a go at a lifting function, which wraps a pure function into
an IO action which forever reads from one MVar and writes to another.
What I'm looking for is some form of Monadic context in which many
pure functions, MVar fillers and MVar consumers could be linked
together, where only the necessary MVars remain (or were created) at
compilation time.

* Would this be a monad, or a monad transformer?

* Can you specialise a monad transformer on a single base (in this
case IO) so that you can use forkIO in the bind or return?

Thanks,

Chris.


module Main (
main
)
where

import Control.Concurrent (forkIO, MVar, newEmptyMVar, putMVar,
takeMVar, ThreadId, threadDelay)
import Control.Monad (forever)

stepA :: MVar String -> IO ()
stepA boxa = forever $ do
                      line <- getLine
                      putMVar boxa line

stepB :: MVar String -> IO ()
stepB boxb = forever $ do
                      line <- takeMVar boxb
                      putStrLn line

-- This simply wraps a string in brackets.
bracket :: String -> String
bracket x = "(" ++ x ++ ")"

-- This lifts a function into an action which forever performs the function
-- between the two MVars given.
lft :: (a -> b) -> MVar a -> MVar b -> IO ()
lft f c d = forever $ do
                     x <- takeMVar c
                     putMVar d (f x)

-- Just like C's main.
main :: IO ()
main = do
      box <- newEmptyMVar
      box2 <- newEmptyMVar
      forkIO $ stepA box
      forkIO $ lft bracket box box2
      forkIO $ stepB box2
      threadDelay 10000000 -- Sleep for at least 10 seconds before exiting.



More information about the Haskell-Cafe mailing list