Copyright | (c) 2012-2013 The leveldb-haskell Authors |
---|---|
License | BSD3 |
Maintainer | kim.altintop@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
LevelDB Haskell binding.
The API closely follows the C-API of LevelDB. For more information, see: http://leveldb.googlecode.com
- data DB
- data BatchOp
- newtype Comparator = Comparator (ByteString -> ByteString -> Ordering)
- data Compression
- data Options = Options {
- blockRestartInterval :: !Int
- blockSize :: !Int
- cacheSize :: !Int
- comparator :: !(Maybe Comparator)
- compression :: !Compression
- createIfMissing :: !Bool
- errorIfExists :: !Bool
- maxOpenFiles :: !Int
- paranoidChecks :: !Bool
- writeBufferSize :: !Int
- filterPolicy :: !(Maybe (Either BloomFilter FilterPolicy))
- data ReadOptions = ReadOptions {
- verifyCheckSums :: !Bool
- fillCache :: !Bool
- useSnapshot :: !(Maybe Snapshot)
- data Snapshot
- type WriteBatch = [BatchOp]
- data WriteOptions = WriteOptions {}
- type Range = (ByteString, ByteString)
- defaultOptions :: Options
- defaultReadOptions :: ReadOptions
- defaultWriteOptions :: WriteOptions
- withDB :: (MonadMask m, MonadIO m) => FilePath -> Options -> (DB -> m a) -> m a
- open :: MonadIO m => FilePath -> Options -> m DB
- put :: MonadIO m => DB -> WriteOptions -> ByteString -> ByteString -> m ()
- delete :: MonadIO m => DB -> WriteOptions -> ByteString -> m ()
- write :: MonadIO m => DB -> WriteOptions -> WriteBatch -> m ()
- get :: MonadIO m => DB -> ReadOptions -> ByteString -> m (Maybe ByteString)
- withSnapshot :: (MonadMask m, MonadIO m) => DB -> (Snapshot -> m a) -> m a
- createSnapshot :: MonadIO m => DB -> m Snapshot
- releaseSnapshot :: MonadIO m => DB -> Snapshot -> m ()
- data FilterPolicy = FilterPolicy {
- fpName :: String
- createFilter :: [ByteString] -> ByteString
- keyMayMatch :: ByteString -> ByteString -> Bool
- data BloomFilter
- createBloomFilter :: MonadIO m => Int -> m BloomFilter
- releaseBloomFilter :: MonadIO m => BloomFilter -> m ()
- data Property
- getProperty :: MonadIO m => DB -> Property -> m (Maybe ByteString)
- destroy :: MonadIO m => FilePath -> Options -> m ()
- repair :: MonadIO m => FilePath -> Options -> m ()
- approximateSize :: MonadIO m => DB -> Range -> m Int64
- compactRange :: MonadIO m => DB -> Range -> m ()
- version :: MonadIO m => m (Int, Int)
- module Database.LevelDB.Iterator
Exported Types
Batch operation
data Compression Source #
Compression setting
Options when opening a database
Options | |
|
data ReadOptions Source #
Options for read operations
ReadOptions | |
|
type WriteBatch = [BatchOp] Source #
data WriteOptions Source #
Options for write operations
WriteOptions | |
|
type Range = (ByteString, ByteString) Source #
Defaults
Basic Database Manipulations
open :: MonadIO m => FilePath -> Options -> m DB Source #
Open a database.
The returned handle has a finalizer attached which will free the underlying
pointers once it goes out of scope. Note, however, that finalizers are not
guaranteed to run, and may not run promptly if they do. Use unsafeClose
to
free the handle immediately, but ensure it is not used after that (otherwise,
the program will segault). Alternatively, use the
Database.LevelDB.MonadResource API, which will take care of resource
management automatically.
put :: MonadIO m => DB -> WriteOptions -> ByteString -> ByteString -> m () Source #
Write a key/value pair.
delete :: MonadIO m => DB -> WriteOptions -> ByteString -> m () Source #
Delete a key/value pair.
write :: MonadIO m => DB -> WriteOptions -> WriteBatch -> m () Source #
Perform a batch mutation.
get :: MonadIO m => DB -> ReadOptions -> ByteString -> m (Maybe ByteString) Source #
Read a value by key.
withSnapshot :: (MonadMask m, MonadIO m) => DB -> (Snapshot -> m a) -> m a Source #
Run an action with a Snapshot
of the database.
createSnapshot :: MonadIO m => DB -> m Snapshot Source #
Create a snapshot of the database.
The returned Snapshot
should be released with releaseSnapshot
.
releaseSnapshot :: MonadIO m => DB -> Snapshot -> m () Source #
Release a snapshot.
The handle will be invalid after calling this action and should no longer be used.
Filter Policy / Bloom Filter
data FilterPolicy Source #
User-defined filter policy
FilterPolicy | |
|
data BloomFilter Source #
Represents the built-in Bloom Filter
createBloomFilter :: MonadIO m => Int -> m BloomFilter Source #
releaseBloomFilter :: MonadIO m => BloomFilter -> m () Source #
Administrative Functions
Properties exposed by LevelDB
getProperty :: MonadIO m => DB -> Property -> m (Maybe ByteString) Source #
Get a DB property.
destroy :: MonadIO m => FilePath -> Options -> m () Source #
Destroy the given LevelDB database.
The database must not be in use during this operation.
approximateSize :: MonadIO m => DB -> Range -> m Int64 Source #
Inspect the approximate sizes of the different levels.
compactRange :: MonadIO m => DB -> Range -> m () Source #
Compact the underlying storage for the given Range. In particular this means discarding deleted and overwritten data as well as rearranging the data to reduce the cost of operations accessing the data.
version :: MonadIO m => m (Int, Int) Source #
Return the runtime version of the underlying LevelDB library as a (major, minor) pair.
Iteration
module Database.LevelDB.Iterator