Safe Haskell | None |
---|---|
Language | Haskell2010 |
PopKey gives you a static key-value storage structure backed by poppy indices. Construction is slow (multiple passes are made over the data to choose a good indexing structure), but querying should be fast, and space overhead should be much lower than Data.Map—on the data set I'm working with, Data.Map has 8.3x more overhead than PopKey—and the raw data transparently lives in an mmap'd region if you use storage
, meaning the actual memory needed for usage is very low.
To construct, you will need PopKeyEncoding
instances. You may choose the granularity by which you encode your data types by choosing one of two auto-deriving patterns. The first, implicitly derived via GHC Generics, will use a granular encoding, indexing fields separately internally, while the second, derived via the StoreBlob
newtype, will encode the data as a single unit. Which is better depends on the situation, but as a general rule you should pack your constant-size structures into a single blob while letting your variable-sized fields use the granular encoding.
-- EncodeMyType
with separate indices for the[ String ]
andString
fields. data MyType = MyType [ String ] String deriving (Generic,PopKeyEncoding)
-- EncodePoint
as a blob, with all 3Int
fields stored contiguously. data Point = Point Int Int Int deriving (Generic,Store) --Store
here is from Data.Store deriving PopKeyEncoding via StoreBlob Point
Reading from and storing to disk come pre-packaged, in such a way that loading your structure from the disk will strictly load the small index metadata while leaving the large raw data to be backed by mmap. You may use this functionality as follows:
myData :: PopKeyStore Point MyType myData = storage "myindex.poppy" main :: IO () main = do -- your data let dat :: [ (Point , MyType) ] = ... -- store the indexed data to disk storePopKey myData dat -- load the indexed data from disk pk :: PopKey Point MyType <- loadPopKey myData ...
Poppy natively supports array-style indexing, so if your "key" set is simply the dense set of integers [ 0 .. n - 1 ]
where n
is the number of items in your data set, key storage may be left implicit and elided entirely. In this API, when the distinction is necessary, working with such an implicit index is signified by a trailing ', e.g., storage
vs storage'
.
Note that constant-factor space & time overhead is fairly high, so unless you have at least a couple thousand items, it is recommended to avoid PopKey. Once you have 10k+ items, the asymptotics should win out, and PopKey should perform well.
Synopsis
- data PopKey k v
- (!) :: PopKeyEncoding k => PopKey k v -> k -> v
- lookup :: PopKeyEncoding k => PopKey k v -> k -> Maybe v
- makePopKey :: forall f k v. (Foldable f, PopKeyEncoding k, PopKeyEncoding v) => f (k, v) -> PopKey k v
- makePopKey' :: forall f v. (Foldable f, PopKeyEncoding v) => f v -> PopKey Int v
- foldrWithKey :: PopKeyEncoding k => (k -> v -> b -> b) -> b -> PopKey k v -> b
- foldlWithKey' :: PopKeyEncoding k => (a -> k -> v -> a) -> a -> PopKey k v -> a
- storage :: (PopKeyEncoding k, PopKeyEncoding v) => FilePath -> PopKeyStore k v
- storage' :: PopKeyEncoding v => FilePath -> PopKeyStore' v
- newtype StoreBlob a = StoreBlob {
- unStoreBlob :: a
- class PopKeyEncoding a
- data PopKeyStore k v
- data PopKeyStore' v
- class StorePopKey k v f | f -> k, f -> v where
- type Input f
- storePopKey :: Foldable t => f -> t (Input f) -> IO ()
- loadPopKey :: f -> IO (PopKey k v)
Documentation
Instances
Functor (PopKey k) Source # | |
Foldable (PopKey k) Source # | |
Defined in PopKey.Internal3 fold :: Monoid m => PopKey k m -> m # foldMap :: Monoid m => (a -> m) -> PopKey k a -> m # foldr :: (a -> b -> b) -> b -> PopKey k a -> b # foldr' :: (a -> b -> b) -> b -> PopKey k a -> b # foldl :: (b -> a -> b) -> b -> PopKey k a -> b # foldl' :: (b -> a -> b) -> b -> PopKey k a -> b # foldr1 :: (a -> a -> a) -> PopKey k a -> a # foldl1 :: (a -> a -> a) -> PopKey k a -> a # elem :: Eq a => a -> PopKey k a -> Bool # maximum :: Ord a => PopKey k a -> a # minimum :: Ord a => PopKey k a -> a # | |
(PopKeyEncoding k, PopKeyEncoding v) => Store (PopKey k v) Source # | |
(!) :: PopKeyEncoding k => PopKey k v -> k -> v Source #
Lookup by a key known to be in the structure.
lookup :: PopKeyEncoding k => PopKey k v -> k -> Maybe v Source #
Lookup by a key which may or may not be in the structure.
makePopKey :: forall f k v. (Foldable f, PopKeyEncoding k, PopKeyEncoding v) => f (k, v) -> PopKey k v Source #
Create a poppy-backed key-value storage structure.
makePopKey' :: forall f v. (Foldable f, PopKeyEncoding v) => f v -> PopKey Int v Source #
Create a poppy-backed structure with elements implicitly indexed by their position.
foldrWithKey :: PopKeyEncoding k => (k -> v -> b -> b) -> b -> PopKey k v -> b Source #
foldlWithKey' :: PopKeyEncoding k => (a -> k -> v -> a) -> a -> PopKey k v -> a Source #
storage :: (PopKeyEncoding k, PopKeyEncoding v) => FilePath -> PopKeyStore k v Source #
You may use storage
to gain a pair of operations to serialize and read your structure from disk. This will be more efficient than if you naively serialize and store the data, as it strictly reads index metadata into memory while leaving the larger raw chunks to be backed by mmap.
storage' :: PopKeyEncoding v => FilePath -> PopKeyStore' v Source #
Like storage
, but for canonical integer keys.
A simple wrapper to declare you do not want this data to be granularly partitioned by poppy.
StoreBlob | |
|
Instances
Bounded a => Bounded (StoreBlob a) Source # | |
Enum a => Enum (StoreBlob a) Source # | |
Defined in PopKey.Encoding succ :: StoreBlob a -> StoreBlob a # pred :: StoreBlob a -> StoreBlob a # toEnum :: Int -> StoreBlob a # fromEnum :: StoreBlob a -> Int # enumFrom :: StoreBlob a -> [StoreBlob a] # enumFromThen :: StoreBlob a -> StoreBlob a -> [StoreBlob a] # enumFromTo :: StoreBlob a -> StoreBlob a -> [StoreBlob a] # enumFromThenTo :: StoreBlob a -> StoreBlob a -> StoreBlob a -> [StoreBlob a] # | |
Eq a => Eq (StoreBlob a) Source # | |
Ord a => Ord (StoreBlob a) Source # | |
Defined in PopKey.Encoding | |
Show a => Show (StoreBlob a) Source # | |
Generic (StoreBlob a) Source # | |
Store a => PopKeyEncoding (StoreBlob a) Source # | |
Defined in PopKey.Encoding shape :: I (Shape (StoreBlob a)) pkEncode :: StoreBlob a -> F' (Shape (StoreBlob a)) ByteString pkDecode :: F' (Shape (StoreBlob a)) ByteString -> StoreBlob a | |
type Rep (StoreBlob a) Source # | |
Defined in PopKey.Encoding |
class PopKeyEncoding a Source #
Inverse law: pkDecode . pkEncode = id
. Note that this encoding is explicitly for use with poppy - use your discretion (or better, test!) to decide the granularity with which you wish to use this encoding as opposed to the standard store encoding. Relying more on PopKeyEncoding will probably use less space, but at the cost of storing items in less contiguous memory.
Instances
data PopKeyStore k v Source #
Instances
StorePopKey k v (PopKeyStore k v) Source # | |
Defined in PopKey.Internal3 type Input (PopKeyStore k v) :: Type Source # storePopKey :: Foldable t => PopKeyStore k v -> t (Input (PopKeyStore k v)) -> IO () Source # loadPopKey :: PopKeyStore k v -> IO (PopKey k v) Source # | |
type Input (PopKeyStore k v) Source # | |
Defined in PopKey.Internal3 |
data PopKeyStore' v Source #
Instances
StorePopKey Int v (PopKeyStore' v) Source # | |
Defined in PopKey.Internal3 type Input (PopKeyStore' v) :: Type Source # storePopKey :: Foldable t => PopKeyStore' v -> t (Input (PopKeyStore' v)) -> IO () Source # loadPopKey :: PopKeyStore' v -> IO (PopKey Int v) Source # | |
type Input (PopKeyStore' v) Source # | |
Defined in PopKey.Internal3 |
class StorePopKey k v f | f -> k, f -> v where Source #
storePopKey :: Foldable t => f -> t (Input f) -> IO () Source #
loadPopKey :: f -> IO (PopKey k v) Source #
Instances
StorePopKey Int v (PopKeyStore' v) Source # | |
Defined in PopKey.Internal3 type Input (PopKeyStore' v) :: Type Source # storePopKey :: Foldable t => PopKeyStore' v -> t (Input (PopKeyStore' v)) -> IO () Source # loadPopKey :: PopKeyStore' v -> IO (PopKey Int v) Source # | |
StorePopKey k v (PopKeyStore k v) Source # | |
Defined in PopKey.Internal3 type Input (PopKeyStore k v) :: Type Source # storePopKey :: Foldable t => PopKeyStore k v -> t (Input (PopKeyStore k v)) -> IO () Source # loadPopKey :: PopKeyStore k v -> IO (PopKey k v) Source # |