knit-haskell-0.8.0.0: a minimal Rmarkdown sort-of-thing for haskell, by way of Pandoc
Copyright(c) Adam Conner-Sax 2019
LicenseBSD-3-Clause
Maintaineradam_conner_sax@yahoo.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Knit.Report.Cache

Description

This module adds types, combinators and knit functions for using knit-haskell with the AtomicCache effect to implement a disk-persisted, in-memory key-value store with some support dependency tracking. The knit-haskell stack uses Text keys, performs binary serialization using Cereal and uses Array from Streamly as values for the in-memory Map.

For details about the cache itself, please see the documentation for AtomicCache.

Examples are available, and might be useful for seeing how all this works.

Synopsis

Dependency Tracking

data WithCacheTime m a Source #

Wrapper to hold (deserializable, if necessary) content and a timestamp. The stamp must be at or after the time the data was constructed

Instances

Instances details
Functor m => Functor (WithCacheTime m) Source # 
Instance details

Defined in Knit.Effect.AtomicCache

Methods

fmap :: (a -> b) -> WithCacheTime m a -> WithCacheTime m b #

(<$) :: a -> WithCacheTime m b -> WithCacheTime m a #

Applicative m => Applicative (WithCacheTime m) Source # 
Instance details

Defined in Knit.Effect.AtomicCache

Methods

pure :: a -> WithCacheTime m a #

(<*>) :: WithCacheTime m (a -> b) -> WithCacheTime m a -> WithCacheTime m b #

liftA2 :: (a -> b -> c) -> WithCacheTime m a -> WithCacheTime m b -> WithCacheTime m c #

(*>) :: WithCacheTime m a -> WithCacheTime m b -> WithCacheTime m b #

(<*) :: WithCacheTime m a -> WithCacheTime m b -> WithCacheTime m a #

Show (m a) => Show (WithCacheTime m a) Source # 
Instance details

Defined in Knit.Effect.AtomicCache

type ActionWithCacheTime r a = WithCacheTime (Sem r) a Source #

Specialize WithCacheTime for use with a Polysemy effects stack.

ignoreCacheTime :: WithCacheTime m a -> m a Source #

Access the computation part of a WithCacheTime a. This or ignoreCacheTimeM is required to use the cached value as anything but input to another cached computation.

ignoreCacheTimeM :: Monad m => m (WithCacheTime m a) -> m a Source #

Access the computation part of an m (WithCacheTime a). This or ignoreCacheTime is required to use the cached value as anything but input to another cached computation.

withCacheTime :: Maybe UTCTime -> m a -> WithCacheTime m a Source #

Construct a WithCacheTime from a Maybe Time.UTCTime and an action.

onlyCacheTime :: Applicative m => Maybe UTCTime -> WithCacheTime m () Source #

Construct a WithCacheTime with a time and no action.

Cache Combinators

store Source #

Arguments

