polysemy-keyed-state-0.1.1: Effect for a set of stateful values indexed by a type of keys
Safe HaskellNone
LanguageHaskell2010

Polysemy.State.Keyed

Synopsis

Documentation

data KeyedState k :: Effect where Source #

An interpreter for KeyedState may or may not obey the following "consistency" law:

  • for any k, k', and v, putAt k v *> getAt k' = if k == k' then pure v else getAt k'

This law is relevant for most pure interpretations of KeyedState, but only applies when the values in the state are disjoint (setting at k does not modify the value at k' when k /= k') and local (never modified by another thread or program). Some useful sets of stateful values violate this law: for example, the sdl2 package provides a set of StateVars for each SDL window created, which are neither disjoint nor local.

Constructors

GetAt :: k a -> KeyedState k m a 
PutAt :: k a -> a -> KeyedState k m () 

Instances

Instances details
type DefiningModule KeyedState Source # 
Instance details

Defined in Polysemy.State.Keyed

type DefiningModule KeyedState = "Polysemy.State.Keyed"

Operations

getAt :: forall k r a. MemberWithError (KeyedState k) r => k a -> Sem r a Source #

putAt :: forall k r a. MemberWithError (KeyedState k) r => k a -> a -> Sem r () Source #

modifyAt :: forall k a r. Member (KeyedState k) r => k a -> (a -> a) -> Sem r () Source #

rename :: forall k k' r a. Member (KeyedState k') r => (forall x. k x -> k' x) -> Sem (KeyedState k ': r) a -> Sem r a Source #

Run a KeyedState operation in the context of another KeyedState effect by translating the keys.

zoomAt :: forall k a r. Member (KeyedState k) r => k a -> InterpreterFor (State a) r Source #

Interpret a State effect as a single variable in a KeyedState effect.

State interpreters

runKeyedStates :: forall k r. (forall a. k a -> ElemOf (State a) r) -> InterpreterFor (KeyedState k) r Source #

Distribute a KeyedState effect across multiple State effects by mapping each key to an effect.

Lawful if the State effects are interpreted lawfully.

newtype KeyedStore k Source #

A KeyedStore k is a total map over keys of type k.

Constructors

KeyedStore 

Fields

lookupAt :: k a -> KeyedStore k -> a Source #

Retrieve a value from a KeyedStore.

updateAt :: forall k a. (Typeable a, Has Typeable k, forall x. Eq (k x)) => k a -> a -> KeyedStore k -> KeyedStore k Source #

Update a value in a KeyedStore, using Typeable instances to check for key type equality.

updateAtBy :: forall k a. (forall x. Eq (k x)) => (forall b. k a -> k b -> Maybe (a :~: b)) -> k a -> a -> KeyedStore k -> KeyedStore k Source #

Update an entry in a KeyedStore, using a specified function to check for key type equality. This can be used with functions like testEquality and geq to avoid Typeable constraints.

runKeyedStateStore :: forall k r. (Member (State (KeyedStore k)) r, forall a. Eq (k a), Has Typeable k) => InterpreterFor (KeyedState k) r Source #

Interpret a KeyedState effect as a State effect over a KeyedStore, using Typeable instances to check for key type equality.

Lawful.

runKeyedStateStoreBy :: forall k r. (Member (State (KeyedStore k)) r, forall a. Eq (k a)) => (forall a b. k a -> k b -> Maybe (a :~: b)) -> InterpreterFor (KeyedState k) r Source #

Interpret a KeyedState effect as a State effect over a KeyedStore, using a specified function to check for key type equality. This can be used with functions like testEquality and geq to avoid Typeable constraints.

Lawful if the key type equality function always returns Just Refl whenever possible (i.e. it correctly says that any two equal types are equal); otherwise, putAt may silently fail to have any effect in some cases.

IO interpreters

class (forall a. c a => HasGetter (k a) a, forall a. c a => HasSetter (k a) a) => Reference c k Source #

An instance of Reference c k indicates that k is an IO reference type (like IORef, STRef, ...) that requires values to meet the constraint c. For more information, see the documentation for HasGetter and HasSetter.

Instances

Instances details
(forall a. c a => HasGetter (k a) a, forall a. c a => HasSetter (k a) a) => Reference c k Source # 
Instance details

Defined in Polysemy.State.Keyed

runKeyedStateRefsIO :: forall k r. (Member (Embed IO) r, Reference Unconstrained k) => InterpreterFor (KeyedState k) r Source #

Interpret each key directly as an IO reference. Useful with "key" types like IORef and STRef.

Note that there is no way to directly interpret a KeyedState effect where the "keys" are references that require Storable or other constraints to modify, like Ptr and ForeignPtr, since PutAt does not have any constraints on its argument type. To use KeyedState with constrained reference types, you can define a GADT key type to represent the set of references and interpret the effect with runStorableKeyedStateVarsIO, runStorableKeyedStateVarsOfIO, runConstrainedKeyedStateVarsIO, or runConstrainedKeyedStateVarsOfIO.

Lawful if all references used with getAt and putAt are disjoint and local.

runKeyedStateVarsIO :: forall ref k r. (Member (Embed IO) r, Reference Unconstrained ref) => (forall a. k a -> ref a) -> InterpreterFor (KeyedState k) r Source #

Interpret a KeyedState effect as a set of IO references by mapping each key to a reference.

Lawful if all references returned by the mapping are disjoint and local.

runKeyedStateVarsOfIO :: forall s ref k r. (Members [Input s, Embed IO] r, Reference Unconstrained ref) => (forall a. k a -> s -> ref a) -> InterpreterFor (KeyedState k) r Source #

Like runKeyedStateVarsIO, but for references that are accessed through some pure handle, like the window attributes in sdl2 package.

Lawful if all references returned by the mapping are disjoint and local.

runStorableKeyedStateVarsIO :: forall ref k r. (Member (Embed IO) r, Reference Storable ref, Has Storable k) => (forall a. k a -> ref a) -> InterpreterFor (KeyedState k) r Source #

Interpret a KeyedState effect as a set of IO references by mapping each key to a reference that requires a Storable constraint on values.

Lawful if all references returned by the mapping are disjoint and local.

runStorableKeyedStateVarsOfIO :: forall s ref k r. (Members [Input s, Embed IO] r, Reference Storable ref, Has Storable k) => (forall a. k a -> s -> ref a) -> InterpreterFor (KeyedState k) r Source #

Like runStorableKeyedStateVarsIO, but for references that are accessed through some pure handle.

Lawful if all references returned by the mapping are disjoint and local.

runConstrainedKeyedStateVarsIO :: forall c ref k r. (Member (Embed IO) r, Reference c ref, Has c k) => (forall a. k a -> ref a) -> InterpreterFor (KeyedState k) r Source #

Interpret a KeyedState effect as a set of IO references by mapping each key to a references that requires some specified constraint on values. This will usually need the TypeApplications extension to disambiguate the constraint. This can be used if you have some exotic reference type that requires a constraint other than Storable@.

Lawful if all references returned by the mapping are disjoint and local.

runConstrainedKeyedStateVarsOfIO :: forall s c ref k r. (Members [Input s, Embed IO] r, Reference c ref, Has c k) => (forall a. k a -> s -> ref a) -> InterpreterFor (KeyedState k) r Source #

Like runConstrainedKeyedStateVarsIO, but for references that are accessed through some pure handle.

Lawful if all references returned by the mapping are disjoint and local.