tokyocabinet-haskell-0.0.5: Haskell binding of Tokyo Cabinet

Database.TokyoCabinet

Contents

Synopsis

Documentation

Basic Usage (sample code)

    import Database.TokyoCabinet
    import Data.ByteString.Char8
    putsample :: String -> [(ByteString, ByteString)] -> TCM Bool
    putsample file kv =
        do tc <- new :: TCM HDB -- alternatively you can use BDB or FDB
           open tc file [OWRITER, OCREAT]
           mapM (uncurry $ put tc) kv
           close tc
    getsample :: String -> ByteString -> TCM (Maybe ByteString)
    getsample file key =
        do tc <- new :: TCM HDB -- alternatively you can use BDB or FDB
           open tc file [OREADER]
           val <- get tc key
           close tc
           return val
    main = runTCM (do putsample "foo.tch" [(pack "foo", pack "bar")]
                      getsample "foo.tch" (pack "foo")) >>=
           maybe (return ()) (putStrLn . show)

data TCM a Source

Tokyo Cabinet related computation. Wrap of IO.

Instances

runTCM :: TCM a -> IO aSource

Unwrap TCM.

data OpenMode Source

Represent open mode for open function.

class TCDB a whereSource

Type class that abstract Tokyo Cabinet database.

Methods

new :: TCM aSource

Create a database object.

delete :: a -> TCM ()Source

Free object resource forcibly.

openSource

Arguments

:: a

database object

-> String

path to database file

-> [OpenMode]

open mode

-> TCM Bool

if successful, the return value is True

Open a database file.

close :: a -> TCM BoolSource

Close the database file. If successful, the return value is True

putSource

Arguments

:: (Storable k, Storable v) 
=> a

database object

-> k

key

-> v

value

-> TCM Bool

if successful, the return value is True

Store a record.

putkeepSource

Arguments

:: (Storable k, Storable v) 
=> a

database object

-> k

key

-> v

value

-> TCM Bool

if successful, the return value is True

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

putcatSource

Arguments

:: (Storable k, Storable v) 
=> a

database object

-> k

key

-> v

value

-> TCM Bool

if successful, the return value is True

Concatenate a value at the end of the existing record.

getSource

Arguments

:: (Storable k, Storable v) 
=> a

database object

-> k

key

-> TCM (Maybe v)

If successful, the return value is the value of the corresponding record wrapped by Just, else, Nothing is returned.

Retrieve a record.

outSource

Arguments

:: Storable k 
=> a

database object

-> k

key

-> TCM Bool

if successful, the return value is True

Remove a record.

vsizSource

Arguments

:: Storable k 
=> a

database object

-> k

key

-> TCM (Maybe Int)

If successful, the return value is the size of the value of the corresponding record wrapped by Just, else, it is Nothing.

Get the size of the value of a record.

iterinit :: a -> TCM BoolSource

Initialize the iterator. If successful, the return value is True.

iternext :: Storable v => a -> TCM (Maybe v)Source

Get the next key of the iterator. If successful, the return value is the next key wrapped by Just, else, it is Nothing.

fwmkeysSource

Arguments

:: (Storable k, Storable v, Sequence q) 
=> a

database object

-> k

search string

-> Int

the maximum number of keys to be fetched

-> TCM (q v)

result keys

Get forward matching keys.

addintSource

Arguments

:: Storable k 
=> a

database object

-> k

key

-> Int

the addtional value

-> TCM (Maybe Int)

If the corresponding record exists, the value is treated as an integer and is added to. If no record corresponds, a new record of the additional value is stored.

Add an integer to a record.

adddoubleSource

Arguments

:: Storable k 
=> a

database object

-> k

key

-> Double

the additional value

-> TCM (Maybe Double)

If the corresponding record exists, the value is treated as a real number and is added to. If no record corresponds, a new record of the additional value is stored.

Add a real number to a record.

sync :: a -> TCM BoolSource

Synchronize updated contents with the file and the device. If successful, the return value is True.

vanish :: a -> TCM BoolSource

Remove all records. If successful, the return value is True.

copySource

Arguments

:: a

database object

-> String

path of the destination file

-> TCM Bool

If successful, the return value is True.

Copy the database file.

path :: a -> TCM (Maybe String)Source

Get the path of the database file.

rnum :: a -> TCM Word64Source

Get the number of records.

size :: a -> TCM Word64Source

Get the size of the database file.

ecode :: a -> TCM ECODESource

Get the last happened error code.

defaultExtension :: a -> StringSource

Get the default extension for specified database object.

Instances

data HDB Source

Instances

data FDB Source

Instances

data TDB Source

Instances

data BDB Source

Instances

Error Code

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

errmsg :: ECODE -> StringSource

Convert error code to message string.