tskiplist-1.0.0: A Skip List Implementation in Software Transactional Memory (STM)

Portabilitynon-portable (requires STM)
Stabilityexperimental
MaintainerPeter Robinson <thaldyron@gmail.com>
Safe HaskellNone

Control.Concurrent.STM.TSkipList

Contents

Description

This module provides an implementation of a skip list in the STM monad. The elements of the skip list are stored in a TVar.

A skip list is a probabilistic data structure with dictionary operations (similar to Map). In contrast to a balanced tree, a skip list does not need any (expensive) rebalancing operation, which makes it particularly suitable for concurrent programming.

See: William Pugh. Skip Lists: A Probabilistic Alternative to Balanced Trees.

This module should be imported qualified.

Example (GHCi):

 t <- newIO :: IO (TSkipList Int String) 
 atomically $ sequence_ [ insert i (show i) t | i <- [1..10] ]

 putStrLn =<< atomically (toString t)
 9
 9
 3 7 9
 1 3 7 9
 1 2 3 4 5 6 7 8 9 10

 atomically $ delete  7 t
 putStrLn =<< atomically (toString t)
 9
 9
 3 9
 1 3 9
 1 2 3 4 5 6 8 9 10
 
 atomically $ sequence [ lookup i t | i <- [5..10] ]
 [Just "5",Just "6",Nothing,Just "8",Just "9",Just "10"]

 atomically $ update 8 "X" t
 atomically $ filterRange (5,10) t 
 ["5","6","X","9","10"]

 atomically $ maximum t
 (10,"10")

Synopsis

Data Type and Construction

data TSkipList k a Source

A skip list data type.

newIO :: IO (TSkipList k a)Source

Creates a skiplist. Default values for storing up to 2^16 elements.

newIO'Source

Arguments

:: Float

Probability for choosing a new level

-> Int

Maximum number of levels.

-> IO (TSkipList k a) 

Creates a skiplist.

new :: STM (TSkipList k a)Source

Creates a skiplist. Default values for storing up to 2^16 elements.

new'Source

Arguments

:: Float

Probability for choosing a new level

-> Int

Maximum number of levels

-> STM (TSkipList k a) 

Creates a skiplist.

Operations

insert :: Ord k => k -> a -> TSkipList k a -> STM ()Source

Insertsupdates the value for a specific key. O(log n)/.

lookup :: Ord k => k -> TSkipList k a -> STM (Maybe a)Source

Searches for a given entry. O(log n).

update :: Ord k => k -> a -> TSkipList k a -> STM ()Source

Updates an element. Throws AssertionFailed if the element is not in the list. O(log n).

delete :: Ord k => k -> TSkipList k a -> STM ()Source

Deletes an element. Does nothing if the element is not found. O(log n).

filter :: Ord k => (k -> Bool) -> TSkipList k a -> STM (Map k a)Source

Returns all elements that satisfy the predicate on keys. O(n).

filterGT :: Ord k => k -> TSkipList k a -> STM (Map k a)Source

Returns all elements greater than the key. TODO: currently in O(n), should be made more efficient (like leq)

filterLT :: Ord k => k -> TSkipList k a -> STM (Map k a)Source

Returns all elements less than the key. Takes O(m) where m is the number of elements that have a smaller key.

filterElems :: Ord k => (k -> a -> Bool) -> TSkipList k a -> STM (Map k a)Source

Returns all elements that satisfy the predicate on keys and values. O(n).

filterRange :: Ord k => (k, k) -> TSkipList k a -> STM [(k, a)]Source

Finds all elements within a specific key range (k1,k2). O(log n + k2 - k1).

minimum :: Ord k => TSkipList k a -> STM (k, a)Source

Returns the minimum entry. O(1).

maximum :: Ord k => TSkipList k a -> STM (k, a)Source

Returns the maximum entry. O(log n).

Utilities

chooseLevel :: TSkipList k a -> IntSource

Returns a randomly chosen level. Used for inserting new elements. For performance reasons, this function uses unsafePerformIO to access the random number generator. (It would be possible to store the random number generator in a TVar and thus be able to access it safely from within the STM monad. This, however, might cause high contention among threads.)

toString :: (Show k, Ord k) => TSkipList k a -> STM StringSource

Returns the skip list as a string.