higher-leveldb-0.4.0.1: A rich monadic API for working with leveldb databases.

Safe HaskellNone
LanguageHaskell98

Database.LevelDB.Higher

Contents

Description

Higher LevelDB provides a rich monadic API for working with leveldb (http://code.google.com/p/leveldb) databases. It uses the leveldb-haskell bindings to the C++ library. The LevelDBT transformer is a Reader that maintains a database context with the open database as well as default read and write options. It also manages a concept called a KeySpace, which is a bucket scheme that provides a low (storage) overhead named identifier to segregate data. Finally it wraps a ResourceT which is required for use of leveldb-haskell functions.

The other major feature is the scan function and its ScanQuery structure that provides a map / fold abstraction over the Iterator exposed by leveldb-haskell.

Synopsis

Introduction

Operations take place within a MonadLevelDB which is built with the LevelDBT transformer; the most basic type would be LevelDBT IO which is type aliased as LevelDB. The basic operations are the same as the underlying leveldb-haskell versions except that the DB and Options arguments are passed along by the LevelDB Reader, and the keys are automatically qualified with the KeySpaceId.

{-# LANGUAGE OverloadedStrings #-}
import Database.LevelDB.Higher

runCreateLevelDB "/tmp/mydb" "MyKeySpace" $ do
    put "key:1" "this is a value"
    get "key:1"

Just "this is a value"

Basic types

type Item = (Key, Value) Source #

The basic unit of storage is a Key/Value pair.

type KeySpace = ByteString Source #

A KeySpace is similar concept to a "bucket" in other libraries and database systems. The ByteString for KeySpace can be arbitrarily long without performance impact because the system maps the KeySpace name to a 4-byte KeySpaceId internally which is preprended to each Key. KeySpaces are cheap and plentiful and indeed with this library you cannot escape them (you can supply an empty ByteString to use a default KeySpace, but it is still used). One intended use case is to use the full Key of a "parent" as the KeySpace of its children (instance data in a time-series for example). This lets you scan over a range-based key without passing over any unneeded items.

Basic operations

get :: MonadLevelDB m => Key -> m (Maybe Value) Source #

Get a value from the current DB and KeySpace.

put :: MonadLevelDB m => Key -> Value -> m () Source #

Put a value in the current DB and KeySpace.

delete :: MonadLevelDB m => Key -> m () Source #

Delete an entry from the current DB and KeySpace.

Batch operations

runBatch :: MonadLevelDB m => WriterT WriteBatch m () -> m () Source #

Write a batch of operations - use the write and deleteB functions to add operations to the batch list.

putB :: MonadLevelDB m => Key -> Value -> WriterT WriteBatch m () Source #

Add a Put operation to a WriteBatch -- for use with runBatch.

deleteB :: MonadLevelDB m => Key -> WriterT WriteBatch m () Source #

Add a Del operation to a WriteBatch -- for use with runBatch.

Scans

scan Source #

Arguments

:: MonadLevelDB m 
=> Key

Key at which to start the scan.

-> ScanQuery a b

query functions to execute -- see ScanQuery docs.

-> m b 

Scan the keyspace, applying functions and returning results. Look at the documentation for ScanQuery for more information.

This is essentially a fold left that will run until the scanWhile condition is met or the iterator is exhausted. All the results will be copied into memory before the function returns.

data ScanQuery a b Source #

Structure containing functions used within the scan function. You may want to start with one of the builder/helper funcions such as queryItems, which is defined as:

queryItems = queryBegins { scanInit = []
                         , scanMap = id
                         , scanFold = (:)
                         }

Constructors

ScanQuery 

Fields

queryItems :: ScanQuery Item [Item] Source #

A basic ScanQuery helper; this query will find all keys that begin the Key argument supplied to scan, and returns them in a list of Item.

Does not require any function overrides.

queryList :: ScanQuery a [a] Source #

a ScanQuery helper with defaults for queryBegins and a list result; requires a map function e.g.:

scan "encoded-values:" queryList { scanMap = \(_, v) -> decode v }

queryBegins :: ScanQuery a b Source #

A partial ScanQuery helper; this query will find all keys that begin with the Key argument supplied to scan.

Requires an scanInit, a scanMap and a scanFold function.

queryCount :: Num a => ScanQuery a a Source #

a ScanQuery helper to count items beginning with Key argument.

Context modifiers

withKeySpace :: MonadLevelDB m => KeySpace -> m a -> m a Source #

Use a local keyspace for the operation. e.g.:

runCreateLevelDB "/tmp/mydb" "MyKeySpace" $ do
   put "somekey" "somevalue"
   withKeySpace "Other KeySpace" $ do
       put "somekey" "someother value"
   get "somekey"

Just "somevalue"

withOptions :: MonadLevelDB m => RWOptions -> m a -> m a Source #

Local Read/Write Options for the action.

withSnapshot :: MonadLevelDB m => m a -> m a Source #

Run a block of get operations based on a single snapshot taken at the beginning of the action. The snapshot will be automatically released when complete.

This means that you can do put operations in the same block, but you will not see those changes inside this computation.

forkLevelDB :: MonadLevelDB m => LevelDB () -> m ThreadId Source #

Fork a LevelDBT IO action and return ThreadId into the current monad. This uses resourceForkIO to handle the reference counting and cleanup resources when the last thread exits.

Monadic Types and Operations

class (Monad m, MonadThrow m, MonadIO m, Applicative m, MonadResource m, MonadBase IO m) => MonadLevelDB m where Source #

MonadLevelDB class used by all the public functions in this module.

Minimal complete definition

withDBContext, liftLevelDB

Methods

withDBContext :: (DBContext -> DBContext) -> m a -> m a Source #

Override context for an action - only usable internally for functions like withKeySpace and withOptions.

liftLevelDB :: LevelDBT IO a -> m a Source #

Lift a LevelDBT IO action into the current monad.

Instances

(Monad m, MonadLevelDB m) => MonadLevelDB (ListT m) Source # 

Methods

withDBContext :: (DBContext -> DBContext) -> ListT m a -> ListT m a Source #

liftLevelDB :: LevelDBT IO a -> ListT m a Source #

(Monad m, MonadLevelDB m) => MonadLevelDB (MaybeT m) Source # 

Methods

withDBContext :: (DBContext -> DBContext) -> MaybeT m a -> MaybeT m a Source #

liftLevelDB :: LevelDBT IO a -> MaybeT m a Source #

MonadResourceBase m => MonadLevelDB (LevelDBT m) Source # 

Methods

withDBContext :: (DBContext -> DBContext) -> LevelDBT m a -> LevelDBT m a Source #

liftLevelDB :: LevelDBT IO a -> LevelDBT m a Source #

(Monoid w, MonadLevelDB m) => MonadLevelDB (WriterT w m) Source # 

Methods

withDBContext :: (DBContext -> DBContext) -> WriterT w m a -> WriterT w m a Source #

liftLevelDB :: LevelDBT IO a -> WriterT w m a Source #

(Monad m, MonadLevelDB m) => MonadLevelDB (StateT s m) Source # 

Methods

withDBContext :: (DBContext -> DBContext) -> StateT s m a -> StateT s m a Source #

liftLevelDB :: LevelDBT IO a -> StateT s m a Source #

(Monad m, MonadLevelDB m) => MonadLevelDB (ExceptT e m) Source # 

Methods

withDBContext :: (DBContext -> DBContext) -> ExceptT e m a -> ExceptT e m a Source #

liftLevelDB :: LevelDBT IO a -> ExceptT e m a Source #

(Monad m, MonadLevelDB m) => MonadLevelDB (IdentityT * m) Source # 

Methods

withDBContext :: (DBContext -> DBContext) -> IdentityT * m a -> IdentityT * m a Source #

liftLevelDB :: LevelDBT IO a -> IdentityT * m a Source #

(Monad m, MonadLevelDB m) => MonadLevelDB (StateT s m) Source # 

Methods

withDBContext :: (DBContext -> DBContext) -> StateT s m a -> StateT s m a Source #

liftLevelDB :: LevelDBT IO a -> StateT s m a Source #

(Monoid w, MonadLevelDB m) => MonadLevelDB (WriterT w m) Source # 

Methods

withDBContext :: (DBContext -> DBContext) -> WriterT w m a -> WriterT w m a Source #

liftLevelDB :: LevelDBT IO a -> WriterT w m a Source #

(Monad m, MonadLevelDB m) => MonadLevelDB (ReaderT * r m) Source # 

Methods

withDBContext :: (DBContext -> DBContext) -> ReaderT * r m a -> ReaderT * r m a Source #

liftLevelDB :: LevelDBT IO a -> ReaderT * r m a Source #

(Monad m, MonadLevelDB m) => MonadLevelDB (ContT * r m) Source # 

Methods

withDBContext :: (DBContext -> DBContext) -> ContT * r m a -> ContT * r m a Source #

liftLevelDB :: LevelDBT IO a -> ContT * r m a Source #

(Monoid w, MonadLevelDB m) => MonadLevelDB (RWST r w s m) Source # 

Methods

withDBContext :: (DBContext -> DBContext) -> RWST r w s m a -> RWST r w s m a Source #

liftLevelDB :: LevelDBT IO a -> RWST r w s m a Source #

(Monoid w, MonadLevelDB m) => MonadLevelDB (RWST r w s m) Source # 

Methods

withDBContext :: (DBContext -> DBContext) -> RWST r w s m a -> RWST r w s m a Source #

liftLevelDB :: LevelDBT IO a -> RWST r w s m a Source #

data LevelDBT m a Source #

LevelDBT Transformer provides a context for database operations provided in this module.

This transformer has the same constraints as ResourceT as it wraps ResourceT along with a DBContext Reader.

If you aren't building a custom monad stack you can just use the LevelDB alias.

Instances

MonadTrans LevelDBT Source # 

Methods

lift :: Monad m => m a -> LevelDBT m a #

MonadTransControl LevelDBT Source # 

Associated Types

type StT (LevelDBT :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run LevelDBT -> m a) -> LevelDBT m a #

restoreT :: Monad m => m (StT LevelDBT a) -> LevelDBT m a #

MonadBase b m => MonadBase b (LevelDBT m) Source # 

Methods

liftBase :: b α -> LevelDBT m α #

MonadBaseControl b m => MonadBaseControl b (LevelDBT m) Source # 

Associated Types

type StM (LevelDBT m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (LevelDBT m) b -> b a) -> LevelDBT m a #

restoreM :: StM (LevelDBT m) a -> LevelDBT m a #

Monad m => Monad (LevelDBT m) Source # 

Methods

(>>=) :: LevelDBT m a -> (a -> LevelDBT m b) -> LevelDBT m b #

(>>) :: LevelDBT m a -> LevelDBT m b -> LevelDBT m b #

return :: a -> LevelDBT m a #

fail :: String -> LevelDBT m a #

Functor m => Functor (LevelDBT m) Source # 

Methods

fmap :: (a -> b) -> LevelDBT m a -> LevelDBT m b #

(<$) :: a -> LevelDBT m b -> LevelDBT m a #

Applicative m => Applicative (LevelDBT m) Source # 

Methods

pure :: a -> LevelDBT m a #

(<*>) :: LevelDBT m (a -> b) -> LevelDBT m a -> LevelDBT m b #

liftA2 :: (a -> b -> c) -> LevelDBT m a -> LevelDBT m b -> LevelDBT m c #

(*>) :: LevelDBT m a -> LevelDBT m b -> LevelDBT m b #

(<*) :: LevelDBT m a -> LevelDBT m b -> LevelDBT m a #

MonadIO m => MonadIO (LevelDBT m) Source # 

Methods

liftIO :: IO a -> LevelDBT m a #

MonadThrow m => MonadThrow (LevelDBT m) Source # 

Methods

throwM :: Exception e => e -> LevelDBT m a #

MonadCatch m => MonadCatch (LevelDBT m) Source # 

Methods

catch :: Exception e => LevelDBT m a -> (e -> LevelDBT m a) -> LevelDBT m a #

MonadMask m => MonadMask (LevelDBT m) Source # 

Methods

mask :: ((forall a. LevelDBT m a -> LevelDBT m a) -> LevelDBT m b) -> LevelDBT m b #

uninterruptibleMask :: ((forall a. LevelDBT m a -> LevelDBT m a) -> LevelDBT m b) -> LevelDBT m b #

MonadResourceBase m => MonadResource (LevelDBT m) Source # 

Methods

liftResourceT :: ResourceT IO a -> LevelDBT m a #

MonadResourceBase m => MonadLevelDB (LevelDBT m) Source # 

Methods

withDBContext :: (DBContext -> DBContext) -> LevelDBT m a -> LevelDBT m a Source #

liftLevelDB :: LevelDBT IO a -> LevelDBT m a Source #

type StT LevelDBT a Source # 
type StT LevelDBT a
type StM (LevelDBT m) a Source # 
type StM (LevelDBT m) a = ComposeSt LevelDBT m a

type LevelDB a = LevelDBT IO a Source #

alias for LevelDBT IO - useful if you aren't building a custom stack.

mapLevelDBT :: (m a -> n b) -> LevelDBT m a -> LevelDBT n b Source #

Map/transform the monad below the LevelDBT

runLevelDB Source #

Arguments

:: MonadResourceBase m 
=> FilePath

path to DB to open/create

-> Options

database options to use

-> RWOptions

default read/write ops; use withOptions to override

-> KeySpace

Bucket in which Keys will be unique

-> LevelDBT m a

The actions to execute

-> m a 

Build a context and execute the actions; uses a ResourceT internally.

tip: you can use the Data.Default (def) method to specify default options e.g.

runLevelDB "/tmp/mydb" def (def, def{sync = true}) "My Keyspace" $ do

runLevelDB' Source #

Arguments

:: MonadResourceBase m 
=> FilePath

path to DB to open/create

-> Options

database options to use

-> RWOptions

default read/write ops; use withOptions to override

-> KeySpace

Bucket in which Keys will be unique

-> LevelDBT m a

The actions to execute

-> ResourceT m a 

Same as runLevelDB but doesn't call runResourceT. This gives you the option to manage that yourself

runCreateLevelDB Source #

Arguments

:: MonadResourceBase m 
=> FilePath

path to DB to open/create

-> KeySpace

Bucket in which Keys will be unique

-> LevelDBT m a

The actions to execute

-> m a 

A helper for runLevelDB using default Options except createIfMissing=True

Re-exports

runResourceT :: MonadBaseControl IO m => ResourceT m a -> m a #

Unwrap a ResourceT transformer, and call all registered release actions.

Note that there is some reference counting involved due to resourceForkIO. If multiple threads are sharing the same collection of resources, only the last call to runResourceT will deallocate the resources.

Since 0.3.0

data Options :: * #

Options when opening a database

Constructors

Options 

Fields

  • blockRestartInterval :: !Int

    Number of keys between restart points for delta encoding of keys.

    This parameter can be changed dynamically. Most clients should leave this parameter alone.

    Default: 16

  • blockSize :: !Int

    Approximate size of user data packed per block.

    Note that the block size specified here corresponds to uncompressed data. The actual size of the unit read from disk may be smaller if compression is enabled.

    This parameter can be changed dynamically.

    Default: 4k

  • cacheSize :: !Int

    Control over blocks (user data is stored in a set of blocks, and a block is the unit of reading from disk).

    If > 0, use the specified cache (in bytes) for blocks. If 0, leveldb will automatically create and use an 8MB internal cache.

    Default: 0

  • comparator :: !(Maybe Comparator)

    Comparator used to defined the order of keys in the table.

    If Nothing, the default comparator is used, which uses lexicographic bytes-wise ordering.

    NOTE: the client must ensure that the comparator supplied here has the same name and orders keys exactly the same as the comparator provided to previous open calls on the same DB.

    Default: Nothing

  • compression :: !Compression

    Compress blocks using the specified compression algorithm.

    This parameter can be changed dynamically.

    Default: Snappy

  • createIfMissing :: !Bool

    If true, the database will be created if it is missing.

    Default: False

  • errorIfExists :: !Bool

    It true, an error is raised if the database already exists.

    Default: False

  • maxOpenFiles :: !Int

    Number of open files that can be used by the DB.

    You may need to increase this if your database has a large working set (budget one open file per 2MB of working set).

    Default: 1000

  • paranoidChecks :: !Bool

    If true, the implementation will do aggressive checking of the data it is processing and will stop early if it detects any errors.

    This may have unforeseen ramifications: for example, a corruption of one DB entry may cause a large number of entries to become unreadable or for the entire DB to become unopenable.

    Default: False

  • writeBufferSize :: !Int

    Amount of data to build up in memory (backed by an unsorted log on disk) before converting to a sorted on-disk file.

    Larger values increase performance, especially during bulk loads. Up to to write buffers may be held in memory at the same time, so you may with to adjust this parameter to control memory usage. Also, a larger write buffer will result in a longer recovery time the next time the database is opened.

    Default: 4MB

  • filterPolicy :: !(Maybe (Either BloomFilter FilterPolicy))
     

Instances

data ReadOptions :: * #

Options for read operations

Constructors

ReadOptions 

Fields

  • verifyCheckSums :: !Bool

    If true, all data read from underlying storage will be verified against corresponding checksums.

    Default: False

  • fillCache :: !Bool

    Should the data read for this iteration be cached in memory? Callers may with to set this field to false for bulk scans.

    Default: True

  • useSnapshot :: !(Maybe Snapshot)

    If Just, read as of the supplied snapshot (which must belong to the DB that is being read and which must not have been released). If Nothing, use an implicit snapshot of the state at the beginning of this read operation.

    Default: Nothing

data WriteOptions :: * #

Options for write operations

Constructors

WriteOptions 

Fields

  • sync :: !Bool

    If true, the write will be flushed from the operating system buffer cache (by calling WritableFile::Sync()) before the write is considered complete. If this flag is true, writes will be slower.

    If this flag is false, and the machine crashes, some recent writes may be lost. Note that if it is just the process that crashes (i.e., the machine does not reboot), no writes will be lost even if sync==false.

    In other words, a DB write with sync==false has similar crash semantics as the "write()" system call. A DB write with sync==true has similar crash semantics to a "write()" system call followed by "fsync()".

    Default: False

def :: Default a => a #

The default value for this type.

class Monad m => MonadThrow (m :: * -> *) #

A class for monads in which exceptions may be thrown.

Instances should obey the following law:

throwM e >> x = throwM e

In other words, throwing an exception short-circuits the rest of the monadic computation.

Minimal complete definition

throwM

Instances

MonadThrow [] 

Methods

throwM :: Exception e => e -> [a] #

MonadThrow Maybe 

Methods

throwM :: Exception e => e -> Maybe a #

MonadThrow IO 

Methods

throwM :: Exception e => e -> IO a #

MonadThrow Q 

Methods

throwM :: Exception e => e -> Q a #

MonadThrow STM 

Methods

throwM :: Exception e => e -> STM a #

(~) * e SomeException => MonadThrow (Either e) 

Methods

throwM :: Exception e => e -> Either e a #

MonadThrow m => MonadThrow (ListT m) 

Methods

throwM :: Exception e => e -> ListT m a #

MonadThrow m => MonadThrow (MaybeT m)

Throws exceptions into the base monad.

Methods

throwM :: Exception e => e -> MaybeT m a #

MonadThrow m => MonadThrow (ResourceT m) 

Methods

throwM :: Exception e => e -> ResourceT m a #

MonadThrow m => MonadThrow (LevelDBT m) # 

Methods

throwM :: Exception e => e -> LevelDBT m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 

Methods

throwM :: Exception e => e -> WriterT w m a #

MonadThrow m => MonadThrow (StateT s m) 

Methods

throwM :: Exception e => e -> StateT s m a #

MonadThrow m => MonadThrow (ExceptT e m)

Throws exceptions into the base monad.

Methods

throwM :: Exception e => e -> ExceptT e m a #

(Error e, MonadThrow m) => MonadThrow (ErrorT e m)

Throws exceptions into the base monad.

Methods

throwM :: Exception e => e -> ErrorT e m a #

MonadThrow m => MonadThrow (IdentityT * m) 

Methods

throwM :: Exception e => e -> IdentityT * m a #

MonadThrow m => MonadThrow (StateT s m) 

Methods

throwM :: Exception e => e -> StateT s m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 

Methods

throwM :: Exception e => e -> WriterT w m a #

MonadThrow m => MonadThrow (ReaderT * r m) 

Methods

throwM :: Exception e => e -> ReaderT * r m a #

MonadThrow m => MonadThrow (ContT * r m) 

Methods

throwM :: Exception e => e -> ContT * r m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 

Methods

throwM :: Exception e => e -> RWST r w s m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 

Methods

throwM :: Exception e => e -> RWST r w s m a #

type MonadResourceBase (m :: * -> *) = (MonadBaseControl IO m, MonadThrow m, MonadBase IO m, MonadIO m, Applicative m) #

A Monad which can be used as a base for a ResourceT.

A ResourceT has some restrictions on its base monad:

  • runResourceT requires an instance of MonadBaseControl IO.
  • MonadResource requires an instance of MonadThrow, MonadIO, and Applicative.

While any instance of MonadBaseControl IO should be an instance of the other classes, this is not guaranteed by the type system (e.g., you may have a transformer in your stack with does not implement MonadThrow). Ideally, we would like to simply create an alias for the five type classes listed, but this is not possible with GHC currently.

Instead, this typeclass acts as a proxy for the other five. Its only purpose is to make your type signatures shorter.

Note that earlier versions of conduit had a typeclass ResourceIO. This fulfills much the same role.

Since 0.3.2