map-classes-0.1.0.0: A set of classes and instances for working with key/value mappings.

Safe HaskellNone
LanguageHaskell2010

Control.Class.Impl.Map

Description

If you just want to perform operations on maps, not write your own instances, Control.Class.Map is probably what you should be importing.

This package provides a number of type-classes that encapulate the idea of a key/value mapping. This includes your standard maps, but also arrays and potentially hashtables. This library only currently provide instances for types in package that are distributed with GHC.

Part of the motivation of this library is also consistency.

Pop quiz: Consider the insert, but don't check the documentation. If the key already exists in the map, which of the following occurs?

  1. The map is unchanged.
  2. The value at that key is updated.
  3. error is called.
  4. The result is undefined.

Personally, I had to check the documentation. The answer is actually option "2".

Imagine the potential minefield when changing collection types.

The classes in this library give explicit names for each of these behaviours, and if the implementers of those instances follow those specifications, users should be able to switch between different container types without changing their code nor their code's behaviour.

The naming convention and argument order is somewhat arbitary.

I've tried to follow existing convention but the existing convention is a bit mixed up.

For example insert for maps is actually called upsert in this library because that's what it actually does.

In anycase, I'll attempt to define the broad naming convention here, but there are further details in each class.

There's a number of prefixes to function which affect expected behaviour.

  1. The unprefixed functions should call error if something is unexpected, e.g. a key already exists on insert or a key is not in collection on delete. They must not just return the structure unchanged, that is the role of maybe prefixed functions.
  2. The "unsafe" prefixed functions may optionally just behave in an undefined fashion in the above case where one would instead error. For example, unsafe functions may do array lookups without bounds checking, potentially resulting in demons if they access memory they shouldn't.
  3. The "maybe" prefixed functions shall not call error if the operation can not be completed but instead return the structure unchanged.
  4. The "safe" prefixed functions actually have a Maybe return type which indicate whether the key is not found/already exists on insert.

Functions suffixed with Lookup actually have a different return type and generally allow one to access the contents of the structure before the change, the exact form depending on the function in particular. The reason for the Lookup suffix is that to implement these naively one can do a lookup before performing the operation. However, for example with deleteLookup on a map, it would be more efficient to just lookup the element to delete, grab it and delete it at the same time, so there is a point in overriding the default implementation.

Finally, you may notice some of the class functions that ordinarily accept a Functor, are renamed ending with a ..F_, and now have the Functor wrapped in a Coyoneda. This is because having Functors in class function defintions does not work with generalised newtype deriving.

The versions of the functions without the following underscores, i.e. ..F are what users should be using. When defining your own instances for these functions, it's probably best just apply 'toCoyonedaTransform'/'toCoyonedaTransformF' to their ordinary definitions. The non underscore style defintions run 'fromCoyonedaTransform'/'fromCoyonedaTransformF' on the class functions. Ideally rewrite rules included in these modules should reduce this pair of functions to id resulting in no runtime difference.

Regarding trailing F on the latter 'toCoyonedaTransform'/'toCoyonedaTransformF' function, use that when defining such Coyondea class functions which have return types wrapped in Maybe, namely the ones prefixed with safe....

To Do: Monadic versions of these functions, to be used on mutable structures for example.

Also To Do: Range lookups (and perhaps even range deletes?). In theory, for say maps, range lookups are not only possible but also faster than accessing the keys individually. But they've impossible for say hashmaps.

Pull requests welcome on github.

Synopsis

Documentation

type family Key t Source #

Instances

type Key ShortByteString Source # 
type Key ByteString Source # 
type Key ByteString Source # 
type Key IntSet Source # 
type Key IntSet = Int
type Key (IntMap v) Source # 
type Key (IntMap v) = Int
type Key (Seq a) Source # 
type Key (Seq a) = Int
type Key (Set a) Source # 
type Key (Set a) = a
type Key (Lazy t) Source # 
type Key (Lazy t) = Key t
type Key (Lazy t) Source # 
type Key (Lazy t) = Key t
type Key (Strict t) Source # 
type Key (Strict t) = Key t
type Key (Array i e) Source # 
type Key (Array i e) = i
type Key (Map k _) Source # 
type Key (Map k _) = k

type family Value t Source #

Instances

type Value ShortByteString Source # 
type Value ByteString Source # 
type Value ByteString Source # 
type Value IntSet Source # 
type Value IntSet = ()
type Value (IntMap v) Source # 
type Value (IntMap v) = v
type Value (Seq a) Source # 
type Value (Seq a) = a
type Value (Set a) Source # 
type Value (Set a) = ()
type Value (Lazy t) Source # 
type Value (Lazy t) = Value t
type Value (Lazy t) Source # 
type Value (Lazy t) = Value t
type Value (Strict t) Source # 
type Value (Strict t) = Value t
type Value (Array i e) Source # 
type Value (Array i e) = e
type Value (Map _ v) Source # 
type Value (Map _ v) = v

class LookupMap t where Source #

LookupMap is a class that simply represents data types indexable by a key that you can read from. Whilst obviously not enforced by the class, it's intended that this only be implemented for types with "fast" lookups, say O(log n) at most.

Hence, LookupMap is not implemented for list for example.

Not that Set is an instance of this type, where the keys are just the set values and the unit type '()' is the "value" type.

You could in theory implement LookupMap (and indeed associated classes like UpdateMap and AlterMap) for structures with multiple keys, by making the key type a sum type or a list or something.

Minimal complete definition

lookup | (unsafeIndex | index), member

Methods

lookup :: Key t -> t -> Maybe (Value t) Source #

lookup k x returns Just v if k is a key, Nothing otherwise

index :: Key t -> t -> Value t Source #

Like lookup but throws an error for values that don't exist

unsafeIndex :: Key t -> t -> Value t Source #

Like index but may be undefined for keys that don't exist

member :: Key t -> t -> Bool Source #

notMember :: Key t -> t -> Bool Source #

Instances

LookupMap ShortByteString Source # 
LookupMap ByteString Source # 
LookupMap ByteString Source # 
LookupMap IntSet Source # 
LookupMap (IntMap v) Source # 

Methods

lookup :: Key (IntMap v) -> IntMap v -> Maybe (Value (IntMap v)) Source #

index :: Key (IntMap v) -> IntMap v -> Value (IntMap v) Source #

unsafeIndex :: Key (IntMap v) -> IntMap v -> Value (IntMap v) Source #

member :: Key (IntMap v) -> IntMap v -> Bool Source #

notMember :: Key (IntMap v) -> IntMap v -> Bool Source #

LookupMap (Seq a) Source # 

Methods

lookup :: Key (Seq a) -> Seq a -> Maybe (Value (Seq a)) Source #

index :: Key (Seq a) -> Seq a -> Value (Seq a) Source #

unsafeIndex :: Key (Seq a) -> Seq a -> Value (Seq a) Source #

member :: Key (Seq a) -> Seq a -> Bool Source #

notMember :: Key (Seq a) -> Seq a -> Bool Source #

Ord a => LookupMap (Set a) Source # 

Methods

lookup :: Key (Set a) -> Set a -> Maybe (Value (Set a)) Source #

index :: Key (Set a) -> Set a -> Value (Set a) Source #

unsafeIndex :: Key (Set a) -> Set a -> Value (Set a) Source #

member :: Key (Set a) -> Set a -> Bool Source #

notMember :: Key (Set a) -> Set a -> Bool Source #

(IsLazyMap t, LookupMap t) => LookupMap (Lazy t) Source # 

Methods

lookup :: Key (Lazy t) -> Lazy t -> Maybe (Value (Lazy t)) Source #

index :: Key (Lazy t) -> Lazy t -> Value (Lazy t) Source #

unsafeIndex :: Key (Lazy t) -> Lazy t -> Value (Lazy t) Source #

member :: Key (Lazy t) -> Lazy t -> Bool Source #

notMember :: Key (Lazy t) -> Lazy t -> Bool Source #

LookupMap (Lazy (IntMap v)) Source # 

Methods

lookup :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Value (Lazy (IntMap v))) Source #

index :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Value (Lazy (IntMap v)) Source #

unsafeIndex :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Value (Lazy (IntMap v)) Source #

member :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Bool Source #

notMember :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Bool Source #

Ord k => LookupMap (Lazy (Map k v)) Source # 

Methods

lookup :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Value (Lazy (Map k v))) Source #

index :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Value (Lazy (Map k v)) Source #

unsafeIndex :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Value (Lazy (Map k v)) Source #

member :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Bool Source #

notMember :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Bool Source #

(IsStrictMap t, LookupMap t) => LookupMap (Strict t) Source # 

Methods

lookup :: Key (Strict t) -> Strict t -> Maybe (Value (Strict t)) Source #

index :: Key (Strict t) -> Strict t -> Value (Strict t) Source #

unsafeIndex :: Key (Strict t) -> Strict t -> Value (Strict t) Source #

member :: Key (Strict t) -> Strict t -> Bool Source #

notMember :: Key (Strict t) -> Strict t -> Bool Source #

Ix i => LookupMap (Array i e) Source # 

Methods

lookup :: Key (Array i e) -> Array i e -> Maybe (Value (Array i e)) Source #

index :: Key (Array i e) -> Array i e -> Value (Array i e) Source #

unsafeIndex :: Key (Array i e) -> Array i e -> Value (Array i e) Source #

member :: Key (Array i e) -> Array i e -> Bool Source #

notMember :: Key (Array i e) -> Array i e -> Bool Source #

Ord k => LookupMap (Map k v) Source # 

Methods

lookup :: Key (Map k v) -> Map k v -> Maybe (Value (Map k v)) Source #

index :: Key (Map k v) -> Map k v -> Value (Map k v) Source #

unsafeIndex :: Key (Map k v) -> Map k v -> Value (Map k v) Source #

member :: Key (Map k v) -> Map k v -> Bool Source #

notMember :: Key (Map k v) -> Map k v -> Bool Source #

class LookupMap t => SingletonMap t where Source #

Data types you can produce a one element container of.

The reason why this is a separate class instead of just the default instance is that there are contrainers where one can trivially make a singleton of but they're not Monoids or AlterMaps, i.e. you can't append or add elements to them at arbitary keys.

For example, arrays certainly don't have the concept of "insert at key", only update, nor is it obvious how to append them, particularly if their ranges overlap.

But given a key, one should be able to produce a singleton array.

Hence this class.

Minimal complete definition

singleton

Methods

singleton :: Key t -> Value t -> t Source #

Instances

SingletonMap IntSet Source # 
SingletonMap (IntMap v) Source # 

Methods

singleton :: Key (IntMap v) -> Value (IntMap v) -> IntMap v Source #

Ord a => SingletonMap (Set a) Source # 

Methods

singleton :: Key (Set a) -> Value (Set a) -> Set a Source #

SingletonMap (Lazy (IntMap v)) Source # 

Methods

singleton :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) Source #

Ord k => SingletonMap (Lazy (Map k v)) Source # 

Methods

singleton :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) Source #

Ix i => SingletonMap (Array i e) Source # 

Methods

singleton :: Key (Array i e) -> Value (Array i e) -> Array i e Source #

Ord k => SingletonMap (Map k v) Source # 

Methods

singleton :: Key (Map k v) -> Value (Map k v) -> Map k v Source #

class LookupMap t => InsertMap t where Source #

InsertMap represents types where new key-values pairs can be inserted.

Minimal complete definition

unsafeInsert | insert | safeInsert

Methods

insert :: Key t -> Value t -> t -> t Source #

Attempts to insert a value, calls error if the key already exists.

unsafeInsert :: Key t -> Value t -> t -> t Source #

Like insert, but if the key already exists the behaviour is undefined.

maybeInsert :: Key t -> Value t -> t -> t Source #

Like insert, but if the key already exists return the structure unchanged.

safeInsert :: Key t -> Value t -> t -> Maybe t Source #

Like insert, but if the key already exists return Nothing.

safeInsert :: UpsertMap t => Key t -> Value t -> t -> Maybe t Source #

Like insert, but if the key already exists return Nothing.

Instances

InsertMap IntSet Source # 
InsertMap (IntMap v) Source # 

Methods

insert :: Key (IntMap v) -> Value (IntMap v) -> IntMap v -> IntMap v Source #

unsafeInsert :: Key (IntMap v) -> Value (IntMap v) -> IntMap v -> IntMap v Source #

maybeInsert :: Key (IntMap v) -> Value (IntMap v) -> IntMap v -> IntMap v Source #

safeInsert :: Key (IntMap v) -> Value (IntMap v) -> IntMap v -> Maybe (IntMap v) Source #

Ord a => InsertMap (Set a) Source # 

Methods

insert :: Key (Set a) -> Value (Set a) -> Set a -> Set a Source #

unsafeInsert :: Key (Set a) -> Value (Set a) -> Set a -> Set a Source #

maybeInsert :: Key (Set a) -> Value (Set a) -> Set a -> Set a Source #

safeInsert :: Key (Set a) -> Value (Set a) -> Set a -> Maybe (Set a) Source #

(IsLazyMap t, InsertMap t) => InsertMap (Lazy t) Source # 

Methods

insert :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Lazy t Source #

unsafeInsert :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Lazy t Source #

maybeInsert :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Lazy t Source #

safeInsert :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Maybe (Lazy t) Source #

InsertMap (Lazy (IntMap v)) Source # 

Methods

insert :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

unsafeInsert :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

maybeInsert :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

safeInsert :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Lazy (IntMap v)) Source #

Ord k => InsertMap (Lazy (Map k v)) Source # 

Methods

insert :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

unsafeInsert :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

maybeInsert :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

safeInsert :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Lazy (Map k v)) Source #

(IsStrictMap t, InsertMap t) => InsertMap (Strict t) Source # 

Methods

insert :: Key (Strict t) -> Value (Strict t) -> Strict t -> Strict t Source #

unsafeInsert :: Key (Strict t) -> Value (Strict t) -> Strict t -> Strict t Source #

maybeInsert :: Key (Strict t) -> Value (Strict t) -> Strict t -> Strict t Source #

