cleff-0.1.0.0: Fast and concise extensible effects
Safe HaskellNone
LanguageHaskell2010

Cleff.KVStore

Synopsis

Effect

data KVStore k v :: Effect where Source #

An effect that provides operations of accessing a key-value store, like a map data structure or a key-value database.

Constructors

LookupKV :: k -> KVStore k v m (Maybe v) 
UpdateKV :: k -> Maybe v -> KVStore k v m () 

Operations

lookupKV :: KVStore k v :> es => k -> Eff es (Maybe v) Source #

updateKV :: KVStore k v :> es => k -> Maybe v -> Eff es () Source #

writeKV :: KVStore k v :> es => k -> v -> Eff es () Source #

Write a value to the given entry.

deleteKV :: forall k v es. KVStore k v :> es => k -> Eff es () Source #

Delete the given entry.

lookupOrThrowKV :: '[KVStore k v, Error e] :>> es => (k -> e) -> k -> Eff es v Source #

Lookup the value of the given key, if not found, then throw some error.

existsKV :: forall k v es. KVStore k v :> es => k -> Eff es Bool Source #

Sees if the key is present in the store.

adjustKV :: forall k v es. KVStore k v :> es => (v -> v) -> k -> Eff es () Source #

If the key is present, changes the value via a function.

modifyKV :: forall k v es. KVStore k v :> es => (v -> Maybe v) -> k -> Eff es () Source #

If the key is present, updates the entry (potentially deleting it) via a function.

alterKV :: forall k v es. KVStore k v :> es => (Maybe v -> Maybe v) -> k -> Eff es () Source #

Updates the entry via a function, no matter the key is present or not.

Interpretations

kvStoreToMapState :: Ord k => Eff (KVStore k v ': es) ~> Eff (State (Map k v) ': es) Source #

Interpret a KVStore effect in terms of Map and strict operations.

kvStoreToLazyMapState :: Ord k => Eff (KVStore k v ': es) ~> Eff (State (Map k v) ': es) Source #

Interpret a KVStore effect in terms of Map and lazy operations.

kvStoreToIntMapState :: Eff (KVStore Key v ': es) ~> Eff (State (IntMap v) ': es) Source #

Interpret a KVStore Int v effect in terms of IntMap and strict operations.

kvStoreToLazyIntMapState :: Eff (KVStore Key v ': es) ~> Eff (State (IntMap v) ': es) Source #

Interpret a KVStore Int v effect in terms of IntMap and lazy operations.

kvStoreToHashMapState :: (Hashable k, Eq k) => Eff (KVStore k v ': es) ~> Eff (State (HashMap k v) ': es) Source #

Interpret a KVStore effect in terms of HashMap and strict operations.

kvStoreToLazyHashMapState :: (Hashable k, Eq k) => Eff (KVStore k v ': es) ~> Eff (State (HashMap k v) ': es) Source #

Interpret a KVStore effect in terms of HashMap and lazy operations.