lens-2.2: Lenses, Folds and Traversals

PortabilityRank2Types
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellSafe-Infered

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 isn'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 should also apply to any lenses you create.

  1. ) Idiomatic naturality:
l pure = pure
  1. ) Sequential composition:
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

Traversing and Lensing

class Focus st whereSource

This class allows us to use focus on a number of different monad transformers.

Methods

focus :: Monad m => LensLike (Focusing m c) a a b b -> st b m c -> st a m cSource

Run a monadic action in a larger context than it was defined in, using a Simple Lens or Simple Traversal.

This is commonly used to lift actions in a simpler state monad into a state monad with a larger state type.

When applied to a 'Simple Traversal over multiple values, the actions for each target are executed sequentially and the results are aggregated monoidally and a monoidal summary of the result is given.

 focus :: Monad m             => Simple Iso a b       -> st b m c -> st a m c
 focus :: Monad m             => Simple Lens a b      -> st b m c -> st a m c
 focus :: (Monad m, Monoid c) => Simple Traversal a b -> st b m c -> st a m c

focus_ :: Monad m => LensLike (Focusing m ()) a a b b -> st b m c -> st a m ()Source

Like focus, but discarding any accumulated results as you go.

 focus_ :: Monad m             => Simple Iso a b       -> st b m c -> st a m ()
 focus_ :: Monad m             => Simple Lens a b      -> st b m c -> st a m ()
 focus_ :: (Monad m, Monoid c) => Simple Traversal a b -> st b m c -> st a m ()

setFocus :: Simple Setter a b -> st b Identity c -> st a Identity ()Source

A much more limited version of focus that can work with a Setter.

Common Lenses

Tuples

class Field1 a b c d | a -> c, b -> d, a d -> b, b c -> a whereSource

Provides access to 1st field of a tuple.

Methods

_1 :: Lens a b c dSource

Access the 1st field of a tuple (and possibly change its type).

>>> import Control.Lens
>>> (1,2)^._1
1
>>> _1 .~ "hello" $ (1,2)
("hello",2)

This can also be used on larger tuples as well

