| Copyright | (c) 2012-2014 The leveldb-haskell Authors | 
|---|---|
| License | BSD3 | 
| Maintainer | kim.altintop@gmail.com | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Database.LevelDB.C
Description
- data LevelDB
- data LCache
- data LComparator
- data LIterator
- data LLogger
- data LOptions
- data LReadOptions
- data LSnapshot
- data LWriteBatch
- data LWriteOptions
- data LFilterPolicy
- type LevelDBPtr = Ptr LevelDB
- type CachePtr = Ptr LCache
- type ComparatorPtr = Ptr LComparator
- type IteratorPtr = Ptr LIterator
- type LoggerPtr = Ptr LLogger
- type OptionsPtr = Ptr LOptions
- type ReadOptionsPtr = Ptr LReadOptions
- type SnapshotPtr = Ptr LSnapshot
- type WriteBatchPtr = Ptr LWriteBatch
- type WriteOptionsPtr = Ptr LWriteOptions
- type FilterPolicyPtr = Ptr LFilterPolicy
- type DBName = CString
- type ErrPtr = Ptr CString
- type Key = CString
- type Val = CString
- newtype CompressionOpt = CompressionOpt {}
- noCompression :: CompressionOpt
- snappyCompression :: CompressionOpt
- c_leveldb_open :: OptionsPtr -> DBName -> ErrPtr -> IO LevelDBPtr
- c_leveldb_close :: LevelDBPtr -> IO ()
- c_leveldb_put :: LevelDBPtr -> WriteOptionsPtr -> Key -> CSize -> Val -> CSize -> ErrPtr -> IO ()
- c_leveldb_delete :: LevelDBPtr -> WriteOptionsPtr -> Key -> CSize -> ErrPtr -> IO ()
- c_leveldb_write :: LevelDBPtr -> WriteOptionsPtr -> WriteBatchPtr -> ErrPtr -> IO ()
- c_leveldb_get :: LevelDBPtr -> ReadOptionsPtr -> Key -> CSize -> Ptr CSize -> ErrPtr -> IO CString
- c_leveldb_create_snapshot :: LevelDBPtr -> IO SnapshotPtr
- c_leveldb_release_snapshot :: LevelDBPtr -> SnapshotPtr -> IO ()
- c_leveldb_property_value :: LevelDBPtr -> CString -> IO CString
- c_leveldb_approximate_sizes :: LevelDBPtr -> CInt -> Ptr CString -> Ptr CSize -> Ptr CString -> Ptr CSize -> Ptr Word64 -> IO ()
- c_leveldb_destroy_db :: OptionsPtr -> DBName -> ErrPtr -> IO ()
- c_leveldb_repair_db :: OptionsPtr -> DBName -> ErrPtr -> IO ()
- c_leveldb_create_iterator :: LevelDBPtr -> ReadOptionsPtr -> IO IteratorPtr
- c_leveldb_iter_destroy :: IteratorPtr -> IO ()
- c_leveldb_iter_valid :: IteratorPtr -> IO CUChar
- c_leveldb_iter_seek_to_first :: IteratorPtr -> IO ()
- c_leveldb_iter_seek_to_last :: IteratorPtr -> IO ()
- c_leveldb_iter_seek :: IteratorPtr -> Key -> CSize -> IO ()
- c_leveldb_iter_next :: IteratorPtr -> IO ()
- c_leveldb_iter_prev :: IteratorPtr -> IO ()
- c_leveldb_iter_key :: IteratorPtr -> Ptr CSize -> IO Key
- c_leveldb_iter_value :: IteratorPtr -> Ptr CSize -> IO Val
- c_leveldb_iter_get_error :: IteratorPtr -> ErrPtr -> IO ()
- c_leveldb_writebatch_create :: IO WriteBatchPtr
- c_leveldb_writebatch_destroy :: WriteBatchPtr -> IO ()
- c_leveldb_writebatch_clear :: WriteBatchPtr -> IO ()
- c_leveldb_writebatch_put :: WriteBatchPtr -> Key -> CSize -> Val -> CSize -> IO ()
- c_leveldb_writebatch_delete :: WriteBatchPtr -> Key -> CSize -> IO ()
- c_leveldb_writebatch_iterate :: WriteBatchPtr -> Ptr () -> FunPtr (Ptr () -> Key -> CSize -> Val -> CSize) -> FunPtr (Ptr () -> Key -> CSize) -> IO ()
- c_leveldb_options_create :: IO OptionsPtr
- c_leveldb_options_destroy :: OptionsPtr -> IO ()
- c_leveldb_options_set_comparator :: OptionsPtr -> ComparatorPtr -> IO ()
- c_leveldb_options_set_filter_policy :: OptionsPtr -> FilterPolicyPtr -> IO ()
- c_leveldb_options_set_create_if_missing :: OptionsPtr -> CUChar -> IO ()
- c_leveldb_options_set_error_if_exists :: OptionsPtr -> CUChar -> IO ()
- c_leveldb_options_set_paranoid_checks :: OptionsPtr -> CUChar -> IO ()
- c_leveldb_options_set_info_log :: OptionsPtr -> LoggerPtr -> IO ()
- c_leveldb_options_set_write_buffer_size :: OptionsPtr -> CSize -> IO ()
- c_leveldb_options_set_max_open_files :: OptionsPtr -> CInt -> IO ()
- c_leveldb_options_set_block_size :: OptionsPtr -> CSize -> IO ()
- c_leveldb_options_set_block_restart_interval :: OptionsPtr -> CInt -> IO ()
- c_leveldb_options_set_compression :: OptionsPtr -> CompressionOpt -> IO ()
- c_leveldb_options_set_cache :: OptionsPtr -> CachePtr -> IO ()
- type StatePtr = Ptr ()
- type Destructor = StatePtr -> ()
- type CompareFun = StatePtr -> CString -> CSize -> CString -> CSize -> IO CInt
- type NameFun = StatePtr -> CString
- mkCmp :: CompareFun -> IO (FunPtr CompareFun)
- mkDest :: Destructor -> IO (FunPtr Destructor)
- mkName :: NameFun -> IO (FunPtr NameFun)
- c_leveldb_comparator_create :: StatePtr -> FunPtr Destructor -> FunPtr CompareFun -> FunPtr NameFun -> IO ComparatorPtr
- c_leveldb_comparator_destroy :: ComparatorPtr -> IO ()
- type CreateFilterFun = StatePtr -> Ptr CString -> Ptr CSize -> CInt -> Ptr CSize -> IO CString
- type KeyMayMatchFun = StatePtr -> CString -> CSize -> CString -> CSize -> IO CUChar
- mkCF :: CreateFilterFun -> IO (FunPtr CreateFilterFun)
- mkKMM :: KeyMayMatchFun -> IO (FunPtr KeyMayMatchFun)
- c_leveldb_filterpolicy_create :: StatePtr -> FunPtr Destructor -> FunPtr CreateFilterFun -> FunPtr KeyMayMatchFun -> FunPtr NameFun -> IO FilterPolicyPtr
- c_leveldb_filterpolicy_destroy :: FilterPolicyPtr -> IO ()
- c_leveldb_filterpolicy_create_bloom :: CInt -> IO FilterPolicyPtr
- c_leveldb_readoptions_create :: IO ReadOptionsPtr
- c_leveldb_readoptions_destroy :: ReadOptionsPtr -> IO ()
- c_leveldb_readoptions_set_verify_checksums :: ReadOptionsPtr -> CUChar -> IO ()
- c_leveldb_readoptions_set_fill_cache :: ReadOptionsPtr -> CUChar -> IO ()
- c_leveldb_readoptions_set_snapshot :: ReadOptionsPtr -> SnapshotPtr -> IO ()
- c_leveldb_writeoptions_create :: IO WriteOptionsPtr
- c_leveldb_writeoptions_destroy :: WriteOptionsPtr -> IO ()
- c_leveldb_writeoptions_set_sync :: WriteOptionsPtr -> CUChar -> IO ()
- c_leveldb_cache_create_lru :: CSize -> IO CachePtr
- c_leveldb_cache_destroy :: CachePtr -> IO ()
- c_leveldb_major_version :: IO CInt
- c_leveldb_minor_version :: IO CInt
Documentation
data LComparator Source
data LReadOptions Source
data LWriteBatch Source
data LWriteOptions Source
data LFilterPolicy Source
type LevelDBPtr = Ptr LevelDB Source
type ComparatorPtr = Ptr LComparator Source
type IteratorPtr = Ptr LIterator Source
type OptionsPtr = Ptr LOptions Source
type ReadOptionsPtr = Ptr LReadOptions Source
type SnapshotPtr = Ptr LSnapshot Source
type WriteBatchPtr = Ptr LWriteBatch Source
type WriteOptionsPtr = Ptr LWriteOptions Source
type FilterPolicyPtr = Ptr LFilterPolicy Source
c_leveldb_open :: OptionsPtr -> DBName -> ErrPtr -> IO LevelDBPtr Source
c_leveldb_close :: LevelDBPtr -> IO () Source
c_leveldb_put :: LevelDBPtr -> WriteOptionsPtr -> Key -> CSize -> Val -> CSize -> ErrPtr -> IO () Source
c_leveldb_delete :: LevelDBPtr -> WriteOptionsPtr -> Key -> CSize -> ErrPtr -> IO () Source
c_leveldb_write :: LevelDBPtr -> WriteOptionsPtr -> WriteBatchPtr -> ErrPtr -> IO () Source
Arguments
| :: LevelDBPtr | |
| -> ReadOptionsPtr | |
| -> Key | |
| -> CSize | |
| -> Ptr CSize | value length | 
| -> ErrPtr | |
| -> IO CString | 
Returns NULL if not found. A malloc()ed array otherwise. Stores the length of the array in *vallen.
c_leveldb_release_snapshot :: LevelDBPtr -> SnapshotPtr -> IO () Source
c_leveldb_property_value :: LevelDBPtr -> CString -> IO CString Source
Returns NULL if property name is unknown. Else returns a pointer to a malloc()-ed null-terminated value.
c_leveldb_destroy_db :: OptionsPtr -> DBName -> ErrPtr -> IO () Source
c_leveldb_repair_db :: OptionsPtr -> DBName -> ErrPtr -> IO () Source
c_leveldb_iter_destroy :: IteratorPtr -> IO () Source
c_leveldb_iter_seek_to_first :: IteratorPtr -> IO () Source
c_leveldb_iter_seek_to_last :: IteratorPtr -> IO () Source
c_leveldb_iter_seek :: IteratorPtr -> Key -> CSize -> IO () Source
c_leveldb_iter_next :: IteratorPtr -> IO () Source
c_leveldb_iter_prev :: IteratorPtr -> IO () Source
c_leveldb_iter_key :: IteratorPtr -> Ptr CSize -> IO Key Source
c_leveldb_iter_value :: IteratorPtr -> Ptr CSize -> IO Val Source
c_leveldb_iter_get_error :: IteratorPtr -> ErrPtr -> IO () Source
c_leveldb_writebatch_clear :: WriteBatchPtr -> IO () Source
c_leveldb_writebatch_put :: WriteBatchPtr -> Key -> CSize -> Val -> CSize -> IO () Source
c_leveldb_writebatch_delete :: WriteBatchPtr -> Key -> CSize -> IO () Source
c_leveldb_options_destroy :: OptionsPtr -> IO () Source
c_leveldb_options_set_comparator :: OptionsPtr -> ComparatorPtr -> IO () Source
c_leveldb_options_set_create_if_missing :: OptionsPtr -> CUChar -> IO () Source
c_leveldb_options_set_error_if_exists :: OptionsPtr -> CUChar -> IO () Source
c_leveldb_options_set_paranoid_checks :: OptionsPtr -> CUChar -> IO () Source
c_leveldb_options_set_info_log :: OptionsPtr -> LoggerPtr -> IO () Source
c_leveldb_options_set_write_buffer_size :: OptionsPtr -> CSize -> IO () Source
c_leveldb_options_set_max_open_files :: OptionsPtr -> CInt -> IO () Source
c_leveldb_options_set_block_size :: OptionsPtr -> CSize -> IO () Source
c_leveldb_options_set_cache :: OptionsPtr -> CachePtr -> IO () Source
type Destructor = StatePtr -> () Source
mkCmp :: CompareFun -> IO (FunPtr CompareFun) Source
Make a FunPtr to a user-defined comparator function
mkDest :: Destructor -> IO (FunPtr Destructor) Source
Make a destructor FunPtr
c_leveldb_comparator_create :: StatePtr -> FunPtr Destructor -> FunPtr CompareFun -> FunPtr NameFun -> IO ComparatorPtr Source
type CreateFilterFun Source
type KeyMayMatchFun Source
mkCF :: CreateFilterFun -> IO (FunPtr CreateFilterFun) Source
Make a FunPtr to a user-defined create_filter function
mkKMM :: KeyMayMatchFun -> IO (FunPtr KeyMayMatchFun) Source
Make a FunPtr to a user-defined key_may_match function
c_leveldb_filterpolicy_create :: StatePtr -> FunPtr Destructor -> FunPtr CreateFilterFun -> FunPtr KeyMayMatchFun -> FunPtr NameFun -> IO FilterPolicyPtr Source
c_leveldb_readoptions_set_fill_cache :: ReadOptionsPtr -> CUChar -> IO () Source
c_leveldb_writeoptions_set_sync :: WriteOptionsPtr -> CUChar -> IO () Source
c_leveldb_cache_destroy :: CachePtr -> IO () Source