Safe Haskell | None |
---|---|
Language | Haskell98 |
An implementation of concurrent finite maps based on skip lists. Only supports lookup and insertions, not modifications or removals.
Skip lists are a probabilistic data structure that roughly approximate balanced trees. At the bottom layer is a standard linked list representation of a finite map. Above this is some number of "index" lists that provide shortcuts to the layer below them. When a key/value pair is added, it is always added to the bottom layer, and is added with exponentially decreasing probability to each index layer above it.
Skip lists are a very good match for lock-free programming, since the linearization point can be taken as insertion into the bottom list, and index nodes can be added *afterward* in a best-effort style (i.e., if there is contention to add them, we can simply walk away, with the effect that the probability of appearing in an index is partly a function of contention.)
To implement skip lists in Haskell, we use a GADT to represent the layers, each of which has a different type (since it indexes the layer below it).
- data SLMap k v
- newSLMap :: Int -> IO (SLMap k v)
- find :: Ord k => SLMap k v -> k -> IO (Maybe v)
- data PutResult v
- putIfAbsent :: (Ord k, MonadIO m, MonadToss m) => SLMap k v -> k -> m v -> m (PutResult v)
- putIfAbsentToss :: (Ord k, MonadIO m) => SLMap k v -> k -> m v -> m Bool -> m (PutResult v)
- foldlWithKey :: Monad m => (forall x. IO x -> m x) -> (a -> k -> v -> m a) -> a -> SLMap k v -> m a
- counts :: SLMap k v -> IO [Int]
- debugShow :: forall k v. (Ord k, Show k, Show v) => SLMapSlice k v -> IO String
- data SLMapSlice k v = Slice (SLMap k v) !(Maybe k) !(Maybe k)
- toSlice :: SLMap k v -> SLMapSlice k v
- splitSlice :: forall k v. (Show k, Ord k) => SLMapSlice k v -> IO (Maybe (SLMapSlice k v, SLMapSlice k v))
- sliceSize :: Ord k => SLMapSlice k v -> IO Int
Documentation
:: (Ord k, MonadIO m, MonadToss m) | |
=> SLMap k v | The map |
-> k | The key to lookup/insert |
-> m v | A computation of the value to insert |
-> m (PutResult v) |
Adds a key/value pair if the key is not present, all within a given monad. Returns the value now associated with the key in the map.
:: (Ord k, MonadIO m) | |
=> SLMap k v | The map |
-> k | The key to lookup/insert |
-> m v | A computation of the value to insert |
-> m Bool | An explicit, thread-local coin to toss |
-> m (PutResult v) |
Adds a key/value pair if the key is not present, all within a given monad. Returns the value now associated with the key in the map.
foldlWithKey :: Monad m => (forall x. IO x -> m x) -> (a -> k -> v -> m a) -> a -> SLMap k v -> m a Source
Concurrently fold over all key/value pairs in the map within the given monad, in increasing key order. Inserts that arrive concurrently may or may not be included in the fold.
Strict in the accumulator.
counts :: SLMap k v -> IO [Int] Source
Returns the sizes of the skiplist levels; for performance debugging.
debugShow :: forall k v. (Ord k, Show k, Show v) => SLMapSlice k v -> IO String Source
Print a slice with each layer on a line.
Slicing SLMaps
data SLMapSlice k v Source
A portion of an SLMap between two keys. If the upper-bound is missing, that means "go to the end". The optional lower bound is used to "lazily" prune the fronts each layer. The reason for this is that we don't want to reallocate an IORef spine and prematurely prune all lower layers IF we're simply going to split again before actually enumerating the contents.
toSlice :: SLMap k v -> SLMapSlice k v Source
Create a slice corresponding to the entire (non-empty) map.
splitSlice :: forall k v. (Show k, Ord k) => SLMapSlice k v -> IO (Maybe (SLMapSlice k v, SLMapSlice k v)) Source
Attempt to split a slice of an SLMap. If there are not enough elements to form two slices, this retruns Nothing.