polysemy-optics-0.1.0.2: Optics for Polysemy.
Safe HaskellNone
LanguageHaskell2010

Optics.Polysemy

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

(<&>) :: Functor f => f a -> (a -> b) -> f b infixl 1 #

Flipped version of <$>.

(<&>) = flip fmap

Examples

Expand

Apply (+1) to a list, a Just and a Right:

>>> Just 2 <&> (+1)
Just 3
>>> [1,2,3] <&> (+1)
[2,3,4]
>>> Right 3 <&> (+1)
Right 4

Since: base-4.11.0.0

itoList :: FoldableWithIndex i f => f a -> [(i, a)] #

Extract the key-value pairs from a structure.

When you don't need access to the indices in the result, then toList is more flexible in what it accepts.

toListmap snd . itoList

ifor_ :: (FoldableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f () #

Traverse elements with access to the index i, discarding the results (with the arguments flipped).

ifor_flip itraverse_

When you don't need access to the index then for_ is more flexible in what it accepts.

for_ a ≡ ifor_ a . const

itraverse_ :: (FoldableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f () #

Traverse elements with access to the index i, discarding the results.

When you don't need access to the index then traverse_ is more flexible in what it accepts.

traverse_ l = itraverse . const

ifor :: (TraversableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f (t b) #

Traverse with an index (and the arguments flipped).

for a ≡ ifor a . const
iforflip itraverse

class Functor f => FunctorWithIndex i (f :: Type -> Type) | f -> i where #

A Functor with an additional index.

Instances must satisfy a modified form of the Functor laws:

imap f . imap g ≡ imap (\i -> f i . g i)
imap (\_ a -> a) ≡ id

Minimal complete definition

Nothing

Methods

imap :: (i -> a -> b) -> f a -> f b #

Map with access to the index.

Instances

Instances details
FunctorWithIndex Int []

The position in the list is available as the index.

Instance details

Defined in WithIndex

Methods

imap :: (Int -> a -> b) -> [a] -> [b] #

FunctorWithIndex Int ZipList

Same instance as for [].

Instance details

Defined in WithIndex

Methods

imap :: (Int -> a -> b) -> ZipList a -> ZipList b #

FunctorWithIndex Int NonEmpty 
Instance details

Defined in WithIndex

Methods

imap :: (Int -> a -> b) -> NonEmpty a -> NonEmpty b #

FunctorWithIndex Int IntMap 
Instance details

Defined in WithIndex

Methods

imap :: (Int -> a -> b) -> IntMap a -> IntMap b #

FunctorWithIndex Int Seq

The position in the Seq is available as the index.

Instance details

Defined in WithIndex

Methods

imap :: (Int -> a -> b) -> Seq a -> Seq b #

FunctorWithIndex () Maybe 
Instance details

Defined in WithIndex

Methods

imap :: (() -> a -> b) -> Maybe a -> Maybe b #

FunctorWithIndex () Par1 
Instance details

Defined in WithIndex

Methods

imap :: (() -> a -> b) -> Par1 a -> Par1 b #

FunctorWithIndex () Identity 
Instance details

Defined in WithIndex

Methods

imap :: (() -> a -> b) -> Identity a -> Identity b #

FunctorWithIndex k (Map k) 
Instance details

Defined in WithIndex

Methods

imap :: (k -> a -> b) -> Map k a -> Map k b #

FunctorWithIndex k ((,) k) 
Instance details

Defined in WithIndex

Methods

imap :: (k -> a -> b) -> (k, a) -> (k, b) #

Ix i => FunctorWithIndex i (Array i) 
Instance details

Defined in WithIndex

Methods

imap :: (i -> a -> b) -> Array i a -> Array i b #

FunctorWithIndex Void (V1 :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> V1 a -> V1 b #

FunctorWithIndex Void (U1 :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> U1 a -> U1 b #

FunctorWithIndex Void (Proxy :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> Proxy a -> Proxy b #

FunctorWithIndex i f => FunctorWithIndex i (Reverse f) 
Instance details

Defined in WithIndex

Methods

imap :: (i -> a -> b) -> Reverse f a -> Reverse f b #

FunctorWithIndex i f => FunctorWithIndex i (Rec1 f) 
Instance details

Defined in WithIndex

Methods

imap :: (i -> a -> b) -> Rec1 f a -> Rec1 f b #

FunctorWithIndex i m => FunctorWithIndex i (IdentityT m) 
Instance details

Defined in WithIndex

Methods

imap :: (i -> a -> b) -> IdentityT m a -> IdentityT m b #

FunctorWithIndex i f => FunctorWithIndex i (Backwards f) 
Instance details

Defined in WithIndex

Methods

imap :: (i -> a -> b) -> Backwards f a -> Backwards f b #

FunctorWithIndex Void (Const e :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> Const e a -> Const e b #

FunctorWithIndex Void (Constant e :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> Constant e a -> Constant e b #

FunctorWithIndex r ((->) r :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

imap :: (r -> a -> b) -> (r -> a) -> r -> b #

FunctorWithIndex Void (K1 i c :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

imap :: (Void -> a -> b) -> K1 i c a -> K1 i c b #

FunctorWithIndex [Int] Tree 
Instance details

Defined in WithIndex

Methods

imap :: ([Int] -> a -> b) -> Tree a -> Tree b #

FunctorWithIndex i m => FunctorWithIndex (e, i) (ReaderT e m) 
Instance details

Defined in WithIndex

Methods

imap :: ((e, i) -> a -> b) -> ReaderT e m a -> ReaderT e m b #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (Sum f g) 
Instance details

Defined in WithIndex

Methods

imap :: (Either i j -> a -> b) -> Sum f g a -> Sum f g b #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (Product f g) 
Instance details

Defined in WithIndex

Methods

imap :: (Either i j -> a -> b) -> Product f g a -> Product f g b #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (f :+: g) 
Instance details

Defined in WithIndex

Methods

imap :: (Either i j -> a -> b) -> (f :+: g) a -> (f :+: g) b #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (f :*: g) 
Instance details

Defined in WithIndex

Methods

imap :: (Either i j -> a -> b) -> (f :*: g) a -> (f :*: g) b #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (i, j) (Compose f g) 
Instance details

Defined in WithIndex

Methods

imap :: ((i, j) -> a -> b) -> Compose f g a -> Compose f g b #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (i, j) (f :.: g) 
Instance details

Defined in WithIndex

Methods

imap :: ((i, j) -> a -> b) -> (f :.: g) a -> (f :.: g) b #

class Foldable f => FoldableWithIndex i (f :: Type -> Type) | f -> i where #

A container that supports folding with an additional index.

Minimal complete definition

Nothing

Methods

ifoldMap :: Monoid m => (i -> a -> m) -> f a -> m #

Fold a container by mapping value to an arbitrary Monoid with access to the index i.

When you don't need access to the index then foldMap is more flexible in what it accepts.

foldMapifoldMap . const

ifoldMap' :: Monoid m => (i -> a -> m) -> f a -> m #

A variant of ifoldMap that is strict in the accumulator.

When you don't need access to the index then foldMap' is more flexible in what it accepts.

foldMap'ifoldMap' . const

ifoldr :: (i -> a -> b -> b) -> b -> f a -> b #

Right-associative fold of an indexed container with access to the index i.

When you don't need access to the index then foldr is more flexible in what it accepts.

foldrifoldr . const

ifoldl :: (i -> b -> a -> b) -> b -> f a -> b #

Left-associative fold of an indexed container with access to the index i.

When you don't need access to the index then foldl is more flexible in what it accepts.

foldlifoldl . const

ifoldr' :: (i -> a -> b -> b) -> b -> f a -> b #

Strictly fold right over the elements of a structure with access to the index i.

When you don't need access to the index then foldr' is more flexible in what it accepts.

foldr'ifoldr' . const

ifoldl' :: (i -> b -> a -> b) -> b -> f a -> b #

Fold over the elements of a structure with an index, associating to the left, but strictly.

When you don't need access to the index then foldlOf' is more flexible in what it accepts.

foldl' l ≡ ifoldl' l . const

Instances

Instances details
FoldableWithIndex Int [] 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> [a] -> m #

ifoldMap' :: Monoid m => (Int -> a -> m) -> [a] -> m #

ifoldr :: (Int -> a -> b -> b) -> b -> [a] -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> [a] -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> [a] -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> [a] -> b #

FoldableWithIndex Int ZipList 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> ZipList a -> m #

ifoldMap' :: Monoid m => (Int -> a -> m) -> ZipList a -> m #

ifoldr :: (Int -> a -> b -> b) -> b -> ZipList a -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> ZipList a -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> ZipList a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> ZipList a -> b #

FoldableWithIndex Int NonEmpty 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> NonEmpty a -> m #

ifoldMap' :: Monoid m => (Int -> a -> m) -> NonEmpty a -> m #

ifoldr :: (Int -> a -> b -> b) -> b -> NonEmpty a -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> NonEmpty a -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> NonEmpty a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> NonEmpty a -> b #

FoldableWithIndex Int IntMap 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> IntMap a -> m #

ifoldMap' :: Monoid m => (Int -> a -> m) -> IntMap a -> m #

ifoldr :: (Int -> a -> b -> b) -> b -> IntMap a -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> IntMap a -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> IntMap a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> IntMap a -> b #

FoldableWithIndex Int Seq 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> Seq a -> m #

ifoldMap' :: Monoid m => (Int -> a -> m) -> Seq a -> m #

ifoldr :: (Int -> a -> b -> b) -> b -> Seq a -> b #

ifoldl :: (Int -> b -> a -> b) -> b -> Seq a -> b #

ifoldr' :: (Int -> a -> b -> b) -> b -> Seq a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> Seq a -> b #

FoldableWithIndex () Maybe 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (() -> a -> m) -> Maybe a -> m #

ifoldMap' :: Monoid m => (() -> a -> m) -> Maybe a -> m #

ifoldr :: (() -> a -> b -> b) -> b -> Maybe a -> b #

ifoldl :: (() -> b -> a -> b) -> b -> Maybe a -> b #

ifoldr' :: (() -> a -> b -> b) -> b -> Maybe a -> b #

ifoldl' :: (() -> b -> a -> b) -> b -> Maybe a -> b #

FoldableWithIndex () Par1 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (() -> a -> m) -> Par1 a -> m #

ifoldMap' :: Monoid m => (() -> a -> m) -> Par1 a -> m #

ifoldr :: (() -> a -> b -> b) -> b -> Par1 a -> b #

ifoldl :: (() -> b -> a -> b) -> b -> Par1 a -> b #

ifoldr' :: (() -> a -> b -> b) -> b -> Par1 a -> b #

ifoldl' :: (() -> b -> a -> b) -> b -> Par1 a -> b #

FoldableWithIndex () Identity 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (() -> a -> m) -> Identity a -> m #

ifoldMap' :: Monoid m => (() -> a -> m) -> Identity a -> m #

ifoldr :: (() -> a -> b -> b) -> b -> Identity a -> b #

ifoldl :: (() -> b -> a -> b) -> b -> Identity a -> b #

ifoldr' :: (() -> a -> b -> b) -> b -> Identity a -> b #

ifoldl' :: (() -> b -> a -> b) -> b -> Identity a -> b #

FoldableWithIndex k (Map k) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (k -> a -> m) -> Map k a -> m #

ifoldMap' :: Monoid m => (k -> a -> m) -> Map k a -> m #

ifoldr :: (k -> a -> b -> b) -> b -> Map k a -> b #

ifoldl :: (k -> b -> a -> b) -> b -> Map k a -> b #

ifoldr' :: (k -> a -> b -> b) -> b -> Map k a -> b #

ifoldl' :: (k -> b -> a -> b) -> b -> Map k a -> b #

FoldableWithIndex k ((,) k) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (k -> a -> m) -> (k, a) -> m #

ifoldMap' :: Monoid m => (k -> a -> m) -> (k, a) -> m #

ifoldr :: (k -> a -> b -> b) -> b -> (k, a) -> b #

ifoldl :: (k -> b -> a -> b) -> b -> (k, a) -> b #

ifoldr' :: (k -> a -> b -> b) -> b -> (k, a) -> b #

ifoldl' :: (k -> b -> a -> b) -> b -> (k, a) -> b #

Ix i => FoldableWithIndex i (Array i) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (i -> a -> m) -> Array i a -> m #

ifoldMap' :: Monoid m => (i -> a -> m) -> Array i a -> m #

ifoldr :: (i -> a -> b -> b) -> b -> Array i a -> b #

ifoldl :: (i -> b -> a -> b) -> b -> Array i a -> b #

ifoldr' :: (i -> a -> b -> b) -> b -> Array i a -> b #

ifoldl' :: (i -> b -> a -> b) -> b -> Array i a -> b #

FoldableWithIndex Void (V1 :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (Void -> a -> m) -> V1 a -> m #

ifoldMap' :: Monoid m => (Void -> a -> m) -> V1 a -> m #

ifoldr :: (Void -> a -> b -> b) -> b -> V1 a -> b #

ifoldl :: (Void -> b -> a -> b) -> b -> V1 a -> b #

ifoldr' :: (Void -> a -> b -> b) -> b -> V1 a -> b #

ifoldl' :: (Void -> b -> a -> b) -> b -> V1 a -> b #

FoldableWithIndex Void (U1 :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (Void -> a -> m) -> U1 a -> m #

ifoldMap' :: Monoid m => (Void -> a -> m) -> U1 a -> m #

ifoldr :: (Void -> a -> b -> b) -> b -> U1 a -> b #

ifoldl :: (Void -> b -> a -> b) -> b -> U1 a -> b #

ifoldr' :: (Void -> a -> b -> b) -> b -> U1 a -> b #

ifoldl' :: (Void -> b -> a -> b) -> b -> U1 a -> b #

FoldableWithIndex Void (Proxy :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (Void -> a -> m) -> Proxy a -> m #

ifoldMap' :: Monoid m => (Void -> a -> m) -> Proxy a -> m #

ifoldr :: (Void -> a -> b -> b) -> b -> Proxy a -> b #

ifoldl :: (Void -> b -> a -> b) -> b -> Proxy a -> b #

ifoldr' :: (Void -> a -> b -> b) -> b -> Proxy a -> b #

ifoldl' :: (Void -> b -> a -> b) -> b -> Proxy a -> b #

FoldableWithIndex i f => FoldableWithIndex i (Reverse f) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (i -> a -> m) -> Reverse f a -> m #

ifoldMap' :: Monoid m => (i -> a -> m) -> Reverse f a -> m #

ifoldr :: (i -> a -> b -> b) -> b -> Reverse f a -> b #

ifoldl :: (i -> b -> a -> b) -> b -> Reverse f a -> b #

ifoldr' :: (i -> a -> b -> b) -> b -> Reverse f a -> b #

ifoldl' :: (i -> b -> a -> b) -> b -> Reverse f a -> b #

FoldableWithIndex i f => FoldableWithIndex i (Rec1 f) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (i -> a -> m) -> Rec1 f a -> m #

ifoldMap' :: Monoid m => (i -> a -> m) -> Rec1 f a -> m #

ifoldr :: (i -> a -> b -> b) -> b -> Rec1 f a -> b #

ifoldl :: (i -> b -> a -> b) -> b -> Rec1 f a -> b #

ifoldr' :: (i -> a -> b -> b) -> b -> Rec1 f a -> b #

ifoldl' :: (i -> b -> a -> b) -> b -> Rec1 f a -> b #

FoldableWithIndex i m => FoldableWithIndex i (IdentityT m) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m0 => (i -> a -> m0) -> IdentityT m a -> m0 #

ifoldMap' :: Monoid m0 => (i -> a -> m0) -> IdentityT m a -> m0 #

ifoldr :: (i -> a -> b -> b) -> b -> IdentityT m a -> b #

ifoldl :: (i -> b -> a -> b) -> b -> IdentityT m a -> b #

ifoldr' :: (i -> a -> b -> b) -> b -> IdentityT m a -> b #

ifoldl' :: (i -> b -> a -> b) -> b -> IdentityT m a -> b #

FoldableWithIndex i f => FoldableWithIndex i (Backwards f) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (i -> a -> m) -> Backwards f a -> m #

ifoldMap' :: Monoid m => (i -> a -> m) -> Backwards f a -> m #

ifoldr :: (i -> a -> b -> b) -> b -> Backwards f a -> b #

ifoldl :: (i -> b -> a -> b) -> b -> Backwards f a -> b #

ifoldr' :: (i -> a -> b -> b) -> b -> Backwards f a -> b #

ifoldl' :: (i -> b -> a -> b) -> b -> Backwards f a -> b #

FoldableWithIndex Void (Const e :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (Void -> a -> m) -> Const e a -> m #

ifoldMap' :: Monoid m => (Void -> a -> m) -> Const e a -> m #

ifoldr :: (Void -> a -> b -> b) -> b -> Const e a -> b #

ifoldl :: (Void -> b -> a -> b) -> b -> Const e a -> b #

ifoldr' :: (Void -> a -> b -> b) -> b -> Const e a -> b #

ifoldl' :: (Void -> b -> a -> b) -> b -> Const e a -> b #

FoldableWithIndex Void (Constant e :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (Void -> a -> m) -> Constant e a -> m #

ifoldMap' :: Monoid m => (Void -> a -> m) -> Constant e a -> m #

ifoldr :: (Void -> a -> b -> b) -> b -> Constant e a -> b #

ifoldl :: (Void -> b -> a -> b) -> b -> Constant e a -> b #

ifoldr' :: (Void -> a -> b -> b) -> b -> Constant e a -> b #

ifoldl' :: (Void -> b -> a -> b) -> b -> Constant e a -> b #

FoldableWithIndex Void (K1 i c :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (Void -> a -> m) -> K1 i c a -> m #

ifoldMap' :: Monoid m => (Void -> a -> m) -> K1 i c a -> m #

ifoldr :: (Void -> a -> b -> b) -> b -> K1 i c a -> b #

ifoldl :: (Void -> b -> a -> b) -> b -> K1 i c a -> b #

ifoldr' :: (Void -> a -> b -> b) -> b -> K1 i c a -> b #

ifoldl' :: (Void -> b -> a -> b) -> b -> K1 i c a -> b #

FoldableWithIndex [Int] Tree 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => ([Int] -> a -> m) -> Tree a -> m #

ifoldMap' :: Monoid m => ([Int] -> a -> m) -> Tree a -> m #

ifoldr :: ([Int] -> a -> b -> b) -> b -> Tree a -> b #

ifoldl :: ([Int] -> b -> a -> b) -> b -> Tree a -> b #

ifoldr' :: ([Int] -> a -> b -> b) -> b -> Tree a -> b #

ifoldl' :: ([Int] -> b -> a -> b) -> b -> Tree a -> b #

(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (Sum f g) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (Either i j -> a -> m) -> Sum f g a -> m #

ifoldMap' :: Monoid m => (Either i j -> a -> m) -> Sum f g a -> m #

ifoldr :: (Either i j -> a -> b -> b) -> b -> Sum f g a -> b #

ifoldl :: (Either i j -> b -> a -> b) -> b -> Sum f g a -> b #

ifoldr' :: (Either i j -> a -> b -> b) -> b -> Sum f g a -> b #

ifoldl' :: (Either i j -> b -> a -> b) -> b -> Sum f g a -> b #

(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (Product f g) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (Either i j -> a -> m) -> Product f g a -> m #

ifoldMap' :: Monoid m => (Either i j -> a -> m) -> Product f g a -> m #

ifoldr :: (Either i j -> a -> b -> b) -> b -> Product f g a -> b #

ifoldl :: (Either i j -> b -> a -> b) -> b -> Product f g a -> b #

ifoldr' :: (Either i j -> a -> b -> b) -> b -> Product f g a -> b #

ifoldl' :: (Either i j -> b -> a -> b) -> b -> Product f g a -> b #

(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (f :+: g) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (Either i j -> a -> m) -> (f :+: g) a -> m #

ifoldMap' :: Monoid m => (Either i j -> a -> m) -> (f :+: g) a -> m #

ifoldr :: (Either i j -> a -> b -> b) -> b -> (f :+: g) a -> b #

ifoldl :: (Either i j -> b -> a -> b) -> b -> (f :+: g) a -> b #

ifoldr' :: (Either i j -> a -> b -> b) -> b -> (f :+: g) a -> b #

ifoldl' :: (Either i j -> b -> a -> b) -> b -> (f :+: g) a -> b #

(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (f :*: g) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => (Either i j -> a -> m) -> (f :*: g) a -> m #

ifoldMap' :: Monoid m => (Either i j -> a -> m) -> (f :*: g) a -> m #

ifoldr :: (Either i j -> a -> b -> b) -> b -> (f :*: g) a -> b #

ifoldl :: (Either i j -> b -> a -> b) -> b -> (f :*: g) a -> b #

ifoldr' :: (Either i j -> a -> b -> b) -> b -> (f :*: g) a -> b #

ifoldl' :: (Either i j -> b -> a -> b) -> b -> (f :*: g) a -> b #

(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (i, j) (Compose f g) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => ((i, j) -> a -> m) -> Compose f g a -> m #

ifoldMap' :: Monoid m => ((i, j) -> a -> m) -> Compose f g a -> m #

ifoldr :: ((i, j) -> a -> b -> b) -> b -> Compose f g a -> b #

ifoldl :: ((i, j) -> b -> a -> b) -> b -> Compose f g a -> b #

ifoldr' :: ((i, j) -> a -> b -> b) -> b -> Compose f g a -> b #

ifoldl' :: ((i, j) -> b -> a -> b) -> b -> Compose f g a -> b #

(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (i, j) (f :.: g) 
Instance details

Defined in WithIndex

Methods

ifoldMap :: Monoid m => ((i, j) -> a -> m) -> (f :.: g) a -> m #

ifoldMap' :: Monoid m => ((i, j) -> a -> m) -> (f :.: g) a -> m #

ifoldr :: ((i, j) -> a -> b -> b) -> b -> (f :.: g) a -> b #

ifoldl :: ((i, j) -> b -> a -> b) -> b -> (f :.: g) a -> b #

ifoldr' :: ((i, j) -> a -> b -> b) -> b -> (f :.: g) a -> b #

ifoldl' :: ((i, j) -> b -> a -> b) -> b -> (f :.: g) a -> b #

class (FunctorWithIndex i t, FoldableWithIndex i t, Traversable t) => TraversableWithIndex i (t :: Type -> Type) | t -> i where #

A Traversable with an additional index.

An instance must satisfy a (modified) form of the Traversable laws:

itraverse (const Identity) ≡ Identity
fmap (itraverse f) . itraverse g ≡ getCompose . itraverse (\i -> Compose . fmap (f i) . g i)

Minimal complete definition

Nothing

Methods

itraverse :: Applicative f => (i -> a -> f b) -> t a -> f (t b) #

Traverse an indexed container.

itraverseitraverseOf itraversed

Instances

Instances details
TraversableWithIndex Int [] 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> [a] -> f [b] #

TraversableWithIndex Int ZipList 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> ZipList a -> f (ZipList b) #

TraversableWithIndex Int NonEmpty 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> NonEmpty a -> f (NonEmpty b) #

TraversableWithIndex Int IntMap 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> IntMap a -> f (IntMap b) #

TraversableWithIndex Int Seq 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> Seq a -> f (Seq b) #

TraversableWithIndex () Maybe 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (() -> a -> f b) -> Maybe a -> f (Maybe b) #

TraversableWithIndex () Par1 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (() -> a -> f b) -> Par1 a -> f (Par1 b) #

TraversableWithIndex () Identity 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (() -> a -> f b) -> Identity a -> f (Identity b) #

TraversableWithIndex k (Map k) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (k -> a -> f b) -> Map k a -> f (Map k b) #

TraversableWithIndex k ((,) k) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (k -> a -> f b) -> (k, a) -> f (k, b) #

Ix i => TraversableWithIndex i (Array i) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (i -> a -> f b) -> Array i a -> f (Array i b) #

TraversableWithIndex Void (V1 :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> V1 a -> f (V1 b) #

TraversableWithIndex Void (U1 :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> U1 a -> f (U1 b) #

TraversableWithIndex Void (Proxy :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> Proxy a -> f (Proxy b) #

TraversableWithIndex i f => TraversableWithIndex i (Reverse f) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => (i -> a -> f0 b) -> Reverse f a -> f0 (Reverse f b) #

TraversableWithIndex i f => TraversableWithIndex i (Rec1 f) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => (i -> a -> f0 b) -> Rec1 f a -> f0 (Rec1 f b) #

TraversableWithIndex i m => TraversableWithIndex i (IdentityT m) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (i -> a -> f b) -> IdentityT m a -> f (IdentityT m b) #

TraversableWithIndex i f => TraversableWithIndex i (Backwards f) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => (i -> a -> f0 b) -> Backwards f a -> f0 (Backwards f b) #

TraversableWithIndex Void (Const e :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> Const e a -> f (Const e b) #

TraversableWithIndex Void (Constant e :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> Constant e a -> f (Constant e b) #

TraversableWithIndex Void (K1 i c :: Type -> Type) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> K1 i c a -> f (K1 i c b) #

TraversableWithIndex [Int] Tree 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f => ([Int] -> a -> f b) -> Tree a -> f (Tree b) #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (Sum f g) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => (Either i j -> a -> f0 b) -> Sum f g a -> f0 (Sum f g b) #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (Product f g) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => (Either i j -> a -> f0 b) -> Product f g a -> f0 (Product f g b) #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (f :+: g) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => (Either i j -> a -> f0 b) -> (f :+: g) a -> f0 ((f :+: g) b) #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (f :*: g) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => (Either i j -> a -> f0 b) -> (f :*: g) a -> f0 ((f :*: g) b) #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (i, j) (Compose f g) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => ((i, j) -> a -> f0 b) -> Compose f g a -> f0 (Compose f g b) #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (i, j) (f :.: g) 
Instance details

Defined in WithIndex

Methods

itraverse :: Applicative f0 => ((i, j) -> a -> f0 b) -> (f :.: g) a -> f0 ((f :.: g) b) #

makePrisms #

Arguments

:: Name

Type constructor name

-> DecsQ 

Generate a Prism for each constructor of a data type. Isos generated when possible. Reviews are created for constructors with existentially quantified constructors and GADTs.

e.g.

data FooBarBaz a
  = Foo Int
  | Bar a
  | Baz Int Char
makePrisms ''FooBarBaz

will create

_Foo :: Prism' (FooBarBaz a) Int
_Bar :: Prism (FooBarBaz a) (FooBarBaz b) a b
_Baz :: Prism' (FooBarBaz a) (Int, Char)

makeClassyPrisms #

Arguments

:: Name

Type constructor name

-> DecsQ 

Generate a Prism for each constructor of a data type and combine them into a single class. No Isos are created. Reviews are created for constructors with existentially quantified constructors and GADTs.

e.g.

data FooBarBaz a
  = Foo Int
  | Bar a
  | Baz Int Char
makeClassyPrisms ''FooBarBaz

will create

class AsFooBarBaz s a | s -> a where
  _FooBarBaz :: Prism' s (FooBarBaz a)
  _Foo :: Prism' s Int
  _Bar :: Prism' s a
  _Baz :: Prism' s (Int,Char)

  _Foo = _FooBarBaz % _Foo
  _Bar = _FooBarBaz % _Bar
  _Baz = _FooBarBaz % _Baz

instance AsFooBarBaz (FooBarBaz a) a

Generate an As class of prisms. Names are selected by prefixing the constructor name with an underscore. Constructors with multiple fields will construct Prisms to tuples of those fields.

type ClassyNamer #

Arguments

 = Name

Name of the data type that lenses are being generated for.

-> Maybe (Name, Name)

Names of the class and the main method it generates, respectively.

The optional rule to create a class and method around a monomorphic data type. If this naming convention is provided, it generates a "classy" lens.

data DefName #

Name to give to generated field optics.

Constructors

TopName Name

Simple top-level definition name

MethodName Name Name

makeFields-style class name and method name

Instances

Instances details
Eq DefName 
Instance details

Defined in Optics.TH.Internal.Product

Methods

(==) :: DefName -> DefName -> Bool #

(/=) :: DefName -> DefName -> Bool #

Ord DefName 
Instance details

Defined in Optics.TH.Internal.Product

Show DefName 
Instance details

Defined in Optics.TH.Internal.Product

type FieldNamer #

Arguments

 = Name

Name of the data type that lenses are being generated for.

-> [Name]

Names of all fields (including the field being named) in the data type.

-> Name

Name of the field being named.

-> [DefName]

Name(s) of the lens functions. If empty, no lens is created for that field.

The rule to create function names of lenses for data fields.

Although it's sometimes useful, you won't need the first two arguments most of the time.

data LensRules #

Rules to construct lenses for data fields.

makeFieldLabelsWith :: LensRules -> Name -> DecsQ #

Build field optics as labels with a custom configuration.

makeFieldLabels :: Name -> DecsQ #

Build field optics as instances of the LabelOptic class for use with overloaded labels. See Optics.Label for how to use this pattern.

e.g.

data Animal
  = Cat { animalAge  :: Int
        , animalName :: String
        }
  | Dog { animalAge    :: Int
        , animalAbsurd :: forall a b. a -> b
        }
makeFieldLabels ''Animal

will create

instance
  (k ~ A_Lens, a ~ Int, b ~ Int
  ) => LabelOptic "age" k Animal Animal a b where
  labelOptic = lensVL $ \f s -> case s of
    Cat x1 x2 -> fmap (\y -> Cat y x2) (f x1)
    Dog x1 x2 -> fmap (\y -> Dog y x2) (f x1)

instance
  (k ~ An_AffineTraversal, a ~ String, b ~ String
  ) => LabelOptic "name" k Animal Animal a b where
  labelOptic = atraversalVL $ \point f s -> case s of
    Cat x1 x2 -> fmap (\y -> Cat x1 y) (f x2)
    Dog x1 x2 -> point (Dog x1 x2)

instance
  ( Dysfunctional "absurd" k Animal Animal a b
  , k ~ An_AffineFold, a ~ (x -> y), b ~ (x -> y)
  ) => LabelOptic "absurd" k Animal Animal a b where
  labelOptic = afolding $ \s -> case s of
    Cat _ _  -> Nothing
    Dog _ f  -> Just f

which can be used as #age, #name and #absurd with the OverloadedLabels language extension.

Note: if you wonder about the structure of instances, see Optics.Label.

makeFieldOptics = makeFieldLabelsWith fieldLabelsRules

makeFieldLabelsNoPrefix :: Name -> DecsQ #

An alias for makeFieldLabels noPrefixFieldLabels.

makeFieldLabelsFor :: [(String, String)] -> Name -> DecsQ #

Derive field optics as labels, specifying explicit pairings of (fieldName, labelName).

If you map multiple fields to the same label and it is present in the same constructor, Traversal (or Fold for a read only version) will be generated.

e.g.

makeFieldLabelsFor [("_foo", "fooLens"), ("baz", "lbaz")] ''Foo
makeFieldLabelsFor [("_barX", "bar"), ("_barY", "bar")] ''Bar

declareFieldLabels :: DecsQ -> DecsQ #

Make field optics as labels for all records in the given declaration quote. All record syntax in the input will be stripped off.

e.g.

declareLenses [d|
  data Dog = Dog { name :: String, age :: Int }
    deriving Show
  |]

will create

data Dog = Dog String Int
  deriving Show
instance (k ~ A_Lens, ...) => LabelOptic "name" k Dog Dog ...
instance (k ~ A_Lens, ...) => LabelOptic "age" k Dog Dog ...

declareFieldLabelsFor :: [(String, String)] -> DecsQ -> DecsQ #

Similar to makeFieldLabelsFor, but takes a declaration quote.

fieldLabelsRules :: LensRules #

Rules for generation of LabelOptic instances for use with OverloadedLabels. Same as lensRules, but uses camelCaseNamer.

Note: if you don't want to prefix field names with the full name of the data type, you can use abbreviatedNamer instead.

fieldLabelsRulesFor #

Arguments

:: [(String, String)]
(Field name, Label name)
-> LensRules 

Construct a LensRules value for generating LabelOptic instances using the given map from field names to definition names.

makeLenses :: Name -> DecsQ #

Build field optics as top level functions with a sensible default configuration.

e.g.

data Animal
  = Cat { _age  :: Int
        , _name :: String
        }
  | Dog { _age    :: Int
        , _absurd :: forall a b. a -> b
        }
makeLenses ''Animal

will create

absurd :: forall a b. AffineFold Animal (a -> b)
absurd = afolding $ \s -> case s of
  Cat _ _ -> Nothing
  Dog _ x -> Just x

age :: Lens' Animal Int
age = lensVL $ \f s -> case s of
  Cat x1 x2 -> fmap (\y -> Cat y x2) (f x1)
  Dog x1 x2 -> fmap (\y -> Dog y x2) (f x1)

name :: AffineTraversal' Animal String
name = atraversalVL $ \point f s -> case s of
  Cat x1 x2 -> fmap (\y -> Cat x1 y) (f x2)
  Dog x1 x2 -> point (Dog x1 x2)
makeLenses = makeLensesWith lensRules

makeLensesFor :: [(String, String)] -> Name -> DecsQ #

Derive field optics, specifying explicit pairings of (fieldName, opticName).

If you map multiple fields to the same optic and it is present in the same constructor, Traversal (or Fold for a read only version) will be generated.

e.g.

makeLensesFor [("_foo", "fooLens"), ("baz", "lbaz")] ''Foo
makeLensesFor [("_barX", "bar"), ("_barY", "bar")] ''Bar

makeLensesWith :: LensRules -> Name -> DecsQ #

Build field optics with a custom configuration.

declareLenses :: DecsQ -> DecsQ #

Make field optics for all records in the given declaration quote. All record syntax in the input will be stripped off.

e.g.

declareLenses [d|
  data Foo = Foo { fooX, fooY :: Int }
    deriving Show
  |]

will create

data Foo = Foo Int Int deriving Show
fooX, fooY :: Lens' Foo Int

declareLensesFor :: [(String, String)] -> DecsQ -> DecsQ #

Similar to makeLensesFor, but takes a declaration quote.

lensRules :: LensRules #

Rules for making read-write field optics as top-level functions. It uses underscoreNoPrefixNamer.

lensRulesFor #

Arguments

:: [(String, String)]
(Field name, Optic name)
-> LensRules 

Construct a LensRules value for generating top-level functions using the given map from field names to definition names.

makeClassy :: Name -> DecsQ #

Make lenses and traversals for a type, and create a class when the type has no arguments.

e.g.

data Foo = Foo { _fooX, _fooY :: Int }
makeClassy ''Foo

will create

class HasFoo c where
  foo  :: Lens' c Foo
  fooX :: Lens' c Int
  fooY :: Lens' c Int
  fooX = foo % fooX
  fooY = foo % fooY

instance HasFoo Foo where
  foo  = lensVL id
  fooX = lensVL $ \f s -> case s of
    Foo x1 x2 -> fmap (\y -> Foo y x2) (f x1)
  fooY = lensVL $ \f s -> case s of
    Foo x1 x2 -> fmap (\y -> Foo x1 y) (f x2)
makeClassy = makeLensesWith classyRules

makeClassy_ :: Name -> DecsQ #

Make lenses and traversals for a type, and create a class when the type has no arguments. Works the same as makeClassy except that (a) it expects that record field names do not begin with an underscore, (b) all record fields are made into lenses, and (c) the resulting lens is prefixed with an underscore.

makeClassyFor :: String -> String -> [(String, String)] -> Name -> DecsQ #

Derive lenses and traversals, using a named wrapper class, and specifying explicit pairings of (fieldName, traversalName).

Example usage:

makeClassyFor "HasFoo" "foo" [("_foo", "fooLens"), ("bar", "lbar")] ''Foo

declareClassy :: DecsQ -> DecsQ #

For each record in the declaration quote, make lenses and traversals for it, and create a class when the type has no arguments. All record syntax in the input will be stripped off.

e.g.

declareClassy [d|
  data Foo = Foo { fooX, fooY :: Int }
    deriving Show
  |]

will create

data Foo = Foo Int Int deriving Show
class HasFoo t where
  foo :: Lens' t Foo
instance HasFoo Foo where foo = id
fooX, fooY :: HasFoo t => Lens' t Int

declareClassyFor :: [(String, (String, String))] -> [(String, String)] -> DecsQ -> DecsQ #

Similar to makeClassyFor, but takes a declaration quote.

classyRules :: LensRules #

Rules for making lenses and traversals that precompose another Lens.

classyRulesFor #

Arguments

:: (String -> Maybe (String, String))

Type Name -> Maybe (Class Name, Method Name)

-> [(String, String)]
(Field Name, Method Name)
-> LensRules 

Rules for making lenses and traversals that precompose another Lens using a custom function for naming the class, main class method, and a mapping from field names to definition names.

makeFields :: Name -> DecsQ #

Generate overloaded field accessors.

e.g

data Foo a = Foo { _fooX :: Int, _fooY :: a }
newtype Bar = Bar { _barX :: Char }
makeFields ''Foo
makeFields ''Bar

will create

class HasX s a | s -> a where
  x :: Lens' s a

instance HasX (Foo a) Int where
  x = lensVL $ \f s -> case s of
    Foo x1 x2 -> fmap (\y -> Foo y x2) (f x1)

class HasY s a | s -> a where
  y :: Lens' s a

instance HasY (Foo a) a where
  y = lensVL $ \f s -> case s of
    Foo x1 x2 -> fmap (\y -> Foo x1 y) (f x2)

instance HasX Bar Char where
  x = lensVL $ \f s -> case s of
    Bar x1 -> fmap (\y -> Bar y) (f x1)

For details, see camelCaseFields.

makeFields = makeLensesWith defaultFieldRules

makeFieldsNoPrefix :: Name -> DecsQ #

Generate overloaded field accessors based on field names which are only prefixed with an underscore (e.g. _name), not additionally with the type name (e.g. _fooName).

This might be the desired behaviour in case the DuplicateRecordFields language extension is used in order to get rid of the necessity to prefix each field name with the type name.

As an example:

data Foo a  = Foo { _x :: Int, _y :: a }
newtype Bar = Bar { _x :: Char }
makeFieldsNoPrefix ''Foo
makeFieldsNoPrefix ''Bar

will create classes

class HasX s a | s -> a where
  x :: Lens' s a
class HasY s a | s -> a where
  y :: Lens' s a

together with instances

instance HasX (Foo a) Int
instance HasY (Foo a) a where
instance HasX Bar Char where

For details, see classUnderscoreNoPrefixFields.

makeFieldsNoPrefix = makeLensesWith classUnderscoreNoPrefixFields

declarePrisms :: DecsQ -> DecsQ #

Generate a Prism for each constructor of each data type.

e.g.

declarePrisms [d|
  data Exp = Lit Int | Var String | Lambda{ bound::String, body::Exp }
  |]

will create

data Exp = Lit Int | Var String | Lambda { bound::String, body::Exp }
_Lit :: Prism' Exp Int
_Var :: Prism' Exp String
_Lambda :: Prism' Exp (String, Exp)

simpleLenses :: Lens' LensRules Bool #

Generate "simple" optics even when type-changing optics are possible. (e.g. Lens' instead of Lens)

generateSignatures :: Lens' LensRules Bool #

Indicate whether or not to supply the signatures for the generated lenses.

Disabling this can be useful if you want to provide a more restricted type signature or if you want to supply hand-written haddocks.

generateUpdateableOptics :: Lens' LensRules Bool #

Generate "updateable" optics when True. When False, (affine) folds will be generated instead of (affine) traversals and getters will be generated instead of lenses. This mode is intended to be used for types with invariants which must be maintained by "smart" constructors.

generateLazyPatterns :: Lens' LensRules Bool #

Generate optics using lazy pattern matches. This can allow fields of an undefined value to be initialized with lenses:

data Foo = Foo {_x :: Int, _y :: Bool}
  deriving Show

makeLensesWith (lensRules & generateLazyPatterns .~ True) ''Foo
> undefined & x .~ 8 & y .~ True
Foo {_x = 8, _y = True}

The downside of this flag is that it can lead to space-leaks and code-size/compile-time increases when generated for large records. By default this flag is turned off, and strict optics are generated.

When using lazy optics the strict optic can be recovered by composing with equality':

strictOptic = equality' % lazyOptic

createClass :: Lens' LensRules Bool #

Create the class if the constructor if generated lenses would be type-preserving and the lensClass rule matches.

lensField :: Lens' LensRules FieldNamer #

Lens' to access the convention for naming fields in our LensRules.

lensClass :: Lens' LensRules ClassyNamer #

Lens' to access the option for naming "classy" lenses.

noPrefixFieldLabels :: LensRules #

Field rules for fields without any prefix. Useful for generation of field labels when paired with DuplicateRecordFields language extension so that no prefixes for field names are necessary.

Since: optics-th-0.2

underscoreFields :: LensRules #

Field rules for fields in the form _prefix_fieldname

camelCaseFields :: LensRules #

Field rules for fields in the form prefixFieldname or _prefixFieldname

If you want all fields to be lensed, then there is no reason to use an _ before the prefix. If any of the record fields leads with an _ then it is assume a field without an _ should not have a lens created.

Note: The prefix must be the same as the typename (with the first letter lowercased). This is a change from lens versions before lens 4.5. If you want the old behaviour, use makeLensesWith abbreviatedFields

classUnderscoreNoPrefixFields :: LensRules #

Field rules for fields in the form _fieldname (the leading underscore is mandatory).

Note: The primary difference to camelCaseFields is that for classUnderscoreNoPrefixFields the field names are not expected to be prefixed with the type name. This might be the desired behaviour when the DuplicateRecordFields extension is enabled.

abbreviatedFields :: LensRules #

Field rules fields in the form prefixFieldname or _prefixFieldname If you want all fields to be lensed, then there is no reason to use an _ before the prefix. If any of the record fields leads with an _ then it is assume a field without an _ should not have a lens created.

Note that prefix may be any string of characters that are not uppercase letters. (In particular, it may be arbitrary string of lowercase letters and numbers) This is the behavior that defaultFieldRules had in lens 4.4 and earlier.

noPrefixNamer :: FieldNamer #

A FieldNamer that leaves the field name as-is. Useful for generation of field labels when paired with DuplicateRecordFields language extension so that no prefixes for field names are necessary.

Since: optics-th-0.2

underscoreNoPrefixNamer :: FieldNamer #

A FieldNamer that strips the _ off of the field name, lowercases the name, and skips the field if it doesn't start with an '_'.

lookingupNamer :: [(String, String)] -> FieldNamer #

Create a FieldNamer from explicit pairings of (fieldName, lensName).

mappingNamer #

Arguments

:: (String -> [String])

A function that maps a fieldName to lensNames.

-> FieldNamer 

Create a FieldNamer from a mapping function. If the function returns [], it creates no lens for the field.

class ViewableOptic k r #

Generalized view (even more powerful than view from the lens library).

View the value(s) pointed to by an optic.

The type of the result depends on the optic. You get:

When in doubt, use specific, flavour restricted versions. This function is mostly useful for things such as passthrough.

Minimal complete definition

gview, gviews

Associated Types

type ViewResult k r #

Instances

Instances details
Monoid r => ViewableOptic A_Fold r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult A_Fold r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' A_Fold is s r -> m (ViewResult A_Fold r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' A_Fold is s a -> (a -> r) -> m (ViewResult A_Fold r) #

ViewableOptic An_AffineFold r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult An_AffineFold r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' An_AffineFold is s r -> m (ViewResult An_AffineFold r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' An_AffineFold is s a -> (a -> r) -> m (ViewResult An_AffineFold r) #

ViewableOptic A_Getter r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult A_Getter r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' A_Getter is s r -> m (ViewResult A_Getter r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' A_Getter is s a -> (a -> r) -> m (ViewResult A_Getter r) #

ViewableOptic A_ReversedPrism r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult A_ReversedPrism r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' A_ReversedPrism is s r -> m (ViewResult A_ReversedPrism r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' A_ReversedPrism is s a -> (a -> r) -> m (ViewResult A_ReversedPrism r) #

Monoid r => ViewableOptic A_Traversal r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult A_Traversal r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' A_Traversal is s r -> m (ViewResult A_Traversal r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' A_Traversal is s a -> (a -> r) -> m (ViewResult A_Traversal r) #

ViewableOptic An_AffineTraversal r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult An_AffineTraversal r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' An_AffineTraversal is s r -> m (ViewResult An_AffineTraversal r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' An_AffineTraversal is s a -> (a -> r) -> m (ViewResult An_AffineTraversal r) #

ViewableOptic A_Prism r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult A_Prism r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' A_Prism is s r -> m (ViewResult A_Prism r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' A_Prism is s a -> (a -> r) -> m (ViewResult A_Prism r) #

ViewableOptic A_Lens r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult A_Lens r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' A_Lens is s r -> m (ViewResult A_Lens r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' A_Lens is s a -> (a -> r) -> m (ViewResult A_Lens r) #

ViewableOptic An_Iso r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult An_Iso r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' An_Iso is s r -> m (ViewResult An_Iso r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' An_Iso is s a -> (a -> r) -> m (ViewResult An_Iso r) #

type family ViewResult k r #

Instances

Instances details
type ViewResult A_Fold r 
Instance details

Defined in Optics.View

type ViewResult A_Fold r = r
type ViewResult An_AffineFold r 
Instance details

Defined in Optics.View

type ViewResult A_Getter r 
Instance details

Defined in Optics.View

type ViewResult A_Getter r = r
type ViewResult A_ReversedPrism r 
Instance details

Defined in Optics.View

type ViewResult A_Traversal r 
Instance details

Defined in Optics.View

type ViewResult An_AffineTraversal r 
Instance details

Defined in Optics.View

type ViewResult A_Prism r 
Instance details

Defined in Optics.View

type ViewResult A_Lens r 
Instance details

Defined in Optics.View

type ViewResult A_Lens r = r
type ViewResult An_Iso r 
Instance details

Defined in Optics.View

type ViewResult An_Iso r = r

class (MonadReader b m, MonadReader a n, Magnify m n b a) => MagnifyMany (m :: Type -> Type) (n :: Type -> Type) b a | m -> b, n -> a, m a -> n, n b -> m where #

Extends Magnify with an ability to magnify using a Fold over multiple targets so that actions for each one are executed sequentially and the results are aggregated.

There is however no sensible instance of MagnifyMany for StateT.

Methods

magnifyMany :: forall k c (is :: IxList). (Is k A_Fold, Monoid c) => Optic' k is a b -> m c -> n c infixr 2 #

Instances

Instances details
MagnifyMany m n b a => MagnifyMany (MaybeT m) (MaybeT n) b a 
Instance details

Defined in Optics.Zoom

Methods

magnifyMany :: forall k c (is :: IxList). (Is k A_Fold, Monoid c) => Optic' k is a b -> MaybeT m c -> MaybeT n c #

MagnifyMany m n b a => MagnifyMany (ListT m) (ListT n) b a 
Instance details

Defined in Optics.Zoom

Methods

magnifyMany :: forall k c (is :: IxList). (Is k A_Fold, Monoid c) => Optic' k is a b -> ListT m c -> ListT n c #

MagnifyMany m n b a => MagnifyMany (ExceptT e m) (ExceptT e n) b a 
Instance details

Defined in Optics.Zoom

Methods

magnifyMany :: forall k c (is :: IxList). (Is k A_Fold, Monoid c) => Optic' k is a b -> ExceptT e m c -> ExceptT e n c #

MagnifyMany m n b a => MagnifyMany (IdentityT m) (IdentityT n) b a 
Instance details

Defined in Optics.Zoom

Methods

magnifyMany :: forall k c (is :: IxList). (Is k A_Fold, Monoid c) => Optic' k is a b -> IdentityT m c -> IdentityT n c #

(Error e, MagnifyMany m n b a) => MagnifyMany (ErrorT e m) (ErrorT e n) b a 
Instance details

Defined in Optics.Zoom

Methods

magnifyMany :: forall k c (is :: IxList). (Is k A_Fold, Monoid c) => Optic' k is a b -> ErrorT e m c -> ErrorT e n c #

Monad m => MagnifyMany (ReaderT b m) (ReaderT a m) b a 
Instance details

Defined in Optics.Zoom

Methods

magnifyMany :: forall k c (is :: IxList). (Is k A_Fold, Monoid c) => Optic' k is a b -> ReaderT b m c -> ReaderT a m c #

(Monoid w, MagnifyMany m n b a) => MagnifyMany (WriterT w m) (WriterT w n) b a 
Instance details

Defined in Optics.Zoom

Methods

magnifyMany :: forall k c (is :: IxList). (Is k A_Fold, Monoid c) => Optic' k is a b -> WriterT w m c -> WriterT w n c #

(Monoid w, MagnifyMany m n b a) => MagnifyMany (WriterT w m) (WriterT w n) b a 
Instance details

Defined in Optics.Zoom

Methods

magnifyMany :: forall k c (is :: IxList). (Is k A_Fold, Monoid c) => Optic' k is a b -> WriterT w m c -> WriterT w n c #

MagnifyMany ((->) b :: Type -> Type) ((->) a :: Type -> Type) b a
magnifyMany = foldMapOf
Instance details

Defined in Optics.Zoom

Methods

magnifyMany :: forall k c (is :: IxList). (Is k A_Fold, Monoid c) => Optic' k is a b -> (b -> c) -> a -> c #

(Monad m, Monoid w) => MagnifyMany (RWST b w s m) (RWST a w s m) b a 
Instance details

Defined in Optics.Zoom

Methods

magnifyMany :: forall k c (is :: IxList). (Is k A_Fold, Monoid c) => Optic' k is a b -> RWST b w s m c -> RWST a w s m c #

(Monad m, Monoid w) => MagnifyMany (RWST b w s m) (RWST a w s m) b a 
Instance details

Defined in Optics.Zoom

Methods

magnifyMany :: forall k c (is :: IxList). (Is k A_Fold, Monoid c) => Optic' k is a b -> RWST b w s m c -> RWST a w s m c #

class AppendIndices (xs :: IxList) (ys :: IxList) (ks :: IxList) | xs ys -> ks #

In pseudo (dependent-)Haskell, provide a witness

foldr f (foldr f init xs) ys = foldr f init (ys ++ xs)
   where f = (->)

Since: optics-core-0.4

Minimal complete definition

appendIndices

Instances

Instances details
AppendIndices xs ('[] :: [Type]) xs

If the second list is empty, we can shortcircuit and pick the first list immediately.

Instance details

Defined in Optics.Internal.Optic.TypeLevel

Methods

appendIndices :: IxEq i (Curry xs (Curry '[] i)) (Curry xs i) #

AppendIndices ('[] :: [Type]) ys ys 
Instance details

Defined in Optics.Internal.Optic.TypeLevel

Methods

appendIndices :: IxEq i (Curry '[] (Curry ys i)) (Curry ys i) #

AppendIndices xs ys ks => AppendIndices (x ': xs) ys (x ': ks) 
Instance details

Defined in Optics.Internal.Optic.TypeLevel

Methods

appendIndices :: IxEq i (Curry (x ': xs) (Curry ys i)) (Curry (x ': ks) i) #

class CurryCompose (xs :: IxList) where #

Class that is inhabited by all type-level lists xs, providing the ability to compose a function under Curry xs.

Methods

composeN :: (i -> j) -> Curry xs i -> Curry xs j #

Compose a function under Curry xs. This generalises (.) (aka fmap for (->)) to work for curried functions with one argument for each type in the list.

Instances

Instances details
CurryCompose ('[] :: [Type]) 
Instance details

Defined in Optics.Internal.Optic.TypeLevel

Methods

composeN :: (i -> j) -> Curry '[] i -> Curry '[] j #

CurryCompose xs => CurryCompose (x ': xs) 
Instance details

Defined in Optics.Internal.Optic.TypeLevel

Methods

composeN :: (i -> j) -> Curry (x ': xs) i -> Curry (x ': xs) j #

type family Curry (xs :: IxList) y where ... #

Curry a type-level list.

In pseudo (dependent-)Haskell:

Curry xs y = foldr (->) y xs

Equations

Curry ('[] :: [Type]) y = y 
Curry (x ': xs) y = x -> Curry xs y 

type WithIx i = '[i] #

Singleton index list

type NoIx = '[] :: [Type] #

An alias for an empty index-list

type IxList = [Type] #

A list of index types, used for indexed optics.

Since: optics-core-0.2

data A_Review #

Tag for a review.

Instances

Instances details
ReversibleOptic A_Review 
Instance details

Defined in Optics.Re

Associated Types

type ReversedOptic A_Review = (r :: Type) #

Methods

re :: forall (is :: IxList) s t a b. AcceptsEmptyIndices "re" is => Optic A_Review is s t a b -> Optic (ReversedOptic A_Review) is b a t s #

Is A_ReversedLens A_Review 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_ReversedLens p => r) -> Constraints A_Review p => r #

Is A_Prism A_Review 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints A_Review p => r #

Is An_Iso A_Review 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Review p => r #

k ~ A_Review => JoinKinds A_Review A_Review k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Review p, Constraints A_Review p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_Review A_ReversedLens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Review p, Constraints A_ReversedLens p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_Review A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Review p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_Review An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Review p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_ReversedLens A_Review k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedLens p, Constraints A_Review p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_Prism A_Review k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Review p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds An_Iso A_Review k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Review p) => r) -> Constraints k p => r #

(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Review f g s t a b 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_Review #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_Review is s t a b -> Optic (MappedOptic A_Review) is (f s) (g t) (f a) (g b) #

type ReversedOptic A_Review 
Instance details

Defined in Optics.Re

type MappedOptic A_Review 
Instance details

Defined in Optics.Mapping

data A_ReversedLens #

Tag for a reversed lens.

Instances

Instances details
ReversibleOptic A_ReversedLens 
Instance details

Defined in Optics.Re

Associated Types

type ReversedOptic A_ReversedLens = (r :: Type) #

Methods

re :: forall (is :: IxList) s t a b. AcceptsEmptyIndices "re" is => Optic A_ReversedLens is s t a b -> Optic (ReversedOptic A_ReversedLens) is b a t s #

Is A_ReversedLens A_Review 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_ReversedLens p => r) -> Constraints A_Review p => r #

Is An_Iso A_ReversedLens 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_ReversedLens p => r #

k ~ A_Review => JoinKinds A_Review A_ReversedLens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Review p, Constraints A_ReversedLens p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_ReversedLens A_Review k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedLens p, Constraints A_Review p) => r) -> Constraints k p => r #

k ~ A_ReversedLens => JoinKinds A_ReversedLens A_ReversedLens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedLens p, Constraints A_ReversedLens p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_ReversedLens A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedLens p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_ReversedLens => JoinKinds A_ReversedLens An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedLens p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_Prism A_ReversedLens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_ReversedLens p) => r) -> Constraints k p => r #

k ~ A_ReversedLens => JoinKinds An_Iso A_ReversedLens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_ReversedLens p) => r) -> Constraints k p => r #

(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_ReversedLens f g s t a b 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_ReversedLens #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_ReversedLens is s t a b -> Optic (MappedOptic A_ReversedLens) is (f s) (g t) (f a) (g b) #

type ReversedOptic A_ReversedLens 
Instance details

Defined in Optics.Re

type MappedOptic A_ReversedLens 
Instance details

Defined in Optics.Mapping

data A_Fold #

Tag for a fold.

Instances

Instances details
Monoid r => ViewableOptic A_Fold r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult A_Fold r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' A_Fold is s r -> m (ViewResult A_Fold r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' A_Fold is s a -> (a -> r) -> m (ViewResult A_Fold r) #

Is An_AffineFold A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineFold p => r) -> Constraints A_Fold p => r #

Is A_Getter A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Getter p => r) -> Constraints A_Fold p => r #

Is A_ReversedPrism A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_ReversedPrism p => r) -> Constraints A_Fold p => r #

Is A_Traversal A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Traversal p => r) -> Constraints A_Fold p => r #

Is An_AffineTraversal A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineTraversal p => r) -> Constraints A_Fold p => r #

Is A_Prism A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints A_Fold p => r #

Is A_Lens A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints A_Fold p => r #

Is An_Iso A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Fold p => r #

k ~ A_Fold => JoinKinds A_Fold A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds An_AffineFold A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Getter A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_ReversedPrism A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Traversal A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds An_AffineTraversal A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Prism A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Lens A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds An_Iso A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Fold p) => r) -> Constraints k p => r #

(s ~ t, a ~ b) => ToReadOnly A_Fold s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic A_Fold #

Methods

getting :: forall (is :: IxList). Optic A_Fold is s t a b -> Optic' (ReadOnlyOptic A_Fold) is s a #

(s ~ t, a ~ b) => IxOptic A_Fold s t a b 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic A_Fold is s t a b -> Optic A_Fold NoIx s t a b #

type ReadOnlyOptic A_Fold 
Instance details

Defined in Optics.ReadOnly

type ViewResult A_Fold r 
Instance details

Defined in Optics.View

type ViewResult A_Fold r = r

data An_AffineFold #

Tag for an affine fold.

Instances

Instances details
ViewableOptic An_AffineFold r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult An_AffineFold r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' An_AffineFold is s r -> m (ViewResult An_AffineFold r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' An_AffineFold is s a -> (a -> r) -> m (ViewResult An_AffineFold r) #

Is An_AffineFold A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineFold p => r) -> Constraints A_Fold p => r #

Is A_Getter An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Getter p => r) -> Constraints An_AffineFold p => r #

Is A_ReversedPrism An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_ReversedPrism p => r) -> Constraints An_AffineFold p => r #

Is An_AffineTraversal An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineTraversal p => r) -> Constraints An_AffineFold p => r #

Is A_Prism An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints An_AffineFold p => r #

Is A_Lens An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints An_AffineFold p => r #

Is An_Iso An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints An_AffineFold p => r #

k ~ A_Fold => JoinKinds A_Fold An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds An_AffineFold A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds An_AffineFold A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Getter An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_ReversedPrism An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Traversal An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineTraversal An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Prism An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Lens An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_Iso An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

(s ~ t, a ~ b) => ToReadOnly An_AffineFold s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic An_AffineFold #

Methods

getting :: forall (is :: IxList). Optic An_AffineFold is s t a b -> Optic' (ReadOnlyOptic An_AffineFold) is s a #

(s ~ t, a ~ b) => IxOptic An_AffineFold s t a b 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic An_AffineFold is s t a b -> Optic An_AffineFold NoIx s t a b #

type ReadOnlyOptic An_AffineFold 
Instance details

Defined in Optics.ReadOnly

type ViewResult An_AffineFold r 
Instance details

Defined in Optics.View

data A_Getter #

Tag for a getter.

Instances

Instances details
ReversibleOptic A_Getter 
Instance details

Defined in Optics.Re

Associated Types

type ReversedOptic A_Getter = (r :: Type) #

Methods

re :: forall (is :: IxList) s t a b. AcceptsEmptyIndices "re" is => Optic A_Getter is s t a b -> Optic (ReversedOptic A_Getter) is b a t s #

ViewableOptic A_Getter r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult A_Getter r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' A_Getter is s r -> m (ViewResult A_Getter r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' A_Getter is s a -> (a -> r) -> m (ViewResult A_Getter r) #

Is A_Getter A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Getter p => r) -> Constraints A_Fold p => r #

Is A_Getter An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Getter p => r) -> Constraints An_AffineFold p => r #

Is A_ReversedPrism A_Getter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_ReversedPrism p => r) -> Constraints A_Getter p => r #

Is A_Lens A_Getter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints A_Getter p => r #

Is An_Iso A_Getter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Getter p => r #

k ~ A_Fold => JoinKinds A_Fold A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Getter A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Getter An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Getter A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Getter A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Getter A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Getter An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Getter A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Getter A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Getter An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_ReversedPrism A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Traversal A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineTraversal A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Prism A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Lens A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds An_Iso A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Getter p) => r) -> Constraints k p => r #

(s ~ t, a ~ b) => ToReadOnly A_Getter s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic A_Getter #

Methods

getting :: forall (is :: IxList). Optic A_Getter is s t a b -> Optic' (ReadOnlyOptic A_Getter) is s a #

(s ~ t, a ~ b) => IxOptic A_Getter s t a b 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic A_Getter is s t a b -> Optic A_Getter NoIx s t a b #

(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Getter f g s t a b
>>> [('a', True), ('b', False)] ^. _1 %& mapping
"ab"
>>> let v = [[ (('a', True), "foo"), (('b', False), "bar")], [ (('c', True), "xyz") ] ]
>>> v ^. _1 % _2 %& mapping %& mapping
[[True,False],[True]]
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_Getter #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_Getter is s t a b -> Optic (MappedOptic A_Getter) is (f s) (g t) (f a) (g b) #

type ReversedOptic A_Getter 
Instance details

Defined in Optics.Re

type ReadOnlyOptic A_Getter 
Instance details

Defined in Optics.ReadOnly

type MappedOptic A_Getter 
Instance details

Defined in Optics.Mapping

type ViewResult A_Getter r 
Instance details

Defined in Optics.View

type ViewResult A_Getter r = r

data A_ReversedPrism #

Tag for a reversed prism.

Instances

Instances details
ReversibleOptic A_ReversedPrism 
Instance details

Defined in Optics.Re

Associated Types

type ReversedOptic A_ReversedPrism = (r :: Type) #

Methods

re :: forall (is :: IxList) s t a b. AcceptsEmptyIndices "re" is => Optic A_ReversedPrism is s t a b -> Optic (ReversedOptic A_ReversedPrism) is b a t s #

ViewableOptic A_ReversedPrism r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult A_ReversedPrism r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' A_ReversedPrism is s r -> m (ViewResult A_ReversedPrism r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' A_ReversedPrism is s a -> (a -> r) -> m (ViewResult A_ReversedPrism r) #

Is A_ReversedPrism A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_ReversedPrism p => r) -> Constraints A_Fold p => r #

Is A_ReversedPrism An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_ReversedPrism p => r) -> Constraints An_AffineFold p => r #

Is A_ReversedPrism A_Getter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_ReversedPrism p => r) -> Constraints A_Getter p => r #

Is An_Iso A_ReversedPrism 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_ReversedPrism p => r #

k ~ A_Fold => JoinKinds A_Fold A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Getter A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_ReversedPrism A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_ReversedPrism An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_ReversedPrism A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ A_ReversedPrism => JoinKinds A_ReversedPrism A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_ReversedPrism A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_ReversedPrism An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_ReversedPrism A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_ReversedPrism A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_ReversedPrism => JoinKinds A_ReversedPrism An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Traversal A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineTraversal A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Prism A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Lens A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_ReversedPrism => JoinKinds An_Iso A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

ToReadOnly A_ReversedPrism s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic A_ReversedPrism #

Methods

getting :: forall (is :: IxList). Optic A_ReversedPrism is s t a b -> Optic' (ReadOnlyOptic A_ReversedPrism) is s a #

(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_ReversedPrism f g s t a b 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_ReversedPrism #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_ReversedPrism is s t a b -> Optic (MappedOptic A_ReversedPrism) is (f s) (g t) (f a) (g b) #

type ReversedOptic A_ReversedPrism 
Instance details

Defined in Optics.Re

type ReadOnlyOptic A_ReversedPrism 
Instance details

Defined in Optics.ReadOnly

type MappedOptic A_ReversedPrism 
Instance details

Defined in Optics.Mapping

type ViewResult A_ReversedPrism r 
Instance details

Defined in Optics.View

data A_Setter #

Tag for a setter.

Instances

Instances details
Is A_Traversal A_Setter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Traversal p => r) -> Constraints A_Setter p => r #

Is An_AffineTraversal A_Setter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineTraversal p => r) -> Constraints A_Setter p => r #

Is A_Prism A_Setter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints A_Setter p => r #

Is A_Lens A_Setter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints A_Setter p => r #

Is An_Iso A_Setter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Setter p => r #

k ~ A_Setter => JoinKinds A_Setter A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints A_Setter p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Setter A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Setter An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Setter A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Setter A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Setter An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Traversal A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Setter p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds An_AffineTraversal A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Setter p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Prism A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Setter p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Lens A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Setter p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds An_Iso A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Setter p) => r) -> Constraints k p => r #

IxOptic A_Setter s t a b 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic A_Setter is s t a b -> Optic A_Setter NoIx s t a b #

data A_Traversal #

Tag for a traversal.

Instances

Instances details
Monoid r => ViewableOptic A_Traversal r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult A_Traversal r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' A_Traversal is s r -> m (ViewResult A_Traversal r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' A_Traversal is s a -> (a -> r) -> m (ViewResult A_Traversal r) #

Is A_Traversal A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Traversal p => r) -> Constraints A_Fold p => r #

Is A_Traversal A_Setter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Traversal p => r) -> Constraints A_Setter p => r #

Is An_AffineTraversal A_Traversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineTraversal p => r) -> Constraints A_Traversal p => r #

Is A_Prism A_Traversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints A_Traversal p => r #

Is A_Lens A_Traversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints A_Traversal p => r #

Is An_Iso A_Traversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Traversal p => r #

Monoid r => PermeableOptic A_Traversal r 
Instance details

Defined in Optics.Passthrough

Methods

passthrough :: forall (is :: IxList) s t a b. Optic A_Traversal is s t a b -> (a -> (r, b)) -> s -> (ViewResult A_Traversal r, t) #

k ~ A_Fold => JoinKinds A_Fold A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds An_AffineFold A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Getter A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_ReversedPrism A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Setter A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Traversal A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Traversal An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Traversal A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Traversal A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Traversal A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Setter p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Traversal A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Traversal An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Traversal A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Traversal A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Traversal An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds An_AffineTraversal A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Prism A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Lens A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds An_Iso A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Traversal p) => r) -> Constraints k p => r #

ToReadOnly A_Traversal s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic A_Traversal #

Methods

getting :: forall (is :: IxList). Optic A_Traversal is s t a b -> Optic' (ReadOnlyOptic A_Traversal) is s a #

IxOptic A_Traversal s t a b 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic A_Traversal is s t a b -> Optic A_Traversal NoIx s t a b #

type ReadOnlyOptic A_Traversal 
Instance details

Defined in Optics.ReadOnly

type ViewResult A_Traversal r 
Instance details

Defined in Optics.View

data An_AffineTraversal #

Tag for an affine traversal.

Instances

Instances details
ViewableOptic An_AffineTraversal r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult An_AffineTraversal r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' An_AffineTraversal is s r -> m (ViewResult An_AffineTraversal r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' An_AffineTraversal is s a -> (a -> r) -> m (ViewResult An_AffineTraversal r) #

Is An_AffineTraversal A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineTraversal p => r) -> Constraints A_Fold p => r #

Is An_AffineTraversal An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineTraversal p => r) -> Constraints An_AffineFold p => r #

Is An_AffineTraversal A_Setter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineTraversal p => r) -> Constraints A_Setter p => r #

