
On Fri, Oct 9, 2009 at 1:39 PM, Felipe Lessa
On Fri, Oct 09, 2009 at 01:27:57PM -0400, David Menendez wrote:
On Fri, Oct 9, 2009 at 11:12 AM, Felipe Lessa
wrote: That's really nice, Oleg, thanks! I just wanted to comment that I'd prefer to write
share :: IO a -> IO (IO a) share m = mdo r <- newIORef (do x <- m writeIORef r (return x) return x) return (readIORef r >>= id)
which unfortunately needs {-# LANGUAGE RecursiveDo #-} or some ugliness from mfix
share :: IO a -> IO (IO a) share m = do r <- mfix $ \r -> newIORef (do x <- m writeIORef r (return x) return x) return (readIORef r >>= id)
Alternatively,
share m = do r <- newIORef undefined writeIORef r $ do x <- m writeIORef r (return x) return x return $ readIORef r >>= id
Which is basically the same as your version, but only needs one IORef.
Hmmm, but my version also needs only one IORef, right? In fact I first wrote the same code as yours but I've frowned upon the need of having that 'undefined' and an extra 'writeIORef'.
It's in the implementation of mfix for IO. From System.IO,
fixIO :: (a -> IO a) -> IO a
fixIO k = do
ref <- newIORef (throw NonTermination)
ans <- unsafeInterleaveIO (readIORef ref)
result <- k ans
writeIORef ref result
return result
If we inline that into your definition, we get
share m = do
ref <- newIORef (throw NonTermination)
ans <- unsafeInterleaveIO (readIORef ref)
r <- newIORef $ do { x <- m; writeIORef ans (return x); return x }
writeIORef ref r
return (readIORef r >>= id)
So behind the scenes, the mfix version still creates an IORef with
undefined and has an extra writeIORef.
It also has that unsafeInterleaveIO, but I don't think there's any way
that can cause a problem.
Incidentally, none of the versions of share discussed so far are
thread-safe. Specifically, if a second thread starts to evaluate the
result of share m while the first thread is still evaluating m, we end
up with the effects of m happening twice. Here's a version that avoids
this by using a semaphore.
share m = do
r <- newIORef undefined
s <- newMVar False
writeIORef r $ do
b <- takeMVar s
if b
then do
putMVar s True
readIORef r >>= id
else do
x <- m
writeIORef r (return x)
putMVar s True
return x
return $ readIORef r >>= id
In the worst case, MVar will get read at most once per thread, so the
overhead is limited. Under normal circumstances, the MVar will be read
once and then discarded.
--
Dave Menendez