lens-1.0.1: Families of Lenses, Folds and Traversals

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

Control.Lens

Contents

Description

This package provides lens families, setters, getters, traversals and folds that can all be composed automatically with each other (and other lenses from other van Laarhoven lens libraries) using (.) from Prelude, while reducing the complexity of the API.

For a longer description and motivation of why you should care about lens families, see http://comonad.com/reader/2012/mirrored-lenses/.

Note: If you merely want your library to provide lenses you may not have to actually import any lens library. For, say, a Simple Lens Bar Foo, just export a function with the signature:

 foo :: Functor f => (Foo -> f Foo) -> Bar -> f Bar

and then you can compose it with other lenses with (.) without needing anything from this library at all.

Usage:

You can derive lenses automatically for many data types:

 import Control.Lens.TH
 data Foo a = Foo { _fooArgs :: [String], _fooValue :: a }
 makeLenses ''Foo

This defines the following lenses:

 fooArgs :: Simple Lens (Foo a) [String]
 fooValue :: Lens (Foo a) (Foo b) a b

The combinators here have unusually specific type signatures, so for particularly tricky ones, I've tried to list the simpler type signatures you might want to pretend the combinators have.

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 Lens is subject to the lens laws:

 view l (set l b a)  = b
 set l (view l a) a  = a
 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 Getter, Setter, Fold or Traversal.

 identity :: Lens (Identity a) (Identity b) a b
 identity f (Identity a) = Identity <$> f a

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 Traversal a b c d = forall f. Applicative f => (c -> f d) -> a -> f bSource

A Traversal can be used directly as a Setter or a Fold (but not as a Lens) and provides the ability to both read and update multiple fields, subject to some relatively weak Traversal laws.

These have also been known as multilenses, but they have the signature and spirit of

 traverse :: Traversable f => Traversal (f a) (f b) a b

