references-0.2.1.1: Generalization of lenses, folds and traversals to handle monads and addition.

Safe HaskellSafe-Inferred

Control.Reference.Operators

Contents

Description

Common operators for references. References bind the types of the read and write monads of a reference.

The naming of the operators follows the given convetions:

  • There are four kinds of operator for every type of reference. The operators are either getters (^_), setters (_=), monadic updaters (_~), pure updaters (_-) or action performers (_|). The _ will be replaced with the signs of the monads accessable.
  • There are pure operators for Lens (.), partial operators for Partial lenses (?), operators for Traversal (*), and operators that work inside IO for IOLens (!).
  • Different reference types can be combined, the outermost monad is the first character. Example: Partial IO lens (?!). But partial lens and traversal combined is simply a traversal.
  • Generic operators (#) do not bind the types of the monads, so they must disambiguated manually.

Synopsis

Getters

(^#) :: RefMonads w r => s -> Reference w r s t a b -> r aSource

Gets the referenced data in the monad of the lens. Does not bind the type of the writer monad, so the reference must have its type disambiguated.

(^.) :: s -> Lens' s t a b -> aSource

Pure version of ^#

(^?) :: s -> Partial' s t a b -> Maybe aSource

Partial version of ^#

(^*) :: s -> Traversal' s t a b -> [a]Source

Traversal version of ^#

(^!) :: s -> IOLens' s t a b -> IO aSource

IO version of ^#

(^?!) :: s -> IOPartial' s t a b -> IO (Maybe a)Source

IO partial version of ^#

(^*!) :: s -> IOTraversal' s t a b -> IO [a]Source

IO traversal version of ^#

Setters

(#=) :: Reference w r s t a b -> b -> s -> w tSource

Sets the referenced data to the given pure value in the monad of the reference.

Does not bind the type of the reader monad, so the reference must have its type disambiguated.

(.=) :: Lens' s t a b -> b -> s -> tSource

Pure version of '#='

(?=) :: Partial' s t a b -> b -> s -> tSource

Partial version of '#='

(*=) :: Traversal' s t a b -> b -> s -> tSource

Traversal version of '#='

(!=) :: IOLens' s t a b -> b -> s -> IO tSource

IO version of '#='

(?!=) :: IOPartial' s t a b -> b -> s -> IO tSource

Partial IO version of '#='

(*!=) :: IOTraversal' s t a b -> b -> s -> IO tSource

Traversal IO version of '#='

Updaters

(#~) :: Reference w r s t a b -> (a -> w b) -> s -> w tSource

Applies the given monadic function on the referenced data in the monad of the lens.

Does not bind the type of the reader monad, so the reference must have its type disambiguated.

(.~) :: Lens' s t a b -> (a -> Identity b) -> s -> tSource

Pure version of '#~'

(?~) :: Partial' s t a b -> (a -> Identity b) -> s -> tSource

Partial version of '#~'

(*~) :: Traversal' s t a b -> (a -> Identity b) -> s -> tSource

Traversal version of '#~'

(!~) :: IOLens' s t a b -> (a -> IO b) -> s -> IO tSource

IO version of '#~'

(?!~) :: IOPartial' s t a b -> (a -> IO b) -> s -> IO tSource

Partial IO version of '#~'

(*!~) :: IOTraversal' s t a b -> (a -> IO b) -> s -> IO tSource

Traversal IO version of '#~'

Updaters with pure function inside

(#-) :: Monad w => Reference w r s t a b -> (a -> b) -> s -> w tSource

Applies the given pure function on the referenced data in the monad of the lens.

Does not bind the type of the reader monad, so the reference must have its type disambiguated.

(.-) :: Lens' s t a b -> (a -> b) -> s -> tSource

Pure version of '#-'

(?-) :: Partial' s t a b -> (a -> b) -> s -> tSource

Partial version of '#-'

(*-) :: Traversal' s t a b -> (a -> b) -> s -> tSource

Traversal version of '#-'

(!-) :: IOLens' s t a b -> (a -> b) -> s -> IO tSource

IO version of '#-'

(?!-) :: IOPartial' s t a b -> (a -> b) -> s -> IO tSource

Partial IO version of '#-'

(*!-) :: IOTraversal' s t a b -> (a -> b) -> s -> IO tSource

Traversal IO version of '#-'

Updaters with only side-effects

(#|) :: Monad w => Reference w r s s a a -> (a -> w x) -> s -> w sSource

Performs the given monadic action on referenced data while giving back the original data.

Does not bind the type of the reader monad, so the reference must have its type disambiguated.

(!|) :: IOLens' s s a a -> (a -> IO c) -> s -> IO sSource

IO version of '#|'

(?!|) :: IOPartial' s s a a -> (a -> IO c) -> s -> IO sSource

Partial IO version of '#|'

(*!|) :: IOTraversal' s s a a -> (a -> IO c) -> s -> IO sSource

Traversal IO version of '#|'

Binary operators on references

(&) :: (Monad w, Monad r) => Reference w r s t c d -> Reference w r c d a b -> Reference w r s t a bSource

Composes two references. They must be of the same kind.

If reference r accesses b inside the context a, and reference p accesses c inside the context b, than the reference r&p will access c inside a.

Composition is associative: (r&p)&q = r&(p&q)

(&+&) :: (Monad w, MonadPlus r, MMorph [] r) => Reference w r s s a a -> Reference w r s s a a -> Reference w r s s a aSource

Adds two references.

Using this operator may result in accessing the same parts of data multiple times. For example twice = self &+& self is a reference that accesses itself twice:

 a ^* twice == [a,a]
 (twice *= x) a == x
 (twice *- f) a == f (f a)

Addition is commutative only if we do not consider the order of the results from a get, or the order in which monadic actions are performed.