tokyocabinet-haskell-0.0.5: Haskell binding of Tokyo Cabinet

Database.TokyoCabinet.FDB

Contents

Description

Interface to Fixed-length DBM. See also, http://tokyocabinet.sourceforge.net/spex-en.html#tcfdbapi for details

Synopsis

Documentation

Example

    import Control.Monad
    import Database.TokyoCabinet.FDB
  
    main = do fdb <- new
              -- open the database
              open fdb "casket.tcf" [OWRITER, OCREAT] >>= err fdb
              -- store records
              puts fdb [(1, "one"), (12, "twelve"), (144, "one forty four")] >>=
                        err fdb . (all id)
              -- retrieve records
              get fdb (1 :: Int) >>= maybe (error "something goes wrong") putStrLn
              -- close the database
              close fdb >>= err fdb
        where
          puts :: FDB -> [(Int, String)] -> IO [Bool]
          puts fdb = mapM (uncurry $ put fdb)
  
          err :: FDB -> Bool -> IO ()
          err fdb = flip unless $ ecode fdb >>= error . show

data FDB 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

data ID Source

Constructors

IDMIN 
IDPREV 
IDMAX 
IDNEXT 
ID Int64 

Instances

Basic API (tokyocabinet.idl compliant)

new :: IO FDBSource

Create a Fixed-length database object.

delete :: FDB -> IO ()Source

Free FDB resource forcibly. FDB 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 FDB object. Its behavior is undefined.

ecode :: FDB -> IO ECODESource

Return the last happened error code.

errmsg :: ECODE -> StringSource

Convert error code to message string.

tuneSource

Arguments

:: FDB

FDB object.

-> Int32

the width of the value of each record.

-> Int64

the limit size of the database file.

-> IO Bool

if successful, the return value is True.

Set the tuning parameters.

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

Open FDB database file.

close :: FDB -> IO BoolSource

Close the database file.

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

Stora a record (key-value pair) on FDB. Key type must be instance of Key class. Value type must be instance of Storable.

putkeep :: (Key k, Storable v) => FDB -> 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 :: (Key k, Storable v) => FDB -> k -> v -> IO BoolSource

Concatenate a value at the end of the existing record.

out :: Key k => FDB -> k -> IO BoolSource

Delete a record.

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

Return the value of record.

vsiz :: Key k => FDB -> k -> IO (Maybe Int)Source

Return the byte size of value in a record.

iterinit :: FDB -> IO BoolSource

Initialize the iterator of a FDB object.

iternext :: Key k => FDB -> IO (Maybe k)Source

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

rangeSource

Arguments

:: (Key k1, Key k2) 
=> FDB

FDB object

-> k1

the lower limit of the range.

-> k1

the upper limit of the range.

-> Int

the maximum number of keys to be fetched.

-> IO [k2]

keys in the specified range.

Return list of keys in the specified range.

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

Return list of forward matched keys.

addint :: Key k => FDB -> k -> Int -> IO (Maybe Int)Source

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

adddouble :: Key k => FDB -> k -> Double -> IO (Maybe Double)Source

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

sync :: FDB -> IO BoolSource

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

optimize :: FDB -> Int32 -> Int64 -> IO BoolSource

Optimize the file of a Hash database object.

vanish :: FDB -> IO BoolSource

Delete all records.

copy :: FDB -> String -> IO BoolSource

Copy the database file.

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

Return the file path of currentry opened database.

rnum :: FDB -> IO Word64Source

Return the number of records in the database.

fsiz :: FDB -> IO Word64Source

Return the size of the database file.