[Haskell-cafe] Monad woes

Jeremy Shaw jeremy at n-heptane.com
Sun Aug 23 11:08:08 EDT 2009


At Sun, 23 Aug 2009 16:23:54 +0200,
Levi Greenspan wrote:

What you probably want is:

test2' :: IO ()
test2' = runM "foo" $ do
    loop callback
    liftIO $ print "here"

Taking a look at your version:

> test2 :: IO ()
> test2 = runM "foo" $ liftIO $ do
>     return $ loop callback
>     print "here"

Since 'print' has the type IO (), this whole do statement has the type
IO ():

 do return $ loop callback
    print "here"

In isolation, we see the following expression has the type:

*Main> :t     return $ loop callback
return $ loop callback :: (Monad m) => m (M ())

so, in context it has the type:

return $ loop callback :: (Monad m) => IO (M ())

It is an IO operation which returns a value of type, M (). But,
nothing is done with that value, it is just thrown away.

We could hack it to work like this:

test2'' :: IO ()
test2'' = runM "foo" $ liftIO $ do
    m <- return $ loop callback
    runM "m" m
    print "here"

but test2' seems better.

If you want to add a forkIO, the forkIO must go before the runM:

testFork :: IO ThreadId
testFork = forkIO $ runM "foo" $ do
    loop callback
    liftIO $ print "here"

Let's say we try to put it after the runM:

testFork :: IO ThreadId
testFork = runM "foo" $ forkIO $ do
    loop callback
    liftIO $ print "here"

This will fail with the error:

    Couldn't match expected type `M ()' against inferred type `IO ()'

Because runM expects something of type M (), but forkIO has the type
IO ThreadId. So, we can use liftIO to convert the forkIO into a value
of type M:

testFork :: IO ThreadId
testFork = runM "foo" $ liftIO (forkIO $ do
    loop callback
    liftIO $ print "here")

Now we get the error: 

    Couldn't match expected type `M ()' against inferred type `IO ()'
    In a stmt of a 'do' expression: loop callback

because forkIO expects values of type IO (), but the do block has the
type M ().

So, we can use runM to convert the M () to an IO ()

testFork :: IO ThreadId
testFork = runM "foo" $ liftIO (forkIO $ do
    runM "loop" $ loop callback
    print "here")

But, we see that we are now back to the position of having the forkIO
before the (second) runM. We can simplfy that expression to just:

testFork :: IO ThreadId
testFork = forkIO $ do
    runM "loop" $ loop callback
    print "here"

hope this helps.

- jeremy 


More information about the Haskell-Cafe mailing list