Safe Haskell | Safe |
---|---|
Language | Haskell98 |
This module provides access to all the internals use by the LRU
type. This can be used to create data structures that violate the
invariants the public interface maintains. Be careful when using
this module. The valid
function can be used to check if an LRU
structure satisfies the invariants the public interface maintains.
If this degree of control isn't needed, consider using Data.Cache.LRU instead.
Synopsis
- data LRU key val = LRU {}
- data LinkedVal key val = Link {}
- 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)
- 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
- hit' :: Ord key => key -> LRU key val -> LRU key val
- delete' :: Ord key => key -> LRU key val -> Map key (LinkedVal key val) -> LinkedVal key val -> LRU key val
- adjust' :: Ord k => (a -> a) -> k -> Map k a -> Map k a
- valid :: Ord key => LRU key val -> Bool
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 # | |
data LinkedVal key val Source #
The values stored in the Map of the LRU cache. They embed a
doubly-linked list through the values of the Map
.
Instances
Functor (LinkedVal key) Source # | |
Foldable (LinkedVal key) Source # | |
Defined in Data.Cache.LRU.Internal fold :: Monoid m => LinkedVal key m -> m # foldMap :: Monoid m => (a -> m) -> LinkedVal key a -> m # foldr :: (a -> b -> b) -> b -> LinkedVal key a -> b # foldr' :: (a -> b -> b) -> b -> LinkedVal key a -> b # foldl :: (b -> a -> b) -> b -> LinkedVal key a -> b # foldl' :: (b -> a -> b) -> b -> LinkedVal key a -> b # foldr1 :: (a -> a -> a) -> LinkedVal key a -> a # foldl1 :: (a -> a -> a) -> LinkedVal key a -> a # toList :: LinkedVal key a -> [a] # null :: LinkedVal key a -> Bool # length :: LinkedVal key a -> Int # elem :: Eq a => a -> LinkedVal key a -> Bool # maximum :: Ord a => LinkedVal key a -> a # minimum :: Ord a => LinkedVal key a -> a # | |
Traversable (LinkedVal key) Source # | |
Defined in Data.Cache.LRU.Internal | |
(Eq val, Eq key) => Eq (LinkedVal key val) Source # | |
(Data key, Data val) => Data (LinkedVal 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) -> LinkedVal key val -> c (LinkedVal key val) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LinkedVal key val) # toConstr :: LinkedVal key val -> Constr # dataTypeOf :: LinkedVal key val -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LinkedVal key val)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LinkedVal key val)) # gmapT :: (forall b. Data b => b -> b) -> LinkedVal key val -> LinkedVal key val # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LinkedVal key val -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LinkedVal key val -> r # gmapQ :: (forall d. Data d => d -> u) -> LinkedVal key val -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LinkedVal key val -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LinkedVal key val -> m (LinkedVal key val) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LinkedVal key val -> m (LinkedVal key val) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LinkedVal key val -> m (LinkedVal key val) # |
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.
pop :: Ord key => LRU key val -> (LRU key val, Maybe (key, val)) Source #
Removes the least-recently accessed element from the LRU. Returns the new LRU, and the key and value from the least-recently used element, if there was one.
hit' :: Ord key => key -> LRU key val -> LRU key val Source #
Internal function. The key passed in must be present in the LRU. Moves the item associated with that key to the most recently accessed position.
:: Ord key | |
=> key | The key must be present in the provided |
-> LRU key val | This is the |
-> Map key (LinkedVal key val) | this is the |
-> LinkedVal key val | This is the |
-> LRU key val |
An internal function used by insert
(when the cache is full)
and delete
. This function has strict requirements on its
arguments in order to work properly.
As this is intended to be an internal function, the arguments were chosen to avoid repeated computation, rather than for simplicity of calling this function.
adjust' :: Ord k => (a -> a) -> k -> Map k a -> Map k a Source #
Internal function. This is very similar to adjust
, with
two major differences. First, it's strict in the application of
the function, which is a huge win when working with this structure.
Second, it requires that the key be present in order to work. If
the key isn't present, undefined
will be inserted into the Map
,
which will cause problems later.
valid :: Ord key => LRU key val -> Bool Source #
Internal function. This checks the four structural invariants of the LRU cache structure:
- The cache's size does not exceed the specified max size.
- The linked list through the nodes is consistent in both directions.
- The linked list contains the same number of nodes as the cache.
- Every key in the linked list is in the
Map
.