safeInsert :: Key (Strict t) -> Value (Strict t) -> Strict t -> Maybe (Strict t) Source #

Ord k => InsertMap (Map k v) Source # 

Methods

insert :: Key (Map k v) -> Value (Map k v) -> Map k v -> Map k v Source #

unsafeInsert :: Key (Map k v) -> Value (Map k v) -> Map k v -> Map k v Source #

maybeInsert :: Key (Map k v) -> Value (Map k v) -> Map k v -> Map k v Source #

safeInsert :: Key (Map k v) -> Value (Map k v) -> Map k v -> Maybe (Map k v) Source #

class LookupMap t => UpdateMap t where Source #

UpdateMap represents types where existing values can be updated.

The ability for keys to be inserted or deleted is optional.

A good example of a type which conforms to this is Seq, which has Int keys of which their values can be updated in "O(log n)" time.

However Seq is not an instance of AlterMap as although one can insert/delete from Seq it alters all the other indexes which would be very unexpected.

Methods

update :: Key t -> Value t -> t -> t Source #

Updates the value of a key, calls error if the key does not exist.

updateLookup :: Key t -> Value t -> t -> (Value t, t) Source #

unsafeUpdate :: Key t -> Value t -> t -> t Source #

Like update, but if the key does not exist the result is undefined.

unsafeUpdateLookup :: Key t -> Value t -> t -> (Value t, t) Source #

maybeUpdate :: Key t -> Value t -> t -> t Source #

safeUpdate :: Key t -> Value t -> t -> Maybe t Source #

safeUpdateLookup :: Key t -> Value t -> t -> Maybe (Value t, t) Source #

adjust :: (Value t -> Value t) -> Key t -> t -> t Source #

adjust f k x applies f to the value at key k and puts that modified value in it's place.

If the key does not exist it should throw an error.

adjustLookup :: (Value t -> (r, Value t)) -> Key t -> t -> (r, t) Source #

adjustF_ :: Functor f => (Value t -> Coyoneda f (Value t)) -> Key t -> t -> Coyoneda f t Source #

unsafeAdjust :: (Value t -> Value t) -> Key t -> t -> t Source #

unsafeAdjustLookup :: (Value t -> (r, Value t)) -> Key t -> t -> (r, t) Source #

unsafeAdjustF_ :: Functor f => (Value t -> Coyoneda f (Value t)) -> Key t -> t -> Coyoneda f t Source #

maybeAdjust :: (Value t -> Value t) -> Key t -> t -> t Source #

safeAdjust :: (Value t -> Value t) -> Key t -> t -> Maybe t Source #

safeAdjustLookup :: (Value t -> (r, Value t)) -> Key t -> t -> Maybe (r, t) Source #

safeAdjustF_ :: Functor f => (Value t -> Coyoneda f (Value t)) -> Key t -> t -> Maybe (Coyoneda f t) Source #

safeAdjustF_ :: (UpsertMap t, Functor f) => (Value t -> Coyoneda f (Value t)) -> Key t -> t -> Maybe (Coyoneda f t) Source #

Instances

UpdateMap IntSet Source # 

Methods

update :: Key IntSet -> Value IntSet -> IntSet -> IntSet Source #

updateLookup :: Key IntSet -> Value IntSet -> IntSet -> (Value IntSet, IntSet) Source #

unsafeUpdate :: Key IntSet -> Value IntSet -> IntSet -> IntSet Source #

unsafeUpdateLookup :: Key IntSet -> Value IntSet -> IntSet -> (Value IntSet, IntSet) Source #

maybeUpdate :: Key IntSet -> Value IntSet -> IntSet -> IntSet Source #

safeUpdate :: Key IntSet -> Value IntSet -> IntSet -> Maybe IntSet Source #

safeUpdateLookup :: Key IntSet -> Value IntSet -> IntSet -> Maybe (Value IntSet, IntSet) Source #

adjust :: (Value IntSet -> Value IntSet) -> Key IntSet -> IntSet -> IntSet Source #

adjustLookup :: (Value IntSet -> (r, Value IntSet)) -> Key IntSet -> IntSet -> (r, IntSet) Source #

adjustF_ :: Functor f => (Value IntSet -> Coyoneda f (Value IntSet)) -> Key IntSet -> IntSet -> Coyoneda f IntSet Source #

unsafeAdjust :: (Value IntSet -> Value IntSet) -> Key IntSet -> IntSet -> IntSet Source #

unsafeAdjustLookup :: (Value IntSet -> (r, Value IntSet)) -> Key IntSet -> IntSet -> (r, IntSet) Source #

unsafeAdjustF_ :: Functor f => (Value IntSet -> Coyoneda f (Value IntSet)) -> Key IntSet -> IntSet -> Coyoneda f IntSet Source #

maybeAdjust :: (Value IntSet -> Value IntSet) -> Key IntSet -> IntSet -> IntSet Source #

safeAdjust :: (Value IntSet -> Value IntSet) -> Key IntSet -> IntSet -> Maybe IntSet Source #

safeAdjustLookup :: (Value IntSet -> (r, Value IntSet)) -> Key IntSet -> IntSet -> Maybe (r, IntSet) Source #

safeAdjustF_ :: Functor f => (Value IntSet -> Coyoneda f (Value IntSet)) -> Key IntSet -> IntSet -> Maybe (Coyoneda f IntSet) Source #

UpdateMap (IntMap v) Source # 

Methods

update :: Key (IntMap v) -> Value (IntMap v) -> IntMap v -> IntMap v Source #

updateLookup :: Key (IntMap v) -> Value (IntMap v) -> IntMap v -> (Value (IntMap v), IntMap v) Source #

unsafeUpdate :: Key (IntMap v) -> Value (IntMap v) -> IntMap v -> IntMap v Source #

unsafeUpdateLookup :: Key (IntMap v) -> Value (IntMap v) -> IntMap v -> (Value (IntMap v), IntMap v) Source #

maybeUpdate :: Key (IntMap v) -> Value (IntMap v) -> IntMap v -> IntMap v Source #

safeUpdate :: Key (IntMap v) -> Value (IntMap v) -> IntMap v -> Maybe (IntMap v) Source #

safeUpdateLookup :: Key (IntMap v) -> Value (IntMap v) -> IntMap v -> Maybe (Value (IntMap v), IntMap v) Source #

adjust :: (Value (IntMap v) -> Value (IntMap v)) -> Key (IntMap v) -> IntMap v -> IntMap v Source #

adjustLookup :: (Value (IntMap v) -> (r, Value (IntMap v))) -> Key (IntMap v) -> IntMap v -> (r, IntMap v) Source #

adjustF_ :: Functor f => (Value (IntMap v) -> Coyoneda f (Value (IntMap v))) -> Key (IntMap v) -> IntMap v -> Coyoneda f (IntMap v) Source #

unsafeAdjust :: (Value (IntMap v) -> Value (IntMap v)) -> Key (IntMap v) -> IntMap v -> IntMap v Source #

unsafeAdjustLookup :: (Value (IntMap v) -> (r, Value (IntMap v))) -> Key (IntMap v) -> IntMap v -> (r, IntMap v) Source #

unsafeAdjustF_ :: Functor f => (Value (IntMap v) -> Coyoneda f (Value (IntMap v))) -> Key (IntMap v) -> IntMap v -> Coyoneda f (IntMap v) Source #

maybeAdjust :: (Value (IntMap v) -> Value (IntMap v)) -> Key (IntMap v) -> IntMap v -> IntMap v Source #

safeAdjust :: (Value (IntMap v) -> Value (IntMap v)) -> Key (IntMap v) -> IntMap v -> Maybe (IntMap v) Source #

safeAdjustLookup :: (Value (IntMap v) -> (r, Value (IntMap v))) -> Key (IntMap v) -> IntMap v -> Maybe (r, IntMap v) Source #

safeAdjustF_ :: Functor f => (Value (IntMap v) -> Coyoneda f (Value (IntMap v))) -> Key (IntMap v) -> IntMap v -> Maybe (Coyoneda f (IntMap v)) Source #

UpdateMap (Seq a) Source # 

Methods

update :: Key (Seq a) -> Value (Seq a) -> Seq a -> Seq a Source #

updateLookup :: Key (Seq a) -> Value (Seq a) -> Seq a -> (Value (Seq a), Seq a) Source #

unsafeUpdate :: Key (Seq a) -> Value (Seq a) -> Seq a -> Seq a Source #

unsafeUpdateLookup :: Key (Seq a) -> Value (Seq a) -> Seq a -> (Value (Seq a), Seq a) Source #

maybeUpdate :: Key (Seq a) -> Value (Seq a) -> Seq a -> Seq a Source #

safeUpdate :: Key (Seq a) -> Value (Seq a) -> Seq a -> Maybe (Seq a) Source #

safeUpdateLookup :: Key (Seq a) -> Value (Seq a) -> Seq a -> Maybe (Value (Seq a), Seq a) Source #

adjust :: (Value (Seq a) -> Value (Seq a)) -> Key (Seq a) -> Seq a -> Seq a Source #

adjustLookup :: (Value (Seq a) -> (r, Value (Seq a))) -> Key (Seq a) -> Seq a -> (r, Seq a) Source #

adjustF_ :: Functor f => (Value (Seq a) -> Coyoneda f (Value (Seq a))) -> Key (Seq a) -> Seq a -> Coyoneda f (Seq a) Source #

unsafeAdjust :: (Value (Seq a) -> Value (Seq a)) -> Key (Seq a) -> Seq a -> Seq a Source #

unsafeAdjustLookup :: (Value (Seq a) -> (r, Value (Seq a))) -> Key (Seq a) -> Seq a -> (r, Seq a) Source #

unsafeAdjustF_ :: Functor f => (Value (Seq a) -> Coyoneda f (Value (Seq a))) -> Key (Seq a) -> Seq a -> Coyoneda f (Seq a) Source #

maybeAdjust :: (Value (Seq a) -> Value (Seq a)) -> Key (Seq a) -> Seq a -> Seq a Source #

safeAdjust :: (Value (Seq a) -> Value (Seq a)) -> Key (Seq a) -> Seq a -> Maybe (Seq a) Source #

safeAdjustLookup :: (Value (Seq a) -> (r, Value (Seq a))) -> Key (Seq a) -> Seq a -> Maybe (r, Seq a) Source #

safeAdjustF_ :: Functor f => (Value (Seq a) -> Coyoneda f (Value (Seq a))) -> Key (Seq a) -> Seq a -> Maybe (Coyoneda f (Seq a)) Source #

Ord a => UpdateMap (Set a) Source # 

Methods

update :: Key (Set a) -> Value (Set a) -> Set a -> Set a Source #

updateLookup :: Key (Set a) -> Value (Set a) -> Set a -> (Value (Set a), Set a) Source #

unsafeUpdate :: Key (Set a) -> Value (Set a) -> Set a -> Set a Source #

unsafeUpdateLookup :: Key (Set a) -> Value (Set a) -> Set a -> (Value (Set a), Set a) Source #

maybeUpdate :: Key (Set a) -> Value (Set a) -> Set a -> Set a Source #

safeUpdate :: Key (Set a) -> Value (Set a) -> Set a -> Maybe (Set a) Source #

safeUpdateLookup :: Key (Set a) -> Value (Set a) -> Set a -> Maybe (Value (Set a), Set a) Source #

adjust :: (Value (Set a) -> Value (Set a)) -> Key (Set a) -> Set a -> Set a Source #

adjustLookup :: (Value (Set a) -> (r, Value (Set a))) -> Key (Set a) -> Set a -> (r, Set a) Source #

adjustF_ :: Functor f => (Value (Set a) -> Coyoneda f (Value (Set a))) -> Key (Set a) -> Set a -> Coyoneda f (Set a) Source #

unsafeAdjust :: (Value (Set a) -> Value (Set a)) -> Key (Set a) -> Set a -> Set a Source #

unsafeAdjustLookup :: (Value (Set a) -> (r, Value (Set a))) -> Key (Set a) -> Set a -> (r, Set a) Source #

unsafeAdjustF_ :: Functor f => (Value (Set a) -> Coyoneda f (Value (Set a))) -> Key (Set a) -> Set a -> Coyoneda f (Set a) Source #

maybeAdjust :: (Value (Set a) -> Value (Set a)) -> Key (Set a) -> Set a -> Set a Source #

safeAdjust :: (Value (Set a) -> Value (Set a)) -> Key (Set a) -> Set a -> Maybe (Set a) Source #

safeAdjustLookup :: (Value (Set a) -> (r, Value (Set a))) -> Key (Set a) -> Set a -> Maybe (r, Set a) Source #

safeAdjustF_ :: Functor f => (Value (Set a) -> Coyoneda f (Value (Set a))) -> Key (Set a) -> Set a -> Maybe (Coyoneda f (Set a)) Source #

(IsLazyMap t, UpdateMap t) => UpdateMap (Lazy t) Source # 

Methods

update :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Lazy t Source #

updateLookup :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> (Value (Lazy t), Lazy t) Source #

unsafeUpdate :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Lazy t Source #

unsafeUpdateLookup :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> (Value (Lazy t), Lazy t) Source #

maybeUpdate :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Lazy t Source #

safeUpdate :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Maybe (Lazy t) Source #

safeUpdateLookup :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Maybe (Value (Lazy t), Lazy t) Source #

adjust :: (Value (Lazy t) -> Value (Lazy t)) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

