profunctor-optics-0.0.0.4: An optics library compatible with the typeclasses in 'profunctors'.

Safe HaskellSafe
LanguageHaskell2010

Data.Profunctor.Optic.Operator

Synopsis

Documentation

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

>>> 5 & (+1) & show
"6"

Since: base-4.8.0.0

(%) :: Semigroup i => Representable p => IndexedOptic p i b1 b2 a1 a2 -> IndexedOptic p i c1 c2 b1 b2 -> IndexedOptic p i c1 c2 a1 a2 infixr 8 Source #

Compose two indexed traversals, combining indices.

Its precedence is one lower than that of function composition, which allows . to be nested in %.

>>> ilists (itraversed . itraversed) exercises
[("crunches",25),("handstands",5),("crunches",20),("pushups",10),("handstands",3),("pushups",15)]
>>> ilists (itraversed % itraversed) exercises
[("Fridaycrunches",25),("Fridayhandstands",5),("Mondaycrunches",20),("Mondaypushups",10),("Wednesdayhandstands",3),("Wednesdaypushups",15)]

If you only need the final index then use .:

>>> ilists (itraversed . itraversed) foobar
[(0,"foo"),(1,"bar"),(0,"baz"),(1,"bip")]

This is identical to the more convoluted:

>>> ilistsFrom (ilast itraversed % ilast itraversed) (Last 0) foobar & fmapped . first' ..~ getLast
[(0,"foo"),(1,"bar"),(0,"baz"),(1,"bip")]

(#) :: Semigroup k => Corepresentable p => CoindexedOptic p k b1 b2 a1 a2 -> CoindexedOptic p k c1 c2 b1 b2 -> CoindexedOptic p k c1 c2 a1 a2 infixr 8 Source #

Compose two coindexed traversals, combining indices.

Its precedence is one lower than that of function composition, which allows . to be nested in #.

If you only need the final index then use ..

(^.) :: s -> AView s a -> a infixl 8 Source #

View the focus of an optic.

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

>>> ("hello","world") ^. second'
"world"
>>> 5 ^. to succ
6
>>> import Data.Complex
>>> ((0, 1 :+ 2), 3) ^. first' . second' . to magnitude
2.23606797749979

(^%) :: Monoid i => s -> AIxview i s a -> (Maybe i, a) infixl 8 Source #

View the focus of an indexed optic along with its index.

>>> ("foo", 42) ^% ifirst
(Just (),"foo")
>>> [(0,'f'),(1,'o'),(2,'o') :: (Int, Char)] ^% iat 2 . ifirst
(Just 2,2)

In order to iview a Choice optic (e.g. Ixaffine, Ixtraversal, Ixfold, etc), a must have a Monoid instance:

>>> ([] :: [Int]) ^% iat 0
(Nothing,0)
>>> ([1] :: [Int]) ^% iat 0
(Just 0,1)

(#^) :: AReview t b -> b -> t infixr 8 Source #

Dual to ^..

from f #^ x ≡ f x
o #^ x ≡ x ^. re o

This is commonly used when using a Prism as a smart constructor.

>>> left' #^ 4
Left 4

(..~) :: Optic (->) s t a b -> (a -> b) -> s -> t infixr 4 Source #

Map over an optic.

>>> Just 1 & just ..~ (+1)
Just 2
>>> Nothing & just ..~ (+1)
Nothing
>>> [1,2,3] & fmapped ..~ (*10)
[10,20,30]
>>> (1,2) & first' ..~ (+1)
(2,2)
>>> (10,20) & first' ..~ show
("10",20)

(.~) :: Optic (->) s t a b -> b -> s -> t infixr 4 Source #

Set all referenced fields to the given value.

(**~) :: Optic (Star f) s t a b -> (a -> f b) -> s -> f t infixr 4 Source #

Map over a representable optic.

(*~) :: Optic (Star f) s t a b -> f b -> s -> f t infixr 4 Source #

Set the focus of a representable optic.

(//~) :: Optic (Costar f) s t a b -> (f a -> b) -> f s -> t infixr 4 Source #

Map over a co-representable optic.

(/~) :: Optic (Costar f) s t a b -> b -> f s -> t infixr 4 Source #

Set the focus of a co-representable optic.

(%%~) :: Monoid i => AIxsetter i s t a b -> (i -> a -> b) -> s -> t infixr 4 Source #

Map over an indexed optic.

See also ##~.

(%~) :: Monoid i => AIxsetter i s t a b -> (i -> b) -> s -> t infixr 4 Source #

Set the focus of an indexed optic.

See also #~.

Note if you're looking for the infix over it is ..~.

(##~) :: Monoid k => ACxsetter k s t a b -> (k -> a -> b) -> s -> t infixr 4 Source #

Map over a coindexed optic.

Infix variant of kover.

See also %%~.

(#~) :: Monoid k => ACxsetter k s t a b -> (k -> b) -> s -> t infixr 4 Source #

Set the focus of a coindexed optic.

See also %~.