popkey-0.0.0.1: Static key-value storage backed by poppy

Safe HaskellNone
LanguageHaskell2010

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.

-- Encode MyType with separate indices for the [ String ] and String fields.
data MyType = MyType [ String ] String
  deriving (Generic,PopKeyEncoding)
-- Encode Point as a blob, with all 3 Int 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'.

Synopsis

Documentation

data PopKey k v Source #

Instances
Profunctor PopKey Source # 
Instance details

Defined in PopKey.Internal3

Methods

dimap :: (a -> b) -> (c -> d) -> PopKey b c -> PopKey a d #

lmap :: (a -> b) -> PopKey b c -> PopKey a c #

rmap :: (b -> c) -> PopKey a b -> PopKey a c #

(#.) :: Coercible c b => q b c -> PopKey a b -> PopKey a c #

(.#) :: Coercible b a => PopKey b c -> q a b -> PopKey a c #

Functor (PopKey k) Source # 
Instance details

Defined in PopKey.Internal3

Methods

fmap :: (a -> b) -> PopKey k a -> PopKey k b #

(<$) :: a -> PopKey k b -> PopKey k a #

Foldable (PopKey k) Source # 
Instance details

Defined in PopKey.Internal3

Methods

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 #

toList :: PopKey k a -> [a] #

null :: PopKey k a -> Bool #

length :: PopKey k a -> Int #

elem :: Eq a => a -> PopKey k a -> Bool #

maximum :: Ord a => PopKey k a -> a #

minimum :: Ord a => PopKey k a -> a #

sum :: Num a => PopKey k a -> a #

product :: Num a => PopKey k a -> a #

(!) :: PopKey k v -> k -> v Source #

Lookup by a key known to be in the structure.

lookup :: 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.

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.

newtype StoreBlob a Source #

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 # 
Instance details

Defined in PopKey.Encoding

Enum a => Enum (StoreBlob a) Source # 
Instance details

Defined in PopKey.Encoding

Eq a => Eq (StoreBlob a) Source # 
Instance details

Defined in PopKey.Encoding

Methods

(==) :: StoreBlob a -> StoreBlob a -> Bool #

(/=) :: StoreBlob a -> StoreBlob a -> Bool #

Ord a => Ord (StoreBlob a) Source # 
Instance details

Defined in PopKey.Encoding

Show a => Show (StoreBlob a) Source # 
Instance details

Defined in PopKey.Encoding

Generic (StoreBlob a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Rep (StoreBlob a) :: Type -> Type #

Methods

from :: StoreBlob a -> Rep (StoreBlob a) x #

to :: Rep (StoreBlob a) x -> StoreBlob a #

Store a => PopKeyEncoding (StoreBlob a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (StoreBlob a) :: Type

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 # 
Instance details

Defined in PopKey.Encoding

type Rep (StoreBlob a) = D1 (MetaData "StoreBlob" "PopKey.Encoding" "popkey-0.0.0.1-2JEz5nMdRL1HGfwtz8cXTw" True) (C1 (MetaCons "StoreBlob" PrefixI True) (S1 (MetaSel (Just "unStoreBlob") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

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 Bool Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Bool :: Type

Methods

shape :: I (Shape Bool)

pkEncode :: Bool -> F' (Shape Bool) ByteString

pkDecode :: F' (Shape Bool) ByteString -> Bool

PopKeyEncoding Char Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Char :: Type

Methods

shape :: I (Shape Char)

pkEncode :: Char -> F' (Shape Char) ByteString

pkDecode :: F' (Shape Char) ByteString -> Char

PopKeyEncoding Double Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Double :: Type

Methods

shape :: I (Shape Double)

pkEncode :: Double -> F' (Shape Double) ByteString

pkDecode :: F' (Shape Double) ByteString -> Double

PopKeyEncoding Float Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Float :: Type

Methods

shape :: I (Shape Float)

pkEncode :: Float -> F' (Shape Float) ByteString

pkDecode :: F' (Shape Float) ByteString -> Float

PopKeyEncoding Int Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Int :: Type

Methods

shape :: I (Shape Int)

pkEncode :: Int -> F' (Shape Int) ByteString

pkDecode :: F' (Shape Int) ByteString -> Int

PopKeyEncoding Int8 Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Int8 :: Type

Methods

shape :: I (Shape Int8)

pkEncode :: Int8 -> F' (Shape Int8) ByteString

pkDecode :: F' (Shape Int8) ByteString -> Int8

PopKeyEncoding Int16 Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Int16 :: Type

Methods

shape :: I (Shape Int16)

pkEncode :: Int16 -> F' (Shape Int16) ByteString

pkDecode :: F' (Shape Int16) ByteString -> Int16

PopKeyEncoding Int32 Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Int32 :: Type

Methods

shape :: I (Shape Int32)

pkEncode :: Int32 -> F' (Shape Int32) ByteString

pkDecode :: F' (Shape Int32) ByteString -> Int32

PopKeyEncoding Int64 Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Int64 :: Type

Methods

shape :: I (Shape Int64)

pkEncode :: Int64 -> F' (Shape Int64) ByteString

pkDecode :: F' (Shape Int64) ByteString -> Int64

PopKeyEncoding Integer Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Integer :: Type

Methods

shape :: I (Shape Integer)

pkEncode :: Integer -> F' (Shape Integer) ByteString

pkDecode :: F' (Shape Integer) ByteString -> Integer

PopKeyEncoding Natural Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Natural :: Type

Methods

shape :: I (Shape Natural)

pkEncode :: Natural -> F' (Shape Natural) ByteString

pkDecode :: F' (Shape Natural) ByteString -> Natural

PopKeyEncoding Rational Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Rational :: Type

Methods

shape :: I (Shape Rational)

pkEncode :: Rational -> F' (Shape Rational) ByteString

pkDecode :: F' (Shape Rational) ByteString -> Rational

PopKeyEncoding Word Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Word :: Type

Methods

shape :: I (Shape Word)

pkEncode :: Word -> F' (Shape Word) ByteString

pkDecode :: F' (Shape Word) ByteString -> Word

PopKeyEncoding Word8 Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Word8 :: Type

Methods

shape :: I (Shape Word8)

pkEncode :: Word8 -> F' (Shape Word8) ByteString

pkDecode :: F' (Shape Word8) ByteString -> Word8

PopKeyEncoding Word16 Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Word16 :: Type

Methods

shape :: I (Shape Word16)

pkEncode :: Word16 -> F' (Shape Word16) ByteString

pkDecode :: F' (Shape Word16) ByteString -> Word16

PopKeyEncoding Word32 Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Word32 :: Type

Methods

shape :: I (Shape Word32)

pkEncode :: Word32 -> F' (Shape Word32) ByteString

pkDecode :: F' (Shape Word32) ByteString -> Word32

PopKeyEncoding Word64 Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Word64 :: Type

Methods

shape :: I (Shape Word64)

pkEncode :: Word64 -> F' (Shape Word64) ByteString

pkDecode :: F' (Shape Word64) ByteString -> Word64

PopKeyEncoding () Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape () :: Type

Methods

shape :: I (Shape ())

pkEncode :: () -> F' (Shape ()) ByteString

pkDecode :: F' (Shape ()) ByteString -> ()

PopKeyEncoding ByteString Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape ByteString :: Type

PopKeyEncoding ByteString Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape ByteString :: Type

Methods

shape :: I (Shape ByteString)

pkEncode :: ByteString -> F' (Shape ByteString) ByteString

pkDecode :: F' (Shape ByteString) ByteString -> ByteString

PopKeyEncoding IntSet Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape IntSet :: Type

Methods

shape :: I (Shape IntSet)

pkEncode :: IntSet -> F' (Shape IntSet) ByteString

pkDecode :: F' (Shape IntSet) ByteString -> IntSet

PopKeyEncoding Graph Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Graph :: Type

Methods

shape :: I (Shape Graph)

pkEncode :: Graph -> F' (Shape Graph) ByteString

pkDecode :: F' (Shape Graph) ByteString -> Graph

PopKeyEncoding Text Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Text :: Type

Methods

shape :: I (Shape Text)

pkEncode :: Text -> F' (Shape Text) ByteString

pkDecode :: F' (Shape Text) ByteString -> Text

PopKeyEncoding Text Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape Text :: Type

Methods

shape :: I (Shape Text)

pkEncode :: Text -> F' (Shape Text) ByteString

pkDecode :: F' (Shape Text) ByteString -> Text

Store a => PopKeyEncoding [a] Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape [a] :: Type

Methods

shape :: I (Shape [a])

pkEncode :: [a] -> F' (Shape [a]) ByteString

pkDecode :: F' (Shape [a]) ByteString -> [a]

PopKeyEncoding a => PopKeyEncoding (Maybe a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (Maybe a) :: Type

Methods

shape :: I (Shape (Maybe a))

pkEncode :: Maybe a -> F' (Shape (Maybe a)) ByteString

pkDecode :: F' (Shape (Maybe a)) ByteString -> Maybe a

Store a => PopKeyEncoding (Ratio a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (Ratio a) :: Type

Methods

shape :: I (Shape (Ratio a))

pkEncode :: Ratio a -> F' (Shape (Ratio a)) ByteString

pkDecode :: F' (Shape (Ratio a)) ByteString -> Ratio a

PopKeyEncoding a => PopKeyEncoding (Min a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (Min a) :: Type

Methods

shape :: I (Shape (Min a))

pkEncode :: Min a -> F' (Shape (Min a)) ByteString

pkDecode :: F' (Shape (Min a)) ByteString -> Min a

PopKeyEncoding a => PopKeyEncoding (Max a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (Max a) :: Type

Methods

shape :: I (Shape (Max a))

pkEncode :: Max a -> F' (Shape (Max a)) ByteString

pkDecode :: F' (Shape (Max a)) ByteString -> Max a

PopKeyEncoding a => PopKeyEncoding (First a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (First a) :: Type

Methods

shape :: I (Shape (First a))

pkEncode :: First a -> F' (Shape (First a)) ByteString

pkDecode :: F' (Shape (First a)) ByteString -> First a

PopKeyEncoding a => PopKeyEncoding (Last a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (Last a) :: Type

Methods

shape :: I (Shape (Last a))

pkEncode :: Last a -> F' (Shape (Last a)) ByteString

pkDecode :: F' (Shape (Last a)) ByteString -> Last a

PopKeyEncoding a => PopKeyEncoding (Option a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (Option a) :: Type

Methods

shape :: I (Shape (Option a))

pkEncode :: Option a -> F' (Shape (Option a)) ByteString

pkDecode :: F' (Shape (Option a)) ByteString -> Option a

PopKeyEncoding a => PopKeyEncoding (Identity a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (Identity a) :: Type

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 (Sum a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (Sum a) :: Type

Methods

shape :: I (Shape (Sum a))

pkEncode :: Sum a -> F' (Shape (Sum a)) ByteString

pkDecode :: F' (Shape (Sum a)) ByteString -> Sum a

PopKeyEncoding a => PopKeyEncoding (Product a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (Product a) :: Type

Methods

shape :: I (Shape (Product a))

pkEncode :: Product a -> F' (Shape (Product a)) ByteString

pkDecode :: F' (Shape (Product a)) ByteString -> Product a

Store a => PopKeyEncoding (IntMap a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (IntMap a) :: Type

Methods

shape :: I (Shape (IntMap a))

pkEncode :: IntMap a -> F' (Shape (IntMap a)) ByteString

pkDecode :: F' (Shape (IntMap a)) ByteString -> IntMap a

Store a => PopKeyEncoding (Seq a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (Seq a) :: Type

Methods

shape :: I (Shape (Seq a))

pkEncode :: Seq a -> F' (Shape (Seq a)) ByteString

pkDecode :: F' (Shape (Seq a)) ByteString -> Seq a

(Ord a, Store a) => PopKeyEncoding (Set a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (Set a) :: Type

Methods

shape :: I (Shape (Set a))

pkEncode :: Set a -> F' (Shape (Set a)) ByteString

pkDecode :: F' (Shape (Set a)) ByteString -> Set a

Store a => PopKeyEncoding (StoreBlob a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (StoreBlob a) :: Type

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 b) => PopKeyEncoding (Either a b) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (Either a b) :: Type

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 a, PopKeyEncoding b) => PopKeyEncoding (a, b) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (a, b) :: Type

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 b) => PopKeyEncoding (Arg a b) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (Arg a b) :: Type

Methods

shape :: I (Shape (Arg a b))

pkEncode :: Arg a b -> F' (Shape (Arg a b)) ByteString

pkDecode :: F' (Shape (Arg a b)) ByteString -> Arg a b

PopKeyEncoding (Proxy a) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (Proxy a) :: Type

Methods

shape :: I (Shape (Proxy a))

pkEncode :: Proxy a -> F' (Shape (Proxy a)) ByteString

pkDecode :: F' (Shape (Proxy a)) ByteString -> Proxy a

(Ord a, Store a, Store b) => PopKeyEncoding (Map a b) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (Map a b) :: Type

Methods

shape :: I (Shape (Map a b))

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 c) => PopKeyEncoding (a, b, c) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (a, b, c) :: Type

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 (Const a b) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (Const a b) :: Type

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 d) => PopKeyEncoding (a, b, c, d) Source # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (a, b, c, d) :: Type

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 # 
Instance details

Defined in PopKey.Encoding

Associated Types

type Shape (a, b, c, d, e) :: Type

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 # 
Instance details

Defined in PopKey.Internal3

Associated Types

type Input (PopKeyStore k v) :: Type 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 # 
Instance details

Defined in PopKey.Internal3

type Input (PopKeyStore k v) = (k, v)

data PopKeyStore' v Source #

Instances
StorePopKey Int v (PopKeyStore' v) Source # 
Instance details

Defined in PopKey.Internal3

Associated Types

type Input (PopKeyStore' v) :: Type Source #

type Input (PopKeyStore' v) Source # 
Instance details

Defined in PopKey.Internal3

type Input (PopKeyStore' v) = v

class StorePopKey k v f | f -> k, f -> v where Source #

Associated Types

type Input f 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 # 
Instance details

Defined in PopKey.Internal3

Associated Types

type Input (PopKeyStore' v) :: Type Source #

StorePopKey k v (PopKeyStore k v) Source # 
Instance details

Defined in PopKey.Internal3

Associated Types

type Input (PopKeyStore k v) :: Type Source #

Methods

storePopKey :: Foldable t => PopKeyStore k v -> t (Input (PopKeyStore k v)) -> IO () Source #

loadPopKey :: PopKeyStore k v -> IO (PopKey k v) Source #