[Haskell-cafe] Caching Actions

Arjen arjenvanweelden at gmail.com
Thu Jan 25 12:31:04 UTC 2018


On Thu, 2018-01-25 at 09:50 +0000, Yotam Ohad wrote:
> Hi,
> I've been digging around the source code of reactive-banana and I
> found this code: 
> 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
> 
> I'm trying to understand the reasom behind the use of mdo. Can't it
> be like this:
> do
>   a <- m
>   liftIO $ writeIORef key (Just a)
>   return a
> Removing the need for a recursive definition?
> 
> Yotam
> 
> 
> 
> 
> _______________________________________________

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:

lazyIO :: IO a -> IO (IO a)
lazyIO action = do
    box <- newMVar Nothing
    return $ modifyMVar box storeResultOnce
    where
    storeResultOnce m@(Just result) = return (m, result)
    storeResultOnce _ = action >>= \r -> return (Just r, r)
{-# RULES "optimize lazyIO" lazyIO = unsafeInterleaveIO . (pure <$>) 
#-}

I think you need to change the type of the cache function if you want
to avoid unsafe IO functions at all:
cache :: (MonadFix m, MonadIO m) => m a -> m (Cached m a)

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.

[1] https://hackage.haskell.org/package/base-4.10.1.0/docs/System-IO-Un
safe.html

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20180125/8658cce8/attachment.html>


More information about the Haskell-Cafe mailing list