lens-3.7.1.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. Gettable 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 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. 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 Getting r s t a b = (a -> Accessor r b) -> s -> Accessor r tSource

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.

Building Getters

to :: (s -> a) -> Getter 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 t a b -> 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 -> Simple Iso s a         -> a
 (^.) ::             s -> Simple Lens s a        -> a
 (^.) :: Monoid m => s -> Simple Traversal s m   -> m

(^$) :: Getting a s t a b -> s -> 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 values.

This is the same operation as view, only infix.

to f ^$ x ≡ f x
>>> to f ^$ x
f x
>>> _2 ^$ (1, "hello")
"hello"
 (^$) ::             Getter s a             -> s -> a
 (^$) :: Monoid m => Fold s m               -> s -> m
 (^$) ::             Simple Iso s a         -> s -> a
 (^$) ::             Simple Lens s a        -> s -> a
 (^$) :: Monoid m => Simple Traversal s m   -> s -> m

(&) :: a -> (a -> b) -> bSource

Passes the result of the left side to the function on the right side (forward pipe operator).

This is the flipped version of ($), which is more common in languages like F# as (|>) where it is needed for inference. Here it is supplied for notational convenience and given a precedence that allows it to be nested inside uses of ($).

>>> a & f
f a
>>> "hello" & length & succ
6

This combinator is commonly used when applying multiple lens operations in sequence.

>>> ("hello","world") & _1.element 0 .~ 'j' & _1.element 4 .~ 'y'
("jelly","world")

This reads somewhat similar to:

>>> flip execState ("hello","world") $ do _1.element 0 .= 'j'; _1.element 4 .= 'y'
("jelly","world")

(^&) :: a -> (a -> b) -> bSource

A version of (&) with much tighter precedence that can be interleaved with (^.)

>>> a ^& f
f a
>>> "hello" ^& length
5
>>> ("hello","world")^._1^&reverse^?!_head
'o'

view :: MonadReader s m => Getting a s t a b -> 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 values.

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 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 restrictive signatures:

 view ::             Getter s a             -> s -> a
 view :: Monoid m => Fold s m               -> s -> m
 view ::             Simple Iso s a         -> s -> a
 view ::             Simple Lens s a        -> s -> a
 view :: Monoid m => Simple 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             => Simple Iso s a       -> m a
 view :: MonadReader s m             => Simple Lens s a      -> m a
 view :: (MonadReader s m, Monoid a) => Simple Traversal s a -> m a

views :: MonadReader s m => Getting r s t a b -> (a -> r) -> m rSource

View the value of a Getter, Iso, 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 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 restrictive signatures:

 views ::             Getter s a             -> (a -> r) -> s -> r
 views :: Monoid m => Fold s a               -> (a -> m) -> s -> m
 views ::             Simple Iso s a         -> (a -> r) -> s -> r
 views ::             Simple Lens s a        -> (a -> r) -> s -> r
 views :: Monoid m => Simple 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             => Simple Iso s a       -> m a
 view :: MonadReader s m             => Simple Lens s a      -> m a
 view :: (MonadReader s m, Monoid a) => Simple Traversal s a -> m a

use :: MonadState s m => Getting a s t a b -> 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             => Simple Iso s a         -> m a
 use :: MonadState s m             => Simple Lens s a        -> m a
 use :: (MonadState s m, Monoid r) => Simple Traversal s r   -> m r

uses :: MonadState s m => Getting r s t a b -> (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             => Simple Lens s a      -> (a -> r) -> m r
 uses :: MonadState s m             => Simple Iso s a       -> (a -> r) -> m r
 uses :: (MonadState s m, Monoid r) => Simple Traversal s a -> (a -> r) -> m r

Simple Getter Operations

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

This is a type restricted version of view that expects a Simple Getter.

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

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 restrictive signatures:

 view' ::             Getter s a             -> s -> a
 view' :: Monoid m => Fold s m               -> s -> m
 view' ::             Simple Iso s a         -> s -> a
 view' ::             Simple Lens s a        -> s -> a
 view' :: Monoid m => Simple 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             => Simple Iso s a       -> m a
 view' :: MonadReader s m             => Simple Lens s a      -> m a
 view' :: (MonadReader s m, Monoid a) => Simple Traversal s a -> m a

views' :: MonadReader s m => Getting r s s a a -> (a -> r) -> m rSource

This is a type restricted version of views that expects a Simple Getter.

View the value of a Getter, Iso, 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 perviews as having these more restrictive signatures:

views' l f ≡ view' (l . to f)
>>> 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 restrictive signatures:

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

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

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

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

This is a type restricted version of use that expects a Simple Getter.

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

This use of this combinator may aid type-inference when working with lenses or traversals that have non-defaultable typeclass constraints on their arguments.

>>> 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             => Simple Iso s a         -> m a
 use' :: MonadState s m             => Simple Lens s a        -> m a
 use' :: (MonadState s m, Monoid r) => Simple Traversal s r   -> m r

uses' :: MonadState s m => Getting r s s a a -> (a -> r) -> m rSource

This is a type restricted version of uses that expects a Simple Getter.

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             => Simple Lens s a      -> (a -> r) -> m r
 uses' :: MonadState s m             => Simple Iso s a       -> (a -> r) -> m r
 uses' :: (MonadState s m, Monoid r) => Simple Traversal s a -> (a -> r) -> m r

Storing Getters

newtype ReifiedGetter s a Source

Useful for storing getters in containers.

Constructors

ReifyGetter 

Fields

reflectGetter :: Getter s a
 

class Functor f => Gettable f Source

Generalizing Const so we can apply simple Applicative transformations to it and so we can get nicer error messages

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

To ensure this, an instance of Gettable is required to satisfy:

id = fmap f = coerce

Which is equivalent to making a Gettable f an "anyvariant" functor.

Instances

data Accessor r a Source

Used instead of Const to report

No instance of (Settable Accessor)

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

Instances