Is An_AffineTraversal A_Traversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineTraversal p => r) -> Constraints A_Traversal p => r #

Is A_Prism An_AffineTraversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints An_AffineTraversal p => r #

Is A_Lens An_AffineTraversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints An_AffineTraversal p => r #

Is An_Iso An_AffineTraversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints An_AffineTraversal p => r #

PermeableOptic An_AffineTraversal r 
Instance details

Defined in Optics.Passthrough

Methods

passthrough :: forall (is :: IxList) s t a b. Optic An_AffineTraversal is s t a b -> (a -> (r, b)) -> s -> (ViewResult An_AffineTraversal r, t) #

k ~ A_Fold => JoinKinds A_Fold An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Getter An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_ReversedPrism An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Setter An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Traversal An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds An_AffineTraversal A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineTraversal An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineTraversal A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineTraversal A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds An_AffineTraversal A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Setter p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds An_AffineTraversal A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds An_AffineTraversal An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds An_AffineTraversal A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds An_AffineTraversal A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds An_AffineTraversal An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds A_Prism An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds A_Lens An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds An_Iso An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

ToReadOnly An_AffineTraversal s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic An_AffineTraversal #

Methods

getting :: forall (is :: IxList). Optic An_AffineTraversal is s t a b -> Optic' (ReadOnlyOptic An_AffineTraversal) is s a #

