fused-effects-lens-1.2.0.1: Monadic lens combinators for fused-effects.
Safe HaskellNone
LanguageHaskell2010

Control.Effect.Lens

Description

Provides combinators for the lens-based manipulation of state and context types provided by the fused-effects library, similar to those provided for mtl-based monad transformers.

Synopsis
  • view :: forall r a sig m. Has (Reader r) sig m => Getting a r a -> m a
  • views :: forall s a b sig m. Has (Reader s) sig m => Getting a s a -> (a -> b) -> m b
  • use :: forall s a sig m. Has (State s) sig m => Getting a s a -> m a
  • uses :: forall s a b f sig. Has (State s) sig f => Getting a s a -> (a -> b) -> f b
  • assign :: forall s a b sig m. Has (State s) sig m => ASetter s s a b -> b -> m ()
  • modifying :: forall s a b sig m. Has (State s) sig m => ASetter s s a b -> (a -> b) -> m ()
  • (.=) :: forall s a b sig m. Has (State s) sig m => ASetter s s a b -> b -> m ()
  • (?=) :: forall s a b sig m. Has (State s) sig m => ASetter s s a (Maybe b) -> b -> m ()
  • (%=) :: forall s a b sig m. Has (State s) sig m => ASetter s s a b -> (a -> b) -> m ()
  • (<~) :: forall s a b sig m. Has (State s) sig m => ASetter s s a b -> m b -> m ()
  • (+=) :: forall s a sig m. (Has (State s) sig m, Num a) => ASetter' s a -> a -> m ()
  • (-=) :: forall s a sig m. (Has (State s) sig m, Num a) => ASetter' s a -> a -> m ()
  • (*=) :: forall s a sig m. (Has (State s) sig m, Num a) => ASetter' s a -> a -> m ()
  • (//=) :: forall s a sig m. (Has (State s) sig m, Fractional a) => ASetter' s a -> a -> m ()

Reader accessors

view :: forall r a sig m. Has (Reader r) sig m => Getting a r a -> m a Source #

View the value pointed to by a Getter, Lens, Traversal, or Fold corresponding to the Reader context of the given monadic carrier.

views :: forall s a b sig m. Has (Reader s) sig m => Getting a s a -> (a -> b) -> m b Source #

View a function of the value pointed to by a Getter or Lens, or the result of folding over all the results of a Fold or Traversal, when applied to the Reader context of the given monadic carrier.

This is slightly more general in lens itself, but should suffice for our purposes.

State getters/setters

use :: forall s a sig m. Has (State s) sig m => Getting a s a -> m a Source #

Extract the target of a Lens or Getter, or use a summary of a Fold or Traversal that points to a monoidal value.

uses :: forall s a b f sig. Has (State s) sig f => Getting a s a -> (a -> b) -> f b Source #

Use a function of the target of a Lens or Getter in the current state, or use a summary of a Fold or Traversal that points to a monoidal value.

assign :: forall s a b sig m. Has (State s) sig m => ASetter s s a b -> b -> m () Source #

Replace the target of a Lens (or all the targets of a Setter or Traversal) within the current monadic state, irrespective of the old value.

This is a prefix version of .=.

modifying :: forall s a b sig m. Has (State s) sig m => ASetter s s a b -> (a -> b) -> m () Source #

Map over the target of a Lens, or all of the targets of a Setter or Traversal, in the current monadic state.

This is a prefix version of %=.

Infix operators

(.=) :: forall s a b sig m. Has (State s) sig m => ASetter s s a b -> b -> m () infix 4 Source #

Replace the target of a Lens (or all the targets of a Setter or Traversal) within the current monadic state, irrespective of the old value.

This is an infix version of assign.

(?=) :: forall s a b sig m. Has (State s) sig m => ASetter s s a (Maybe b) -> b -> m () infix 4 Source #

Replace the target of a Lens or all of the targets of a Setter or Traversal in our monadic state with Just a new value, irrespective of the old.

(%=) :: forall s a b sig m. Has (State s) sig m => ASetter s s a b -> (a -> b) -> m () infix 4 Source #

Map over the target of a Lens, or all of the targets of a Setter or Traversal, in the current monadic state.

This is an infix version of modifying.

(<~) :: forall s a b sig m. Has (State s) sig m => ASetter s s a b -> m b -> m () infixr 2 Source #

Run a monadic action, and set all of the targets of a Lens, Setter or Traversal to its result.

Mathematical operators

(+=) :: forall s a sig m. (Has (State s) sig m, Num a) => ASetter' s a -> a -> m () infix 4 Source #

Modify the target(s) of a Lens, Iso, Setter or Traversal by adding a value.

(-=) :: forall s a sig m. (Has (State s) sig m, Num a) => ASetter' s a -> a -> m () infix 4 Source #

Modify the target(s) of a Lens, Iso, Setter or Traversal by subtracting a value.

(*=) :: forall s a sig m. (Has (State s) sig m, Num a) => ASetter' s a -> a -> m () infix 4 Source #

Modify the target(s) of a Lens, Iso, Setter or Traversal by subtracting a value.

(//=) :: forall s a sig m. (Has (State s) sig m, Fractional a) => ASetter' s a -> a -> m () infix 4 Source #

Modify the target(s) of a Lens, Iso, Setter or Traversal by dividing a value.