<html><head></head><body><div>On Thu, 2018-01-25 at 09:50 +0000, Yotam Ohad wrote:</div><blockquote type="cite" style="margin:0 0 0 .8ex; border-left:2px #729fcf solid;padding-left:1ex"><div dir="rtl"><div dir="ltr">Hi,</div><div dir="ltr"><br></div><div dir="ltr">I've been digging around the source code of reactive-banana and I found this <a href="https://github.com/HeinrichApfelmus/reactive-banana/blob/master/reactive-banana/src/Reactive/Banana/Prim/Cached.hs">code</a>: <br><pre>data Cached m a = Cached (m a)

runCached :: Cached m a -> m a
runCached (Cached x) = x

-- | An action whose result will be cached.
-- Executing the action the first time in the monad will
-- execute the side effects. From then on,
-- only the generated value will be returned.
{-# NOINLINE cache #-}
cache :: (MonadFix m, MonadIO m) => m a -> Cached m a
cache m = unsafePerformIO $ do
    key <- liftIO $ newIORef Nothing
    return $ Cached $ do
        ma <- liftIO $ readIORef key    -- read the cached result
        case ma of
            Just a  -> return a         -- return the cached result.
            Nothing -> mdo
                liftIO $                -- write the result already
                    writeIORef key (Just a)
                a <- m                  -- evaluate
                return a<br><br></pre><pre><font face="sans-serif">I'm trying to understand the reasom behind the use of <font face="monospace">mdo<font face="sans-serif">. Can't it be like this:<br></font></font></font></pre><pre><font face="sans-serif"><font face="monospace"><font face="sans-serif"><font face="monospace">do<br>  a <- m<br>  liftIO $ writeIORef key (Just a)<br>  return a<br></font></font></font></font></pre><pre><font face="sans-serif"><font face="monospace"><font face="sans-serif"><font face="monospace"><font face="sans-serif">Removing the need for a recursive definition?<br><br></font></font></font></font></font></pre><pre><font face="sans-serif"><font face="monospace"><font face="sans-serif"><font face="monospace"><font face="sans-serif">Yotam<br></font></font></font></font></font></pre></div>

</div>
<pre>_______________________________________________</pre></blockquote><div><div style="font-family: monospace; width: 71ch;"><br></div><div style="font-family: monospace; width: 71ch;">I ran into a need for something similar for FRP myself. I agree that one probably has to be careful about duplicate/concurrent evaluation. My solution at the time was an action, which returns an action that is performed only once:</div><div style="font-family: monospace; width: 71ch;"><br></div><div style="font-family: monospace; width: 71ch;">lazyIO :: IO a -> IO (IO a)</div><div style="font-family: monospace; width: 71ch;">lazyIO action = do</div><div style="font-family: monospace; width: 71ch;">    box <- newMVar Nothing</div><div style="font-family: monospace; width: 71ch;">    return $ modifyMVar box storeResultOnce</div><div style="font-family: monospace; width: 71ch;">    where</div><div style="font-family: monospace; width: 71ch;">    storeResultOnce m@(Just result) = return (m, result)</div><div style="font-family: monospace; width: 71ch;">    storeResultOnce _ = action >>= \r -> return (Just r, r)</div><div style="font-family: monospace; width: 71ch;">{-# RULES "optimize lazyIO" lazyIO = unsafeInterleaveIO . (pure <$>) </div><div style="font-family: monospace; width: 71ch;">#-}</div><div style="font-family: monospace; width: 71ch;"><br></div><div style="font-family: monospace; width: 71ch;">I think you need to change the type of the cache function if you want to avoid unsafe IO functions at all:</div><div style="font-family: monospace; width: 71ch;">cache :: (MonadFix m, MonadIO m) => m a -> m (Cached m a)</div><div style="font-family: monospace; width: 71ch;"><br></div><div style="font-family: monospace; width: 71ch;">unsafePerformIO [1] already prevents duplicate/concurrent evaluation of its argument. And if you're using unsafe IO already, why not simplify it to just using unsafeInterleaveIO? It has the same guarantees about no duplication according to its Haskell source.</div><div style="font-family: monospace; width: 71ch;"><br></div><div style="font-family: monospace; width: 71ch;">[1] <a href="https://hackage.haskell.org/package/base-4.10.1.0/docs/System-IO-Unsafe.html">https://hackage.haskell.org/package/base-4.10.1.0/docs/System-IO-Unsafe.html</a></div><div><br></div></div></body></html>