data-effects-0.4.2.0: A basic framework for effect systems based on effects represented by GADTs.
Copyright(c) 2025 Sayo contributors
LicenseMPL-2.0 (see the file LICENSE)
Maintainerymdfield@outlook.jp
Safe HaskellNone
LanguageGHC2021

Data.Effect.KVStore

Description

This module provides the KVStore effect, comes from Polysemy.KVStore in the polysemy-kvstore package.

Documentation

data KVStore k v (a :: Type -> Type) b where Source #

Constructors

LookupKV :: forall k v (a :: Type -> Type). k -> KVStore k v a (Maybe v) 
UpdateKV :: forall k v (a :: Type -> Type). k -> Maybe v -> KVStore k v a () 

Instances

Instances details
FirstOrder (KVStore k v) Source # 
Instance details

Defined in Data.Effect.KVStore

PolyHFunctor (KVStore k v) Source # 
Instance details

Defined in Data.Effect.KVStore

HFunctor (KVStore k v) Source # 
Instance details

Defined in Data.Effect.KVStore

Methods

hfmap :: (forall x. f x -> g x) -> KVStore k v f a -> KVStore k v g a #

type FormOf (KVStore k v) Source # 
Instance details

Defined in Data.Effect.KVStore

type FormOf (KVStore k v) = 'Polynomial
type LabelOf (KVStore k v) Source # 
Instance details

Defined in Data.Effect.KVStore

type OrderOf (KVStore k v) Source # 
Instance details

Defined in Data.Effect.KVStore

type OrderOf (KVStore k v) = 'FirstOrder

lookupKV :: forall k v f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, KVStore k v :> es) => k -> f (Maybe v) Source #

lookupKV' :: forall {k1} (key :: k1) k2 v f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (KVStore k2 v) es) => k2 -> f (Maybe v) Source #

lookupKV'' :: forall {k1} (tag :: k1) k2 v f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (KVStore k2 v) :> es) => k2 -> f (Maybe v) Source #

lookupKV'_ :: forall k v f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (KVStore k v) es) => k -> f (Maybe v) Source #

updateKV :: forall k v f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, KVStore k v :> es) => k -> Maybe v -> f () Source #

updateKV' :: forall {k1} (key :: k1) k2 v f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Has key (KVStore k2 v) es) => k2 -> Maybe v -> f () Source #

updateKV'' :: forall {k1} (tag :: k1) k2 v f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, Tagged tag (KVStore k2 v) :> es) => k2 -> Maybe v -> f () Source #

updateKV'_ :: forall k v f (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, f ~ Eff ff es, In (KVStore k v) es) => k -> Maybe v -> f () Source #

lookupOrThrowKV :: forall k v e (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KVStore k v :> es, Throw e :> es, Monad (Eff ff es), Free c ff) => (k -> e) -> k -> Eff ff es v Source #

existsKV :: forall v k (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KVStore k v :> es, Functor (Eff ff es), Free c ff) => k -> Eff ff es Bool Source #

writeKV :: forall k v (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KVStore k v :> es, Free c ff) => k -> v -> Eff ff es () Source #

deleteKV :: forall v k (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KVStore k v :> es, Free c ff) => k -> Eff ff es () Source #

modifyKV :: forall k v (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (KVStore k v :> es, Monad (Eff ff es), Free c ff) => v -> (v -> v) -> k -> Eff ff es () Source #

runKVStoreIORef :: forall k v a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Ord k, Emb IO :> es, forall (es' :: [Effect]). Monad (Eff ff es'), Free c ff) => Map k v -> Eff ff (KVStore k v ': es) a -> Eff ff es (Map k v, a) Source #

runKVStoreAsState :: forall k v (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Ord k, State (Map k v) :> es, Monad (Eff ff es), Free c ff) => Eff ff (KVStore k v ': es) ~> Eff ff es Source #