{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
#if __GLASGOW_HASKELL__ >= 704
{-# LANGUAGE ConstraintKinds #-}
#endif
{-# LANGUAGE Safe #-}
module Control.Monad.Trans.Resource
(
ResourceT
, ResIO
, ReleaseKey
, runResourceT
, resourceForkIO
, transResourceT
, joinResourceT
, allocate
, register
, release
, unprotect
, resourceMask
, MonadResource (..)
, MonadResourceBase
, InvalidAccess (..)
, MonadBaseControl
, InternalState
, getInternalState
, runInternalState
, withInternalState
, createInternalState
, closeInternalState
, ExceptionT (..)
, runExceptionT
, runExceptionT_
, runException
, runException_
, MonadThrow (..)
, monadThrow
) where
import qualified Data.IntMap as IntMap
import Control.Exception (SomeException, throw)
import Control.Monad.Trans.Control
( MonadBaseControl (..), liftBaseDiscard, control )
import qualified Data.IORef as I
import Control.Monad.Base (MonadBase, liftBase)
import Control.Applicative (Applicative (..))
import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad (liftM)
import qualified Control.Exception as E
import Data.Monoid (Monoid)
import qualified Control.Exception.Lifted as L
import Control.Monad.Trans.Resource.Internal
import Control.Concurrent (ThreadId, forkIO)
import Data.Functor.Identity (Identity, runIdentity)
import Control.Monad.Catch (MonadThrow, throwM)
import Control.Monad.Catch.Pure (CatchT, runCatchT)
import Data.Acquire.Internal (ReleaseType (..))
register :: MonadResource m => IO () -> m ReleaseKey
register = liftResourceT . registerRIO
release :: MonadIO m => ReleaseKey -> m ()
release (ReleaseKey istate rk) = liftIO $ release' istate rk
(maybe (return ()) id)
unprotect :: MonadIO m => ReleaseKey -> m (Maybe (IO ()))
unprotect (ReleaseKey istate rk) = liftIO $ release' istate rk return
allocate :: MonadResource m
=> IO a
-> (a -> IO ())
-> m (ReleaseKey, a)
allocate a = liftResourceT . allocateRIO a
resourceMask :: MonadResource m => ((forall a. ResourceT IO a -> ResourceT IO a) -> ResourceT IO b) -> m b
resourceMask r = liftResourceT (resourceMaskRIO r)
allocateRIO :: IO a -> (a -> IO ()) -> ResourceT IO (ReleaseKey, a)
allocateRIO acquire rel = ResourceT $ \istate -> liftIO $ E.mask $ \restore -> do
a <- acquire
key <- register' istate $ rel a
return (key, a)
registerRIO :: IO () -> ResourceT IO ReleaseKey
registerRIO rel = ResourceT $ \istate -> liftIO $ register' istate rel
resourceMaskRIO :: ((forall a. ResourceT IO a -> ResourceT IO a) -> ResourceT IO b) -> ResourceT IO b
resourceMaskRIO f = ResourceT $ \istate -> liftIO $ E.mask $ \restore ->
let ResourceT f' = f (go restore)
in f' istate
where
go :: (forall a. IO a -> IO a) -> (forall a. ResourceT IO a -> ResourceT IO a)
go r (ResourceT g) = ResourceT (\i -> r (g i))
release' :: I.IORef ReleaseMap
-> Int
-> (Maybe (IO ()) -> IO a)
-> IO a
release' istate key act = E.mask_ $ do
maction <- I.atomicModifyIORef istate lookupAction
act maction
where
lookupAction rm@(ReleaseMap next rf m) =
case IntMap.lookup key m of
Nothing -> (rm, Nothing)
Just action ->
( ReleaseMap next rf $ IntMap.delete key m
, Just (action ReleaseEarly)
)
lookupAction ReleaseMapClosed = (ReleaseMapClosed, Nothing)
runResourceT :: MonadBaseControl IO m => ResourceT m a -> m a
runResourceT (ResourceT r) = control $ \run -> do
istate <- createInternalState
E.mask $ \restore -> do
res <- restore (run (r istate)) `E.onException`
stateCleanup ReleaseException istate
stateCleanup ReleaseNormal istate
return res
bracket_ :: MonadBaseControl IO m
=> IO ()
-> IO ()
-> IO ()
-> m a
-> m a
bracket_ alloc cleanupNormal cleanupExc inside =
control $ \run -> E.mask $ \restore -> do
alloc
res <- restore (run inside) `E.onException` cleanupExc
cleanupNormal
return res
finally :: MonadBaseControl IO m => m a -> IO () -> m a
finally action cleanup =
control $ \run -> E.finally (run action) cleanup
joinResourceT :: ResourceT (ResourceT m) a
-> ResourceT m a
joinResourceT (ResourceT f) = ResourceT $ \r -> unResourceT (f r) r
type ExceptionT = CatchT
runExceptionT :: ExceptionT m a -> m (Either SomeException a)
runExceptionT = runCatchT
runExceptionT_ :: Monad m => ExceptionT m a -> m a
runExceptionT_ = liftM (either E.throw id) . runExceptionT
runException :: ExceptionT Identity a -> Either SomeException a
runException = runIdentity . runExceptionT
runException_ :: ExceptionT Identity a -> a
runException_ = runIdentity . runExceptionT_
resourceForkIO :: MonadBaseControl IO m => ResourceT m () -> ResourceT m ThreadId
resourceForkIO (ResourceT f) = ResourceT $ \r -> L.mask $ \restore ->
bracket_
(stateAlloc r)
(return ())
(return ())
(liftBaseDiscard forkIO $ bracket_
(return ())
(stateCleanup ReleaseNormal r)
(stateCleanup ReleaseException r)
(restore $ f r))
#if __GLASGOW_HASKELL__ >= 704
type MonadResourceBase m = (MonadBaseControl IO m, MonadThrow m, MonadBase IO m, MonadIO m, Applicative m)
#else
class (MonadBaseControl IO m, MonadThrow m, MonadIO m, Applicative m) => MonadResourceBase m
instance (MonadBaseControl IO m, MonadThrow m, MonadIO m, Applicative m) => MonadResourceBase m
#endif
createInternalState :: MonadBase IO m => m InternalState
createInternalState = liftBase
$ I.newIORef
$ ReleaseMap maxBound (minBound + 1) IntMap.empty
closeInternalState :: MonadBase IO m => InternalState -> m ()
closeInternalState = liftBase . stateCleanup ReleaseNormal
getInternalState :: Monad m => ResourceT m InternalState
getInternalState = ResourceT return
type InternalState = I.IORef ReleaseMap
runInternalState :: ResourceT m a -> InternalState -> m a
runInternalState = unResourceT
withInternalState :: (InternalState -> m a) -> ResourceT m a
withInternalState = ResourceT
monadThrow :: (E.Exception e, MonadThrow m) => e -> m a
monadThrow = throwM