Copyright | (c) Adam Smith 2012 |
---|---|
License | BSD-style |
Safe Haskell | Safe-Inferred |
Language | Haskell98 |
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 ByteString
s, 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 String
s 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
- data CDB
- class Packable k
- class Unpackable v
- pack :: Packable k => k -> ByteString
- unpack :: Unpackable v => ByteString -> v
- cdbInit :: FilePath -> IO CDB
- cdbGet :: (Packable k, Unpackable v) => CDB -> k -> Maybe v
- cdbGetAll :: (Packable k, Unpackable v) => CDB -> k -> [v]
- cdbHasKey :: Packable k => CDB -> k -> Bool
- cdbCount :: Packable k => CDB -> k -> Int
- cdbMake :: FilePath -> CDBMake -> IO ()
- cdbAdd :: (Packable k, Packable v) => k -> v -> CDBMake
- cdbAddMany :: (Packable k, Packable v) => [(k, v)] -> CDBMake
The CDB
type
Classes
An instance of Packable
can be losslessly transformed into a ByteString
.
Instances
Packable Word32 Source # | |
Defined in Database.CDB.Packable pack :: Word32 -> ByteString Source # | |
Packable ByteString Source # | |
Defined in Database.CDB.Packable pack :: ByteString -> ByteString Source # | |
Packable [Word8] Source # | |
Defined in Database.CDB.Packable pack :: [Word8] -> ByteString Source # | |
Packable [Char] Source # | |
Defined in Database.CDB.Packable pack :: [Char] -> ByteString Source # | |
Packable (UArray Word32 Word32) Source # | |
Defined in Database.CDB.Packable |
class Unpackable v Source #
An instance of Unpackable
can be losslessly transformed from a ByteString
.
Instances
Unpackable ByteString Source # | |
Defined in Database.CDB.Packable unpack :: ByteString -> ByteString Source # | |
Unpackable [Word8] Source # | |
Defined in Database.CDB.Packable unpack :: ByteString -> [Word8] Source # | |
Unpackable [Char] Source # | |
Defined in Database.CDB.Packable unpack :: ByteString -> [Char] Source # |
pack :: Packable k => k -> ByteString Source #
unpack :: Unpackable v => ByteString -> v Source #
Reading interface
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.