IxOptic An_AffineTraversal s t a b 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic An_AffineTraversal is s t a b -> Optic An_AffineTraversal NoIx s t a b #

type ReadOnlyOptic An_AffineTraversal 
Instance details

Defined in Optics.ReadOnly

type ViewResult An_AffineTraversal r 
Instance details

Defined in Optics.View

data A_Prism #

Tag for a prism.

Instances

Instances details
ReversibleOptic A_Prism 
Instance details

Defined in Optics.Re

Associated Types

type ReversedOptic A_Prism = (r :: Type) #

Methods

re :: forall (is :: IxList) s t a b. AcceptsEmptyIndices "re" is => Optic A_Prism is s t a b -> Optic (ReversedOptic A_Prism) is b a t s #

ViewableOptic A_Prism r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult A_Prism r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' A_Prism is s r -> m (ViewResult A_Prism r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' A_Prism is s a -> (a -> r) -> m (ViewResult A_Prism r) #

Is A_Prism A_Review 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints A_Review p => r #

Is A_Prism A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints A_Fold p => r #

Is A_Prism An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints An_AffineFold p => r #

Is A_Prism A_Setter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints A_Setter p => r #

Is A_Prism A_Traversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints A_Traversal p => r #

Is A_Prism An_AffineTraversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints An_AffineTraversal p => r #

Is An_Iso A_Prism 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Prism p => r #

PermeableOptic A_Prism r 
Instance details

Defined in Optics.Passthrough

Methods

passthrough :: forall (is :: IxList) s t a b. Optic A_Prism is s t a b -> (a -> (r, b)) -> s -> (ViewResult A_Prism r, t) #

k ~ A_Review => JoinKinds A_Review A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Review p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_ReversedLens A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedLens p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Getter A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_ReversedPrism A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Setter A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Traversal A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds An_AffineTraversal A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_Prism A_Review k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Review p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_Prism A_ReversedLens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_ReversedLens p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Prism A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Prism An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Prism A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Prism A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Prism A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Setter p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Prism A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds A_Prism An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ A_Prism => JoinKinds A_Prism A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds A_Prism A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Prism => JoinKinds A_Prism An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds A_Lens A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Prism => JoinKinds An_Iso A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Prism p) => r) -> Constraints k p => r #

ToReadOnly A_Prism s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic A_Prism #

Methods

getting :: forall (is :: IxList). Optic A_Prism is s t a b -> Optic' (ReadOnlyOptic A_Prism) is s a #

(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Prism f g s t a b 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_Prism #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_Prism is s t a b -> Optic (MappedOptic A_Prism) is (f s) (g t) (f a) (g b) #

(GConstructorImpl repDefined name s t a b, _name ~ AppendSymbol "_" name) => GenericOptic repDefined (_name :: Symbol) A_Prism s t a b 
Instance details

Defined in Optics.Label

Methods

genericOptic :: Optic A_Prism NoIx s t a b

type ReversedOptic A_Prism 
Instance details

Defined in Optics.Re

type ReadOnlyOptic A_Prism 
Instance details

Defined in Optics.ReadOnly

type MappedOptic A_Prism 
Instance details

Defined in Optics.Mapping

type ViewResult A_Prism r 
Instance details

Defined in Optics.View

data A_Lens #

Tag for a lens.

Instances

Instances details
ReversibleOptic A_Lens 
Instance details

Defined in Optics.Re

Associated Types

type ReversedOptic A_Lens = (r :: Type) #

Methods

re :: forall (is :: IxList) s t a b. AcceptsEmptyIndices "re" is => Optic A_Lens is s t a b -> Optic (ReversedOptic A_Lens) is b a t s #

ViewableOptic A_Lens r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult A_Lens r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' A_Lens is s r -> m (ViewResult A_Lens r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' A_Lens is s a -> (a -> r) -> m (ViewResult A_Lens r) #

Is A_Lens A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints A_Fold p => r #

Is A_Lens An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints An_AffineFold p => r #

Is A_Lens A_Getter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints A_Getter p => r #

Is A_Lens A_Setter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints A_Setter p => r #

Is A_Lens A_Traversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints A_Traversal p => r #

Is A_Lens An_AffineTraversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints An_AffineTraversal p => r #

Is An_Iso A_Lens 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Lens p => r #

PermeableOptic A_Lens r 
Instance details

Defined in Optics.Passthrough

Methods

passthrough :: forall (is :: IxList) s t a b. Optic A_Lens is s t a b -> (a -> (r, b)) -> s -> (ViewResult A_Lens r, t) #

k ~ A_Fold => JoinKinds A_Fold A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Getter A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_ReversedPrism A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Setter A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Traversal A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds An_AffineTraversal A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds A_Prism A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Lens A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Lens An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Lens A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Lens A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Lens A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Setter p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Lens A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds A_Lens An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds A_Lens A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Lens => JoinKinds A_Lens A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Lens => JoinKinds A_Lens An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Lens => JoinKinds An_Iso A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Lens p) => r) -> Constraints k p => r #

ToReadOnly A_Lens s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic A_Lens #

Methods

getting :: forall (is :: IxList). Optic A_Lens is s t a b -> Optic' (ReadOnlyOptic A_Lens) is s a #

IxOptic A_Lens s t a b 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic A_Lens is s t a b -> Optic A_Lens NoIx s t a b #

(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Lens f g s t a b 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_Lens #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_Lens is s t a b -> Optic (MappedOptic A_Lens) is (f s) (g t) (f a) (g b) #

GFieldImpl name s t a b => GenericOptic repDefined (name :: Symbol) A_Lens s t a b 
Instance details

Defined in Optics.Label

Methods

genericOptic :: Optic A_Lens NoIx s t a b

type ReversedOptic A_Lens 
Instance details

Defined in Optics.Re

type ReadOnlyOptic A_Lens 
Instance details

Defined in Optics.ReadOnly

type MappedOptic A_Lens 
Instance details

Defined in Optics.Mapping

type ViewResult A_Lens r 
Instance details

Defined in Optics.View

type ViewResult A_Lens r = r

data An_Iso #

Tag for an iso.

Instances

Instances details
ReversibleOptic An_Iso 
Instance details

Defined in Optics.Re

Associated Types

type ReversedOptic An_Iso = (r :: Type) #

Methods

re :: forall (is :: IxList) s t a b. AcceptsEmptyIndices "re" is => Optic An_Iso is s t a b -> Optic (ReversedOptic An_Iso) is b a t s #

ViewableOptic An_Iso r 
Instance details

Defined in Optics.View

Associated Types

type ViewResult An_Iso r #

Methods

gview :: forall s m (is :: IxList). MonadReader s m => Optic' An_Iso is s r -> m (ViewResult An_Iso r) #

gviews :: forall s m (is :: IxList) a. MonadReader s m => Optic' An_Iso is s a -> (a -> r) -> m (ViewResult An_Iso r) #

Is An_Iso A_Review 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Review p => r #

Is An_Iso A_ReversedLens 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_ReversedLens p => r #

Is An_Iso A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Fold p => r #

Is An_Iso An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints An_AffineFold p => r #

Is An_Iso A_Getter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Getter p => r #

Is An_Iso A_ReversedPrism 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_ReversedPrism p => r #

Is An_Iso A_Setter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Setter p => r #

Is An_Iso A_Traversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Traversal p => r #

Is An_Iso An_AffineTraversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints An_AffineTraversal p => r #

Is An_Iso A_Prism 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Prism p => r #

Is An_Iso A_Lens 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Lens p => r #

PermeableOptic An_Iso r 
Instance details

Defined in Optics.Passthrough

Methods

passthrough :: forall (is :: IxList) s t a b. Optic An_Iso is s t a b -> (a -> (r, b)) -> s -> (ViewResult An_Iso r, t) #

k ~ A_Review => JoinKinds A_Review An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Review p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_ReversedLens => JoinKinds A_ReversedLens An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedLens p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Getter An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_ReversedPrism => JoinKinds A_ReversedPrism An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Setter An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Traversal An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds An_AffineTraversal An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Prism => JoinKinds A_Prism An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Lens => JoinKinds A_Lens An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds An_Iso A_Review k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Review p) => r) -> Constraints k p => r #

k ~ A_ReversedLens => JoinKinds An_Iso A_ReversedLens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_ReversedLens p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds An_Iso A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_Iso An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds An_Iso A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ A_ReversedPrism => JoinKinds An_Iso A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds An_Iso A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Setter p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds An_Iso A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds An_Iso An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ A_Prism => JoinKinds An_Iso A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Lens => JoinKinds An_Iso A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ An_Iso => JoinKinds An_Iso An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints An_Iso p) => r) -> Constraints k p => r #

ToReadOnly An_Iso s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic An_Iso #

Methods

getting :: forall (is :: IxList). Optic An_Iso is s t a b -> Optic' (ReadOnlyOptic An_Iso) is s a #

(Functor f, Functor g) => MappingOptic An_Iso f g s t a b 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic An_Iso #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic An_Iso is s t a b -> Optic (MappedOptic An_Iso) is (f s) (g t) (f a) (g b) #

type ReversedOptic An_Iso 
Instance details

Defined in Optics.Re

type ReadOnlyOptic An_Iso 
Instance details

Defined in Optics.ReadOnly

type MappedOptic An_Iso 
Instance details

Defined in Optics.Mapping

type ViewResult An_Iso r 
Instance details

Defined in Optics.View

type ViewResult An_Iso r = r

type OpticKind = Type #

Kind for types used as optic tags, such as A_Lens.

Since: optics-core-0.2

class JoinKinds k l m | k l -> m #

Computes the least upper bound of two optics kinds.

In presence of a JoinKinds k l m constraint Optic m represents the least upper bound of an Optic k and an Optic l. This means in particular that composition of an Optic k and an Optic k will yield an Optic m.

Since: optics-core-0.4

Minimal complete definition

joinKinds

Instances

Instances details
(JoinKinds k l m, TypeError (('ShowType k :<>: 'Text " cannot be composed with ") :<>: 'ShowType l) :: Constraint) => JoinKinds k l m 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints k p, Constraints l p) => r) -> Constraints m p => r #

k ~ A_Review => JoinKinds A_Review A_Review k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Review p, Constraints A_Review p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_Review A_ReversedLens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Review p, Constraints A_ReversedLens p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_Review A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Review p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_Review An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Review p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_ReversedLens A_Review k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedLens p, Constraints A_Review p) => r) -> Constraints k p => r #

k ~ A_ReversedLens => JoinKinds A_ReversedLens A_ReversedLens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedLens p, Constraints A_ReversedLens p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_ReversedLens A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedLens p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_ReversedLens => JoinKinds A_ReversedLens An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedLens p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Fold An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Fold p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds An_AffineFold A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds An_AffineFold A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineFold An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineFold p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Getter A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Getter An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Getter A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Getter A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Getter A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Getter An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Getter A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Getter A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Getter An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Getter p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_ReversedPrism A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_ReversedPrism An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_ReversedPrism A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ A_ReversedPrism => JoinKinds A_ReversedPrism A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_ReversedPrism A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_ReversedPrism An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_ReversedPrism A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_ReversedPrism A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_ReversedPrism => JoinKinds A_ReversedPrism An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_ReversedPrism p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Setter A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints A_Setter p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Setter A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Setter An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Setter A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Setter A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Setter An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Setter p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Traversal A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Traversal An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Traversal A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Traversal A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Traversal A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Setter p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Traversal A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Traversal An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Traversal A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Traversal A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Traversal An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Traversal p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds An_AffineTraversal A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineTraversal An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineTraversal A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_AffineTraversal A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds An_AffineTraversal A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Setter p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds An_AffineTraversal A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds An_AffineTraversal An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds An_AffineTraversal A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds An_AffineTraversal A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds An_AffineTraversal An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_AffineTraversal p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_Prism A_Review k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Review p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds A_Prism A_ReversedLens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_ReversedLens p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Prism A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Prism An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Prism A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Prism A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Prism A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Setter p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Prism A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds A_Prism An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ A_Prism => JoinKinds A_Prism A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds A_Prism A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Prism => JoinKinds A_Prism An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Prism p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds A_Lens A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds A_Lens An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Lens A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds A_Lens A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds A_Lens A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Setter p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds A_Lens A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds A_Lens An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds A_Lens A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Lens => JoinKinds A_Lens A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ A_Lens => JoinKinds A_Lens An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints A_Lens p, Constraints An_Iso p) => r) -> Constraints k p => r #

k ~ A_Review => JoinKinds An_Iso A_Review k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Review p) => r) -> Constraints k p => r #

k ~ A_ReversedLens => JoinKinds An_Iso A_ReversedLens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_ReversedLens p) => r) -> Constraints k p => r #

k ~ A_Fold => JoinKinds An_Iso A_Fold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Fold p) => r) -> Constraints k p => r #

k ~ An_AffineFold => JoinKinds An_Iso An_AffineFold k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints An_AffineFold p) => r) -> Constraints k p => r #

k ~ A_Getter => JoinKinds An_Iso A_Getter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Getter p) => r) -> Constraints k p => r #

k ~ A_ReversedPrism => JoinKinds An_Iso A_ReversedPrism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_ReversedPrism p) => r) -> Constraints k p => r #

k ~ A_Setter => JoinKinds An_Iso A_Setter k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Setter p) => r) -> Constraints k p => r #

k ~ A_Traversal => JoinKinds An_Iso A_Traversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Traversal p) => r) -> Constraints k p => r #

k ~ An_AffineTraversal => JoinKinds An_Iso An_AffineTraversal k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints An_AffineTraversal p) => r) -> Constraints k p => r #

k ~ A_Prism => JoinKinds An_Iso A_Prism k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Prism p) => r) -> Constraints k p => r #

k ~ A_Lens => JoinKinds An_Iso A_Lens k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints A_Lens p) => r) -> Constraints k p => r #

k ~ An_Iso => JoinKinds An_Iso An_Iso k 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

joinKinds :: forall (p :: Type -> Type -> Type -> Type) r. ((Constraints An_Iso p, Constraints An_Iso p) => r) -> Constraints k p => r #

class Is k l #

Subtyping relationship between kinds of optics.

An instance of Is k l means that any Optic k can be used as an Optic l. For example, we have an Is A_Lens A_Traversal instance, but not Is A_Traversal A_Lens.

This class needs instances for all possible combinations of tags.

Minimal complete definition

implies

Instances

Instances details
(TypeError (((('ShowType k :<>: 'Text " cannot be used as ") :<>: 'ShowType l) :$$: 'Text "Perhaps you meant one of these:") :$$: ShowEliminations (EliminationForms k)) :: Constraint) => Is k l

Overlappable instance for a custom type error.

Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints k p => r) -> Constraints l p => r #

Is k k

Every kind of optic can be used as itself.

Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints k p => r) -> Constraints k p => r #

Is A_ReversedLens A_Review 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_ReversedLens p => r) -> Constraints A_Review p => r #

Is An_AffineFold A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineFold p => r) -> Constraints A_Fold p => r #

Is A_Getter A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Getter p => r) -> Constraints A_Fold p => r #

Is A_Getter An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Getter p => r) -> Constraints An_AffineFold p => r #

Is A_ReversedPrism A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_ReversedPrism p => r) -> Constraints A_Fold p => r #

Is A_ReversedPrism An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_ReversedPrism p => r) -> Constraints An_AffineFold p => r #

Is A_ReversedPrism A_Getter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_ReversedPrism p => r) -> Constraints A_Getter p => r #

Is A_Traversal A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Traversal p => r) -> Constraints A_Fold p => r #

Is A_Traversal A_Setter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Traversal p => r) -> Constraints A_Setter p => r #

Is An_AffineTraversal A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineTraversal p => r) -> Constraints A_Fold p => r #

Is An_AffineTraversal An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineTraversal p => r) -> Constraints An_AffineFold p => r #

Is An_AffineTraversal A_Setter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineTraversal p => r) -> Constraints A_Setter p => r #

Is An_AffineTraversal A_Traversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_AffineTraversal p => r) -> Constraints A_Traversal p => r #

Is A_Prism A_Review 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints A_Review p => r #

Is A_Prism A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints A_Fold p => r #

Is A_Prism An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints An_AffineFold p => r #

Is A_Prism A_Setter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints A_Setter p => r #

Is A_Prism A_Traversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints A_Traversal p => r #

Is A_Prism An_AffineTraversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Prism p => r) -> Constraints An_AffineTraversal p => r #

Is A_Lens A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints A_Fold p => r #

Is A_Lens An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints An_AffineFold p => r #

Is A_Lens A_Getter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints A_Getter p => r #

Is A_Lens A_Setter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints A_Setter p => r #

Is A_Lens A_Traversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints A_Traversal p => r #

Is A_Lens An_AffineTraversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints A_Lens p => r) -> Constraints An_AffineTraversal p => r #

Is An_Iso A_Review 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Review p => r #

Is An_Iso A_ReversedLens 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_ReversedLens p => r #

Is An_Iso A_Fold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Fold p => r #

Is An_Iso An_AffineFold 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints An_AffineFold p => r #

Is An_Iso A_Getter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Getter p => r #

Is An_Iso A_ReversedPrism 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_ReversedPrism p => r #

Is An_Iso A_Setter 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Setter p => r #

Is An_Iso A_Traversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Traversal p => r #

Is An_Iso An_AffineTraversal 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints An_AffineTraversal p => r #

Is An_Iso A_Prism 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Prism p => r #

Is An_Iso A_Lens 
Instance details

Defined in Optics.Internal.Optic.Subtyping

Methods

implies :: forall (p :: Type -> Type -> Type -> Type) r. (Constraints An_Iso p => r) -> Constraints A_Lens p => r #

type Optic' k (is :: IxList) s a = Optic k is s s a a #

Common special case of Optic where source and target types are equal.

Here, we need only one "big" and one "small" type. For lenses, this means that in the restricted form we cannot do type-changing updates.

data Optic k (is :: IxList) s t a b #

Wrapper newtype for the whole family of optics.

The first parameter k identifies the particular optic kind (e.g. A_Lens or A_Traversal).

The parameter is is a list of types available as indices. This will typically be NoIx for unindexed optics, or WithIx for optics with a single index. See the "Indexed optics" section of the overview documentation in the Optics module of the main optics package for more details.

The parameters s and t represent the "big" structure, whereas a and b represent the "small" structure.

castOptic :: forall destKind srcKind (is :: IxList) s t a b. Is srcKind destKind => Optic srcKind is s t a b -> Optic destKind is s t a b #

Explicit cast from one optic flavour to another.

The resulting optic kind is given in the first type argument, so you can use TypeApplications to set it. For example

 castOptic @A_Lens o

turns o into a Lens.

This is the identity function, modulo some constraint jiggery-pokery.

(%) :: forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a b. (JoinKinds k l m, AppendIndices is js ks) => Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b infixl 9 #

Compose two optics of compatible flavours.

Returns an optic of the appropriate supertype. If either or both optics are indexed, the composition preserves all the indices.

