hs-cdb-0.1.2: A library for reading CDB (Constant Database) files.
Copyright(c) Adam Smith 2012
LicenseBSD-style
Safe HaskellSafe-Inferred
LanguageHaskell98

Database.CDB

Description

A library for reading and writing CDB (Constant Database) files.

CDB files are immutable key-value stores, designed for extremely fast and memory-efficient construction and lookup. They can be as large as 4GB, and at no point in their construction or use must all data be loaded into memory. CDB files can contain multiple values for a given key.

For more information on the CDB file format, please see: http://cr.yp.to/cdb.html

Using hs-cdb should be fairly straightforward. Here's a simple example:

   printStuff :: IO ()
   printStuff = do
     cdb <- cdbInit "my.cdb"
     let foo = cdbGet cdb "foo"
     let bars = cdbGetAll cdb "bar"
     maybe (putStrLn "Not found") putStrLn foo
     mapM_ putStrLn bars

The CDB will be automatically cleaned up by the garbage collector after use.

The only sticking point may be the use of the Packable and Unpackable classes. This allows the hs-cdb interface to be both generic (so your CDB can store effectively any kind of data) but also convenient in the common case of plaintext data. Internally, hs-cdb uses ByteStrings, but it will automatically pack and unpack keys and values to suit the types you're using in your program. In particular, in an instance is provided for String, so hs-cdb can use Strings as keys and values transparently.

Writing a CDB is just as straightforward:

   makeCDB :: IO ()
   makeCDB = cdbMake "my.cdb" $ do
     cdbAdd "foo" "this is the data associated with foo"
     cdbAddMany [("bar1", "bar1data"), ("bar2", "bar2data")]

Again, hs-cdb automatically closes the files after use. Moreover, in CDB tradition, hs-cdb actually creates a CDB named file.cdb by first writing it to file.cdb.tmp, and then atomically renaming it over file.cdb. This means that readers never need to pause when you're regenerating a CDB.

Note that the CDBMake monad is nothing more than a State wrapper around the IO monad, so you can use IO commands with liftIO from Control.Monad.State.

Synopsis

The CDB type

data CDB Source #

Internal representation of a CDB file on disk.

Classes

class Packable k Source #

An instance of Packable can be losslessly transformed into a ByteString.

Minimal complete definition

pack

Instances

Instances details
Packable Word32 Source # 
Instance details

Defined in Database.CDB.Packable

Packable ByteString Source # 
Instance details

Defined in Database.CDB.Packable

Packable [Word8] Source # 
Instance details

Defined in Database.CDB.Packable

Methods

pack :: [Word8] -> ByteString Source #

Packable [Char] Source # 
Instance details

Defined in Database.CDB.Packable

Methods

pack :: [Char] -> ByteString Source #

Packable (UArray Word32 Word32) Source # 
Instance details

Defined in Database.CDB.Packable

class Unpackable v Source #

An instance of Unpackable can be losslessly transformed from a ByteString.

Minimal complete definition

unpack

Instances

Instances details
Unpackable ByteString Source # 
Instance details

Defined in Database.CDB.Packable

Unpackable [Word8] Source # 
Instance details

Defined in Database.CDB.Packable

Methods

unpack :: ByteString -> [Word8] Source #

Unpackable [Char] Source # 
Instance details

Defined in Database.CDB.Packable

Methods

unpack :: ByteString -> [Char] Source #

Reading interface

cdbInit :: FilePath -> IO CDB Source #

Loads a CDB from a file.

cdbGet :: (Packable k, Unpackable v) => CDB -> k -> Maybe v Source #

Finds the first entry associated with a key in a CDB.

cdbGetAll :: (Packable k, Unpackable v) => CDB -> k -> [v] Source #

Finds all entries associated with a key in a CDB.

cdbHasKey :: Packable k => CDB -> k -> Bool Source #

Returns True if the CDB has a value associated with the given key.

cdbCount :: Packable k => CDB -> k -> Int Source #

Returns the number of values a CDB has for a given key.

Writing interface

cdbMake :: FilePath -> CDBMake -> IO () Source #

Construct a CDB as described inside the supplied CDBMake computation. During construction, it will be written to a temporary file and then moved over top of the given file atomically.

cdbAdd :: (Packable k, Packable v) => k -> v -> CDBMake Source #

Adds a given key-value pair to the CDB being built.

cdbAddMany :: (Packable k, Packable v) => [(k, v)] -> CDBMake Source #

Add a list of key-value pairs to the CDB being built.