
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