tokyocabinet-haskell-0.0.5: Haskell binding of Tokyo Cabinet

Database.TokyoCabinet.ADB

Description

Interface to TC's Abstract DataBase. See also, http://tokyocabinet.sourceforge.net/spex-en.html#tcadbapi for details

Synopsis

Documentation

Example

   import Control.Monad
   import Database.TokyoCabinet.ADB
   main = do adb <- new
             -- open the abstract database object
             -- "+" means that the database will be an on-memory tree database
             open adb "+" >>= err adb "open failed"
             -- store records
             puts adb [("foo", "hop"), ("bar", "step"), ("baz", "jump")] >>=
                      err adb "put failed" . (all id)
             -- retrieve records
             get_print adb "foo"
             -- traverse records
             iterinit adb
             iter adb >>= mapM_ (k -> putStr (k++":") >> get_print adb k)
             -- close the database
             close adb >>= err adb "close failed"
       where
         puts :: ADB -> [(String, String)] -> IO [Bool]
         puts adb = mapM (uncurry $ put adb)
         get_print :: ADB -> String -> IO ()
         get_print adb key = get adb key >>=
                             maybe (error "something goes wrong") putStrLn
         err :: ADB -> String -> Bool -> IO ()
         err adb msg = flip unless $ error msg
         iter :: ADB -> IO [String]
         iter adb = iternext adb >>=
                    maybe (return []) (x -> return . (x:) =<< iter adb)

data ADB Source

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

new :: IO ADBSource

Create a Abstract database object.

delete :: ADB -> IO ()Source

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

open :: ADB -> String -> IO BoolSource

Open an abstract dataabse.

close :: ADB -> IO BoolSource

Close an abstract database object.

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

Stora a record into an abstract database object.

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

Store a new record into an abstract database object.

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

Concatenate a value at the end of the existing record in an abstract database object.

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

Remove a record of an abstract database object.

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

Retrieve a record in an abstract database object.

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

Get the size of the value of a record in an abstract database object.

iterinit :: ADB -> IO BoolSource

Initialize the iterator of an abstract database object.

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

Get the next key of the iterator of an abstract database object.

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

Get forward matching keys in an abstract database object.

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

Add an integer to a record in an abstract database object.

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

Add a real number to a record in an abstract database object.

sync :: ADB -> IO BoolSource

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

optimize :: ADB -> String -> IO BoolSource

Optimize the storage of an abstract database object.

vanish :: ADB -> IO BoolSource

Remove all records of an abstract database object.

copy :: ADB -> String -> IO BoolSource

Copy the database file of an abstract database object.

tranbegin :: ADB -> IO BoolSource

Begin the transaction of an abstract database object.

trancommit :: ADB -> IO BoolSource

Commit the transaction of an abstract database object.

tranabort :: ADB -> IO BoolSource

Abort the transaction of an abstract database object.

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

Get the file path of an abstract database object.

rnum :: ADB -> IO Word64Source

Get the number of records of an abstract database object.

size :: ADB -> IO Word64Source

Get the size of the database of an abstract database object.

misc :: (Storable a, Storable b, Sequence q1, Sequence q2) => ADB -> String -> q1 a -> IO (q2 b)Source

Call a versatile function for miscellaneous operations of an abstract database object.