{-# LANGUAGE RecursiveDo #-}
{-# LANGUAGE TemplateHaskell #-}
module System.Cache
(
Handle
, Config
, mkConfig
, requestOr
, cacheIO
, new
, mkCached
) where
import Data.Functor
import Data.Hashable
import System.Clock.Seconds
import System.Cache.Internal.Interface
import qualified System.Cache.Impl.Ghc as Ghc
import qualified System.Cache.Impl.MVar as MVar
import System.Environment
import System.IO.Unsafe
mkConfig
:: Int
-> Clock
-> Config
mkConfig :: Int -> Clock -> Config
mkConfig Int
n Clock
clock = Config :: Seconds -> Clock -> Config
Config
{ configLongestAge :: Seconds
configLongestAge = Integer -> Seconds
fromNanoSecs (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
1_000_000_000)
, configClock :: Clock
configClock = Clock
clock
}
requestOr
:: Handle a b
-> a
-> (a -> IO b)
-> IO b
requestOr :: Handle a b -> a -> (a -> IO b) -> IO b
requestOr Handle {IO Seconds
a -> IO ()
Seconds -> a -> (a -> IO b) -> IO b
getClockTime :: forall a b. Handle a b -> IO Seconds
remove :: forall a b. Handle a b -> a -> IO ()
requestOrInternal :: forall a b. Handle a b -> Seconds -> a -> (a -> IO b) -> IO b
getClockTime :: IO Seconds
remove :: a -> IO ()
requestOrInternal :: Seconds -> a -> (a -> IO b) -> IO b
..} a
k a -> IO b
f = do
Seconds
tm <- IO Seconds
getClockTime
Seconds -> a -> (a -> IO b) -> IO b
requestOrInternal Seconds
tm a
k a -> IO b
f
cacheIO
:: Handle a b
-> (a -> IO b)
-> (a -> IO b)
cacheIO :: Handle a b -> (a -> IO b) -> a -> IO b
cacheIO Handle a b
handle a -> IO b
f = \a
k -> Handle a b -> a -> (a -> IO b) -> IO b
forall a b. Handle a b -> a -> (a -> IO b) -> IO b
requestOr Handle a b
handle a
k a -> IO b
f
new
:: (Show a, Hashable a, Ord a)
=> Config
-> IO (Handle a b)
{-# NOINLINE new #-}
new :: Config -> IO (Handle a b)
new = IO (Config -> IO (Handle a b)) -> Config -> IO (Handle a b)
forall a. IO a -> a
unsafePerformIO (IO (Config -> IO (Handle a b)) -> Config -> IO (Handle a b))
-> IO (Config -> IO (Handle a b)) -> Config -> IO (Handle a b)
forall a b. (a -> b) -> a -> b
$ do
String -> IO (Maybe String)
lookupEnv String
"GHC_CACHE_IMPL" IO (Maybe String)
-> (Maybe String -> IO (Config -> IO (Handle a b)))
-> IO (Config -> IO (Handle a b))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Just String
"MVAR" -> (Config -> IO (Handle a b)) -> IO (Config -> IO (Handle a b))
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Config -> IO (Handle a b)) -> IO (Config -> IO (Handle a b)))
-> (Config -> IO (Handle a b)) -> IO (Config -> IO (Handle a b))
forall a b. (a -> b) -> a -> b
$ Config -> IO (Handle a b)
forall a b.
(Show a, Hashable a, Ord a) =>
Config -> IO (Handle a b)
MVar.new
Maybe String
_ -> (Config -> IO (Handle a b)) -> IO (Config -> IO (Handle a b))
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Config -> IO (Handle a b)) -> IO (Config -> IO (Handle a b)))
-> (Config -> IO (Handle a b)) -> IO (Config -> IO (Handle a b))
forall a b. (a -> b) -> a -> b
$ Config -> IO (Handle a b)
forall a b.
(Show a, Hashable a, Ord a) =>
Config -> IO (Handle a b)
Ghc.new
mkCached
:: (Config -> IO (Handle a b))
-> Config
-> (a -> IO b)
-> IO (a -> IO b)
mkCached :: (Config -> IO (Handle a b))
-> Config -> (a -> IO b) -> IO (a -> IO b)
mkCached Config -> IO (Handle a b)
mk Config
config a -> IO b
f =
Config -> IO (Handle a b)
mk Config
config IO (Handle a b) -> (Handle a b -> a -> IO b) -> IO (a -> IO b)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \Handle a b
handle -> Handle a b -> (a -> IO b) -> a -> IO b
forall a b. Handle a b -> (a -> IO b) -> a -> IO b
cacheIO Handle a b
handle a -> IO b
f