tokyocabinet-haskell-0.0.5: Haskell binding of Tokyo Cabinet

Database.TokyoCabinet.TDB

Description

Interface to the table database. See also, http://tokyocabinet.sourceforge.net/spex-en.html#tctdbapi for details

Synopsis

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

data TDB 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 OpenMode Source

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 IndexType Source

Represents the index type

Constructors

ITLEXICAL

for lexical string

ITDECIMAL

for decimal string

ITOPT

the index is optimized

ITVOID

the index is removed

ITKEEP IndexType

if the index exists, setindex function merely returns failure

newtype AssocList k v Source

Constructors

AssocList 

Fields

unAssocList :: [(k, v)]
 

Instances

Associative AssocList 
(Eq k, Eq v) => Eq (AssocList k v) 
(Ord k, Ord v) => Ord (AssocList k v) 
(Show k, Show v) => Show (AssocList k v) 

new :: IO TDBSource

Create the new table database object.

delete :: TDB -> IO ()Source

Free object resource forcibly.

ecode :: TDB -> IO ECODESource

Get the last happened error code.

errmsg :: ECODE -> StringSource

Convert error code to message string.

tuneSource

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.

setcacheSource

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.

setxmsizSource

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.

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

Open the table database file

close :: TDB -> IO BoolSource

Open the database file

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.

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

Remove a record of a table database object.

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.

iterinit :: TDB -> IO BoolSource

Initialize the iterator of 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.

sync :: TDB -> IO BoolSource

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

optimizeSource

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.

vanish :: TDB -> IO BoolSource

Remove all records of a table database object.

copySource

Arguments

:: TDB

TDB object

-> String

new file path

-> IO Bool

if successful, the return value is True

Copy the database file of a table database object.

tranbegin :: TDB -> IO BoolSource

Begin the transaction of a table database object.

trancommit :: TDB -> IO BoolSource

Commit the transaction of a table database object.

tranabort :: TDB -> IO BoolSource

Abort the transaction of a table database object.

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

Get the file path of a table database object.

rnum :: TDB -> IO Word64Source

Get the number of records of a table database object.

fsiz :: TDB -> IO Word64Source

Get the size of the database file of a table database object.

setindex :: TDB -> String -> IndexType -> IO BoolSource

Set a column index to a table database object.

genuid :: TDB -> IO (Maybe Int64)Source

Generate a unique ID number of a table database object.