1{-# LANGUAGE FlexibleContexts #-} 2{-# LANGUAGE FlexibleInstances #-} 3{-# LANGUAGE MultiParamTypeClasses #-} 4{-# LANGUAGE UndecidableInstances #-} 5{-# LANGUAGE TypeFamilies #-} 6{-# LANGUAGE RankNTypes #-} 7{-# LANGUAGE CPP #-} 8{-# LANGUAGE DeriveDataTypeable #-} 9{-# LANGUAGE ConstraintKinds #-} 10-- | Allocate resources which are guaranteed to be released. 11-- 12-- For more information, see <https://github.com/snoyberg/conduit/tree/master/resourcet#readme>. 13-- 14-- One point to note: all register cleanup actions live in the @IO@ monad, not 15-- the main monad. This allows both more efficient code, and for monads to be 16-- transformed. 17module Control.Monad.Trans.Resource 18 ( -- * Data types 19 ResourceT 20 , ResIO 21 , ReleaseKey 22 -- * Unwrap 23 , runResourceT 24 -- ** Check cleanup exceptions 25 , runResourceTChecked 26 , ResourceCleanupException (..) 27 -- * Special actions 28 , resourceForkWith 29 , resourceForkIO 30 -- * Monad transformation 31 , transResourceT 32 , joinResourceT 33 -- * Registering/releasing 34 , allocate 35 , allocate_ 36 , register 37 , release 38 , unprotect 39 , resourceMask 40 -- * Type class/associated types 41 , MonadResource (..) 42 , MonadResourceBase 43 -- ** Low-level 44 , InvalidAccess (..) 45 -- * Re-exports 46 , MonadUnliftIO 47 -- * Internal state 48 -- $internalState 49 , InternalState 50 , getInternalState 51 , runInternalState 52 , withInternalState 53 , createInternalState 54 , closeInternalState 55 -- * Reexport 56 , MonadThrow (..) 57 ) where 58 59import qualified Data.IntMap as IntMap 60import qualified Data.IORef as I 61import Control.Monad.IO.Unlift (MonadIO (..), MonadUnliftIO, withRunInIO) 62import qualified Control.Exception as E 63 64import Control.Monad.Trans.Resource.Internal 65 66import Control.Concurrent (ThreadId, forkIO) 67 68import Control.Monad.Catch (MonadThrow, throwM) 69import Data.Acquire.Internal (ReleaseType (..)) 70 71 72 73-- | Register some action that will be called precisely once, either when 74-- 'runResourceT' is called, or when the 'ReleaseKey' is passed to 'release'. 75-- 76-- Since 0.3.0 77register :: MonadResource m => IO () -> m ReleaseKey 78register = liftResourceT . registerRIO 79 80-- | Call a release action early, and deregister it from the list of cleanup 81-- actions to be performed. 82-- 83-- Since 0.3.0 84release :: MonadIO m => ReleaseKey -> m () 85release (ReleaseKey istate rk) = liftIO $ release' istate rk 86 (maybe (return ()) id) 87 88-- | Unprotect resource from cleanup actions; this allows you to send 89-- resource into another resourcet process and reregister it there. 90-- It returns a release action that should be run in order to clean 91-- resource or Nothing in case if resource is already freed. 92-- 93-- Since 0.4.5 94unprotect :: MonadIO m => ReleaseKey -> m (Maybe (IO ())) 95unprotect (ReleaseKey istate rk) = liftIO $ release' istate rk return 96 97-- | Perform some allocation, and automatically register a cleanup action. 98-- 99-- This is almost identical to calling the allocation and then 100-- @register@ing the release action, but this properly handles masking of 101-- asynchronous exceptions. 102-- 103-- Since 0.3.0 104allocate :: MonadResource m 105 => IO a -- ^ allocate 106 -> (a -> IO ()) -- ^ free resource 107 -> m (ReleaseKey, a) 108allocate a = liftResourceT . allocateRIO a 109 110-- | Perform some allocation where the return value is not required, and 111-- automatically register a cleanup action. 112-- 113-- @allocate_@ is to @allocate@ as @bracket_@ is to @bracket@ 114-- 115-- This is almost identical to calling the allocation and then 116-- @register@ing the release action, but this properly handles masking of 117-- asynchronous exceptions. 118-- 119-- @since 1.2.4 120allocate_ :: MonadResource m 121 => IO a -- ^ allocate 122 -> IO () -- ^ free resource 123 -> m ReleaseKey 124allocate_ a = fmap fst . allocate a . const 125 126-- | Perform asynchronous exception masking. 127-- 128-- This is more general then @Control.Exception.mask@, yet more efficient 129-- than @Control.Exception.Lifted.mask@. 130-- 131-- Since 0.3.0 132resourceMask :: MonadResource m => ((forall a. ResourceT IO a -> ResourceT IO a) -> ResourceT IO b) -> m b 133resourceMask r = liftResourceT (resourceMaskRIO r) 134 135allocateRIO :: IO a -> (a -> IO ()) -> ResourceT IO (ReleaseKey, a) 136allocateRIO acquire rel = ResourceT $ \istate -> liftIO $ E.mask_ $ do 137 a <- acquire 138 key <- register' istate $ rel a 139 return (key, a) 140 141registerRIO :: IO () -> ResourceT IO ReleaseKey 142registerRIO rel = ResourceT $ \istate -> liftIO $ register' istate rel 143 144resourceMaskRIO :: ((forall a. ResourceT IO a -> ResourceT IO a) -> ResourceT IO b) -> ResourceT IO b 145resourceMaskRIO f = ResourceT $ \istate -> liftIO $ E.mask $ \restore -> 146 let ResourceT f' = f (go restore) 147 in f' istate 148 where 149 go :: (forall a. IO a -> IO a) -> (forall a. ResourceT IO a -> ResourceT IO a) 150 go r (ResourceT g) = ResourceT (\i -> r (g i)) 151 152 153 154release' :: I.IORef ReleaseMap 155 -> Int 156 -> (Maybe (IO ()) -> IO a) 157 -> IO a 158release' istate key act = E.mask_ $ do 159 maction <- I.atomicModifyIORef istate lookupAction 160 act maction 161 where 162 lookupAction rm@(ReleaseMap next rf m) = 163 case IntMap.lookup key m of 164 Nothing -> (rm, Nothing) 165 Just action -> 166 ( ReleaseMap next rf $ IntMap.delete key m 167 , Just (action ReleaseEarly) 168 ) 169 -- We tried to call release, but since the state is already closed, we 170 -- can assume that the release action was already called. Previously, 171 -- this threw an exception, though given that @release@ can be called 172 -- from outside the context of a @ResourceT@ starting with version 173 -- 0.4.4, it's no longer a library misuse or a library bug. 174 lookupAction ReleaseMapClosed = (ReleaseMapClosed, Nothing) 175 176 177 178-- | Unwrap a 'ResourceT' transformer, and call all registered release actions. 179-- 180-- Note that there is some reference counting involved due to 'resourceForkIO'. 181-- If multiple threads are sharing the same collection of resources, only the 182-- last call to @runResourceT@ will deallocate the resources. 183-- 184-- /NOTE/ Since version 1.2.0, this function will throw a 185-- 'ResourceCleanupException' if any of the cleanup functions throw an 186-- exception. 187-- 188-- @since 0.3.0 189runResourceT :: MonadUnliftIO m => ResourceT m a -> m a 190runResourceT (ResourceT r) = withRunInIO $ \run -> do 191 istate <- createInternalState 192 E.mask $ \restore -> do 193 res <- restore (run (r istate)) `E.catch` \e -> do 194 stateCleanupChecked (Just e) istate 195 E.throwIO e 196 stateCleanupChecked Nothing istate 197 return res 198 199-- | Backwards compatible alias for 'runResourceT'. 200-- 201-- @since 1.1.11 202runResourceTChecked :: MonadUnliftIO m => ResourceT m a -> m a 203runResourceTChecked = runResourceT 204{-# INLINE runResourceTChecked #-} 205 206bracket_ :: MonadUnliftIO m 207 => IO () -- ^ allocate 208 -> IO () -- ^ normal cleanup 209 -> IO () -- ^ exceptional cleanup 210 -> m a 211 -> m a 212bracket_ alloc cleanupNormal cleanupExc inside = 213 withRunInIO $ \run -> E.mask $ \restore -> do 214 alloc 215 res <- restore (run inside) `E.onException` cleanupExc 216 cleanupNormal 217 return res 218 219-- | This function mirrors @join@ at the transformer level: it will collapse 220-- two levels of @ResourceT@ into a single @ResourceT@. 221-- 222-- Since 0.4.6 223joinResourceT :: ResourceT (ResourceT m) a 224 -> ResourceT m a 225joinResourceT (ResourceT f) = ResourceT $ \r -> unResourceT (f r) r 226 227-- | Introduce a reference-counting scheme to allow a resource context to be 228-- shared by multiple threads. Once the last thread exits, all remaining 229-- resources will be released. 230-- 231-- The first parameter is a function which will be used to create the 232-- thread, such as @forkIO@ or @async@. 233-- 234-- Note that abuse of this function will greatly delay the deallocation of 235-- registered resources. This function should be used with care. A general 236-- guideline: 237-- 238-- If you are allocating a resource that should be shared by multiple threads, 239-- and will be held for a long time, you should allocate it at the beginning of 240-- a new @ResourceT@ block and then call @resourceForkWith@ from there. 241-- 242-- @since 1.1.9 243resourceForkWith 244 :: MonadUnliftIO m 245 => (IO () -> IO a) 246 -> ResourceT m () 247 -> ResourceT m a 248resourceForkWith g (ResourceT f) = 249 ResourceT $ \r -> withRunInIO $ \run -> E.mask $ \restore -> 250 -- We need to make sure the counter is incremented before this call 251 -- returns. Otherwise, the parent thread may call runResourceT before 252 -- the child thread increments, and all resources will be freed 253 -- before the child gets called. 254 bracket_ 255 (stateAlloc r) 256 (return ()) 257 (return ()) 258 (g $ bracket_ 259 (return ()) 260 (stateCleanup ReleaseNormal r) 261 (stateCleanup ReleaseException r) 262 (restore $ run $ f r)) 263 264-- | Launch a new reference counted resource context using @forkIO@. 265-- 266-- This is defined as @resourceForkWith forkIO@. 267-- 268-- Note: Using regular 'forkIO' inside of a 'ResourceT' is inherently unsafe, 269-- since the forked thread may try access the resources of the parent after they are cleaned up. 270-- When you use 'resourceForkIO' or 'resourceForkWith', 'ResourceT' is made aware of the new thread, and will only cleanup resources when all threads finish. 271-- Other concurrency mechanisms, like 'concurrently' or 'race', are safe to use. 272-- 273-- If you encounter 'InvalidAccess' exceptions ("The mutable state is being accessed after cleanup"), 274-- use of 'forkIO' is a possible culprit. 275-- 276-- @since 0.3.0 277resourceForkIO :: MonadUnliftIO m => ResourceT m () -> ResourceT m ThreadId 278resourceForkIO = resourceForkWith forkIO 279 280-- | Just use 'MonadUnliftIO' directly now, legacy explanation continues: 281-- 282-- A @Monad@ which can be used as a base for a @ResourceT@. 283-- 284-- A @ResourceT@ has some restrictions on its base monad: 285-- 286-- * @runResourceT@ requires an instance of @MonadUnliftIO@. 287-- * @MonadResource@ requires an instance of @MonadIO@ 288-- 289-- Note that earlier versions of @conduit@ had a typeclass @ResourceIO@. This 290-- fulfills much the same role. 291-- 292-- Since 0.3.2 293type MonadResourceBase = MonadUnliftIO 294{-# DEPRECATED MonadResourceBase "Use MonadUnliftIO directly instead" #-} 295 296-- $internalState 297-- 298-- A @ResourceT@ internally is a modified @ReaderT@ monad transformer holding 299-- onto a mutable reference to all of the release actions still remaining to be 300-- performed. If you are building up a custom application monad, it may be more 301-- efficient to embed this @ReaderT@ functionality directly in your own monad 302-- instead of wrapping around @ResourceT@ itself. This section provides you the 303-- means of doing so. 304 305-- | Create a new internal state. This state must be closed with 306-- @closeInternalState@. It is your responsibility to ensure exception safety. 307-- Caveat emptor! 308-- 309-- Since 0.4.9 310createInternalState :: MonadIO m => m InternalState 311createInternalState = liftIO 312 $ I.newIORef 313 $ ReleaseMap maxBound (minBound + 1) IntMap.empty 314 315-- | Close an internal state created by @createInternalState@. 316-- 317-- Since 0.4.9 318closeInternalState :: MonadIO m => InternalState -> m () 319closeInternalState = liftIO . stateCleanup ReleaseNormal 320 321-- | Get the internal state of the current @ResourceT@. 322-- 323-- Since 0.4.6 324getInternalState :: Monad m => ResourceT m InternalState 325getInternalState = ResourceT return 326 327-- | The internal state held by a @ResourceT@ transformer. 328-- 329-- Since 0.4.6 330type InternalState = I.IORef ReleaseMap 331 332-- | Unwrap a @ResourceT@ using the given @InternalState@. 333-- 334-- Since 0.4.6 335runInternalState :: ResourceT m a -> InternalState -> m a 336runInternalState = unResourceT 337 338-- | Run an action in the underlying monad, providing it the @InternalState@. 339-- 340-- Since 0.4.6 341withInternalState :: (InternalState -> m a) -> ResourceT m a 342withInternalState = ResourceT 343