-- |
-- Module      : Streamly.Internal.Data.IOFinalizer
-- Copyright   : (c) 2020 Composewell Technologies and Contributors
-- License     : BSD-3-Clause
-- Maintainer  : streamly@composewell.com
-- Stability   : experimental
-- Portability : GHC
--
-- A value associated with an IO action that is automatically called whenever
-- the value is garbage collected.

module Streamly.Internal.Data.IOFinalizer
    (
      IOFinalizer(..)
    , newIOFinalizer
    , runIOFinalizer
    , clearingIOFinalizer
    )
where

import Control.Exception (mask_)
import Control.Monad (void)
import Control.Monad.IO.Class (MonadIO(..))
import Data.IORef (newIORef, readIORef, mkWeakIORef, writeIORef, IORef)

-- | An 'IOFinalizer' has an associated IO action that is automatically called
-- whenever the finalizer is garbage collected. The action can be run and
-- cleared prematurely.
--
-- You can hold a reference to the finalizer in your data structure, if the
-- data structure gets garbage collected the finalizer will be called.
--
-- It is implemented using 'mkWeakIORef'.
--
-- /Pre-release/
newtype IOFinalizer = IOFinalizer (IORef (Maybe (IO ())))

-- | GC hook to run an IO action stored in a finalized IORef.
runFinalizerGC :: IORef (Maybe (IO ())) -> IO ()
runFinalizerGC :: IORef (Maybe (IO ())) -> IO ()
runFinalizerGC IORef (Maybe (IO ()))
ref = do
    Maybe (IO ())
res <- forall a. IORef a -> IO a
readIORef IORef (Maybe (IO ()))
ref
    case Maybe (IO ())
res of
        Maybe (IO ())
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
        Just IO ()
f -> IO ()
f

-- | Create a finalizer that calls the supplied function automatically when the
-- it is garbage collected.
--
-- /The finalizer is always run using the state of the monad that is captured
-- at the time of calling 'newFinalizer'./
--
-- Note: To run it on garbage collection we have no option but to use the monad
-- state captured at some earlier point of time.  For the case when the
-- finalizer is run manually before GC we could run it with the current state
-- of the monad but we want to keep both the cases consistent.
--
-- /Pre-release/
newIOFinalizer :: MonadIO m => IO a -> m IOFinalizer
newIOFinalizer :: forall (m :: * -> *) a. MonadIO m => IO a -> m IOFinalizer
newIOFinalizer IO a
finalizer = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    let f :: IO ()
f = forall (f :: * -> *) a. Functor f => f a -> f ()
void IO a
finalizer
    IORef (Maybe (IO ()))
ref <- forall a. a -> IO (IORef a)
newIORef forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just IO ()
f
    Weak (IORef (Maybe (IO ())))
_ <- forall a. IORef a -> IO () -> IO (Weak (IORef a))
mkWeakIORef IORef (Maybe (IO ()))
ref (IORef (Maybe (IO ())) -> IO ()
runFinalizerGC IORef (Maybe (IO ()))
ref)
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ IORef (Maybe (IO ())) -> IOFinalizer
IOFinalizer IORef (Maybe (IO ()))
ref

-- | Run the action associated with the finalizer and deactivate it so that it
-- never runs again.  Note, the finalizing action runs with async exceptions
-- masked.
--
-- /Pre-release/
runIOFinalizer :: MonadIO m => IOFinalizer -> m ()
runIOFinalizer :: forall (m :: * -> *). MonadIO m => IOFinalizer -> m ()
runIOFinalizer (IOFinalizer IORef (Maybe (IO ()))
ref) = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
    Maybe (IO ())
res <- forall a. IORef a -> IO a
readIORef IORef (Maybe (IO ()))
ref
    case Maybe (IO ())
res of
        Maybe (IO ())
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
        Just IO ()
action -> do
            -- if an async exception comes after writing 'Nothing' then the
            -- finalizing action will never be run. We need to do this
            -- atomically wrt async exceptions.
            forall a. IO a -> IO a
mask_ forall a b. (a -> b) -> a -> b
$ do
                forall a. IORef a -> a -> IO ()
writeIORef IORef (Maybe (IO ()))
ref forall a. Maybe a
Nothing
                IO ()
action

-- | Run an action clearing the finalizer atomically wrt async exceptions. The
-- action is run with async exceptions masked.
--
-- /Pre-release/
clearingIOFinalizer :: MonadIO m => IOFinalizer -> IO a -> m a
clearingIOFinalizer :: forall (m :: * -> *) a. MonadIO m => IOFinalizer -> IO a -> m a
clearingIOFinalizer (IOFinalizer IORef (Maybe (IO ()))
ref) IO a
action = do
    forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. IO a -> IO a
mask_ forall a b. (a -> b) -> a -> b
$ do
        forall a. IORef a -> a -> IO ()
writeIORef IORef (Maybe (IO ()))
ref forall a. Maybe a
Nothing
        IO a
action