:: forall sc ct k r a. (Members '[SerializeEnv sc ct, Cache k ct, Error CacheError, Embed IO] r, LogWithPrefixesLE r, Show k, sc a) 
=> k

Key

-> a

(Serializable) Data to store

-> Sem r () 

Store an a (serialized) at key k. Throw PandocIOError on IOError.

clear :: Member (Cache k ct) r => k -> Sem r () Source #

Clear the cache at a given key. Throws an exception if item is not present.

clearIfPresent :: (Member (Cache k ct) r, MemberWithError (Error CacheError) r) => k -> Sem r () Source #

Clear the cache at a given key. Doesn't throw if item is missing.

retrieve Source #

Arguments

:: forall sc ct k r a. (Members '[SerializeEnv sc ct, Cache k ct, Error CacheError, Embed IO] r, LogWithPrefixesLE r, Show k, sc a) 
=> k

Key

-> Sem r (ActionWithCacheTime r a)

Time-stamped return from cache.

Retrieve an a from the store at key. Throw if not found or I/O Error.

retrieveOrMake Source #

Arguments

:: forall sc ct k r a b. (Members '[SerializeEnv sc ct, Cache k ct, Error CacheError, Embed IO] r, LogWithPrefixesLE r, Show k, sc a) 
=> k

Key

-> ActionWithCacheTime r b

Cached dependencies with time-stamp

-> (b -> Sem r a)

Computation to produce a if absent from cache or cached version is older than dependencies.

-> Sem r (ActionWithCacheTime r a)

Time-stamped return from cache.

Retrieve an a from the store at key k. If retrieve fails then perform the action and store the resulting a at key k.

retrieveOrMakeTransformed Source #

Arguments

:: forall sc ct k r a b c. (Members '[SerializeEnv sc ct, Cache k ct, Error CacheError, Embed IO] r, LogWithPrefixesLE r, Show k, sc b) 
=> (a -> b)

Transform a to Serializable b

-> (b -> a)

Transform Serializable b to a

-> k

Key

-> ActionWithCacheTime r c

Cached dependencies with time-stamp

-> (c -> Sem r a)

Computation to produce a if absent from cache or cached version is older than dependencies.

-> Sem r (ActionWithCacheTime r a)

Time-stamped a from cache.

Retrieve an a from the store at key k. If retrieve fails then perform the action and store the resulting a at key k. Also has functions for mapping the input and output: useful for caching something without a Serialize instance but which is isomorphic to something with one.

Streamly-Based

Dependency Tracking

type StreamWithCacheTime r a = WithCacheTime (SerialT (Sem r)) a Source #

Specify a Streamly Stream as the action in a WithCacheTime

ignoreCacheTimeStream :: Sem r (StreamWithCacheTime r a) -> SerialT (Sem r) a Source #

Wrapper for AtomicCache.ignoreCacheTime, plus the concatM bit for streamly

Interoperation with non-stream actions

streamToAction :: (SerialT (Sem r) a -> Sem r b) -> StreamWithCacheTime r a -> ActionWithCacheTime r b Source #

Use a function from a Stream (Sem r) a to Sem r a to map from a stream action to a plain action over Sem.

streamAsAction :: StreamWithCacheTime r a -> ActionWithCacheTime r (SerialT (Sem r) a) Source #

Wrap a stream action in Sem r to make a stream action into a plain one holding the (still effectful) stream.

Cache Combinators

storeStream Source #

Arguments

:: forall sc ct k r a. (Members '[SerializeEnv sc ct, Cache k ct, Error CacheError, Embed IO] r, MemberWithError (Error SomeException) r, LogWithPrefixesLE r, Show k, sc [a]) 
=> k

Key

-> SerialT (Sem r) a

Streamly stream to store

-> Sem r () 

Store a Streamly stream of a at key k. Throw PandocIOError on IOError.

retrieveStream Source #

Arguments

:: forall sc k ct r a. (Members '[SerializeEnv sc ct, Cache k ct, Error CacheError, Embed IO] r, LogWithPrefixesLE r, MemberWithError (Error SomeException) r, Show k, sc [a]) 
=> k

Key

-> Maybe UTCTime

Cached item invalidation time. Supply Nothing to retrieve regardless of time-stamp.

-> Sem r (StreamWithCacheTime r a)

Time-stamped stream from cache.

Retrieve a Streamly stream of a from the store at key k. Throw if not found or IOError ignore dependency info

retrieveOrMakeStream Source #

Arguments

:: forall sc k ct r a b. (Members '[SerializeEnv sc ct, Cache k ct, Error CacheError, Embed IO] r, LogWithPrefixesLE r, MemberWithError (Error SomeException) r, Show k, sc [a]) 
=> k

Key

-> ActionWithCacheTime r b

Cached dependencies with time-stamp

-> (b -> SerialT (Sem r) a)

Computation to produce Stream of a if absent from cache or cached version is older than dependencies.

-> Sem r (StreamWithCacheTime r a)

Time-stamped stream.

Retrieve a Streamly stream of a from the store at key k. If retrieve fails then perform the action and store the resulting stream at key k.

retrieveOrMakeTransformedStream Source #

Arguments

:: forall sc ct k r a b c. (Members '[SerializeEnv sc ct, Cache k ct, Error CacheError, Embed IO] r, LogWithPrefixesLE r, MemberWithError (Error SomeException) r, Show k, sc [b]) 
=> (a -> b)

Transform a to Serializable b

-> (b -> a)

Transform Serializable b to a

-> k

Key

-> ActionWithCacheTime r c

Cached dependencies with time-stamp

-> (c -> SerialT (Sem r) a)

Computation to produce Stream of a if absent from cache or cached version is older than dependencies.

-> Sem r (StreamWithCacheTime r a)

Time-stamped stream.

Retrieve a Streamly stream of a from the store at key k. If retrieve fails then perform the action and store the resulting stream at key k. Also has functions for mapping the input and output: useful for caching something without a Serialize instance but which is isomorphic to something with one.

Re-Exports

data UTCTime #

This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.

Instances

Instances details
Eq UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

(==) :: UTCTime -> UTCTime -> Bool #

(/=) :: UTCTime -> UTCTime -> Bool #

Data UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UTCTime -> c UTCTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UTCTime #

toConstr :: UTCTime -> Constr #

dataTypeOf :: UTCTime -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UTCTime) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UTCTime) #

gmapT :: (forall b. Data b => b -> b) -> UTCTime -> UTCTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> UTCTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UTCTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

Ord UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

NFData UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

rnf :: UTCTime -> () #

ToJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON