Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
PopKey
Description
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
Foldable (PopKey k) Source # | |
Defined in PopKey.Internal3 Methods fold :: Monoid m => PopKey k m -> m # foldMap :: Monoid m => (a -> m) -> PopKey k a -> 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 # | |
Functor (PopKey k) Source # | |
(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.
Constructors
StoreBlob | |
Fields
|
Instances
Bounded a => Bounded (StoreBlob a) Source # | |
Enum a => Enum (StoreBlob a) Source # | |
Defined in PopKey.Encoding Methods 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] # | |
Generic (StoreBlob a) Source # | |
Show a => Show (StoreBlob a) Source # | |
Eq a => Eq (StoreBlob a) Source # | |
Ord a => Ord (StoreBlob a) Source # | |
Defined in PopKey.Encoding | |
Store a => PopKeyEncoding (StoreBlob a) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (StoreBlob a) Methods 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
PopKeyEncoding Int16 Source # | |
Defined in PopKey.Encoding Associated Types type Shape Int16 Methods pkEncode :: Int16 -> F' (Shape Int16) ByteString pkDecode :: F' (Shape Int16) ByteString -> Int16 | |
PopKeyEncoding Int32 Source # | |
Defined in PopKey.Encoding Associated Types type Shape Int32 Methods pkEncode :: Int32 -> F' (Shape Int32) ByteString pkDecode :: F' (Shape Int32) ByteString -> Int32 | |
PopKeyEncoding Int64 Source # | |
Defined in PopKey.Encoding Associated Types type Shape Int64 Methods pkEncode :: Int64 -> F' (Shape Int64) ByteString pkDecode :: F' (Shape Int64) ByteString -> Int64 | |
PopKeyEncoding Int8 Source # | |
Defined in PopKey.Encoding Associated Types type Shape Int8 | |
PopKeyEncoding Rational Source # | |
Defined in PopKey.Encoding Associated Types type Shape Rational Methods pkEncode :: Rational -> F' (Shape Rational) ByteString pkDecode :: F' (Shape Rational) ByteString -> Rational | |
PopKeyEncoding Word16 Source # | |
Defined in PopKey.Encoding Associated Types type Shape Word16 Methods pkEncode :: Word16 -> F' (Shape Word16) ByteString pkDecode :: F' (Shape Word16) ByteString -> Word16 | |
PopKeyEncoding Word32 Source # | |
Defined in PopKey.Encoding Associated Types type Shape Word32 Methods pkEncode :: Word32 -> F' (Shape Word32) ByteString pkDecode :: F' (Shape Word32) ByteString -> Word32 | |
PopKeyEncoding Word64 Source # | |
Defined in PopKey.Encoding Associated Types type Shape Word64 Methods pkEncode :: Word64 -> F' (Shape Word64) ByteString pkDecode :: F' (Shape Word64) ByteString -> Word64 | |
PopKeyEncoding Word8 Source # | |
Defined in PopKey.Encoding Associated Types type Shape Word8 Methods pkEncode :: Word8 -> F' (Shape Word8) ByteString pkDecode :: F' (Shape Word8) ByteString -> Word8 | |
PopKeyEncoding ByteString Source # | |
Defined in PopKey.Encoding Associated Types type Shape ByteString Methods shape :: I (Shape ByteString) pkEncode :: ByteString -> F' (Shape ByteString) ByteString pkDecode :: F' (Shape ByteString) ByteString -> ByteString | |
PopKeyEncoding ByteString Source # | |
Defined in PopKey.Encoding Associated Types type Shape ByteString Methods shape :: I (Shape ByteString) pkEncode :: ByteString -> F' (Shape ByteString) ByteString0 pkDecode :: F' (Shape ByteString) ByteString0 -> ByteString | |
PopKeyEncoding Graph Source # | |
Defined in PopKey.Encoding Associated Types type Shape Graph Methods pkEncode :: Graph -> F' (Shape Graph) ByteString pkDecode :: F' (Shape Graph) ByteString -> Graph | |
PopKeyEncoding IntSet Source # | |
Defined in PopKey.Encoding Associated Types type Shape IntSet Methods pkEncode :: IntSet -> F' (Shape IntSet) ByteString pkDecode :: F' (Shape IntSet) ByteString -> IntSet | |
PopKeyEncoding Text Source # | |
Defined in PopKey.Encoding Associated Types type Shape Text | |
PopKeyEncoding Text Source # | |
Defined in PopKey.Encoding Associated Types type Shape Text | |
PopKeyEncoding Integer Source # | |
Defined in PopKey.Encoding Associated Types type Shape Integer Methods pkEncode :: Integer -> F' (Shape Integer) ByteString pkDecode :: F' (Shape Integer) ByteString -> Integer | |
PopKeyEncoding Natural Source # | |
Defined in PopKey.Encoding Associated Types type Shape Natural Methods pkEncode :: Natural -> F' (Shape Natural) ByteString pkDecode :: F' (Shape Natural) ByteString -> Natural | |
PopKeyEncoding () Source # | |
Defined in PopKey.Encoding Associated Types type Shape () Methods shape :: I (Shape ()) pkEncode :: () -> F' (Shape ()) ByteString pkDecode :: F' (Shape ()) ByteString -> () | |
PopKeyEncoding Bool Source # | |
Defined in PopKey.Encoding Associated Types type Shape Bool | |
PopKeyEncoding Char Source # | |
Defined in PopKey.Encoding Associated Types type Shape Char | |
PopKeyEncoding Double Source # | |
Defined in PopKey.Encoding Associated Types type Shape Double Methods pkEncode :: Double -> F' (Shape Double) ByteString pkDecode :: F' (Shape Double) ByteString -> Double | |
PopKeyEncoding Float Source # | |
Defined in PopKey.Encoding Associated Types type Shape Float Methods pkEncode :: Float -> F' (Shape Float) ByteString pkDecode :: F' (Shape Float) ByteString -> Float | |
PopKeyEncoding Int Source # | |
Defined in PopKey.Encoding Associated Types type Shape Int | |
PopKeyEncoding Word Source # | |
Defined in PopKey.Encoding Associated Types type Shape Word | |
PopKeyEncoding a => PopKeyEncoding (Identity a) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (Identity a) Methods shape :: I (Shape (Identity a)) pkEncode :: Identity a -> F' (Shape (Identity a)) ByteString pkDecode :: F' (Shape (Identity a)) ByteString -> Identity a | |
PopKeyEncoding a => PopKeyEncoding (First a) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (First a) Methods pkEncode :: First a -> F' (Shape (First a)) ByteString pkDecode :: F' (Shape (First a)) ByteString -> First a | |
PopKeyEncoding a => PopKeyEncoding (Last a) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (Last a) Methods pkEncode :: Last a -> F' (Shape (Last a)) ByteString pkDecode :: F' (Shape (Last a)) ByteString -> Last a | |
PopKeyEncoding a => PopKeyEncoding (Max a) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (Max a) Methods pkEncode :: Max a -> F' (Shape (Max a)) ByteString pkDecode :: F' (Shape (Max a)) ByteString -> Max a | |
PopKeyEncoding a => PopKeyEncoding (Min a) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (Min a) Methods pkEncode :: Min a -> F' (Shape (Min a)) ByteString pkDecode :: F' (Shape (Min a)) ByteString -> Min a | |
PopKeyEncoding a => PopKeyEncoding (Product a) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (Product a) Methods shape :: I (Shape (Product a)) pkEncode :: Product a -> F' (Shape (Product a)) ByteString pkDecode :: F' (Shape (Product a)) ByteString -> Product a | |
PopKeyEncoding a => PopKeyEncoding (Sum a) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (Sum a) Methods pkEncode :: Sum a -> F' (Shape (Sum a)) ByteString pkDecode :: F' (Shape (Sum a)) ByteString -> Sum a | |
Store a => PopKeyEncoding (Ratio a) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (Ratio a) Methods pkEncode :: Ratio a -> F' (Shape (Ratio a)) ByteString pkDecode :: F' (Shape (Ratio a)) ByteString -> Ratio a | |
Store a => PopKeyEncoding (IntMap a) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (IntMap a) Methods pkEncode :: IntMap a -> F' (Shape (IntMap a)) ByteString pkDecode :: F' (Shape (IntMap a)) ByteString -> IntMap a | |
Store a => PopKeyEncoding (Seq a) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (Seq a) Methods pkEncode :: Seq a -> F' (Shape (Seq a)) ByteString pkDecode :: F' (Shape (Seq a)) ByteString -> Seq a | |
(Ord a, Store a) => PopKeyEncoding (Set a) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (Set a) Methods pkEncode :: Set a -> F' (Shape (Set a)) ByteString pkDecode :: F' (Shape (Set a)) ByteString -> Set a | |
Store a => PopKeyEncoding (StoreBlob a) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (StoreBlob a) Methods shape :: I (Shape (StoreBlob a)) pkEncode :: StoreBlob a -> F' (Shape (StoreBlob a)) ByteString pkDecode :: F' (Shape (StoreBlob a)) ByteString -> StoreBlob a | |
PopKeyEncoding a => PopKeyEncoding (Maybe a) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (Maybe a) Methods pkEncode :: Maybe a -> F' (Shape (Maybe a)) ByteString pkDecode :: F' (Shape (Maybe a)) ByteString -> Maybe a | |
Store a => PopKeyEncoding [a] Source # | |
Defined in PopKey.Encoding Associated Types type Shape [a] Methods shape :: I (Shape [a]) pkEncode :: [a] -> F' (Shape [a]) ByteString pkDecode :: F' (Shape [a]) ByteString -> [a] | |
(PopKeyEncoding a, PopKeyEncoding b) => PopKeyEncoding (Either a b) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (Either a b) Methods shape :: I (Shape (Either a b)) pkEncode :: Either a b -> F' (Shape (Either a b)) ByteString pkDecode :: F' (Shape (Either a b)) ByteString -> Either a b | |
PopKeyEncoding (Proxy a) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (Proxy a) Methods pkEncode :: Proxy a -> F' (Shape (Proxy a)) ByteString pkDecode :: F' (Shape (Proxy a)) ByteString -> Proxy a | |
(PopKeyEncoding a, PopKeyEncoding b) => PopKeyEncoding (Arg a b) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (Arg a b) Methods pkEncode :: Arg a b -> F' (Shape (Arg a b)) ByteString pkDecode :: F' (Shape (Arg a b)) ByteString -> Arg a b | |
(Ord a, Store a, Store b) => PopKeyEncoding (Map a b) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (Map a b) Methods pkEncode :: Map a b -> F' (Shape (Map a b)) ByteString pkDecode :: F' (Shape (Map a b)) ByteString -> Map a b | |
(PopKeyEncoding a, PopKeyEncoding b) => PopKeyEncoding (a, b) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (a, b) Methods shape :: I (Shape (a, b)) pkEncode :: (a, b) -> F' (Shape (a, b)) ByteString pkDecode :: F' (Shape (a, b)) ByteString -> (a, b) | |
PopKeyEncoding a => PopKeyEncoding (Const a b) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (Const a b) Methods shape :: I (Shape (Const a b)) pkEncode :: Const a b -> F' (Shape (Const a b)) ByteString pkDecode :: F' (Shape (Const a b)) ByteString -> Const a b | |
(PopKeyEncoding a, PopKeyEncoding b, PopKeyEncoding c) => PopKeyEncoding (a, b, c) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (a, b, c) Methods shape :: I (Shape (a, b, c)) pkEncode :: (a, b, c) -> F' (Shape (a, b, c)) ByteString pkDecode :: F' (Shape (a, b, c)) ByteString -> (a, b, c) | |
(PopKeyEncoding a, PopKeyEncoding b, PopKeyEncoding c, PopKeyEncoding d) => PopKeyEncoding (a, b, c, d) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (a, b, c, d) Methods shape :: I (Shape (a, b, c, d)) pkEncode :: (a, b, c, d) -> F' (Shape (a, b, c, d)) ByteString pkDecode :: F' (Shape (a, b, c, d)) ByteString -> (a, b, c, d) | |
(PopKeyEncoding a, PopKeyEncoding b, PopKeyEncoding c, PopKeyEncoding d, PopKeyEncoding e) => PopKeyEncoding (a, b, c, d, e) Source # | |
Defined in PopKey.Encoding Associated Types type Shape (a, b, c, d, e) Methods shape :: I (Shape (a, b, c, d, e)) pkEncode :: (a, b, c, d, e) -> F' (Shape (a, b, c, d, e)) ByteString pkDecode :: F' (Shape (a, b, c, d, e)) ByteString -> (a, b, c, d, e) |
data PopKeyStore k v Source #
Instances
StorePopKey k v (PopKeyStore k v) Source # | |
Defined in PopKey.Internal3 Associated Types type Input (PopKeyStore k v) Source # Methods 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 Associated Types type Input (PopKeyStore' v) Source # Methods 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 #
Methods
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 Associated Types type Input (PopKeyStore' v) Source # Methods 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 Associated Types type Input (PopKeyStore k v) Source # Methods storePopKey :: Foldable t => PopKeyStore k v -> t (Input (PopKeyStore k v)) -> IO () Source # loadPopKey :: PopKeyStore k v -> IO (PopKey k v) Source # |