Getting WriterT log lazily

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... /M -- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus@therning.org http://therning.org/magnus identi.ca|twitter: magthe

How about this:
type ActionLog v = Writer [IO v]
myTell :: v -> ActionLog v () myTell a = tell [sleep 1 >> return a]
foo :: ActionLog Int () foo = mapM_ myTell [1..10]
main = sequence_ results where (_, vals) = runWriter foo results = map (>>= print) vals
-- ryan
On Sun, May 3, 2009 at 2:17 PM, Magnus Therning
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...
/M
-- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus@therning.org http://therning.org/magnus identi.ca|twitter: magthe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
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/

Magnus Therning wrote:
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...
So what you're trying to do is run two IO actions at the same time: one to produce values, the other to consume values. If you want to be really safe use threads (does that sound paradoxical?), as Ertegrul suggested, although I'd use channels instead of an MVar since this seems to be a perfect example for them. Otherwise, you can use unsafeInterleaveIO: no unsafePerformIO or seq needed, but there's still "unsafe" in that name there. This works for me:
foo :: WriterT [Int] IO () foo = let _tell i = do a <- lift $ unsafeInterleaveIO $ threadDelay 100000 >> return 0 tell [i + a] in do mapM_ _tell [1..10]
Martijn.

Martijn van Steenbergen wrote:
Magnus Therning wrote:
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...
So what you're trying to do is run two IO actions at the same time: one to produce values, the other to consume values.
If you want to be really safe use threads (does that sound paradoxical?), as Ertegrul suggested, although I'd use channels instead of an MVar since this seems to be a perfect example for them.
Otherwise, you can use unsafeInterleaveIO: no unsafePerformIO or seq needed, but there's still "unsafe" in that name there. This works for me:
foo :: WriterT [Int] IO () foo = let _tell i = do a <- lift $ unsafeInterleaveIO $ threadDelay 100000 >> return 0 tell [i + a] in do mapM_ _tell [1..10]
Thanks, that does indeed work, but it still requires that "unsafe" there so I'm hesitant replacing the call to threadDelay with something more complicated, where it isn't obviously safe. Indeed, I think I'll go for the MVar or possibly a Chan. Thanks for the help. /M -- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus@therning.org http://therning.org/magnus identi.ca|twitter: magthe

Magnus Therning wrote:
Martijn van Steenbergen wrote:
Otherwise, you can use unsafeInterleaveIO: no unsafePerformIO or seq needed, but there's still "unsafe" in that name there. This works for me:
... Thanks, that does indeed work, but it still requires that "unsafe" there so I'm hesitant replacing the call to threadDelay with something more complicated, where it isn't obviously safe.
Sorry for the late reply, but I'd like to piggy-back on this. It's my understanding that unsafeInterleaveIO is only unsafe insofar as it makes the IO lazy and so the IO may be performed later or never at all (if its return value is never wanted) and is therefore no less safe than, say, generating a list of IO actions as was suggested by an earlier reply. It seems to me that its unsafeness is of a completely different nature than unsafePerformIO... am I missing something? steve

Stephen Hicks
Magnus Therning wrote:
Martijn van Steenbergen wrote:
Otherwise, you can use unsafeInterleaveIO: no unsafePerformIO or seq needed, but there's still "unsafe" in that name there. This works for me:
... Thanks, that does indeed work, but it still requires that "unsafe" there so I'm hesitant replacing the call to threadDelay with something more complicated, where it isn't obviously safe.
Sorry for the late reply, but I'd like to piggy-back on this. It's my understanding that unsafeInterleaveIO is only unsafe insofar as it makes the IO lazy and so the IO may be performed later or never at all (if its return value is never wanted) and is therefore no less safe than, say, generating a list of IO actions as was suggested by an earlier reply. It seems to me that its unsafeness is of a completely different nature than unsafePerformIO... am I missing something?
There are two issues with unsafePerformIO: The laziness makes evaluation unpredictable to some extent, but that's intentional. But for example what if the IO computation throws an exception? There is no well-defined behaviour, not even a well-known convention. For example, hGetContents simply aborts, which makes errors undetectable. All in all, unsafeInterleaveIO is a handy tool, but you need to be careful about its side effects. Greets, Ertugrul. -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/

Ertugrul Soeylemez
There are two issues with unsafePerformIO: [...]
Of course I meant unsafeInterleaveIO, sorry. There are a lot more than two issues with unsafePerformIO. =) Greets, Ertugrul. -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/
participants (5)
-
Ertugrul Soeylemez
-
Magnus Therning
-
Martijn van Steenbergen
-
Ryan Ingram
-
Stephen Hicks