lens-2.7.0.1: Lenses, Folds and Traversals

PortabilityRank2Types
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

Control.Lens.Type

Contents

Description

A Lens a b c d is a purely functional reference.

While a Traversal could be used for Getting like a valid Fold, it wasn't a valid Getter as Applicative wasn't a superclass of Gettable.

Functor, however is the superclass of both.

type Lens a b c d = forall f. Functor f => (c -> f d) -> a -> f b

Every Lens is a valid Setter, choosing f = Mutator.

Every Lens can be used for Getting like a Fold that doesn't use the Applicative or Gettable.

Every Lens is a valid Traversal that only uses the Functor part of the Applicative it is supplied.

Every Lens can be used for Getting like a valid Getter, since Functor is a superclass of Gettable

Since every Lens can be used for Getting like a valid Getter it follows that it must view exactly one element in the structure.

The lens laws follow from this property and the desire for it to act like a Traversable when used as a Traversal.

Synopsis

Lenses

type Lens a b c d = forall f. Functor f => (c -> f d) -> a -> f bSource

A Lens is actually a lens family as described in http://comonad.com/reader/2012/mirrored-lenses/.

With great power comes great responsibility and a Lensis subject to the three common sense lens laws:

1) You get back what you put in:

view l (set l b a)  ≡ b

2) Putting back what you got doesn't change anything:

set l (view l a) a  ≡ a

3) Setting twice is the same as setting once:

set l c (set l b a) ≡ set l c a

These laws are strong enough that the 4 type parameters of a Lens cannot vary fully independently. For more on how they interact, read the "Why is it a Lens Family?" section of http://comonad.com/reader/2012/mirrored-lenses/.

Every Lens can be used directly as a Setter or Traversal.

You can also use a Lens for Getting as if it were a Fold or Getter.

Since every lens is a valid Traversal, the traversal laws are required of any lenses you create:

 l purepure
 fmap (l f) . l g ≡ getCompose . l (Compose . fmap f . g)
type Lens a b c d = forall f. Functor f => LensLike f a b c d

type Simple f a b = f a a b bSource

A Simple Lens, Simple Traversal, ... can be used instead of a Lens,Traversal, ... whenever the type variables don't change upon setting a value.

 imaginary :: Simple Lens (Complex a) a
 traverseHead :: Simple Traversal [a] a

Note: To use this alias in your own code with LensLike f or Setter, you may have to turn on LiberalTypeSynonyms.

lens :: (a -> c) -> (a -> d -> b) -> Lens a b c dSource

Build a Lens from a getter and a setter.

lens :: Functor f => (a -> c) -> (a -> d -> b) -> (c -> f d) -> a -> f b

(%%~) :: LensLike f a b c d -> (c -> f d) -> a -> f bSource

(%%~) can be used in one of two scenarios:

When applied to a Lens, it can edit the target of the Lens in a structure, extracting a functorial result.

When applied to a Traversal, it can edit the targets of the Traversals, extracting an applicative summary of its actions.

For all that the definition of this combinator is just:

(%%~) ≡ id
 (%%~) :: Functor f =>     Iso a b c d       -> (c -> f d) -> a -> f b
 (%%~) :: Functor f =>     Lens a b c d      -> (c -> f d) -> a -> f b
 (%%~) :: Applicative f => Traversal a b c d -> (c -> f d) -> a -> f b

It may be beneficial to think about it as if it had these even more restrictive types, however:

When applied to a Traversal, it can edit the targets of the Traversals, extracting a supplemental monoidal summary of its actions, by choosing f = ((,) m)

 (%%~) ::             Iso a b c d       -> (c -> (e, d)) -> a -> (e, b)
 (%%~) ::             Lens a b c d      -> (c -> (e, d)) -> a -> (e, b)
 (%%~) :: Monoid m => Traversal a b c d -> (c -> (m, d)) -> a -> (m, b)