and the more evocative name suggests their application.

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: If you plan to use this alias in your code, you may have to turn on

 {-# LANGUAGE LiberalTypeSynonyms #-}

type SimpleLens a b = Lens a a b bSource

This alias is supplied for those who don't want to use {--} and Simple

 'SimpleLens' = 'Simple' 'Lens'

type SimpleTraversal a b = Traversal a a b bSource

This alias is supplied for those who don't want to use {--} and Simple

 'SimpleTraversal' = 'Simple' 'Traversal'

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

This alias is supplied for those who don't want to use {--} and Simple

 'SimpleLensLike' f = 'Simple' ('LensLike' f)

Constructing Lenses

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

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

Built a Lens from an isomorphism family

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

Traversing and Lensing

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

(%%~) 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 supplemental result, and the new structure.

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

For all that the definition of this combinator is just:

 (%%~) = id

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

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

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 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 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.

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

Map each element of a structure targeted by a Lens or Traversal, evaluate these actions from left to right, and collect the results.

 traverseOf = id
 traverse = traverseOf traverse
 traverseOf :: Lens a b c d      -> (c -> f d) -> a -> f b
 traverseOf :: Traversal a b c d -> (c -> f d) -> a -> f b

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

 forOf = flip
 forOf l = flip (traverseOf l)
 for = forOf traverse

sequenceAOf :: LensLike f a b (f c) c -> a -> f bSource

Evaluate each action in the structure from left to right, and collect the results.

 sequenceA = sequenceAOf traverse
 sequenceAOf l = traverseOf l id
 sequenceAOf l = l id
 sequenceAOf ::                  Lens a b (f c) c -> a -> f b
 sequenceAOf :: Applicative f => Traversal a b (f c) c -> a -> f b

mapMOf :: LensLike (WrappedMonad m) a b c d -> (c -> m d) -> a -> m bSource

Map each element of a structure targeted by a lens to a monadic action, evaluate these actions from left to right, and collect the results.

 mapM = mapMOf traverse
 mapMOf ::            Lens a b c d      -> (c -> m d) -> a -> m b
 mapMOf :: Monad m => Traversal a b c d -> (c -> m d) -> a -> m b

forMOf :: LensLike (WrappedMonad m) a b c d -> a -> (c -> m d) -> m bSource

 forM = forMOf traverse
 forMOf l = flip (mapMOf l)
 forMOf ::            Lens a b c d -> a -> (c -> m d) -> m b
 forMOf :: Monad m => Lens a b c d -> a -> (c -> m d) -> m b

sequenceOf :: LensLike (WrappedMonad m) a b (m c) c -> a -> m bSource

 sequence = sequenceOf traverse
 sequenceOf l = mapMOf l id
 sequenceOf l = unwrapMonad . l WrapMonad
 sequenceOf ::            Lens a b (m c) c      -> a -> m b
 sequenceOf :: Monad m => Traversal a b (m c) c -> a -> m b

transposeOf :: LensLike ZipList a b [c] c -> a -> [b]Source

This generalizes transpose to an arbitrary Traversal.

 transpose = transposeOf traverse
 ghci> transposeOf traverse [[1,2,3],[4,5,6]]
 [[1,4],[2,5],[3,6]]

Since every Lens is a Traversal, we can use this as a form of monadic strength.

 transposeOf _2 :: (b, [a]) -> [(b, a)]

Common Lenses

valueAt :: Ord k => k -> Simple Lens (Map k v) (Maybe v)Source

This Lens can be used to read, write or delete the value associated with a key in a Map.

 ghci> Map.fromList [("hello",12)] ^. valueAt "hello"
 Just 12
 valueAt :: Ord k => k -> (Maybe v -> f (Maybe v)) -> Map k v -> f (Map k v)

valueAtInt :: Int -> Simple Lens (IntMap v) (Maybe v)Source

This Lens can be used to read, write or delete a member of an IntMap.

 ghci> IntMap.fromList [(1,"hello")]  ^. valueAtInt 1
 Just "hello"
 ghci> valueAtInt 2 +~ "goodbye" $ IntMap.fromList [(1,"hello")]
 fromList [(1,"hello"),(2,"goodbye")]
 valueAtInt :: Int -> (Maybe v -> f (Maybe v)) -> IntMap v -> f (IntMap v)

contains :: Ord k => k -> Simple Lens (Set k) BoolSource

This Lens can be used to read, write or delete a member of a Set

 ghci> contains 3 +~ False $ Set.fromList [1,2,3,4]
 fromList [1,2,4]
 contains :: Ord k => k -> (Bool -> f Bool) -> Set k -> f (Set k)

containsInt :: Int -> Simple Lens IntSet BoolSource

This Lens can be used to read, write or delete a member of an IntSet

 ghci> containsInt 3 +~ False $ IntSet.fromList [1,2,3,4]
 fromList [1,2,4]
 containsInt :: Int -> (Bool -> f Bool) -> IntSet -> f IntSet

bitAt :: Bits b => Int -> Simple Lens b BoolSource

This lens can be used to access the value of the nth bit in a number.

bitsAt n is only a legal Lens into b if 0 <= n < bitSize (undefined :: b)

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.

identity :: Lens (Identity a) (Identity b) a bSource

This lens can be used to access the contents of the Identity monad

real :: Simple Lens (Complex a) aSource

Access the real part of a complex number

 real :: Functor f => (a -> f a) -> Complex a -> f (Complex a)

imaginary :: Simple Lens (Complex a) aSource

Access the imaginary part of a complex number

 imaginary :: Functor f => (a -> f a) -> Complex a -> f (Complex a)

polarize :: RealFloat a => Simple Lens (Complex a) (a, a)Source

This isn't quite a legal lens. Notably the view l (set l b a) = b law is violated when you set a polar value with 0 magnitude and non-zero phase as the phase information is lost. So don't do that!

Otherwise, this is a perfectly convenient lens.

 polarize :: Functor f => ((a,a) -> f (a,a)) -> Complex a -> f (Complex a)

_1 :: Lens (a, c) (b, c) a bSource

This is a lens that can change the value (and type) of the first field of a pair.

 ghci> (1,2)^._1
 1
 ghci> _1 +~ "hello" $ (1,2)
 ("hello",2)
 _1 :: Functor f => (a -> f b) -> (a,c) -> f (a,c)

_2 :: Lens (c, a) (c, b) a bSource

As _1, but for the second field of a pair.

 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
 _2 :: Functor f => (a -> f b) -> (c,a) -> f (c,b)

Setters

type Setter a b c d = (c -> Identity d) -> a -> Identity bSource

The only Lens-like law that can apply to a Setter l is that

 set l c (set l b a) = set l c a

You can't view a Setter in general, so the other two laws are irrelevant.

You can compose a Setter with a Lens or a Traversal using (.) from the Prelude and the result is always only a Setter and nothing more.

 type Setter a b c d = LensLike Identity a b c d

type SimpleSetter a b = Lens a a b bSource

This alias is supplied for those who don't want to bother using {--} and Simple.

 'SimpleSetter ' = 'Simple' 'Setter'

sets :: ((c -> d) -> a -> b) -> Setter a b c dSource

Build a Setter.

 sets . adjust = id
 adjust . sets = id

mapped :: Functor f => Setter (f a) (f b) a bSource

This setter can be used to map over all of the values in a Functor.

 fmap        = adjust mapped
 fmapDefault = adjust traverse
 (<$)        = set mapped

Setting Values

adjust :: Setter a b c d -> (c -> d) -> a -> bSource

Modify the target of a Lens or all the targets of a Setter or Traversal with a function.

 fmap        = adjust mapped
 fmapDefault = adjust traverse
 sets . adjust = id
 adjust . sets = id

set :: Setter a b c d -> d -> a -> bSource

Replace the target of a Lens or all of the targets of a Setter or Traversal with a constant value.

 (<$) = set mapped

(^~) :: Setter a b c d -> d -> a -> bSource

Replace the target of a Lens or all of the targets of a Setter or Traversal with a constant value.

This is an infix version of set

 f <$ a = mapped ^~ f $ a
 ghci> bitAt 0 ^~ True $ 0
 1

(+~) :: Num c => Setter a b c c -> c -> a -> bSource

Increment the target(s) of a numerically valued Lens, Setter' or Traversal

 ghci> _1 +~ 1 $ (1,2)
 (2,2)

(-~) :: Num c => Setter a b c c -> c -> a -> bSource

Decrement the target(s) of a numerically valued Lens, Setter or Traversal

 ghci> _1 -~ 2 $ (1,2)
 (-1,2)

(*~) :: Num c => Setter a b c c -> c -> a -> bSource

Multiply the target(s) of a numerically valued Lens, Setter or Traversal

 ghci> _2 *~ 4 $ (1,2)
 (1,8)

(//~) :: Fractional c => Setter a b c c -> c -> a -> bSource

Divide the target(s) of a numerically valued Lens, Setter or Traversal

(||~) :: Setter a b Bool Bool -> Bool -> a -> bSource

Logically || the target(s) of a Bool-valued Lens or Setter

(&&~) :: Setter a b Bool Bool -> Bool -> a -> bSource

Logically && the target(s) of a Bool-valued Lens or Setter

(|~) :: Bits c => Setter a b c c -> c -> a -> bSource

Bitwise .|. the target(s) of a Bool-valued Lens or Setter

(&~) :: Bits c => Setter a b c c -> c -> a -> bSource

Bitwise .&. the target(s) of a Bool-valued Lens or Setter

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

Modifies the target of a Lens or all of the targets of a Setter or Traversal with a user supplied function.

This is an infix version of adjust

 fmap f = mapped %~ f
 fmapDefault f = traverse %~ f
 ghci> _2 %~ length $ (1,"hello")
 (1,5)

Setting State

(^=) :: MonadState a m => Setter a a c d -> d -> m ()Source

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

(+=) :: (MonadState a m, Num b) => Simple Setter a b -> b -> m ()Source

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

Example:

 fresh = do
   id += 1
   access id

(-=) :: (MonadState a m, Num b) => Simple Setter a b -> b -> m ()Source

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

(*=) :: (MonadState a m, Num b) => Simple Setter a b -> b -> m ()Source

Modify the target(s) of a Simple Lens, Setter or Traversal by multiplying by value

(//=) :: (MonadState a m, Fractional b) => Simple Setter a b -> b -> m ()Source

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

(||=) :: MonadState a m => Simple Setter a Bool -> Bool -> m ()Source

Modify the target(s) of a Simple Lens, Setter or Traversal by taking their logical || with a value

(&&=) :: MonadState a m => Simple Setter a Bool -> Bool -> m ()Source

Modify the target(s) of a Simple Lens, Setter or Traversal by taking their logical && with a value

(|=) :: (MonadState a m, Bits b) => Simple Setter a b -> b -> m ()Source

Modify the target(s) of a Simple Lens, Setter or Traversal by computing its bitwise .|. with another value.

(&=) :: (MonadState a m, Bits b) => Simple Setter a b -> b -> m ()Source

Modify the target(s) of a Simple Lens, Setter or Traversal by computing its bitwise .&. with another value.

(%=) :: MonadState a m => Setter a a c d -> (c -> d) -> m ()Source

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

Getters and Folds

Getters

type Getter a b c d = forall z. (c -> Const z d) -> a -> Const z bSource

A Getter describes how to retrieve a single value in a way that can be composed with other lens-like constructions.

Unlike a Lens a Getter is read-only. Since a Getter cannot be used to write back there are no lens laws that can be applied to it.

Moreover, a Getter can be used directly as a Fold, since it just ignores the Monoid.

In practice the b and d are left dangling and unused, and as such is no real point in using a Simple Getter.

type Getter a b c d = forall z. LensLike (Const z) a b c d

to :: (a -> c) -> Getter a b c dSource

Build a Getter from an arbitrary Haskell function.

 to f . to g = to (g . f)

Folds

type Fold a b c d = forall m. Monoid m => (c -> Const m d) -> a -> Const m bSource

A Fold describes how to retrieve multiple values in a way that can be composed with other lens-like constructions.

A Fold a b c d provides a structure with operations very similar to those of the Foldable typeclass, see foldMapOf and the other Fold combinators.

By convention, if there exists a foo method that expects a Foldable (f c), then there should be a fooOf method that takes a Fold a b c d and a value of type a.

A Getter is a legal Fold that just ignores the supplied Monoid

Unlike a Traversal a Fold is read-only. Since a Fold cannot be used to write back there are no lens laws that can be applied to it.

In practice the b and d are left dangling and unused, and as such is no real point in a Simple Fold.

 type Fold a b c d = forall m. Monoid m => Getting m a b c d

folded :: Foldable f => Fold (f c) b c dSource

Obtain a Fold from any Foldable

filtered :: Monoid m => (c -> Bool) -> Getting m a b c d -> Getting m a b c dSource

Obtain a Fold by filtering a Lens, 'Getter, Fold or Traversal.

reversed :: Getting (Dual m) a b c d -> Getting m a b c dSource

Obtain a Fold by reversing the order of traversal for a Lens, Getter, Fold or Traversal.

Of course, reversing a Fold or Getter has no effect.

Getting and Folding

type Getting r a b c d = (c -> Const r d) -> a -> Const r bSource

Most Getter combinators are able to be used with both a Getter or a Fold in limited situations, to do so, they need to be monomorphic in what we are going to extract with Const.

If a function accepts a Getting r a b c d, then when r is a Monoid, you can pass a Fold (or Traversal), otherwise you can only pass this a Getter or Lens.

 type Getting r a b c d = LensLike (Const r) a b c d

view :: Getting c a b c d -> a -> cSource

View the value pointed to by a Getter or Lens or the result of folding over all the results of a Fold or Traversal that points at a monoidal values.

It may be useful to think of view as having these more restrictive signatures:

 view ::             Lens a b c d      -> a -> c
 view ::             Getter a b c d    -> a -> c
 view :: Monoid m => Fold a b m d      -> a -> m
 view :: Monoid m => Traversal a b m d -> a -> m
 view :: ((c -> Const c d) -> a -> Const c b) -> a -> c

views :: Getting m a b c d -> (c -> m) -> a -> mSource

View the value of a Getter, Lens or the result of folding over the result of mapping the targets of a Fold or Traversal.

It may be useful to think of views as having these more restrictive signatures:

 views ::             Getter a b c d    -> (c -> d) -> a -> d
 views ::             Lens a b c d      -> (c -> d) -> a -> d
 views :: Monoid m => Fold a b c d      -> (c -> m) -> a -> m
 views :: Monoid m => Traversal a b c d -> (c -> m) -> a -> m
 views :: ((c -> Const m d) -> a -> Const m b) -> (c -> m) -> a -> m

(^.) :: a -> Getting c a b c d -> cSource

View the value pointed to by a Getter or Lens or the result of folding over all the results of a Fold or Traversal that points at a monoidal values.

This is the same operation as view with the arguments flipped.

The fixity and semantics are such that subsequent field accesses can be performed with (Prelude..)

 ghci> ((0, 1 :+ 2), 3)^._1._2.to magnitude
 2.23606797749979
 (^.) ::             a -> Lens a b c d      -> c
 (^.) ::             a -> Getter a b c d    -> c
 (^.) :: Monoid m => a -> Fold a b m d      -> m
 (^.) :: Monoid m => a -> Traversal a b m d -> m
 (^.) :: a -> ((c -> Const c d) -> a -> Const c b) -> c

(^$) :: Getting c a b c d -> a -> cSource

View the value pointed to by a Getter or Lens or the result of folding over all the results of a Fold or Traversal that points at a monoidal values.

This is the same operation as view, only infix.

 (^$) ::             Lens a b c d      -> a -> c
 (^$) ::             Getter a b c d    -> a -> c
 (^$) :: Monoid m => Fold a b m d      -> a -> m
 (^$) :: Monoid m => Traversal a b m d -> a -> m
 (^$) :: ((c -> Const c d) -> a -> Const c b) -> a -> c

foldMapOf :: Getting m a b c d -> (c -> m) -> a -> mSource

 foldMap = foldMapOf folded
 foldMapOf = views
 foldMapOf ::             Getter a b c d    -> (c -> m) -> a -> m
 foldMapOf ::             Lens a b c d      -> (c -> m) -> a -> m
 foldMapOf :: Monoid m => Fold a b c d      -> (c -> m) -> a -> m
 foldMapOf :: Monoid m => Traversal a b c d -> (c -> m) -> a -> m

foldOf :: Getting m a b m d -> a -> mSource

 fold = foldOf folded
 foldOf = view
 foldOf ::             Getter a b m d    -> a -> m
 foldOf ::             Lens a b m d      -> a -> m
 foldOf :: Monoid m => Fold a b m d      -> a -> m
 foldOf :: Monoid m => Traversal a b m d -> a -> m

foldrOf :: Getting (Endo e) a b c d -> (c -> e -> e) -> e -> a -> eSource

Right-associative fold of parts of a structure that are viewed through a Lens, Getter, Fold or Traversal.

 foldr = foldrOf folded
 foldrOf :: Getter a b c d    -> (c -> e -> e) -> e -> a -> e
 foldrOf :: Lens a b c d      -> (c -> e -> e) -> e -> a -> e
 foldrOf :: Fold a b c d      -> (c -> e -> e) -> e -> a -> e
 foldrOf :: Traversal a b c d -> (c -> e -> e) -> e -> a -> e

foldlOf :: Getting (Dual (Endo e)) a b c d -> (e -> c -> e) -> e -> a -> eSource

Left-associative fold of the parts of a structure that are viewed through a Lens, Getter, Fold or Traversal.

 foldl = foldlOf folded
 foldlOf :: Getter a b c d    -> (e -> c -> e) -> e -> a -> e
 foldlOf :: Lens a b c d      -> (e -> c -> e) -> e -> a -> e
 foldlOf :: Fold a b c d      -> (e -> c -> e) -> e -> a -> e
 foldlOf :: Traversal a b c d -> (e -> c -> e) -> e -> a -> e

toListOf :: Getting [c] a b c d -> a -> [c]Source

 toList = toListOf folded
 toListOf :: Getter a b c d    -> a -> [c]
 toListOf :: Lens a b c d      -> a -> [c]
 toListOf :: Fold a b c d      -> a -> [c]
 toListOf :: Traversal a b c d -> a -> [c]

anyOf :: Getting Any a b c d -> (c -> Bool) -> a -> BoolSource

 any = anyOf folded
 anyOf :: Getter a b c d    -> (c -> Bool) -> a -> Bool
 anyOf :: Lens a b c d      -> (c -> Bool) -> a -> Bool
 anyOf :: Fold a b c d      -> (c -> Bool) -> a -> Bool
 anyOf :: Traversal a b c d -> (c -> Bool) -> a -> Bool

allOf :: Getting All a b c d -> (c -> Bool) -> a -> BoolSource

 all = allOf folded
 allOf :: Getter a b c d    -> (c -> Bool) -> a -> Bool
 allOf :: Lens a b c d      -> (c -> Bool) -> a -> Bool
 allOf :: Fold a b c d      -> (c -> Bool) -> a -> Bool
 allOf :: Traversal a b c d -> (c -> Bool) -> a -> Bool

andOf :: Getting All a b Bool d -> a -> BoolSource

 and = andOf folded
 andOf :: Getter a b Bool d   -> a -> Bool
 andOf :: Lens a b Bool d     -> a -> Bool
 andOf :: Fold a b Bool d     -> a -> Bool
 andOf :: Traversl a b Bool d -> a -> Bool

orOf :: Getting Any a b Bool d -> a -> BoolSource

 or = orOf folded
 orOf :: Getter a b Bool d    -> a -> Bool
 orOf :: Lens a b Bool d      -> a -> Bool
 orOf :: Fold a b Bool d      -> a -> Bool
 orOf :: Traversal a b Bool d -> a -> Bool

productOf :: Getting (Product c) a b c d -> a -> cSource

 product = productOf folded
 productOf ::          Getter a b c d    -> a -> c
 productOf ::          Lens a b c d      -> a -> c
 productOf :: Num c => Fold a b c d      -> a -> c
 productOf :: Num c => Traversal a b c d -> a -> c

sumOf :: Getting (Sum c) a b c d -> a -> cSource

 sum = sumOf folded
 sumOf _1 :: (a, b) -> a
 sumOf (folded._1) :: (Foldable f, Num a) => f (a, b) -> a
 sumOf ::          Getter a b c d    -> a -> c
 sumOf ::          Lens a b c d      -> a -> c
 sumOf :: Num c => Fold a b c d      -> a -> c
 sumOf :: Num c => Traversal a b c d -> a -> c

traverseOf_ :: Functor f => Getting (Traversed f) a b c d -> (c -> f e) -> a -> f ()Source

When passed a Getter, traverseOf_ can work over a Functor.

When passed a Fold, traverseOf_ requires an Applicative.

 traverse_ = traverseOf_ folded
 traverseOf_ _2 :: Functor f => (c -> f e) -> (c1, c) -> f ()
 traverseOf_ traverseLeft :: Applicative f => (a -> f b) -> Either a c -> f ()

The rather specific signature of traverseOf_ allows it to be used as if the signature was either:

 traverseOf_ :: Functor f     => Getter a b c d    -> (c -> f e) -> a -> f ()
 traverseOf_ :: Functor f     => Lens a b c d      -> (c -> f e) -> a -> f ()
 traverseOf_ :: Applicative f => Fold a b c d      -> (c -> f e) -> a -> f ()
 traverseOf_ :: Applicative f => Traversal a b c d -> (c -> f e) -> a -> f ()

forOf_ :: Functor f => Getting (Traversed f) a b c d -> a -> (c -> f e) -> f ()Source

 for_ = forOf_ folded
 forOf_ :: Functor f     => Getter a b c d    -> a -> (c -> f e) -> f ()
 forOf_ :: Functor f     => Lens a b c d      -> a -> (c -> f e) -> f ()
 forOf_ :: Applicative f => Fold a b c d      -> a -> (c -> f e) -> f ()
 forOf_ :: Applicative f => Traversal a b c d -> a -> (c -> f e) -> f ()

sequenceAOf_ :: Functor f => Getting (Traversed f) a b (f ()) d -> a -> f ()Source

 sequenceA_ = sequenceAOf_ folded
 sequenceAOf_ :: Functor f     => Getter a b (f ()) d    -> a -> f ()
 sequenceAOf_ :: Functor f     => Lens a b (f ()) d      -> a -> f ()
 sequenceAOf_ :: Applicative f => Fold a b (f ()) d      -> a -> f ()
 sequenceAOf_ :: Applicative f => Traversal a b (f ()) d -> a -> f ()

mapMOf_ :: Monad m => Getting (Action m) a b c d -> (c -> m e) -> a -> m ()Source

 mapM_ = mapMOf_ folded
 mapMOf_ :: Monad m => Getter a b c d    -> (c -> m e) -> a -> m ()
 mapMOf_ :: Monad m => Lens a b c d      -> (c -> m e) -> a -> m ()
 mapMOf_ :: Monad m => Fold a b c d      -> (c -> m e) -> a -> m ()
 mapMOf_ :: Monad m => Traversal a b c d -> (c -> m e) -> a -> m ()

forMOf_ :: Monad m => Getting (Action m) a b c d -> a -> (c -> m e) -> m ()Source

 forM_ = forMOf_ folded
 forMOf_ :: Monad m => Getter a b c d    -> a -> (c -> m e) -> m ()
 forMOf_ :: Monad m => Lens a b c d      -> a -> (c -> m e) -> m ()
 forMOf_ :: Monad m => Fold a b c d      -> a -> (c -> m e) -> m ()
 forMOf_ :: Monad m => Traversal a b c d -> a -> (c -> m e) -> m ()

sequenceOf_ :: Monad m => Getting (Action m) a b (m c) d -> a -> m ()Source

 sequence_ = sequenceOf_ folded
 sequenceOf_ :: Monad m => Getter a b (m b) d    -> a -> m ()
 sequenceOf_ :: Monad m => Lens a b (m b) d      -> a -> m ()
 sequenceOf_ :: Monad m => Fold a b (m b) d      -> a -> m ()
 sequenceOf_ :: Monad m => Traversal a b (m b) d -> a -> m ()

asumOf :: Alternative f => Getting (Endo (f c)) a b (f c) d -> a -> f cSource

The sum of a collection of actions, generalizing concatOf.

 asum = asumOf folded
 asumOf :: Alternative f => Getter a b c d    -> a -> f c
 asumOf :: Alternative f => Lens a b c d      -> a -> f c
 asumOf :: Alternative f => Fold a b c d      -> a -> f c
 asumOf :: Alternative f => Traversal a b c d -> a -> f c

msumOf :: MonadPlus m => Getting (Endo (m c)) a b (m c) d -> a -> m cSource

The sum of a collection of actions, generalizing concatOf.

 msum = msumOf folded
 msumOf :: MonadPlus m => Getter a b c d    -> a -> m c
 msumOf :: MonadPlus m => Lens a b c d      -> a -> m c
 msumOf :: MonadPlus m => Fold a b c d      -> a -> m c
 msumOf :: MonadPlus m => Traversal a b c d -> a -> m c

concatMapOf :: Getting [e] a b c d -> (c -> [e]) -> a -> [e]Source

 concatMap = concatMapOf folded
 concatMapOf :: Getter a b c d    -> (c -> [e]) -> a -> [e]
 concatMapOf :: Lens a b c d      -> (c -> [e]) -> a -> [e]
 concatMapOf :: Fold a b c d      -> (c -> [e]) -> a -> [e]
 concatMapOf :: Traversal a b c d -> (c -> [e]) -> a -> [e]

concatOf :: Getting [e] a b [e] d -> a -> [e]Source

 concat = concatOf folded
 concatOf :: Getter a b [e] d -> a -> [e]
 concatOf :: Lens a b [e] d -> a -> [e]
 concatOf :: Fold a b [e] d -> a -> [e]
 concatOf :: a b [e] d -> a -> [e]

elemOf :: Eq c => Getting Any a b c d -> c -> a -> BoolSource

 elem = elemOf folded
 elemOf :: Eq c => Getter a b c d    -> c -> a -> Bool
 elemOf :: Eq c => Lens a b c d      -> c -> a -> Bool
 elemOf :: Eq c => Fold a b c d      -> c -> a -> Bool
 elemOf :: Eq c => Traversal a b c d -> c -> a -> Bool

notElemOf :: Eq c => Getting All a b c d -> c -> a -> BoolSource

 notElem = notElemOf folded
 notElemOf :: Eq c => Getter a b c d    -> c -> a -> Bool
 notElemOf :: Eq c => Fold a b c d      -> c -> a -> Bool
 notElemOf :: Eq c => Lens a b c d      -> c -> a -> Bool
 notElemOf :: Eq c => Traversal a b c d -> c -> a -> Bool

lengthOf :: Getting (Sum Int) a b c d -> a -> IntSource

Note: this can be rather inefficient for large containers.

 length = lengthOf folded
 lengthOf _1 :: (a, b) -> Int
 lengthOf _1 = 1
 lengthOf (folded.folded) :: Foldable f => f (g a) -> Int
 lengthOf :: Getter a b c d    -> a -> Int
 lengthOf :: Lens a b c d      -> a -> Int
 lengthOf :: Fold a b c d      -> a -> Int
 lengthOf :: Traversal a b c d -> a -> Int

nullOf :: Getting All a b c d -> a -> BoolSource

Returns True if this Fold or Traversal has no targets in the given container.

Note: nullOf on a valid Lens or Getter will always return False

 null = nullOf folded

This may be rather inefficient compared to the null check of many containers.

 nullOf _1 :: (a, b) -> Int
 nullOf _1 = False
 nullOf (folded._1.folded) :: Foldable f => f (g a, b) -> Bool
 nullOf :: Getter a b c d    -> a -> Bool
 nullOf :: Lens a b c d      -> a -> Bool
 nullOf :: Fold a b c d      -> a -> Bool
 nullOf :: Traversal a b c d -> a -> Bool

maximumOf :: Getting (Max c) a b c d -> a -> Maybe cSource

Obtain the maximum element (if any) targeted by a Fold or Traversal

Note: maximumOf on a valid Lens or Getter will always return Just a value.

 maximum = fromMaybe (error "empty") . maximumOf folded
 maximumOf ::          Getter a b c d    -> a -> Maybe c
 maximumOf ::          Lens a b c d      -> a -> Maybe c
 maximumOf :: Ord c => Fold a b c d      -> a -> Maybe c
 maximumOf :: Ord c => Traversal a b c d -> a -> Maybe c

minimumOf :: Getting (Min c) a b c d -> a -> Maybe cSource

Obtain the minimum element (if any) targeted by a Fold or Traversal

Note: minimumOf on a valid Lens or Getter will always return Just a value.

 minimum = fromMaybe (error "empty") . minimumOf folded
 minimumOf ::          Getter a b c d    -> a -> Maybe c
 minimumOf ::          Lens a b c d      -> a -> Maybe c
 minimumOf :: Ord c => Fold a b c d      -> a -> Maybe c
 minimumOf :: Ord c => Traversal a b c d -> a -> Maybe c

maximumByOf :: Getting (Endo (Maybe c)) a b c d -> (c -> c -> Ordering) -> a -> Maybe cSource

Obtain the maximum element (if any) targeted by a Fold, Traversal, Lens or Getter according to a user supplied ordering.

 maximumBy cmp = fromMaybe (error "empty") . maximumByOf folded cmp
 maximumByOf :: Getter a b c d    -> (c -> c -> Ordering) -> a -> Maybe c
 maximumByOf :: Lens a b c d      -> (c -> c -> Ordering) -> a -> Maybe c
 maximumByOf :: Fold a b c d      -> (c -> c -> Ordering) -> a -> Maybe c
 maximumByOf :: Traversal a b c d -> (c -> c -> Ordering) -> a -> Maybe c

minimumByOf :: Getting (Endo (Maybe c)) a b c d -> (c -> c -> Ordering) -> a -> Maybe cSource

Obtain the minimum element (if any) targeted by a Fold, Traversal, Lens or Getter according to a user supplied ordering.

 minimumBy cmp = fromMaybe (error "empty") . minimumByOf folded cmp
 minimumByOf :: Getter a b c d    -> (c -> c -> Ordering) -> a -> Maybe c
 minimumByOf :: Lens a b c d      -> (c -> c -> Ordering) -> a -> Maybe c
 minimumByOf :: Fold a b c d      -> (c -> c -> Ordering) -> a -> Maybe c
 minimumByOf :: Traversal a b c d -> (c -> c -> Ordering) -> a -> Maybe c

findOf :: Getting (First c) a b c d -> (c -> Bool) -> a -> Maybe cSource

The findOf function takes a lens, a predicate and a structure and returns the leftmost element of the structure matching the predicate, or Nothing if there is no such element.

foldrOf' :: Getting (Dual (Endo (e -> e))) a b c d -> (c -> e -> e) -> e -> a -> eSource

Strictly fold right over the elements of a structure.

 foldr' = foldrOf' folded
 foldrOf' :: Getter a b c d    -> (c -> e -> e) -> e -> a -> e
 foldrOf' :: Lens a b c d      -> (c -> e -> e) -> e -> a -> e
 foldrOf' :: Fold a b c d      -> (c -> e -> e) -> e -> a -> e
 foldrOf' :: Traversal a b c d -> (c -> e -> e) -> e -> a -> e

foldlOf' :: Getting (Endo (e -> e)) a b c d -> (e -> c -> e) -> e -> a -> eSource

Fold over the elements of a structure, associating to the left, but strictly.

 foldl' = foldlOf' folded
 foldlOf' :: Getter a b c d    -> (e -> c -> e) -> e -> a -> e
 foldlOf' :: Lens a b c d      -> (e -> c -> e) -> e -> a -> e
 foldlOf' :: Fold a b c d      -> (e -> c -> e) -> e -> a -> e
 foldlOf' :: Traversal a b c d -> (e -> c -> e) -> e -> a -> e

foldr1Of :: Getting (Endo (Maybe c)) a b c d -> (c -> c -> c) -> a -> cSource

A variant of foldrOf that has no base case and thus may only be applied to lenses and structures such that the lens views at least one element of the structure.

 foldr1Of l f = Prelude.foldr1 f . toListOf l
 foldr1 = foldr1Of folded
 foldr1Of :: Getter a b c d    -> (c -> c -> c) -> a -> c
 foldr1Of :: Lens a b c d      -> (c -> c -> c) -> a -> c
 foldr1Of :: Fold a b c d      -> (c -> c -> c) -> a -> c
 foldr1Of :: Traversal a b c d -> (c -> c -> c) -> a -> c

foldl1Of :: Getting (Dual (Endo (Maybe c))) a b c d -> (c -> c -> c) -> a -> cSource

A variant of foldlOf that has no base case and thus may only be applied to lenses and strutures such that the lens views at least one element of the structure.

 foldl1Of l f = Prelude.foldl1Of l f . toList
 foldl1 = foldl1Of folded
 foldl1Of :: Getter a b c d    -> (c -> c -> c) -> a -> c
 foldl1Of :: Lens a b c d      -> (c -> c -> c) -> a -> c
 foldl1Of :: Fold a b c d      -> (c -> c -> c) -> a -> c
 foldl1Of :: Traversal a b c d -> (c -> c -> c) -> a -> c

foldrMOf :: Monad m => Getting (Dual (Endo (e -> m e))) a b c d -> (c -> e -> m e) -> e -> a -> m eSource

Monadic fold over the elements of a structure, associating to the right, i.e. from right to left.

 foldrM = foldrMOf folded
 foldrMOf :: Monad m => Getter a b c d    -> (c -> e -> m e) -> e -> a -> m e
 foldrMOf :: Monad m => Lens a b c d      -> (c -> e -> m e) -> e -> a -> m e
 foldrMOf :: Monad m => Fold a b c d      -> (c -> e -> m e) -> e -> a -> m e
 foldrMOf :: Monad m => Traversal a b c d -> (c -> e -> m e) -> e -> a -> m e

foldlMOf :: Monad m => Getting (Endo (e -> m e)) a b c d -> (e -> c -> m e) -> e -> a -> m eSource

Monadic fold over the elements of a structure, associating to the left, i.e. from left to right.

 foldlM = foldlMOf folded
 foldlMOf :: Monad m => Getter a b c d    -> (e -> c -> m e) -> e -> a -> m e
 foldlMOf :: Monad m => Lens a b c d      -> (e -> c -> m e) -> e -> a -> m e
 foldlMOf :: Monad m => Fold a b c d      -> (e -> c -> m e) -> e -> a -> m e
 foldlMOf :: Monad m => Traversal a b c d -> (e -> c -> m e) -> e -> a -> m e

Getting and Folding State

use :: MonadState a m => Getting c a b c d -> m cSource

Use 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.

 use :: MonadState a m             => Getter a b c d    -> m c
 use :: MonadState a m             => Lens a b c d      -> m c
 use :: (MonadState a m, Monoid c) => Fold a b c d      -> m c
 use :: (MonadState a m, Monoid c) => Traversal a b c d -> m c
 use :: MonadState a m => ((c -> Const c d) -> a -> Const c b) -> m c

uses :: MonadState a m => Getting e a b c d -> (c -> e) -> m eSource

Use 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.

 uses :: MonadState a m             => Getter a b c d    -> (c -> e) -> m e
 uses :: MonadState a m             => Lens a b c d      -> (c -> e) -> m e
 uses :: (MonadState a m, Monoid c) => Fold a b c d      -> (c -> e) -> m e
 uses :: (MonadState a m, Monoid c) => Traversal a b c d -> (c -> e) -> m e
 uses :: MonadState a m => ((c -> Const e d) -> a -> Const e b) -> (c -> e) -> m e

Common Traversals

traverseNothing :: Traversal a a c dSource

This is the traversal that never succeeds at returning any values

 traverseNothing :: Applicative f => (c -> f d) -> a -> f a

traverseLeft :: Traversal (Either a c) (Either b c) a bSource

A traversal for tweaking the left-hand value in an Either:

 traverseLeft :: Applicative f => (a -> f b) -> Either a c -> f (Either b c)

traverseRight :: Traversal (Either c a) (Either c b) a bSource

traverse the right-hand value in an Either:

 traverseRight :: Applicative f => (a -> f b) -> Either c a -> f (Either c a)
 traverseRight = traverse

Unfortunately the instance for 'Traversable (Either c)' is still missing from base, so this can't just be traverse

traverseValueAt :: Ord k => k -> Simple Traversal (Map k v) vSource

Traverse the value at a given key in a Map

 traverseValueAt :: (Applicative f, Ord k) => k -> (v -> f v) -> Map k v -> f (Map k v)
 traverseValueAt k = valueAt k . traverse

traverseValueAtInt :: Int -> Simple Traversal (IntMap v) vSource

Traverse the value at a given key in an IntMap

 traverseValueAtInt :: Applicative f => Int -> (v -> f v) -> IntMap v -> f (IntMap v)
 traverseValueAtInt k = valueAtInt k . traverse

traverseHead :: Simple Traversal [a] aSource

 traverseHead :: Applicative f => (a -> f a) -> [a] -> f [a]

traverseTail :: Simple Traversal [a] [a]Source

Traversal for editing the tail of a list.

 traverseTail :: Applicative f => ([a] -> f [a]) -> [a] -> f [a]

traverseLast :: Simple Traversal [a] aSource

Traverse the last element in a list.

 traverseLast = traverseValueAtMax
 traverseLast :: Applicative f => (a -> f a) -> [a] -> f [a]

traverseInit :: Simple Traversal [a] [a]Source

Traverse all but the last element of a list

 traverseInit :: Applicative f => ([a] -> f [a]) -> [a] -> f [a]

class TraverseByteString t whereSource

Provides ad hoc overloading for traverseByteString

Methods

traverseByteString :: Simple Traversal t Word8Source

Traverse the individual bytes in a ByteString

 anyOf traverseByteString (==0x80) :: TraverseByteString b => b -> Bool

class TraverseText t whereSource

Provides ad hoc overloading for traverseText

Methods

traverseText :: Simple Traversal t CharSource

Traverse the individual characters in a Text

 anyOf traverseText (=='c') :: TraverseText b => b -> Bool

class TraverseValueAtMin t whereSource

Types that support traversal of the value of the minimal key

This is separate from TraverseValueAtMax because a min-heap or max-heap may be able to support one, but not the other.

Methods

traverseValueAtMin :: Simple Traversal (t v) vSource

Traverse the value for the minimal key

class TraverseValueAtMax t whereSource

Types that support traversal of the value of the maximal key

This is separate from TraverseValueAtMin because a min-heap or max-heap may be able to support one, but not the other.

Methods

traverseValueAtMax :: Simple Traversal (t v) vSource

Traverse the value for the maximal key

traverseBits :: Bits b => Simple Traversal b BoolSource

Traverse over all bits in a numeric type.

 ghci> toListOf traverseBits (5 :: Word8)
 [True,False,True,False,False,False,False,False]

If you supply this an Integer, it won't crash, but the result will be an infinite traversal that can be productively consumed.

 ghci> toListOf traverseBits 5
 [True,False,True,False,False,False,False,False,False,False,False,False...

traverseDynamic :: (Typeable a, Typeable b) => Traversal Dynamic Dynamic a bSource

Traverse the typed value contained in a Dynamic where the type required by your function matches that of the contents of the Dynamic.

 traverseDynamic :: (Applicative f, Typeable a, Typeable b) => (a -> f b) -> Dynamic -> f Dynamic

traverseException :: (Exception a, Exception b) => Traversal SomeException SomeException a bSource

Traverse the strongly typed Exception contained in SomeException where the type of your function matches the desired Exception.

 traverseException :: (Applicative f, Exception a, Exception b) => (a -> f b) -> SomeException -> f SomeException

traverseElement :: Traversable t => Int -> Simple Traversal (t a) aSource

Traverse a single element in a traversable container.

 traverseElement :: (Applicative f, Traversable t) => Int -> (a -> f a) -> t a -> f (t a)

traverseElements :: Traversable t => (Int -> Bool) -> Simple Traversal (t a) aSource

Traverse elements where a predicate holds on their position in a traversable container

 traverseElements :: Applicative f, Traversable t) => (Int -> Bool) -> (a -> f a) -> t a -> f (t a)

Transforming Traversals

elementOf :: Applicative f => LensLike (AppliedState f) a b c c -> Int -> LensLike f a b c cSource

Yields a Traversal of the nth element of another Traversal

 traverseHead = elementOf traverse 0

elementsOf :: Applicative f => LensLike (AppliedState f) a b c c -> (Int -> Bool) -> LensLike f a b c cSource

A Traversal of the elements in another Traversal where their positions in that Traversal satisfy a predicate

 traverseTail = elementsOf traverse (>0)

backwards :: LensLike (Backwards f) a b c d -> LensLike f a b c dSource

This allows you to traverse the elements of a Traversal in the opposite order.

Note: reversed is similar, but is able to accept a Fold (or Getter) and produce a Fold (or Getter).

This requires at least a Traversal (or Lens) and can produce a Traversal (or Lens) in turn.

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.