{-# LANGUAGE RecursiveDo #-}
module System.Cache.Impl.NoCache
( new
) where
import System.Cache.Internal.Interface
import System.Clock.Seconds
new :: Config -> IO (Handle a b)
new :: Config -> IO (Handle a b)
new Config{Seconds
Clock
configClock :: Config -> Clock
configLongestAge :: Config -> Seconds
configClock :: Clock
configLongestAge :: Seconds
..} = do
Handle a b -> IO (Handle a b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Handle a b -> IO (Handle a b)) -> Handle a b -> IO (Handle a b)
forall a b. (a -> b) -> a -> b
$ Handle :: forall a b.
(Seconds -> a -> (a -> IO b) -> IO b)
-> (a -> IO ()) -> IO Seconds -> Handle a b
Handle
{ requestOrInternal :: Seconds -> a -> (a -> IO b) -> IO b
requestOrInternal = \Seconds
_ a
k a -> IO b
f -> a -> IO b
f a
k
, remove :: a -> IO ()
remove = \a
_ -> () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
, getClockTime :: IO Seconds
getClockTime = Clock -> IO Seconds
getTime Clock
configClock
}