tbox-0.1.0: Transactional variables and data structures with IO hooks

Portabilitynon-portable (requires STM)
Stabilityexperimental
MaintainerPeter Robinson <robinson@ecs.tuwien.ac.at>

Control.Concurrent.TFile.TSkipList

Contents

Description

Instantiates the STM skiplist implementation of Control.Concurrent.TBox.TSkipList with the TFile backend.

This module should be imported qualified.

Example:

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

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

 atomically $ delete  7 t
 putStr =<< atomically (toString 100 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 $ sequence [ lookup i t | i <- [5..10] ]
 [Just "5",Just "6",Nothing,Just "X",Just "9",Just "10"]

Synopsis

Data type

newEmptyIO :: (Binary a, Show k, Ord k, Read k, TBox TFile k a) => Float -> Int -> IO (TSkipList k a)Source

Returns a new (reconstructed!) TSkipList. Automatically inserts all TFile entries found in "basedir/". Note that the TFiles are initially empty, i.e., the file content will only be read into memory on demand.

newIO :: (Binary a, Show k, Ord k, Read k, TBox TFile k a) => Float -> Int -> IO (TSkipList k a)Source

Returns a new (reconstructed!) TSkipList. Automatically inserts all TFile entries found in "basedir/". In contrast to newEmptyIO, the TFiles initially contain the file content. Use this if you want to have all data in memory from the start.

Operations

insert :: (Ord k, TBox t k a) => k -> a -> TSkipList t k a -> AdvSTM ()Source

lookup :: (Ord k, TBox t k a) => k -> TSkipList t k a -> AdvSTM (Maybe a)Source

update :: (Ord k, TBox t k a) => k -> a -> TSkipList t k a -> AdvSTM ()Source

Updates an element. Throws AssertionFailed if the element is not in the list.

leq :: (Ord k, TBox t k a) => k -> TSkipList t k a -> AdvSTM (Map k a)Source

Returns all elements that are smaller than the key.

geq :: (Ord k, TBox t k a) => k -> TSkipList t k a -> AdvSTM (Map k a)Source

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

min :: (Ord k, TBox t k a) => TSkipList t k a -> AdvSTM (Maybe a)Source

Returns the element with the least key, if it exists. O(1).

filter :: (Ord k, TBox t k a) => (k -> a -> Bool) -> TSkipList t k a -> AdvSTM (Map k a)Source

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

delete :: (Ord k, TBox t k a) => k -> TSkipList t k a -> AdvSTM ()Source

Utilities

chooseLevel :: TSkipList t k a -> AdvSTM IntSource

Returns a randomly chosen level. Is used for inserting new elements. Note that this function uses unsafeIOToAdvSTM to access the random number generator.

toString :: (Ord k, Show k, TBox t k a) => k -> TSkipList t k a -> AdvSTM StringSource

Debug helper. Returns the skip list as a string. All elements smaller than the given key are written to the string.