lens-3.9.2: Lenses, Folds and Traversals

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

Control.Lens.Getter

Contents

Description

A Getter s a is just any function (s -> a), which we've flipped into continuation passing style, (a -> r) -> s -> r and decorated with Accessor to obtain:

type Getting r s t a b = (a -> Accessor r b) -> s -> Accessor r t

If we restrict access to knowledge about the type r and can work for any b and t, we could get:

type Getter s a = forall r. Getting r s s a a

But we actually hide the use of Accessor behind a class Gettable to error messages from type class resolution rather than at unification time, where they are much uglier.

type Getter s a = forall f. Gettable f => (a -> f a) -> s -> f s

Everything you can do with a function, you can do with a Getter, but note that because of the continuation passing style (.) composes them in the opposite order.

Since it is only a function, every Getter obviously only retrieves a single value for a given input.

Synopsis

Getters

type Getter s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f sSource

A Getter describes how to retrieve a single value in a way that can be composed with other LensLike 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. In fact, it is isomorphic to an arbitrary function from (a -> s).

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

type IndexedGetter i s a = forall p f. (Indexable i p, Contravariant f, Functor f) => p a (f a) -> s -> f sSource

Every IndexedGetter is a valid IndexedFold and can be used for Getting like a Getter.

type Getting r s a = (a -> Accessor r a) -> s -> Accessor r sSource

When you see this in a type signature it indicates that you can pass the function a Lens, Getter, Traversal, Fold, Prism, Iso, or one of the indexed variants, and it will just "do the right thing".

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. To be compatible with Lens, Traversal and Iso we also restricted choices of the irrelevant t and b parameters.

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

type IndexedGetting i m s a = Indexed i a (Accessor m a) -> s -> Accessor m sSource

Used to consume an IndexedFold.

type Accessing p m s a = p a (Accessor m a) -> s -> Accessor m sSource

This is a convenient alias used when consuming (indexed) getters and (indexed) folds in a highly general fashion.

Building Getters

to :: (s -> a) -> IndexPreservingGetter s aSource

Build a Getter from an arbitrary Haskell function.

 to f . to g ≡ to (g . f)
 a ^. to f ≡ f a
>>> a ^.to f
f a
>>> ("hello","world")^.to snd
"world"
>>> 5^.to succ
6
>>> (0, -5)^._2.to abs
5

Combinators for Getters and Folds

(^.) :: s -> Getting a s a -> aSource

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

>>> (a,b)^._2
b
>>> ("hello","world")^._2
"world"
>>> import Data.Complex
>>> ((0, 1 :+ 2), 3)^._1._2.to magnitude
2.23606797749979
 (^.) ::             s -> Getter s a     -> a
 (^.) :: Monoid m => s -> Fold s m       -> m
 (^.) ::             s -> Iso' s a       -> a
 (^.) ::             s -> Lens' s a      -> a
 (^.) :: Monoid m => s -> Traversal' s m -> m

view :: MonadReader s m => Getting a s a -> m aSource

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

 view . toid
>>> view (to f) a
f a
>>> view _2 (1,"hello")
"hello"
>>> view (to succ) 5
6
>>> view (_2._1) ("hello",("world","!!!"))
"world"

As view is commonly used to access the target of a Getter or obtain a monoidal summary of the targets of a Fold, It may be useful to think of it as having one of these more restricted signatures:

 view ::             Getter s a     -> s -> a
 view :: Monoid m => Fold s m       -> s -> m
 view ::             Iso' s a       -> s -> a
 view ::             Lens' s a      -> s -> a
 view :: Monoid m => Traversal' s m -> s -> m

In a more general setting, such as when working with a Monad transformer stack you can use:

 view :: MonadReader s m             => Getter s a     -> m a
 view :: (MonadReader s m, Monoid a) => Fold s a       -> m a
 view :: MonadReader s m             => Iso' s a       -> m a
 view :: MonadReader s m             => Lens' s a      -> m a
 view :: (MonadReader s m, Monoid a) => Traversal' s a -> m a

views :: (Profunctor p, MonadReader s m) => Overloading p (->) (Accessor r) s s a a -> p a r -> m rSource

View a function of the value pointed to by a Getter or Lens or the result of folding over the result of mapping the targets of a Fold or Traversal.

 views l f ≡ view (l . to f)
>>> views (to f) g a
g (f a)
>>> views _2 length (1,"hello")
5

As views is commonly used to access the target of a Getter or obtain a monoidal summary of the targets of a Fold, It may be useful to think of it as having one of these more restricted signatures:

 views ::             Getter s a     -> (a -> r) -> s -> r
 views :: Monoid m => Fold s a       -> (a -> m) -> s -> m
 views ::             Iso' s a       -> (a -> r) -> s -> r
 views ::             Lens' s a      -> (a -> r) -> s -> r
 views :: Monoid m => Traversal' s a -> (a -> m) -> s -> m

