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

Safe HaskellNone
LanguageHaskell2010

Data.Profunctor.Optic.Operator

Synopsis

Documentation

re :: Optic (Re p a b) s t a b -> Optic p b a t s Source #

Reverse an optic to obtain its dual.

>>> 5 ^. re left
Left 5
>>> 6 ^. re (left . from succ)
Left 7
re . re  ≡ id
re :: Iso s t a b   -> Iso b a t s
re :: Lens s t a b  -> Colens b a t s
re :: Prism s t a b -> Coprism b a t s

invert :: AIso s t a b -> Iso b a t s Source #

Invert an isomorphism.

invert (invert o) ≡ o

view :: MonadReader s m => AView s a -> m a Source #

View the value pointed to by a View, 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 t22 (1, "hello")
"hello"
>>> view (to succ) 5
6
>>> view (t22 . t21) ("hello",("world","!!!"))
"world"

review :: MonadReader b m => AReview t b -> m t Source #

Turn an optic around and look through the other end.

reviewview . re
review . fromid
>>> review (from succ) 5
6
review :: Iso' s a   -> a -> s
review :: Prism' s a -> a -> s
review :: Colens' s a -> a -> s

preview :: MonadReader s m => AFold0 a s a -> m (Maybe a) Source #

TODO: Document

over :: ASetter s t a b -> (a -> b) -> s -> t Source #

Extract a SEC from a Setter.

Used to modify the target of a Lens or all the targets of a Setter or Traversal.

over o idid 
over o f . over o g ≡ over o (f . g)
setter . overid
over . setterid
>>> over fmapped (+1) (Just 1)
Just 2
>>> over fmapped (*10) [1,2,3]
[10,20,30]
>>> over t21 (+1) (1,2)
(2,2)
>>> over t21 show (10,20)
("10",20)
over :: Setter s t a b -> (a -> r) -> s -> r
over :: Monoid r => Fold s t a b -> (a -> r) -> s -> r

under :: AResetter s t a b -> (a -> b) -> s -> t Source #

Extract a SEC from a Resetter.

under o idid 
under o f . under o g ≡ under o (f . g)
resetter . underid
under . resetterid

Note that under (more properly co-over) is distinct from reover:

>>> :t under $ wrapped @(Identity Int)
under $ wrapped @(Identity Int)
  :: (Int -> Int) -> Identity Int -> Identity Int
>>> :t over $ wrapped @(Identity Int)
over $ wrapped @(Identity Int)
  :: (Int -> Int) -> Identity Int -> Identity Int
>>> :t over . re $ wrapped @(Identity Int)
over . re $ wrapped @(Identity Int)
  :: (Identity Int -> Identity Int) -> Int -> Int
>>> :t reover $ wrapped @(Identity Int)
reover $ wrapped @(Identity Int)
  :: (Identity Int -> Identity Int) -> Int -> Int

Compare to the lens-family version.

set :: ASetter s t a b -> b -> s -> t Source #

Set all referenced fields to the given value.

 set l y (set l x a) ≡ set l y a

reset :: AResetter s t a b -> b -> s -> t Source #

Set all referenced fields to the given value.

resetset . re

is :: ATraversal0 s t a b -> s -> Bool Source #

Check whether the optic is matchesed.

>>> is just Nothing
False

matches :: ATraversal0 s t a b -> s -> t + a Source #

Test whether the optic matches or not.

>>> matches just (Just 2)
Right 2
>>> matches just (Nothing :: Maybe Int) :: Either (Maybe Bool) Int
Left Nothing

(&) :: 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 %.

If you only need the final index then use .:

>>> ixlists (ixtraversed . ixtraversed) foobar
[(0,"foo"),(1,"bar"),(0,"baz"),(1,"bip")]
>>> ixlistsFrom (ixlast ixtraversed % ixlast ixtraversed) (Last 0) foobar & fmapped . t21 ..~ getLast
[(0,"foo"),(1,"bar"),(0,"baz"),(1,"bip")]
>>> ixlists (ixtraversed . ixtraversed) exercises
[("crunches",25),("handstands",5),("crunches",20),("pushups",10),("handstands",3),("pushups",15)]
>>> ixlists (ixtraversed % ixtraversed) exercises
[("Fridaycrunches",25),("Fridayhandstands",5),("Mondaycrunches",20),("Mondaypushups",10),("Wednesdayhandstands",3),("Wednesdaypushups",15)]

