Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- createDB :: forall indexes a. Serialize a => InsertIndex indexes a => ByteString -> Int -> Maybe (Int -> Int -> IO ()) -> Indexes indexes a -> IO (Either String (DB indexes a))
- readDB :: forall indexes a. Serialize a => InsertIndex indexes a => FilePath -> Maybe (Int -> Int -> IO ()) -> Indexes indexes a -> IO (Either String (DB indexes a))
- data Name (a :: Symbol)
- data Indexes (indexes :: [(Symbol, *)]) a
- unindexed :: Indexes '[] a
- byteStringIndex :: KnownSymbol s => Name s -> (a -> b) -> (b -> ByteString) -> Indexes indexes a -> Indexes ('(s, ByteStringIndex b) ': indexes) a
- word32Index :: KnownSymbol s => Name s -> (a -> b) -> (b -> Word32) -> Indexes indexes a -> Indexes ('(s, Word32Index b) ': indexes) a
Construction / reading
:: Serialize a | |
=> InsertIndex indexes a | |
=> ByteString | Serialised elements |
-> Int | Element count |
-> Maybe (Int -> Int -> IO ()) | Progress indicating function, called with the number of elements currently read and the total count of elements |
-> Indexes indexes a |
|
-> IO (Either String (DB indexes a)) | Resulting database or a parse/deserializiation error |
Create a database from a ByteString
and build up
in-memory indexes according to the Indexes
description.
:: Serialize a | |
=> InsertIndex indexes a | |
=> FilePath | File path to database |
-> Maybe (Int -> Int -> IO ()) | Progress indicating function, called with the number of elements currently read and the total count of elements |
-> Indexes indexes a |
|
-> IO (Either String (DB indexes a)) | Resulting database or a parse/deserializiation error |
Read a database from a file path and build up in-memory indexes
according to the Indexes
description.
Indexes
data Indexes (indexes :: [(Symbol, *)]) a Source #
Indexes
description. Currently, there are two supported index types:
Word32
and ByteString
. Both can be specified using the
utility functions word32Index
and byteStringIndex
, respectively.
For example, one might define indexes over a datatype in the following way:
data Person = Person { name ::String
, age ::Int
} deriving (Generic,Serialize
) personIndexes =byteStringIndex
#nameIndex (pack
. name) $word32Index
#ageIndex (fromIntegral
. age)unindexed
Composite or computed indexes can be built by supplying an appropriate
function to byteStringIndex
or
word32Index
, e.g:
personIndexes =byteStringIndex
#nameAndAgePlusOneIndex (\p ->pack
(name p<>
show
(age p + 1)))unindexed
:: KnownSymbol s | |
=> Name s | Index name |
-> (a -> b) | Projecting function |
-> (b -> ByteString) | Index computing function |
-> Indexes indexes a |
|
-> Indexes ('(s, ByteStringIndex b) ': indexes) a | Resulting |
Add a ByteString
index to an Indexes
description to be built when
reading a database.
:: KnownSymbol s | |
=> Name s | Index name |
-> (a -> b) | Projecting function |
-> (b -> Word32) | Index computing function |
-> Indexes indexes a |
|
-> Indexes ('(s, Word32Index b) ': indexes) a | Resulting |