Safe Haskell | None |
---|---|
Language | Haskell2010 |
A cache implementation that periodically (and asynchronously) polls an external action for updated values.
Synopsis
- class (MonadCatch m, MonadIO m) => MonadCache m where
- data PollingCache a
- data CacheMiss
- type CacheHit a = (a, UTCTime)
- type CacheResult a = Either CacheMiss (CacheHit a)
- data FailureMode
- data DelayMode a
- = DelayForMicroseconds Int
- | DelayDynamically (Either SomeException a -> Int)
- | DelayDynamicallyWithBounds (Int, Int) (Either SomeException a -> Int)
- type ThreadDelay = Int
- data CacheOptions a
- basicOptions :: DelayMode a -> FailureMode -> CacheOptions a
- newPollingCache :: forall a m. MonadCache m => CacheOptions a -> m a -> m (PollingCache a)
- cachedValue :: MonadCache m => PollingCache a -> m (CacheResult a)
- stopPolling :: MonadCache m => PollingCache a -> m ()
Entry-point types and typeclasses
class (MonadCatch m, MonadIO m) => MonadCache m where Source #
The top-level Monad
in which caching operations are performed.
This exists primarily for testing purposes. Production uses should drop in IO
and forget that this exists.
currentTime :: m UTCTime Source #
The current system time.
randomize :: (Int, Int) -> m Int Source #
Generate a random number between two bounds (inclusive).
Delay execution of the current thread for a number of microseconds.
newThread :: m () -> m ThreadId Source #
Spawn a new thread of execution to run an action.
repeatedly :: m () -> m () Source #
Run an action forever.
killCache :: ThreadId -> m () Source #
Stop a thread of execution. The thread can be assumed to have been started using newThread
.
data PollingCache a Source #
An opaque type containing the internals necessary for background polling and caching.
Library functions will allow the user to create and interact with a PollingCache
, but
the raw data is not exposed to users so that the library can maintain invariants.
Types for working with cached results
The supported "empty" states for a PollingCache
.
See CacheResult
for a more in-depth explanation of why this is necessary.
NotYetLoaded | A value has never been loaded into the cache. |
LoadFailed UTCTime | The external action used to populate the cache threw an exception at some point in time. |
Stopped | The cache has been shut down and can no longer be used. |
Instances
type CacheHit a = (a, UTCTime) Source #
A successfully cached value with the time at which it was generated.
type CacheResult a = Either CacheMiss (CacheHit a) Source #
The result of reading a value from a PollingCache
, including the possibility of failure.
Due to the asynchronous (and likely effectful) nature of executing external actions to populate
the cache, it's possible for the cache to be "empty" at any point in time. The possible empty
states are controlled by the FailureMode
selected by the user when creating the PollingCache
instance.
Types for cache creation
data FailureMode Source #
The supported failure handling modes for a PollingCache
instance.
In the context of the cache action, "failure" means an Exception thrown from the user-supplied action that generates values to populate the cache.
Because these operations are performed in a background thread, the user must decide how failures are to be handled upon cache creation.
Ignore | Failures should be ignored entirely; the most relaxed failure handling strategy. This means that |
EvictImmediately | If a failure occurs, any previously cached value is immediately evicted from the cache; the strictest failure handling strategy. |
EvictAfterTime NominalDiffTime | Failures will be ignored unless they persist beyond the supplied time span. This is a middle-ground failure handling strategy that probably makes sense to use in most scenarios. The nature of asynchronous polling implies that somewhat stale values are not an issue to the consumer; therefore, allowing some level of transient failure can often improve reliability without sacrificing correctness. |
Instances
Eq FailureMode Source # | |
Defined in Data.Cache.Internal (==) :: FailureMode -> FailureMode -> Bool # (/=) :: FailureMode -> FailureMode -> Bool # | |
Show FailureMode Source # | |
Defined in Data.Cache.Internal showsPrec :: Int -> FailureMode -> ShowS # show :: FailureMode -> String # showList :: [FailureMode] -> ShowS # |
The supported delay modes for a PollingCache
instance.
The delay associated with a cache instance define the amount of time that will pass between cache refreshes.
DelayForMicroseconds Int | Delay for static number of microseconds between each refresh. |
DelayDynamically (Either SomeException a -> Int) | Delay for a dynamic number of microseconds between each refresh. This is useful if different delays should be used for successes or failures, or if the result being retrieved contains information that could affect the delay period. |
DelayDynamicallyWithBounds (Int, Int) (Either SomeException a -> Int) | Delay for a dynamic number of microseconds between each refresh within a set of bounds. This is similarly useful to |
type ThreadDelay = Int Source #
The minimum amount of time (in microseconds) that should pass before a cache reload is attempted.
data CacheOptions a Source #
Options that dictate the behavior of a PollingCache
instance.
Functions for creating and interacting with caches
basicOptions :: DelayMode a -> FailureMode -> CacheOptions a Source #
Create a CacheOptions
with basic functionality enabled.
Record update syntax can be use to further customize options created using this function:
basicOpts = basicOptions (DelayForMicroseconds 60000000) EvictImmediately customOpts = basicOpts { delayFuzzing = Just 100 }
newPollingCache :: forall a m. MonadCache m => CacheOptions a -> m a -> m (PollingCache a) Source #
Creates a new PollingCache
.
The supplied action is used to generate values that are stored in the cache. The action is executed in the background
with its delay, failure, and fuzzing behavior controlled by the provided CacheOptions
.
cachedValue :: MonadCache m => PollingCache a -> m (CacheResult a) Source #
Retrieve the current values from a PollingCache
.
stopPolling :: MonadCache m => PollingCache a -> m () Source #
Stops the background processing thread associated with a PollingCache
.
Calling this function will place the Stopped
value into the cache after stopping the processing thread,
ensuring that a PollingCache
that has been stopped can no longer be used to query stale values.