In a more general setting, such as when working with a Monad transformer stack you can use:

 view :: MonadReader s m             => Getter s a     -> m a
 view :: (MonadReader s m, Monoid a) => Fold s a       -> m a
 view :: MonadReader s m             => Iso' s a       -> m a
 view :: MonadReader s m             => Lens' s a      -> m a
 view :: (MonadReader s m, Monoid a) => Traversal' s a -> m a
 views :: MonadReader s m => Getting r s a -> (a -> r) -> m r

use :: MonadState s m => Getting a s a -> m aSource

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

>>> evalState (use _1) (a,b)
a
>>> evalState (use _1) ("hello","world")
"hello"
 use :: MonadState s m             => Getter s a     -> m a
 use :: (MonadState s m, Monoid r) => Fold s r       -> m r
 use :: MonadState s m             => Iso' s a       -> m a
 use :: MonadState s m             => Lens' s a      -> m a
 use :: (MonadState s m, Monoid r) => Traversal' s r -> m r

uses :: (Profunctor p, MonadState s m) => Overloading p (->) (Accessor r) s s a a -> p a r -> m rSource

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

>>> evalState (uses _1 length) ("hello","world")
5
 uses :: MonadState s m             => Getter s a     -> (a -> r) -> m r
 uses :: (MonadState s m, Monoid r) => Fold s a       -> (a -> r) -> m r
 uses :: MonadState s m             => Lens' s a      -> (a -> r) -> m r
 uses :: MonadState s m             => Iso' s a       -> (a -> r) -> m r
 uses :: (MonadState s m, Monoid r) => Traversal' s a -> (a -> r) -> m r
 uses :: MonadState s m => Getting r s t a b -> (a -> r) -> m r

listening :: MonadWriter w m => Getting u w u -> m a -> m (a, u)Source

This is a generalized form of listen that only extracts the portion of the log that is focused on by a Getter. If given a Fold or a Traversal then a monoidal summary of the parts of the log that are visited will be returned.

 listening :: MonadWriter w m             => Getter w u     -> m a -> m (a, u)
 listening :: MonadWriter w m             => Lens' w u      -> m a -> m (a, u)
 listening :: MonadWriter w m             => Iso' w u       -> m a -> m (a, u)
 listening :: (MonadWriter w m, Monoid u) => Fold w u       -> m a -> m (a, u)
 listening :: (MonadWriter w m, Monoid u) => Traversal' w u -> m a -> m (a, u)
 listening :: (MonadWriter w m, Monoid u) => Prism' w u     -> m a -> m (a, u)

listenings :: MonadWriter w m => Getting v w u -> (u -> v) -> m a -> m (a, v)Source

This is a generalized form of listen that only extracts the portion of the log that is focused on by a Getter. If given a Fold or a Traversal then a monoidal summary of the parts of the log that are visited will be returned.

 listenings :: MonadWriter w m             => Getter w u     -> (u -> v) -> m a -> m (a, v)
 listenings :: MonadWriter w m             => Lens' w u      -> (u -> v) -> m a -> m (a, v)
 listenings :: MonadWriter w m             => Iso' w u       -> (u -> v) -> m a -> m (a, v)
 listenings :: (MonadWriter w m, Monoid v) => Fold w u       -> (u -> v) -> m a -> m (a, v)
 listenings :: (MonadWriter w m, Monoid v) => Traversal' w u -> (u -> v) -> m a -> m (a, v)
 listenings :: (MonadWriter w m, Monoid v) => Prism' w u     -> (u -> v) -> m a -> m (a, v)

Indexed Getters

Indexed Getter Combinators

(^@.) :: s -> IndexedGetting i (i, a) s a -> (i, a)Source

View the value pointed to by a Getter or Lens.

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

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

>>> (a,b,c,d)^@._2
(1,b)
>>> ("hello","world","!!!")^@._2
(1,"world")
 (^@.) :: s -> IndexedGetter i s a -> (i, a)
 (^@.) :: s -> IndexedLens' i s a  -> (i, a)

The result probably doesn't have much meaning when applied to an IndexedFold.

iview :: MonadReader s m => IndexedGetting i (i, a) s a -> m (i, a)Source

View the index and value of an IndexedGetter into the current environment as a pair.

When applied to an IndexedFold the result will most likely be a nonsensical monoidal summary of the indices tupled with a monoidal summary of the values and probably not whatever it is you wanted.

iviews :: MonadReader s m => IndexedGetting i r s a -> (i -> a -> r) -> m rSource

View a function of the index and value of an IndexedGetter into the current environment.

When applied to an IndexedFold the result will be a monoidal summary instead of a single answer.

 iviewsifoldMapOf

iuse :: MonadState s m => IndexedGetting i (i, a) s a -> m (i, a)Source

Use the index and value of an IndexedGetter into the current state as a pair.

