Copyright | (c) 2013-2023 Brendan Hay |
---|---|
License | Mozilla Public License, v. 2.0. |
Maintainer | Brendan Hay <brendan.g.hay+amazonka@gmail.com> |
Stability | provisional |
Portability | non-portable (GHC extensions) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Re-export a number of lens types and combinators for use in service bindings.
Synopsis
- (<&>) :: Functor f => f a -> (a -> b) -> f b
- throwingM :: MonadThrow m => AReview SomeException b -> b -> m r
- trying :: MonadCatch m => Getting (First a) SomeException a -> m r -> m (Either a r)
- catching_ :: MonadCatch m => Getting (First a) SomeException a -> m r -> m r -> m r
- catching :: MonadCatch m => Getting (First a) SomeException a -> m r -> (a -> m r) -> m r
- exception :: Exception a => Prism' SomeException a
- _IOException :: AsIOException t => Prism' t IOException
- _last :: Snoc s s a a => Traversal' s a
- coerced :: forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
- non :: Eq a => a -> Iso' (Maybe a) a
- mapping :: forall (f :: Type -> Type) (g :: Type -> Type) s t a b. (Functor f, Functor g) => AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
- iso :: (s -> a) -> (b -> t) -> Iso s t a b
- traversed :: forall (f :: Type -> Type) a b. Traversable f => IndexedTraversal Int (f a) (f b) a b
- has :: Getting Any s a -> s -> Bool
- (^?) :: s -> Getting (First a) s a -> Maybe a
- concatOf :: Getting [r] s [r] -> s -> [r]
- allOf :: Getting All s a -> (a -> Bool) -> s -> Bool
- anyOf :: Getting Any s a -> (a -> Bool) -> s -> Bool
- (^..) :: s -> Getting (Endo [a]) s a -> [a]
- filtered :: (Choice p, Applicative f) => (a -> Bool) -> Optic' p f a a
- folding :: Foldable f => (s -> f a) -> Fold s a
- _Just :: Prism (Maybe a) (Maybe b) a b
- prism :: (b -> t) -> (s -> Either t a) -> Prism s t a b
- (#) :: AReview t b -> b -> t
- un :: (Profunctor p, Bifunctor p, Functor f) => Getting a s a -> Optic' p f a s
- (^.) :: s -> Getting a s a -> a
- view :: MonadReader s m => Getting a s a -> m a
- to :: (Profunctor p, Contravariant f) => (s -> a) -> Optic' p f s a
- type Getting r s a = (a -> Const r a) -> s -> Const r s
- _1 :: Field1 s t a b => Lens s t a b
- _2 :: Field2 s t a b => Lens s t a b
- lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
- (<>~) :: Semigroup a => ASetter s t a a -> a -> s -> t
- (?~) :: ASetter s t a (Maybe b) -> b -> s -> t
- (.~) :: ASetter s t a b -> b -> s -> t
- (%~) :: ASetter s t a b -> (a -> b) -> s -> t
- sets :: (Profunctor p, Profunctor q, Settable f) => (p a b -> q s t) -> Optical p q f s t a b
- type Lens s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t
- type Lens' s a = Lens s s a a
- type Traversal' s a = Traversal s s a a
- type IndexedTraversal' i s a = IndexedTraversal i s s a a
- type Setter' s a = Setter s s a a
- type Iso' s a = Iso s s a a
- type AReview t b = Optic' (Tagged :: Type -> Type -> Type) Identity t b
- type Prism' s a = Prism s s a a
- type Getter s a = forall (f :: Type -> Type). (Contravariant f, Functor f) => (a -> f a) -> s -> f s
- type Fold s a = forall (f :: Type -> Type). (Contravariant f, Applicative f) => (a -> f a) -> s -> f s
- type Optic' (p :: k -> k1 -> Type) (f :: k -> k1) (s :: k) (a :: k) = Optic p f s s a a
- class Profunctor p => Choice (p :: Type -> Type -> Type)
Documentation
throwingM :: MonadThrow m => AReview SomeException b -> b -> m r #
A variant of throwing
that can only be used within the IO
Monad
(or any other MonadCatch
instance) to throw an Exception
described
by a ReifiedPrism
.
Although throwingM
has a type that is a specialization of the type of
throwing
, the two functions are subtly different:
throwing
l e `seq` x ≡throwing
ethrowingM
l e `seq` x ≡ x
The first example will cause the Exception
e
to be raised, whereas the
second one won't. In fact, throwingM
will only cause an Exception
to
be raised when it is used within the MonadCatch
instance. The throwingM
variant should be used in preference to throwing
to raise an Exception
within the Monad
because it guarantees ordering with respect to other
monadic operations, whereas throwing
does not.
throwingM
l ≡reviews
lthrow
throwingM
::MonadThrow
m =>Prism'
SomeException
t -> t -> m rthrowingM
::MonadThrow
m =>Iso'
SomeException
t -> t -> m r
trying :: MonadCatch m => Getting (First a) SomeException a -> m r -> m (Either a r) #
A variant of try
that takes a ReifiedPrism
(or any ReifiedFold
) to select which
exceptions are caught (c.f. tryJust
, catchJust
). If the
Exception
does not match the predicate, it is re-thrown.
trying
::MonadCatch
m =>Prism'
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatch
m =>Lens'
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatch
m =>Traversal'
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatch
m =>Iso'
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatch
m =>ReifiedGetter
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatch
m =>ReifiedFold
SomeException
a -> m r -> m (Either
a r)
catching_ :: MonadCatch m => Getting (First a) SomeException a -> m r -> m r -> m r #
Catch exceptions that match a given ReifiedPrism
(or any ReifiedGetter
), discarding
the information about the match. This is particularly useful when you have
a
where the result of the Prism'
e ()ReifiedPrism
or ReifiedFold
isn't
particularly valuable, just the fact that it matches.
>>>
catching_ _AssertionFailed (assert False (return "uncaught")) $ return "caught"
"caught"
catching_
::MonadCatch
m =>Prism'
SomeException
a -> m r -> m r -> m rcatching_
::MonadCatch
m =>Lens'
SomeException
a -> m r -> m r -> m rcatching_
::MonadCatch
m =>Traversal'
SomeException
a -> m r -> m r -> m rcatching_
::MonadCatch
m =>Iso'
SomeException
a -> m r -> m r -> m rcatching_
::MonadCatch
m =>ReifiedGetter
SomeException
a -> m r -> m r -> m rcatching_
::MonadCatch
m =>ReifiedFold
SomeException
a -> m r -> m r -> m r
catching :: MonadCatch m => Getting (First a) SomeException a -> m r -> (a -> m r) -> m r #
Catch exceptions that match a given ReifiedPrism
(or any ReifiedFold
, really).
>>>
catching _AssertionFailed (assert False (return "uncaught")) $ \ _ -> return "caught"
"caught"
catching
::MonadCatch
m =>Prism'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>Lens'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>Traversal'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>Iso'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>ReifiedGetter
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>ReifiedFold
SomeException
a -> m r -> (a -> m r) -> m r
exception :: Exception a => Prism' SomeException a #
Traverse the strongly typed Exception
contained in SomeException
where the type of your function matches
the desired Exception
.
exception
:: (Applicative
f,Exception
a) => (a -> f a) ->SomeException
-> fSomeException
_IOException :: AsIOException t => Prism' t IOException #
Unfortunately the name ioException
is taken by base
for
throwing IOExceptions.
_IOException
::Prism'
IOException
IOException
_IOException
::Prism'
SomeException
IOException
Many combinators for working with an IOException
are available
in System.IO.Error.Lens.
_last :: Snoc s s a a => Traversal' s a #
A Traversal
reading and writing to the last element of a non-empty container.
>>>
[a,b,c]^?!_last
c
>>>
[]^?_last
Nothing
>>>
[a,b,c] & _last %~ f
[a,b,f c]
>>>
[1,2]^?_last
Just 2
>>>
[] & _last .~ 1
[]
>>>
[0] & _last .~ 2
[2]
>>>
[0,1] & _last .~ 2
[0,2]
This Traversal
is not limited to lists, however. We can also work with other containers, such as a Vector
.
>>>
Vector.fromList "abcde" ^? _last
Just 'e'
>>>
Vector.empty ^? _last
Nothing
>>>
(Vector.fromList "abcde" & _last .~ 'Q') == Vector.fromList "abcdQ"
True
_last
::Traversal'
[a] a_last
::Traversal'
(Seq
a) a_last
::Traversal'
(Vector
a) a
coerced :: forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b #
Data types that are representationally equal are isomorphic.
This is only available on GHC 7.8+
Since: lens-4.13
non :: Eq a => a -> Iso' (Maybe a) a #
If v
is an element of a type a
, and a'
is a
sans the element v
, then
is an isomorphism from
non
v
to Maybe
a'a
.
non
≡non'
.
only
Keep in mind this is only a real isomorphism if you treat the domain as being
.Maybe
(a sans v)
This is practically quite useful when you want to have a Map
where all the entries should have non-zero values.
>>>
Map.fromList [("hello",1)] & at "hello" . non 0 +~ 2
fromList [("hello",3)]
>>>
Map.fromList [("hello",1)] & at "hello" . non 0 -~ 1
fromList []
>>>
Map.fromList [("hello",1)] ^. at "hello" . non 0
1
>>>
Map.fromList [] ^. at "hello" . non 0
0
This combinator is also particularly useful when working with nested maps.
e.g. When you want to create the nested Map
when it is missing:
>>>
Map.empty & at "hello" . non Map.empty . at "world" ?~ "!!!"
fromList [("hello",fromList [("world","!!!")])]
and when have deleting the last entry from the nested Map
mean that we
should delete its entry from the surrounding one:
>>>
Map.fromList [("hello",Map.fromList [("world","!!!")])] & at "hello" . non Map.empty . at "world" .~ Nothing
fromList []
It can also be used in reverse to exclude a given value:
>>>
non 0 # rem 10 4
Just 2
>>>
non 0 # rem 10 5
Nothing
mapping :: forall (f :: Type -> Type) (g :: Type -> Type) s t a b. (Functor f, Functor g) => AnIso s t a b -> Iso (f s) (g t) (f a) (g b) #
traversed :: forall (f :: Type -> Type) a b. Traversable f => IndexedTraversal Int (f a) (f b) a b #
Traverse any Traversable
container. This is an IndexedTraversal
that is indexed by ordinal position.
has :: Getting Any s a -> s -> Bool #
Check to see if this Fold
or Traversal
matches 1 or more entries.
>>>
has (element 0) []
False
>>>
has _Left (Left 12)
True
>>>
has _Right (Left 12)
False
This will always return True
for a Lens
or Getter
.
>>>
has _1 ("hello","world")
True
has
::Getter
s a -> s ->Bool
has
::Fold
s a -> s ->Bool
has
::Iso'
s a -> s ->Bool
has
::Lens'
s a -> s ->Bool
has
::Traversal'
s a -> s ->Bool
(^?) :: s -> Getting (First a) s a -> Maybe a infixl 8 #
Perform a safe head
of a Fold
or Traversal
or retrieve Just
the result
from a Getter
or Lens
.
When using a Traversal
as a partial Lens
, or a Fold
as a partial Getter
this can be a convenient
way to extract the optional value.
Note: if you get stack overflows due to this, you may want to use firstOf
instead, which can deal
more gracefully with heavily left-biased trees. This is because ^?
works by using the
First
monoid, which can occasionally cause space leaks.
>>>
Left 4 ^?_Left
Just 4
>>>
Right 4 ^?_Left
Nothing
>>>
"world" ^? ix 3
Just 'l'
>>>
"world" ^? ix 20
Nothing
This operator works as an infix version of preview
.
(^?
) ≡flip
preview
It may be helpful to think of ^?
as having one of the following
more specialized types:
(^?
) :: s ->Getter
s a ->Maybe
a (^?
) :: s ->Fold
s a ->Maybe
a (^?
) :: s ->Lens'
s a ->Maybe
a (^?
) :: s ->Iso'
s a ->Maybe
a (^?
) :: s ->Traversal'
s a ->Maybe
a
concatOf :: Getting [r] s [r] -> s -> [r] #
Concatenate all of the lists targeted by a Fold
into a longer list.
>>>
concatOf both ("pan","ama")
"panama"
concat
≡concatOf
folded
concatOf
≡view
concatOf
::Getter
s [r] -> s -> [r]concatOf
::Fold
s [r] -> s -> [r]concatOf
::Iso'
s [r] -> s -> [r]concatOf
::Lens'
s [r] -> s -> [r]concatOf
::Traversal'
s [r] -> s -> [r]
allOf :: Getting All s a -> (a -> Bool) -> s -> Bool #
Returns True
if every target of a Fold
satisfies a predicate.
>>>
allOf both (>=3) (4,5)
True>>>
allOf folded (>=2) [1..10]
False
all
≡allOf
folded
iallOf
l =allOf
l.
Indexed
allOf
::Getter
s a -> (a ->Bool
) -> s ->Bool
allOf
::Fold
s a -> (a ->Bool
) -> s ->Bool
allOf
::Lens'
s a -> (a ->Bool
) -> s ->Bool
allOf
::Iso'
s a -> (a ->Bool
) -> s ->Bool
allOf
::Traversal'
s a -> (a ->Bool
) -> s ->Bool
allOf
::Prism'
s a -> (a ->Bool
) -> s ->Bool
anyOf :: Getting Any s a -> (a -> Bool) -> s -> Bool #
Returns True
if any target of a Fold
satisfies a predicate.
>>>
anyOf both (=='x') ('x','y')
True>>>
import Data.Data.Lens
>>>
anyOf biplate (== "world") (((),2::Int),"hello",("world",11::Int))
True
any
≡anyOf
folded
ianyOf
l ≡anyOf
l.
Indexed
anyOf
::Getter
s a -> (a ->Bool
) -> s ->Bool
anyOf
::Fold
s a -> (a ->Bool
) -> s ->Bool
anyOf
::Lens'
s a -> (a ->Bool
) -> s ->Bool
anyOf
::Iso'
s a -> (a ->Bool
) -> s ->Bool
anyOf
::Traversal'
s a -> (a ->Bool
) -> s ->Bool
anyOf
::Prism'
s a -> (a ->Bool
) -> s ->Bool
(^..) :: s -> Getting (Endo [a]) s a -> [a] infixl 8 #
A convenient infix (flipped) version of toListOf
.
>>>
[[1,2],[3]]^..id
[[[1,2],[3]]]>>>
[[1,2],[3]]^..traverse
[[1,2],[3]]>>>
[[1,2],[3]]^..traverse.traverse
[1,2,3]
>>>
(1,2)^..both
[1,2]
toList
xs ≡ xs^..
folded
(^..
) ≡flip
toListOf
(^..
) :: s ->Getter
s a -> a :: s ->Fold
s a -> a :: s ->Lens'
s a -> a :: s ->Iso'
s a -> a :: s ->Traversal'
s a -> a :: s ->Prism'
s a -> [a]
filtered :: (Choice p, Applicative f) => (a -> Bool) -> Optic' p f a a #
Obtain a Fold
that can be composed with to filter another Lens
, Iso
, Getter
, Fold
(or Traversal
).
Note: This is not a legal Traversal
, unless you are very careful not to invalidate the predicate on the target.
Note: This is also not a legal Prism
, unless you are very careful not to inject a value that fails the predicate.
As a counter example, consider that given evens =
the second filtered
even
Traversal
law is violated:
over
evenssucc
.
over
evenssucc
/=
over
evens (succ
.
succ
)
So, in order for this to qualify as a legal Traversal
you can only use it for actions that preserve the result of the predicate!
>>>
[1..10]^..folded.filtered even
[2,4,6,8,10]
This will preserve an index if it is present.
_Just :: Prism (Maybe a) (Maybe b) a b #
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
(#) :: AReview t b -> b -> t infixr 8 #
An infix alias for review
.
unto
f # x ≡ f x l # x ≡ x^.
re
l
This is commonly used when using a Prism
as a smart constructor.
>>>
_Left # 4
Left 4
But it can be used for any Prism
>>>
base 16 # 123
"7b"
(#) ::Iso'
s a -> a -> s (#) ::Prism'
s a -> a -> s (#) ::Review
s a -> a -> s (#) ::Equality'
s a -> a -> s
(^.) :: s -> Getting a s a -> a infixl 8 #
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 a #
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
.
to
≡id
>>>
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 -> aview
::Monoid
m =>Fold
s m -> s -> mview
::Iso'
s a -> s -> aview
::Lens'
s a -> s -> aview
::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 aview
:: (MonadReader
s m,Monoid
a) =>Fold
s a -> m aview
::MonadReader
s m =>Iso'
s a -> m aview
::MonadReader
s m =>Lens'
s a -> m aview
:: (MonadReader
s m,Monoid
a) =>Traversal'
s a -> m a
to :: (Profunctor p, Contravariant f) => (s -> a) -> Optic' p f s a #
type Getting r s a = (a -> Const r a) -> s -> Const r s #
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
, then when Getting
r s ar
is a Monoid
, then
you can pass a Fold
(or
Traversal
), otherwise you can only pass this a
Getter
or Lens
.
_1 :: Field1 s t a b => Lens s t a b #
Access the 1st field of a tuple (and possibly change its type).
>>>
(1,2)^._1
1
>>>
_1 .~ "hello" $ (1,2)
("hello",2)
>>>
(1,2) & _1 .~ "hello"
("hello",2)
>>>
_1 putStrLn ("hello","world")
hello ((),"world")
This can also be used on larger tuples as well:
>>>
(1,2,3,4,5) & _1 +~ 41
(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,b,c,d,e,f,g,h,i) (a',b,c,d,e,f,g,h,i) a a'
_2 :: Field2 s t a b => Lens s t a b #
Access the 2nd field of a tuple.
>>>
_2 .~ "hello" $ (1,(),3,4)
(1,"hello",3,4)
>>>
(1,2,3,4) & _2 *~ 3
(1,6,3,4)
>>>
_2 print (1,2)
2 (1,())
anyOf
_2
:: (s ->Bool
) -> (a, s) ->Bool
traverse
.
_2
:: (Applicative
f,Traversable
t) => (a -> f b) -> t (s, a) -> f (t (s, b))foldMapOf
(traverse
.
_2
) :: (Traversable
t,Monoid
m) => (s -> m) -> t (b, s) -> m
(<>~) :: Semigroup a => ASetter s t a a -> a -> s -> t infixr 4 #
Modify the target of a Semigroup
value by using (
.<>
)
>>>
(Sum a,b) & _1 <>~ Sum c
(Sum {getSum = a + c},b)
>>>
(Sum a,Sum b) & both <>~ Sum c
(Sum {getSum = a + c},Sum {getSum = b + c})
>>>
both <>~ "!!!" $ ("hello","world")
("hello!!!","world!!!")
(<>~
) ::Semigroup
a =>Setter
s t a a -> a -> s -> t (<>~
) ::Semigroup
a =>Iso
s t a a -> a -> s -> t (<>~
) ::Semigroup
a =>Lens
s t a a -> a -> s -> t (<>~
) ::Semigroup
a =>Traversal
s t a a -> a -> s -> t
(?~) :: ASetter s t a (Maybe b) -> b -> s -> t infixr 4 #
Set the target of a Lens
, Traversal
or Setter
to Just
a value.
l?~
t ≡set
l (Just
t)
>>>
Nothing & id ?~ a
Just a
>>>
Map.empty & at 3 ?~ x
fromList [(3,x)]
?~
can be used type-changily:
>>>
('a', ('b', 'c')) & _2.both ?~ 'x'
('a',(Just 'x',Just 'x'))
(?~
) ::Setter
s t a (Maybe
b) -> b -> s -> t (?~
) ::Iso
s t a (Maybe
b) -> b -> s -> t (?~
) ::Lens
s t a (Maybe
b) -> b -> s -> t (?~
) ::Traversal
s t a (Maybe
b) -> b -> s -> t
(.~) :: ASetter s t a b -> b -> s -> t infixr 4 #
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
, provided for consistency with (.=
).
f<$
a ≡mapped
.~
f$
a
>>>
(a,b,c,d) & _4 .~ e
(a,b,c,e)
>>>
(42,"world") & _1 .~ "hello"
("hello","world")
>>>
(a,b) & both .~ c
(c,c)
(.~
) ::Setter
s t a b -> b -> s -> t (.~
) ::Iso
s t a b -> b -> s -> t (.~
) ::Lens
s t a b -> b -> s -> t (.~
) ::Traversal
s t a b -> b -> s -> t
(%~) :: ASetter s t a b -> (a -> b) -> s -> t infixr 4 #
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 over
.
fmap
f ≡mapped
%~
ffmapDefault
f ≡traverse
%~
f
>>>
(a,b,c) & _3 %~ f
(a,b,f c)
>>>
(a,b) & both %~ f
(f a,f b)
>>>
_2 %~ length $ (1,"hello")
(1,5)
>>>
traverse %~ f $ [a,b,c]
[f a,f b,f c]
>>>
traverse %~ even $ [1,2,3]
[False,True,False]
>>>
traverse.traverse %~ length $ [["hello","world"],["!!!"]]
[[5,5],[3]]
(%~
) ::Setter
s t a b -> (a -> b) -> s -> t (%~
) ::Iso
s t a b -> (a -> b) -> s -> t (%~
) ::Lens
s t a b -> (a -> b) -> s -> t (%~
) ::Traversal
s t a b -> (a -> b) -> s -> t
sets :: (Profunctor p, Profunctor q, Settable f) => (p a b -> q s t) -> Optical p q f s t a b #
Build a Setter
, IndexedSetter
or IndexPreservingSetter
depending on your choice of Profunctor
.
sets
:: ((a -> b) -> s -> t) ->Setter
s t a b
type Lens s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t #
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
three common sense Lens
laws:
1) You get back what you put in:
view
l (set
l v s) ≡ v
2) Putting back what you got doesn't change anything:
set
l (view
l s) s ≡ s
3) Setting twice is the same as setting once:
set
l v' (set
l v s) ≡set
l v' s
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/.
There are some emergent properties of these laws:
1)
must be injective for every set
l ss
This is a consequence of law #1
2)
must be surjective, because of law #2, which indicates that it is possible to obtain any set
lv
from some s
such that set
s v = s
3) Given just the first two laws you can prove a weaker form of law #3 where the values v
that you are setting match:
set
l v (set
l v s) ≡set
l v s
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 are required of any Lens
you create:
lpure
≡pure
fmap
(l f).
l g ≡getCompose
.
l (Compose
.
fmap
f.
g)
typeLens
s t a b = forall f.Functor
f =>LensLike
f s t a b
type Traversal' s a = Traversal s s a a #
typeTraversal'
=Simple
Traversal
type IndexedTraversal' i s a = IndexedTraversal i s s a a #
typeIndexedTraversal'
i =Simple
(IndexedTraversal
i)
type Getter s a = forall (f :: Type -> Type). (Contravariant f, Functor f) => (a -> f a) -> s -> f s #
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 (s -> a)
.
Moreover, a Getter
can be used directly as a Fold
,
since it just ignores the Applicative
.
type Fold s a = forall (f :: Type -> Type). (Contravariant f, Applicative f) => (a -> f a) -> s -> f s #
A Fold
describes how to retrieve multiple values in a way that can be composed
with other LensLike
constructions.
A
provides a structure with operations very similar to those of the Fold
s aFoldable
typeclass, see foldMapOf
and the other Fold
combinators.
By convention, if there exists a foo
method that expects a
, then there should be a
Foldable
(f a)fooOf
method that takes a
and a value of type Fold
s as
.
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 apply.
class Profunctor p => Choice (p :: Type -> Type -> Type) #
The generalization of Costar
of Functor
that is strong with respect
to Either
.
Note: This is also a notion of strength, except with regards to another monoidal structure that we can choose to equip Hask with: the cocartesian coproduct.