Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Implements an LRU cache.
This module provides a pure LRU cache based on a doubly-linked list
through a Data.Map structure. This gives O(log n) operations on
insert
, lookup
, delete
, and pop
, and O(n * log n) for toList
.
The interface this module provides is opaque. If further control is desired, the Data.Cache.LRU.Internal module can be used.
Synopsis
- data LRU key val
- newLRU :: Ord key => Maybe Integer -> LRU key val
- fromList :: Ord key => Maybe Integer -> [(key, val)] -> LRU key val
- toList :: Ord key => LRU key val -> [(key, val)]
- pairs :: (Ord key, Applicative f, Contravariant f) => ((key, val) -> f (key, val)) -> LRU key val -> f (LRU key val)
- keys :: (Ord key, Applicative f, Contravariant f) => (key -> f key) -> LRU key val -> f (LRU key val)
- maxSize :: LRU key val -> Maybe Integer
- insert :: Ord key => key -> val -> LRU key val -> LRU key val
- insertInforming :: Ord key => key -> val -> LRU key val -> (LRU key val, Maybe (key, val))
- lookup :: Ord key => key -> LRU key val -> (LRU key val, Maybe val)
- delete :: Ord key => key -> LRU key val -> (LRU key val, Maybe val)
- pop :: Ord key => LRU key val -> (LRU key val, Maybe (key, val))
- size :: LRU key val -> Int
Documentation
Stores the information that makes up an LRU cache
Instances
Functor (LRU key) Source # | |
Ord key => Foldable (LRU key) Source # | |
Defined in Data.Cache.LRU.Internal fold :: Monoid m => LRU key m -> m # foldMap :: Monoid m => (a -> m) -> LRU key a -> m # foldr :: (a -> b -> b) -> b -> LRU key a -> b # foldr' :: (a -> b -> b) -> b -> LRU key a -> b # foldl :: (b -> a -> b) -> b -> LRU key a -> b # foldl' :: (b -> a -> b) -> b -> LRU key a -> b # foldr1 :: (a -> a -> a) -> LRU key a -> a # foldl1 :: (a -> a -> a) -> LRU key a -> a # elem :: Eq a => a -> LRU key a -> Bool # maximum :: Ord a => LRU key a -> a # minimum :: Ord a => LRU key a -> a # | |
Ord key => Traversable (LRU key) Source # | |
(Eq key, Eq val) => Eq (LRU key val) Source # | |
(Data key, Data val, Ord key) => Data (LRU key val) Source # | |
Defined in Data.Cache.LRU.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LRU key val -> c (LRU key val) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LRU key val) # toConstr :: LRU key val -> Constr # dataTypeOf :: LRU key val -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LRU key val)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LRU key val)) # gmapT :: (forall b. Data b => b -> b) -> LRU key val -> LRU key val # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LRU key val -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LRU key val -> r # gmapQ :: (forall d. Data d => d -> u) -> LRU key val -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LRU key val -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LRU key val -> m (LRU key val) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LRU key val -> m (LRU key val) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LRU key val -> m (LRU key val) # | |
(Ord key, Show key, Show val) => Show (LRU key val) Source # | |
Make an LRU. If a size limit is specified, the LRU is guaranteed to not grow above the specified number of entries.
Build a new LRU from the given maximum size and list of contents, in order from most recently accessed to least recently accessed.
toList :: Ord key => LRU key val -> [(key, val)] Source #
Retrieve a list view of an LRU. The items are returned in order from most recently accessed to least recently accessed.
pairs :: (Ord key, Applicative f, Contravariant f) => ((key, val) -> f (key, val)) -> LRU key val -> f (LRU key val) Source #
Traverse the (key, value) pairs of the LRU, in a read-only
way. This is a Fold
in the sense used by the
lens package. It must be
read-only because alterations could break the underlying Map
structure.
keys :: (Ord key, Applicative f, Contravariant f) => (key -> f key) -> LRU key val -> f (LRU key val) Source #
Traverse the keys of the LRU, in a read-only
way. This is a Fold
in the sense used by the
lens package. It must be
read-only because alterations could break the underlying Map
structure.
insert :: Ord key => key -> val -> LRU key val -> LRU key val Source #
Add an item to an LRU. If the key was already present in the LRU, the value is changed to the new value passed in. The item added is marked as the most recently accessed item in the LRU returned.
If this would cause the LRU to exceed its maximum size, the least recently used item is dropped from the cache.
insertInforming :: Ord key => key -> val -> LRU key val -> (LRU key val, Maybe (key, val)) Source #
Same as insert
, but also returns element which was dropped from
cache, if any.
lookup :: Ord key => key -> LRU key val -> (LRU key val, Maybe val) Source #
Look up an item in an LRU. If it was present, it is marked as the most recently accesed in the returned LRU.
delete :: Ord key => key -> LRU key val -> (LRU key val, Maybe val) Source #
Remove an item from an LRU. Returns the new LRU, and the value removed if the key was present.