Safe Haskell | None |
---|---|
Language | Haskell2010 |
General interface for the cache. This module is intended to be used in th user code.
TLDR
{-# LANGUAGE ImportQualifiedPost #-} {-# LANGUAGE NumericUnderscores #-} {-# LANGUAGE BlockArguments #-} import Control.Concurrent import System.Cache qualified as Cache import System.Cache.Impl.Ghc qualified as Cache.Ghc import System.Clock.Seconds main :: IO () main = do -- we create a new cache handle that acts as a storage for -- cached values cache <- Cache.Ghc.new
do Cache.mkConfig
60MonotonicCoarse
-- we create a cached version of computation -- in order to hide implementation let cachedTimeout = Cache.mkCached
cache
i -> do threadDelay $ i * 1_000_000 pure i -- We use our cached function print (cachedTimeout 1)
Synopsis
- data Handle a b
- data Config
- mkConfig :: Int -> Clock -> Config
- requestOr :: Handle a b -> a -> (a -> IO b) -> IO b
- cacheIO :: Handle a b -> (a -> IO b) -> a -> IO b
- new :: (Show a, Hashable a, Ord a) => Config -> IO (Handle a b)
- mkCached :: (Config -> IO (Handle a b)) -> Config -> (a -> IO b) -> IO (a -> IO b)
API
Create
In order to use this library you first need to explicitly create a storage
for the values. This storage is implemented by the abstract type Handle
that
provides only a public function interface but hides an actual implementation.
You can find full description of the Handle
in the System.Cache.Internal.Interface
module.
The public interface for the cache values storage.
A storage is expected to provide the following properties:
- If the function return succesfully then the result should be cached for a time period, All later calls should return the cached value.
- In case of the concurrent actions an implementation should be the best effort to avoid reduntant calls
In order to create a Handle
you'll need to call appropiate function from the
System.Cache.Impl.*.new
module. This way you can chose an actual implementation.
Alternatively you can use new
function that will make a choise for you, or
create your own implementation.
Each of those functions take a Config
as a parameter
Configuration for Cache
See System.Cache.Internal.Interface for all details on the fields.
:: Int | Max time that the value can be cached (in seconds). |
-> Clock | Type of the clock that the cache will use. |
-> Config |
Helper to create a config.
Use
Once the storage is created you can use it for caching values via requestOr
method.
Perform a request.
The API of the method is not safe enough because you can for example ignore input value in the funciton, or pass different function in different invocations with the same storage. One the one hand we do not want to prevent such usages as may be done for a purpose, but in order to provide additional safety we provide more safe methods:
:: Handle a b | Values storage |
-> (a -> IO b) | Action to cache |
-> a -> IO b | A version that caches the result |
Wraps an IO action and returns a cached version of that method.
Helpers
new :: (Show a, Hashable a, Ord a) => Config -> IO (Handle a b) Source #
Set default cache implementation. This method perfers to use
System.Cache.Impl.Ghc implementation unless GHC_CACHE_IMPL
environment value
has value MVAR
in this case System.Cache.Impl.MVar is used.
This method is useful as a default one because it prefers a faster and stabler implementation, but in case of emergency it allows to switch to the conservative implementation without program recompilation.
N.B. this methos uses unsafePerformIO
.