Database.TokyoCabinet.TDB
Description
Interface to the table database. See also, http://tokyocabinet.sourceforge.net/spex-en.html#tctdbapi for details
- data TDB
- data ECODE
- data OpenMode
- data TuningOption
- data IndexType
- newtype AssocList k v = AssocList {
- unAssocList :: [(k, v)]
- new :: IO TDB
- delete :: TDB -> IO ()
- ecode :: TDB -> IO ECODE
- errmsg :: ECODE -> String
- tune :: TDB -> Int64 -> Int8 -> Int8 -> [TuningOption] -> IO Bool
- setcache :: TDB -> Int32 -> Int32 -> Int32 -> IO Bool
- setxmsiz :: TDB -> Int64 -> IO Bool
- open :: TDB -> String -> [OpenMode] -> IO Bool
- close :: TDB -> IO Bool
- put :: (Storable k, Storable v, Associative m) => TDB -> v -> m k v -> IO Bool
- put' :: (Storable k, Storable v) => TDB -> k -> v -> IO Bool
- putkeep :: (Storable k, Storable v, Associative m) => TDB -> v -> m k v -> IO Bool
- putkeep' :: (Storable k, Storable v) => TDB -> k -> v -> IO Bool
- putcat :: (Storable k, Storable v, Associative m) => TDB -> v -> m k v -> IO Bool
- putcat' :: (Storable k, Storable v) => TDB -> k -> v -> IO Bool
- out :: Storable k => TDB -> k -> IO Bool
- get :: (Storable k, Storable v, Associative m) => TDB -> k -> IO (m k v)
- get' :: (Storable k, Storable v) => TDB -> k -> IO (Maybe v)
- vsiz :: Storable k => TDB -> k -> IO (Maybe Int)
- iterinit :: TDB -> IO Bool
- iternext :: Storable k => TDB -> IO (Maybe k)
- fwmkeys :: (Storable k1, Storable k2, Sequence q) => TDB -> k1 -> Int -> IO (q k2)
- addint :: Storable k => TDB -> k -> Int -> IO (Maybe Int)
- adddouble :: Storable k => TDB -> k -> Double -> IO (Maybe Double)
- sync :: TDB -> IO Bool
- optimize :: TDB -> Int64 -> Int8 -> Int8 -> [TuningOption] -> IO Bool
- vanish :: TDB -> IO Bool
- copy :: TDB -> String -> IO Bool
- tranbegin :: TDB -> IO Bool
- trancommit :: TDB -> IO Bool
- tranabort :: TDB -> IO Bool
- path :: TDB -> IO (Maybe String)
- rnum :: TDB -> IO Word64
- fsiz :: TDB -> IO Word64
- setindex :: TDB -> String -> IndexType -> IO Bool
- genuid :: TDB -> IO (Maybe Int64)
Documentation
Example
import Control.Monad (unless) import Database.TokyoCabinet.TDB import Database.TokyoCabinet.TDB.Query hiding (new) import qualified Database.TokyoCabinet.Map as M import qualified Database.TokyoCabinet.TDB.Query as Q (new)
data Profile = Profile { name :: String
, age :: Int } deriving Show
insertProfile :: TDB -> Profile -> IO Bool
insertProfile tdb profile =
do m <- M.new
M.put m "name" (name profile)
M.put m "age" (show . age $ profile)
Just pk <- genuid tdb
put tdb (show pk) m
main :: IO ()
main = do t <- new
open t "foo.tct" [OWRITER, OCREAT] >>= err t
mapM_ (insertProfile t) [ Profile "tom" 23
, Profile "bob" 24
, Profile "alice" 20 ]
q <- Q.new t
addcond q "age" QCNUMGE "23"
setorder q "name" QOSTRASC
proc q $ pk cols -> do
Just name <- M.get cols "name"
putStrLn name
M.put cols "name" (name ++ "!")
return (QPPUT cols)
close t >>= err t
return ()
where
err tdb = flip unless $ ecode tdb >>= error . show
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 |
Represents open mode
Constructors
| OREADER | read only mode |
| OWRITER | write mode |
| OCREAT | if this value is included in open mode list, `open function' creates a new database if not exist. |
| OTRUNC | creates a new database regardless if one exists |
| ONOLCK | open the database file without file locking |
| OLCKNB | open the database file with locking performed without blocking. |
| OTSYNC | every transaction synchronizes updated contents with the device |
data TuningOption Source
Instances
Represents the index type
Constructors
| AssocList | |
Fields
| |
Arguments
| :: TDB | TDB 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] | options |
| -> IO Bool | if successful, the return value is True. |
Set the tuning parameters.
Arguments
| :: TDB | TDB object |
| -> Int32 | the maximum number of records to be cached |
| -> Int32 | the maximum number of leaf nodes to be cached |
| -> Int32 | the maximum number of non-leaf nodes to be cached |
| -> IO Bool | if successful, the return value is True. |
Set the caching parameters of a table database object.
Arguments
| :: TDB | TDB object |
| -> Int64 | the size of the extra mapped memory |
| -> IO Bool | if successful, the return value is True. |
Set the size of the extra mapped memory of a table database object.
put :: (Storable k, Storable v, Associative m) => TDB -> v -> m k v -> IO BoolSource
Store a record into a table database object.
put' :: (Storable k, Storable v) => TDB -> k -> v -> IO BoolSource
Store a string record into a table database object with a zero separated column string.
putkeep :: (Storable k, Storable v, Associative m) => TDB -> v -> m k v -> IO BoolSource
Store a new record into a table database object.
putkeep' :: (Storable k, Storable v) => TDB -> k -> v -> IO BoolSource
Store a new string record into a table database object with a zero separated column string.
putcat :: (Storable k, Storable v, Associative m) => TDB -> v -> m k v -> IO BoolSource
Concatenate columns of the existing record in a table database object.
putcat' :: (Storable k, Storable v) => TDB -> k -> v -> IO BoolSource
Concatenate columns in a table database object with a zero separated column string.
get :: (Storable k, Storable v, Associative m) => TDB -> k -> IO (m k v)Source
Retrieve a record in a table database object.
get' :: (Storable k, Storable v) => TDB -> k -> IO (Maybe v)Source
Retrieve a record in a table database object as a zero separated column string.
vsiz :: Storable k => TDB -> k -> IO (Maybe Int)Source
Get the size of the value of a record in a table database object.
iternext :: Storable k => TDB -> IO (Maybe k)Source
Get the next primary key of the iterator of a table database object.
fwmkeys :: (Storable k1, Storable k2, Sequence q) => TDB -> k1 -> Int -> IO (q k2)Source
Get forward matching primary keys in a table database object.
addint :: Storable k => TDB -> k -> Int -> IO (Maybe Int)Source
Add an integer to a column of a record in a table database object.
adddouble :: Storable k => TDB -> k -> Double -> IO (Maybe Double)Source
Add a real number to a column of a record in a table database object.
Synchronize updated contents of a table database object with the file and the device.
Arguments
| :: TDB | TDB 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] | options |
| -> IO Bool | if successful, the return value is True. |
Optimize the file of a table database object.
Copy the database file of a table database object.
trancommit :: TDB -> IO BoolSource
Commit the transaction of a table database object.