{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE RankNTypes #-}
module Std.IO.Resource (
Resource(..)
, initResource
, initResource_
, withResource
, withResource'
, Pool
, PoolState(..)
, initPool
, statPool
, initInPool
) where
import Control.Concurrent.STM
import Control.Concurrent.STM.TVar
import Control.Monad
import qualified Control.Monad.Catch as MonadCatch
import Control.Monad.IO.Class
import Std.Data.PrimIORef
import Std.IO.LowResTimer
import Std.IO.Exception
newtype Resource a = Resource { acquire :: HasCallStack => IO (a, IO ()) }
initResource :: IO a -> (a -> IO ()) -> Resource a
{-# INLINE initResource #-}
initResource create release = Resource $ do
r <- create
return $ (r, release r)
initResource_ :: IO () -> IO () -> Resource ()
{-# INLINE initResource_ #-}
initResource_ create release = Resource $ do
r <- create
return $ (r, release)
instance Functor Resource where
{-# INLINE fmap #-}
fmap f resource = Resource $ do
(a, release) <- acquire resource
return (f a, release)
instance Applicative Resource where
{-# INLINE pure #-}
pure a = Resource (pure (a, pure ()))
{-# INLINE (<*>) #-}
resource1 <*> resource2 = Resource $ do
(f, release1) <- acquire resource1
(x, release2) <- acquire resource2 `onException` release1
return (f x, release2 >> release1)
instance Monad Resource where
{-# INLINE return #-}
return = pure
{-# INLINE (>>=) #-}
m >>= f = Resource $ do
(m', release1) <- acquire m
(x , release2) <- acquire (f m') `onException` release1
return (x, release2 >> release1)
instance MonadIO Resource where
{-# INLINE liftIO #-}
liftIO f = Resource $ fmap (\ a -> (a, dummyRelease)) f
where dummyRelease = return ()
withResource :: (MonadCatch.MonadMask m, MonadIO m, HasCallStack)
=> Resource a -> (a -> m b) -> m b
{-# INLINABLE withResource #-}
withResource resource k = MonadCatch.bracket
(liftIO (acquire resource))
(\(_, release) -> liftIO release)
(\(a, _) -> k a)
withResource' :: (MonadCatch.MonadMask m, MonadIO m, HasCallStack)
=> Resource a -> (a -> m () -> m b) -> m b
{-# INLINABLE withResource' #-}
withResource' resource k = do
c <- liftIO (newCounter 0)
MonadCatch.bracket
(liftIO $ do
(a, release) <- (acquire resource)
let release' = do
c' <- atomicOrCounter c 1
when (c' == 0) release
return (a, release'))
(\(_, release) -> liftIO release)
(\(a, release) -> k a (liftIO release))
data Entry a = Entry
(a, IO ())
{-# UNPACK #-} !Int
data PoolState = PoolClosed | PoolScanning | PoolEmpty deriving (Eq, Show)
data Pool a = Pool
{ poolResource :: Resource a
, poolLimit :: Int
, poolIdleTime :: Int
, poolEntries :: TVar [Entry a]
, poolInUse :: TVar Int
, poolState :: TVar PoolState
}
initPool :: Resource a
-> Int
-> Int
-> Resource (Pool a)
initPool res limit itime = initResource createPool closePool
where
createPool = do
entries <- newTVarIO []
inuse <- newTVarIO 0
state <- newTVarIO PoolEmpty
return (Pool res limit itime entries inuse state)
closePool (Pool _ _ _ entries _ state) = join . atomically $ do
c <- readTVar state
if c == PoolClosed
then return (return ())
else do
writeTVar state PoolClosed
return (do
es <- readTVarIO entries
forM_ es $ \ (Entry (_, close) _) ->
MonadCatch.handleAll (\ _ -> return ()) close)
statPool :: Pool a -> IO PoolState
statPool pool = readTVarIO (poolState pool)
initInPool :: Pool a -> Resource a
initInPool (Pool res limit itime entries inuse state) = fst <$> initResource takeFromPool returnToPool
where
takeFromPool = join . atomically $ do
c <- readTVar state
if c == PoolClosed
then throwECLOSEDSTM
else do
es <- readTVar entries
case es of
((Entry a _):es') -> do
writeTVar entries es'
return (return a)
_ -> do
i <- readTVar inuse
when (i == limit) retry
modifyTVar' inuse (+1)
return (acquire res `onException`
atomically (modifyTVar' inuse (subtract 1)))
returnToPool a = join . atomically $ do
c <- readTVar state
case c of
PoolClosed -> return (snd a)
PoolEmpty -> do
modifyTVar' entries (Entry a itime:)
writeTVar state PoolScanning
return (void $ registerLowResTimer 10 (scanPool entries inuse state))
_ -> do
modifyTVar' entries (Entry a itime:)
return (return ())
scanPool entries inuse state = do
join . atomically $ do
c <- readTVar state
if c == PoolClosed
then return (return ())
else do
es <- readTVar entries
if (null es)
then do
writeTVar state PoolEmpty
return (return ())
else do
let (deadNum, dead, living) = age es 0 [] []
writeTVar entries living
modifyTVar' inuse (subtract deadNum)
return (do
forM_ dead $ \ (_, close) ->
MonadCatch.handleAll (\ _ -> return ()) close
void $ registerLowResTimer 10 (scanPool entries inuse state))
age ((Entry a life):es) !deadNum dead living
| life > 1 = age es deadNum dead (Entry a (life-1):living)
| otherwise = age es (deadNum+1) (a:dead) living
age _ !deadNum dead living = (deadNum, dead, living)