
Hi all, I try to create a simple monad using a stack of Reader and IO but when using it, I encounter some problems. The Monad is defined as M a: {-# LANGUAGE GeneralizedNewtypeDeriving #-} module Main where import Control.Monad.Reader import Control.Concurrent newtype M a = M { unM :: ReaderT String IO a } deriving (Monad, MonadIO, MonadReader String) runM :: String -> M a -> IO a runM s m = runReaderT (unM m) s loop :: (String -> M ()) -> M () loop f = forever $ f "hello" I then define a callback function to be invoked by 'loop': callback :: String -> M () callback s = liftIO $ print s >> threadDelay 1000000 So far so good. Then I test it like this: test1 :: IO () test1 = runM "foo" $ do loop callback liftIO $ print "here" -- OK. Never reached Still works fine. 'loop' never returns. In a real life application 'loop' is an event loop and I'd like to fork it into a new thread like this: test3 :: IO () test3 = runM "foo" $ liftIO $ do forkIO $ do return $ loop callback return () print "here" threadDelay 2000000 This not only looks ugly, it also doesn't work. For 'loop callback' to pass the type checker, it had to be returned into the IO monad. But I guess due to laziness, 'loop' will never be called. This can be confirmed without forkIO: test2 :: IO () test2 = runM "foo" $ liftIO $ do return $ loop callback print "here" Again, 'loop callback' will not be invoked. Now, given that I must find a way to combine IO and my M monad I don't know what to try next. Prima facie it seems I must somehow force 'loop callback' to be evaluated, but how? Not to mention all the liftIO clutter. I would greatly appreciate some help here. Thank you very much! Cheers, Levi

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

Also, you could define a forkM function like this: forkM :: M () -> M ThreadId forkM (M r) = M $ mapReaderT forkIO r which could be used like this: test = runM "foo" $ do forkM $ loop callback liftIO $ print "here" If we were to expand forkM in test, we would get something like: test' = runM "foo" $ do env <- ask liftIO $ forkIO (runM env $ loop callback) liftIO $ print "here" So, this does not change the 'rule' of forkIO having to come before a runM. It just wraps it up nicely. - jeremy

On Sun, Aug 23, 2009 at 5:21 PM, Jeremy Shaw
Also, you could define a forkM function like this:
forkM :: M () -> M ThreadId forkM (M r) = M $ mapReaderT forkIO r
which could be used like this:
test = runM "foo" $ do forkM $ loop callback liftIO $ print "here"
If we were to expand forkM in test, we would get something like:
test' = runM "foo" $ do env <- ask liftIO $ forkIO (runM env $ loop callback) liftIO $ print "here"
So, this does not change the 'rule' of forkIO having to come before a runM. It just wraps it up nicely.
Somehow I missed this e-mail when I replied last time. Now this is actually the solution to my problem. I didn't think of a second runM with the same environment. Brilliant (OTOH it probably highlights the fact that I am only a Monad novice). Many thanks Jeremy. You saved my day! Cheers, Levi

Hi Jeremy,
On Sun, Aug 23, 2009 at 5:08 PM, Jeremy Shaw
What you probably want is:
test2' :: IO () test2' = runM "foo" $ do loop callback liftIO $ print "here"
This equals my test1 version which is fine without forkIO.
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.
I see. This is what I feared.
If you want to add a forkIO, the forkIO must go before the runM:
OK. I tried all kinds of combinations, but not forkIO in front of 'runM' . The reason being that I only use forkIO because 'loop' never returns so in order to proceed I would have to put it into the background. Basically I want two threads running inside the same M monad.
hope this helps.
Many thanks Jeremy. Your explanations are indeed very helpful. But they also strengthen my gut feeling that running two threads in the same M monad is hard (if not impossible) to do. Cheers, Levi

On Sun, Aug 23, 2009 at 9:14 AM, Levi
Greenspan
Many thanks Jeremy. Your explanations are indeed very helpful. But they also strengthen my gut feeling that running two threads in the same M monad is hard (if not impossible) to do.
I think here is where you are going wrong; there is no "same M monad". Perhaps it will help if you saw how ReaderT works: newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a } That gives you these two functions: ReaderT :: (r -> m a) -> ReaderT r m a runReaderT :: ReaderT r m a -> r -> m a There's nothing magic about it; ReaderT just wraps up a function and provides "bind" and "return" so that you can glue actions together: (>>=) :: Monad m => ReaderT r m a -> (a -> ReaderT r m b) -> ReaderT r m b ma >>= f = ReaderT $ \r -> do a <- runReaderT ma r let mb = f a b <- runReaderT mb r return b (of course the code is written more concisely than this, but I am trying to help make it explicit) So internally *every* bind has multiple "runM"s inside of it, magically whipped up by the compiler inside of "deriving Monad". When you do "runM" explicitly here, you are just helping to lift "forkIO" back into your monad. -- ryan
participants (3)
-
Jeremy Shaw
-
Levi Greenspan
-
Ryan Ingram