lens-3.9.0.3: Lenses, Folds and Traversals

Portabilitynon-portable
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellTrustworthy

Control.Lens.Prism

Contents

Description

 

Synopsis

Prisms

type Prism s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t)Source

A Prism l is a 0-or-1 target Traversal that can also be turned around with re to obtain a Getter in the opposite direction.

There are two laws that a Prism should satisfy:

First, if I re or review a value with a Prism and then preview or use (^?), I will get it back:

 preview l (review l b) ≡ Just b

Second, if you can extract a value a using a Prism l from a value s, then the value s is completely described my l and a:

If preview l s ≡ Just a then review l a ≡ s

These two laws imply that the Traversal laws hold for every Prism and that we traverse at most 1 element:

 lengthOf l x <= 1

It may help to think of this as a Iso that can be partial in one direction.

Every Prism is a valid Traversal.

Every Iso is a valid Prism.

For example, you might have a Prism' Integer Natural allows you to always go from a Natural to an Integer, and provide you with tools to check if an Integer is a Natural and/or to edit one if it is.

 nat :: Prism' Integer Natural
 nat = prism toInteger $ \ i ->
    if i < 0
    then Left i
    else Right (fromInteger i)

Now we can ask if an Integer is a Natural.

>>> 5^?nat
Just 5
>>> (-5)^?nat
Nothing

We can update the ones that are:

>>> (-3,4) & both.nat *~ 2
(-3,8)

And we can then convert from a Natural to an Integer.

>>> 5 ^. re nat -- :: Natural
5

Similarly we can use a Prism to traverse the Left half of an Either:

>>> Left "hello" & _Left %~ length
Left 5

or to construct an Either:

>>> 5^.re _Left
Left 5

such that if you query it with the Prism, you will get your original input back.

>>> 5^.re _Left ^? _Left
Just 5

Another interesting way to think of a Prism is as the categorical dual of a Lens -- a co-Lens, so to speak. This is what permits the construction of outside.

Note: Composition with a Prism is index-preserving.

type Prism' s a = Prism s s a aSource

type APrism s t a b = Market a b a (Mutator b) -> Market a b s (Mutator t)Source

If you see this in a signature for a function, the function is expecting a Prism.

type APrism' s a = APrism s s a aSource

 type APrism' = Simple APrism

Constructing Prisms

prism :: (b -> t) -> (s -> Either t a) -> Prism s t a bSource

Build a Prism.

Either t a is used instead of Maybe a to permit the types of s and t to differ.

prism' :: (b -> s) -> (s -> Maybe a) -> Prism s s a bSource

This is usually used to build a Prism', when you have to use an operation like cast which already returns a Maybe.

Consuming Prisms

clonePrism :: APrism s t a b -> Prism s t a bSource

Clone a Prism so that you can reuse the same monomorphically typed Prism for different purposes.

See cloneLens and cloneTraversal for examples of why you might want to do this.

outside :: APrism s t a b -> Lens (t -> r) (s -> r) (b -> r) (a -> r)Source

Use a Prism as a kind of first-class pattern.

outside :: Prism s t a b -> Lens (t -> r) (s -> r) (b -> r) (a -> r)

aside :: APrism s t a b -> Prism (e, s) (e, t) (e, a) (e, b)Source

Use a Prism to work over part of a structure.

without :: APrism s t a b -> APrism u v c d -> Prism (Either s u) (Either t v) (Either a c) (Either b d)Source

Given a pair of prisms, project sums.

Viewing a Prism as a co-Lens, this combinator can be seen to be dual to alongside.

isn't :: APrism s t a b -> s -> BoolSource

Check to see if this Prism doesn't match.

>>> isn't _Left (Right 12)
True
>>> isn't _Left (Left 12)
False

Common Prisms

_Left :: Prism (Either a c) (Either b c) a bSource

This Prism provides a Traversal for tweaking the Left half of an Either:

>>> over _Left (+1) (Left 2)
Left 3
>>> over _Left (+1) (Right 2)
Right 2
>>> Right 42 ^._Left :: String
""
>>> Left "hello" ^._Left
"hello"

It also can be turned around to obtain the embedding into the Left half of an Either:

>>> _Left # 5
Left 5
>>> 5^.re _Left
Left 5

_Right :: Prism (Either c a) (Either c b) a bSource

This Prism provides a Traversal for tweaking the Right half of an Either:

>>> over _Right (+1) (Left 2)
Left 2
>>> over _Right (+1) (Right 2)
Right 3
>>> Right "hello" ^._Right
"hello"
>>> Left "hello" ^._Right :: [Double]
[]

It also can be turned around to obtain the embedding into the Right half of an Either:

>>> _Right # 5
Right 5
>>> 5^.re _Right
Right 5

_Just :: Prism (Maybe a) (Maybe b) a bSource

This Prism provides a Traversal for tweaking the target of the value of Just in a Maybe.

>>> over _Just (+1) (Just 2)
Just 3

Unlike traverse this is a Prism, and so you can use it to inject as well:

>>> _Just # 5
Just 5
>>> 5^.re _Just
Just 5

Interestingly,

 m ^? _Just ≡ m
>>> Just x ^? _Just
Just x
>>> Nothing ^? _Just
Nothing

_Nothing :: Prism' (Maybe a) ()Source

This Prism provides the Traversal of a Nothing in a Maybe.

>>> Nothing ^? _Nothing
Just ()
>>> Just () ^? _Nothing
Nothing

But you can turn it around and use it to construct Nothing as well:

>>> _Nothing # ()
Nothing

_Void :: Prism s s a VoidSource

Void is a logically uninhabited data type.

This is a Prism that will always fail to match.

only :: Eq a => a -> Prism' a ()Source

This Prism compares for exact equality with a given value.

>>> only 4 # ()
4
>>> 5 ^? only 4
Nothing

Prismatic profunctors

class Profunctor p => Choice p where

The generalization of DownStar of a "costrong" Functor

Minimal complete definition: left' or right'

Note: We use traverse and extract as approximate costrength as needed.

Methods

left' :: p a b -> p (Either a c) (Either b c)

right' :: p a b -> p (Either c a) (Either c b)

Instances

Choice (->) 
Choice Reviewed 
Monad m => Choice (Kleisli m) 
Comonad w => Choice (Cokleisli w)

extract approximates costrength

Traversable w => Choice (DownStar w)

sequence approximates costrength

Applicative f => Choice (UpStar f) 
ArrowChoice p => Choice (WrappedArrow p) 
Monoid r => Choice (Forget r) 
Choice (Tagged *) 
Choice (Indexed i) 
Choice (Market a b)