(%%=) :: MonadState a m => LensLike ((,) e) a a c d -> (c -> (e, d)) -> m eSource

Modify the target of a Lens in the current state returning some extra information of c or modify all targets of a Traversal in the current state, extracting extra information of type c and return a monoidal summary of the changes.

(%%=) ≡ (state .)

It may be useful to think of (%%=), instead, as having either of the following more restricted type signatures:

 (%%=) :: MonadState a m             => Iso a a c d       -> (c -> (e, d) -> m e
 (%%=) :: MonadState a m             => Lens a a c d      -> (c -> (e, d) -> m e
 (%%=) :: (MonadState a m, Monoid e) => Traversal a a c d -> (c -> (e, d) -> m e

resultAt :: Eq e => e -> Simple Lens (e -> a) aSource

This lens can be used to change the result of a function but only where the arguments match the key given.

Lateral Composition

merged :: Functor f => LensLike f a b c c -> LensLike f a' b' c c -> LensLike f (Either a a') (Either b b') c cSource

Merge two lenses, getters, setters, folds or traversals.

alongside :: Lens a b c d -> Lens a' b' c' d' -> Lens (a, a') (b, b') (c, c') (d, d')Source

alongside makes a Lens from two other lenses (or isomorphisms)

Setting Functionally with Passthrough

(<%~) :: LensLike ((,) d) a b c d -> (c -> d) -> a -> (d, b)Source

Modify the target of a Lens and return the result

When you do not need the result of the addition, (%~) is more flexible.

 (<%~) ::             Lens a b c d      -> (c -> d) -> a -> (d, b)
 (<%~) ::             Iso a b c d       -> (c -> d) -> a -> (d, b)
 (<%~) :: Monoid d => Traversal a b c d -> (c -> d) -> a -> (d, b)

(<+~) :: Num c => LensLike ((,) c) a b c c -> c -> a -> (c, b)Source

Increment the target of a numerically valued Lens and return the result

When you do not need the result of the addition, (+~) is more flexible.

 (<+~) :: Num b => Simple Lens a b -> b -> a -> (b, a)
 (<+~) :: Num b => Simple Iso a b  -> b -> a -> (b, a)

(<-~) :: Num c => LensLike ((,) c) a b c c -> c -> a -> (c, b)Source

Decrement the target of a numerically valued Lens and return the result

When you do not need the result of the subtraction, (-~) is more flexible.

 (<-~) :: Num b => Simple Lens a b -> b -> a -> (b, a)
 (<-~) :: Num b => Simple Iso a b  -> b -> a -> (b, a)

(<*~) :: Num c => LensLike ((,) c) a b c c -> c -> a -> (c, b)Source

Multiply the target of a numerically valued Lens and return the result

When you do not need the result of the multiplication, (*~) is more flexible.

 (<*~) :: Num b => Simple Lens a b -> b -> a -> (b, a)
 (<*~) :: Num b => Simple Iso a b  -> b -> a -> (b, a)

(<//~) :: Fractional c => LensLike ((,) c) a b c c -> c -> a -> (c, b)Source

Divide the target of a fractionally valued Lens and return the result.

When you do not need the result of the division, (//~) is more flexible.

 (<//~) :: Fractional b => Simple Lens a b -> b -> a -> (b, a)
 (<//~) :: Fractional b => Simple Iso a b  -> b -> a -> (b, a)

(<^~) :: (Num c, Integral d) => LensLike ((,) c) a b c c -> d -> a -> (c, b)Source

Raise the target of a numerically valued Lens to a non-negative Integral power and return the result

When you do not need the result of the division, (^~) is more flexible.

 (<^~) :: (Num b, Integral c) => Simple Lens a b -> c -> a -> (b, a)
 (<^~) :: (Num b, Integral c) => Simple Iso a b  -> c -> a -> (b, a)

(<^^~) :: (Fractional c, Integral d) => LensLike ((,) c) a b c c -> d -> a -> (c, b)Source

Raise the target of a fractionally valued Lens to an Integral power and return the result.

When you do not need the result of the division, (^^~) is more flexible.

 (<^^~) :: (Fractional b, Integral c) => Simple Lens a b -> c -> a -> (b, a)
 (<^^~) :: (Fractional b, Integral c) => Simple Iso a b  -> c -> a -> (b, a)

(<**~) :: Floating c => LensLike ((,) c) a b c c -> c -> a -> (c, b)Source

Raise the target of a floating-point valued Lens to an arbitrary power and return the result.

When you do not need the result of the division, (**~) is more flexible.

 (<**~) :: Floating b => Simple Lens a b -> b -> a -> (b, a)
 (<**~) :: Floating b => Simple Iso a b  -> b -> a -> (b, a)

(<||~) :: LensLike ((,) Bool) a b Bool Bool -> Bool -> a -> (Bool, b)Source

Logically || a Boolean valued Lens and return the result

When you do not need the result of the operation, (||~) is more flexible.

 (<||~) :: Simple Lens a Bool -> Bool -> a -> (Bool, a)
 (<||~) :: Simple Iso a Bool  -> Bool -> a -> (Bool, a)

(<&&~) :: LensLike ((,) Bool) a b Bool Bool -> Bool -> a -> (Bool, b)Source

Logically && a Boolean valued Lens and return the result

When you do not need the result of the operation, (&&~) is more flexible.

 (<&&~) :: Simple Lens a Bool -> Bool -> a -> (Bool, a)
 (<&&~) :: Simple Iso a Bool  -> Bool -> a -> (Bool, a)

Setting State with Passthrough

(<%=) :: MonadState a m => LensLike ((,) d) a a c d -> (c -> d) -> m dSource

Modify the target of a Lens into your monad's state by a user supplied function and return the result.

When applied to a Traversal, it this will return a monoidal summary of all of the intermediate results.

When you do not need the result of the operation, (%=) is more flexible.

 (<%=) :: MonadState a m             => Simple Lens a b     -> (b -> b) -> m b
 (<%=) :: MonadState a m             => Simple Iso a b      -> (b -> b) -> m b
 (<%=) :: (MonadState a m, Monoid b) => Simple Traveral a b -> (b -> b) -> m b

(<+=) :: (MonadState a m, Num b) => SimpleLensLike ((,) b) a b -> b -> m bSource

Add to the target of a numerically valued Lens into your monad's state and return the result.

When you do not need the result of the multiplication, (+=) is more flexible.

 (<+=) :: (MonadState a m, Num b) => Simple Lens a b -> b -> m b
 (<+=) :: (MonadState a m, Num b) => Simple Iso a b  -> b -> m b

(<-=) :: (MonadState a m, Num b) => SimpleLensLike ((,) b) a b -> b -> m bSource

Subtract from the target of a numerically valued Lens into your monad's state and return the result.

When you do not need the result of the multiplication, (-=) is more flexible.

 (<-=) :: (MonadState a m, Num b) => Simple Lens a b -> b -> m b
 (<-=) :: (MonadState a m, Num b) => Simple Iso a b  -> b -> m b

(<*=) :: (MonadState a m, Num b) => SimpleLensLike ((,) b) a b -> b -> m bSource

Multiply the target of a numerically valued Lens into your monad's state and return the result.

When you do not need the result of the multiplication, (*=) is more flexible.

 (<*=) :: (MonadState a m, Num b) => Simple Lens a b -> b -> m b
 (<*=) :: (MonadState a m, Num b) => Simple Iso a b  -> b -> m b

(<//=) :: (MonadState a m, Fractional b) => SimpleLensLike ((,) b) a b -> b -> m bSource

Divide the target of a fractionally valued Lens into your monad's state and return the result.

When you do not need the result of the division, (//=) is more flexible.

 (<//=) :: (MonadState a m, Fractional b) => Simple Lens a b -> b -> m b
 (<//=) :: (MonadState a m, Fractional b) => Simple Iso a b  -> b -> m b

(<^=) :: (MonadState a m, Num b, Integral c) => SimpleLensLike ((,) b) a b -> c -> m bSource

Raise the target of a numerically valued Lens into your monad's state to a non-negative Integral power and return the result.

When you do not need the result of the operation, (**=) is more flexible.

 (<^=) :: (MonadState a m, Num b, Integral c) => Simple Lens a b -> c -> m b
 (<^=) :: (MonadState a m, Num b, Integral c) => Simple Iso a b  -> c -> m b

(<^^=) :: (MonadState a m, Fractional b, Integral c) => SimpleLensLike ((,) b) a b -> c -> m bSource

Raise the target of a fractionally valued Lens into your monad's state to an Integral power and return the result.

When you do not need the result of the operation, (^^=) is more flexible.

 (<^^=) :: (MonadState a m, Fractional b, Integral c) => Simple Lens a b -> c -> m b
 (<^^=) :: (MonadState a m, Fractional b, Integral c) => Simple Iso a b  -> c -> m b

(<**=) :: (MonadState a m, Floating b) => SimpleLensLike ((,) b) a b -> b -> m bSource

Raise the target of a floating-point valued Lens into your monad's state to an arbitrary power and return the result.

When you do not need the result of the operation, (**=) is more flexible.

 (<**=) :: (MonadState a m, Floating b) => Simple Lens a b -> b -> m b
 (<**=) :: (MonadState a m, Floating b) => Simple Iso a b  -> b -> m b

(<||=) :: MonadState a m => SimpleLensLike ((,) Bool) a Bool -> Bool -> m BoolSource

Logically || a Boolean valued Lens into your monad's state and return the result.

When you do not need the result of the operation, (||=) is more flexible.

 (<||=) :: MonadState a m => Simple Lens a Bool -> Bool -> m Bool
 (<||=) :: MonadState a m => Simple Iso a Bool  -> Bool -> m Bool

(<&&=) :: MonadState a m => SimpleLensLike ((,) Bool) a Bool -> Bool -> m BoolSource

Logically && a Boolean valued Lens into your monad's state and return the result.

When you do not need the result of the operation, (&&=) is more flexible.

 (<&&=) :: MonadState a m => Simple Lens a Bool -> Bool -> m Bool
 (<&&=) :: MonadState a m => Simple Iso a Bool  -> Bool -> m Bool

Cloning Lenses

cloneLens :: Functor f => LensLike (Context c d) a b c d -> (c -> f d) -> a -> f bSource

Cloning a Lens is one way to make sure you arent given something weaker, such as a Traversal and can be used as a way to pass around lenses that have to be monomorphic in f.

Note: This only accepts a proper Lens.

\"Costate Comonad Coalgebra is equivalent of Java's member variable update technology for Haskell\" -- @PLT_Borat on Twitter

newtype ReifiedLens a b c d Source

Useful for storing lenses in containers.

Constructors

ReifyLens 

Fields

reflectLens :: Lens a b c d
 

Simplified and In-Progress

type LensLike f a b c d = (c -> f d) -> a -> f bSource

Many combinators that accept a Lens can also accept a Traversal in limited situations.

They do so by specializing the type of Functor that they require of the caller.

If a function accepts a LensLike f a b c d for some Functor f, then they may be passed a Lens.

Further, if f is an Applicative, they may also be passed a Traversal.

type Overloaded k f a b c d = k (c -> f d) (a -> f b)Source

type LensLike f a b c d = Overloaded (->) f a b c d

type SimpleLens a b = Lens a a b bSource

type SimpleLensLike f a b = LensLike f a a b bSource

type SimpleOverloaded k f a b = Overloaded k f a a b bSource

type SimpleOverloaded k f a b = Simple (Overloaded k f) a b