btree-0.4.0: B-Tree on Unmanaged Heap

Safe HaskellNone
LanguageHaskell2010

BTree.Store

Contents

Synopsis

Documentation

data BTree k v Source #

Instances
Storable (BTree k v) Source # 
Instance details

Defined in BTree.Store

Methods

sizeOf :: BTree k v -> Int #

alignment :: BTree k v -> Int #

peekElemOff :: Ptr (BTree k v) -> Int -> IO (BTree k v) #

pokeElemOff :: Ptr (BTree k v) -> Int -> BTree k v -> IO () #

peekByteOff :: Ptr b -> Int -> IO (BTree k v) #

pokeByteOff :: Ptr b -> Int -> BTree k v -> IO () #

peek :: Ptr (BTree k v) -> IO (BTree k v) #

poke :: Ptr (BTree k v) -> BTree k v -> IO () #

Initialize (BTree k v) Source # 
Instance details

Defined in BTree.Store

Methods

initialize :: Ptr (BTree k v) -> IO () #

initializeElemOff :: Ptr (BTree k v) -> Int -> IO () #

initializeElems :: Ptr (BTree k v) -> Int -> IO () #

(Storable k, Deinitialize v) => Deinitialize (BTree k v) Source # 
Instance details

Defined in BTree.Store

Methods

deinitialize :: Ptr (BTree k v) -> IO () #

deinitializeElemOff :: Ptr (BTree k v) -> Int -> IO () #

deinitializeElems :: Ptr (BTree k v) -> Int -> IO () #

class Storable a => Initialize a where #

The class for initializing memory at a pointer representing Storable values.

Minimal complete definition

initialize

Methods

initialize :: Ptr a -> IO () #

Initialize the memory at a pointer. An implementation of this function may do nothing, or if the data contains more pointers, initialize may allocate additional memory.

initializeElemOff :: Ptr a -> Int -> IO () #

Initialize the memory at an offset from the pointer. This has a default implementation but may be overriden for efficiency.

initializeElems :: Ptr a -> Int -> IO () #

Initialize a pointer representing an array with a given number of elements. This has a default implementation but may be overriden for efficiency.

Instances
Initialize Char 
Instance details

Defined in Initialize

Methods

initialize :: Ptr Char -> IO () #

initializeElemOff :: Ptr Char -> Int -> IO () #

initializeElems :: Ptr Char -> Int -> IO () #

Initialize Int 
Instance details

Defined in Initialize

Methods

initialize :: Ptr Int -> IO () #

initializeElemOff :: Ptr Int -> Int -> IO () #

initializeElems :: Ptr Int -> Int -> IO () #

Initialize Int8 
Instance details

Defined in Initialize

Methods

initialize :: Ptr Int8 -> IO () #

initializeElemOff :: Ptr Int8 -> Int -> IO () #

initializeElems :: Ptr Int8 -> Int -> IO () #

Initialize Int16 
Instance details

Defined in Initialize

Methods

initialize :: Ptr Int16 -> IO () #

initializeElemOff :: Ptr Int16 -> Int -> IO () #

initializeElems :: Ptr Int16 -> Int -> IO () #

Initialize Int32 
Instance details

Defined in Initialize

Methods

initialize :: Ptr Int32 -> IO () #

initializeElemOff :: Ptr Int32 -> Int -> IO () #

initializeElems :: Ptr Int32 -> Int -> IO () #

Initialize Int64 
Instance details

Defined in Initialize

Methods

initialize :: Ptr Int64 -> IO () #

initializeElemOff :: Ptr Int64 -> Int -> IO () #

initializeElems :: Ptr Int64 -> Int -> IO () #

Initialize Word 
Instance details

Defined in Initialize

Methods

initialize :: Ptr Word -> IO () #

initializeElemOff :: Ptr Word -> Int -> IO () #

initializeElems :: Ptr Word -> Int -> IO () #

Initialize Word8 
Instance details

Defined in Initialize

Methods

initialize :: Ptr Word8 -> IO () #

initializeElemOff :: Ptr Word8 -> Int -> IO () #

initializeElems :: Ptr Word8 -> Int -> IO () #

Initialize Word16 
Instance details

Defined in Initialize

Initialize Word32 
Instance details

Defined in Initialize

Initialize Word64 
Instance details

Defined in Initialize

Storable a => Initialize (Uninitialized a) 
Instance details

Defined in Initialize

Initialize (BTree k v) Source # 
Instance details

Defined in BTree.Store

Methods

initialize :: Ptr (BTree k v) -> IO () #

initializeElemOff :: Ptr (BTree k v) -> Int -> IO () #

initializeElems :: Ptr (BTree k v) -> Int -> IO () #

class Storable a => Deinitialize a where #

