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 |
- 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
- defaultWriteOptions :: WriteOptions
- defaultReadOptions :: ReadOptions
- withSnapshot :: MonadResource m => DB -> (Snapshot -> m a) -> m a
- open :: MonadResource 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)
- createSnapshot :: MonadResource m => DB -> m Snapshot
- createSnapshot' :: MonadResource m => DB -> m (ReleaseKey, Snapshot)
- data FilterPolicy = FilterPolicy {
- fpName :: String
- createFilter :: [ByteString] -> ByteString
- keyMayMatch :: ByteString -> ByteString -> Bool
- bloomFilter :: MonadResource m => Int -> m BloomFilter
- 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)
- data Iterator
- withIterator :: MonadResource m => DB -> ReadOptions -> (Iterator -> m a) -> m a
- iterOpen :: MonadResource m => DB -> ReadOptions -> m Iterator
- iterOpen' :: MonadResource m => DB -> ReadOptions -> m (ReleaseKey, Iterator)
- iterValid :: MonadIO m => Iterator -> m Bool
- iterSeek :: MonadIO m => Iterator -> ByteString -> m ()
- iterFirst :: MonadIO m => Iterator -> m ()
- iterLast :: MonadIO m => Iterator -> m ()
- iterNext :: MonadIO m => Iterator -> m ()
- iterPrev :: MonadIO m => Iterator -> m ()
- iterKey :: MonadIO m => Iterator -> m (Maybe ByteString)
- iterValue :: MonadIO m => Iterator -> m (Maybe ByteString)
- iterGetError :: MonadIO m => Iterator -> m (Maybe ByteString)
- class (MonadThrow m, MonadIO m, Applicative m, MonadBase IO m) => MonadResource m where
- runResourceT :: MonadBaseControl IO m => ResourceT m a -> m a
- resourceForkIO :: MonadBaseControl IO m => ResourceT m () -> ResourceT m ThreadId
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 Manipulation
withSnapshot :: MonadResource m => DB -> (Snapshot -> m a) -> m a Source #
Run an action with a snapshot of the database.
The snapshot will be released when the action terminates or throws an
exception. Note that this function is provided for convenience and does not
prevent the Snapshot
handle to escape. It will, however, be invalid after
this function returns and should not be used anymore.
open :: MonadResource m => FilePath -> Options -> m DB Source #
Open a database
The returned handle will automatically be released when the enclosing
runResourceT
terminates.
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.
createSnapshot :: MonadResource m => DB -> m Snapshot Source #
Create a snapshot of the database.
The returned Snapshot
will be released automatically when the enclosing
runResourceT
terminates. It is recommended to use createSnapshot'
instead
and release the resource manually as soon as possible.
createSnapshot' :: MonadResource m => DB -> m (ReleaseKey, Snapshot) Source #
Create a snapshot of the database which can (and should) be released early.
Filter Policy / Bloom Filter
data FilterPolicy Source #
User-defined filter policy
FilterPolicy | |
|
bloomFilter :: MonadResource m => Int -> m BloomFilter Source #
Create a BloomFilter
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
Iterator handle
Note that an Iterator
requires external synchronization if it is shared
between multiple threads which mutate it's state. See
examples/iterforkio.hs
for a simple example of how to do that.
withIterator :: MonadResource m => DB -> ReadOptions -> (Iterator -> m a) -> m a Source #
Run an action with an Iterator. The iterator will be closed after the action returns or an error is thrown. Thus, the iterator will not be valid after this function terminates.
iterOpen :: MonadResource m => DB -> ReadOptions -> m Iterator Source #
Create an Iterator
.
The iterator will be released when the enclosing runResourceT
terminates.
You may consider to use iterOpen'
instead and manually release the iterator
as soon as it is no longer needed (alternatively, use withIterator
).
Note that an Iterator
creates a snapshot of the database implicitly, so
updates written after the iterator was created are not visible. You may,
however, specify an older Snapshot
in the ReadOptions
.
iterOpen' :: MonadResource m => DB -> ReadOptions -> m (ReleaseKey, Iterator) Source #
Create an Iterator
which can be released early.
iterValid :: MonadIO m => Iterator -> m Bool Source #
An iterator is either positioned at a key/value pair, or not valid. This function returns true iff the iterator is valid.
iterSeek :: MonadIO m => Iterator -> ByteString -> m () Source #
Position at the first key in the source that is at or past target. The iterator is valid after this call iff the source contains an entry that comes at or past target.
iterFirst :: MonadIO m => Iterator -> m () Source #
Position at the first key in the source. The iterator is valid after this call iff the source is not empty.
iterLast :: MonadIO m => Iterator -> m () Source #
Position at the last key in the source. The iterator is valid after this call iff the source is not empty.
iterNext :: MonadIO m => Iterator -> m () Source #
Moves to the next entry in the source. After this call, iterValid
is
true iff the iterator was not positioned at the last entry in the source.
If the iterator is not valid, this function does nothing. Note that this is a
shortcoming of the C API: an iterPrev
might still be possible, but we can't
determine if we're at the last or first entry.
iterPrev :: MonadIO m => Iterator -> m () Source #
Moves to the previous entry in the source. After this call, iterValid
is
true iff the iterator was not positioned at the first entry in the source.
If the iterator is not valid, this function does nothing. Note that this is a
shortcoming of the C API: an iterNext
might still be possible, but we can't
determine if we're at the last or first entry.
iterKey :: MonadIO m => Iterator -> m (Maybe ByteString) Source #
Return the key for the current entry if the iterator is currently
positioned at an entry, ie. iterValid
.
iterValue :: MonadIO m => Iterator -> m (Maybe ByteString) Source #
Return the value for the current entry if the iterator is currently
positioned at an entry, ie. iterValid
.
iterGetError :: MonadIO m => Iterator -> m (Maybe ByteString) Source #
Check for errors
Note that this captures somewhat severe errors such as a corrupted database.
Re-exports
class (MonadThrow m, MonadIO m, Applicative m, MonadBase IO m) => MonadResource m where #
A Monad
which allows for safe resource allocation. In theory, any monad
transformer stack which includes a ResourceT
can be an instance of
MonadResource
.
Note: runResourceT
has a requirement for a MonadBaseControl IO m
monad,
which allows control operations to be lifted. A MonadResource
does not
have this requirement. This means that transformers such as ContT
can be
an instance of MonadResource
. However, the ContT
wrapper will need to be
unwrapped before calling runResourceT
.
Since 0.3.0
liftResourceT :: ResourceT IO a -> m a #
Lift a ResourceT IO
action into the current Monad
.
Since 0.4.0
MonadResource m => MonadResource (ListT m) | |
(MonadThrow m, MonadBase IO m, MonadIO m, Applicative m) => MonadResource (ResourceT m) | |
MonadResource m => MonadResource (MaybeT m) | |
(Error e, MonadResource m) => MonadResource (ErrorT e m) | |
MonadResource m => MonadResource (ExceptT e m) | |
MonadResource m => MonadResource (StateT s m) | |
MonadResource m => MonadResource (StateT s m) | |
(Monoid w, MonadResource m) => MonadResource (WriterT w m) | |
(Monoid w, MonadResource m) => MonadResource (WriterT w m) | |
MonadResource m => MonadResource (IdentityT * m) | |
MonadResource m => MonadResource (ContT * r m) | |
MonadResource m => MonadResource (ReaderT * r m) | |
(Monoid w, MonadResource m) => MonadResource (RWST r w s m) | |
(Monoid w, MonadResource m) => MonadResource (RWST r w s m) | |
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
resourceForkIO :: MonadBaseControl IO m => ResourceT m () -> ResourceT m ThreadId #
Launch a new reference counted resource context using forkIO
.
This is defined as resourceForkWith forkIO
.
Since: 0.3.0