Hello Magnus, although your approach is a bit more pragmatic, I always prefer to use concurrency to implement predictable logging. This is a bit more code, but works much nicer and a lot more predictable:
{-# LANGUAGE ExistentialQuantification #-} module Main where import Control.Concurrent import Control.Monad data LoggerMsg = forall a. Show a => LogLine a | QuitLogger (IO ()) main :: IO () main = do log <- newEmptyMVar forkIO $ forever $ do msg <- takeMVar log case msg of LogLine ln -> print ln QuitLogger c -> c >> myThreadId >>= killThread forM_ [1..10] $ putMVar log . LogLine waiter <- newEmptyMVar putMVar log $ QuitLogger (putMVar waiter ()) takeMVar waiter Whenever you put a LogLine message into the MVar, as soon as the putMVar action returns, it is guaranteed that the last log line has been processed. If you don't need that guarantee, use Chan instead of MVar. Greets, Ertugrul. Magnus Therning <mag...@therning.org> wrote: > I've been playing around with (WriterT [Int] IO), trying to get the > log out and map `print` over it... and do it lazily. However, I'm not > really happy with what I have so far, since I've had to resort to > `unsafePerformIO`. Any hints are welcome. > > What I have so far is: > > foo = let > _tell i = do > a <- return $ unsafePerformIO $ sleep 1 > tell [a + 1 `seq` i] > in do > mapM_ _tell [1..10] > > main = do > (_, ~res) <- runWriterT foo > mapM_ print res > > Without the `seq` the call to sleep will simply be skipped (is there > an easier way to force evaluation there?). Without `unsafePerformIO` > all the sleeping is done up front, and all numbers are print at once > at the end. > > The goal is of course to use code along the same shape to do something > more useful, and then `unsafePerformIO` will really be unsafe... -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe