{-# LANGUAGE RecordWildCards, ViewPatterns #-}
module Development.Shake.Internal.Resource(
Resource, newResourceIO, newThrottleIO, acquireResource, releaseResource
) where
import Data.Function
import System.IO.Unsafe
import Control.Concurrent.Extra
import Control.Exception.Extra
import Data.Tuple.Extra
import Control.Monad
import General.Bilist
import Development.Shake.Internal.Core.Pool
import System.Time.Extra
import Data.Monoid
import Prelude
{-# NOINLINE resourceIds #-}
resourceIds :: Var Int
resourceIds = unsafePerformIO $ newVar 0
resourceId :: IO Int
resourceId = modifyVar resourceIds $ \i -> let j = i + 1 in j `seq` return (j, j)
data Resource = Resource
{resourceOrd :: Int
,resourceShow :: String
,acquireResource :: Pool -> Int -> IO () -> IO ()
,releaseResource :: Pool -> Int -> IO ()
}
instance Show Resource where show = resourceShow
instance Eq Resource where (==) = (==) `on` resourceOrd
instance Ord Resource where compare = compare `on` resourceOrd
data Finite = Finite
{finiteAvailable :: !Int
,finiteWaiting :: Bilist (Int, IO ())
}
newResourceIO :: String -> Int -> IO Resource
newResourceIO name mx = do
when (mx < 0) $
errorIO $ "You cannot create a resource named " ++ name ++ " with a negative quantity, you used " ++ show mx
key <- resourceId
var <- newVar $ Finite mx mempty
return $ Resource (negate key) shw (acquire var) (release var)
where
shw = "Resource " ++ name
acquire :: Var Finite -> Pool -> Int -> IO () -> IO ()
acquire var pool want continue
| want < 0 = errorIO $ "You cannot acquire a negative quantity of " ++ shw ++ ", requested " ++ show want
| want > mx = errorIO $ "You cannot acquire more than " ++ show mx ++ " of " ++ shw ++ ", requested " ++ show want
| otherwise = join $ modifyVar var $ \x@Finite{..} -> return $
if want <= finiteAvailable then
(x{finiteAvailable = finiteAvailable - want}, continue)
else
(x{finiteWaiting = finiteWaiting `snoc` (want, addPoolResume pool continue)}, return ())
release :: Var Finite -> Pool -> Int -> IO ()
release var _ i = join $ modifyVar var $ \x -> return $ f x{finiteAvailable = finiteAvailable x + i}
where
f (Finite i (uncons -> Just ((wi,wa),ws)))
| wi <= i = second (wa >>) $ f $ Finite (i-wi) ws
| otherwise = first (add (wi,wa)) $ f $ Finite i ws
f (Finite i _) = (Finite i mempty, return ())
add a s = s{finiteWaiting = a `cons` finiteWaiting s}
waiter :: Seconds -> IO () -> IO ()
waiter period act = void $ forkIO $ do
sleep period
act
blockPool :: Pool -> IO (IO ())
blockPool pool = do
bar <- newBarrier
addPoolResume pool $ do
cancel <- increasePool pool
waitBarrier bar
cancel
return $ signalBarrier bar ()
data Throttle
= ThrottleAvailable !Int
| ThrottleWaiting (IO ()) (Bilist (Int, IO ()))
newThrottleIO :: String -> Int -> Double -> IO Resource
newThrottleIO name count period = do
when (count < 0) $
errorIO $ "You cannot create a throttle named " ++ name ++ " with a negative quantity, you used " ++ show count
key <- resourceId
var <- newVar $ ThrottleAvailable count
return $ Resource key shw (acquire var) (release var)
where
shw = "Throttle " ++ name
acquire :: Var Throttle -> Pool -> Int -> IO () -> IO ()
acquire var pool want continue
| want < 0 = errorIO $ "You cannot acquire a negative quantity of " ++ shw ++ ", requested " ++ show want
| want > count = errorIO $ "You cannot acquire more than " ++ show count ++ " of " ++ shw ++ ", requested " ++ show want
| otherwise = join $ modifyVar var $ \x -> case x of
ThrottleAvailable i
| i >= want -> return (ThrottleAvailable $ i - want, continue)
| otherwise -> do
stop <- blockPool pool
return (ThrottleWaiting stop $ (want - i, addPoolResume pool continue) `cons` mempty, return ())
ThrottleWaiting stop xs -> return (ThrottleWaiting stop $ xs `snoc` (want, addPoolResume pool continue), return ())
release :: Var Throttle -> Pool -> Int -> IO ()
release var pool n = waiter period $ join $ modifyVar var $ \x -> return $ case x of
ThrottleAvailable i -> (ThrottleAvailable $ i+n, return ())
ThrottleWaiting stop xs -> f stop n xs
where
f stop i (uncons -> Just ((wi,wa),ws))
| i >= wi = second (wa >>) $ f stop (i-wi) ws
| otherwise = (ThrottleWaiting stop $ (wi-i,wa) `cons` ws, return ())
f stop i _ = (ThrottleAvailable i, stop)