caching-0: Cache combinators.

Safe HaskellNone
LanguageHaskell2010

Data.Cache.Type

Description

By tracing operations we can transform one type of cache into another.

Synopsis

Documentation

data Cache m k t v Source #

Constructors

Caching c m k t v => Cache c 

insert :: (Monad m, Caching c m k () v) => c -> k -> v -> m () Source #

lookup :: (MonadFail m, Caching c m k t v) => c -> k -> m v Source #

lookupMaybe :: (Monad m, Caching c m k t v) => c -> k -> m (Maybe v) Source #

lookupCreating :: (Monad m, Caching c m k () v) => c -> k -> m v -> m v Source #

cached :: (Monad m, Caching c m k t v) => c -> k -> m Bool Source #

evict :: (Monad m, Caching c m k t v) => c -> k -> m () Source #

data CacheEvent k t v Source #

Constructors

CacheEvict 

Fields

CacheAdd 

Fields

Instances
(Eq k, Eq t, Eq v) => Eq (CacheEvent k t v) Source # 
Instance details

Defined in Data.Cache.Trace

Methods

(==) :: CacheEvent k t v -> CacheEvent k t v -> Bool #

(/=) :: CacheEvent k t v -> CacheEvent k t v -> Bool #

(Ord k, Ord t, Ord v) => Ord (CacheEvent k t v) Source # 
Instance details

Defined in Data.Cache.Trace

Methods

compare :: CacheEvent k t v -> CacheEvent k t v -> Ordering #

(<) :: CacheEvent k t v -> CacheEvent k t v -> Bool #

(<=) :: CacheEvent k t v -> CacheEvent k t v -> Bool #

(>) :: CacheEvent k t v -> CacheEvent k t v -> Bool #

(>=) :: CacheEvent k t v -> CacheEvent k t v -> Bool #

max :: CacheEvent k t v -> CacheEvent k t v -> CacheEvent k t v #

min :: CacheEvent k t v -> CacheEvent k t v -> CacheEvent k t v #

(Read k, Read t, Read v) => Read (CacheEvent k t v) Source # 
Instance details

Defined in Data.Cache.Trace

(Show k, Show t, Show v) => Show (CacheEvent k t v) Source # 
Instance details

Defined in Data.Cache.Trace

Methods

showsPrec :: Int -> CacheEvent k t v -> ShowS #

show :: CacheEvent k t v -> String #

showList :: [CacheEvent k t v] -> ShowS #

type CacheTrace k t v = DList (CacheEvent k t v) Source #

class Caching c (m :: * -> *) k t v | c -> m, c -> k, c -> t, c -> v where Source #

c - The cache type. m - The Monad. k - The key. t - The tracking data. This allows caches to store metadata for 3rd parties. v - The value.

Methods

insetTraced :: forall (trc :: Bool). c -> k -> t -> v -> Tracable trc (CacheTrace k t v) m () Source #

lookupTraced :: forall (trc :: Bool). c -> k -> Tracable trc (CacheTrace k t v) m (Maybe v) Source #

evictTraced :: forall (trc :: Bool). c -> k -> Tracable trc (CacheTrace k t v) m () Source #

updateTracking :: forall (trc :: Bool). c -> k -> (t -> t) -> Tracable trc (CacheTrace k t v) m () Source #

Instances
Caching (DictCache m k t v) m k t v Source # 
Instance details

Defined in Data.Cache.Type

Methods

insetTraced :: DictCache m k t v -> k -> t -> v -> Tracable trc (CacheTrace k t v) m () Source #

lookupTraced :: DictCache m k t v -> k -> Tracable trc (CacheTrace k t v) m (Maybe v) Source #

evictTraced :: DictCache m k t v -> k -> Tracable trc (CacheTrace k t v) m () Source #

updateTracking :: DictCache m k t v -> k -> (t -> t) -> Tracable trc (CacheTrace k t v) m () Source #

data DictCache (m :: * -> *) k t v Source #

A reified Caching dictionary so that we can assemble them on demand.

Constructors

DictCache 

Fields

Instances
Caching (DictCache m k t v) m k t v Source # 
Instance details

Defined in Data.Cache.Type

Methods

insetTraced :: DictCache m k t v -> k -> t -> v -> Tracable trc (CacheTrace k t v) m () Source #

lookupTraced :: DictCache m k t v -> k -> Tracable trc (CacheTrace k t v) m (Maybe v) Source #

evictTraced :: DictCache m k t v -> k -> Tracable trc (CacheTrace k t v) m () Source #

updateTracking :: DictCache m k t v -> k -> (t -> t) -> Tracable trc (CacheTrace k t v) m () Source #