{-# LANGUAGE DataKinds #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE QuantifiedConstraints #-} module Data.Cache ( filtering ) where import Data.Cache.Trace import Data.Cache.Type -- | We can translate the tracking data. -- When the first cache evicts data, try to insert it into the second. -- Left bias, faster cache should come first. --exclusive :: (Cache c1 m k t1 v, Cache c2 k t2 v) => c1 -> c2 -> (t1 -> t2) -> Cache m k t1 v -- | Insert any data into both caches, retrieve it from either. -- Left bias, faster cache should come first. --inclusive :: (Cache c1 m k t v, Cache c2 k t v) => c1 -> c2 -> Cache m k t v -- | Inserts to both, evicts if evicts from either. -- Example usage is to augment a cache with a dataset size limit --intersection :: (Cache c1 m k t1 v, Cache c2 k t2 v) => c1 -> c2 -> Cache m k (t1, t2) v -- | Maps the key to one of a given number of caches and inserts and retrieves from there. --stripped :: (Cache c m k t v) => [c] -> Cache m k t v filtering :: (Monad m, forall (trc::Bool) . (Monad m) => Applicative (Tracable trc (CacheTrace k t v) m), Caching c m k t v) => (k -> t -> Bool) -> c -> DictCache m k t v filtering f c = DictCache (\k t v -> if f k t then insetTraced c k t v else pure ()) (lookupTraced c) (evictTraced c) (updateTracking c)