tokyocabinet-haskell-0.0.5: Haskell binding of Tokyo Cabinet

Database.TokyoCabinet.HDB

Contents

Description

Interface to Hash based DBM. See also, http://tokyocabinet.sourceforge.net/spex-en.html#tchdbapi for details

Synopsis

Documentation

Example

    import Control.Monad
    import Database.TokyoCabinet.HDB
    main = do hdb <- new
              -- open the database
              open hdb "casket.tch" [OWRITER, OCREAT] >>= err hdb
              -- store records
              puts hdb [("foo", "hop"), ("bar", "step"), ("baz", "jump")] >>=
                       err hdb . (all id)
              -- retrieve records
              get_print hdb "foo"
              -- traverse records
              iterinit hdb
              iter hdb >>= mapM_ (k -> putStr (k++":") >> get_print hdb k)
              -- close the database
              close hdb >>= err hdb
        where
          puts :: HDB -> [(String, String)] -> IO [Bool]
          puts hdb = mapM (uncurry $ put hdb)
          get_print :: HDB -> String -> IO ()
          get_print hdb key = get hdb key >>=
                              maybe (error "something goes wrong") putStrLn
  
          err :: HDB -> Bool -> IO ()
          err hdb = flip unless $ ecode hdb >>= error . show
    
          iter :: HDB -> IO [String]
          iter hdb = iternext hdb >>=
                     maybe (return []) (x -> return . (x:) =<< iter hdb)

data HDB Source

Instances

data ECODE Source

Represents error

Constructors

ESUCCESS

success

ETHREAD

threading error

EINVALID

invalid operation

ENOFILE

file not found

ENOPERM

no permission

EMETA

invalid meta data

ERHEAD

invalid record header

EOPEN

open error

ECLOSE

close error

ETRUNC

trunc error

ESYNC

sync error

ESTAT

stat error

ESEEK

seek error

EREAD

read error

EWRITE

write error

EMMAP

mmap error

ELOCK

lock error

EUNLINK

unlink error

ERENAME

rename error

EMKDIR

mkdir error

ERMDIR

rmdir error

EKEEP

existing record

ENOREC

no record found

EMISC

miscellaneous error

Instances

Basic API (tokyocabinet.idl compliant)

new :: IO HDBSource

Create a Hash database object.

delete :: HDB -> IO ()Source

Free HDB resource forcibly. HDB is kept by ForeignPtr, so Haskell runtime GC cleans up memory for almost situation. Most always, you don't need to call this. After call this, you must not touch HDB object. Its behavior is undefined.

ecode :: HDB -> IO ECODESource

Return the last happened error code.

errmsg :: ECODE -> StringSource

Convert error code to message string.

tuneSource

Arguments

:: HDB

HDB object

-> Int64

the number of elements of the bucket array.

-> Int8

the size of record alignment by power of 2.

-> Int8

the maximum number of elements of the free block pool by power of 2.

-> [TuningOption]

tuning options.

-> IO Bool

if successful, the return value is True.

Set the tuning parameters.

setcacheSource

Arguments

:: HDB

HDB object.

-> Int32

the maximum number of records to be cached.

-> IO Bool

if successful, the return value is True.

Set the caching parameters.

setxmsiz :: HDB -> Int64 -> IO BoolSource

Set the size of extra mapped memory.

open :: HDB -> String -> [OpenMode] -> IO BoolSource

Open a database file.

close :: HDB -> IO BoolSource

Close the database file.

put :: (Storable k, Storable v) => HDB -> k -> v -> IO BoolSource

Stora a record (key-value pair) on HDB. Key and value type must be instance of Storable class. Usually, we can use String, ByteString for key, String, ByteString, Int, Double for value.

putkeep :: (Storable k, Storable v) => HDB -> k -> v -> IO BoolSource

Store a new record. If a record with the same key exists in the database, this function has no effect.

putcat :: (Storable k, Storable v) => HDB -> k -> v -> IO BoolSource

Concatenate a value at the end of the existing record.

putasync :: (Storable k, Storable v) => HDB -> k -> v -> IO BoolSource

Store a record into a hash database object in asynchronous fashion.

out :: Storable k => HDB -> k -> IO BoolSource

Delete a record.

get :: (Storable k, Storable v) => HDB -> k -> IO (Maybe v)Source

Return the value of record.

vsiz :: Storable k => HDB -> k -> IO (Maybe Int)Source

Return the byte size of value in a record.

iterinit :: HDB -> IO BoolSource

Initialize the iterator of a HDB object.

iternext :: Storable k => HDB -> IO (Maybe k)Source

Return the next key of the iterator of a HDB object.

fwmkeys :: (Storable k1, Storable k2, Sequence q) => HDB -> k1 -> Int -> IO (q k2)Source

Return list of forward matched keys.

addint :: Storable k => HDB -> k -> Int -> IO (Maybe Int)Source

Increment the corresponding value. (The value specified by a key is treated as integer.)

adddouble :: Storable k => HDB -> k -> Double -> IO (Maybe Double)Source

Increment the corresponding value. (The value specified by a key is treated as double.)

sync :: HDB -> IO BoolSource

Synchronize updated contents of a database object with the file and the device.

optimizeSource

Arguments

:: HDB

HDB object

-> Int64

the number of elements of the bucket array.

-> Int8

the size of record alignment by power of 2.

-> Int8

the maximum number of elements of the free block pool by power of 2.

-> [TuningOption]

tuning options.

-> IO Bool

if successful, the return value is True.

Optimize the file of a Hash database object.

vanish :: HDB -> IO BoolSource

Delete all records.

copy :: HDB -> String -> IO BoolSource

Copy the database file.

tranbegin :: HDB -> IO BoolSource

Begin the transaction.

trancommit :: HDB -> IO BoolSource

Commit the transaction.

tranabort :: HDB -> IO BoolSource

Abort the transaction.

path :: HDB -> IO (Maybe String)Source

Return the file path of currentry opened database.

rnum :: HDB -> IO Word64Source

Return the number of records in the database.

fsiz :: HDB -> IO Word64Source

Return the size of the database file.