>>> _1 +~ 41 $ (1,2,3,4,5)
(42,2,3,4,5)
 _1 :: Lens (a,b) (a',b) a a'
 _1 :: Lens (a,b,c) (a',b,c) a a'
 _1 :: Lens (a,b,c,d) (a',b,c,d) a a'
 ...
 _1 :: Lens (a,c,d,e,f,g,h,i) (a',b,c,d,e,f,g,h,i) a a'

Instances

Field1 (a, b) (a', b) a a' 
Field1 (a, b, c) (a', b, c) a a' 
Field1 (a, b, c, d) (a', b, c, d) a a' 
Field1 (a, b, c, d, e) (a', b, c, d, e) a a' 
Field1 (a, b, c, d, e, f) (a', b, c, d, e, f) a a' 
Field1 (a, b, c, d, e, f, g) (a', b, c, d, e, f, g) a a' 
Field1 (a, b, c, d, e, f, g, h) (a', b, c, d, e, f, g, h) a a' 
Field1 (a, b, c, d, e, f, g, h, i) (a', b, c, d, e, f, g, h, i) a a' 

class Field2 a b c d | a -> c, b -> d, a d -> b, b c -> a whereSource

Provides access to the 2nd field of a tuple

Methods

_2 :: Lens a b c dSource

Access the 2nd field of a tuple

>>> import Control.Lens
>>> _2 .~ "hello" $ (1,(),3,4)
(1,"hello",3,4)
 anyOf _2 :: (c -> Bool) -> (a, c) -> Bool
 traverse . _2 :: (Applicative f, Traversable t) => (a -> f b) -> t (c, a) -> f (t (c, b))
 foldMapOf (traverse . _2) :: (Traversable t, Monoid m) => (c -> m) -> t (b, c) -> m

Instances

Field2 (a, b) (a, b') b b' 
Field2 (a, b, c) (a, b', c) b b' 
Field2 (a, b, c, d) (a, b', c, d) b b' 
Field2 (a, b, c, d, e) (a, b', c, d, e) b b' 
Field2 (a, b, c, d, e, f) (a, b', c, d, e, f) b b' 
Field2 (a, b, c, d, e, f, g) (a, b', c, d, e, f, g) b b' 
Field2 (a, b, c, d, e, f, g, h) (a, b', c, d, e, f, g, h) b b' 
Field2 (a, b, c, d, e, f, g, h, i) (a, b', c, d, e, f, g, h, i) b b' 

class Field3 a b c d | a -> c, b -> d, a d -> b, b c -> a whereSource

Provides access to the 3rd field of a tuple

Methods

_3 :: Lens a b c dSource

Access the 3rd field of a tuple

Instances

Field3 (a, b, c) (a, b, c') c c' 
Field3 (a, b, c, d) (a, b, c', d) c c' 
Field3 (a, b, c, d, e) (a, b, c', d, e) c c' 
Field3 (a, b, c, d, e, f) (a, b, c', d, e, f) c c' 
Field3 (a, b, c, d, e, f, g) (a, b, c', d, e, f, g) c c' 
Field3 (a, b, c, d, e, f, g, h) (a, b, c', d, e, f, g, h) c c' 
Field3 (a, b, c, d, e, f, g, h, i) (a, b, c', d, e, f, g, h, i) c c' 

class Field4 a b c d | a -> c, b -> d, a d -> b, b c -> a whereSource

Provide access to the 4th field of a tuple

Methods

_4 :: Lens a b c dSource

Access the 4th field of a tuple

Instances

Field4 (a, b, c, d) (a, b, c, d') d d' 
Field4 (a, b, c, d, e) (a, b, c, d', e) d d' 
Field4 (a, b, c, d, e, f) (a, b, c, d', e, f) d d' 
Field4 (a, b, c, d, e, f, g) (a, b, c, d', e, f, g) d d' 
Field4 (a, b, c, d, e, f, g, h) (a, b, c, d', e, f, g, h) d d' 
Field4 (a, b, c, d, e, f, g, h, i) (a, b, c, d', e, f, g, h, i) d d' 

class Field5 a b c d | a -> c, b -> d, a d -> b, b c -> a whereSource

Provides access to the 5th field of a tuple

Methods

_5 :: Lens a b c dSource

Access the 5th field of a tuple

Instances

Field5 (a, b, c, d, e) (a, b, c, d, e') e e' 
Field5 (a, b, c, d, e, f) (a, b, c, d, e', f) e e' 
Field5 (a, b, c, d, e, f, g) (a, b, c, d, e', f, g) e e' 
Field5 (a, b, c, d, e, f, g, h) (a, b, c, d, e', f, g, h) e e' 
Field5 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e', f, g, h, i) e e' 

class Field6 a b c d | a -> c, b -> d, a d -> b, b c -> a whereSource

Provides access to the 6th element of a tuple

Methods

_6 :: Lens a b c dSource

Access the 6th field of a tuple

Instances

Field6 (a, b, c, d, e, f) (a, b, c, d, e, f') f f' 
Field6 (a, b, c, d, e, f, g) (a, b, c, d, e, f', g) f f' 
Field6 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f', g, h) f f' 
Field6 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f', g, h, i) f f' 

class Field7 a b c d | a -> c, b -> d, a d -> b, b c -> a whereSource

Provide access to the 7th field of a tuple

Methods

_7 :: Lens a b c dSource

Access the 7th field of a tuple

Instances

Field7 (a, b, c, d, e, f, g) (a, b, c, d, e, f, g') g g' 
Field7 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g', h) g g' 
Field7 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g', h, i) g g' 

class Field8 a b c d | a -> c, b -> d, a d -> b, b c -> a whereSource

Provide access to the 8th field of a tuple

Methods

_8 :: Lens a b c dSource

Access the 8th field of a tuple

Instances

Field8 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g, h') h h' 
Field8 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h', i) h h' 

class Field9 a b c d | a -> c, b -> d, a d -> b, b c -> a whereSource

Provides access to the 9th field of a tuple

Methods

_9 :: Lens a b c dSource

Access the 9th field of a tuple

Instances

Field9 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h, i') i i' 

Functions

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.

(<+~) :: 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 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 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.

(<//~) :: 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.

(<^~) :: (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.

(<^^~) :: (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.

(<**~) :: 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.

(<||~) :: 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.

(<&&~) :: 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.

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 you do not need the result of the operation, (%=) is more flexible.

(<+=) :: (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) => 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) => 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, 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, 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, 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, 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 => 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 => 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.

Cloning Lenses

clone :: Functor f => LensLike (IndexedStore 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, because IndexedStore lacks its (admissable) Applicative instance.

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

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