effet-0.3.0.0: An Effect System based on Type Classes
Copyright(c) Michael Szvetits 2020
LicenseBSD3 (see the file LICENSE)
Maintainertypedbyte@qualified.name
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Control.Effect.Map

Description

The map effect for modeling a mutable collection of key-value pairs.

Lazy and strict interpretations of the effect are available here: Control.Effect.Map.Lazy and Control.Effect.Map.Strict.

Synopsis

Tagged Map Effect

class Monad m => Map' tag k v m | tag m -> k v where Source #

An effect that adds a mutable collection of key-value pairs to a given computation.

Methods

clear' :: m () Source #

Deletes all key-value pairs from the map.

lookup' :: k -> m (Maybe v) Source #

Searches for a value that corresponds to a given key. Returns Nothing if the key cannot be found.

update' :: k -> Maybe v -> m () Source #

Updates the value that corresponds to a given key. Passing Nothing as the updated value removes the key-value pair from the map.

Instances

Instances details
Handle (Map' tag k2 v) t m => Map' (tag :: k1) k2 v (EachVia (Map' tag k2 v ': effs) t m) Source # 
Instance details

Defined in Control.Effect.Map

Methods

clear' :: EachVia (Map' tag k2 v ': effs) t m () Source #

lookup' :: k2 -> EachVia (Map' tag k2 v ': effs) t m (Maybe v) Source #

update' :: k2 -> Maybe v -> EachVia (Map' tag k2 v ': effs) t m () Source #

Find (Map' tag k2 v) effs t m => Map' (tag :: k1) k2 v (EachVia (other ': effs) t m) Source # 
Instance details

Defined in Control.Effect.Map

Methods

clear' :: EachVia (other ': effs) t m () Source #

lookup' :: k2 -> EachVia (other ': effs) t m (Maybe v) Source #

update' :: k2 -> Maybe v -> EachVia (other ': effs) t m () Source #

Lift (Map' tag k2 v) t m => Map' (tag :: k1) k2 v (EachVia ('[] :: [Effect]) t m) Source # 
Instance details

Defined in Control.Effect.Map

Methods

clear' :: EachVia '[] t m () Source #

lookup' :: k2 -> EachVia '[] t m (Maybe v) Source #

update' :: k2 -> Maybe v -> EachVia '[] t m () Source #

(Monad m, Ord k2) => Map' (tag :: k1) k2 v (LazyMap k2 v m) Source # 
Instance details

Defined in Control.Effect.Map.Lazy

Methods

clear' :: LazyMap k2 v m () Source #

lookup' :: k2 -> LazyMap k2 v m (Maybe v) Source #

update' :: k2 -> Maybe v -> LazyMap k2 v m () Source #

(Monad m, Ord k2) => Map' (tag :: k1) k2 v (StrictMap k2 v m) Source # 
Instance details

Defined in Control.Effect.Map.Strict

Methods

clear' :: StrictMap k2 v m () Source #

lookup' :: k2 -> StrictMap k2 v m (Maybe v) Source #

update' :: k2 -> Maybe v -> StrictMap k2 v m () Source #

Map' new k3 v m => Map' (tag :: k2) k3 v (Tagger tag new m) Source # 
Instance details

Defined in Control.Effect.Map

Methods

clear' :: Tagger tag new m () Source #

lookup' :: k3 -> Tagger tag new m (Maybe v) Source #

update' :: k3 -> Maybe v -> Tagger tag new m () Source #

Untagged Map Effect

If you don't require disambiguation of multiple map effects (i.e., you only have one map effect in your monadic context), it is recommended to always use the untagged map effect.

type Map k v = Map' G k v Source #

clear :: Map k v m => m () Source #

lookup :: Map k v m => k -> m (Maybe v) Source #

update :: Map k v m => k -> Maybe v -> m () Source #

Convenience Functions

If you don't require disambiguation of multiple map effects (i.e., you only have one map effect in your monadic context), it is recommended to always use the untagged functions.

delete' :: forall tag k v m. Map' tag k v m => k -> m () Source #

Deletes a key and its corresponding value from the map.

delete :: Map k v m => k -> m () Source #

The untagged version of delete'.

exists' :: forall tag k v m. Map' tag k v m => k -> m Bool Source #

Checks if the map contains a given key.

exists :: Map k v m => k -> m Bool Source #

The untagged version of exists'.

insert' :: forall tag k v m. Map' tag k v m => k -> v -> m () Source #

Inserts a new key-value pair into the map. If the key is already present in the map, the associated value is replaced with the new value.

insert :: Map k v m => k -> v -> m () Source #

The untagged version of insert'.

modify' Source #

Arguments

:: forall tag k v m. Map' tag k v m 
=> v

The default value that is assumed if the key is missing.

-> (v -> v)

The function for updating the value. This function is also applied to the default value if the key is missing.

-> k

The key whose corresponding value is updated.

-> m ()

The operation produces no value.

Updates the value that corresponds to a given key. If the key cannot be found, a corresponding default value is assumed.

modify :: Map k v m => v -> (v -> v) -> k -> m () Source #

The untagged version of modify'.

Tagging and Untagging

Conversion functions between the tagged and untagged map effect, usually used in combination with type applications, like:

    tagMap' @"newTag" program
    retagMap' @"oldTag" @"newTag" program
    untagMap' @"erasedTag" program

tagMap' :: forall new k v m a. Via (Map' G k v) (Tagger G new) m a -> m a Source #

retagMap' :: forall tag new k v m a. Via (Map' tag k v) (Tagger tag new) m a -> m a Source #

untagMap' :: forall tag k v m a. Via (Map' tag k v) (Tagger tag G) m a -> m a Source #