When applied to an IndexedFold the result will most likely be a nonsensical monoidal summary of the indices tupled with a monoidal summary of the values and probably not whatever it is you wanted.

iuses :: MonadState s m => IndexedGetting i r s a -> (i -> a -> r) -> m rSource

Use a function of the index and value of an IndexedGetter into the current state.

When applied to an IndexedFold the result will be a monoidal summary instead of a single answer.

ilistening :: MonadWriter w m => IndexedGetting i (i, u) w u -> m a -> m (a, (i, u))Source

This is a generalized form of listen that only extracts the portion of the log that is focused on by a Getter. If given a Fold or a Traversal then a monoidal summary of the parts of the log that are visited will be returned.

 ilistening :: MonadWriter w m             => IndexedGetter i w u     -> m a -> m (a, (i, u))
 ilistening :: MonadWriter w m             => IndexedLens' i w u      -> m a -> m (a, (i, u))
 ilistening :: (MonadWriter w m, Monoid u) => IndexedFold i w u       -> m a -> m (a, (i, u))
 ilistening :: (MonadWriter w m, Monoid u) => IndexedTraversal' i w u -> m a -> m (a, (i, u))

ilistenings :: MonadWriter w m => IndexedGetting i v w u -> (i -> u -> v) -> m a -> m (a, v)Source

This is a generalized form of listen that only extracts the portion of the log that is focused on by a Getter. If given a Fold or a Traversal then a monoidal summary of the parts of the log that are visited will be returned.

 ilistenings :: MonadWriter w m             => IndexedGetter w u     -> (i -> u -> v) -> m a -> m (a, v)
 ilistenings :: MonadWriter w m             => IndexedLens' w u      -> (i -> u -> v) -> m a -> m (a, v)
 ilistenings :: (MonadWriter w m, Monoid v) => IndexedFold w u       -> (i -> u -> v) -> m a -> m (a, v)
 ilistenings :: (MonadWriter w m, Monoid v) => IndexedTraversal' w u -> (i -> u -> v) -> m a -> m (a, v)

Implementation Details

class Contravariant f where

Any instance should be subject to the following laws:

 contramap id = id
 contramap f . contramap g = contramap (g . f)

Note, that the second law follows from the free theorem of the type of contramap and the first law, so you need only check that the former condition holds.

Methods

contramap :: (a -> b) -> f b -> f a

Instances

Contravariant Predicate

A Predicate is a Contravariant Functor, because contramap can apply its function argument to the input of the predicate.

Contravariant Comparison

A Comparison is a Contravariant Functor, because contramap can apply its function argument to each input to each input to the comparison function.

Contravariant Equivalence

Equivalence relations are Contravariant, because you can apply the contramapped function to each input to the equivalence relation.

Contravariant (Const a) 
Contravariant (Op a) 
Contravariant (Proxy *) 
Contravariant f => Contravariant (Backwards f) 
Contravariant f => Contravariant (Reverse f) 
Contravariant (Constant a) 
Contravariant (Accessor r) 
Contravariant f => Contravariant (Indexing64 f) 
Contravariant f => Contravariant (Indexing f) 
(Contravariant f, Contravariant g) => Contravariant (Coproduct f g) 
(Functor f, Contravariant g) => Contravariant (ComposeFC f g) 
(Contravariant f, Functor g) => Contravariant (ComposeCF f g) 
(Functor f, Contravariant g) => Contravariant (Compose f g) 
(Contravariant f, Contravariant g) => Contravariant (Product f g) 
Contravariant (Effect m r) 
(Profunctor p, Contravariant g) => Contravariant (PretextT p g a b) 
(Profunctor p, Contravariant g) => Contravariant (BazaarT p g a b) 
Contravariant f => Contravariant (TakingWhile p f a b) 
Contravariant (EffectRWS w st m s) 

coerce :: (Contravariant f, Functor f) => f a -> f bSource

This Generalizes Const so we can apply simple Applicative transformations to it and so we can get nicer error messages.

A Functor you can coerce ignores its argument, which it carries solely as a phantom type parameter.

By the Functor and Contravariant laws, an instance of Gettable will necessarily satisfy:

id = fmap f = coerce = contramap g

coerced :: (Functor f, Contravariant f) => LensLike f s t a b -> LensLike' f s aSource

Coerce a Gettable LensLike to a Simple LensLike. This is useful when using a Traversal that is not simple as a Getter or a Fold.

newtype Accessor r a Source

Used instead of Const to report

No instance for (Settable Accessor)

when the user attempts to misuse a Setter as a Getter, rather than a monolithic unification error.

Constructors

Accessor 

Fields

runAccessor :: r
 

Instances

class (Contravariant f, Functor f) => Gettable f Source

This class is provided mostly for backwards compatibility with lens 3.8, but it can also shorten type signatures.

Instances