(#) :: 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 #

An infix alias for view. Dual to #.

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

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

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

Bring the index and value of a indexed optic into the current environment as a pair.

This a flipped, infix variant of ixview and an indexed variant of ^..

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

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

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

An infix variant of review. 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
(#^) :: Iso'      s a -> a -> s
(#^) :: Prism'    s a -> a -> s
(#^) :: Colens'   s a -> a -> s
(#^) :: Review    s a -> a -> s
(#^) :: Equality' s a -> a -> s

(^?) :: s -> AFold0 a s a -> Maybe a infixl 8 Source #

An infix variant of preview'.

(^?) ≡ flip preview'

Perform a safe head of a Fold or Traversal or retrieve Just the result from a View or Lens.

When using a Traversal as a partial Lens, or a Fold as a partial View this can be a convenient way to extract the optional value.

>>> Left 4 ^? left
Just 4
>>> Right 4 ^? left
Nothing

(^..) :: s -> AFold (Endo [a]) s a -> [a] infixl 8 Source #

Infix version of lists.

toList xs ≡ xs ^.. folding
(^..) ≡ flip lists
>>> [[1,2], [3 :: Int]] ^.. id
[[[1,2],[3]]]
>>> [[1,2], [3 :: Int]] ^.. traversed
[[1,2],[3]]
>>> [[1,2], [3 :: Int]] ^.. traversed . traversed
[1,2,3]
>>> (1,2) ^.. bitraversed
[1,2]
(^..) :: s -> View 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 :: s -> Affine' s a    -> [a]

(^%%) :: Monoid i => s -> AIxfold (Endo [(i, a)]) i s a -> [(i, a)] infixl 8 Source #

Infix version of ixlists.

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

TODO: Document

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

An infix variant of ixset. Dual to #~.

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

TODO: Document

>>> Nothing & just ..~ (+1)
Nothing

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

An infix variant of ixover. Dual to ##~.

(/~) :: AResetter s t a b -> b -> s -> t infixr 4 Source #

An infix variant of reset. Dual to .~.

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

An infix variant of cxset. Dual to %~.

(//~) :: AResetter s t a b -> (a -> b) -> s -> t infixr 4 Source #

An infix variant of under. Dual to ..~.

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

An infix variant of cxover. Dual to %%~.

>>> Just "foo" & catchOn 0 ##~ (\k msg -> show k ++ ": " ++ msg)
Just "0: foo"
>>> Nothing & catchOn 0 ##~ (\k msg -> show k ++ ": " ++ msg)
Just "caught"

(?~) :: ASetter s t a (Maybe b) -> b -> s -> t infixr 4 Source #

Set the target of a settable optic to Just a value.

l ?~ t ≡ set l (Just t)
>>> Nothing & id ?~ 1
Just 1

?~ can be used type-changily:

>>> ('a', ('b', 'c')) & t22 . both ?~ 'x'
('a',(Just 'x',Just 'x'))
(?~) :: Iso s t a (Maybe b)       -> b -> s -> t
(?~) :: Lens s t a (Maybe b)      -> b -> s -> t
(?~) :: Grate s t a (Maybe b)     -> b -> s -> t
(?~) :: Setter s t a (Maybe b)    -> b -> s -> t
(?~) :: Traversal s t a (Maybe b) -> b -> s -> t

(<>~) :: Semigroup a => ASetter s t a a -> a -> s -> t infixr 4 Source #

Modify the target by adding another value.

>>> both <>~ False $ (False,True)
(False,True)
>>> both <>~ "!!!" $ ("hello","world")
("hello!!!","world!!!")
(<>~) :: Semigroup a => Iso s t a a       -> a -> s -> t
(<>~) :: Semigroup a => Lens s t a a      -> a -> s -> t
(<>~) :: Semigroup a => Grate s t a a     -> a -> s -> t
(<>~) :: Semigroup a => Setter s t a a    -> a -> s -> t
(<>~) :: Semigroup a => Traversal s t a a -> a -> s -> t

(><~) :: Semiring a => ASetter s t a a -> a -> s -> t infixr 4 Source #

Modify the target by multiplying by another value.

>>> both ><~ False $ (False,True)
(False,False)
(><~) :: Semiring a => Iso s t a a       -> a -> s -> t
(><~) :: Semiring a => Lens s t a a      -> a -> s -> t
(><~) :: Semiring a => Grate s t a a     -> a -> s -> t
(><~) :: Semiring a => Setter s t a a    -> a -> s -> t
(><~) :: Semiring a => Traversal s t a a -> a -> s -> t