(%%) :: forall k (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a b. AppendIndices is js ks => Optic k is s t u v -> Optic k js u v a b -> Optic k ks s t a b infixl 9 #

Compose two optics of the same flavour.

Normally you can simply use (%) instead, but this may be useful to help type inference if the type of one of the optics is otherwise under-constrained.

(%&) :: forall k (is :: IxList) s t a b l (js :: IxList) s' t' a' b'. Optic k is s t a b -> (Optic k is s t a b -> Optic l js s' t' a' b') -> Optic l js s' t' a' b' infixl 9 #

Flipped function application, specialised to optics and binding tightly.

Useful for post-composing optics transformations:

>>> toListOf (ifolded %& ifiltered (\i s -> length s <= i)) ["", "a","abc"]
["","a"]

class is ~ '[i] => HasSingleIndex (is :: IxList) i #

Generate sensible error messages in case a user tries to pass either an unindexed optic or indexed optic with unflattened indices where indexed optic with a single index is expected.

Instances

Instances details
(TypeError ('Text "Indexed optic is expected") :: Constraint, ('[] :: [Type]) ~ '[i]) => HasSingleIndex ('[] :: [Type]) i 
Instance details

Defined in Optics.Internal.Indexed

(TypeError ('Text "Use (<%>) or icompose to combine indices of type " :<>: ShowTypes is) :: Constraint, is ~ '[i1, i2], is ~ '[i]) => HasSingleIndex '[i1, i2] i 
Instance details

Defined in Optics.Internal.Indexed

(TypeError ('Text "Use icompose3 to combine indices of type " :<>: ShowTypes is) :: Constraint, is ~ '[i1, i2, i3], is ~ '[i]) => HasSingleIndex '[i1, i2, i3] i 
Instance details

Defined in Optics.Internal.Indexed

(TypeError ('Text "Use icompose4 to combine indices of type " :<>: ShowTypes is) :: Constraint, is ~ '[i1, i2, i3, i4], is ~ '[i]) => HasSingleIndex '[i1, i2, i3, i4] i 
Instance details

Defined in Optics.Internal.Indexed

(TypeError ('Text "Use icompose5 to flatten indices of type " :<>: ShowTypes is) :: Constraint, is ~ '[i1, i2, i3, i4, i5], is ~ '[i]) => HasSingleIndex '[i1, i2, i3, i4, i5] i 
Instance details

Defined in Optics.Internal.Indexed

(TypeError ('Text "Use icomposeN to flatten indices of type " :<>: ShowTypes is) :: Constraint, is ~ (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': (i6 ': is')))))), is ~ '[i]) => HasSingleIndex (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': (i6 ': is')))))) i 
Instance details

Defined in Optics.Internal.Indexed

HasSingleIndex '[i] i 
Instance details

Defined in Optics.Internal.Indexed

class NonEmptyIndices (is :: IxList) #

Check whether a list of indices is not empty and generate sensible error message if it's not.

Instances

Instances details
(TypeError ('Text "Indexed optic is expected") :: Constraint) => NonEmptyIndices ('[] :: [Type]) 
Instance details

Defined in Optics.Internal.Indexed

NonEmptyIndices (x ': xs) 
Instance details

Defined in Optics.Internal.Indexed

class is ~ NoIx => AcceptsEmptyIndices (f :: Symbol) (is :: IxList) #

Show useful error message when a function expects optics without indices.

Instances

Instances details
AcceptsEmptyIndices f ('[] :: [Type]) 
Instance details

Defined in Optics.Internal.Indexed

(TypeError (('Text "\8216" :<>: 'Text f) :<>: 'Text "\8217 accepts only optics with no indices") :: Constraint, (x ': xs) ~ NoIx) => AcceptsEmptyIndices f (x ': xs) 
Instance details

Defined in Optics.Internal.Indexed

conjoined :: forall (is :: IxList) i k s t a b. HasSingleIndex is i => Optic k NoIx s t a b -> Optic k is s t a b -> Optic k is s t a b #

Construct a conjoined indexed optic that provides a separate code path when used without indices. Useful for defining indexed optics that are as efficient as their unindexed equivalents when used without indices.

Note: conjoined f g is well-defined if and only if f ≡ noIx g.

type Getter s a = Optic' A_Getter NoIx s a #

Type synonym for a getter.

view :: forall k (is :: IxList) s a. Is k A_Getter => Optic' k is s a -> s -> a #

View the value pointed to by a getter.

If you want to view a type-modifying optic that is insufficiently polymorphic to be type-preserving, use getting.

views :: forall k (is :: IxList) s a r. Is k A_Getter => Optic' k is s a -> (a -> r) -> s -> r #

View the function of the value pointed to by a getter.

to :: (s -> a) -> Getter s a #

Build a getter from a function.

type AffineTraversalVL' s a = AffineTraversalVL s s a a #

Type synonym for a type-preserving van Laarhoven affine traversal.

type AffineTraversalVL s t a b = forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (a -> f b) -> s -> f t #

Type synonym for a type-modifying van Laarhoven affine traversal.

Note: this isn't exactly van Laarhoven representation as there is no Pointed class (which would be a superclass of Applicative that contains pure but not <*>). You can interpret the first argument as a dictionary of Pointed that supplies the point function (i.e. the implementation of pure).

A TraversalVL has Applicative available and hence can combine the effects arising from multiple elements using <*>. In contrast, an AffineTraversalVL has no way to combine effects from multiple elements, so it must act on at most one element. (It can act on none at all thanks to the availability of point.)

type AffineTraversal' s a = Optic' An_AffineTraversal NoIx s a #

Type synonym for a type-preserving affine traversal.

type AffineTraversal s t a b = Optic An_AffineTraversal NoIx s t a b #

Type synonym for a type-modifying affine traversal.

atraversal :: (s -> Either t a) -> (s -> b -> t) -> AffineTraversal s t a b #

Build an affine traversal from a matcher and an updater.

If you want to build an AffineTraversal from the van Laarhoven representation, use atraversalVL.

withAffineTraversal :: forall k (is :: IxList) s t a b r. Is k An_AffineTraversal => Optic k is s t a b -> ((s -> Either t a) -> (s -> b -> t) -> r) -> r #

Work with an affine traversal as a matcher and an updater.

atraversalVL :: AffineTraversalVL s t a b -> AffineTraversal s t a b #

Build an affine traversal from the van Laarhoven representation.

Example:

>>> :{
azSnd = atraversalVL $ \point f ab@(a, b) ->
  if a >= 'a' && a <= 'z'
  then (a, ) <$> f b
  else point ab
:}
>>> preview azSnd ('a', "Hi")
Just "Hi"
>>> preview azSnd ('@', "Hi")
Nothing
>>> over azSnd (++ "!!!") ('f', "Hi")
('f',"Hi!!!")
>>> set azSnd "Bye" ('Y', "Hi")
('Y',"Hi")

atraverseOf :: forall k f (is :: IxList) s t a b. (Is k An_AffineTraversal, Functor f) => Optic k is s t a b -> (forall r. r -> f r) -> (a -> f b) -> s -> f t #

Traverse over the target of an AffineTraversal and compute a Functor-based answer.

Since: optics-core-0.3

matching :: forall k (is :: IxList) s t a b. Is k An_AffineTraversal => Optic k is s t a b -> s -> Either t a #

Retrieve the value targeted by an AffineTraversal or return the original value while allowing the type to change if it does not match.

preview o ≡ either (const Nothing) id . matching o

unsafeFiltered :: (a -> Bool) -> AffineTraversal' a a #

Filter result(s) of a traversal that don't satisfy a predicate.

Note: This is not a legal Traversal, unless you are very careful not to invalidate the predicate on the target.

As a counter example, consider that given evens = unsafeFiltered even the second Traversal law is violated:

over evens succ . over evens succ /= 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!

For a safe variant see indices (or filtered for read-only optics).

type AffineFold s a = Optic' An_AffineFold NoIx s a #

Type synonym for an affine fold.

afoldVL :: (forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (a -> f u) -> s -> f v) -> AffineFold s a #

Obtain an AffineFold by lifting traverse_ like function.

afoldVL . atraverseOf_id
atraverseOf_ . afoldVLid

Since: optics-core-0.3

preview :: forall k (is :: IxList) s a. Is k An_AffineFold => Optic' k is s a -> s -> Maybe a #

Retrieve the value targeted by an AffineFold.

>>> let _Right = prism Right $ either (Left . Left) Right
>>> preview _Right (Right 'x')
Just 'x'
>>> preview _Right (Left 'y')
Nothing

previews :: forall k (is :: IxList) s a r. Is k An_AffineFold => Optic' k is s a -> (a -> r) -> s -> Maybe r #

Retrieve a function of the value targeted by an AffineFold.

atraverseOf_ :: forall k f (is :: IxList) s a u. (Is k An_AffineFold, Functor f) => Optic' k is s a -> (forall r. r -> f r) -> (a -> f u) -> s -> f () #

Traverse over the target of an AffineFold, computing a Functor-based answer, but unlike atraverseOf do not construct a new structure.

Since: optics-core-0.3

afolding :: (s -> Maybe a) -> AffineFold s a #

Create an AffineFold from a partial function.

>>> preview (afolding listToMaybe) "foo"
Just 'f'

filtered :: (a -> Bool) -> AffineFold a a #

Filter result(s) of a fold that don't satisfy a predicate.

afailing :: forall k l (is :: IxList) s a (js :: IxList). (Is k An_AffineFold, Is l An_AffineFold) => Optic' k is s a -> Optic' l js s a -> AffineFold s a infixl 3 #

Try the first AffineFold. If it returns no entry, try the second one.

>>> preview (ix 1 % re _Left `afailing` ix 2 % re _Right) [0,1,2,3]
Just (Left 1)
>>> preview (ix 42 % re _Left `afailing` ix 2 % re _Right) [0,1,2,3]
Just (Right 2)

isn't :: forall k (is :: IxList) s a. Is k An_AffineFold => Optic' k is s a -> s -> Bool #

Check to see if this AffineFold doesn't match.

>>> isn't _Just Nothing
True

The negation of this operator is is from Optics.Core.Extras.

type Fold s a = Optic' A_Fold NoIx s a #

Type synonym for a fold.

foldVL :: (forall (f :: Type -> Type). Applicative f => (a -> f u) -> s -> f v) -> Fold s a #

Obtain a Fold by lifting traverse_ like function.

foldVL . traverseOf_id
traverseOf_ . foldVLid

foldOf :: forall k a (is :: IxList) s. (Is k A_Fold, Monoid a) => Optic' k is s a -> s -> a #

Combine the results of a fold using a monoid.

foldMapOf :: forall k m (is :: IxList) s a. (Is k A_Fold, Monoid m) => Optic' k is s a -> (a -> m) -> s -> m #

Fold via embedding into a monoid.

foldrOf :: forall k (is :: IxList) s a r. Is k A_Fold => Optic' k is s a -> (a -> r -> r) -> r -> s -> r #

Fold right-associatively.

foldlOf' :: forall k (is :: IxList) s a r. Is k A_Fold => Optic' k is s a -> (r -> a -> r) -> r -> s -> r #

Fold left-associatively, and strictly.

toListOf :: forall k (is :: IxList) s a. Is k A_Fold => Optic' k is s a -> s -> [a] #

Fold to a list.

>>> toListOf (_1 % folded % _Right) ([Right 'h', Left 5, Right 'i'], "bye")
"hi"

traverseOf_ :: forall k f (is :: IxList) s a r. (Is k A_Fold, Applicative f) => Optic' k is s a -> (a -> f r) -> s -> f () #

Traverse over all of the targets of a Fold, computing an Applicative-based answer, but unlike traverseOf do not construct a new structure. traverseOf_ generalizes traverse_ to work over any Fold.

>>> traverseOf_ each putStrLn ("hello","world")
hello
world
traverse_traverseOf_ folded

forOf_ :: forall k f (is :: IxList) s a r. (Is k A_Fold, Applicative f) => Optic' k is s a -> s -> (a -> f r) -> f () #

A version of traverseOf_ with the arguments flipped.

sequenceOf_ :: forall k f (is :: IxList) s a. (Is k A_Fold, Applicative f) => Optic' k is s (f a) -> s -> f () #

Evaluate each action in a structure observed by a Fold from left to right, ignoring the results.

sequenceA_sequenceOf_ folded
>>> sequenceOf_ each (putStrLn "hello",putStrLn "world")
hello
world

folded :: Foldable f => Fold (f a) a #

Fold via the Foldable class.

folding :: Foldable f => (s -> f a) -> Fold s a #

Obtain a Fold by lifting an operation that returns a Foldable result.

This can be useful to lift operations from Data.List and elsewhere into a Fold.

>>> toListOf (folding tail) [1,2,3,4]
[2,3,4]

foldring :: (forall (f :: Type -> Type). Applicative f => (a -> f u -> f u) -> f v -> s -> f w) -> Fold s a #

Obtain a Fold by lifting foldr like function.

>>> toListOf (foldring foldr) [1,2,3,4]
[1,2,3,4]

unfolded :: (s -> Maybe (a, s)) -> Fold s a #

Build a Fold that unfolds its values from a seed.

unfoldrtoListOf . unfolded
>>> toListOf (unfolded $ \b -> if b == 0 then Nothing else Just (b, b - 1)) 10
[10,9,8,7,6,5,4,3,2,1]

pre :: forall k (is :: IxList) s a. Is k A_Fold => Optic' k is s a -> AffineFold s a #

Convert a fold to an AffineFold that visits the first element of the original fold.

For the traversal version see singular.

backwards_ :: forall k (is :: IxList) s a. Is k A_Fold => Optic' k is s a -> Fold s a #

This allows you to traverse the elements of a Fold in the opposite order.

summing :: forall k l (is :: IxList) s a (js :: IxList). (Is k A_Fold, Is l A_Fold) => Optic' k is s a -> Optic' l js s a -> Fold s a infixr 6 #

Return entries of the first Fold, then the second one.

>>> toListOf (_1 % ix 0 `summing` _2 % ix 1) ([1,2], [4,7,1])
[1,7]

For the traversal version see adjoin.

failing :: forall k l (is :: IxList) s a (js :: IxList). (Is k A_Fold, Is l A_Fold) => Optic' k is s a -> Optic' l js s a -> Fold s a infixl 3 #

Try the first Fold. If it returns no entries, try the second one.

>>> toListOf (ix 1 `failing` ix 0) [4,7]
[7]
>>> toListOf (ix 1 `failing` ix 0) [4]
[4]

has :: forall k (is :: IxList) s a. Is k A_Fold => Optic' k is s a -> s -> Bool #

Check to see if this optic matches 1 or more entries.

>>> 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

hasn't :: forall k (is :: IxList) s a. Is k A_Fold => Optic' k is s a -> s -> Bool #

Check to see if this Fold or Traversal has no matches.

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

headOf :: forall k (is :: IxList) s a. Is k A_Fold => Optic' k is s a -> s -> Maybe a #

Retrieve the first entry of a Fold.

>>> headOf folded [1..10]
Just 1
>>> headOf each (1,2)
Just 1

lastOf :: forall k (is :: IxList) s a. Is k A_Fold => Optic' k is s a -> s -> Maybe a #

Retrieve the last entry of a Fold.

>>> lastOf folded [1..10]
Just 10
>>> lastOf each (1,2)
Just 2

andOf :: forall k (is :: IxList) s. Is k A_Fold => Optic' k is s Bool -> s -> Bool #

Returns True if every target of a Fold is True.

>>> andOf each (True, False)
False
>>> andOf each (True, True)
True
andandOf folded

orOf :: forall k (is :: IxList) s. Is k A_Fold => Optic' k is s Bool -> s -> Bool #

Returns True if any target of a Fold is True.

>>> orOf each (True, False)
True
>>> orOf each (False, False)
False
ororOf folded

anyOf :: forall k (is :: IxList) s a. Is k A_Fold => Optic' k is s a -> (a -> Bool) -> s -> Bool #

Returns True if any target of a Fold satisfies a predicate.

>>> anyOf each (=='x') ('x','y')
True

allOf :: forall k (is :: IxList) s a. Is k A_Fold => Optic' k is s a -> (a -> Bool) -> s -> Bool #

Returns True if every target of a Fold satisfies a predicate.

>>> allOf each (>=3) (4,5)
True
>>> allOf folded (>=2) [1..10]
False
allallOf folded

noneOf :: forall k (is :: IxList) s a. Is k A_Fold => Optic' k is s a -> (a -> Bool) -> s -> Bool #

Returns True only if no targets of a Fold satisfy a predicate.

>>> noneOf each (not . isn't _Nothing) (Just 3, Just 4, Just 5)
True
>>> noneOf (folded % folded) (<10) [[13,99,20],[3,71,42]]
False

productOf :: forall k a (is :: IxList) s. (Is k A_Fold, Num a) => Optic' k is s a -> s -> a #

Calculate the Product of every number targeted by a Fold.

>>> productOf each (4,5)
20
>>> productOf folded [1,2,3,4,5]
120
productproductOf folded

This operation may be more strict than you would expect. If you want a lazier version use \o -> getProduct . foldMapOf o Product.

sumOf :: forall k a (is :: IxList) s. (Is k A_Fold, Num a) => Optic' k is s a -> s -> a #

Calculate the Sum of every number targeted by a Fold.

>>> sumOf each (5,6)
11
>>> sumOf folded [1,2,3,4]
10
>>> sumOf (folded % each) [(1,2),(3,4)]
10
sumsumOf folded

This operation may be more strict than you would expect. If you want a lazier version use \o -> getSum . foldMapOf o Sum

asumOf :: forall k f (is :: IxList) s a. (Is k A_Fold, Alternative f) => Optic' k is s (f a) -> s -> f a #

The sum of a collection of actions.

>>> asumOf each ("hello","world")
"helloworld"
>>> asumOf each (Nothing, Just "hello", Nothing)
Just "hello"
asumasumOf folded

msumOf :: forall k m (is :: IxList) s a. (Is k A_Fold, MonadPlus m) => Optic' k is s (m a) -> s -> m a #

The sum of a collection of actions.

>>> msumOf each ("hello","world")
"helloworld"
>>> msumOf each (Nothing, Just "hello", Nothing)
Just "hello"
msummsumOf folded

elemOf :: forall k a (is :: IxList) s. (Is k A_Fold, Eq a) => Optic' k is s a -> a -> s -> Bool #

Does the element occur anywhere within a given Fold of the structure?

>>> elemOf each "hello" ("hello","world")
True
elemelemOf folded

notElemOf :: forall k a (is :: IxList) s. (Is k A_Fold, Eq a) => Optic' k is s a -> a -> s -> Bool #

Does the element not occur anywhere within a given Fold of the structure?

>>> notElemOf each 'd' ('a','b','c')
True
>>> notElemOf each 'a' ('a','b','c')
False
notElemnotElemOf folded

lengthOf :: forall k (is :: IxList) s a. Is k A_Fold => Optic' k is s a -> s -> Int #

Calculate the number of targets there are for a Fold in a given container.

Note: This can be rather inefficient for large containers and just like length, this will not terminate for infinite folds.

lengthlengthOf folded
>>> lengthOf _1 ("hello",())
1
>>> lengthOf folded [1..10]
10
>>> lengthOf (folded % folded) [[1,2],[3,4],[5,6]]
6

maximumOf :: forall k a (is :: IxList) s. (Is k A_Fold, Ord a) => Optic' k is s a -> s -> Maybe a #

Obtain the maximum element (if any) targeted by a Fold safely.

Note: maximumOf on a valid Iso, Lens or Getter will always return Just a value.

>>> maximumOf folded [1..10]
Just 10
>>> maximumOf folded []
Nothing
>>> maximumOf (folded % filtered even) [1,4,3,6,7,9,2]
Just 6
maximumfromMaybe (error "empty") . maximumOf folded

In the interest of efficiency, This operation has semantics more strict than strictly necessary. \o -> getMax . foldMapOf o Max has lazier semantics but could leak memory.

minimumOf :: forall k a (is :: IxList) s. (Is k A_Fold, Ord a) => Optic' k is s a -> s -> Maybe a #

Obtain the minimum element (if any) targeted by a Fold safely.

Note: minimumOf on a valid Iso, Lens or Getter will always return Just a value.

>>> minimumOf folded [1..10]
Just 1
>>> minimumOf folded []
Nothing
>>> minimumOf (folded % filtered even) [1,4,3,6,7,9,2]
Just 2
minimumfromMaybe (error "empty") . minimumOf folded

In the interest of efficiency, This operation has semantics more strict than strictly necessary. \o -> getMin . foldMapOf o Min has lazier semantics but could leak memory.

maximumByOf :: forall k (is :: IxList) s a. Is k A_Fold => Optic' k is s a -> (a -> a -> Ordering) -> s -> Maybe a #

Obtain the maximum element (if any) targeted by a Fold according to a user supplied Ordering.

>>> maximumByOf folded (compare `on` length) ["mustard","relish","ham"]
Just "mustard"

In the interest of efficiency, This operation has semantics more strict than strictly necessary.

maximumBy cmp ≡ fromMaybe (error "empty") . maximumByOf folded cmp

minimumByOf :: forall k (is :: IxList) s a. Is k A_Fold => Optic' k is s a -> (a -> a -> Ordering) -> s -> Maybe a #

Obtain the minimum element (if any) targeted by a Fold according to a user supplied Ordering.

In the interest of efficiency, This operation has semantics more strict than strictly necessary.

>>> minimumByOf folded (compare `on` length) ["mustard","relish","ham"]
Just "ham"
minimumBy cmp ≡ fromMaybe (error "empty") . minimumByOf folded cmp

findOf :: forall k (is :: IxList) s a. Is k A_Fold => Optic' k is s a -> (a -> Bool) -> s -> Maybe a #

The findOf function takes a Fold, a predicate and a structure and returns the leftmost element of the structure matching the predicate, or Nothing if there is no such element.

>>> findOf each even (1,3,4,6)
Just 4
>>> findOf folded even [1,3,5,7]
Nothing
findfindOf folded

findMOf :: forall k m (is :: IxList) s a. (Is k A_Fold, Monad m) => Optic' k is s a -> (a -> m Bool) -> s -> m (Maybe a) #

The findMOf function takes a Fold, a monadic predicate and a structure and returns in the monad the leftmost element of the structure matching the predicate, or Nothing if there is no such element.

>>> findMOf each (\x -> print ("Checking " ++ show x) >> return (even x)) (1,3,4,6)
"Checking 1"
"Checking 3"
"Checking 4"
Just 4
>>> findMOf each (\x -> print ("Checking " ++ show x) >> return (even x)) (1,3,5,7)
"Checking 1"
"Checking 3"
"Checking 5"
"Checking 7"
Nothing
findMOf folded :: (Monad m, Foldable f) => (a -> m Bool) -> f a -> m (Maybe a)

lookupOf :: forall k a (is :: IxList) s v. (Is k A_Fold, Eq a) => Optic' k is s (a, v) -> a -> s -> Maybe v #

The lookupOf function takes a Fold, a key, and a structure containing key/value pairs. It returns the first value corresponding to the given key. This function generalizes lookup to work on an arbitrary Fold instead of lists.

>>> lookupOf folded 4 [(2, 'a'), (4, 'b'), (4, 'c')]
Just 'b'
>>> lookupOf folded 2 [(2, 'a'), (4, 'b'), (4, 'c')]
Just 'a'

universeOf :: forall k (is :: IxList) a. Is k A_Fold => Optic' k is a a -> a -> [a] #

Given a Fold that knows how to locate immediate children, retrieve all of the transitive descendants of a node, including itself.

Since: optics-core-0.4.1

cosmosOf :: forall k (is :: IxList) a. Is k A_Fold => Optic' k is a a -> Fold a a #

Given a Fold that knows how to locate immediate children, fold all of the transitive descendants of a node, including itself.

Since: optics-core-0.4.1

paraOf :: forall k (is :: IxList) a r. Is k A_Fold => Optic' k is a a -> (a -> [r] -> r) -> a -> r #

Perform a fold-like computation on each value, technically a paramorphism.

Since: optics-core-0.4.1

type IxAffineFold i s a = Optic' An_AffineFold (WithIx i) s a #

Type synonym for an indexed affine fold.

iafoldVL :: (forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (i -> a -> f u) -> s -> f v) -> IxAffineFold i s a #

Obtain an IxAffineFold by lifting itraverse_ like function.

aifoldVL . iatraverseOf_id
aitraverseOf_ . iafoldVLid

Since: optics-core-0.3

ipreview :: forall k (is :: IxList) i s a. (Is k An_AffineFold, HasSingleIndex is i) => Optic' k is s a -> s -> Maybe (i, a) #

Retrieve the value along with its index targeted by an IxAffineFold.

ipreviews :: forall k (is :: IxList) i s a r. (Is k An_AffineFold, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> r) -> s -> Maybe r #

Retrieve a function of the value and its index targeted by an IxAffineFold.

iatraverseOf_ :: forall k f (is :: IxList) i s a u. (Is k An_AffineFold, Functor f, HasSingleIndex is i) => Optic' k is s a -> (forall r. r -> f r) -> (i -> a -> f u) -> s -> f () #

Traverse over the target of an IxAffineFold, computing a Functor-based answer, but unlike iatraverseOf do not construct a new structure.

Since: optics-core-0.3

iafolding :: (s -> Maybe (i, a)) -> IxAffineFold i s a #

Create an IxAffineFold from a partial function.

filteredBy :: forall k (is :: IxList) a i. Is k An_AffineFold => Optic' k is a i -> IxAffineFold i a a #

Obtain a potentially empty IxAffineFold by taking the element from another AffineFold and using it as an index.

Since: optics-core-0.3

iafailing :: forall k l (is1 :: IxList) i (is2 :: IxList) s a. (Is k An_AffineFold, Is l An_AffineFold, HasSingleIndex is1 i, HasSingleIndex is2 i) => Optic' k is1 s a -> Optic' l is2 s a -> IxAffineFold i s a infixl 3 #

Try the first IxAffineFold. If it returns no entry, try the second one.

type IxAffineTraversalVL' i s a = IxAffineTraversalVL i s s a a #

Type synonym for a type-preserving van Laarhoven indexed affine traversal.

type IxAffineTraversalVL i s t a b = forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (i -> a -> f b) -> s -> f t #

Type synonym for a type-modifying van Laarhoven indexed affine traversal.

Note: this isn't exactly van Laarhoven representation as there is no Pointed class (which would be a superclass of Applicative that contains pure but not <*>). You can interpret the first argument as a dictionary of Pointed that supplies the point function (i.e. the implementation of pure).

type IxAffineTraversal' i s a = Optic' An_AffineTraversal (WithIx i) s a #

Type synonym for a type-preserving indexed affine traversal.

type IxAffineTraversal i s t a b = Optic An_AffineTraversal (WithIx i) s t a b #

Type synonym for a type-modifying indexed affine traversal.

iatraversal :: (s -> Either t (i, a)) -> (s -> b -> t) -> IxAffineTraversal i s t a b #

Build an indexed affine traversal from a matcher and an updater.

If you want to build an IxAffineTraversal from the van Laarhoven representation, use iatraversalVL.

iatraversalVL :: IxAffineTraversalVL i s t a b -> IxAffineTraversal i s t a b #

Build an indexed affine traversal from the van Laarhoven representation.

iatraverseOf :: forall k f (is :: IxList) i s t a b. (Is k An_AffineTraversal, Functor f, HasSingleIndex is i) => Optic k is s t a b -> (forall r. r -> f r) -> (i -> a -> f b) -> s -> f t #

Traverse over the target of an IxAffineTraversal and compute a Functor-based answer.

Since: optics-core-0.3

unsafeFilteredBy :: forall k (is :: IxList) a i. Is k An_AffineFold => Optic' k is a i -> IxAffineTraversal' i a a #

Obtain a potentially empty IxAffineTraversal by taking the element from another AffineFold and using it as an index.

  • - Note: This is not a legal IxTraversal, unless you are very careful not to invalidate the predicate on the target (see unsafeFiltered for more details).

Since: optics-core-0.3

ignored :: IxAffineTraversal i s s a b #

This is the trivial empty IxAffineTraversal, i.e. the optic that targets no substructures.

This is the identity element when a Fold, AffineFold, IxFold, IxAffineFold, Traversal or IxTraversal is viewed as a monoid.

>>> 6 & ignored %~ absurd
6

type IxFold i s a = Optic' A_Fold (WithIx i) s a #

Type synonym for an indexed fold.

ifoldVL :: (forall (f :: Type -> Type). Applicative f => (i -> a -> f u) -> s -> f v) -> IxFold i s a #

Obtain an indexed fold by lifting itraverse_ like function.

ifoldVL . itraverseOf_id
itraverseOf_ . ifoldVLid

ifoldMapOf :: forall k m (is :: IxList) i s a. (Is k A_Fold, Monoid m, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> m) -> s -> m #

Fold with index via embedding into a monoid.

ifoldrOf :: forall k (is :: IxList) i s a r. (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> r -> r) -> r -> s -> r #

Fold with index right-associatively.

ifoldlOf' :: forall k (is :: IxList) i s a r. (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> (i -> r -> a -> r) -> r -> s -> r #

Fold with index left-associatively, and strictly.

itoListOf :: forall k (is :: IxList) i s a. (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> s -> [(i, a)] #

Fold with index to a list.

>>> itoListOf (folded % ifolded) ["abc", "def"]
[(0,'a'),(1,'b'),(2,'c'),(0,'d'),(1,'e'),(2,'f')]

Note: currently indexed optics can be used as non-indexed.

>>> toListOf (folded % ifolded) ["abc", "def"]
"abcdef"

itraverseOf_ :: forall k f (is :: IxList) i s a r. (Is k A_Fold, Applicative f, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> f r) -> s -> f () #

Traverse over all of the targets of an IxFold, computing an Applicative-based answer, but unlike itraverseOf do not construct a new structure.

>>> itraverseOf_ each (curry print) ("hello","world")
(0,"hello")
(1,"world")

iforOf_ :: forall k f (is :: IxList) i s a r. (Is k A_Fold, Applicative f, HasSingleIndex is i) => Optic' k is s a -> s -> (i -> a -> f r) -> f () #

A version of itraverseOf_ with the arguments flipped.

ifolded :: FoldableWithIndex i f => IxFold i (f a) a #

Indexed fold via FoldableWithIndex class.

ifolding :: FoldableWithIndex i f => (s -> f a) -> IxFold i s a #

Obtain an IxFold by lifting an operation that returns a FoldableWithIndex result.

This can be useful to lift operations from Data.List and elsewhere into an IxFold.

>>> itoListOf (ifolding words) "how are you"
[(0,"how"),(1,"are"),(2,"you")]

ifoldring :: (forall (f :: Type -> Type). Applicative f => (i -> a -> f u -> f u) -> f v -> s -> f w) -> IxFold i s a #

Obtain an IxFold by lifting ifoldr like function.

>>> itoListOf (ifoldring ifoldr) "hello"
[(0,'h'),(1,'e'),(2,'l'),(3,'l'),(4,'o')]

ipre :: forall k (is :: IxList) i s a. (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> IxAffineFold i s a #

Convert an indexed fold to an IxAffineFold that visits the first element of the original fold.

For the traversal version see isingular.

ifiltered :: forall k (is :: IxList) i a s. (Is k A_Fold, HasSingleIndex is i) => (i -> a -> Bool) -> Optic' k is s a -> IxFold i s a #

Filter results of an IxFold that don't satisfy a predicate.

>>> toListOf (ifolded %& ifiltered (>)) [3,2,1,0]
[1,0]

ibackwards_ :: forall k (is :: IxList) i s a. (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> IxFold i s a #

This allows you to traverse the elements of an IxFold in the opposite order.

isumming :: forall k l (is1 :: IxList) i (is2 :: IxList) s a. (Is k A_Fold, Is l A_Fold, HasSingleIndex is1 i, HasSingleIndex is2 i) => Optic' k is1 s a -> Optic' l is2 s a -> IxFold i s a infixr 6 #

Return entries of the first IxFold, then the second one.

>>> itoListOf (ifolded `isumming` ibackwards_ ifolded) ["a","b"]
[(0,"a"),(1,"b"),(1,"b"),(0,"a")]

For the traversal version see iadjoin.

ifailing :: forall k l (is1 :: IxList) i (is2 :: IxList) s a. (Is k A_Fold, Is l A_Fold, HasSingleIndex is1 i, HasSingleIndex is2 i) => Optic' k is1 s a -> Optic' l is2 s a -> IxFold i s a infixl 3 #

Try the first IxFold. If it returns no entries, try the second one.

>>> itoListOf (_1 % ifolded `ifailing` _2 % ifolded) (["a"], ["b","c"])
[(0,"a")]
>>> itoListOf (_1 % ifolded `ifailing` _2 % ifolded) ([], ["b","c"])
[(0,"b"),(1,"c")]

iheadOf :: forall k (is :: IxList) i s a. (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> s -> Maybe (i, a) #

Retrieve the first entry of an IxFold along with its index.

>>> iheadOf ifolded [1..10]
Just (0,1)

ilastOf :: forall k (is :: IxList) i s a. (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> s -> Maybe (i, a) #

Retrieve the last entry of an IxFold along with its index.

>>> ilastOf ifolded [1..10]
Just (9,10)

ianyOf :: forall k (is :: IxList) i s a. (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool #

Return whether or not any element viewed through an IxFold satisfies a predicate, with access to the i.

When you don't need access to the index then anyOf is more flexible in what it accepts.

anyOf o ≡ ianyOf o . const

iallOf :: forall k (is :: IxList) i s a. (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool #

Return whether or not all elements viewed through an IxFold satisfy a predicate, with access to the i.

When you don't need access to the index then allOf is more flexible in what it accepts.

allOf o ≡ iallOf o . const

inoneOf :: forall k (is :: IxList) i s a. (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool #

Return whether or not none of the elements viewed through an IxFold satisfy a predicate, with access to the i.

When you don't need access to the index then noneOf is more flexible in what it accepts.

noneOf o ≡ inoneOf o . const

ifindOf :: forall k (is :: IxList) i s a. (Is k A_Fold, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> Bool) -> s -> Maybe (i, a) #

The ifindOf function takes an IxFold, a predicate that is also supplied the index, a structure and returns the left-most element of the structure along with its index matching the predicate, or Nothing if there is no such element.

When you don't need access to the index then findOf is more flexible in what it accepts.

ifindMOf :: forall k m (is :: IxList) i s a. (Is k A_Fold, Monad m, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> m Bool) -> s -> m (Maybe (i, a)) #

The ifindMOf function takes an IxFold, a monadic predicate that is also supplied the index, a structure and returns in the monad the left-most element of the structure matching the predicate, or Nothing if there is no such element.

When you don't need access to the index then findMOf is more flexible in what it accepts.

type IxGetter i s a = Optic' A_Getter (WithIx i) s a #

Type synonym for an indexed getter.

ito :: (s -> (i, a)) -> IxGetter i s a #

Build an indexed getter from a function.

>>> iview (ito id) ('i', 'x')
('i','x')

selfIndex :: IxGetter a a a #

Use a value itself as its own index. This is essentially an indexed version of equality.

iview :: forall k (is :: IxList) i s a. (Is k A_Getter, HasSingleIndex is i) => Optic' k is s a -> s -> (i, a) #

View the value pointed to by an indexed getter.

iviews :: forall k (is :: IxList) i s a r. (Is k A_Getter, HasSingleIndex is i) => Optic' k is s a -> (i -> a -> r) -> s -> r #

View the function of the value pointed to by an indexed getter.

type IxLensVL' i s a = IxLensVL i s s a a #

Type synonym for a type-preserving van Laarhoven indexed lens.

type IxLensVL i s t a b = forall (f :: Type -> Type). Functor f => (i -> a -> f b) -> s -> f t #

Type synonym for a type-modifying van Laarhoven indexed lens.

type IxLens' i s a = Optic' A_Lens (WithIx i) s a #

Type synonym for a type-preserving indexed lens.

type IxLens i s t a b = Optic A_Lens (WithIx i) s t a b #

Type synonym for a type-modifying indexed lens.

ilens :: (s -> (i, a)) -> (s -> b -> t) -> IxLens i s t a b #

Build an indexed lens from a getter and a setter.

If you want to build an IxLens from the van Laarhoven representation, use ilensVL.

ilensVL :: IxLensVL i s t a b -> IxLens i s t a b #

Build an indexed lens from the van Laarhoven representation.

toIxLensVL :: forall k (is :: IxList) i s t a b. (Is k A_Lens, HasSingleIndex is i) => Optic k is s t a b -> IxLensVL i s t a b #

Convert an indexed lens to its van Laarhoven representation.

withIxLensVL :: forall k (is :: IxList) i s t a b r. (Is k A_Lens, HasSingleIndex is i) => Optic k is s t a b -> (IxLensVL i s t a b -> r) -> r #

Work with an indexed lens in the van Laarhoven representation.

chosen :: IxLens (Either () ()) (Either a a) (Either b b) a b #

Focus on both sides of an Either.

devoid :: IxLens' i Void a #

There is an indexed field for every type in the Void.

>>> set (mapped % devoid) 1 []
[]
>>> over (_Just % devoid) abs Nothing
Nothing

ifst :: IxLens i (a, i) (b, i) a b #

Indexed _1 with other half of a pair as an index.

See isnd for examples.

Since: optics-core-0.4

isnd :: IxLens i (i, a) (i, b) a b #

Indexed _2 with other half of a pair as an index. Specialized version of itraversed to pairs, which can be IxLens.

>>> iview isnd ('a', True)
('a',True)

That is not possible with itraversed, because it is an IxTraversal.

>>> :t itraversed :: IxTraversal i (i, a) (i, b) a b
itraversed :: IxTraversal i (i, a) (i, b) a b
  :: IxTraversal i (i, a) (i, b) a b

Since: optics-core-0.4

type IxSetter' i s a = Optic' A_Setter (WithIx i) s a #

Type synonym for a type-preserving indexed setter.

type IxSetter i s t a b = Optic A_Setter (WithIx i) s t a b #

Type synonym for a type-modifying indexed setter.

iover :: forall k (is :: IxList) i s t a b. (Is k A_Setter, HasSingleIndex is i) => Optic k is s t a b -> (i -> a -> b) -> s -> t #

Apply an indexed setter as a modifier.

iover' :: forall k (is :: IxList) i s t a b. (Is k A_Setter, HasSingleIndex is i) => Optic k is s t a b -> (i -> a -> b) -> s -> t #

Apply an indexed setter as a modifier, strictly.

iset :: forall k (is :: IxList) i s t a b. (Is k A_Setter, HasSingleIndex is i) => Optic k is s t a b -> (i -> b) -> s -> t #

Apply an indexed setter.

iset o f ≡ iover o (i _ -> f i)

iset' :: forall k (is :: IxList) i s t a b. (Is k A_Setter, HasSingleIndex is i) => Optic k is s t a b -> (i -> b) -> s -> t #

Apply an indexed setter, strictly.

isets :: ((i -> a -> b) -> s -> t) -> IxSetter i s t a b #

Build an indexed setter from a function to modify the element(s).

imapped :: FunctorWithIndex i f => IxSetter i (f a) (f b) a b #

Indexed setter via the FunctorWithIndex class.

iover imappedimap

type LensVL' s a = LensVL s s a a #

Type synonym for a type-preserving van Laarhoven lens.

type LensVL s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t #

Type synonym for a type-modifying van Laarhoven lens.

type Lens' s a = Optic' A_Lens NoIx s a #

Type synonym for a type-preserving lens.

type Lens s t a b = Optic A_Lens NoIx s t a b #

Type synonym for a type-modifying lens.

lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b #

Build a lens from a getter and a setter, which must respect the well-formedness laws.

If you want to build a Lens from the van Laarhoven representation, use lensVL.

withLens :: forall k (is :: IxList) s t a b r. Is k A_Lens => Optic k is s t a b -> ((s -> a) -> (s -> b -> t) -> r) -> r #

Work with a lens as a getter and a setter.

withLens (lens f g) k ≡ k f g

lensVL :: LensVL s t a b -> Lens s t a b #

Build a lens from the van Laarhoven representation.

toLensVL :: forall k (is :: IxList) s t a b. Is k A_Lens => Optic k is s t a b -> LensVL s t a b #

Convert a lens to the van Laarhoven representation.

withLensVL :: forall k (is :: IxList) s t a b r. Is k A_Lens => Optic k is s t a b -> (LensVL s t a b -> r) -> r #

Work with a lens in the van Laarhoven representation.

equality' :: Lens a b a b #

Strict version of equality.

Useful for strictifying optics with lazy (irrefutable) pattern matching by precomposition, e.g.

_1' = equality' % _1

alongside :: forall k l (is :: IxList) s t a b (js :: IxList) s' t' a' b'. (Is k A_Lens, Is l A_Lens) => Optic k is s t a b -> Optic l js s' t' a' b' -> Lens (s, s') (t, t') (a, a') (b, b') #

Make a Lens from two other lenses by executing them on their respective halves of a product.

>>> (Left 'a', Right 'b') ^. alongside chosen chosen
('a','b')
>>> (Left 'a', Right 'b') & alongside chosen chosen .~ ('c','d')
(Left 'c',Right 'd')

united :: Lens' a () #

We can always retrieve a () from any type.

>>> view united "hello"
()
>>> set united () "hello"
"hello"

type Prism' s a = Optic' A_Prism NoIx s a #

Type synonym for a type-preserving prism.

type Prism s t a b = Optic A_Prism NoIx s t a b #

Type synonym for a type-modifying prism.

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

Build a prism from a constructor and a matcher, which must respect the well-formedness laws.

If you want to build a Prism from the van Laarhoven representation, use prismVL from the optics-vl package.

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

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

withPrism :: forall k (is :: IxList) s t a b r. Is k A_Prism => Optic k is s t a b -> ((b -> t) -> (s -> Either t a) -> r) -> r #

Work with a Prism as a constructor and a matcher.

aside :: forall k (is :: IxList) s t a b e. Is k A_Prism => Optic k is s t a b -> Prism (e, s) (e, t) (e, a) (e, b) #

Use a Prism to work over part of a structure.

without :: forall k l (is :: IxList) s t a b u v c d. (Is k A_Prism, Is l A_Prism) => Optic k is s t a b -> Optic l is u v c d -> Prism (Either s u) (Either t v) (Either a c) (Either b d) #

Given a pair of prisms, project sums.

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

below :: forall k f (is :: IxList) s a. (Is k A_Prism, Traversable f) => Optic' k is s a -> Prism' (f s) (f a) #

Lift a Prism through a Traversable functor, giving a Prism that matches only if all the elements of the container match the Prism.

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

This Prism compares for exact equality with a given value.

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

nearly :: a -> (a -> Bool) -> Prism' a () #

This Prism compares for approximate equality with a given value and a predicate for testing, an example where the value is the empty list and the predicate checks that a list is empty (same as _Empty with the AsEmpty list instance):

>>> nearly [] null # ()
[]
>>> [1,2,3,4] ^? nearly [] null
Nothing
nearly [] null :: Prism' [a] ()

To comply with the Prism laws the arguments you supply to nearly a p are somewhat constrained.

We assume p x holds iff x ≡ a. Under that assumption then this is a valid Prism.

This is useful when working with a type where you can test equality for only a subset of its values, and the prism selects such a value.

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

A Prism that matches on the Nothing constructor of Maybe.

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

A Prism that matches on the Just constructor of Maybe.

(%?) :: forall (is :: IxList) (js :: IxList) (ks :: IxList) k k' l m s t u v a b. (AppendIndices is js ks, JoinKinds k A_Prism k', JoinKinds k' l m) => Optic k is s t (Maybe u) (Maybe v) -> Optic l js u v a b -> Optic m ks s t a b infixl 9 #

Shortcut for % _Just %.

Useful for composing lenses of Maybe type.

Since: optics-core-0.4.1

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

A Prism that matches on the Left constructor of Either.

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

A Prism that matches on the Right constructor of Either.

class ReversibleOptic k where #

Class for optics that can be reversed.

Associated Types

type ReversedOptic k = (r :: Type) | r -> k #

Methods

re :: forall (is :: IxList) s t a b. AcceptsEmptyIndices "re" is => Optic k is s t a b -> Optic (ReversedOptic k) is b a t s #

Reverses optics, turning around Iso into Iso, Prism into ReversedPrism (and back), Lens into ReversedLens (and back) and Getter into Review (and back).

Instances

Instances details
ReversibleOptic A_Review 
Instance details

Defined in Optics.Re

Associated Types

type ReversedOptic A_Review = (r :: Type) #

Methods

re :: forall (is :: IxList) s t a b. AcceptsEmptyIndices "re" is => Optic A_Review is s t a b -> Optic (ReversedOptic A_Review) is b a t s #

ReversibleOptic A_ReversedLens 
Instance details

Defined in Optics.Re

Associated Types

type ReversedOptic A_ReversedLens = (r :: Type) #

Methods

re :: forall (is :: IxList) s t a b. AcceptsEmptyIndices "re" is => Optic A_ReversedLens is s t a b -> Optic (ReversedOptic A_ReversedLens) is b a t s #

ReversibleOptic A_Getter 
Instance details

Defined in Optics.Re

Associated Types

type ReversedOptic A_Getter = (r :: Type) #

Methods

re :: forall (is :: IxList) s t a b. AcceptsEmptyIndices "re" is => Optic A_Getter is s t a b -> Optic (ReversedOptic A_Getter) is b a t s #

ReversibleOptic A_ReversedPrism 
Instance details

Defined in Optics.Re

Associated Types

type ReversedOptic A_ReversedPrism = (r :: Type) #

Methods

re :: forall (is :: IxList) s t a b. AcceptsEmptyIndices "re" is => Optic A_ReversedPrism is s t a b -> Optic (ReversedOptic A_ReversedPrism) is b a t s #

ReversibleOptic A_Prism 
Instance details

Defined in Optics.Re

Associated Types

type ReversedOptic A_Prism = (r :: Type) #

Methods

re :: forall (is :: IxList) s t a b. AcceptsEmptyIndices "re" is => Optic A_Prism is s t a b -> Optic (ReversedOptic A_Prism) is b a t s #

ReversibleOptic A_Lens 
Instance details

Defined in Optics.Re

Associated Types

type ReversedOptic A_Lens = (r :: Type) #

Methods

re :: forall (is :: IxList) s t a b. AcceptsEmptyIndices "re" is => Optic A_Lens is s t a b -> Optic (ReversedOptic A_Lens) is b a t s #

ReversibleOptic An_Iso 
Instance details

Defined in Optics.Re

Associated Types

type ReversedOptic An_Iso = (r :: Type) #

Methods

re :: forall (is :: IxList) s t a b. AcceptsEmptyIndices "re" is => Optic An_Iso is s t a b -> Optic (ReversedOptic An_Iso) is b a t s #

type family ReversedOptic k = (r :: Type) | r -> k #

Instances

Instances details
type ReversedOptic A_Review 
Instance details

Defined in Optics.Re

type ReversedOptic A_ReversedLens 
Instance details

Defined in Optics.Re

type ReversedOptic A_Getter 
Instance details

Defined in Optics.Re

type ReversedOptic A_ReversedPrism 
Instance details

Defined in Optics.Re

type ReversedOptic A_Prism 
Instance details

Defined in Optics.Re

type ReversedOptic A_Lens 
Instance details

Defined in Optics.Re

type ReversedOptic An_Iso 
Instance details

Defined in Optics.Re

class ToReadOnly k s t a b where #

Class for read-write optics that have their read-only counterparts.

Associated Types

type ReadOnlyOptic k #

Methods

getting :: forall (is :: IxList). Optic k is s t a b -> Optic' (ReadOnlyOptic k) is s a #

Turn read-write optic into its read-only counterpart (or leave read-only optics as-is).

This is useful when you have an optic :: Optic k is s t a b of read-write kind k such that s, t, a, b are rigid, there is no evidence that s ~ t and a ~ b and you want to pass optic to one of the functions that accept read-only optic kinds.

Example:

>>> let fstIntToChar = _1 :: Lens (Int, r) (Char, r) Int Char
>>> :t view fstIntToChar
...
...Couldn't match type ‘Char’ with ‘Int’
...
>>> :t view (getting fstIntToChar)
view (getting fstIntToChar) :: (Int, r) -> Int

Instances

Instances details
(s ~ t, a ~ b) => ToReadOnly A_Fold s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic A_Fold #

Methods

getting :: forall (is :: IxList). Optic A_Fold is s t a b -> Optic' (ReadOnlyOptic A_Fold) is s a #

(s ~ t, a ~ b) => ToReadOnly An_AffineFold s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic An_AffineFold #

Methods

getting :: forall (is :: IxList). Optic An_AffineFold is s t a b -> Optic' (ReadOnlyOptic An_AffineFold) is s a #

(s ~ t, a ~ b) => ToReadOnly A_Getter s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic A_Getter #

Methods

getting :: forall (is :: IxList). Optic A_Getter is s t a b -> Optic' (ReadOnlyOptic A_Getter) is s a #

ToReadOnly A_ReversedPrism s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic A_ReversedPrism #

Methods

getting :: forall (is :: IxList). Optic A_ReversedPrism is s t a b -> Optic' (ReadOnlyOptic A_ReversedPrism) is s a #

ToReadOnly A_Traversal s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic A_Traversal #

Methods

getting :: forall (is :: IxList). Optic A_Traversal is s t a b -> Optic' (ReadOnlyOptic A_Traversal) is s a #

ToReadOnly An_AffineTraversal s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic An_AffineTraversal #

Methods

getting :: forall (is :: IxList). Optic An_AffineTraversal is s t a b -> Optic' (ReadOnlyOptic An_AffineTraversal) is s a #

ToReadOnly A_Prism s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic A_Prism #

Methods

getting :: forall (is :: IxList). Optic A_Prism is s t a b -> Optic' (ReadOnlyOptic A_Prism) is s a #

ToReadOnly A_Lens s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic A_Lens #

Methods

getting :: forall (is :: IxList). Optic A_Lens is s t a b -> Optic' (ReadOnlyOptic A_Lens) is s a #

ToReadOnly An_Iso s t a b 
Instance details

Defined in Optics.ReadOnly

Associated Types

type ReadOnlyOptic An_Iso #

Methods

getting :: forall (is :: IxList). Optic An_Iso is s t a b -> Optic' (ReadOnlyOptic An_Iso) is s a #

type family ReadOnlyOptic k #

Instances

Instances details
type ReadOnlyOptic A_Fold 
Instance details

Defined in Optics.ReadOnly

type ReadOnlyOptic An_AffineFold 
Instance details

Defined in Optics.ReadOnly

type ReadOnlyOptic A_Getter 
Instance details

Defined in Optics.ReadOnly

type ReadOnlyOptic A_ReversedPrism 
Instance details

Defined in Optics.ReadOnly

type ReadOnlyOptic A_Traversal 
Instance details

Defined in Optics.ReadOnly

type ReadOnlyOptic An_AffineTraversal 
Instance details

Defined in Optics.ReadOnly

type ReadOnlyOptic A_Prism 
Instance details

Defined in Optics.ReadOnly

type ReadOnlyOptic A_Lens 
Instance details

Defined in Optics.ReadOnly

type ReadOnlyOptic An_Iso 
Instance details

Defined in Optics.ReadOnly

type ReversedLens' t b = Optic' A_ReversedLens NoIx t b #

Type synonym for a type-preserving reversed lens.

type ReversedLens s t a b = Optic A_ReversedLens NoIx s t a b #

Type synonym for a type-modifying reversed lens.

type ReversedPrism' s a = Optic' A_ReversedPrism NoIx s a #

Type synonym for a type-preserving reversed prism.

type ReversedPrism s t a b = Optic A_ReversedPrism NoIx s t a b #

Type synonym for a type-modifying reversed prism.

type Review t b = Optic' A_Review NoIx t b #

Type synonym for a review.

review :: forall k (is :: IxList) t b. Is k A_Review => Optic' k is t b -> b -> t #

Retrieve the value targeted by a Review.

>>> review _Left "hi"
Left "hi"

unto :: (b -> t) -> Review t b #

An analogue of to for reviews.

class Bifunctor p => Swapped (p :: Type -> Type -> Type) where #

This class provides for symmetric bifunctors.

Methods

swapped :: Iso (p a b) (p c d) (p b a) (p d c) #

swapped . swappedid
first f . swapped = swapped . second f
second g . swapped = swapped . first g
bimap f g . swapped = swapped . bimap g f
>>> view swapped (1,2)
(2,1)

Instances

Instances details
Swapped Either 
Instance details

Defined in Optics.Iso

Methods

swapped :: Iso (Either a b) (Either c d) (Either b a) (Either d c) #

Swapped (,) 
Instance details

Defined in Optics.Iso

Methods

swapped :: Iso (a, b) (c, d) (b, a) (d, c) #

type Iso' s a = Optic' An_Iso NoIx s a #

Type synonym for a type-preserving iso.

type Iso s t a b = Optic An_Iso NoIx s t a b #

Type synonym for a type-modifying iso.

iso :: (s -> a) -> (b -> t) -> Iso s t a b #

Build an iso from a pair of inverse functions.

If you want to build an Iso from the van Laarhoven representation, use isoVL from the optics-vl package.

withIso :: Iso s t a b -> ((s -> a) -> (b -> t) -> r) -> r #

Extract the two components of an isomorphism.

au :: Functor f => Iso s t a b -> ((b -> t) -> f s) -> f a #

Based on ala from Conor McBride's work on Epigram.

This version is generalized to accept any Iso, not just a newtype.

>>> au (coerced1 @Sum) foldMap [1,2,3,4]
10

You may want to think of this combinator as having the following, simpler type:

au :: Iso s t a b -> ((b -> t) -> e -> s) -> e -> a

under :: Iso s t a b -> (t -> s) -> b -> a #

The opposite of working over a Setter is working under an isomorphism.

underover . re

equality :: (s ~ a, t ~ b) => Iso s t a b #

Capture type constraints as an isomorphism.

Note: This is the identity optic:

>>> :t view equality
view equality :: a -> a

simple :: Iso' a a #

Proof of reflexivity.

coerced :: (Coercible s a, Coercible t b) => Iso s t a b #

Data types that are representationally equal are isomorphic.

>>> view coerced 'x' :: Identity Char
Identity 'x'

coercedTo :: forall a s. Coercible s a => Iso' s a #

Type-preserving version of coerced with type parameters rearranged for TypeApplications.

>>> newtype MkInt = MkInt Int deriving Show
>>> over (coercedTo @Int) (*3) (MkInt 2)
MkInt 6

coerced1 :: forall f s a. (Coercible s (f s), Coercible a (f a)) => Iso (f s) (f a) s a #

Special case of coerced for trivial newtype wrappers.

>>> over (coerced1 @Identity) (++ "bar") (Identity "foo")
Identity "foobar"

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 non v is an isomorphism from Maybe a' to a.

nonnon' . 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 %~ (subtract 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

Since: optics-core-0.2

non' :: Prism' a () -> Iso' (Maybe a) a #

non' p generalizes non (p # ()) to take any unit Prism

This function generates an isomorphism between Maybe (a | isn't p a) and a.

>>> Map.singleton "hello" Map.empty & at "hello" % non' _Empty % at "world" ?~ "!!!"
fromList [("hello",fromList [("world","!!!")])]
>>> Map.fromList [("hello", Map.fromList [("world","!!!")])] & at "hello" % non' _Empty % at "world" .~ Nothing
fromList []

Since: optics-core-0.2

anon :: a -> (a -> Bool) -> Iso' (Maybe a) a #

anon a p generalizes non a to take any value and a predicate.

anon a ≡ non' . nearly a

This function assumes that p a holds True and generates an isomorphism between Maybe (a | not (p a)) and a.

>>> Map.empty & at "hello" % anon Map.empty Map.null % at "world" ?~ "!!!"
fromList [("hello",fromList [("world","!!!")])]
>>> Map.fromList [("hello", Map.fromList [("world","!!!")])] & at "hello" % anon Map.empty Map.null % at "world" .~ Nothing
fromList []

Since: optics-core-0.2

curried :: Iso ((a, b) -> c) ((d, e) -> f) (a -> b -> c) (d -> e -> f) #

The canonical isomorphism for currying and uncurrying a function.

curried = iso curry uncurry
>>> view curried fst 3 4
3

uncurried :: Iso (a -> b -> c) (d -> e -> f) ((a, b) -> c) ((d, e) -> f) #

The canonical isomorphism for uncurrying and currying a function.

uncurried = iso uncurry curry
uncurried = re curried
>>> (view uncurried (+)) (1,2)
3

flipped :: Iso (a -> b -> c) (a' -> b' -> c') (b -> a -> c) (b' -> a' -> c') #

The isomorphism for flipping a function.

>>> (view flipped (,)) 1 2
(2,1)

involuted :: (a -> a) -> Iso' a a #

Given a function that is its own inverse, this gives you an Iso using it in both directions.

involutedjoin iso
>>> "live" ^. involuted reverse
"evil"
>>> "live" & involuted reverse %~ ('d':)
"lived"

class MappingOptic k (f :: Type -> Type) (g :: Type -> Type) s t a b where #

Class for optics supporting mapping through a Functor.

Since: optics-core-0.3

Associated Types

type MappedOptic k #

Type family that maps an optic to the optic kind produced by mapping using it.

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic k is s t a b -> Optic (MappedOptic k) is (f s) (g t) (f a) (g b) #

The mapping can be used to lift optic through a Functor.

mapping :: Iso    s t a b -> Iso    (f s) (g t) (f a) (g b)
mapping :: Lens   s   a   -> Getter (f s)       (f a)
mapping :: Getter s   a   -> Getter (f s)       (f a)
mapping :: Prism    t   b -> Review       (g t)       (g b)
mapping :: Review   t   b -> Review       (g t)       (g b)

Instances

Instances details
(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Review f g s t a b 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_Review #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_Review is s t a b -> Optic (MappedOptic A_Review) is (f s) (g t) (f a) (g b) #

(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_ReversedLens f g s t a b 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_ReversedLens #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_ReversedLens is s t a b -> Optic (MappedOptic A_ReversedLens) is (f s) (g t) (f a) (g b) #

(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Getter f g s t a b
>>> [('a', True), ('b', False)] ^. _1 %& mapping
"ab"
>>> let v = [[ (('a', True), "foo"), (('b', False), "bar")], [ (('c', True), "xyz") ] ]
>>> v ^. _1 % _2 %& mapping %& mapping
[[True,False],[True]]
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_Getter #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_Getter is s t a b -> Optic (MappedOptic A_Getter) is (f s) (g t) (f a) (g b) #

(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_ReversedPrism f g s t a b 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_ReversedPrism #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_ReversedPrism is s t a b -> Optic (MappedOptic A_ReversedPrism) is (f s) (g t) (f a) (g b) #

(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Prism f g s t a b 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_Prism #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_Prism is s t a b -> Optic (MappedOptic A_Prism) is (f s) (g t) (f a) (g b) #

(Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Lens f g s t a b 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic A_Lens #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic A_Lens is s t a b -> Optic (MappedOptic A_Lens) is (f s) (g t) (f a) (g b) #

(Functor f, Functor g) => MappingOptic An_Iso f g s t a b 
Instance details

Defined in Optics.Mapping

Associated Types

type MappedOptic An_Iso #

Methods

mapping :: forall (is :: IxList). AcceptsEmptyIndices "mapping" is => Optic An_Iso is s t a b -> Optic (MappedOptic An_Iso) is (f s) (g t) (f a) (g b) #

type family MappedOptic k #

Type family that maps an optic to the optic kind produced by mapping using it.

Instances

Instances details
type MappedOptic A_Review 
Instance details

Defined in Optics.Mapping

type MappedOptic A_ReversedLens 
Instance details

Defined in Optics.Mapping

type MappedOptic A_Getter 
Instance details

Defined in Optics.Mapping

type MappedOptic A_ReversedPrism 
Instance details

Defined in Optics.Mapping

type MappedOptic A_Prism 
Instance details

Defined in Optics.Mapping

type MappedOptic A_Lens 
Instance details

Defined in Optics.Mapping

type MappedOptic An_Iso 
Instance details

Defined in Optics.Mapping

class AsEmpty a where #

Class for types that may be _Empty.

Minimal complete definition

Nothing

Methods

_Empty :: Prism' a () #

>>> isn't _Empty [1,2,3]
True

Instances

Instances details
AsEmpty Ordering 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' Ordering () #

AsEmpty () 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' () () #

AsEmpty Event 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' Event () #

AsEmpty All 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' All () #

AsEmpty Any 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' Any () #

AsEmpty IntSet 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' IntSet () #

AsEmpty [a] 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' [a] () #

AsEmpty (Maybe a) 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' (Maybe a) () #

AsEmpty (ZipList a) 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' (ZipList a) () #

AsEmpty (First a) 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' (First a) () #

AsEmpty (Last a) 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' (Last a) () #

AsEmpty a => AsEmpty (Dual a) 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' (Dual a) () #

(Eq a, Num a) => AsEmpty (Sum a) 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' (Sum a) () #

(Eq a, Num a) => AsEmpty (Product a) 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' (Product a) () #

AsEmpty (IntMap a) 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' (IntMap a) () #

AsEmpty (Seq a) 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' (Seq a) () #

AsEmpty (Set a) 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' (Set a) () #

(AsEmpty a, AsEmpty b) => AsEmpty (a, b) 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' (a, b) () #

AsEmpty (Map k a) 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' (Map k a) () #

(AsEmpty a, AsEmpty b, AsEmpty c) => AsEmpty (a, b, c) 
Instance details

Defined in Optics.Empty.Core

Methods

_Empty :: Prism' (a, b, c) () #

pattern Empty :: AsEmpty a => a #

Pattern synonym for matching on any type with an AsEmpty instance.

>>> case Nothing of { Empty -> True; _ -> False }
True

type Setter' s a = Optic' A_Setter NoIx s a #

Type synonym for a type-preserving setter.

type Setter s t a b = Optic A_Setter NoIx s t a b #

Type synonym for a type-modifying setter.

over :: forall k (is :: IxList) s t a b. Is k A_Setter => Optic k is s t a b -> (a -> b) -> s -> t #

Apply a setter as a modifier.

over' :: forall k (is :: IxList) s t a b. Is k A_Setter => Optic k is s t a b -> (a -> b) -> s -> t #

Apply a setter as a modifier, strictly.

TODO DOC: what exactly is the strictness property?

Example:

 f :: Int -> (Int, a) -> (Int, a)
 f k acc
   | k > 0     = f (k - 1) $ over' _1 (+1) acc
   | otherwise = acc

runs in constant space, but would result in a space leak if used with over.

Note that replacing $ with $! or _1 with _1' (which amount to the same thing) doesn't help when over is used, because the first coordinate of a pair is never forced.

set :: forall k (is :: IxList) s t a b. Is k A_Setter => Optic k is s t a b -> b -> s -> t #

Apply a setter.

set o v ≡ over o (const v)
>>> set _1 'x' ('y', 'z')
('x','z')

set' :: forall k (is :: IxList) s t a b. Is k A_Setter => Optic k is s t a b -> b -> s -> t #

Apply a setter, strictly.

TODO DOC: what exactly is the strictness property?

sets :: ((a -> b) -> s -> t) -> Setter s t a b #

Build a setter from a function to modify the element(s), which must respect the well-formedness laws.

mapped :: Functor f => Setter (f a) (f b) a b #

Create a Setter for a Functor.

over mappedfmap

rewriteOf :: forall k (is :: IxList) a b. Is k A_Setter => Optic k is a b a b -> (b -> Maybe a) -> a -> b #

Rewrite by applying a rule everywhere you can. Ensures that the rule cannot be applied anywhere in the result:

propRewriteOf l r x = all (isNothing . r) (universeOf l (rewriteOf l r x))

Usually transformOf is more appropriate, but rewriteOf can give better compositionality. Given two single transformations f and g, you can construct \a -> f a <|> g a which performs both rewrites until a fixed point.

Since: optics-core-0.4.1

transformOf :: forall k (is :: IxList) a b. Is k A_Setter => Optic k is a b a b -> (b -> b) -> a -> b #

Transform every element by recursively applying a given Setter in a bottom-up manner.

Since: optics-core-0.4.1

(^.) :: forall k s (is :: IxList) a. Is k A_Getter => s -> Optic' k is s a -> a infixl 8 #

Flipped infix version of view.

(^?) :: forall k s (is :: IxList) a. Is k An_AffineFold => s -> Optic' k is s a -> Maybe a infixl 8 #

Flipped infix version of preview.

(^..) :: forall k s (is :: IxList) a. Is k A_Fold => s -> Optic' k is s a -> [a] infixl 8 #

Flipped infix version of toListOf.

(#) :: forall k (is :: IxList) t b. Is k A_Review => Optic' k is t b -> b -> t infixr 8 #

Infix version of review.

(%~) :: forall k (is :: IxList) s t a b. Is k A_Setter => Optic k is s t a b -> (a -> b) -> s -> t infixr 4 #

Infix version of over.

(%!~) :: forall k (is :: IxList) s t a b. Is k A_Setter => Optic k is s t a b -> (a -> b) -> s -> t infixr 4 #

Infix version of over'.

(.~) :: forall k (is :: IxList) s t a b. Is k A_Setter => Optic k is s t a b -> b -> s -> t infixr 4 #

Infix version of set.

(!~) :: forall k (is :: IxList) s t a b. Is k A_Setter => Optic k is s t a b -> b -> s -> t infixr 4 #

Infix version of set'.

(?~) :: forall k (is :: IxList) s t a b. Is k A_Setter => Optic k is s t a (Maybe b) -> b -> s -> t infixr 4 #

Set the target of a Setter to Just a value.

o ?~ b ≡ set o (Just b)
>>> Nothing & equality ?~ 'x'
Just 'x'
>>> Map.empty & at 3 ?~ 'x'
fromList [(3,'x')]

(?!~) :: forall k (is :: IxList) s t a b. Is k A_Setter => Optic k is s t a (Maybe b) -> b -> s -> t infixr 4 #

Strict version of (?~).

class (Ixed m, IxKind m ~ An_AffineTraversal) => At m where #

At provides a Lens that can be used to read, write or delete the value associated with a key in a Map-like container on an ad hoc basis.

An instance of At should satisfy:

ix k ≡ at k % _Just

Methods

at :: Index m -> Lens' m (Maybe (IxValue m)) #

>>> Map.fromList [(1,"world")] ^. at 1
Just "world"
>>> at 1 ?~ "hello" $ Map.empty
fromList [(1,"hello")]

Note: Usage of this function might introduce space leaks if you're not careful to make sure that values put inside the Just constructor are evaluated. To force the values and avoid such leaks, use at' instead.

Note: Map-like containers form a reasonable instance, but not Array-like ones, where you cannot satisfy the Lens laws.

Instances

Instances details
At IntSet 
Instance details

Defined in Optics.At.Core

At (Maybe a) 
Instance details

Defined in Optics.At.Core

Methods

at :: Index (Maybe a) -> Lens' (Maybe a) (Maybe (IxValue (Maybe a))) #

At (IntMap a) 
Instance details

Defined in Optics.At.Core

Methods

at :: Index (IntMap a) -> Lens' (IntMap a) (Maybe (IxValue (IntMap a))) #

Ord k => At (Set k) 
Instance details

Defined in Optics.At.Core

Methods

at :: Index (Set k) -> Lens' (Set k) (Maybe (IxValue (Set k))) #

Ord k => At (Map k a) 
Instance details

Defined in Optics.At.Core

Methods

at :: Index (Map k a) -> Lens' (Map k a) (Maybe (IxValue (Map k a))) #

class Ixed m where #

Provides a simple AffineTraversal lets you traverse the value at a given key in a Map or element at an ordinal position in a list or Seq.

Minimal complete definition

Nothing

Associated Types

type IxKind m #

Type family that takes a key-value container type and returns the kind of optic to index into it. For most containers, it's An_AffineTraversal, Representable (Naperian) containers it is A_Lens, and multi-maps would have A_Traversal.

Methods

ix :: Index m -> Optic' (IxKind m) NoIx m (IxValue m) #

NB: Setting the value of this AffineTraversal will only set the value in at if it is already present.

If you want to be able to insert missing values, you want at.

>>> [1,2,3,4] & ix 2 %~ (*10)
[1,2,30,4]
>>> "abcd" & ix 2 .~ 'e'
"abed"
>>> "abcd" ^? ix 2
Just 'c'
>>> [] ^? ix 2
Nothing

Instances

Instances details
Ixed IntSet 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind IntSet #

Ixed [a] 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind [a] #

Methods

ix :: Index [a] -> Optic' (IxKind [a]) NoIx [a] (IxValue [a]) #

Ixed (Maybe a) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (Maybe a) #

Methods

ix :: Index (Maybe a) -> Optic' (IxKind (Maybe a)) NoIx (Maybe a) (IxValue (Maybe a)) #

Ixed (Identity a) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (Identity a) #

Methods

ix :: Index (Identity a) -> Optic' (IxKind (Identity a)) NoIx (Identity a) (IxValue (Identity a)) #

Ixed (NonEmpty a) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (NonEmpty a) #

Methods

ix :: Index (NonEmpty a) -> Optic' (IxKind (NonEmpty a)) NoIx (NonEmpty a) (IxValue (NonEmpty a)) #

Ixed (IntMap a) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (IntMap a) #

Methods

ix :: Index (IntMap a) -> Optic' (IxKind (IntMap a)) NoIx (IntMap a) (IxValue (IntMap a)) #

Ixed (Tree a) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (Tree a) #

Methods

ix :: Index (Tree a) -> Optic' (IxKind (Tree a)) NoIx (Tree a) (IxValue (Tree a)) #

Ixed (Seq a) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (Seq a) #

Methods

ix :: Index (Seq a) -> Optic' (IxKind (Seq a)) NoIx (Seq a) (IxValue (Seq a)) #

Ord k => Ixed (Set k) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (Set k) #

Methods

ix :: Index (Set k) -> Optic' (IxKind (Set k)) NoIx (Set k) (IxValue (Set k)) #

Eq e => Ixed (e -> a) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (e -> a) #

Methods

ix :: Index (e -> a) -> Optic' (IxKind (e -> a)) NoIx (e -> a) (IxValue (e -> a)) #

a0 ~ a1 => Ixed (a0, a1) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (a0, a1) #

Methods

ix :: Index (a0, a1) -> Optic' (IxKind (a0, a1)) NoIx (a0, a1) (IxValue (a0, a1)) #

(IArray UArray e, Ix i) => Ixed (UArray i e)
arr ! i ≡ arr ^. ix i
arr // [(i,e)] ≡ ix i .~ e $ arr
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (UArray i e) #

Methods

ix :: Index (UArray i e) -> Optic' (IxKind (UArray i e)) NoIx (UArray i e) (IxValue (UArray i e)) #

Ix i => Ixed (Array i e)
arr ! i ≡ arr ^. ix i
arr // [(i,e)] ≡ ix i .~ e $ arr
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (Array i e) #

Methods

ix :: Index (Array i e) -> Optic' (IxKind (Array i e)) NoIx (Array i e) (IxValue (Array i e)) #

Ord k => Ixed (Map k a) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (Map k a) #

Methods

ix :: Index (Map k a) -> Optic' (IxKind (Map k a)) NoIx (Map k a) (IxValue (Map k a)) #

(a0 ~ a1, a0 ~ a2) => Ixed (a0, a1, a2) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (a0, a1, a2) #

Methods

ix :: Index (a0, a1, a2) -> Optic' (IxKind (a0, a1, a2)) NoIx (a0, a1, a2) (IxValue (a0, a1, a2)) #

(a0 ~ a1, a0 ~ a2, a0 ~ a3) => Ixed (a0, a1, a2, a3) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (a0, a1, a2, a3) #

Methods

ix :: Index (a0, a1, a2, a3) -> Optic' (IxKind (a0, a1, a2, a3)) NoIx (a0, a1, a2, a3) (IxValue (a0, a1, a2, a3)) #

(a0 ~ a1, a0 ~ a2, a0 ~ a3, a0 ~ a4) => Ixed (a0, a1, a2, a3, a4) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (a0, a1, a2, a3, a4) #

Methods

ix :: Index (a0, a1, a2, a3, a4) -> Optic' (IxKind (a0, a1, a2, a3, a4)) NoIx (a0, a1, a2, a3, a4) (IxValue (a0, a1, a2, a3, a4)) #

(a0 ~ a1, a0 ~ a2, a0 ~ a3, a0 ~ a4, a0 ~ a5) => Ixed (a0, a1, a2, a3, a4, a5) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (a0, a1, a2, a3, a4, a5) #

Methods

ix :: Index (a0, a1, a2, a3, a4, a5) -> Optic' (IxKind (a0, a1, a2, a3, a4, a5)) NoIx (a0, a1, a2, a3, a4, a5) (IxValue (a0, a1, a2, a3, a4, a5)) #

(a0 ~ a1, a0 ~ a2, a0 ~ a3, a0 ~ a4, a0 ~ a5, a0 ~ a6) => Ixed (a0, a1, a2, a3, a4, a5, a6) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (a0, a1, a2, a3, a4, a5, a6) #

Methods

ix :: Index (a0, a1, a2, a3, a4, a5, a6) -> Optic' (IxKind (a0, a1, a2, a3, a4, a5, a6)) NoIx (a0, a1, a2, a3, a4, a5, a6) (IxValue (a0, a1, a2, a3, a4, a5, a6)) #

(a0 ~ a1, a0 ~ a2, a0 ~ a3, a0 ~ a4, a0 ~ a5, a0 ~ a6, a0 ~ a7) => Ixed (a0, a1, a2, a3, a4, a5, a6, a7) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (a0, a1, a2, a3, a4, a5, a6, a7) #

Methods

ix :: Index (a0, a1, a2, a3, a4, a5, a6, a7) -> Optic' (IxKind (a0, a1, a2, a3, a4, a5, a6, a7)) NoIx (a0, a1, a2, a3, a4, a5, a6, a7) (IxValue (a0, a1, a2, a3, a4, a5, a6, a7)) #

(a0 ~ a1, a0 ~ a2, a0 ~ a3, a0 ~ a4, a0 ~ a5, a0 ~ a6, a0 ~ a7, a0 ~ a8) => Ixed (a0, a1, a2, a3, a4, a5, a6, a7, a8) 
Instance details

Defined in Optics.At.Core

Associated Types

type IxKind (a0, a1, a2, a3, a4, a5, a6, a7, a8) #

Methods

ix :: Index (a0, a1, a2, a3, a4, a5, a6, a7, a8) -> Optic' (IxKind (a0, a1, a2, a3, a4, a5, a6, a7, a8)) NoIx (a0, a1, a2, a3, a4, a5, a6, a7, a8) (IxValue (a0, a1, a2, a3, a4, a5, a6, a7, a8)) #

type family IxKind m #

Type family that takes a key-value container type and returns the kind of optic to index into it. For most containers, it's An_AffineTraversal, Representable (Naperian) containers it is A_Lens, and multi-maps would have A_Traversal.

Instances

Instances details
type IxKind ByteString 
Instance details

Defined in Optics.At

type IxKind ByteString 
Instance details

Defined in Optics.At

type IxKind IntSet 
Instance details

Defined in Optics.At.Core

type IxKind Text 
Instance details

Defined in Optics.At

type IxKind Text 
Instance details

Defined in Optics.At

type IxKind [a] 
Instance details

Defined in Optics.At.Core

type IxKind (Maybe a) 
Instance details

Defined in Optics.At.Core

type IxKind (Identity a) 
Instance details

Defined in Optics.At.Core

type IxKind (NonEmpty a) 
Instance details

Defined in Optics.At.Core

type IxKind (IntMap a) 
Instance details

Defined in Optics.At.Core

type IxKind (Tree a) 
Instance details

Defined in Optics.At.Core

type IxKind (Seq a) 
Instance details

Defined in Optics.At.Core

type IxKind (Set k) 
Instance details

Defined in Optics.At.Core

type IxKind (Vector a) 
Instance details

Defined in Optics.At

type IxKind (Vector a) 
Instance details

Defined in Optics.At

type IxKind (Vector a) 
Instance details

Defined in Optics.At

type IxKind (HashSet k) 
Instance details

Defined in Optics.At

type IxKind (Vector a) 
Instance details

Defined in Optics.At

type IxKind (e -> a) 
Instance details

Defined in Optics.At.Core

type IxKind (e -> a) = A_Lens
type IxKind (a0, a1) 
Instance details

Defined in Optics.At.Core

type IxKind (a0, a1) = An_AffineTraversal
type IxKind (UArray i e) 
Instance details

Defined in Optics.At.Core

type IxKind (Array i e) 
Instance details

Defined in Optics.At.Core

type IxKind (Map k a) 
Instance details

Defined in Optics.At.Core

type IxKind (HashMap k a) 
Instance details

Defined in Optics.At

type IxKind (a0, a1, a2) 
Instance details

Defined in Optics.At.Core

type IxKind (a0, a1, a2) = An_AffineTraversal
type IxKind (a0, a1, a2, a3) 
Instance details

Defined in Optics.At.Core

type IxKind (a0, a1, a2, a3) = An_AffineTraversal
type IxKind (a0, a1, a2, a3, a4) 
Instance details

Defined in Optics.At.Core

type IxKind (a0, a1, a2, a3, a4) = An_AffineTraversal
type IxKind (a0, a1, a2, a3, a4, a5) 
Instance details

Defined in Optics.At.Core

type IxKind (a0, a1, a2, a3, a4, a5) = An_AffineTraversal
type IxKind (a0, a1, a2, a3, a4, a5, a6) 
Instance details

Defined in Optics.At.Core

type IxKind (a0, a1, a2, a3, a4, a5, a6) = An_AffineTraversal
type IxKind (a0, a1, a2, a3, a4, a5, a6, a7) 
Instance details

Defined in Optics.At.Core

type IxKind (a0, a1, a2, a3, a4, a5, a6, a7) = An_AffineTraversal
type IxKind (a0, a1, a2, a3, a4, a5, a6, a7, a8) 
Instance details

Defined in Optics.At.Core

type IxKind (a0, a1, a2, a3, a4, a5, a6, a7, a8) = An_AffineTraversal

type family IxValue m #

Type family that takes a key-value container type and returns the type of values stored in the container, for example IxValue (Map k a) ~ a. This is shared by both Ixed and At.

Instances

Instances details
type IxValue ByteString 
Instance details

Defined in Optics.At

type IxValue ByteString 
Instance details

Defined in Optics.At

type IxValue IntSet 
Instance details

Defined in Optics.At.Core

type IxValue IntSet = ()
type IxValue Text 
Instance details

Defined in Optics.At

type IxValue Text 
Instance details

Defined in Optics.At

type IxValue [a] 
Instance details

Defined in Optics.At.Core

type IxValue [a] = a
type IxValue (Maybe a) 
Instance details

Defined in Optics.At.Core

type IxValue (Maybe a) = a
type IxValue (Identity a) 
Instance details

Defined in Optics.At.Core

type IxValue (Identity a) = a
type IxValue (NonEmpty a) 
Instance details

Defined in Optics.At.Core

type IxValue (NonEmpty a) = a
type IxValue (IntMap a) 
Instance details

Defined in Optics.At.Core

type IxValue (IntMap a) = a
type IxValue (Tree a) 
Instance details

Defined in Optics.At.Core

type IxValue (Tree a) = a
type IxValue (Seq a) 
Instance details

Defined in Optics.At.Core

type IxValue (Seq a) = a
type IxValue (Set k) 
Instance details

Defined in Optics.At.Core

type IxValue (Set k) = ()
type IxValue (Vector a) 
Instance details

Defined in Optics.At

type IxValue (Vector a) = a
type IxValue (Vector a) 
Instance details

Defined in Optics.At

type IxValue (Vector a) = a
type IxValue (Vector a) 
Instance details

Defined in Optics.At

type IxValue (Vector a) = a
type IxValue (HashSet k) 
Instance details

Defined in Optics.At

type IxValue (HashSet k) = ()
type IxValue (Vector a) 
Instance details

Defined in Optics.At

type IxValue (Vector a) = a
type IxValue (e -> a) 
Instance details

Defined in Optics.At.Core

type IxValue (e -> a) = a
type IxValue (a0, a2)
ix :: Int -> AffineTraversal' (a, a) a
Instance details

Defined in Optics.At.Core

type IxValue (a0, a2) = a0
type IxValue (UArray i e) 
Instance details

Defined in Optics.At.Core

type IxValue (UArray i e) = e
type IxValue (Array i e) 
Instance details

Defined in Optics.At.Core

type IxValue (Array i e) = e
type IxValue (Map k a) 
Instance details

Defined in Optics.At.Core

type IxValue (Map k a) = a
type IxValue (HashMap k a) 
Instance details

Defined in Optics.At

type IxValue (HashMap k a) = a
type IxValue (a0, a1, a2)
ix :: Int -> AffineTraversal' (a, a, a) a
Instance details

Defined in Optics.At.Core

type IxValue (a0, a1, a2) = a0
type IxValue (a0, a1, a2, a3)
ix :: Int -> AffineTraversal' (a, a, a, a) a
Instance details

Defined in Optics.At.Core

type IxValue (a0, a1, a2, a3) = a0
type IxValue (a0, a1, a2, a3, a4)
ix :: Int -> AffineTraversal' (a, a, a, a, a) a
Instance details

Defined in Optics.At.Core

type IxValue (a0, a1, a2, a3, a4) = a0
type IxValue (a0, a1, a2, a3, a4, a5)
ix :: Int -> AffineTraversal' (a, a, a, a, a, a) a
Instance details

Defined in Optics.At.Core

type IxValue (a0, a1, a2, a3, a4, a5) = a0
type IxValue (a0, a1, a2, a3, a4, a5, a6)
ix :: Int -> AffineTraversal' (a, a, a, a, a, a, a) a
Instance details

Defined in Optics.At.Core

type IxValue (a0, a1, a2, a3, a4, a5, a6) = a0
type IxValue (a0, a1, a2, a3, a4, a5, a6, a7)
ix :: Int -> AffineTraversal' (a, a, a, a, a, a, a, a) a
Instance details

Defined in Optics.At.Core

type IxValue (a0, a1, a2, a3, a4, a5, a6, a7) = a0
type IxValue (a0, a1, a2, a3, a4, a5, a6, a7, a8)
ix :: Int -> AffineTraversal' (a, a, a, a, a, a, a, a, a) a
Instance details

Defined in Optics.At.Core

type IxValue (a0, a1, a2, a3, a4, a5, a6, a7, a8) = a0

class Contains m where #

This class provides a simple Lens that lets you view (and modify) information about whether or not a container contains a given Index. Instances are provided for Set-like containers only.

Methods

contains :: Index m -> Lens' m Bool #

>>> IntSet.fromList [1,2,3,4] ^. contains 3
True
>>> IntSet.fromList [1,2,3,4] ^. contains 5
False
>>> IntSet.fromList [1,2,3,4] & contains 3 .~ False
fromList [1,2,4]

Instances

Instances details
Contains IntSet 
Instance details

Defined in Optics.At.Core

Ord a => Contains (Set a) 
Instance details

Defined in Optics.At.Core

Methods

contains :: Index (Set a) -> Lens' (Set a) Bool #

type family Index s #

Type family that takes a key-value container type and returns the type of keys (indices) into the container, for example Index (Map k a) ~ k. This is shared by Ixed, At and Contains.

Instances

Instances details
type Index ByteString 
Instance details

Defined in Optics.At

type Index ByteString 
Instance details

Defined in Optics.At

type Index IntSet 
Instance details

Defined in Optics.At.Core

type Index Text 
Instance details

Defined in Optics.At

type Index Text = Int
type Index Text 
Instance details

Defined in Optics.At

type Index [a] 
Instance details

Defined in Optics.At.Core

type Index [a] = Int
type Index (Maybe a) 
Instance details

Defined in Optics.At.Core

type Index (Maybe a) = ()
type Index (Complex a) 
Instance details

Defined in Optics.At.Core

type Index (Complex a) = Int
type Index (Identity a) 
Instance details

Defined in Optics.At.Core

type Index (Identity a) = ()
type Index (NonEmpty a) 
Instance details

Defined in Optics.At.Core

type Index (NonEmpty a) = Int
type Index (IntMap a) 
Instance details

Defined in Optics.At.Core

type Index (IntMap a) = Int
type Index (Tree a) 
Instance details

Defined in Optics.At.Core

type Index (Tree a) = [Int]
type Index (Seq a) 
Instance details

Defined in Optics.At.Core

type Index (Seq a) = Int
type Index (Set a) 
Instance details

Defined in Optics.At.Core

type Index (Set a) = a
type Index (Vector a) 
Instance details

Defined in Optics.At

type Index (Vector a) = Int
type Index (Vector a) 
Instance details

Defined in Optics.At

type Index (Vector a) = Int
type Index (Vector a) 
Instance details

Defined in Optics.At

type Index (Vector a) = Int
type Index (HashSet a) 
Instance details

Defined in Optics.At

type Index (HashSet a) = a
type Index (Vector a) 
Instance details

Defined in Optics.At

type Index (Vector a) = Int
type Index (e -> a) 
Instance details

Defined in Optics.At.Core

type Index (e -> a) = e
type Index (a, b) 
Instance details

Defined in Optics.At.Core

type Index (a, b) = Int
type Index (UArray i e) 
Instance details

Defined in Optics.At.Core

type Index (UArray i e) = i
type Index (Array i e) 
Instance details

Defined in Optics.At.Core

type Index (Array i e) = i
type Index (Map k a) 
Instance details

Defined in Optics.At.Core

type Index (Map k a) = k
type Index (HashMap k a) 
Instance details

Defined in Optics.At

type Index (HashMap k a) = k
type Index (a, b, c) 
Instance details

Defined in Optics.At.Core

type Index (a, b, c) = Int
type Index (a, b, c, d) 
Instance details

Defined in Optics.At.Core

type Index (a, b, c, d) = Int
type Index (a, b, c, d, e) 
Instance details

Defined in Optics.At.Core

type Index (a, b, c, d, e) = Int
type Index (a, b, c, d, e, f) 
Instance details

Defined in Optics.At.Core

type Index (a, b, c, d, e, f) = Int
type Index (a, b, c, d, e, f, g) 
Instance details

Defined in Optics.At.Core

type Index (a, b, c, d, e, f, g) = Int
type Index (a, b, c, d, e, f, g, h) 
Instance details

Defined in Optics.At.Core

type Index (a, b, c, d, e, f, g, h) = Int
type Index (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Optics.At.Core

type Index (a, b, c, d, e, f, g, h, i) = Int

ixAt :: At m => Index m -> AffineTraversal' m (IxValue m) #

A definition of ix for types with an At instance. This is the default if you don't specify a definition for ix.

at' :: At m => Index m -> Lens' m (Maybe (IxValue m)) #

Version of at strict in the value inside the Just constructor.

Example:

>>> (at () .~ Just (error "oops") $ Nothing) `seq` ()
()
>>> (at' () .~ Just (error "oops") $ Nothing) `seq` ()
*** Exception: oops
...
>>> view (at ()) (Just $ error "oops") `seq` ()
()
>>> view (at' ()) (Just $ error "oops") `seq` ()
*** Exception: oops
...

It also works as expected for other data structures:

>>> (at 1 .~ Just (error "oops") $ Map.empty) `seq` ()
()
>>> (at' 1 .~ Just (error "oops") $ Map.empty) `seq` ()
*** Exception: oops
...

sans :: At m => Index m -> m -> m #

Delete the value associated with a key in a Map-like container

sans k = at k .~ Nothing

type TraversalVL' s a = TraversalVL s s a a #

Type synonym for a type-preserving van Laarhoven traversal.

type TraversalVL s t a b = forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t #

Type synonym for a type-modifying van Laarhoven traversal.

type Traversal' s a = Optic' A_Traversal NoIx s a #

Type synonym for a type-preserving traversal.

type Traversal s t a b = Optic A_Traversal NoIx s t a b #

Type synonym for a type-modifying traversal.

traversalVL :: TraversalVL s t a b -> Traversal s t a b #

Build a traversal from the van Laarhoven representation.

traversalVL . traverseOfid
traverseOf . traversalVLid

traverseOf :: forall k f (is :: IxList) s t a b. (Is k A_Traversal, Applicative f) => Optic k is s t a b -> (a -> f b) -> s -> f t #

Map each element of a structure targeted by a Traversal, evaluate these actions from left to right, and collect the results.

forOf :: forall k f (is :: IxList) s t a b. (Is k A_Traversal, Applicative f) => Optic k is s t a b -> s -> (a -> f b) -> f t #

A version of traverseOf with the arguments flipped.

sequenceOf :: forall k f (is :: IxList) s t b. (Is k A_Traversal, Applicative f) => Optic k is s t (f b) b -> s -> f t #

Evaluate each action in the structure from left to right, and collect the results.

>>> sequenceOf each ([1,2],[3,4])
[(1,3),(1,4),(2,3),(2,4)]
sequencesequenceOf traversedtraverse id
sequenceOf o ≡ traverseOf o id

transposeOf :: forall k (is :: IxList) s t a. Is k A_Traversal => Optic k is s t [a] a -> s -> [t] #

This generalizes transpose to an arbitrary Traversal.

Note: transpose handles ragged inputs more intelligently, but for non-ragged inputs:

>>> transposeOf traversed [[1,2,3],[4,5,6]]
[[1,4],[2,5],[3,6]]
transposetransposeOf traverse

mapAccumLOf :: forall k (is :: IxList) s t a b acc. Is k A_Traversal => Optic k is s t a b -> (acc -> a -> (b, acc)) -> acc -> s -> (t, acc) #

This generalizes mapAccumL to an arbitrary Traversal.

mapAccumLmapAccumLOf traverse

mapAccumLOf accumulates State from left to right.

mapAccumROf :: forall k (is :: IxList) s t a b acc. Is k A_Traversal => Optic k is s t a b -> (acc -> a -> (b, acc)) -> acc -> s -> (t, acc) #

This generalizes mapAccumR to an arbitrary Traversal.

mapAccumRmapAccumROf traversed

mapAccumROf accumulates State from right to left.

scanl1Of :: forall k (is :: IxList) s t a. Is k A_Traversal => Optic k is s t a a -> (a -> a -> a) -> s -> t #

This permits the use of scanl1 over an arbitrary Traversal.

scanl1scanl1Of traversed

scanr1Of :: forall k (is :: IxList) s t a. Is k A_Traversal => Optic k is s t a a -> (a -> a -> a) -> s -> t #

This permits the use of scanr1 over an arbitrary Traversal.

scanr1scanr1Of traversed

rewriteMOf :: forall k m (is :: IxList) a b. (Is k A_Traversal, Monad m) => Optic k is a b a b -> (b -> m (Maybe a)) -> a -> m b #

Rewrite by applying a monadic rule everywhere you recursing with a user-specified Traversal.

Ensures that the rule cannot be applied anywhere in the result.

Since: optics-core-0.4.1

transformMOf :: forall k m (is :: IxList) a b. (Is k A_Traversal, Monad m) => Optic k is a b a b -> (b -> m b) -> a -> m b #

Transform every element in a tree using a user supplied Traversal in a bottom-up manner with a monadic effect.

Since: optics-core-0.4.1

failover :: forall k (is :: IxList) s t a b. Is k A_Traversal => Optic k is s t a b -> (a -> b) -> s -> Maybe t #

Try to map a function over this Traversal, returning Nothing if the traversal has no targets.

>>> failover (element 3) (*2) [1,2]
Nothing
>>> failover _Left (*2) (Right 4)
Nothing
>>> failover _Right (*2) (Right 4)
Just (Right 8)

failover' :: forall k (is :: IxList) s t a b. Is k A_Traversal => Optic k is s t a b -> (a -> b) -> s -> Maybe t #

Version of failover strict in the application of f.

traversed :: Traversable t => Traversal (t a) (t b) a b #

Construct a Traversal via the Traversable class.

traverseOf traversed = traverse

both :: Bitraversable r => Traversal (r a a) (r b b) a b #

Traverse both parts of a Bitraversable container with matching types.

Note: for traversing a pair or an Either it's better to use each and chosen respectively to reduce potential for bugs due to too much polymorphism.

>>> (1,2) & both %~ (*10)
(10,20)
>>> over both length ("hello","world")
(5,5)
>>> foldOf both ("hello","world")
"helloworld"

Since: optics-core-0.4

backwards :: forall k (is :: IxList) s t a b. Is k A_Traversal => Optic k is s t a b -> Traversal s t a b #

This allows you to traverse the elements of a traversal in the opposite order.

partsOf :: forall k (is :: IxList) s t a. Is k A_Traversal => Optic k is s t a a -> Lens s t [a] [a] #

partsOf turns a Traversal into a Lens.

Note: You should really try to maintain the invariant of the number of children in the list.

>>> ('a','b','c') & partsOf each .~ ['x','y','z']
('x','y','z')

Any extras will be lost. If you do not supply enough, then the remainder will come from the original structure.

>>> ('a','b','c') & partsOf each .~ ['w','x','y','z']
('w','x','y')
>>> ('a','b','c') & partsOf each .~ ['x','y']
('x','y','c')
>>> ('b', 'a', 'd', 'c') & partsOf each %~ sort
('a','b','c','d')

So technically, this is only a Lens if you do not change the number of results it returns.

singular :: forall k (is :: IxList) s a. Is k A_Traversal => Optic' k is s a -> AffineTraversal' s a #

Convert a traversal to an AffineTraversal that visits the first element of the original traversal.

For the fold version see pre.

>>> "foo" & singular traversed .~ 'z'
"zoo"

Since: optics-core-0.3

adjoin :: forall k l (is :: IxList) s a (js :: IxList). (Is k A_Traversal, Is l A_Traversal) => Optic' k is s a -> Optic' l js s a -> Traversal' s a infixr 6 #

Combine two disjoint traversals into one.

>>> over (_1 % _Just `adjoin` _2 % _Right) not (Just True, Right False)
(Just False,Right True)

Note: if the argument traversals are not disjoint, the result will not respect the Traversal laws, because it will visit the same element multiple times. See section 7 of Understanding Idiomatic Traversals Backwards and Forwards by Bird et al. for why this is illegal.

>>> view (partsOf (each `adjoin` _1)) ('x','y')
"xyx"
>>> set (partsOf (each `adjoin` _1)) "abc" ('x','y')
('c','b')

For the Fold version see summing.

Since: optics-core-0.4

type IxTraversalVL' i s a = IxTraversalVL i s s a a #

Type synonym for a type-preserving van Laarhoven indexed traversal.

type IxTraversalVL i s t a b = forall (f :: Type -> Type). Applicative f => (i -> a -> f b) -> s -> f t #

Type synonym for a type-modifying van Laarhoven indexed traversal.

type IxTraversal' i s a = Optic' A_Traversal (WithIx i) s a #

Type synonym for a type-preserving indexed traversal.

type IxTraversal i s t a b = Optic A_Traversal (WithIx i) s t a b #

Type synonym for a type-modifying indexed traversal.

itraversalVL :: IxTraversalVL i s t a b -> IxTraversal i s t a b #

Build an indexed traversal from the van Laarhoven representation.

itraversalVL . itraverseOfid
itraverseOf . itraversalVLid

itraverseOf :: forall k f (is :: IxList) i s t a b. (Is k A_Traversal, Applicative f, HasSingleIndex is i) => Optic k is s t a b -> (i -> a -> f b) -> s -> f t #

Map each element of a structure targeted by an IxTraversal (supplying the index), evaluate these actions from left to right, and collect the results.

This yields the van Laarhoven representation of an indexed traversal.

iforOf :: forall k f (is :: IxList) i s t a b. (Is k A_Traversal, Applicative f, HasSingleIndex is i) => Optic k is s t a b -> s -> (i -> a -> f b) -> f t #

A version of itraverseOf with the arguments flipped.

imapAccumLOf :: forall k (is :: IxList) i s t a b acc. (Is k A_Traversal, HasSingleIndex is i) => Optic k is s t a b -> (i -> acc -> a -> (b, acc)) -> acc -> s -> (t, acc) #

Generalizes mapAccumL to an arbitrary IxTraversal.

imapAccumLOf accumulates state from left to right.

mapAccumLOf o ≡ imapAccumLOf o . const

imapAccumROf :: forall k (is :: IxList) i s t a b acc. (Is k A_Traversal, HasSingleIndex is i) => Optic k is s t a b -> (i -> acc -> a -> (b, acc)) -> acc -> s -> (t, acc) #

Generalizes mapAccumR to an arbitrary IxTraversal.

imapAccumROf accumulates state from right to left.

mapAccumROf o ≡ imapAccumROf o . const

iscanl1Of :: forall k (is :: IxList) i s t a. (Is k A_Traversal, HasSingleIndex is i) => Optic k is s t a a -> (i -> a -> a -> a) -> s -> t #

This permits the use of scanl1 over an arbitrary IxTraversal.

iscanr1Of :: forall k (is :: IxList) i s t a. (Is k A_Traversal, HasSingleIndex is i) => Optic k is s t a a -> (i -> a -> a -> a) -> s -> t #

This permits the use of scanr1 over an arbitrary IxTraversal.

ifailover :: forall k (is :: IxList) i s t a b. (Is k A_Traversal, HasSingleIndex is i) => Optic k is s t a b -> (i -> a -> b) -> s -> Maybe t #

Try to map a function which uses the index over this IxTraversal, returning Nothing if the IxTraversal has no targets.

ifailover' :: forall k (is :: IxList) i s t a b. (Is k A_Traversal, HasSingleIndex is i) => Optic k is s t a b -> (i -> a -> b) -> s -> Maybe t #

Version of ifailover strict in the application of the function.

itraversed :: TraversableWithIndex i f => IxTraversal i (f a) (f b) a b #

Indexed traversal via the TraversableWithIndex class.

itraverseOf itraverseditraverse
>>> iover (itraversed <%> itraversed) (,) ["ab", "cd"]
[[((0,0),'a'),((0,1),'b')],[((1,0),'c'),((1,1),'d')]]

indices :: forall k (is :: IxList) i s t a. (Is k A_Traversal, HasSingleIndex is i) => (i -> Bool) -> Optic k is s t a a -> IxTraversal i s t a a #

Filter results of an IxTraversal that don't satisfy a predicate on the indices.

>>> toListOf (itraversed %& indices even) "foobar"
"foa"

ibackwards :: forall k (is :: IxList) i s t a b. (Is k A_Traversal, HasSingleIndex is i) => Optic k is s t a b -> IxTraversal i s t a b #

This allows you to traverse the elements of an indexed traversal in the opposite order.

elementsOf :: forall k (is :: IxList) s t a. Is k A_Traversal => Optic k is s t a a -> (Int -> Bool) -> IxTraversal Int s t a a #

Traverse selected elements of a Traversal where their ordinal positions match a predicate.

elements :: Traversable f => (Int -> Bool) -> IxTraversal' Int (f a) a #

Traverse elements of a Traversable container where their ordinal positions match a predicate.

elementselementsOf traverse

elementOf :: forall k (is :: IxList) s a. Is k A_Traversal => Optic' k is s a -> Int -> IxAffineTraversal' Int s a #

Traverse the nth element of a Traversal if it exists.

element :: Traversable f => Int -> IxAffineTraversal' Int (f a) a #

Traverse the nth element of a Traversable container.

elementelementOf traversed

ipartsOf :: forall k (is :: IxList) i s t a. (Is k A_Traversal, HasSingleIndex is i) => Optic k is s t a a -> IxLens [i] s t [a] [a] #

An indexed version of partsOf that receives the entire list of indices as its indices.

isingular :: forall k (is :: IxList) i s a. (Is k A_Traversal, HasSingleIndex is i) => Optic' k is s a -> IxAffineTraversal' i s a #

Convert an indexed traversal to an IxAffineTraversal that visits the first element of the original traversal.

For the fold version see ipre.

>>> [1,2,3] & iover (isingular itraversed) (-)
[-1,2,3]

Since: optics-core-0.3

iadjoin :: forall k l (is :: IxList) i s a. (Is k A_Traversal, Is l A_Traversal, HasSingleIndex is i) => Optic' k is s a -> Optic' l is s a -> IxTraversal' i s a infixr 6 #

Combine two disjoint indexed traversals into one.

>>> iover (_1 % itraversed `iadjoin` _2 % itraversed) (+) ([0, 0, 0], (3, 5))
([0,1,2],(3,8))

Note: if the argument traversals are not disjoint, the result will not respect the IxTraversal laws, because it will visit the same element multiple times. See section 7 of Understanding Idiomatic Traversals Backwards and Forwards by Bird et al. for why this is illegal.

>>> iview (ipartsOf (each `iadjoin` each)) ("x","y")
([0,1,0,1],["x","y","x","y"])
>>> iset (ipartsOf (each `iadjoin` each)) (const ["a","b","c","d"]) ("x","y")
("c","d")

For the IxFold version see isumming.

Since: optics-core-0.4

class Each i s t a b | s -> i a, t -> i b, s b -> t, t a -> s where #

Extract each element of a (potentially monomorphic) container.

>>> over each (*10) (1,2,3)
(10,20,30)
>>> iover each (\i a -> a*10 + succ i) (1,2,3)
(11,22,33)

Minimal complete definition

Nothing

Methods

each :: IxTraversal i s t a b #

Instances

Instances details
Each Int [a] [b] a b
each :: IxTraversal Int [a] [b] a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal Int [a] [b] a b #

Each Int (NonEmpty a) (NonEmpty b) a b
each :: IxTraversal Int (NonEmpty a) (NonEmpty b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal Int (NonEmpty a) (NonEmpty b) a b #

Each Int (IntMap a) (IntMap b) a b
each :: IxTraversal Int (IntMap a) (IntMap b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal Int (IntMap a) (IntMap b) a b #

Each Int (Seq a) (Seq b) a b
each :: IxTraversal Int (Seq a) (Seq b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal Int (Seq a) (Seq b) a b #

Each () (Maybe a) (Maybe b) a b
each :: IxTraversal () (Maybe a) (Maybe b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal () (Maybe a) (Maybe b) a b #

Each () (Identity a) (Identity b) a b
each :: IxTraversal () (Identity a) (Identity b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal () (Identity a) (Identity b) a b #

(a ~ a1, b ~ b1) => Each Int (a, a1) (b, b1) a b
each :: IxTraversal Int (a, a) (b, b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal Int (a, a1) (b, b1) a b #

k ~ k' => Each k (Map k a) (Map k' b) a b
each :: IxTraversal k (Map k a) (Map k b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal k (Map k a) (Map k' b) a b #

(Ix i, i ~ j) => Each i (Array i a) (Array j b) a b
each :: Ix i => IxTraversal i (Array i a) (Array i b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal i (Array i a) (Array j b) a b #

(a ~ a1, a ~ a2, b ~ b1, b ~ b2) => Each Int (a, a1, a2) (b, b1, b2) a b
each :: IxTraversal Int (a, a, a) (b, b, b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal Int (a, a1, a2) (b, b1, b2) a b #

(a ~ a1, a ~ a2, a ~ a3, b ~ b1, b ~ b2, b ~ b3) => Each Int (a, a1, a2, a3) (b, b1, b2, b3) a b
each :: IxTraversal Int (a, a, a, a) (b, b, b, b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal Int (a, a1, a2, a3) (b, b1, b2, b3) a b #

(a ~ a1, a ~ a2, a ~ a3, a ~ a4, b ~ b1, b ~ b2, b ~ b3, b ~ b4) => Each Int (a, a1, a2, a3, a4) (b, b1, b2, b3, b4) a b
each :: IxTraversal Int (a, a, a, a, a) (b, b, b, b, b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal Int (a, a1, a2, a3, a4) (b, b1, b2, b3, b4) a b #

(a ~ a1, a ~ a2, a ~ a3, a ~ a4, a ~ a5, b ~ b1, b ~ b2, b ~ b3, b ~ b4, b ~ b5) => Each Int (a, a1, a2, a3, a4, a5) (b, b1, b2, b3, b4, b5) a b
each :: IxTraversal Int (a, a, a, a, a, a) (b, b, b, b, b, b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal Int (a, a1, a2, a3, a4, a5) (b, b1, b2, b3, b4, b5) a b #

(a ~ a1, a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, b ~ b1, b ~ b2, b ~ b3, b ~ b4, b ~ b5, b ~ b6) => Each Int (a, a1, a2, a3, a4, a5, a6) (b, b1, b2, b3, b4, b5, b6) a b
each :: IxTraversal Int (a, a, a, a, a, a, a) (b, b, b, b, b, b, b)
 a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal Int (a, a1, a2, a3, a4, a5, a6) (b, b1, b2, b3, b4, b5, b6) a b #

(a ~ a1, a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, a ~ a7, b ~ b1, b ~ b2, b ~ b3, b ~ b4, b ~ b5, b ~ b6, b ~ b7) => Each Int (a, a1, a2, a3, a4, a5, a6, a7) (b, b1, b2, b3, b4, b5, b6, b7) a b
each :: IxTraversal Int (a, a, a, a, a, a, a, a) (b, b, b, b, b, b,
 b, b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal Int (a, a1, a2, a3, a4, a5, a6, a7) (b, b1, b2, b3, b4, b5, b6, b7) a b #

(a ~ a1, a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, a ~ a7, a ~ a8, b ~ b1, b ~ b2, b ~ b3, b ~ b4, b ~ b5, b ~ b6, b ~ b7, b ~ b8) => Each Int (a, a1, a2, a3, a4, a5, a6, a7, a8) (b, b1, b2, b3, b4, b5, b6, b7, b8) a b
each :: IxTraversal Int (a, a, a, a, a, a, a, a, a) (b, b, b, b, b,
 b, b, b, b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal Int (a, a1, a2, a3, a4, a5, a6, a7, a8) (b, b1, b2, b3, b4, b5, b6, b7, b8) a b #

(a ~ a1, a ~ a2, a ~ a3, a ~ a4, a ~ a5, a ~ a6, a ~ a7, a ~ a8, a ~ a9, b ~ b1, b ~ b2, b ~ b3, b ~ b4, b ~ b5, b ~ b6, b ~ b7, b ~ b8, b ~ b9) => Each Int (a, a1, a2, a3, a4, a5, a6, a7, a8, a9) (b, b1, b2, b3, b4, b5, b6, b7, b8, b9) a b
each :: IxTraversal Int (a, a, a, a, a, a, a, a, a, a) (b, b, b, b,
 b, b, b, b, b, b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal Int (a, a1, a2, a3, a4, a5, a6, a7, a8, a9) (b, b1, b2, b3, b4, b5, b6, b7, b8, b9) a b #

Each [Int] (Tree a) (Tree b) a b
each :: IxTraversal [Int] (Tree a) (Tree b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal [Int] (Tree a) (Tree b) a b #

Each (Either () ()) (Complex a) (Complex b) a b
each :: (RealFloat a, RealFloat b) => IxTraversal (Either () ())
 (Complex a) (Complex b) a b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal (Either () ()) (Complex a) (Complex b) a b #

(a ~ a', b ~ b') => Each (Either () ()) (Either a a') (Either b b') a b
each :: IxTraversal (Either () ()) (Either a a) (Either b b) a
 b
Instance details

Defined in Optics.Each.Core

Methods

each :: IxTraversal (Either () ()) (Either a a') (Either b b') a b #

class Generic a => GenericLabelOptics a #

If the explicit-generic-labels Cabal flag is enabled, only types with this instance (which can be trivially derived with DeriveAnyClass extension) will be able to use labels as generic optics with a specific type.

It's an option for application developers to disable implicit fallback to generic optics for more control.

Libraries using generic labels with their data types should derive this instance for compatibility with the explicit-generic-labels flag.

Note: the flag explicit-generic-labels is disabled by default. Enabling it is generally unsupported as it might lead to compilation errors of dependencies relying on implicit fallback to generic optics.

Since: optics-core-0.4

Associated Types

type HasGenericLabelOptics a :: Bool #

type family HasGenericLabelOptics a :: Bool #

type LabelOptic' (name :: Symbol) k s a = LabelOptic name k s s a a #

Type synonym for a type-preserving optic as overloaded label.

class LabelOptic (name :: Symbol) k s t a b | name s -> k a, name t -> k b, name s b -> t, name t a -> s where #

Support for overloaded labels as optics.

An overloaded label #foo can be used as an optic if there is an instance LabelOptic "foo" k s t a b.

Alternatively, if both s and t have a Generic (GenericLabelOptics if explicit-generic-labels flag is enabled) instance, a total field of s is accessible by a label #field of kind A_Lens, whereas its constructor by a label #_Constructor of kind A_Prism.

Methods

labelOptic :: Optic k NoIx s t a b #

Used to interpret overloaded label syntax. An overloaded label #foo corresponds to labelOptic @"foo".

Instances

Instances details
GenericLabelOpticContext repDefined name k s t a b => LabelOptic name k s t a b

If no instance matches, try to use Generic machinery for field access.

For more information have a look at gfield and gconstructor.

Since: optics-core-0.4

Instance details

Defined in Optics.Label

Methods

labelOptic :: Optic k NoIx s t a b #

(k ~ An_Iso, a ~ Void0, b ~ Void0) => LabelOptic name k Void0 Void0 a b

If for an overloaded label #label there is no instance starting with LabelOptic "label" in scope, using it in the context of optics makes GHC immediately pick the overlappable instance defined below (since no other instance could match). If at this point GHC has no information about s or t, it ends up picking incoherent instance of GenericLabelOptic defined below. Prevent that (if only to be able to inspect most polymorphic types of bar or view #foo in GHCi) by defining a dummy instance that matches all names, thus postponing instance resolution until s or t is known.

Instance details

Defined in Optics.Label

Methods

labelOptic :: Optic k NoIx Void0 Void0 a b #

class IxOptic k s t a b where #

Class for optic kinds that can have indices.

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic k is s t a b -> Optic k NoIx s t a b #

Convert an indexed optic to its unindexed equivalent.

Instances

Instances details
(s ~ t, a ~ b) => IxOptic A_Fold s t a b 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic A_Fold is s t a b -> Optic A_Fold NoIx s t a b #

(s ~ t, a ~ b) => IxOptic An_AffineFold s t a b 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic An_AffineFold is s t a b -> Optic An_AffineFold NoIx s t a b #

(s ~ t, a ~ b) => IxOptic A_Getter s t a b 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic A_Getter is s t a b -> Optic A_Getter NoIx s t a b #

IxOptic A_Setter s t a b 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic A_Setter is s t a b -> Optic A_Setter NoIx s t a b #

IxOptic A_Traversal s t a b 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic A_Traversal is s t a b -> Optic A_Traversal NoIx s t a b #

IxOptic An_AffineTraversal s t a b 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic An_AffineTraversal is s t a b -> Optic An_AffineTraversal NoIx s t a b #

IxOptic A_Lens s t a b 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: forall (is :: IxList). NonEmptyIndices is => Optic A_Lens is s t a b -> Optic A_Lens NoIx s t a b #

(<%>) :: forall k l m s t a b (is :: IxList) i (js :: IxList) j u v. (JoinKinds k l m, IxOptic m s t a b, HasSingleIndex is i, HasSingleIndex js j) => Optic k is s t u v -> Optic l js u v a b -> Optic m (WithIx (i, j)) s t a b infixl 9 #

Compose two indexed optics. Their indices are composed as a pair.

>>> itoListOf (ifolded <%> ifolded) ["foo", "bar"]
[((0,0),'f'),((0,1),'o'),((0,2),'o'),((1,0),'b'),((1,1),'a'),((1,2),'r')]

(%>) :: forall k l m s t u v (is :: IxList) (js :: IxList) a b. (JoinKinds k l m, IxOptic k s t u v, NonEmptyIndices is) => Optic k is s t u v -> Optic l js u v a b -> Optic m js s t a b infixl 9 #

Compose two indexed optics and drop indices of the left one. (If you want to compose a non-indexed and an indexed optic, you can just use (%).)

>>> itoListOf (ifolded %> ifolded) ["foo", "bar"]
[(0,'f'),(1,'o'),(2,'o'),(0,'b'),(1,'a'),(2,'r')]

(<%) :: forall k l m u v a b (js :: IxList) (is :: IxList) s t. (JoinKinds k l m, IxOptic l u v a b, NonEmptyIndices js) => Optic k is s t u v -> Optic l js u v a b -> Optic m is s t a b infixl 9 #

Compose two indexed optics and drop indices of the right one. (If you want to compose an indexed and a non-indexed optic, you can just use (%).)

>>> itoListOf (ifolded <% ifolded) ["foo", "bar"]
[(0,'f'),(0,'o'),(0,'o'),(1,'b'),(1,'a'),(1,'r')]

reindexed :: forall (is :: IxList) i j k s t a b. HasSingleIndex is i => (i -> j) -> Optic k is s t a b -> Optic k (WithIx j) s t a b #

Remap the index.

>>> itoListOf (reindexed succ ifolded) "foo"
[(1,'f'),(2,'o'),(3,'o')]
>>> itoListOf (ifolded %& reindexed succ) "foo"
[(1,'f'),(2,'o'),(3,'o')]

icompose :: (i -> j -> ix) -> Optic k '[i, j] s t a b -> Optic k (WithIx ix) s t a b #

Flatten indices obtained from two indexed optics.

>>> itoListOf (ifolded % ifolded %& icompose (,)) ["foo","bar"]
[((0,0),'f'),((0,1),'o'),((0,2),'o'),((1,0),'b'),((1,1),'a'),((1,2),'r')]

icompose3 :: (i1 -> i2 -> i3 -> ix) -> Optic k '[i1, i2, i3] s t a b -> Optic k (WithIx ix) s t a b #

Flatten indices obtained from three indexed optics.

>>> itoListOf (ifolded % ifolded % ifolded %& icompose3 (,,)) [["foo","bar"],["xyz"]]
[((0,0,0),'f'),((0,0,1),'o'),((0,0,2),'o'),((0,1,0),'b'),((0,1,1),'a'),((0,1,2),'r'),((1,0,0),'x'),((1,0,1),'y'),((1,0,2),'z')]

icompose4 :: (i1 -> i2 -> i3 -> i4 -> ix) -> Optic k '[i1, i2, i3, i4] s t a b -> Optic k (WithIx ix) s t a b #

Flatten indices obtained from four indexed optics.

icompose5 :: (i1 -> i2 -> i3 -> i4 -> i5 -> ix) -> Optic k '[i1, i2, i3, i4, i5] s t a b -> Optic k (WithIx ix) s t a b #

Flatten indices obtained from five indexed optics.

icomposeN :: forall k i (is :: IxList) s t a b. (CurryCompose is, NonEmptyIndices is) => Curry is i -> Optic k is s t a b -> Optic k (WithIx i) s t a b #

Flatten indices obtained from arbitrary number of indexed optics.

class GPlate a s where #

Traverse occurrences of a type a within a type s using its Generic instance.

>>> toListOf (gplate @Char) ('h', ((), 'e', Just 'l'), "lo")
"hello"

If a occurs recursively in its own definition, only outermost occurrences of a within s will be traversed:

>>> toListOf (gplate @String) ("one","two")
["one","two"]

Note: types without a Generic instance in scope when GPlate class constraint is resolved will not be entered during the traversal.

>>> let noG = (NoG 'n', (Just 'i', "c"), 'e')
>>> toListOf (gplate @Char) noG
"ice"
>>> deriving instance Generic NoG
>>> toListOf (gplate @Char) noG
"nice"

Since: optics-core-0.4

Methods

gplate :: Traversal' s a #

Instances

Instances details
GPlateContext a s => GPlate a s 
Instance details

Defined in Optics.Generic

Methods

gplate :: Traversal' s a #

GPlate a Void0

Hidden instance.

Instance details

Defined in Optics.Generic

Methods

gplate :: Traversal' Void0 a #

GPlate Void0 a

Hidden instance.

Instance details

Defined in Optics.Generic

Methods

gplate :: Traversal' a Void0 #

class GConstructor (name :: Symbol) s t a b | name s -> t a b, name t -> s a b where #

Focus on a constructor name of a type s using its Generic instance.

>>> :{
data Animal = Dog { name :: String, age :: Int }
            | Cat { name :: String, purrs :: Bool }
  deriving (Show, Generic)
:}
>>> let dog = Dog "Sparky" 2
>>> let cat = Cat "Cuddly" True
>>> dog ^? gconstructor @"Dog"
Just ("Sparky",2)
>>> dog ^? gconstructor @"Cat"
Nothing
>>> cat & gconstructor @"Cat" % _2 %~ not
Cat {name = "Cuddly", purrs = False}
>>> dog & gconstructor @"Cat" % _1 .~ "Merry"
Dog {name = "Sparky", age = 2}
>>> cat ^? gconstructor @"Parrot"
...
...Type ‘Animal’ doesn't have a constructor named ‘Parrot’
...In the...
...

Types without a Generic instance are not supported:

>>> NoG 'x' ^. gconstructor @"NoG"
...
...Type ‘NoG’ doesn't have a Generic instance
...In the...
...

Note: gconstructor is supported by labelOptic and can be used with a concise syntax via OverloadedLabels.

>>> dog ^? #_Dog
Just ("Sparky",2)
>>> cat & #_Cat % _1 .~ "Merry"
Cat {name = "Merry", purrs = True}

Since: optics-core-0.4

Methods

gconstructor :: Prism s t a b #

Instances

Instances details
GConstructorContext repDefined name s t a b => GConstructor name s t a b 
Instance details

Defined in Optics.Generic

Methods

gconstructor :: Prism s t a b #

(a ~ Void0, b ~ Void0) => GConstructor name Void0 Void0 a b

Hidden instance.

Instance details

Defined in Optics.Generic

Methods

gconstructor :: Prism Void0 Void0 a b #

class GPosition (n :: Nat) s t a b | n s -> t a b, n t -> s a b where #

Focus on a field at position n of type a within a type s using its Generic instance.

>>> ('a', 'b', 'c') ^. gposition @2
'b'
>>> ('a', 'b') & gposition @1 .~ "hi" & gposition @2 .~ "there"
("hi","there")
>>> ('a', 'b', 'c') ^. gposition @4
...
...Data constructor ‘(,,)’ has 3 fields, 4th requested
...In the...
...
>>> () ^. gposition @1
...
...Data constructor ‘()’ has no fields, 1st requested
...In the...
...

Types without a Generic instance are not supported:

>>> NoG 'x' ^. gposition @1
...
...Type ‘NoG’ doesn't have a Generic instance
...In the...
...

Note: Positions start from 1:

>>> ('a', 'b') ^. gposition @0
...
...There is no 0th position
...In the...
...

Since: optics-core-0.4

Methods

gposition :: Lens s t a b #

Instances

Instances details
GPositionContext repDefined n s t a b => GPosition n s t a b 
Instance details

Defined in Optics.Generic

Methods

gposition :: Lens s t a b #

(a ~ Void0, b ~ Void0) => GPosition name Void0 Void0 a b

Hidden instance.

Instance details

Defined in Optics.Generic

Methods

gposition :: Lens Void0 Void0 a b #

class GAffineField (name :: Symbol) s t a b | name s -> t a b, name t -> s a b where #

Focus on a possibly partial field name of type a within a type s using its Generic instance.

>>> :{
data Fish = Herring { name :: String }
          | Tuna    { name :: String, sleeping :: Bool }
  deriving Generic
:}
>>> let herring = Herring { name = "Henry" }
>>> let tuna    = Tuna { name = "Tony", sleeping = True }
>>> herring ^? gafield @"name"
Just "Henry"
>>> herring ^? gafield @"sleeping"
Nothing
>>> tuna ^? gafield @"sleeping"
Just True

Types without a Generic instance are not supported:

>>> NoG 'x' ^? gafield @"any"
...
...Type ‘NoG’ doesn't have a Generic instance
...In the...
...

Note: trying to access a field that doesn't exist in any data constructor results in an error:

>>> tuna ^? gafield @"salary"
...
...Type ‘Fish’ doesn't have a field named ‘salary’
...In the...
...

Since: optics-core-0.4

Methods

gafield :: AffineTraversal s t a b #

Instances

Instances details
GAFieldContext repDefined name s t a b => GAffineField name s t a b 
Instance details

Defined in Optics.Generic

Methods

gafield :: AffineTraversal s t a b #

(a ~ Void0, b ~ Void0) => GAffineField name Void0 Void0 a b

Hidden instance.

Instance details

Defined in Optics.Generic

Methods

gafield :: AffineTraversal Void0 Void0 a b #

class GField (name :: Symbol) s t a b | name s -> t a b, name t -> s a b where #

Focus on a field name of type a within a type s using its Generic instance.

>>> :{
data User a
  = User { name :: String
         , age  :: a
         }
  | LazyUser { name :: String
             , age  :: a
             , lazy :: Bool
             }
  deriving (Show, Generic)
:}
>>> let user = User "Tom" 32 :: User Int
>>> user ^. gfield @"name"
"Tom"
>>> user ^. gfield @"age"
32
>>> user ^. gfield @"salary"
...
...Data constructor ‘User’ doesn't have a field named ‘salary’
...In the...
...

Only total fields are accessible (for partial ones see gafield):

>>> user ^. gfield @"lazy"
...
...Data constructor ‘User’ doesn't have a field named ‘lazy’
...In the...
...

Type changing updates are supported:

>>> user & gfield @"age" .~ ()
User {name = "Tom", age = ()}

Types without a Generic instance are not supported:

>>> NoG 'x' ^. gfield @"any"
...
...Type ‘NoG’ doesn't have a Generic instance
...In the...
...

Note: gfield is supported by labelOptic and can be used with a concise syntax via OverloadedLabels.

>>> user ^. #name
"Tom"
>>> user & #age %~ (+1)
User {name = "Tom", age = 33}

Since: optics-core-0.4

Methods

gfield :: Lens s t a b #

Instances

Instances details
GFieldContext name s t a b => GField name s t a b 
Instance details

Defined in Optics.Generic

Methods

gfield :: Lens s t a b #

(a ~ Void0, b ~ Void0) => GField name Void0 Void0 a b

Hidden instance.

Instance details

Defined in Optics.Generic

Methods

gfield :: Lens Void0 Void0 a b #

class Field9 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 9th field of a tuple.

Minimal complete definition

Nothing

Methods

_9 :: Lens s t a b #

Access the 9th field of a tuple.

Instances

Instances details
Field9 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h, i') i i' 
Instance details

Defined in Data.Tuple.Optics

Methods

_9 :: Lens (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h, i') i i' #

class Field8 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provide access to the 8th field of a tuple.

Minimal complete definition

Nothing

Methods

_8 :: Lens s t a b #

Access the 8th field of a tuple.

Instances

Instances details
Field8 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g, h') h h' 
Instance details

Defined in Data.Tuple.Optics

Methods

_8 :: Lens (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g, h') h h' #

Field8 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h', i) h h' 
Instance details

Defined in Data.Tuple.Optics

Methods

_8 :: Lens (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h', i) h h' #

class Field7 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provide access to the 7th field of a tuple.

Minimal complete definition

Nothing

Methods

_7 :: Lens s t a b #

Access the 7th field of a tuple.

Instances

Instances details
Field7 (a, b, c, d, e, f, g) (a, b, c, d, e, f, g') g g' 
Instance details

Defined in Data.Tuple.Optics

Methods

_7 :: Lens (a, b, c, d, e, f, g) (a, b, c, d, e, f, g') g g' #

Field7 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g', h) g g' 
Instance details

Defined in Data.Tuple.Optics

Methods

_7 :: Lens (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g', h) g g' #

Field7 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g', h, i) g g' 
Instance details

Defined in Data.Tuple.Optics

Methods

_7 :: Lens (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g', h, i) g g' #

class Field6 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 6th element of a tuple.

Minimal complete definition

Nothing

Methods

_6 :: Lens s t a b #

Access the 6th field of a tuple.

Instances

Instances details
Field6 (a, b, c, d, e, f) (a, b, c, d, e, f') f f' 
Instance details

Defined in Data.Tuple.Optics

Methods

_6 :: Lens (a, b, c, d, e, f) (a, b, c, d, e, f') f f' #

Field6 (a, b, c, d, e, f, g) (a, b, c, d, e, f', g) f f' 
Instance details

Defined in Data.Tuple.Optics

Methods

_6 :: Lens (a, b, c, d, e, f, g) (a, b, c, d, e, f', g) f f' #

Field6 (a, b, c, d, e, f, g, h) (a, b, c, d, e, f', g, h) f f' 
Instance details

Defined in Data.Tuple.Optics

Methods

_6 :: Lens (a, b, c, d, e, f, g, h) (a, b, c, d, e, f', g, h) f f' #

Field6 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f', g, h, i) f f' 
Instance details

Defined in Data.Tuple.Optics

Methods

_6 :: Lens (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f', g, h, i) f f' #

class Field5 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 5th field of a tuple.

Minimal complete definition

Nothing

Methods

_5 :: Lens s t a b #

Access the 5th field of a tuple.

Instances

Instances details
Field5 (a, b, c, d, e) (a, b, c, d, e') e e' 
Instance details

Defined in Data.Tuple.Optics

Methods

_5 :: Lens (a, b, c, d, e) (a, b, c, d, e') e e' #

Field5 (a, b, c, d, e, f) (a, b, c, d, e', f) e e' 
Instance details

Defined in Data.Tuple.Optics

Methods

_5 :: Lens (a, b, c, d, e, f) (a, b, c, d, e', f) e e' #

Field5 (a, b, c, d, e, f, g) (a, b, c, d, e', f, g) e e' 
Instance details

Defined in Data.Tuple.Optics

Methods

_5 :: Lens (a, b, c, d, e, f, g) (a, b, c, d, e', f, g) e e' #

Field5 (a, b, c, d, e, f, g, h) (a, b, c, d, e', f, g, h) e e' 
Instance details

Defined in Data.Tuple.Optics

Methods

_5 :: Lens (a, b, c, d, e, f, g, h) (a, b, c, d, e', f, g, h) e e' #

Field5 (a, b, c, d, e, f, g, h, i) (a, b, c, d, e', f, g, h, i) e e' 
Instance details

Defined in Data.Tuple.Optics

Methods

_5 :: Lens (a, b, c, d, e, f, g, h, i) (a, b, c, d, e', f, g, h, i) e e' #

class Field4 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provide access to the 4th field of a tuple.

Minimal complete definition

Nothing

Methods

_4 :: Lens s t a b #

Access the 4th field of a tuple.

Instances

Instances details
Field4 (a, b, c, d) (a, b, c, d') d d' 
Instance details

Defined in Data.Tuple.Optics

Methods

_4 :: Lens (a, b, c, d) (a, b, c, d') d d' #

Field4 (a, b, c, d, e) (a, b, c, d', e) d d' 
Instance details

Defined in Data.Tuple.Optics

Methods

_4 :: Lens (a, b, c, d, e) (a, b, c, d', e) d d' #

Field4 (a, b, c, d, e, f) (a, b, c, d', e, f) d d' 
Instance details

Defined in Data.Tuple.Optics

Methods

_4 :: Lens (a, b, c, d, e, f) (a, b, c, d', e, f) d d' #

Field4 (a, b, c, d, e, f, g) (a, b, c, d', e, f, g) d d' 
Instance details

Defined in Data.Tuple.Optics

Methods

_4 :: Lens (a, b, c, d, e, f, g) (a, b, c, d', e, f, g) d d' #

Field4 (a, b, c, d, e, f, g, h) (a, b, c, d', e, f, g, h) d d' 
Instance details

Defined in Data.Tuple.Optics

Methods

_4 :: Lens (a, b, c, d, e, f, g, h) (a, b, c, d', e, f, g, h) d d' #

Field4 (a, b, c, d, e, f, g, h, i) (a, b, c, d', e, f, g, h, i) d d' 
Instance details

Defined in Data.Tuple.Optics

Methods

_4 :: Lens (a, b, c, d, e, f, g, h, i) (a, b, c, d', e, f, g, h, i) d d' #

class Field3 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 3rd field of a tuple.

Minimal complete definition

Nothing

Methods

_3 :: Lens s t a b #

Access the 3rd field of a tuple.

Instances

Instances details
Field3 (a, b, c) (a, b, c') c c' 
Instance details

Defined in Data.Tuple.Optics

Methods

_3 :: Lens (a, b, c) (a, b, c') c c' #

Field3 (a, b, c, d) (a, b, c', d) c c' 
Instance details

Defined in Data.Tuple.Optics

Methods

_3 :: Lens (a, b, c, d) (a, b, c', d) c c' #

Field3 (a, b, c, d, e) (a, b, c', d, e) c c' 
Instance details

Defined in Data.Tuple.Optics

Methods

_3 :: Lens (a, b, c, d, e) (a, b, c', d, e) c c' #

Field3 (a, b, c, d, e, f) (a, b, c', d, e, f) c c' 
Instance details

Defined in Data.Tuple.Optics

Methods

_3 :: Lens (a, b, c, d, e, f) (a, b, c', d, e, f) c c' #

Field3 (a, b, c, d, e, f, g) (a, b, c', d, e, f, g) c c' 
Instance details

Defined in Data.Tuple.Optics

Methods

_3 :: Lens (a, b, c, d, e, f, g) (a, b, c', d, e, f, g) c c' #

Field3 (a, b, c, d, e, f, g, h) (a, b, c', d, e, f, g, h) c c' 
Instance details

Defined in Data.Tuple.Optics

Methods

_3 :: Lens (a, b, c, d, e, f, g, h) (a, b, c', d, e, f, g, h) c c' #

Field3 (a, b, c, d, e, f, g, h, i) (a, b, c', d, e, f, g, h, i) c c' 
Instance details

Defined in Data.Tuple.Optics

Methods

_3 :: Lens (a, b, c, d, e, f, g, h, i) (a, b, c', d, e, f, g, h, i) c c' #

class Field2 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to the 2nd field of a tuple.

Minimal complete definition

Nothing

Methods

_2 :: 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)
>>> traverseOf _2 print (1,2)
2
(1,())

Instances

Instances details
Field2 (a, b) (a, b') b b' 
Instance details

Defined in Data.Tuple.Optics

Methods

_2 :: Lens (a, b) (a, b') b b' #

Field2 (a, b, c) (a, b', c) b b' 
Instance details

Defined in Data.Tuple.Optics

Methods

_2 :: Lens (a, b, c) (a, b', c) b b' #

Field2 (a, b, c, d) (a, b', c, d) b b' 
Instance details

Defined in Data.Tuple.Optics

Methods

_2 :: Lens (a, b, c, d) (a, b', c, d) b b' #

Field2 ((f :*: g) p) ((f :*: g') p) (g p) (g' p) 
Instance details

Defined in Data.Tuple.Optics

Methods

_2 :: Lens ((f :*: g) p) ((f :*: g') p) (g p) (g' p) #

Field2 (Product f g a) (Product f g' a) (g a) (g' a) 
Instance details

Defined in Data.Tuple.Optics

Methods

_2 :: Lens (Product f g a) (Product f g' a) (g a) (g' a) #

Field2 (a, b, c, d, e) (a, b', c, d, e) b b' 
Instance details

Defined in Data.Tuple.Optics

Methods

_2 :: Lens (a, b, c, d, e) (a, b', c, d, e) b b' #

Field2 (a, b, c, d, e, f) (a, b', c, d, e, f) b b' 
Instance details

Defined in Data.Tuple.Optics

Methods

_2 :: Lens (a, b, c, d, e, f) (a, b', c, d, e, f) b b' #

Field2 (a, b, c, d, e, f, g) (a, b', c, d, e, f, g) b b' 
Instance details

Defined in Data.Tuple.Optics

Methods

_2 :: Lens (a, b, c, d, e, f, g) (a, b', c, d, e, f, g) b b' #

Field2 (a, b, c, d, e, f, g, h) (a, b', c, d, e, f, g, h) b b' 
Instance details

Defined in Data.Tuple.Optics

Methods

_2 :: Lens (a, b, c, d, e, f, g, h) (a, b', c, d, e, f, g, h) b b' #

Field2 (a, b, c, d, e, f, g, h, i) (a, b', c, d, e, f, g, h, i) b b' 
Instance details

Defined in Data.Tuple.Optics

Methods

_2 :: Lens (a, b, c, d, e, f, g, h, i) (a, b', c, d, e, f, g, h, i) b b' #

class Field1 s t a b | s -> a, t -> b, s b -> t, t a -> s where #

Provides access to 1st field of a tuple.

Minimal complete definition

Nothing

Methods

_1 :: Lens s t a b #

Access the 1st field of a tuple (and possibly change its type).

>>> (1,2) ^. _1
1
>>> (1,2) & _1 .~ "hello"
("hello",2)
>>> traverseOf _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)

Instances

Instances details
Field1 (Identity a) (Identity b) a b 
Instance details

Defined in Data.Tuple.Optics

Methods

_1 :: Lens (Identity a) (Identity b) a b #

Field1 (a, b) (a', b) a a' 
Instance details

Defined in Data.Tuple.Optics

Methods

_1 :: Lens (a, b) (a', b) a a' #

Field1 (a, b, c) (a', b, c) a a' 
Instance details

Defined in Data.Tuple.Optics

Methods

_1 :: Lens (a, b, c) (a', b, c) a a' #

Field1 (a, b, c, d) (a', b, c, d) a a' 
Instance details

Defined in Data.Tuple.Optics

Methods

_1 :: Lens (a, b, c, d) (a', b, c, d) a a' #

Field1 ((f :*: g) p) ((f' :*: g) p) (f p) (f' p) 
Instance details

Defined in Data.Tuple.Optics

Methods

_1 :: Lens ((f :*: g) p) ((f' :*: g) p) (f p) (f' p) #

Field1 (Product f g a) (Product f' g a) (f a) (f' a) 
Instance details

Defined in Data.Tuple.Optics

Methods

_1 :: Lens (Product f g a) (Product f' g a) (f a) (f' a) #

Field1 (a, b, c, d, e) (a', b, c, d, e) a a' 
Instance details

Defined in Data.Tuple.Optics

Methods

_1 :: Lens (a, b, c, d, e) (a', b, c, d, e) a a' #

Field1 (a, b, c, d, e, f) (a', b, c, d, e, f) a a' 
Instance details

Defined in Data.Tuple.Optics

Methods

_1 :: Lens (a, b, c, d, e, f) (a', b, c, d, e, f) a a' #

Field1 (a, b, c, d, e, f, g) (a', b, c, d, e, f, g) a a' 
Instance details

Defined in Data.Tuple.Optics

Methods

_1 :: Lens (a, b, c, d, e, f, g) (a', b, c, d, e, f, g) a a' #

Field1 (a, b, c, d, e, f, g, h) (a', b, c, d, e, f, g, h) a a' 
Instance details

Defined in Data.Tuple.Optics

Methods

_1 :: Lens (a, b, c, d, e, f, g, h) (a', b, c, d, e, f, g, h) a a' #

Field1 (a, b, c, d, e, f, g, h, i) (a', b, c, d, e, f, g, h, i) a a' 
Instance details

Defined in Data.Tuple.Optics

Methods

_1 :: Lens (a, b, c, d, e, f, g, h, i) (a', b, c, d, e, f, g, h, i) a a' #

_1' :: Field1 s t a b => Lens s t a b #

Strict version of _1

_2' :: Field2 s t a b => Lens s t a b #

Strict version of _2

_3' :: Field3 s t a b => Lens s t a b #

Strict version of _3

_4' :: Field4 s t a b => Lens s t a b #

Strict version of _4

_5' :: Field5 s t a b => Lens s t a b #

Strict version of _5

_6' :: Field6 s t a b => Lens s t a b #

Strict version of _6

_7' :: Field7 s t a b => Lens s t a b #

Strict version of _7

_8' :: Field8 s t a b => Lens s t a b #

Strict version of _8

_9' :: Field9 s t a b => Lens s t a b #

Strict version of _9

class Snoc s t a b | s -> a, t -> b, s b -> t, t a -> s where #

This class provides a way to attach or detach elements on the right side of a structure in a flexible manner.

Methods

_Snoc :: Prism s t (s, a) (t, b) #

Instances

Instances details
Snoc [a] [b] a b 
Instance details

Defined in Optics.Cons.Core

Methods

_Snoc :: Prism [a] [b] ([a], a) ([b], b) #

Snoc (ZipList a) (ZipList b) a b 
Instance details

Defined in Optics.Cons.Core

Methods

_Snoc :: Prism (ZipList a) (ZipList b) (ZipList a, a) (ZipList b, b) #

Snoc (Seq a) (Seq b) a b 
Instance details

Defined in Optics.Cons.Core

Methods

_Snoc :: Prism (Seq a) (Seq b) (Seq a, a) (Seq b, b) #

class Cons s t a b | s -> a, t -> b, s b -> t, t a -> s where #

This class provides a way to attach or detach elements on the left side of a structure in a flexible manner.

Methods

_Cons :: Prism s t (a, s) (b, t) #

_Cons :: Prism [a] [b] (a, [a]) (b, [b])
_Cons :: Prism (Seq a) (Seq b) (a, Seq a) (b, Seq b)
_Cons :: Prism (Vector a) (Vector b) (a, Vector a) (b, Vector b)
_Cons :: Prism' String (Char, String)
_Cons :: Prism' Text (Char, Text)
_Cons :: Prism' ByteString (Word8, ByteString)

Instances

Instances details
Cons [a] [b] a b 
Instance details

Defined in Optics.Cons.Core

Methods

_Cons :: Prism [a] [b] (a, [a]) (b, [b]) #

Cons (ZipList a) (ZipList b) a b 
Instance details

Defined in Optics.Cons.Core

Methods

_Cons :: Prism (ZipList a) (ZipList b) (a, ZipList a) (b, ZipList b) #

Cons (Seq a) (Seq b) a b 
Instance details

Defined in Optics.Cons.Core

Methods

_Cons :: Prism (Seq a) (Seq b) (a, Seq a) (b, Seq b) #

pattern (:>) :: Snoc s s a a => s -> a -> s infixl 5 #

Pattern synonym for matching on the rightmost element of a structure.

>>> case ['a','b','c'] of (_ :> x) -> x
'c'

pattern (:<) :: Cons s s a a => a -> s -> s infixr 5 #

Pattern synonym for matching on the leftmost element of a structure.

>>> case ['a','b','c'] of (x :< _) -> x
'a'

(<|) :: Cons s s a a => a -> s -> s infixr 5 #

cons an element onto a container.

This is an infix alias for cons.

>>> 1 <| []
[1]
>>> 'a' <| "bc"
"abc"
>>> 1 <| []
[1]
>>> 1 <| [2, 3]
[1,2,3]

cons :: Cons s s a a => a -> s -> s infixr 5 #

cons an element onto a container.

>>> cons 'a' ""
"a"
>>> cons 'a' "bc"
"abc"

uncons :: Cons s s a a => s -> Maybe (a, s) #

Attempt to extract the left-most element from a container, and a version of the container without that element.

>>> uncons []
Nothing
>>> uncons [1, 2, 3]
Just (1,[2,3])

_head :: Cons s s a a => AffineTraversal' s a #

An AffineTraversal reading and writing to the head of a non-empty container.

>>> "abc" ^? _head
Just 'a'
>>> "abc" & _head .~ 'd'
"dbc"
>>> [1,2,3] & _head %~ (*10)
[10,2,3]
>>> [] & _head %~ absurd
[]
>>> [1,2,3] ^? _head
Just 1
>>> [] ^? _head
Nothing
>>> [1,2] ^? _head
Just 1
>>> [] & _head .~ 1
[]
>>> [0] & _head .~ 2
[2]
>>> [0,1] & _head .~ 2
[2,1]

_tail :: Cons s s a a => AffineTraversal' s s #

An AffineTraversal reading and writing to the tail of a non-empty container.

>>> "ab" & _tail .~ "cde"
"acde"
>>> [] & _tail .~ [1,2]
[]
>>> [1,2,3,4,5] & _tail % traversed %~ (*10)
[1,20,30,40,50]
>>> [1,2] & _tail .~ [3,4,5]
[1,3,4,5]
>>> [] & _tail .~ [1,2]
[]
>>> "abc" ^? _tail
Just "bc"
>>> "hello" ^? _tail
Just "ello"
>>> "" ^? _tail
Nothing

_init :: Snoc s s a a => AffineTraversal' s s #

An AffineTraversal reading and replacing all but the a last element of a non-empty container.

>>> "abcd" ^? _init
Just "abc"
>>> "" ^? _init
Nothing
>>> "ab" & _init .~ "cde"
"cdeb"
>>> [] & _init .~ [1,2]
[]
>>> [1,2,3,4] & _init % traversed %~ (*10)
[10,20,30,4]
>>> [1,2,3] ^? _init
Just [1,2]
>>> "hello" ^? _init
Just "hell"
>>> [] ^? _init
Nothing

_last :: Snoc s s a a => AffineTraversal' s a #

An AffineTraversal reading and writing to the last element of a non-empty container.

>>> "abc" ^? _last
Just 'c'
>>> "" ^? _last
Nothing
>>> [1,2,3] & _last %~ (+1)
[1,2,4]
>>> [1,2] ^? _last
Just 2
>>> [] & _last .~ 1
[]
>>> [0] & _last .~ 2
[2]
>>> [0,1] & _last .~ 2
[0,2]

(|>) :: Snoc s s a a => s -> a -> s infixl 5 #

snoc an element onto the end of a container.

This is an infix alias for snoc.

>>> "" |> 'a'
"a"
>>> "bc" |> 'a'
"bca"

snoc :: Snoc s s a a => s -> a -> s infixl 5 #

snoc an element onto the end of a container.

>>> snoc "hello" '!'
"hello!"

unsnoc :: Snoc s s a a => s -> Maybe (s, a) #

Attempt to extract the right-most element from a container, and a version of the container without that element.

>>> unsnoc "hello!"
Just ("hello",'!')
>>> unsnoc ""
Nothing

class (Is k A_Traversal, ViewableOptic k r) => PermeableOptic k r where #

Methods

passthrough :: forall (is :: IxList) s t a b. Optic k is s t a b -> (a -> (r, b)) -> s -> (ViewResult k r, t) #

Modify the target of an Optic returning extra information of type r.

Instances

Instances details
Monoid r => PermeableOptic A_Traversal r 
Instance details

Defined in Optics.Passthrough

Methods

passthrough :: forall (is :: IxList) s t a b. Optic A_Traversal is s t a b -> (a -> (r, b)) -> s -> (ViewResult A_Traversal r, t) #

PermeableOptic An_AffineTraversal r 
Instance details

Defined in Optics.Passthrough

Methods

passthrough :: forall (is :: IxList) s t a b. Optic An_AffineTraversal is s t a b -> (a -> (r, b)) -> s -> (ViewResult An_AffineTraversal r, t) #

PermeableOptic A_Prism r 
Instance details

Defined in Optics.Passthrough

Methods

passthrough :: forall (is :: IxList) s t a b. Optic A_Prism is s t a b -> (a -> (r, b)) -> s -> (ViewResult A_Prism r, t) #

PermeableOptic A_Lens r 
Instance details

Defined in Optics.Passthrough

Methods

passthrough :: forall (is :: IxList) s t a b. Optic A_Lens is s t a b -> (a -> (r, b)) -> s -> (ViewResult A_Lens r, t) #

PermeableOptic An_Iso r 
Instance details

Defined in Optics.Passthrough

Methods

passthrough :: forall (is :: IxList) s t a b. Optic An_Iso is s t a b -> (a -> (r, b)) -> s -> (ViewResult An_Iso r, t) #

gview :: (ViewableOptic k r, Member (Reader s) effs) => Optic' k is s r -> Sem effs (ViewResult k r) Source #

gviews :: (ViewableOptic k r, Member (Reader s) effs) => Optic' k is s a -> (a -> r) -> Sem effs (ViewResult k r) Source #

modifying :: (Is k A_Setter, Member (State s) effs) => Optic k is s s a b -> (a -> b) -> Sem effs () Source #

modifying' :: (Is k A_Setter, Member (State s) effs) => Optic k is s s a b -> (a -> b) -> Sem effs () Source #

assign :: (Is k A_Setter, Member (State s) effs) => Optic k is s s a b -> b -> Sem effs () Source #

assign' :: (Is k A_Setter, Member (State s) effs) => Optic k is s s a b -> b -> Sem effs () Source #

use :: (Is k A_Getter, Member (State s) effs) => Optic' k is s a -> Sem effs a Source #

preuse :: (Is k An_AffineFold, Member (State s) effs) => Optic' k is s a -> Sem effs (Maybe a) Source #

(.=) :: (Is k A_Setter, Member (State s) effs) => Optic k is s s a b -> b -> Sem effs () infix 4 Source #

(?=) :: (Is k A_Setter, Member (State s) effs) => Optic k is s s (Maybe a) (Maybe b) -> b -> Sem effs () infix 4 Source #

(%=) :: (Is k A_Setter, Member (State s) effs) => Optic k is s s a b -> (a -> b) -> Sem effs () infix 4 Source #

(%%=) :: (PermeableOptic k r, Member (State s) effs) => Optic k is s s a b -> (a -> (r, b)) -> Sem effs (ViewResult k r) infix 4 Source #

(<.=) :: (PermeableOptic k b, Member (State s) effs) => Optic k is s s a b -> b -> Sem effs (ViewResult k b) infix 4 Source #

(<?=) :: (PermeableOptic k (Maybe b), Member (State s) effs) => Optic k is s s (Maybe a) (Maybe b) -> b -> Sem effs (ViewResult k (Maybe b)) infix 4 Source #

(<%=) :: (PermeableOptic k b, Member (State s) effs) => Optic k is s s a b -> (a -> b) -> Sem effs (ViewResult k b) infix 4 Source #

(<<.=) :: (PermeableOptic k a, Member (State s) effs) => Optic k is s s a b -> b -> Sem effs (ViewResult k a) infix 4 Source #

(<<?=) :: (PermeableOptic k (Maybe a), Member (State s) effs) => Optic k is s s (Maybe a) (Maybe b) -> b -> Sem effs (ViewResult k (Maybe a)) infix 4 Source #

(<<%=) :: (PermeableOptic k a, Member (State s) effs) => Optic k is s s a b -> (a -> b) -> Sem effs (ViewResult k a) infix 4 Source #

guse :: (ViewableOptic k a, Member (State s) effs) => Optic' k is s a -> Sem effs (ViewResult k a) Source #

guses :: (ViewableOptic k r, Member (State s) effs) => Optic' k is s a -> (a -> r) -> Sem effs (ViewResult k r) Source #

zoom :: (Is k A_Lens, Member (State s) effs) => Optic' k is s a -> Sem (State a ': effs) c -> Sem effs c Source #

zoomMaybe :: (Is k An_AffineTraversal, Member (State s) effs) => Optic' k is s a -> Sem (State a ': effs) c -> Sem effs (Maybe c) Source #

glistening :: (ViewableOptic k r, Member (Writer s) effs) => Optic' k is s r -> Sem effs a -> Sem effs (a, ViewResult k r) Source #

glistenings :: (ViewableOptic k r, Member (Writer s) effs) => Optic' k is s a -> (a -> r) -> Sem effs b -> Sem effs (b, ViewResult k r) Source #