module Optics.Operators
( (^.)
, (^..)
, (^?)
, (#)
, (%~)
, (%!~)
, (.~)
, (!~)
, (?~)
, (?!~)
)
where
import Optics.AffineFold
import Optics.Fold
import Optics.Getter
import Optics.Optic
import Optics.Review
import Optics.Setter
(^.) :: Is k A_Getter => s -> Optic' k is s a -> a
^. :: s -> Optic' k is s a -> a
(^.) = (Optic' k is s a -> s -> a) -> s -> Optic' k is s a -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Optic' k is s a -> s -> a
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view
{-# INLINE (^.) #-}
infixl 8 ^.
(^?) :: Is k An_AffineFold => s -> Optic' k is s a -> Maybe a
^? :: s -> Optic' k is s a -> Maybe a
(^?) = (Optic' k is s a -> s -> Maybe a)
-> s -> Optic' k is s a -> Maybe a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Optic' k is s a -> s -> Maybe a
forall k (is :: IxList) s a.
Is k An_AffineFold =>
Optic' k is s a -> s -> Maybe a
preview
{-# INLINE (^?) #-}
infixl 8 ^?
(^..) :: Is k A_Fold => s -> Optic' k is s a -> [a]
^.. :: s -> Optic' k is s a -> [a]
(^..) = (Optic' k is s a -> s -> [a]) -> s -> Optic' k is s a -> [a]
forall a b c. (a -> b -> c) -> b -> a -> c
flip Optic' k is s a -> s -> [a]
forall k (is :: IxList) s a.
Is k A_Fold =>
Optic' k is s a -> s -> [a]
toListOf
{-# INLINE (^..) #-}
infixl 8 ^..
(#) :: Is k A_Review => Optic' k is t b -> b -> t
# :: Optic' k is t b -> b -> t
(#) = Optic' k is t b -> b -> t
forall k (is :: IxList) t b.
Is k A_Review =>
Optic' k is t b -> b -> t
review
{-# INLINE (#) #-}
infixr 8 #
(%~) :: Is k A_Setter => Optic k is s t a b -> (a -> b) -> s -> t
%~ :: Optic k is s t a b -> (a -> b) -> s -> t
(%~) = Optic k is s t a b -> (a -> b) -> s -> t
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
over
{-# INLINE (%~) #-}
infixr 4 %~
(%!~) :: Is k A_Setter => Optic k is s t a b -> (a -> b) -> s -> t
%!~ :: Optic k is s t a b -> (a -> b) -> s -> t
(%!~) = Optic k is s t a b -> (a -> b) -> s -> t
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> (a -> b) -> s -> t
over'
{-# INLINE (%!~) #-}
infixr 4 %!~
(.~) :: Is k A_Setter => Optic k is s t a b -> b -> s -> t
.~ :: Optic k is s t a b -> b -> s -> t
(.~) = Optic k is s t a b -> b -> s -> t
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set
{-# INLINE (.~) #-}
infixr 4 .~
(!~) :: Is k A_Setter => Optic k is s t a b -> b -> s -> t
!~ :: Optic k is s t a b -> b -> s -> t
(!~) = Optic k is s t a b -> b -> s -> t
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set'
{-# INLINE (!~) #-}
infixr 4 !~
(?~) :: Is k A_Setter => Optic k is s t a (Maybe b) -> b -> s -> t
?~ :: Optic k is s t a (Maybe b) -> b -> s -> t
(?~) = \Optic k is s t a (Maybe b)
o -> Optic k is s t a (Maybe b) -> Maybe b -> s -> t
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set Optic k is s t a (Maybe b)
o (Maybe b -> s -> t) -> (b -> Maybe b) -> b -> s -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Maybe b
forall a. a -> Maybe a
Just
{-# INLINE (?~) #-}
infixr 4 ?~
(?!~) :: Is k A_Setter => Optic k is s t a (Maybe b) -> b -> s -> t
?!~ :: Optic k is s t a (Maybe b) -> b -> s -> t
(?!~) = \Optic k is s t a (Maybe b)
o !b
b -> Optic k is s t a (Maybe b) -> Maybe b -> s -> t
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set' Optic k is s t a (Maybe b)
o (b -> Maybe b
forall a. a -> Maybe a
Just b
b)
{-# INLINE (?!~) #-}
infixr 4 ?!~