adjustLookup :: (Value (Lazy t) -> (r, Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> (r, Lazy t) Source #

adjustF_ :: Functor f => (Value (Lazy t) -> Coyoneda f (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Coyoneda f (Lazy t) Source #

unsafeAdjust :: (Value (Lazy t) -> Value (Lazy t)) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

unsafeAdjustLookup :: (Value (Lazy t) -> (r, Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> (r, Lazy t) Source #

unsafeAdjustF_ :: Functor f => (Value (Lazy t) -> Coyoneda f (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Coyoneda f (Lazy t) Source #

maybeAdjust :: (Value (Lazy t) -> Value (Lazy t)) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

safeAdjust :: (Value (Lazy t) -> Value (Lazy t)) -> Key (Lazy t) -> Lazy t -> Maybe (Lazy t) Source #

safeAdjustLookup :: (Value (Lazy t) -> (r, Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Maybe (r, Lazy t) Source #

safeAdjustF_ :: Functor f => (Value (Lazy t) -> Coyoneda f (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Maybe (Coyoneda f (Lazy t)) Source #

UpdateMap (Lazy (IntMap v)) Source # 

Methods

update :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

updateLookup :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> (Value (Lazy (IntMap v)), Lazy (IntMap v)) Source #

unsafeUpdate :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

unsafeUpdateLookup :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> (Value (Lazy (IntMap v)), Lazy (IntMap v)) Source #

maybeUpdate :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

safeUpdate :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Lazy (IntMap v)) Source #

safeUpdateLookup :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Value (Lazy (IntMap v)), Lazy (IntMap v)) Source #

adjust :: (Value (Lazy (IntMap v)) -> Value (Lazy (IntMap v))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

adjustLookup :: (Value (Lazy (IntMap v)) -> (r, Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (r, Lazy (IntMap v)) Source #

adjustF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Coyoneda f (Lazy (IntMap v)) Source #

unsafeAdjust :: (Value (Lazy (IntMap v)) -> Value (Lazy (IntMap v))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

unsafeAdjustLookup :: (Value (Lazy (IntMap v)) -> (r, Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (r, Lazy (IntMap v)) Source #

unsafeAdjustF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Coyoneda f (Lazy (IntMap v)) Source #

maybeAdjust :: (Value (Lazy (IntMap v)) -> Value (Lazy (IntMap v))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

safeAdjust :: (Value (Lazy (IntMap v)) -> Value (Lazy (IntMap v))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Lazy (IntMap v)) Source #

safeAdjustLookup :: (Value (Lazy (IntMap v)) -> (r, Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (r, Lazy (IntMap v)) Source #

safeAdjustF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Coyoneda f (Lazy (IntMap v))) Source #

Ord k => UpdateMap (Lazy (Map k v)) Source # 

Methods

update :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

updateLookup :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> (Value (Lazy (Map k v)), Lazy (Map k v)) Source #

unsafeUpdate :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

unsafeUpdateLookup :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> (Value (Lazy (Map k v)), Lazy (Map k v)) Source #

maybeUpdate :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

safeUpdate :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Lazy (Map k v)) Source #

safeUpdateLookup :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Value (Lazy (Map k v)), Lazy (Map k v)) Source #

adjust :: (Value (Lazy (Map k v)) -> Value (Lazy (Map k v))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

adjustLookup :: (Value (Lazy (Map k v)) -> (r, Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> (r, Lazy (Map k v)) Source #

adjustF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Coyoneda f (Lazy (Map k v)) Source #

unsafeAdjust :: (Value (Lazy (Map k v)) -> Value (Lazy (Map k v))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

unsafeAdjustLookup :: (Value (Lazy (Map k v)) -> (r, Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> (r, Lazy (Map k v)) Source #

unsafeAdjustF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Coyoneda f (Lazy (Map k v)) Source #

maybeAdjust :: (Value (Lazy (Map k v)) -> Value (Lazy (Map k v))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

safeAdjust :: (Value (Lazy (Map k v)) -> Value (Lazy (Map k v))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Lazy (Map k v)) Source #

safeAdjustLookup :: (Value (Lazy (Map k v)) -> (r, Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (r, Lazy (Map k v)) Source #

safeAdjustF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Coyoneda f (Lazy (Map k v))) Source #

(IsStrictMap t, UpdateMap t) => UpdateMap (Strict t) Source # 

Methods

update :: Key (Strict t) -> Value (Strict t) -> Strict t -> Strict t Source #

updateLookup :: Key (Strict t) -> Value (Strict t) -> Strict t -> (Value (Strict t), Strict t) Source #

unsafeUpdate :: Key (Strict t) -> Value (Strict t) -> Strict t -> Strict t Source #

unsafeUpdateLookup :: Key (Strict t) -> Value (Strict t) -> Strict t -> (Value (Strict t), Strict t) Source #

maybeUpdate :: Key (Strict t) -> Value (Strict t) -> Strict t -> Strict t Source #

safeUpdate :: Key (Strict t) -> Value (Strict t) -> Strict t -> Maybe (Strict t) Source #

safeUpdateLookup :: Key (Strict t) -> Value (Strict t) -> Strict t -> Maybe (Value (Strict t), Strict t) Source #

adjust :: (Value (Strict t) -> Value (Strict t)) -> Key (Strict t) -> Strict t -> Strict t Source #

adjustLookup :: (Value (Strict t) -> (r, Value (Strict t))) -> Key (Strict t) -> Strict t -> (r, Strict t) Source #

adjustF_ :: Functor f => (Value (Strict t) -> Coyoneda f (Value (Strict t))) -> Key (Strict t) -> Strict t -> Coyoneda f (Strict t) Source #

unsafeAdjust :: (Value (Strict t) -> Value (Strict t)) -> Key (Strict t) -> Strict t -> Strict t Source #

unsafeAdjustLookup :: (Value (Strict t) -> (r, Value (Strict t))) -> Key (Strict t) -> Strict t -> (r, Strict t) Source #

unsafeAdjustF_ :: Functor f => (Value (Strict t) -> Coyoneda f (Value (Strict t))) -> Key (Strict t) -> Strict t -> Coyoneda f (Strict t) Source #

maybeAdjust :: (Value (Strict t) -> Value (Strict t)) -> Key (Strict t) -> Strict t -> Strict t Source #

safeAdjust :: (Value (Strict t) -> Value (Strict t)) -> Key (Strict t) -> Strict t -> Maybe (Strict t) Source #

safeAdjustLookup :: (Value (Strict t) -> (r, Value (Strict t))) -> Key (Strict t) -> Strict t -> Maybe (r, Strict t) Source #

safeAdjustF_ :: Functor f => (Value (Strict t) -> Coyoneda f (Value (Strict t))) -> Key (Strict t) -> Strict t -> Maybe (Coyoneda f (Strict t)) Source #

Ord k => UpdateMap (Map k v) Source # 

Methods

update :: Key (Map k v) -> Value (Map k v) -> Map k v -> Map k v Source #

updateLookup :: Key (Map k v) -> Value (Map k v) -> Map k v -> (Value (Map k v), Map k v) Source #

unsafeUpdate :: Key (Map k v) -> Value (Map k v) -> Map k v -> Map k v Source #

unsafeUpdateLookup :: Key (Map k v) -> Value (Map k v) -> Map k v -> (Value (Map k v), Map k v) Source #

maybeUpdate :: Key (Map k v) -> Value (Map k v) -> Map k v -> Map k v Source #

safeUpdate :: Key (Map k v) -> Value (Map k v) -> Map k v -> Maybe (Map k v) Source #

safeUpdateLookup :: Key (Map k v) -> Value (Map k v) -> Map k v -> Maybe (Value (Map k v), Map k v) Source #

adjust :: (Value (Map k v) -> Value (Map k v)) -> Key (Map k v) -> Map k v -> Map k v Source #

adjustLookup :: (Value (Map k v) -> (r, Value (Map k v))) -> Key (Map k v) -> Map k v -> (r, Map k v) Source #

adjustF_ :: Functor f => (Value (Map k v) -> Coyoneda f (Value (Map k v))) -> Key (Map k v) -> Map k v -> Coyoneda f (Map k v) Source #

unsafeAdjust :: (Value (Map k v) -> Value (Map k v)) -> Key (Map k v) -> Map k v -> Map k v Source #

unsafeAdjustLookup :: (Value (Map k v) -> (r, Value (Map k v))) -> Key (Map k v) -> Map k v -> (r, Map k v) Source #

unsafeAdjustF_ :: Functor f => (Value (Map k v) -> Coyoneda f (Value (Map k v))) -> Key (Map k v) -> Map k v -> Coyoneda f (Map k v) Source #

maybeAdjust :: (Value (Map k v) -> Value (Map k v)) -> Key (Map k v) -> Map k v -> Map k v Source #

safeAdjust :: (Value (Map k v) -> Value (Map k v)) -> Key (Map k v) -> Map k v -> Maybe (Map k v) Source #

safeAdjustLookup :: (Value (Map k v) -> (r, Value (Map k v))) -> Key (Map k v) -> Map k v -> Maybe (r, Map k v) Source #

safeAdjustF_ :: Functor f => (Value (Map k v) -> Coyoneda f (Value (Map k v))) -> Key (Map k v) -> Map k v -> Maybe (Coyoneda f (Map k v)) Source #

adjustF :: (UpdateMap t, Functor f) => (Value t -> f (Value t)) -> Key t -> t -> f t Source #

unsafeAdjustF :: (UpdateMap t, Functor f) => (Value t -> f (Value t)) -> Key t -> t -> f t Source #

safeAdjustF :: (UpdateMap t, Functor f) => (Value t -> f (Value t)) -> Key t -> t -> Maybe (f t) Source #

class LookupMap t => DeleteMap t where Source #

DeleteMap represents types where keys can be deleted.

Minimal complete definition

unsafeDelete | delete | safeDelete | safeDeleteLookup

Methods

delete :: Key t -> t -> t Source #

Attempt to delete a key and call error if it's not found.

deleteLookup :: Key t -> t -> (Value t, t) Source #

Like delete, but also return the value at the key before deletion.

unsafeDelete :: Key t -> t -> t Source #

Like delete but if the key isn't found the result is undefined

unsafeDeleteLookup :: Key t -> t -> (Value t, t) Source #

Like deleteLookup but if the key isn't found the result is undefined

maybeDelete :: Key t -> t -> t Source #

Like delete, but return the structure unmodified if the key does not exist.

safeDelete :: Key t -> t -> Maybe t Source #

Like delete, but return Nothing the key does not exist.

safeDeleteLookup :: Key t -> t -> Maybe (Value t, t) Source #

Like safeDelete, but also return the value of the key before the delete.

optDelete :: (Value t -> Bool) -> Key t -> t -> t Source #

Attempt to optDelete a key based on it's value and call error if it's not found.

optDeleteLookup :: (Value t -> (r, Bool)) -> Key t -> t -> (r, t) Source #

Like optDelete, but also return the value at the key before deletion.

optDeleteF_ :: Functor f => (Value t -> Coyoneda f Bool) -> Key t -> t -> Coyoneda f t Source #

unsafeOptDelete :: (Value t -> Bool) -> Key t -> t -> t Source #

Like optDelete but if the key isn't found the result is undefined

unsafeOptDeleteLookup :: (Value t -> (r, Bool)) -> Key t -> t -> (r, t) Source #

Like optDeleteLookup but if the key isn't found the result is undefined

unsafeOptDeleteF_ :: Functor f => (Value t -> Coyoneda f Bool) -> Key t -> t -> Coyoneda f t Source #

maybeOptDelete :: (Value t -> Bool) -> Key t -> t -> t Source #

Like optDelete, but return the structure unmodified if the key does not exist.

safeOptDelete :: (Value t -> Bool) -> Key t -> t -> Maybe t Source #

Like optDelete, but return Nothing the key does not exist.

safeOptDeleteLookup :: (Value t -> (r, Bool)) -> Key t -> t -> Maybe (r, t) Source #

Like safeOptDelete, but also return the value of the key before the optDelete.

safeOptDeleteF_ :: Functor f => (Value t -> Coyoneda f Bool) -> Key t -> t -> Maybe (Coyoneda f t) Source #

safeOptDeleteF_ :: (UpleteMap t, Functor f) => (Value t -> Coyoneda f Bool) -> Key t -> t -> Maybe (Coyoneda f t) Source #

Instances

DeleteMap IntSet Source # 
DeleteMap (IntMap v) Source # 

Methods

delete :: Key (IntMap v) -> IntMap v -> IntMap v Source #

deleteLookup :: Key (IntMap v) -> IntMap v -> (Value (IntMap v), IntMap v) Source #

unsafeDelete :: Key (IntMap v) -> IntMap v -> IntMap v Source #

unsafeDeleteLookup :: Key (IntMap v) -> IntMap v -> (Value (IntMap v), IntMap v) Source #

maybeDelete :: Key (IntMap v) -> IntMap v -> IntMap v Source #

safeDelete :: Key (IntMap v) -> IntMap v -> Maybe (IntMap v) Source #

safeDeleteLookup :: Key (IntMap v) -> IntMap v -> Maybe (Value (IntMap v), IntMap v) Source #

optDelete :: (Value (IntMap v) -> Bool) -> Key (IntMap v) -> IntMap v -> IntMap v Source #

optDeleteLookup :: (Value (IntMap v) -> (r, Bool)) -> Key (IntMap v) -> IntMap v -> (r, IntMap v) Source #

optDeleteF_ :: Functor f => (Value (IntMap v) -> Coyoneda f Bool) -> Key (IntMap v) -> IntMap v -> Coyoneda f (IntMap v) Source #

unsafeOptDelete :: (Value (IntMap v) -> Bool) -> Key (IntMap v) -> IntMap v -> IntMap v Source #

unsafeOptDeleteLookup :: (Value (IntMap v) -> (r, Bool)) -> Key (IntMap v) -> IntMap v -> (r, IntMap v) Source #

unsafeOptDeleteF_ :: Functor f => (Value (IntMap v) -> Coyoneda f Bool) -> Key (IntMap v) -> IntMap v -> Coyoneda f (IntMap v) Source #

maybeOptDelete :: (Value (IntMap v) -> Bool) -> Key (IntMap v) -> IntMap v -> IntMap v Source #

safeOptDelete :: (Value (IntMap v) -> Bool) -> Key (IntMap v) -> IntMap v -> Maybe (IntMap v) Source #

safeOptDeleteLookup :: (Value (IntMap v) -> (r, Bool)) -> Key (IntMap v) -> IntMap v -> Maybe (r, IntMap v) Source #

safeOptDeleteF_ :: Functor f => (Value (IntMap v) -> Coyoneda f Bool) -> Key (IntMap v) -> IntMap v -> Maybe (Coyoneda f (IntMap v)) Source #

Ord a => DeleteMap (Set a) Source # 

Methods

delete :: Key (Set a) -> Set a -> Set a Source #

deleteLookup :: Key (Set a) -> Set a -> (Value (Set a), Set a) Source #

unsafeDelete :: Key (Set a) -> Set a -> Set a Source #

unsafeDeleteLookup :: Key (Set a) -> Set a -> (Value (Set a), Set a) Source #

maybeDelete :: Key (Set a) -> Set a -> Set a Source #

safeDelete :: Key (Set a) -> Set a -> Maybe (Set a) Source #

safeDeleteLookup :: Key (Set a) -> Set a -> Maybe (Value (Set a), Set a) Source #

optDelete :: (Value (Set a) -> Bool) -> Key (Set a) -> Set a -> Set a Source #

optDeleteLookup :: (Value (Set a) -> (r, Bool)) -> Key (Set a) -> Set a -> (r, Set a) Source #

optDeleteF_ :: Functor f => (Value (Set a) -> Coyoneda f Bool) -> Key (Set a) -> Set a -> Coyoneda f (Set a) Source #

unsafeOptDelete :: (Value (Set a) -> Bool) -> Key (Set a) -> Set a -> Set a Source #

unsafeOptDeleteLookup :: (Value (Set a) -> (r, Bool)) -> Key (Set a) -> Set a -> (r, Set a) Source #

unsafeOptDeleteF_ :: Functor f => (Value (Set a) -> Coyoneda f Bool) -> Key (Set a) -> Set a -> Coyoneda f (Set a) Source #

maybeOptDelete :: (Value (Set a) -> Bool) -> Key (Set a) -> Set a -> Set a Source #

safeOptDelete :: (Value (Set a) -> Bool) -> Key (Set a) -> Set a -> Maybe (Set a) Source #

safeOptDeleteLookup :: (Value (Set a) -> (r, Bool)) -> Key (Set a) -> Set a -> Maybe (r, Set a) Source #

safeOptDeleteF_ :: Functor f => (Value (Set a) -> Coyoneda f Bool) -> Key (Set a) -> Set a -> Maybe (Coyoneda f (Set a)) Source #

(IsLazyMap t, DeleteMap t) => DeleteMap (Lazy t) Source # 

Methods

delete :: Key (Lazy t) -> Lazy t -> Lazy t Source #

deleteLookup :: Key (Lazy t) -> Lazy t -> (Value (Lazy t), Lazy t) Source #

unsafeDelete :: Key (Lazy t) -> Lazy t -> Lazy t Source #

unsafeDeleteLookup :: Key (Lazy t) -> Lazy t -> (Value (Lazy t), Lazy t) Source #

maybeDelete :: Key (Lazy t) -> Lazy t -> Lazy t Source #

safeDelete :: Key (Lazy t) -> Lazy t -> Maybe (Lazy t) Source #

safeDeleteLookup :: Key (Lazy t) -> Lazy t -> Maybe (Value (Lazy t), Lazy t) Source #

optDelete :: (Value (Lazy t) -> Bool) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

optDeleteLookup :: (Value (Lazy t) -> (r, Bool)) -> Key (Lazy t) -> Lazy t -> (r, Lazy t) Source #

optDeleteF_ :: Functor f => (Value (Lazy t) -> Coyoneda f Bool) -> Key (Lazy t) -> Lazy t -> Coyoneda f (Lazy t) Source #

unsafeOptDelete :: (Value (Lazy t) -> Bool) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

unsafeOptDeleteLookup :: (Value (Lazy t) -> (r, Bool)) -> Key (Lazy t) -> Lazy t -> (r, Lazy t) Source #

unsafeOptDeleteF_ :: Functor f => (Value (Lazy t) -> Coyoneda f Bool) -> Key (Lazy t) -> Lazy t -> Coyoneda f (Lazy t) Source #

maybeOptDelete :: (Value (Lazy t) -> Bool) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

safeOptDelete :: (Value (Lazy t) -> Bool) -> Key (Lazy t) -> Lazy t -> Maybe (Lazy t) Source #

safeOptDeleteLookup :: (Value (Lazy t) -> (r, Bool)) -> Key (Lazy t) -> Lazy t -> Maybe (r, Lazy t) Source #

safeOptDeleteF_ :: Functor f => (Value (Lazy t) -> Coyoneda f Bool) -> Key (Lazy t) -> Lazy t -> Maybe (Coyoneda f (Lazy t)) Source #

DeleteMap (Lazy (IntMap v)) Source # 

Methods

delete :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

deleteLookup :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (Value (Lazy (IntMap v)), Lazy (IntMap v)) Source #

unsafeDelete :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

unsafeDeleteLookup :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (Value (Lazy (IntMap v)), Lazy (IntMap v)) Source #

maybeDelete :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

safeDelete :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Lazy (IntMap v)) Source #

safeDeleteLookup :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Value (Lazy (IntMap v)), Lazy (IntMap v)) Source #

optDelete :: (Value (Lazy (IntMap v)) -> Bool) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

optDeleteLookup :: (Value (Lazy (IntMap v)) -> (r, Bool)) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (r, Lazy (IntMap v)) Source #

optDeleteF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f Bool) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Coyoneda f (Lazy (IntMap v)) Source #

unsafeOptDelete :: (Value (Lazy (IntMap v)) -> Bool) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

unsafeOptDeleteLookup :: (Value (Lazy (IntMap v)) -> (r, Bool)) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (r, Lazy (IntMap v)) Source #

unsafeOptDeleteF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f Bool) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Coyoneda f (Lazy (IntMap v)) Source #

maybeOptDelete :: (Value (Lazy (IntMap v)) -> Bool) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

safeOptDelete :: (Value (Lazy (IntMap v)) -> Bool) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Lazy (IntMap v)) Source #

safeOptDeleteLookup :: (Value (Lazy (IntMap v)) -> (r, Bool)) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (r, Lazy (IntMap v)) Source #

safeOptDeleteF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f Bool) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Coyoneda f (Lazy (IntMap v))) Source #

Ord k => DeleteMap (Lazy (Map k v)) Source # 

Methods

delete :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

deleteLookup :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> (Value (Lazy (Map k v)), Lazy (Map k v)) Source #

unsafeDelete :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

unsafeDeleteLookup :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> (Value (Lazy (Map k v)), Lazy (Map k v)) Source #

maybeDelete :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

safeDelete :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Lazy (Map k v)) Source #

safeDeleteLookup :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Value (Lazy (Map k v)), Lazy (Map k v)) Source #

optDelete :: (Value (Lazy (Map k v)) -> Bool) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

optDeleteLookup :: (Value (Lazy (Map k v)) -> (r, Bool)) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> (r, Lazy (Map k v)) Source #

optDeleteF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f Bool) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Coyoneda f (Lazy (Map k v)) Source #

unsafeOptDelete :: (Value (Lazy (Map k v)) -> Bool) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

unsafeOptDeleteLookup :: (Value (Lazy (Map k v)) -> (r, Bool)) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> (r, Lazy (Map k v)) Source #

unsafeOptDeleteF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f Bool) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Coyoneda f (Lazy (Map k v)) Source #

maybeOptDelete :: (Value (Lazy (Map k v)) -> Bool) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

safeOptDelete :: (Value (Lazy (Map k v)) -> Bool) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Lazy (Map k v)) Source #

safeOptDeleteLookup :: (Value (Lazy (Map k v)) -> (r, Bool)) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (r, Lazy (Map k v)) Source #

safeOptDeleteF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f Bool) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Coyoneda f (Lazy (Map k v))) Source #

(IsStrictMap t, DeleteMap t) => DeleteMap (Strict t) Source # 

Methods

delete :: Key (Strict t) -> Strict t -> Strict t Source #

deleteLookup :: Key (Strict t) -> Strict t -> (Value (Strict t), Strict t) Source #

unsafeDelete :: Key (Strict t) -> Strict t -> Strict t Source #

unsafeDeleteLookup :: Key (Strict t) -> Strict t -> (Value (Strict t), Strict t) Source #

maybeDelete :: Key (Strict t) -> Strict t -> Strict t Source #

safeDelete :: Key (Strict t) -> Strict t -> Maybe (Strict t) Source #

safeDeleteLookup :: Key (Strict t) -> Strict t -> Maybe (Value (Strict t), Strict t) Source #

optDelete :: (Value (Strict t) -> Bool) -> Key (Strict t) -> Strict t -> Strict t Source #

optDeleteLookup :: (Value (Strict t) -> (r, Bool)) -> Key (Strict t) -> Strict t -> (r, Strict t) Source #

optDeleteF_ :: Functor f => (Value (Strict t) -> Coyoneda f Bool) -> Key (Strict t) -> Strict t -> Coyoneda f (Strict t) Source #

unsafeOptDelete :: (Value (Strict t) -> Bool) -> Key (Strict t) -> Strict t -> Strict t Source #

unsafeOptDeleteLookup :: (Value (Strict t) -> (r, Bool)) -> Key (Strict t) -> Strict t -> (r, Strict t) Source #

unsafeOptDeleteF_ :: Functor f => (Value (Strict t) -> Coyoneda f Bool) -> Key (Strict t) -> Strict t -> Coyoneda f (Strict t) Source #

maybeOptDelete :: (Value (Strict t) -> Bool) -> Key (Strict t) -> Strict t -> Strict t Source #

safeOptDelete :: (Value (Strict t) -> Bool) -> Key (Strict t) -> Strict t -> Maybe (Strict t) Source #

safeOptDeleteLookup :: (Value (Strict t) -> (r, Bool)) -> Key (Strict t) -> Strict t -> Maybe (r, Strict t) Source #

safeOptDeleteF_ :: Functor f => (Value (Strict t) -> Coyoneda f Bool) -> Key (Strict t) -> Strict t -> Maybe (Coyoneda f (Strict t)) Source #

Ord k => DeleteMap (Map k v) Source # 

Methods

delete :: Key (Map k v) -> Map k v -> Map k v Source #

deleteLookup :: Key (Map k v) -> Map k v -> (Value (Map k v), Map k v) Source #

unsafeDelete :: Key (Map k v) -> Map k v -> Map k v Source #

unsafeDeleteLookup :: Key (Map k v) -> Map k v -> (Value (Map k v), Map k v) Source #

maybeDelete :: Key (Map k v) -> Map k v -> Map k v Source #

safeDelete :: Key (Map k v) -> Map k v -> Maybe (Map k v) Source #

safeDeleteLookup :: Key (Map k v) -> Map k v -> Maybe (Value (Map k v), Map k v) Source #

optDelete :: (Value (Map k v) -> Bool) -> Key (Map k v) -> Map k v -> Map k v Source #

optDeleteLookup :: (Value (Map k v) -> (r, Bool)) -> Key (Map k v) -> Map k v -> (r, Map k v) Source #

optDeleteF_ :: Functor f => (Value (Map k v) -> Coyoneda f Bool) -> Key (Map k v) -> Map k v -> Coyoneda f (Map k v) Source #

unsafeOptDelete :: (Value (Map k v) -> Bool) -> Key (Map k v) -> Map k v -> Map k v Source #

unsafeOptDeleteLookup :: (Value (Map k v) -> (r, Bool)) -> Key (Map k v) -> Map k v -> (r, Map k v) Source #

unsafeOptDeleteF_ :: Functor f => (Value (Map k v) -> Coyoneda f Bool) -> Key (Map k v) -> Map k v -> Coyoneda f (Map k v) Source #

maybeOptDelete :: (Value (Map k v) -> Bool) -> Key (Map k v) -> Map k v -> Map k v Source #

safeOptDelete :: (Value (Map k v) -> Bool) -> Key (Map k v) -> Map k v -> Maybe (Map k v) Source #

safeOptDeleteLookup :: (Value (Map k v) -> (r, Bool)) -> Key (Map k v) -> Map k v -> Maybe (r, Map k v) Source #

safeOptDeleteF_ :: Functor f => (Value (Map k v) -> Coyoneda f Bool) -> Key (Map k v) -> Map k v -> Maybe (Coyoneda f (Map k v)) Source #

optDeleteF :: (DeleteMap t, Functor f) => (Value t -> f Bool) -> Key t -> t -> f t Source #

unsafeOptDeleteF :: (DeleteMap t, Functor f) => (Value t -> f Bool) -> Key t -> t -> f t Source #

safeOptDeleteF :: (DeleteMap t, Functor f) => (Value t -> f Bool) -> Key t -> t -> Maybe (f t) Source #

class (InsertMap t, UpdateMap t) => UpsertMap t where Source #

Functions for doing inserts that don't fail on the keys being found but instead override existing values.

Methods

upsert :: Key t -> Value t -> t -> t Source #

upsertLookup :: Key t -> Value t -> t -> (Maybe (Value t), t) Source #

adsert :: (Maybe (Value t) -> Value t) -> Key t -> t -> t Source #

adsertLookup :: (Maybe (Value t) -> (r, Value t)) -> Key t -> t -> (r, t) Source #

adsertF_ :: Functor f => (Maybe (Value t) -> Coyoneda f (Value t)) -> Key t -> t -> Coyoneda f t Source #

adsertF_ :: (AlterMap t, Functor f) => (Maybe (Value t) -> Coyoneda f (Value t)) -> Key t -> t -> Coyoneda f t Source #

Instances

UpsertMap IntSet Source # 
UpsertMap (IntMap v) Source # 

Methods

upsert :: Key (IntMap v) -> Value (IntMap v) -> IntMap v -> IntMap v Source #

upsertLookup :: Key (IntMap v) -> Value (IntMap v) -> IntMap v -> (Maybe (Value (IntMap v)), IntMap v) Source #

adsert :: (Maybe (Value (IntMap v)) -> Value (IntMap v)) -> Key (IntMap v) -> IntMap v -> IntMap v Source #

adsertLookup :: (Maybe (Value (IntMap v)) -> (r, Value (IntMap v))) -> Key (IntMap v) -> IntMap v -> (r, IntMap v) Source #

adsertF_ :: Functor f => (Maybe (Value (IntMap v)) -> Coyoneda f (Value (IntMap v))) -> Key (IntMap v) -> IntMap v -> Coyoneda f (IntMap v) Source #

Ord a => UpsertMap (Set a) Source # 

Methods

upsert :: Key (Set a) -> Value (Set a) -> Set a -> Set a Source #

upsertLookup :: Key (Set a) -> Value (Set a) -> Set a -> (Maybe (Value (Set a)), Set a) Source #

adsert :: (Maybe (Value (Set a)) -> Value (Set a)) -> Key (Set a) -> Set a -> Set a Source #

adsertLookup :: (Maybe (Value (Set a)) -> (r, Value (Set a))) -> Key (Set a) -> Set a -> (r, Set a) Source #

adsertF_ :: Functor f => (Maybe (Value (Set a)) -> Coyoneda f (Value (Set a))) -> Key (Set a) -> Set a -> Coyoneda f (Set a) Source #

(IsLazyMap t, UpsertMap t) => UpsertMap (Lazy t) Source # 

Methods

upsert :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Lazy t Source #

upsertLookup :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> (Maybe (Value (Lazy t)), Lazy t) Source #

adsert :: (Maybe (Value (Lazy t)) -> Value (Lazy t)) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

adsertLookup :: (Maybe (Value (Lazy t)) -> (r, Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> (r, Lazy t) Source #

adsertF_ :: Functor f => (Maybe (Value (Lazy t)) -> Coyoneda f (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Coyoneda f (Lazy t) Source #

UpsertMap (Lazy (IntMap v)) Source # 

Methods

upsert :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

upsertLookup :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> (Maybe (Value (Lazy (IntMap v))), Lazy (IntMap v)) Source #

adsert :: (Maybe (Value (Lazy (IntMap v))) -> Value (Lazy (IntMap v))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

adsertLookup :: (Maybe (Value (Lazy (IntMap v))) -> (r, Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (r, Lazy (IntMap v)) Source #

adsertF_ :: Functor f => (Maybe (Value (Lazy (IntMap v))) -> Coyoneda f (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Coyoneda f (Lazy (IntMap v)) Source #

Ord k => UpsertMap (Lazy (Map k v)) Source # 

Methods

upsert :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

upsertLookup :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> (Maybe (Value (Lazy (Map k v))), Lazy (Map k v)) Source #

adsert :: (Maybe (Value (Lazy (Map k v))) -> Value (Lazy (Map k v))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

adsertLookup :: (Maybe (Value (Lazy (Map k v))) -> (r, Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> (r, Lazy (Map k v)) Source #

adsertF_ :: Functor f => (Maybe (Value (Lazy (Map k v))) -> Coyoneda f (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Coyoneda f (Lazy (Map k v)) Source #

(IsStrictMap t, UpsertMap t) => UpsertMap (Strict t) Source # 

Methods

upsert :: Key (Strict t) -> Value (Strict t) -> Strict t -> Strict t Source #

upsertLookup :: Key (Strict t) -> Value (Strict t) -> Strict t -> (Maybe (Value (Strict t)), Strict t) Source #

adsert :: (Maybe (Value (Strict t)) -> Value (Strict t)) -> Key (Strict t) -> Strict t -> Strict t Source #

adsertLookup :: (Maybe (Value (Strict t)) -> (r, Value (Strict t))) -> Key (Strict t) -> Strict t -> (r, Strict t) Source #

adsertF_ :: Functor f => (Maybe (Value (Strict t)) -> Coyoneda f (Value (Strict t))) -> Key (Strict t) -> Strict t -> Coyoneda f (Strict t) Source #

Ord k => UpsertMap (Map k v) Source # 

Methods

upsert :: Key (Map k v) -> Value (Map k v) -> Map k v -> Map k v Source #

upsertLookup :: Key (Map k v) -> Value (Map k v) -> Map k v -> (Maybe (Value (Map k v)), Map k v) Source #

adsert :: (Maybe (Value (Map k v)) -> Value (Map k v)) -> Key (Map k v) -> Map k v -> Map k v Source #

adsertLookup :: (Maybe (Value (Map k v)) -> (r, Value (Map k v))) -> Key (Map k v) -> Map k v -> (r, Map k v) Source #

adsertF_ :: Functor f => (Maybe (Value (Map k v)) -> Coyoneda f (Value (Map k v))) -> Key (Map k v) -> Map k v -> Coyoneda f (Map k v) Source #

adsertF :: (UpsertMap t, Functor f) => (Maybe (Value t) -> f (Value t)) -> Key t -> t -> f t Source #

class (DeleteMap t, UpdateMap t) => UpleteMap t where Source #

Methods

adlete :: (Value t -> Maybe (Value t)) -> Key t -> t -> t Source #

adleteLookup :: (Value t -> (r, Maybe (Value t))) -> Key t -> t -> (r, t) Source #

adleteF_ :: Functor f => (Value t -> Coyoneda f (Maybe (Value t))) -> Key t -> t -> Coyoneda f t Source #

unsafeAdlete :: (Value t -> Maybe (Value t)) -> Key t -> t -> t Source #

unsafeAdleteLookup :: (Value t -> (r, Maybe (Value t))) -> Key t -> t -> (r, t) Source #

unsafeAdleteF_ :: Functor f => (Value t -> Coyoneda f (Maybe (Value t))) -> Key t -> t -> Coyoneda f t Source #

maybeAdlete :: (Value t -> Maybe (Value t)) -> Key t -> t -> t Source #

safeAdlete :: (Value t -> Maybe (Value t)) -> Key t -> t -> Maybe t Source #

safeAdleteLookup :: (Value t -> (r, Maybe (Value t))) -> Key t -> t -> Maybe (r, t) Source #

safeAdleteF_ :: Functor f => (Value t -> Coyoneda f (Maybe (Value t))) -> Key t -> t -> Maybe (Coyoneda f t) Source #

safeAdleteF_ :: (AlterMap t, Functor f) => (Value t -> Coyoneda f (Maybe (Value t))) -> Key t -> t -> Maybe (Coyoneda f t) Source #

Instances

UpleteMap IntSet Source # 
UpleteMap (IntMap v) Source # 

Methods

adlete :: (Value (IntMap v) -> Maybe (Value (IntMap v))) -> Key (IntMap v) -> IntMap v -> IntMap v Source #

adleteLookup :: (Value (IntMap v) -> (r, Maybe (Value (IntMap v)))) -> Key (IntMap v) -> IntMap v -> (r, IntMap v) Source #

adleteF_ :: Functor f => (Value (IntMap v) -> Coyoneda f (Maybe (Value (IntMap v)))) -> Key (IntMap v) -> IntMap v -> Coyoneda f (IntMap v) Source #

unsafeAdlete :: (Value (IntMap v) -> Maybe (Value (IntMap v))) -> Key (IntMap v) -> IntMap v -> IntMap v Source #

unsafeAdleteLookup :: (Value (IntMap v) -> (r, Maybe (Value (IntMap v)))) -> Key (IntMap v) -> IntMap v -> (r, IntMap v) Source #

unsafeAdleteF_ :: Functor f => (Value (IntMap v) -> Coyoneda f (Maybe (Value (IntMap v)))) -> Key (IntMap v) -> IntMap v -> Coyoneda f (IntMap v) Source #

maybeAdlete :: (Value (IntMap v) -> Maybe (Value (IntMap v))) -> Key (IntMap v) -> IntMap v -> IntMap v Source #

safeAdlete :: (Value (IntMap v) -> Maybe (Value (IntMap v))) -> Key (IntMap v) -> IntMap v -> Maybe (IntMap v) Source #

safeAdleteLookup :: (Value (IntMap v) -> (r, Maybe (Value (IntMap v)))) -> Key (IntMap v) -> IntMap v -> Maybe (r, IntMap v) Source #

safeAdleteF_ :: Functor f => (Value (IntMap v) -> Coyoneda f (Maybe (Value (IntMap v)))) -> Key (IntMap v) -> IntMap v -> Maybe (Coyoneda f (IntMap v)) Source #

Ord a => UpleteMap (Set a) Source # 

Methods

adlete :: (Value (Set a) -> Maybe (Value (Set a))) -> Key (Set a) -> Set a -> Set a Source #

adleteLookup :: (Value (Set a) -> (r, Maybe (Value (Set a)))) -> Key (Set a) -> Set a -> (r, Set a) Source #

adleteF_ :: Functor f => (Value (Set a) -> Coyoneda f (Maybe (Value (Set a)))) -> Key (Set a) -> Set a -> Coyoneda f (Set a) Source #

unsafeAdlete :: (Value (Set a) -> Maybe (Value (Set a))) -> Key (Set a) -> Set a -> Set a Source #

unsafeAdleteLookup :: (Value (Set a) -> (r, Maybe (Value (Set a)))) -> Key (Set a) -> Set a -> (r, Set a) Source #

unsafeAdleteF_ :: Functor f => (Value (Set a) -> Coyoneda f (Maybe (Value (Set a)))) -> Key (Set a) -> Set a -> Coyoneda f (Set a) Source #

maybeAdlete :: (Value (Set a) -> Maybe (Value (Set a))) -> Key (Set a) -> Set a -> Set a Source #

safeAdlete :: (Value (Set a) -> Maybe (Value (Set a))) -> Key (Set a) -> Set a -> Maybe (Set a) Source #

safeAdleteLookup :: (Value (Set a) -> (r, Maybe (Value (Set a)))) -> Key (Set a) -> Set a -> Maybe (r, Set a) Source #

safeAdleteF_ :: Functor f => (Value (Set a) -> Coyoneda f (Maybe (Value (Set a)))) -> Key (Set a) -> Set a -> Maybe (Coyoneda f (Set a)) Source #

(IsLazyMap t, UpleteMap t) => UpleteMap (Lazy t) Source # 

Methods

adlete :: (Value (Lazy t) -> Maybe (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

adleteLookup :: (Value (Lazy t) -> (r, Maybe (Value (Lazy t)))) -> Key (Lazy t) -> Lazy t -> (r, Lazy t) Source #

adleteF_ :: Functor f => (Value (Lazy t) -> Coyoneda f (Maybe (Value (Lazy t)))) -> Key (Lazy t) -> Lazy t -> Coyoneda f (Lazy t) Source #

unsafeAdlete :: (Value (Lazy t) -> Maybe (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

unsafeAdleteLookup :: (Value (Lazy t) -> (r, Maybe (Value (Lazy t)))) -> Key (Lazy t) -> Lazy t -> (r, Lazy t) Source #

unsafeAdleteF_ :: Functor f => (Value (Lazy t) -> Coyoneda f (Maybe (Value (Lazy t)))) -> Key (Lazy t) -> Lazy t -> Coyoneda f (Lazy t) Source #

maybeAdlete :: (Value (Lazy t) -> Maybe (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

safeAdlete :: (Value (Lazy t) -> Maybe (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Maybe (Lazy t) Source #

safeAdleteLookup :: (Value (Lazy t) -> (r, Maybe (Value (Lazy t)))) -> Key (Lazy t) -> Lazy t -> Maybe (r, Lazy t) Source #

safeAdleteF_ :: Functor f => (Value (Lazy t) -> Coyoneda f (Maybe (Value (Lazy t)))) -> Key (Lazy t) -> Lazy t -> Maybe (Coyoneda f (Lazy t)) Source #

UpleteMap (Lazy (IntMap v)) Source # 

Methods

adlete :: (Value (Lazy (IntMap v)) -> Maybe (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

adleteLookup :: (Value (Lazy (IntMap v)) -> (r, Maybe (Value (Lazy (IntMap v))))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (r, Lazy (IntMap v)) Source #

adleteF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f (Maybe (Value (Lazy (IntMap v))))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Coyoneda f (Lazy (IntMap v)) Source #

unsafeAdlete :: (Value (Lazy (IntMap v)) -> Maybe (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

unsafeAdleteLookup :: (Value (Lazy (IntMap v)) -> (r, Maybe (Value (Lazy (IntMap v))))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (r, Lazy (IntMap v)) Source #

unsafeAdleteF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f (Maybe (Value (Lazy (IntMap v))))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Coyoneda f (Lazy (IntMap v)) Source #

maybeAdlete :: (Value (Lazy (IntMap v)) -> Maybe (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

safeAdlete :: (Value (Lazy (IntMap v)) -> Maybe (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Lazy (IntMap v)) Source #

safeAdleteLookup :: (Value (Lazy (IntMap v)) -> (r, Maybe (Value (Lazy (IntMap v))))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (r, Lazy (IntMap v)) Source #

safeAdleteF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f (Maybe (Value (Lazy (IntMap v))))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Coyoneda f (Lazy (IntMap v))) Source #

Ord k => UpleteMap (Lazy (Map k v)) Source # 

Methods

adlete :: (Value (Lazy (Map k v)) -> Maybe (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

adleteLookup :: (Value (Lazy (Map k v)) -> (r, Maybe (Value (Lazy (Map k v))))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> (r, Lazy (Map k v)) Source #

adleteF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f (Maybe (Value (Lazy (Map k v))))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Coyoneda f (Lazy (Map k v)) Source #

unsafeAdlete :: (Value (Lazy (Map k v)) -> Maybe (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

unsafeAdleteLookup :: (Value (Lazy (Map k v)) -> (r, Maybe (Value (Lazy (Map k v))))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> (r, Lazy (Map k v)) Source #

unsafeAdleteF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f (Maybe (Value (Lazy (Map k v))))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Coyoneda f (Lazy (Map k v)) Source #

maybeAdlete :: (Value (Lazy (Map k v)) -> Maybe (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

safeAdlete :: (Value (Lazy (Map k v)) -> Maybe (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Lazy (Map k v)) Source #

safeAdleteLookup :: (Value (Lazy (Map k v)) -> (r, Maybe (Value (Lazy (Map k v))))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (r, Lazy (Map k v)) Source #

safeAdleteF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f (Maybe (Value (Lazy (Map k v))))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Coyoneda f (Lazy (Map k v))) Source #

(IsStrictMap t, UpleteMap t) => UpleteMap (Strict t) Source # 

Methods

adlete :: (Value (Strict t) -> Maybe (Value (Strict t))) -> Key (Strict t) -> Strict t -> Strict t Source #

adleteLookup :: (Value (Strict t) -> (r, Maybe (Value (Strict t)))) -> Key (Strict t) -> Strict t -> (r, Strict t) Source #

adleteF_ :: Functor f => (Value (Strict t) -> Coyoneda f (Maybe (Value (Strict t)))) -> Key (Strict t) -> Strict t -> Coyoneda f (Strict t) Source #

unsafeAdlete :: (Value (Strict t) -> Maybe (Value (Strict t))) -> Key (Strict t) -> Strict t -> Strict t Source #

unsafeAdleteLookup :: (Value (Strict t) -> (r, Maybe (Value (Strict t)))) -> Key (Strict t) -> Strict t -> (r, Strict t) Source #

unsafeAdleteF_ :: Functor f => (Value (Strict t) -> Coyoneda f (Maybe (Value (Strict t)))) -> Key (Strict t) -> Strict t -> Coyoneda f (Strict t) Source #

maybeAdlete :: (Value (Strict t) -> Maybe (Value (Strict t))) -> Key (Strict t) -> Strict t -> Strict t Source #

safeAdlete :: (Value (Strict t) -> Maybe (Value (Strict t))) -> Key (Strict t) -> Strict t -> Maybe (Strict t) Source #

safeAdleteLookup :: (Value (Strict t) -> (r, Maybe (Value (Strict t)))) -> Key (Strict t) -> Strict t -> Maybe (r, Strict t) Source #

safeAdleteF_ :: Functor f => (Value (Strict t) -> Coyoneda f (Maybe (Value (Strict t)))) -> Key (Strict t) -> Strict t -> Maybe (Coyoneda f (Strict t)) Source #

Ord k => UpleteMap (Map k v) Source # 

Methods

adlete :: (Value (Map k v) -> Maybe (Value (Map k v))) -> Key (Map k v) -> Map k v -> Map k v Source #

adleteLookup :: (Value (Map k v) -> (r, Maybe (Value (Map k v)))) -> Key (Map k v) -> Map k v -> (r, Map k v) Source #

adleteF_ :: Functor f => (Value (Map k v) -> Coyoneda f (Maybe (Value (Map k v)))) -> Key (Map k v) -> Map k v -> Coyoneda f (Map k v) Source #

unsafeAdlete :: (Value (Map k v) -> Maybe (Value (Map k v))) -> Key (Map k v) -> Map k v -> Map k v Source #

unsafeAdleteLookup :: (Value (Map k v) -> (r, Maybe (Value (Map k v)))) -> Key (Map k v) -> Map k v -> (r, Map k v) Source #

unsafeAdleteF_ :: Functor f => (Value (Map k v) -> Coyoneda f (Maybe (Value (Map k v)))) -> Key (Map k v) -> Map k v -> Coyoneda f (Map k v) Source #

maybeAdlete :: (Value (Map k v) -> Maybe (Value (Map k v))) -> Key (Map k v) -> Map k v -> Map k v Source #

safeAdlete :: (Value (Map k v) -> Maybe (Value (Map k v))) -> Key (Map k v) -> Map k v -> Maybe (Map k v) Source #

safeAdleteLookup :: (Value (Map k v) -> (r, Maybe (Value (Map k v)))) -> Key (Map k v) -> Map k v -> Maybe (r, Map k v) Source #

safeAdleteF_ :: Functor f => (Value (Map k v) -> Coyoneda f (Maybe (Value (Map k v)))) -> Key (Map k v) -> Map k v -> Maybe (Coyoneda f (Map k v)) Source #

adleteF :: (UpleteMap t, Functor f) => (Value t -> f (Maybe (Value t))) -> Key t -> t -> f t Source #

unsafeAdleteF :: (UpleteMap t, Functor f) => (Value t -> f (Maybe (Value t))) -> Key t -> t -> f t Source #

safeAdleteF :: (UpleteMap t, Functor f) => (Value t -> f (Maybe (Value t))) -> Key t -> t -> Maybe (f t) Source #

class (UpsertMap t, UpleteMap t) => AlterMap t where Source #

AlterMap is a class that represents key-value mappings where one can do inserts, deletes, updates, pretty much everything you expect from a simple key/value store.

Methods

alter :: (Maybe (Value t) -> Maybe (Value t)) -> Key t -> t -> t Source #

alter f k x attempts to gets the value of the key k.

If key k exists, as say it is v, it passes Just v to f.

If key k does not exist, it passes Nothing to f.

If the result of f is Just something, then alter either inserts or updates the key k, inserting if key k previously didn't exist and updating if it did.

If the result of f is Nothing, and the key k did exist, we deleted it.

Otherwise, if the result of f is Nothing, nd the key k did not exist, then do nothing and simply return the structure unmodified.

alterLookup :: (Maybe (Value t) -> (r, Maybe (Value t))) -> Key t -> t -> (r, t) Source #

Like alter, but returns the value both before and after the alteration.

alterF_ :: Functor f => (Maybe (Value t) -> Coyoneda f (Maybe (Value t))) -> Key t -> t -> Coyoneda f t Source #

Instances

AlterMap IntSet Source # 
AlterMap (IntMap v) Source # 

Methods

alter :: (Maybe (Value (IntMap v)) -> Maybe (Value (IntMap v))) -> Key (IntMap v) -> IntMap v -> IntMap v Source #

alterLookup :: (Maybe (Value (IntMap v)) -> (r, Maybe (Value (IntMap v)))) -> Key (IntMap v) -> IntMap v -> (r, IntMap v) Source #

alterF_ :: Functor f => (Maybe (Value (IntMap v)) -> Coyoneda f (Maybe (Value (IntMap v)))) -> Key (IntMap v) -> IntMap v -> Coyoneda f (IntMap v) Source #

Ord a => AlterMap (Set a) Source # 

Methods

alter :: (Maybe (Value (Set a)) -> Maybe (Value (Set a))) -> Key (Set a) -> Set a -> Set a Source #

alterLookup :: (Maybe (Value (Set a)) -> (r, Maybe (Value (Set a)))) -> Key (Set a) -> Set a -> (r, Set a) Source #

alterF_ :: Functor f => (Maybe (Value (Set a)) -> Coyoneda f (Maybe (Value (Set a)))) -> Key (Set a) -> Set a -> Coyoneda f (Set a) Source #

(IsLazyMap t, AlterMap t) => AlterMap (Lazy t) Source # 

Methods

alter :: (Maybe (Value (Lazy t)) -> Maybe (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

alterLookup :: (Maybe (Value (Lazy t)) -> (r, Maybe (Value (Lazy t)))) -> Key (Lazy t) -> Lazy t -> (r, Lazy t) Source #

alterF_ :: Functor f => (Maybe (Value (Lazy t)) -> Coyoneda f (Maybe (Value (Lazy t)))) -> Key (Lazy t) -> Lazy t -> Coyoneda f (Lazy t) Source #

AlterMap (Lazy (IntMap v)) Source # 

Methods

alter :: (Maybe (Value (Lazy (IntMap v))) -> Maybe (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

alterLookup :: (Maybe (Value (Lazy (IntMap v))) -> (r, Maybe (Value (Lazy (IntMap v))))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (r, Lazy (IntMap v)) Source #

alterF_ :: Functor f => (Maybe (Value (Lazy (IntMap v))) -> Coyoneda f (Maybe (Value (Lazy (IntMap v))))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Coyoneda f (Lazy (IntMap v)) Source #

Ord k => AlterMap (Lazy (Map k v)) Source # 

Methods

alter :: (Maybe (Value (Lazy (Map k v))) -> Maybe (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

alterLookup :: (Maybe (Value (Lazy (Map k v))) -> (r, Maybe (Value (Lazy (Map k v))))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> (r, Lazy (Map k v)) Source #

alterF_ :: Functor f => (Maybe (Value (Lazy (Map k v))) -> Coyoneda f (Maybe (Value (Lazy (Map k v))))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Coyoneda f (Lazy (Map k v)) Source #

(IsStrictMap t, AlterMap t) => AlterMap (Strict t) Source # 

Methods

alter :: (Maybe (Value (Strict t)) -> Maybe (Value (Strict t))) -> Key (Strict t) -> Strict t -> Strict t Source #

alterLookup :: (Maybe (Value (Strict t)) -> (r, Maybe (Value (Strict t)))) -> Key (Strict t) -> Strict t -> (r, Strict t) Source #

alterF_ :: Functor f => (Maybe (Value (Strict t)) -> Coyoneda f (Maybe (Value (Strict t)))) -> Key (Strict t) -> Strict t -> Coyoneda f (Strict t) Source #

Ord k => AlterMap (Map k v) Source # 

Methods

alter :: (Maybe (Value (Map k v)) -> Maybe (Value (Map k v))) -> Key (Map k v) -> Map k v -> Map k v Source #

alterLookup :: (Maybe (Value (Map k v)) -> (r, Maybe (Value (Map k v)))) -> Key (Map k v) -> Map k v -> (r, Map k v) Source #

alterF_ :: Functor f => (Maybe (Value (Map k v)) -> Coyoneda f (Maybe (Value (Map k v)))) -> Key (Map k v) -> Map k v -> Coyoneda f (Map k v) Source #

alterF :: (AlterMap t, Functor f) => (Maybe (Value t) -> f (Maybe (Value t))) -> Key t -> t -> f t Source #

newtype Strict t Source #

For certain types like maps in the standard containers library that ships with GHC, the strict version of the data type: Map, and the lazy version of the data type: Map, are actually the exact same type. In this case, they're just reexports of the same type.

That's fine when one has two separate modules with strict and lazy versions one can explicitly use, but the choice can't be automatic based on the type.

As a result, there's no way one can tell whether to use strict or lazy functions on the data. Wrapping these types in either Strict or Lazy specifies how these types are intend to be worked on.

By default however, if one doesn't wrap, the Strict version is used.

Constructors

Strict 

Fields

Instances

(IsStrictMap t, AlterMap t) => AlterMap (Strict t) Source # 

Methods

alter :: (Maybe (Value (Strict t)) -> Maybe (Value (Strict t))) -> Key (Strict t) -> Strict t -> Strict t Source #

alterLookup :: (Maybe (Value (Strict t)) -> (r, Maybe (Value (Strict t)))) -> Key (Strict t) -> Strict t -> (r, Strict t) Source #

alterF_ :: Functor f => (Maybe (Value (Strict t)) -> Coyoneda f (Maybe (Value (Strict t)))) -> Key (Strict t) -> Strict t -> Coyoneda f (Strict t) Source #

(IsStrictMap t, UpleteMap t) => UpleteMap (Strict t) Source # 

Methods

adlete :: (Value (Strict t) -> Maybe (Value (Strict t))) -> Key (Strict t) -> Strict t -> Strict t Source #

adleteLookup :: (Value (Strict t) -> (r, Maybe (Value (Strict t)))) -> Key (Strict t) -> Strict t -> (r, Strict t) Source #

adleteF_ :: Functor f => (Value (Strict t) -> Coyoneda f (Maybe (Value (Strict t)))) -> Key (Strict t) -> Strict t -> Coyoneda f (Strict t) Source #

unsafeAdlete :: (Value (Strict t) -> Maybe (Value (Strict t))) -> Key (Strict t) -> Strict t -> Strict t Source #

unsafeAdleteLookup :: (Value (Strict t) -> (r, Maybe (Value (Strict t)))) -> Key (Strict t) -> Strict t -> (r, Strict t) Source #

unsafeAdleteF_ :: Functor f => (Value (Strict t) -> Coyoneda f (Maybe (Value (Strict t)))) -> Key (Strict t) -> Strict t -> Coyoneda f (Strict t) Source #

maybeAdlete :: (Value (Strict t) -> Maybe (Value (Strict t))) -> Key (Strict t) -> Strict t -> Strict t Source #

safeAdlete :: (Value (Strict t) -> Maybe (Value (Strict t))) -> Key (Strict t) -> Strict t -> Maybe (Strict t) Source #

safeAdleteLookup :: (Value (Strict t) -> (r, Maybe (Value (Strict t)))) -> Key (Strict t) -> Strict t -> Maybe (r, Strict t) Source #

safeAdleteF_ :: Functor f => (Value (Strict t) -> Coyoneda f (Maybe (Value (Strict t)))) -> Key (Strict t) -> Strict t -> Maybe (Coyoneda f (Strict t)) Source #

(IsStrictMap t, UpsertMap t) => UpsertMap (Strict t) Source # 

Methods

upsert :: Key (Strict t) -> Value (Strict t) -> Strict t -> Strict t Source #

upsertLookup :: Key (Strict t) -> Value (Strict t) -> Strict t -> (Maybe (Value (Strict t)), Strict t) Source #

adsert :: (Maybe (Value (Strict t)) -> Value (Strict t)) -> Key (Strict t) -> Strict t -> Strict t Source #

adsertLookup :: (Maybe (Value (Strict t)) -> (r, Value (Strict t))) -> Key (Strict t) -> Strict t -> (r, Strict t) Source #

adsertF_ :: Functor f => (Maybe (Value (Strict t)) -> Coyoneda f (Value (Strict t))) -> Key (Strict t) -> Strict t -> Coyoneda f (Strict t) Source #

(IsStrictMap t, DeleteMap t) => DeleteMap (Strict t) Source # 

Methods

delete :: Key (Strict t) -> Strict t -> Strict t Source #

deleteLookup :: Key (Strict t) -> Strict t -> (Value (Strict t), Strict t) Source #

unsafeDelete :: Key (Strict t) -> Strict t -> Strict t Source #

unsafeDeleteLookup :: Key (Strict t) -> Strict t -> (Value (Strict t), Strict t) Source #

maybeDelete :: Key (Strict t) -> Strict t -> Strict t Source #

safeDelete :: Key (Strict t) -> Strict t -> Maybe (Strict t) Source #

safeDeleteLookup :: Key (Strict t) -> Strict t -> Maybe (Value (Strict t), Strict t) Source #

optDelete :: (Value (Strict t) -> Bool) -> Key (Strict t) -> Strict t -> Strict t Source #

optDeleteLookup :: (Value (Strict t) -> (r, Bool)) -> Key (Strict t) -> Strict t -> (r, Strict t) Source #

optDeleteF_ :: Functor f => (Value (Strict t) -> Coyoneda f Bool) -> Key (Strict t) -> Strict t -> Coyoneda f (Strict t) Source #

unsafeOptDelete :: (Value (Strict t) -> Bool) -> Key (Strict t) -> Strict t -> Strict t Source #

unsafeOptDeleteLookup :: (Value (Strict t) -> (r, Bool)) -> Key (Strict t) -> Strict t -> (r, Strict t) Source #

unsafeOptDeleteF_ :: Functor f => (Value (Strict t) -> Coyoneda f Bool) -> Key (Strict t) -> Strict t -> Coyoneda f (Strict t) Source #

maybeOptDelete :: (Value (Strict t) -> Bool) -> Key (Strict t) -> Strict t -> Strict t Source #

safeOptDelete :: (Value (Strict t) -> Bool) -> Key (Strict t) -> Strict t -> Maybe (Strict t) Source #

safeOptDeleteLookup :: (Value (Strict t) -> (r, Bool)) -> Key (Strict t) -> Strict t -> Maybe (r, Strict t) Source #

safeOptDeleteF_ :: Functor f => (Value (Strict t) -> Coyoneda f Bool) -> Key (Strict t) -> Strict t -> Maybe (Coyoneda f (Strict t)) Source #

(IsStrictMap t, InsertMap t) => InsertMap (Strict t) Source # 

Methods

insert :: Key (Strict t) -> Value (Strict t) -> Strict t -> Strict t Source #

unsafeInsert :: Key (Strict t) -> Value (Strict t) -> Strict t -> Strict t Source #

maybeInsert :: Key (Strict t) -> Value (Strict t) -> Strict t -> Strict t Source #

safeInsert :: Key (Strict t) -> Value (Strict t) -> Strict t -> Maybe (Strict t) Source #

(IsStrictMap t, UpdateMap t) => UpdateMap (Strict t) Source # 

Methods

update :: Key (Strict t) -> Value (Strict t) -> Strict t -> Strict t Source #

updateLookup :: Key (Strict t) -> Value (Strict t) -> Strict t -> (Value (Strict t), Strict t) Source #

unsafeUpdate :: Key (Strict t) -> Value (Strict t) -> Strict t -> Strict t Source #

unsafeUpdateLookup :: Key (Strict t) -> Value (Strict t) -> Strict t -> (Value (Strict t), Strict t) Source #

maybeUpdate :: Key (Strict t) -> Value (Strict t) -> Strict t -> Strict t Source #

safeUpdate :: Key (Strict t) -> Value (Strict t) -> Strict t -> Maybe (Strict t) Source #

safeUpdateLookup :: Key (Strict t) -> Value (Strict t) -> Strict t -> Maybe (Value (Strict t), Strict t) Source #

adjust :: (Value (Strict t) -> Value (Strict t)) -> Key (Strict t) -> Strict t -> Strict t Source #

adjustLookup :: (Value (Strict t) -> (r, Value (Strict t))) -> Key (Strict t) -> Strict t -> (r, Strict t) Source #

adjustF_ :: Functor f => (Value (Strict t) -> Coyoneda f (Value (Strict t))) -> Key (Strict t) -> Strict t -> Coyoneda f (Strict t) Source #

unsafeAdjust :: (Value (Strict t) -> Value (Strict t)) -> Key (Strict t) -> Strict t -> Strict t Source #

unsafeAdjustLookup :: (Value (Strict t) -> (r, Value (Strict t))) -> Key (Strict t) -> Strict t -> (r, Strict t) Source #

unsafeAdjustF_ :: Functor f => (Value (Strict t) -> Coyoneda f (Value (Strict t))) -> Key (Strict t) -> Strict t -> Coyoneda f (Strict t) Source #

maybeAdjust :: (Value (Strict t) -> Value (Strict t)) -> Key (Strict t) -> Strict t -> Strict t Source #

safeAdjust :: (Value (Strict t) -> Value (Strict t)) -> Key (Strict t) -> Strict t -> Maybe (Strict t) Source #

safeAdjustLookup :: (Value (Strict t) -> (r, Value (Strict t))) -> Key (Strict t) -> Strict t -> Maybe (r, Strict t) Source #

safeAdjustF_ :: Functor f => (Value (Strict t) -> Coyoneda f (Value (Strict t))) -> Key (Strict t) -> Strict t -> Maybe (Coyoneda f (Strict t)) Source #

(IsStrictMap t, LookupMap t) => LookupMap (Strict t) Source # 

Methods

lookup :: Key (Strict t) -> Strict t -> Maybe (Value (Strict t)) Source #

index :: Key (Strict t) -> Strict t -> Value (Strict t) Source #

unsafeIndex :: Key (Strict t) -> Strict t -> Value (Strict t) Source #

member :: Key (Strict t) -> Strict t -> Bool Source #

notMember :: Key (Strict t) -> Strict t -> Bool Source #

type Value (Strict t) Source # 
type Value (Strict t) = Value t
type Key (Strict t) Source # 
type Key (Strict t) = Key t

newtype Lazy t Source #

See Strict documentation for a discussion of the Lazy wrapper.

Constructors

Lazy 

Fields

Instances

(IsLazyMap t, AlterMap t) => AlterMap (Lazy t) Source # 

Methods

alter :: (Maybe (Value (Lazy t)) -> Maybe (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

alterLookup :: (Maybe (Value (Lazy t)) -> (r, Maybe (Value (Lazy t)))) -> Key (Lazy t) -> Lazy t -> (r, Lazy t) Source #

alterF_ :: Functor f => (Maybe (Value (Lazy t)) -> Coyoneda f (Maybe (Value (Lazy t)))) -> Key (Lazy t) -> Lazy t -> Coyoneda f (Lazy t) Source #

AlterMap (Lazy (IntMap v)) Source # 

Methods

alter :: (Maybe (Value (Lazy (IntMap v))) -> Maybe (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

alterLookup :: (Maybe (Value (Lazy (IntMap v))) -> (r, Maybe (Value (Lazy (IntMap v))))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (r, Lazy (IntMap v)) Source #

alterF_ :: Functor f => (Maybe (Value (Lazy (IntMap v))) -> Coyoneda f (Maybe (Value (Lazy (IntMap v))))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Coyoneda f (Lazy (IntMap v)) Source #

Ord k => AlterMap (Lazy (Map k v)) Source # 

Methods

alter :: (Maybe (Value (Lazy (Map k v))) -> Maybe (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

alterLookup :: (Maybe (Value (Lazy (Map k v))) -> (r, Maybe (Value (Lazy (Map k v))))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> (r, Lazy (Map k v)) Source #

alterF_ :: Functor f => (Maybe (Value (Lazy (Map k v))) -> Coyoneda f (Maybe (Value (Lazy (Map k v))))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Coyoneda f (Lazy (Map k v)) Source #

(IsLazyMap t, UpleteMap t) => UpleteMap (Lazy t) Source # 

Methods

adlete :: (Value (Lazy t) -> Maybe (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

adleteLookup :: (Value (Lazy t) -> (r, Maybe (Value (Lazy t)))) -> Key (Lazy t) -> Lazy t -> (r, Lazy t) Source #

adleteF_ :: Functor f => (Value (Lazy t) -> Coyoneda f (Maybe (Value (Lazy t)))) -> Key (Lazy t) -> Lazy t -> Coyoneda f (Lazy t) Source #

unsafeAdlete :: (Value (Lazy t) -> Maybe (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

unsafeAdleteLookup :: (Value (Lazy t) -> (r, Maybe (Value (Lazy t)))) -> Key (Lazy t) -> Lazy t -> (r, Lazy t) Source #

unsafeAdleteF_ :: Functor f => (Value (Lazy t) -> Coyoneda f (Maybe (Value (Lazy t)))) -> Key (Lazy t) -> Lazy t -> Coyoneda f (Lazy t) Source #

maybeAdlete :: (Value (Lazy t) -> Maybe (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

safeAdlete :: (Value (Lazy t) -> Maybe (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Maybe (Lazy t) Source #

safeAdleteLookup :: (Value (Lazy t) -> (r, Maybe (Value (Lazy t)))) -> Key (Lazy t) -> Lazy t -> Maybe (r, Lazy t) Source #

safeAdleteF_ :: Functor f => (Value (Lazy t) -> Coyoneda f (Maybe (Value (Lazy t)))) -> Key (Lazy t) -> Lazy t -> Maybe (Coyoneda f (Lazy t)) Source #

UpleteMap (Lazy (IntMap v)) Source # 

Methods

adlete :: (Value (Lazy (IntMap v)) -> Maybe (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

adleteLookup :: (Value (Lazy (IntMap v)) -> (r, Maybe (Value (Lazy (IntMap v))))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (r, Lazy (IntMap v)) Source #

adleteF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f (Maybe (Value (Lazy (IntMap v))))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Coyoneda f (Lazy (IntMap v)) Source #

unsafeAdlete :: (Value (Lazy (IntMap v)) -> Maybe (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

unsafeAdleteLookup :: (Value (Lazy (IntMap v)) -> (r, Maybe (Value (Lazy (IntMap v))))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (r, Lazy (IntMap v)) Source #

unsafeAdleteF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f (Maybe (Value (Lazy (IntMap v))))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Coyoneda f (Lazy (IntMap v)) Source #

maybeAdlete :: (Value (Lazy (IntMap v)) -> Maybe (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

safeAdlete :: (Value (Lazy (IntMap v)) -> Maybe (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Lazy (IntMap v)) Source #

safeAdleteLookup :: (Value (Lazy (IntMap v)) -> (r, Maybe (Value (Lazy (IntMap v))))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (r, Lazy (IntMap v)) Source #

safeAdleteF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f (Maybe (Value (Lazy (IntMap v))))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Coyoneda f (Lazy (IntMap v))) Source #

Ord k => UpleteMap (Lazy (Map k v)) Source # 

Methods

adlete :: (Value (Lazy (Map k v)) -> Maybe (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

adleteLookup :: (Value (Lazy (Map k v)) -> (r, Maybe (Value (Lazy (Map k v))))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> (r, Lazy (Map k v)) Source #

adleteF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f (Maybe (Value (Lazy (Map k v))))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Coyoneda f (Lazy (Map k v)) Source #

unsafeAdlete :: (Value (Lazy (Map k v)) -> Maybe (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

unsafeAdleteLookup :: (Value (Lazy (Map k v)) -> (r, Maybe (Value (Lazy (Map k v))))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> (r, Lazy (Map k v)) Source #

unsafeAdleteF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f (Maybe (Value (Lazy (Map k v))))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Coyoneda f (Lazy (Map k v)) Source #

maybeAdlete :: (Value (Lazy (Map k v)) -> Maybe (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

safeAdlete :: (Value (Lazy (Map k v)) -> Maybe (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Lazy (Map k v)) Source #

safeAdleteLookup :: (Value (Lazy (Map k v)) -> (r, Maybe (Value (Lazy (Map k v))))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (r, Lazy (Map k v)) Source #

safeAdleteF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f (Maybe (Value (Lazy (Map k v))))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Coyoneda f (Lazy (Map k v))) Source #

(IsLazyMap t, UpsertMap t) => UpsertMap (Lazy t) Source # 

Methods

upsert :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Lazy t Source #

upsertLookup :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> (Maybe (Value (Lazy t)), Lazy t) Source #

adsert :: (Maybe (Value (Lazy t)) -> Value (Lazy t)) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

adsertLookup :: (Maybe (Value (Lazy t)) -> (r, Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> (r, Lazy t) Source #

adsertF_ :: Functor f => (Maybe (Value (Lazy t)) -> Coyoneda f (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Coyoneda f (Lazy t) Source #

UpsertMap (Lazy (IntMap v)) Source # 

Methods

upsert :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

upsertLookup :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> (Maybe (Value (Lazy (IntMap v))), Lazy (IntMap v)) Source #

adsert :: (Maybe (Value (Lazy (IntMap v))) -> Value (Lazy (IntMap v))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

adsertLookup :: (Maybe (Value (Lazy (IntMap v))) -> (r, Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (r, Lazy (IntMap v)) Source #

adsertF_ :: Functor f => (Maybe (Value (Lazy (IntMap v))) -> Coyoneda f (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Coyoneda f (Lazy (IntMap v)) Source #

Ord k => UpsertMap (Lazy (Map k v)) Source # 

Methods

upsert :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

upsertLookup :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> (Maybe (Value (Lazy (Map k v))), Lazy (Map k v)) Source #

adsert :: (Maybe (Value (Lazy (Map k v))) -> Value (Lazy (Map k v))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

adsertLookup :: (Maybe (Value (Lazy (Map k v))) -> (r, Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> (r, Lazy (Map k v)) Source #

adsertF_ :: Functor f => (Maybe (Value (Lazy (Map k v))) -> Coyoneda f (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Coyoneda f (Lazy (Map k v)) Source #

(IsLazyMap t, DeleteMap t) => DeleteMap (Lazy t) Source # 

Methods

delete :: Key (Lazy t) -> Lazy t -> Lazy t Source #

deleteLookup :: Key (Lazy t) -> Lazy t -> (Value (Lazy t), Lazy t) Source #

unsafeDelete :: Key (Lazy t) -> Lazy t -> Lazy t Source #

unsafeDeleteLookup :: Key (Lazy t) -> Lazy t -> (Value (Lazy t), Lazy t) Source #

maybeDelete :: Key (Lazy t) -> Lazy t -> Lazy t Source #

safeDelete :: Key (Lazy t) -> Lazy t -> Maybe (Lazy t) Source #

safeDeleteLookup :: Key (Lazy t) -> Lazy t -> Maybe (Value (Lazy t), Lazy t) Source #

optDelete :: (Value (Lazy t) -> Bool) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

optDeleteLookup :: (Value (Lazy t) -> (r, Bool)) -> Key (Lazy t) -> Lazy t -> (r, Lazy t) Source #

optDeleteF_ :: Functor f => (Value (Lazy t) -> Coyoneda f Bool) -> Key (Lazy t) -> Lazy t -> Coyoneda f (Lazy t) Source #

unsafeOptDelete :: (Value (Lazy t) -> Bool) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

unsafeOptDeleteLookup :: (Value (Lazy t) -> (r, Bool)) -> Key (Lazy t) -> Lazy t -> (r, Lazy t) Source #

unsafeOptDeleteF_ :: Functor f => (Value (Lazy t) -> Coyoneda f Bool) -> Key (Lazy t) -> Lazy t -> Coyoneda f (Lazy t) Source #

maybeOptDelete :: (Value (Lazy t) -> Bool) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

safeOptDelete :: (Value (Lazy t) -> Bool) -> Key (Lazy t) -> Lazy t -> Maybe (Lazy t) Source #

safeOptDeleteLookup :: (Value (Lazy t) -> (r, Bool)) -> Key (Lazy t) -> Lazy t -> Maybe (r, Lazy t) Source #

safeOptDeleteF_ :: Functor f => (Value (Lazy t) -> Coyoneda f Bool) -> Key (Lazy t) -> Lazy t -> Maybe (Coyoneda f (Lazy t)) Source #

DeleteMap (Lazy (IntMap v)) Source # 

Methods

delete :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

deleteLookup :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (Value (Lazy (IntMap v)), Lazy (IntMap v)) Source #

unsafeDelete :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

unsafeDeleteLookup :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (Value (Lazy (IntMap v)), Lazy (IntMap v)) Source #

maybeDelete :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

safeDelete :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Lazy (IntMap v)) Source #

safeDeleteLookup :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Value (Lazy (IntMap v)), Lazy (IntMap v)) Source #

optDelete :: (Value (Lazy (IntMap v)) -> Bool) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

optDeleteLookup :: (Value (Lazy (IntMap v)) -> (r, Bool)) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (r, Lazy (IntMap v)) Source #

optDeleteF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f Bool) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Coyoneda f (Lazy (IntMap v)) Source #

unsafeOptDelete :: (Value (Lazy (IntMap v)) -> Bool) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

unsafeOptDeleteLookup :: (Value (Lazy (IntMap v)) -> (r, Bool)) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (r, Lazy (IntMap v)) Source #

unsafeOptDeleteF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f Bool) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Coyoneda f (Lazy (IntMap v)) Source #

maybeOptDelete :: (Value (Lazy (IntMap v)) -> Bool) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

safeOptDelete :: (Value (Lazy (IntMap v)) -> Bool) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Lazy (IntMap v)) Source #

safeOptDeleteLookup :: (Value (Lazy (IntMap v)) -> (r, Bool)) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (r, Lazy (IntMap v)) Source #

safeOptDeleteF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f Bool) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Coyoneda f (Lazy (IntMap v))) Source #

Ord k => DeleteMap (Lazy (Map k v)) Source # 

Methods

delete :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

deleteLookup :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> (Value (Lazy (Map k v)), Lazy (Map k v)) Source #

unsafeDelete :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

unsafeDeleteLookup :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> (Value (Lazy (Map k v)), Lazy (Map k v)) Source #

maybeDelete :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

safeDelete :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Lazy (Map k v)) Source #

safeDeleteLookup :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Value (Lazy (Map k v)), Lazy (Map k v)) Source #

optDelete :: (Value (Lazy (Map k v)) -> Bool) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

optDeleteLookup :: (Value (Lazy (Map k v)) -> (r, Bool)) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> (r, Lazy (Map k v)) Source #

optDeleteF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f Bool) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Coyoneda f (Lazy (Map k v)) Source #

unsafeOptDelete :: (Value (Lazy (Map k v)) -> Bool) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

unsafeOptDeleteLookup :: (Value (Lazy (Map k v)) -> (r, Bool)) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> (r, Lazy (Map k v)) Source #

unsafeOptDeleteF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f Bool) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Coyoneda f (Lazy (Map k v)) Source #

maybeOptDelete :: (Value (Lazy (Map k v)) -> Bool) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

safeOptDelete :: (Value (Lazy (Map k v)) -> Bool) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Lazy (Map k v)) Source #

safeOptDeleteLookup :: (Value (Lazy (Map k v)) -> (r, Bool)) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (r, Lazy (Map k v)) Source #

safeOptDeleteF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f Bool) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Coyoneda f (Lazy (Map k v))) Source #

(IsLazyMap t, InsertMap t) => InsertMap (Lazy t) Source # 

Methods

insert :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Lazy t Source #

unsafeInsert :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Lazy t Source #

maybeInsert :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Lazy t Source #

safeInsert :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Maybe (Lazy t) Source #

InsertMap (Lazy (IntMap v)) Source # 

Methods

insert :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

unsafeInsert :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

maybeInsert :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

safeInsert :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Lazy (IntMap v)) Source #

Ord k => InsertMap (Lazy (Map k v)) Source # 

Methods

insert :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

unsafeInsert :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

maybeInsert :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

safeInsert :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Lazy (Map k v)) Source #

(IsLazyMap t, UpdateMap t) => UpdateMap (Lazy t) Source # 

Methods

update :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Lazy t Source #

updateLookup :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> (Value (Lazy t), Lazy t) Source #

unsafeUpdate :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Lazy t Source #

unsafeUpdateLookup :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> (Value (Lazy t), Lazy t) Source #

maybeUpdate :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Lazy t Source #

safeUpdate :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Maybe (Lazy t) Source #

safeUpdateLookup :: Key (Lazy t) -> Value (Lazy t) -> Lazy t -> Maybe (Value (Lazy t), Lazy t) Source #

adjust :: (Value (Lazy t) -> Value (Lazy t)) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

adjustLookup :: (Value (Lazy t) -> (r, Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> (r, Lazy t) Source #

adjustF_ :: Functor f => (Value (Lazy t) -> Coyoneda f (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Coyoneda f (Lazy t) Source #

unsafeAdjust :: (Value (Lazy t) -> Value (Lazy t)) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

unsafeAdjustLookup :: (Value (Lazy t) -> (r, Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> (r, Lazy t) Source #

unsafeAdjustF_ :: Functor f => (Value (Lazy t) -> Coyoneda f (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Coyoneda f (Lazy t) Source #

maybeAdjust :: (Value (Lazy t) -> Value (Lazy t)) -> Key (Lazy t) -> Lazy t -> Lazy t Source #

safeAdjust :: (Value (Lazy t) -> Value (Lazy t)) -> Key (Lazy t) -> Lazy t -> Maybe (Lazy t) Source #

safeAdjustLookup :: (Value (Lazy t) -> (r, Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Maybe (r, Lazy t) Source #

safeAdjustF_ :: Functor f => (Value (Lazy t) -> Coyoneda f (Value (Lazy t))) -> Key (Lazy t) -> Lazy t -> Maybe (Coyoneda f (Lazy t)) Source #

UpdateMap (Lazy (IntMap v)) Source # 

Methods

update :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

updateLookup :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> (Value (Lazy (IntMap v)), Lazy (IntMap v)) Source #

unsafeUpdate :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

unsafeUpdateLookup :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> (Value (Lazy (IntMap v)), Lazy (IntMap v)) Source #

maybeUpdate :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

safeUpdate :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Lazy (IntMap v)) Source #

safeUpdateLookup :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Value (Lazy (IntMap v)), Lazy (IntMap v)) Source #

adjust :: (Value (Lazy (IntMap v)) -> Value (Lazy (IntMap v))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

adjustLookup :: (Value (Lazy (IntMap v)) -> (r, Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (r, Lazy (IntMap v)) Source #

adjustF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Coyoneda f (Lazy (IntMap v)) Source #

unsafeAdjust :: (Value (Lazy (IntMap v)) -> Value (Lazy (IntMap v))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

unsafeAdjustLookup :: (Value (Lazy (IntMap v)) -> (r, Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> (r, Lazy (IntMap v)) Source #

unsafeAdjustF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Coyoneda f (Lazy (IntMap v)) Source #

maybeAdjust :: (Value (Lazy (IntMap v)) -> Value (Lazy (IntMap v))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Lazy (IntMap v) Source #

safeAdjust :: (Value (Lazy (IntMap v)) -> Value (Lazy (IntMap v))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Lazy (IntMap v)) Source #

safeAdjustLookup :: (Value (Lazy (IntMap v)) -> (r, Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (r, Lazy (IntMap v)) Source #

safeAdjustF_ :: Functor f => (Value (Lazy (IntMap v)) -> Coyoneda f (Value (Lazy (IntMap v)))) -> Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Coyoneda f (Lazy (IntMap v))) Source #

Ord k => UpdateMap (Lazy (Map k v)) Source # 

Methods

update :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

updateLookup :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> (Value (Lazy (Map k v)), Lazy (Map k v)) Source #

unsafeUpdate :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

unsafeUpdateLookup :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> (Value (Lazy (Map k v)), Lazy (Map k v)) Source #

maybeUpdate :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

safeUpdate :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Lazy (Map k v)) Source #

safeUpdateLookup :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Value (Lazy (Map k v)), Lazy (Map k v)) Source #

adjust :: (Value (Lazy (Map k v)) -> Value (Lazy (Map k v))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

adjustLookup :: (Value (Lazy (Map k v)) -> (r, Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> (r, Lazy (Map k v)) Source #

adjustF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Coyoneda f (Lazy (Map k v)) Source #

unsafeAdjust :: (Value (Lazy (Map k v)) -> Value (Lazy (Map k v))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

unsafeAdjustLookup :: (Value (Lazy (Map k v)) -> (r, Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> (r, Lazy (Map k v)) Source #

unsafeAdjustF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Coyoneda f (Lazy (Map k v)) Source #

maybeAdjust :: (Value (Lazy (Map k v)) -> Value (Lazy (Map k v))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Lazy (Map k v) Source #

safeAdjust :: (Value (Lazy (Map k v)) -> Value (Lazy (Map k v))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Lazy (Map k v)) Source #

safeAdjustLookup :: (Value (Lazy (Map k v)) -> (r, Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (r, Lazy (Map k v)) Source #

safeAdjustF_ :: Functor f => (Value (Lazy (Map k v)) -> Coyoneda f (Value (Lazy (Map k v)))) -> Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Coyoneda f (Lazy (Map k v))) Source #

SingletonMap (Lazy (IntMap v)) Source # 

Methods

singleton :: Key (Lazy (IntMap v)) -> Value (Lazy (IntMap v)) -> Lazy (IntMap v) Source #

Ord k => SingletonMap (Lazy (Map k v)) Source # 

Methods

singleton :: Key (Lazy (Map k v)) -> Value (Lazy (Map k v)) -> Lazy (Map k v) Source #

(IsLazyMap t, LookupMap t) => LookupMap (Lazy t) Source # 

Methods

lookup :: Key (Lazy t) -> Lazy t -> Maybe (Value (Lazy t)) Source #

index :: Key (Lazy t) -> Lazy t -> Value (Lazy t) Source #

unsafeIndex :: Key (Lazy t) -> Lazy t -> Value (Lazy t) Source #

member :: Key (Lazy t) -> Lazy t -> Bool Source #

notMember :: Key (Lazy t) -> Lazy t -> Bool Source #

LookupMap (Lazy (IntMap v)) Source # 

Methods

lookup :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Maybe (Value (Lazy (IntMap v))) Source #

index :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Value (Lazy (IntMap v)) Source #

unsafeIndex :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Value (Lazy (IntMap v)) Source #

member :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Bool Source #

notMember :: Key (Lazy (IntMap v)) -> Lazy (IntMap v) -> Bool Source #

Ord k => LookupMap (Lazy (Map k v)) Source # 

Methods

lookup :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Maybe (Value (Lazy (Map k v))) Source #

index :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Value (Lazy (Map k v)) Source #

unsafeIndex :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Value (Lazy (Map k v)) Source #

member :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Bool Source #

notMember :: Key (Lazy (Map k v)) -> Lazy (Map k v) -> Bool Source #

type Value (Lazy t) Source # 
type Value (Lazy t) = Value t
type Value (Lazy t) Source # 
type Value (Lazy t) = Value t
type Key (Lazy t) Source # 
type Key (Lazy t) = Key t
type Key (Lazy t) Source # 
type Key (Lazy t) = Key t

(!) :: LookupMap t => t -> Key t -> Value t Source #

fromCoyonedaTransform :: Functor f1 => ((a1 -> Coyoneda f2 a2) -> t1 -> t2 -> Coyoneda f1 a3) -> (a1 -> f2 a2) -> t1 -> t2 -> f1 a3 Source #

fromCoyonedaTransformF :: (Functor f1, Functor f3) => ((a1 -> Coyoneda f2 a2) -> t1 -> t2 -> f3 (Coyoneda f1 a3)) -> (a1 -> f2 a2) -> t1 -> t2 -> f3 (f1 a3) Source #

toCoyonedaTransform :: Functor f => (forall f'. Functor f' => (a1 -> f' a2) -> t1 -> t2 -> f' a3) -> (a1 -> Coyoneda f a2) -> t1 -> t2 -> Coyoneda f a3 Source #

toCoyonedaTransformF :: Functor f => (forall f'. Functor f' => (a1 -> f' a2) -> t1 -> t2 -> f3 (f' a3)) -> (a1 -> Coyoneda f a2) -> t1 -> t2 -> f3 (Coyoneda f a3) Source #