The class for freeing memory at a pointer representing Storable values.

Minimal complete definition

deinitialize

Methods

deinitialize :: Ptr a -> IO () #

Free the memory at a pointer.

deinitializeElemOff :: Ptr a -> Int -> IO () #

Free the memory at an offset from the pointer. This has a default implementation but may be overriden for efficiency.

deinitializeElems :: Ptr a -> Int -> IO () #

Free any memory pointed to by elements of the array. This has a default implementation but may be overriden for efficiency.

Instances
Deinitialize Char 
Instance details

Defined in Initialize

Deinitialize Int 
Instance details

Defined in Initialize

Methods

deinitialize :: Ptr Int -> IO () #

deinitializeElemOff :: Ptr Int -> Int -> IO () #

deinitializeElems :: Ptr Int -> Int -> IO () #

Deinitialize Int8 
Instance details

Defined in Initialize

Deinitialize Int16 
Instance details

Defined in Initialize

Deinitialize Int32 
Instance details

Defined in Initialize

Deinitialize Int64 
Instance details

Defined in Initialize

Deinitialize Word 
Instance details

Defined in Initialize

Deinitialize Word8 
Instance details

Defined in Initialize

Deinitialize Word16 
Instance details

Defined in Initialize

Deinitialize Word32 
Instance details

Defined in Initialize

Deinitialize Word64 
Instance details

Defined in Initialize

Storable a => Deinitialize (Uninitialized a) 
Instance details

Defined in Initialize

(Storable k, Deinitialize v) => Deinitialize (BTree k v) Source # 
Instance details

Defined in BTree.Store

Methods

deinitialize :: Ptr (BTree k v) -> IO () #

deinitializeElemOff :: Ptr (BTree k v) -> Int -> IO () #

deinitializeElems :: Ptr (BTree k v) -> Int -> IO () #

data Decision Source #

Constructors

Keep 
Delete 

new :: forall k v. (Storable k, Storable v) => IO (BTree k v) Source #

free :: forall k v. (Storable k, Deinitialize v) => BTree k v -> IO () Source #

Release all memory allocated by the b-tree. Do not attempt to use the b-tree after calling this.

with :: (Storable k, Initialize v, Deinitialize v) => (BTree k v -> IO (a, BTree k v)) -> IO a Source #

with_ :: (Storable k, Initialize v, Deinitialize v) => (BTree k v -> IO (BTree k v)) -> IO () Source #

lookup :: forall k v. (Ord k, Storable k, Storable v) => BTree k v -> k -> IO (Maybe v) Source #

insert :: (Ord k, Storable k, Initialize v) => BTree k v -> k -> v -> IO (BTree k v) Source #

modifyWithM_ Source #

Arguments

:: (Ord k, Storable k, Initialize v) 
=> BTree k v 
-> k 
-> (v -> IO v)

value modification, happens for newly inserted elements and for previously existing elements

-> IO (BTree k v) 

modifyWithM Source #

Arguments

:: (Ord k, Storable k, Initialize v) 
=> BTree k v 
-> k 
-> (v -> IO (a, v))

value modification, happens for newly inserted elements and for previously existing elements

-> IO (a, BTree k v) 

modifyWithPtr Source #

Arguments

:: (Ord k, Storable k, Initialize v) 
=> BTree k v 
-> k 
-> Either r (Ptr v -> Int -> IO r)

modifications to newly inserted value

-> (Ptr v -> Int -> IO (r, Decision))

modification to value if key is found

-> IO (r, BTree k v) 

foldrWithKey :: forall k v b. (Ord k, Storable k, Storable v) => (k -> v -> b -> IO b) -> b -> BTree k v -> IO b Source #

toAscList :: forall k v. (Ord k, Storable k, Storable v) => BTree k v -> IO [(k, v)] Source #

This is provided for convenience but is not something typically useful in production code.

Weird Operations

index :: forall k v. (Storable k, Storable v) => BTree k v -> (Int -> Int) -> Int -> IO v Source #

indexNode :: forall k v. (Storable k, Storable v) => BTree k v -> (Int -> Int) -> Int -> IO (Ptr v, Int) Source #

Force inlining

inlineModifyWithPtr Source #

Arguments

:: (Ord k, Storable k, Initialize v) 
=> BTree k v 
-> k 
-> Either r (Ptr v -> Int -> IO r)

modifications to newly inserted value

-> (Ptr v -> Int -> IO (r, Decision))

modification to value if key is found

-> IO (r, BTree k v) 

inlineModifyWithM Source #

Arguments

:: (Ord k, Storable k, Initialize v) 
=> BTree k v 
-> k 
-> (v -> IO (a, v))

value modification, happens for newly inserted elements and for previously existing elements

-> IO (a, BTree k v)